ce883f2d87e605f3f973c2e7f55dbe5c5462a278
[ghc-hetmet.git] / ghc / compiler / prelude / PrimRep.lhs
1 %
2 % (c) The GRASP Project, Glasgow University, 1992-1996
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       , showPrimRepToUser
23       , ppPrimRep
24       , guessPrimRep
25       , decodePrimRep
26       ) where
27
28 #include "HsVersions.h"
29
30 import Util
31 import Outputable
32
33 -- Oh dear.
34 -- NOTE: we have to reach out and grab this header file
35 -- in our current source/build tree, and not the one supplied
36 -- by whoever's compiling us.
37 #include "../../includes/GhcConstants.h"
38 \end{code}
39
40 %************************************************************************
41 %*                                                                      *
42 \subsection[PrimRep-datatype]{The @PrimRep@ datatype}
43 %*                                                                      *
44 %************************************************************************
45
46 \begin{code}
47 data PrimRep
48   = -- These pointer-kinds are all really the same, but we keep
49     -- them separate for documentation purposes.
50     PtrRep              -- Pointer to a closure; a ``word''.
51   | CodePtrRep          -- Pointer to code
52   | DataPtrRep          -- Pointer to data
53   | RetRep              -- Pointer to code or data (return vector or code pointer)
54   | CostCentreRep       -- Pointer to a cost centre
55
56   | CharRep             -- Machine characters
57   | IntRep              --         integers (at least 32 bits)
58   | WordRep             --         ditto (but *unsigned*)
59   | AddrRep             --         addresses ("C pointers")
60   | FloatRep            --         floats
61   | DoubleRep           --         doubles
62   | Word64Rep           --    guaranteed to be 64 bits (no more, no less.)
63   | Int64Rep            --    guaranteed to be 64 bits (no more, no less.)
64
65   | ForeignObjRep       -- This has to be a special kind because ccall
66                         -- generates special code when passing/returning
67                         -- one of these. [ADR]
68
69   | StablePtrRep        -- We could replace this with IntRep but maybe
70                         -- there's some documentation gain from having
71                         -- it special? [ADR]
72
73   | ArrayRep            -- Primitive array of Haskell pointers
74   | ByteArrayRep        -- Primitive array of bytes (no Haskell pointers)
75
76   | VoidRep             -- Occupies no space at all!
77                         -- (Primitive states are mapped onto this)
78   deriving (Eq, Ord)
79         -- Kinds are used in PrimTyCons, which need both Eq and Ord
80 \end{code}
81
82 %************************************************************************
83 %*                                                                      *
84 \subsection[PrimRep-predicates]{Follow-ness, sizes, and such---on @PrimitiveKinds@}
85 %*                                                                      *
86 %************************************************************************
87
88 Whether or not the thing is a pointer that the garbage-collector
89 should follow. Or, to put it another (less confusing) way, whether
90 the object in question is a heap object. 
91
92 Depending on the outcome, this predicate determines what stack
93 the pointer/object possibly will have to be saved onto, and the
94 computation of GC liveness info.
95
96 \begin{code}
97 isFollowableRep :: PrimRep -> Bool
98
99 isFollowableRep PtrRep        = True
100 isFollowableRep ArrayRep      = True
101 isFollowableRep ByteArrayRep  = True
102 -- why is a ForeignObj followable? 4/96 SOF
103 --
104 -- A: they're followable because these objects
105 -- should be lugged around by the storage manager
106 -- (==> registers containing them are live) -- 3/97 SOF
107 isFollowableRep ForeignObjRep  = True
108
109 isFollowableRep StablePtrRep  = False
110 -- StablePtrs aren't followable because they are just indices into a
111 -- table for which explicit allocation/ deallocation is required.
112
113 isFollowableRep other           = False
114
115 separateByPtrFollowness :: (a -> PrimRep) -> [a] -> ([a], [a])
116
117 separateByPtrFollowness kind_fun things
118   = sep_things kind_fun things [] []
119     -- accumulating params for follow-able and don't-follow things...
120   where
121     sep_things kfun []     bs us = (reverse bs, reverse us)
122     sep_things kfun (t:ts) bs us
123       = if (isFollowableRep . kfun) t then
124             sep_things kfun ts (t:bs) us
125         else
126             sep_things kfun ts bs (t:us)
127 \end{code}
128
129 @isFloatingRep@ is used to distinguish @Double@ and @Float@ which
130 cause inadvertent numeric conversions if you aren't jolly careful.
131 See codeGen/CgCon:cgTopRhsCon.
132
133 \begin{code}
134 isFloatingRep :: PrimRep -> Bool
135
136 isFloatingRep DoubleRep = True
137 isFloatingRep FloatRep  = True
138 isFloatingRep other     = False
139
140 \end{code}
141
142 \begin{code}
143 is64BitRep :: PrimRep -> Bool
144
145 is64BitRep Int64Rep  = True
146 is64BitRep Word64Rep = True
147 is64BitRep other     = False
148
149 \end{code}
150
151
152
153 \begin{code}
154 getPrimRepSize :: PrimRep -> Int
155
156 getPrimRepSize DoubleRep  = DOUBLE_SIZE -- "words", of course
157 getPrimRepSize Word64Rep  = WORD64_SIZE
158 getPrimRepSize Int64Rep   = INT64_SIZE
159 --getPrimRepSize FloatRep = 1
160 --getPrimRepSize CharRep  = 1   -- ToDo: count in bytes?
161 --getPrimRepSize ArrayRep = 1   -- Listed specifically for *documentation*
162 --getPrimRepSize ByteArrayRep = 1
163 getPrimRepSize VoidRep    = 0
164 getPrimRepSize other      = 1
165
166 retPrimRepSize = getPrimRepSize RetRep
167
168 -- size in bytes, ToDo: cpp in the right vals.
169 -- (used in some settings to figure out how many bytes
170 -- we have to push onto the stack when calling external
171 -- entry points (e.g., stdcalling on win32))
172 getPrimRepSizeInBytes :: PrimRep -> Int
173 getPrimRepSizeInBytes pr =
174  case pr of
175     CharRep        ->    1
176     IntRep         ->    4
177     AddrRep        ->    4
178     FloatRep       ->    4
179     DoubleRep      ->    8
180     Word64Rep      ->    8
181     Int64Rep       ->    8
182     ForeignObjRep  ->    4
183     StablePtrRep   ->    4
184     ArrayRep       ->    4
185     ByteArrayRep   ->    4
186     _              ->   panic "getPrimRepSize: ouch - this wasn't supposed to happen!"
187
188 \end{code}
189
190 %************************************************************************
191 %*                                                                      *
192 \subsection[PrimRep-instances]{Boring instance decls for @PrimRep@}
193 %*                                                                      *
194 %************************************************************************
195
196 \begin{code}
197 instance Outputable PrimRep where
198     ppr kind = text (showPrimRep kind)
199
200 showPrimRep  :: PrimRep -> String
201 showPrimRepToUser :: PrimRep -> String
202 -- dumping PrimRep tag for unfoldings
203 ppPrimRep  :: PrimRep -> SDoc
204
205 guessPrimRep :: String -> PrimRep       -- a horrible "inverse" function
206 decodePrimRep :: Char  -> PrimRep       -- of equal nature
207
208 ppPrimRep k =
209  char 
210   (case k of
211      PtrRep        -> 'P'
212      CodePtrRep    -> 'p'
213      DataPtrRep    -> 'd'
214      CostCentreRep -> 'c'       -- Pointer to a cost centre
215      RetRep        -> 'R'
216      CharRep       -> 'C'
217      IntRep        -> 'I'
218      Int64Rep      -> 'i'
219      WordRep       -> 'W'
220      Word64Rep     -> 'w'
221      AddrRep       -> 'A'
222      FloatRep      -> 'F'
223      DoubleRep     -> 'D'
224      ArrayRep      -> 'a'
225      ByteArrayRep  -> 'b'
226      StablePtrRep  -> 'S'
227      ForeignObjRep -> 'f'
228      VoidRep       -> 'V'
229      _             -> panic "ppPrimRep")
230
231 showPrimRep PtrRep          = "P_"      -- short for StgPtr
232
233 showPrimRep CodePtrRep    = "P_"        -- DEATH to StgFunPtr! (94/02/22 WDP)
234     -- but aren't code pointers and function pointers different sizes
235     -- on some machines (eg 80x86)? ADR
236     -- Are you trying to ruin my life, or what? (WDP)
237
238 showPrimRep DataPtrRep    = "D_"
239 showPrimRep RetRep        = "StgRetAddr"
240 showPrimRep CostCentreRep = "CostCentre"
241 showPrimRep CharRep       = "StgChar"
242 showPrimRep IntRep        = "I_"        -- short for StgInt
243 showPrimRep WordRep       = "W_"        -- short for StgWord
244 showPrimRep Int64Rep      = "LI_"       -- short for StgLongInt
245 showPrimRep Word64Rep     = "LW_"       -- short for StgLongWord
246 showPrimRep AddrRep       = "StgAddr"
247 showPrimRep FloatRep      = "StgFloat"
248 showPrimRep DoubleRep     = "StgDouble"
249 showPrimRep ArrayRep      = "StgArray" -- see comment below
250 showPrimRep ByteArrayRep  = "StgByteArray"
251 showPrimRep StablePtrRep  = "StgStablePtr"
252 showPrimRep ForeignObjRep  = "StgPtr" -- see comment below
253 showPrimRep VoidRep       = "!!VOID_KIND!!"
254
255 showPrimRepToUser pr =
256   case pr of
257     CharRep       -> "StgChar"
258     IntRep        -> "StgInt"
259     WordRep       -> "StgWord"
260     Int64Rep      -> "StgInt64"
261     Word64Rep     -> "StgWord64"
262     AddrRep       -> "StgAddr"
263     FloatRep      -> "StgFloat"
264     DoubleRep     -> "StgDouble"
265     ArrayRep      -> "StgArray"
266     ByteArrayRep  -> "StgByteArray"
267     StablePtrRep  -> "StgStablePtr"
268     ForeignObjRep -> "StgPtr"
269     _             -> panic ("showPrimRepToUser: " ++ showPrimRep pr)
270     
271
272 decodePrimRep ch =
273  case ch of
274      'P' -> PtrRep        
275      'p' -> CodePtrRep    
276      'd' -> DataPtrRep    
277      'c' -> CostCentreRep 
278      'R' -> RetRep        
279      'C' -> CharRep       
280      'I' -> IntRep        
281      'W' -> WordRep       
282      'i' -> Int64Rep        
283      'w' -> Word64Rep       
284      'A' -> AddrRep       
285      'F' -> FloatRep      
286      'D' -> DoubleRep     
287      'a' -> ArrayRep      
288      'b' -> ByteArrayRep  
289      'S' -> StablePtrRep  
290      'f' -> ForeignObjRep 
291      'V' -> VoidRep
292      _   -> panic "decodePrimRep"
293
294 guessPrimRep "D_"           = DataPtrRep
295 guessPrimRep "StgRetAddr"   = RetRep
296 guessPrimRep "StgChar"      = CharRep
297 guessPrimRep "I_"           = IntRep
298 guessPrimRep "LI_"          = Int64Rep
299 guessPrimRep "W_"           = WordRep
300 guessPrimRep "LW_"          = Word64Rep
301 guessPrimRep "StgAddr"      = AddrRep
302 guessPrimRep "StgFloat"     = FloatRep
303 guessPrimRep "StgDouble"    = DoubleRep
304 guessPrimRep "StgArray"     = ArrayRep
305 guessPrimRep "StgByteArray" = ByteArrayRep
306 guessPrimRep "StgStablePtr" = StablePtrRep
307 \end{code}
308
309 All local C variables of @ArrayRep@ are declared in C as type
310 @StgArray@.  The coercion to a more precise C type is done just before
311 indexing (by the relevant C primitive-op macro).
312
313 Nota Bene. There are three types associated with @ForeignObj@ (MallocPtr++): 
314 \begin{itemize}
315 \item
316 @StgForeignObjClosure@ is the type of the thing the prim. op @mkForeignObj@ returns.
317 {- old comment for MallocPtr
318 (This typename is hardwired into @ppr_casm_results@ in
319 @PprAbsC.lhs@.)
320 -}
321
322 \item
323 @StgForeignObj@ is the type of the thing we give the C world.
324
325 \item
326 @StgPtr@ is the type of the (pointer to the) heap object which we
327 pass around inside the STG machine.
328 \end{itemize}
329
330 It is really easy to confuse the two.  (I'm not sure this choice of
331 type names helps.) [ADR]