[project @ 1998-12-02 13:17:09 by simonm]
[ghc-hetmet.git] / ghc / compiler / prelude / PrimRep.lhs
1 %
2 % (c) The GRASP Project, Glasgow University, 1992-1998
3 %
4 \section[PrimRep]{Primitive machine-level kinds of things.}
5
6 At various places in the back end, we want to be to tag things with a
7 ``primitive kind''---i.e., the machine-manipulable implementation
8 types.
9
10 \begin{code}
11 module PrimRep 
12       (
13         PrimRep(..)
14       , separateByPtrFollowness
15       , isFollowableRep
16       , isFloatingRep
17       , is64BitRep
18       , getPrimRepSize
19       , getPrimRepSizeInBytes
20       , retPrimRepSize
21       , showPrimRep
22       , primRepString
23       , showPrimRepToUser
24       ) where
25
26 #include "HsVersions.h"
27
28 import Constants ( dOUBLE_SIZE, iNT64_SIZE, wORD64_SIZE )
29 import Util
30 import Outputable
31 \end{code}
32
33 %************************************************************************
34 %*                                                                      *
35 \subsection[PrimRep-datatype]{The @PrimRep@ datatype}
36 %*                                                                      *
37 %************************************************************************
38
39 \begin{code}
40 data PrimRep
41   = -- These pointer-kinds are all really the same, but we keep
42     -- them separate for documentation purposes.
43     PtrRep              -- Pointer to a closure; a ``word''.
44   | CodePtrRep          -- Pointer to code
45   | DataPtrRep          -- Pointer to data
46   | RetRep              -- Pointer to code or data (return vector or code pointer)
47   | CostCentreRep       -- Pointer to a cost centre
48
49   | CharRep             -- Machine characters
50   | IntRep              --         integers (same size as ptr on this arch)
51   | WordRep             --         ditto (but *unsigned*)
52   | AddrRep             --         addresses ("C pointers")
53   | FloatRep            --         floats
54   | DoubleRep           --         doubles
55   | Word64Rep           --    guaranteed to be 64 bits (no more, no less.)
56   | Int64Rep            --    guaranteed to be 64 bits (no more, no less.)
57
58   | WeakPtrRep
59   | ForeignObjRep       
60
61   | StablePtrRep        -- We could replace this with IntRep but maybe
62                         -- there's some documentation gain from having
63                         -- it special? [ADR]
64
65   | ThreadIdRep         -- Really a pointer to a TSO
66
67   | ArrayRep            -- Primitive array of Haskell pointers
68   | ByteArrayRep        -- Primitive array of bytes (no Haskell pointers)
69
70   | VoidRep             -- Occupies no space at all!
71                         -- (Primitive states are mapped onto this)
72   deriving (Eq, Ord)
73         -- Kinds are used in PrimTyCons, which need both Eq and Ord
74 \end{code}
75
76 These pretty much correspond to the C types declared in StgTypes.h,
77 with the following exceptions:
78
79    - when an Array or ByteArray is passed to C, we again pass a pointer
80      to the contents.  The actual type that is passed is StgPtr for
81      ArrayRep, and StgByteArray (probably a char *) for ByteArrayRep.
82
83 These hacks are left until the final printing of the C, in
84 PprAbsC.lhs.
85
86 %************************************************************************
87 %*                                                                      *
88 \subsection[PrimRep-predicates]{Follow-ness, sizes, and such---on @PrimitiveKinds@}
89 %*                                                                      *
90 %************************************************************************
91
92 Whether or not the thing is a pointer that the garbage-collector
93 should follow. Or, to put it another (less confusing) way, whether
94 the object in question is a heap object. 
95
96 Depending on the outcome, this predicate determines what stack
97 the pointer/object possibly will have to be saved onto, and the
98 computation of GC liveness info.
99
100 \begin{code}
101 isFollowableRep :: PrimRep -> Bool
102
103 isFollowableRep PtrRep        = True
104 isFollowableRep ArrayRep      = True    -- all heap objects:
105 isFollowableRep ByteArrayRep  = True    --      ''
106 isFollowableRep WeakPtrRep    = True    --      ''
107 isFollowableRep ForeignObjRep = True    --      ''
108 isFollowableRep ThreadIdRep   = True    -- pointer to a TSO
109
110 isFollowableRep other           = False
111
112 separateByPtrFollowness :: (a -> PrimRep) -> [a] -> ([a], [a])
113
114 separateByPtrFollowness kind_fun things
115   = sep_things kind_fun things [] []
116     -- accumulating params for follow-able and don't-follow things...
117   where
118     sep_things kfun []     bs us = (reverse bs, reverse us)
119     sep_things kfun (t:ts) bs us
120       = if (isFollowableRep . kfun) t then
121             sep_things kfun ts (t:bs) us
122         else
123             sep_things kfun ts bs (t:us)
124 \end{code}
125
126 @isFloatingRep@ is used to distinguish @Double@ and @Float@ which
127 cause inadvertent numeric conversions if you aren't jolly careful.
128 See codeGen/CgCon:cgTopRhsCon.
129
130 \begin{code}
131 isFloatingRep :: PrimRep -> Bool
132
133 isFloatingRep DoubleRep = True
134 isFloatingRep FloatRep  = True
135 isFloatingRep other     = False
136
137 \end{code}
138
139 \begin{code}
140 is64BitRep :: PrimRep -> Bool
141
142 is64BitRep Int64Rep  = True
143 is64BitRep Word64Rep = True
144 is64BitRep other     = False
145
146 \end{code}
147
148
149
150 \begin{code}
151 getPrimRepSize :: PrimRep -> Int
152
153 getPrimRepSize DoubleRep  = dOUBLE_SIZE -- "words", of course
154 getPrimRepSize Word64Rep  = wORD64_SIZE
155 getPrimRepSize Int64Rep   = iNT64_SIZE
156 --getPrimRepSize FloatRep = 1
157 --getPrimRepSize CharRep  = 1   -- ToDo: count in bytes?
158 --getPrimRepSize ArrayRep = 1   -- Listed specifically for *documentation*
159 --getPrimRepSize ByteArrayRep = 1
160 getPrimRepSize VoidRep    = 0
161 getPrimRepSize other      = 1
162
163 retPrimRepSize = getPrimRepSize RetRep
164
165 -- size in bytes, ToDo: cpp in the right vals.
166 -- (used in some settings to figure out how many bytes
167 -- we have to push onto the stack when calling external
168 -- entry points (e.g., stdcalling on win32))
169 getPrimRepSizeInBytes :: PrimRep -> Int
170 getPrimRepSizeInBytes pr =
171  case pr of
172     CharRep        ->    1
173     IntRep         ->    4
174     AddrRep        ->    4
175     FloatRep       ->    4
176     DoubleRep      ->    8
177     Word64Rep      ->    8
178     Int64Rep       ->    8
179     WeakPtrRep     ->    4
180     ForeignObjRep  ->    4
181     StablePtrRep   ->    4
182     ArrayRep       ->    4
183     ByteArrayRep   ->    4
184     _              ->   panic "getPrimRepSize: ouch - this wasn't supposed to happen!"
185
186 \end{code}
187
188 %************************************************************************
189 %*                                                                      *
190 \subsection[PrimRep-instances]{Boring instance decls for @PrimRep@}
191 %*                                                                      *
192 %************************************************************************
193
194 \begin{code}
195 instance Outputable PrimRep where
196     ppr kind = text (showPrimRep kind)
197
198 showPrimRep  :: PrimRep -> String
199 showPrimRepToUser :: PrimRep -> String
200
201 showPrimRep PtrRep         = "P_"       -- short for StgPtr
202
203 showPrimRep CodePtrRep     = "P_"       -- DEATH to StgFunPtr! (94/02/22 WDP)
204 showPrimRep PtrRep         = "P_"       -- short for StgPtr
205 showPrimRep CodePtrRep     = "P_"       -- DEATH to StgFunPtr! (94/02/22 WDP)
206 showPrimRep DataPtrRep     = "D_"
207 showPrimRep RetRep         = "P_"
208 showPrimRep CostCentreRep  = "CostCentre"
209 showPrimRep CharRep        = "C_"
210 showPrimRep IntRep         = "I_"       -- short for StgInt
211 showPrimRep WordRep        = "W_"       -- short for StgWord
212 showPrimRep Int64Rep       = "LI_"       -- short for StgLongInt
213 showPrimRep Word64Rep      = "LW_"       -- short for StgLongWord
214 showPrimRep AddrRep        = "StgAddr"
215 showPrimRep FloatRep       = "StgFloat"
216 showPrimRep DoubleRep      = "StgDouble"
217 showPrimRep ArrayRep       = "P_" -- see comment below
218 showPrimRep ByteArrayRep   = "StgByteArray"
219 showPrimRep StablePtrRep   = "StgStablePtr"
220 showPrimRep ThreadIdRep    = "StgTSO*"
221 showPrimRep WeakPtrRep     = "P_"
222 showPrimRep ForeignObjRep  = "StgAddr"
223 showPrimRep VoidRep        = "!!VOID_KIND!!"
224
225 primRepString CharRep           = "Char"
226 primRepString IntRep            = "Int"
227 primRepString WordRep           = "Word"
228 primRepString Int64Rep          = "Int64"
229 primRepString Word64Rep         = "Word64"
230 primRepString AddrRep           = "Addr"
231 primRepString FloatRep          = "Float"
232 primRepString DoubleRep         = "Double"
233 primRepString WeakPtrRep        = "Weak"
234 primRepString ForeignObjRep     = "ForeignObj"
235 primRepString StablePtrRep      = "StablePtr"
236 primRepString other             = pprPanic "primRepString" (ppr other)
237
238 showPrimRepToUser pr = primRepString pr
239 \end{code}
240
241 Foreign Objects and Arrays are treated specially by the code for
242 _ccall_s: we pass a pointer to the contents of the object, not the
243 object itself.