[project @ 2001-01-31 12:27:24 by sewardj]
[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, wORD_SIZE )
29 import Outputable
30 \end{code}
31
32 %************************************************************************
33 %*                                                                      *
34 \subsection[PrimRep-datatype]{The @PrimRep@ datatype}
35 %*                                                                      *
36 %************************************************************************
37
38 \begin{code}
39 data PrimRep
40   = -- These pointer-kinds are all really the same, but we keep
41     -- them separate for documentation purposes.
42     PtrRep              -- Pointer to a closure; a ``word''.
43   | CodePtrRep          -- Pointer to code
44   | DataPtrRep          -- Pointer to data
45   | RetRep              -- Pointer to code or data (return vector or code pointer)
46   | CostCentreRep       -- Pointer to a cost centre
47
48   | CharRep             -- Machine characters
49   | IntRep              --         integers (same size as ptr on this arch)
50   | WordRep             --         ditto (but *unsigned*)
51   | AddrRep             --         addresses ("C pointers")
52   | FloatRep            --         floats
53   | DoubleRep           --         doubles
54   | Word64Rep           --    guaranteed to be 64 bits (no more, no less.)
55   | Int64Rep            --    guaranteed to be 64 bits (no more, no less.)
56
57     -- These are not expected to appear in the front end.  They are
58     -- only here to help the native code generator, and should appear
59     -- nowhere else.
60   | Int8Rep             --         8  bit signed   integers
61   | Word8Rep            --         8  bit unsigned integers
62   | Int16Rep            --         16 bit signed   integers
63   | Word16Rep           --         16 bit unsigned integers
64   | Int32Rep            --         32 bit signed   integers
65   | Word32Rep           --         32 bit unsigned integers
66   
67   -- Perhaps all sized integers and words should be primitive types.
68   
69   -- Word8Rep is currently used to simulate some old CharRep usages
70   -- when Char changed size from 8 to 31 bits. It does not correspond
71   -- to a Haskell unboxed type, in particular it's not used by Word8.
72   
73   | WeakPtrRep
74   | ForeignObjRep       
75   | BCORep
76
77   | StablePtrRep        -- guaranteed to be represented by a pointer
78
79   | StableNameRep       -- A stable name is a real heap object, unpointed,
80                         -- with one field containing an index into the
81                         -- stable pointer table.  It has to be a heap
82                         -- object so the garbage collector can track these
83                         -- objects and reclaim stable pointer entries.
84
85   | ThreadIdRep         -- Really a pointer to a TSO
86
87   | ArrayRep            -- Primitive array of Haskell pointers
88   | ByteArrayRep        -- Primitive array of bytes (no Haskell pointers)
89
90   | PrimPtrRep          -- Used for MutVars and MVars; 
91                         -- a pointer to a primitive object
92                         -- ToDo: subsumes WeakPtrRep, ThreadIdRep, 
93                         -- StableNameRep, ForeignObjRep, and BCORep ?
94
95   | VoidRep             -- Occupies no space at all!
96                         -- (Primitive states are mapped onto this)
97   deriving (Eq, Ord)
98         -- Kinds are used in PrimTyCons, which need both Eq and Ord
99 \end{code}
100
101 These pretty much correspond to the C types declared in StgTypes.h,
102 with the following exceptions:
103
104    - when an Array or ByteArray is passed to C, we again pass a pointer
105      to the contents.  The actual type that is passed is StgPtr for
106      ArrayRep, and StgByteArray (probably a char *) for ByteArrayRep.
107
108 These hacks are left until the final printing of the C, in
109 PprAbsC.lhs.
110
111 %************************************************************************
112 %*                                                                      *
113 \subsection[PrimRep-predicates]{Follow-ness, sizes, and such---on @PrimitiveKinds@}
114 %*                                                                      *
115 %************************************************************************
116
117 Whether or not the thing is a pointer that the garbage-collector
118 should follow. Or, to put it another (less confusing) way, whether
119 the object in question is a heap object. 
120
121 Depending on the outcome, this predicate determines what stack
122 the pointer/object possibly will have to be saved onto, and the
123 computation of GC liveness info.
124
125 \begin{code}
126 isFollowableRep :: PrimRep -> Bool
127
128 isFollowableRep PtrRep        = True
129 isFollowableRep ArrayRep      = True    -- all heap objects:
130 isFollowableRep ByteArrayRep  = True    --      ''
131 isFollowableRep WeakPtrRep    = True    --      ''
132 isFollowableRep ForeignObjRep = True    --      ''
133 isFollowableRep StableNameRep = True    --      ''
134 isFollowableRep PrimPtrRep    = True    --      ''
135 isFollowableRep ThreadIdRep   = True    -- pointer to a TSO
136 isFollowableRep BCORep        = True
137
138 isFollowableRep other         = False
139
140 separateByPtrFollowness :: (a -> PrimRep) -> [a] -> ([a], [a])
141
142 separateByPtrFollowness kind_fun things
143   = sep_things kind_fun things [] []
144     -- accumulating params for follow-able and don't-follow things...
145   where
146     sep_things kfun []     bs us = (reverse bs, reverse us)
147     sep_things kfun (t:ts) bs us
148       = if (isFollowableRep . kfun) t then
149             sep_things kfun ts (t:bs) us
150         else
151             sep_things kfun ts bs (t:us)
152 \end{code}
153
154 @isFloatingRep@ is used to distinguish @Double@ and @Float@ which
155 cause inadvertent numeric conversions if you aren't jolly careful.
156 See codeGen/CgCon:cgTopRhsCon.
157
158 \begin{code}
159 isFloatingRep :: PrimRep -> Bool
160
161 isFloatingRep DoubleRep = True
162 isFloatingRep FloatRep  = True
163 isFloatingRep other     = False
164
165 \end{code}
166
167 \begin{code}
168 is64BitRep :: PrimRep -> Bool
169
170 is64BitRep Int64Rep  = True
171 is64BitRep Word64Rep = True
172 is64BitRep other     = False
173
174 \end{code}
175
176
177
178 \begin{code}
179 getPrimRepSize :: PrimRep -> Int
180
181 getPrimRepSize DoubleRep  = dOUBLE_SIZE -- "words", of course
182 getPrimRepSize Word64Rep  = wORD64_SIZE
183 getPrimRepSize Int64Rep   = iNT64_SIZE
184 getPrimRepSize VoidRep    = 0
185 getPrimRepSize other      = 1
186
187 retPrimRepSize = getPrimRepSize RetRep
188
189 -- sizes in bytes.
190 -- (used in some settings to figure out how many bytes
191 -- we have to push onto the stack when calling external
192 -- entry points (e.g., stdcalling on win32)
193 getPrimRepSizeInBytes :: PrimRep -> Int
194 getPrimRepSizeInBytes pr =
195  case pr of
196     Int8Rep        ->    1
197     Word8Rep       ->    1
198     Int16Rep       ->    2
199     Word16Rep      ->    2
200     Int32Rep       ->    4
201     Word32Rep      ->    4
202
203     CharRep        ->    4
204     IntRep         ->    wORD_SIZE
205     AddrRep        ->    wORD_SIZE
206     FloatRep       ->    wORD_SIZE
207     DoubleRep      ->    dOUBLE_SIZE * wORD_SIZE
208     Word64Rep      ->    wORD64_SIZE * wORD_SIZE
209     Int64Rep       ->    iNT64_SIZE * wORD_SIZE
210     WeakPtrRep     ->    wORD_SIZE
211     ForeignObjRep  ->    wORD_SIZE
212     StablePtrRep   ->    wORD_SIZE
213     StableNameRep  ->    wORD_SIZE
214     ArrayRep       ->    wORD_SIZE
215     ByteArrayRep   ->    wORD_SIZE
216     _              ->    panic "getPrimRepSize: ouch - this wasn't supposed to happen!"
217
218 \end{code}
219
220 %************************************************************************
221 %*                                                                      *
222 \subsection[PrimRep-instances]{Boring instance decls for @PrimRep@}
223 %*                                                                      *
224 %************************************************************************
225
226 \begin{code}
227 instance Outputable PrimRep where
228     ppr kind = text (showPrimRep kind)
229
230 showPrimRep  :: PrimRep -> String
231 showPrimRepToUser :: PrimRep -> String
232
233 showPrimRep PtrRep         = "P_"       -- short for StgPtr
234 showPrimRep CodePtrRep     = "P_"       -- DEATH to StgFunPtr! (94/02/22 WDP)
235 showPrimRep DataPtrRep     = "D_"
236 showPrimRep RetRep         = "P_"
237 showPrimRep CostCentreRep  = "CostCentre"
238 showPrimRep CharRep        = "C_"
239 showPrimRep Int8Rep        = "StgInt8"
240 showPrimRep Int16Rep       = "StgInt16"
241 showPrimRep Int32Rep       = "StgInt32"
242 showPrimRep Word8Rep       = "StgWord8"
243 showPrimRep Word16Rep      = "StgWord16"
244 showPrimRep Word32Rep      = "StgWord32"
245 showPrimRep IntRep         = "I_"       -- short for StgInt
246 showPrimRep WordRep        = "W_"       -- short for StgWord
247 showPrimRep Int64Rep       = "LI_"       -- short for StgLongInt
248 showPrimRep Word64Rep      = "LW_"       -- short for StgLongWord
249 showPrimRep AddrRep        = "StgAddr"
250 showPrimRep FloatRep       = "StgFloat"
251 showPrimRep DoubleRep      = "StgDouble"
252 showPrimRep ArrayRep       = "P_" -- see comment below
253 showPrimRep PrimPtrRep     = "P_"
254 showPrimRep ByteArrayRep   = "StgByteArray"
255 showPrimRep StablePtrRep   = "StgStablePtr"
256 showPrimRep StableNameRep  = "P_"
257 showPrimRep ThreadIdRep    = "StgTSO*"
258 showPrimRep WeakPtrRep     = "P_"
259 showPrimRep ForeignObjRep  = "StgAddr"
260 showPrimRep VoidRep        = "!!VOID_KIND!!"
261 showPrimRep BCORep         = "P_"       -- not sure -- JRS 000708
262
263 primRepString CharRep           = "Char"
264 primRepString Int8Rep           = "Char" -- To have names like newCharArray#
265 primRepString IntRep            = "Int"
266 primRepString WordRep           = "Word"
267 primRepString Int64Rep          = "Int64"
268 primRepString Word64Rep         = "Word64"
269 primRepString AddrRep           = "Addr"
270 primRepString FloatRep          = "Float"
271 primRepString DoubleRep         = "Double"
272 primRepString WeakPtrRep        = "Weak"
273 primRepString ForeignObjRep     = "ForeignObj"
274 primRepString StablePtrRep      = "StablePtr"
275 primRepString StableNameRep     = "StableName"
276 primRepString other             = pprPanic "primRepString" (ppr other)
277
278 showPrimRepToUser pr = primRepString pr
279 \end{code}
280
281 Foreign Objects and Arrays are treated specially by the code for
282 _ccall_s: we pass a pointer to the contents of the object, not the
283 object itself.