[project @ 2004-08-13 13:04:50 by simonmar]
[ghc-hetmet.git] / ghc / compiler / codeGen / SMRep.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 \section[SMRep]{Storage manager representations of closure}
5
6 This is here, rather than in ClosureInfo, just to keep nhc happy.
7 Other modules should access this info through ClosureInfo.
8
9 \begin{code}
10 module SMRep (
11         -- Words and bytes
12         StgWord, StgHalfWord, 
13         hALF_WORD_SIZE, hALF_WORD_SIZE_IN_BITS,
14         WordOff, ByteOff,
15
16         -- Argument/return representations
17         CgRep(..), nonVoidArg,
18         argMachRep, primRepToCgRep, primRepHint,
19         isFollowableArg, isVoidArg, 
20         isFloatingArg, isNonPtrArg, is64BitArg,
21         separateByPtrFollowness,
22         cgRepSizeW, cgRepSizeB,
23         retAddrSizeW,
24
25         typeCgRep, idCgRep, tyConCgRep, typeHint,
26
27         -- Closure repesentation
28         SMRep(..), ClosureType(..),
29         isStaticRep,
30         fixedHdrSize, arrWordsHdrSize, arrPtrsHdrSize,
31         profHdrSize,
32         tablesNextToCode,
33         smRepClosureType, smRepClosureTypeInt,
34
35         rET_SMALL, rET_VEC_SMALL, rET_BIG, rET_VEC_BIG
36     ) where
37
38 #include "HsVersions.h"
39 #include "../includes/MachDeps.h"
40
41 import Id               ( Id, idType )
42 import Type             ( Type, typePrimRep, PrimRep(..) )
43 import TyCon            ( TyCon, tyConPrimRep )
44 import MachOp           ( MachRep(..), MachHint(..), wordRep )
45 import CmdLineOpts      ( opt_SccProfilingOn, opt_GranMacros, opt_Unregisterised )
46 import Constants
47 import Outputable
48
49 import DATA_WORD
50 \end{code}
51
52
53 %************************************************************************
54 %*                                                                      *
55                 Words and bytes
56 %*                                                                      *
57 %************************************************************************
58
59 \begin{code}
60 type WordOff = Int      -- Word offset, or word count
61 type ByteOff = Int      -- Byte offset, or byte count
62 \end{code}
63
64 StgWord is a type representing an StgWord on the target platform.
65
66 \begin{code}
67 #if SIZEOF_HSWORD == 4
68 type StgWord     = Word32
69 type StgHalfWord = Word16
70 hALF_WORD_SIZE = 2 :: ByteOff
71 hALF_WORD_SIZE_IN_BITS = 16 :: Int
72 #elif SIZEOF_HSWORD == 8
73 type StgWord     = Word64
74 type StgHalfWord = Word32
75 hALF_WORD_SIZE = 4 :: ByteOff
76 hALF_WORD_SIZE_IN_BITS = 32 :: Int
77 #else
78 #error unknown SIZEOF_HSWORD
79 #endif
80 \end{code}
81
82
83 %************************************************************************
84 %*                                                                      *
85                         CgRep
86 %*                                                                      *
87 %************************************************************************
88
89 An CgRep is an abstraction of a Type which tells the code generator
90 all it needs to know about the calling convention for arguments (and
91 results) of that type.  In particular, the ArgReps of a function's
92 arguments are used to decide which of the RTS's generic apply
93 functions to call when applying an unknown function.
94
95 It contains more information than the back-end data type MachRep,
96 so one can easily convert from CgRep -> MachRep.  (Except that
97 there's no MachRep for a VoidRep.)
98
99 It distinguishes 
100         pointers from non-pointers (we sort the pointers together
101         when building closures)
102
103         void from other types: a void argument is different from no argument
104
105 All 64-bit types map to the same CgRep, because they're passed in the
106 same register, but a PtrArg is still different from an NonPtrArg
107 because the function's entry convention has to take into account the
108 pointer-hood of arguments for the purposes of describing the stack on
109 entry to the garbage collector.
110
111 \begin{code}
112 data CgRep 
113   = VoidArg     -- Void
114   | PtrArg      -- Word-sized Ptr
115   | NonPtrArg   -- Word-sized non-pointer
116   | LongArg     -- 64-bit non-pointer
117   | FloatArg    -- 32-bit float
118   | DoubleArg   -- 64-bit float
119   deriving Eq
120
121 instance Outputable CgRep where
122     ppr VoidArg   = ptext SLIT("V_")
123     ppr PtrArg    = ptext SLIT("P_")
124     ppr NonPtrArg = ptext SLIT("I_")
125     ppr LongArg   = ptext SLIT("L_")
126     ppr FloatArg  = ptext SLIT("F_")
127     ppr DoubleArg = ptext SLIT("D_")
128
129 argMachRep :: CgRep -> MachRep
130 argMachRep PtrArg    = wordRep
131 argMachRep NonPtrArg = wordRep
132 argMachRep LongArg   = I64
133 argMachRep FloatArg  = F32
134 argMachRep DoubleArg = F64
135 argMachRep VoidArg   = panic "argMachRep:VoidRep"
136
137 primRepToCgRep :: PrimRep -> CgRep
138 primRepToCgRep VoidRep    = VoidArg
139 primRepToCgRep PtrRep     = PtrArg
140 primRepToCgRep IntRep     = NonPtrArg
141 primRepToCgRep WordRep    = NonPtrArg
142 primRepToCgRep Int64Rep   = LongArg
143 primRepToCgRep Word64Rep  = LongArg
144 primRepToCgRep AddrRep    = NonPtrArg
145 primRepToCgRep FloatRep   = FloatArg
146 primRepToCgRep DoubleRep  = DoubleArg
147
148 primRepHint :: PrimRep -> MachHint
149 primRepHint VoidRep     = panic "primRepHint:VoidRep"
150 primRepHint PtrRep      = PtrHint
151 primRepHint IntRep      = SignedHint
152 primRepHint WordRep     = NoHint
153 primRepHint Int64Rep    = SignedHint
154 primRepHint Word64Rep   = NoHint
155 primRepHint AddrRep     = PtrHint -- NB! PtrHint, but NonPtrArg
156 primRepHint FloatRep    = FloatHint
157 primRepHint DoubleRep   = FloatHint
158
159 idCgRep :: Id -> CgRep
160 idCgRep = typeCgRep . idType
161
162 tyConCgRep :: TyCon -> CgRep
163 tyConCgRep = primRepToCgRep . tyConPrimRep
164
165 typeCgRep :: Type -> CgRep
166 typeCgRep = primRepToCgRep . typePrimRep
167
168 typeHint :: Type -> MachHint
169 typeHint = primRepHint . typePrimRep
170 \end{code}
171
172 Whether or not the thing is a pointer that the garbage-collector
173 should follow. Or, to put it another (less confusing) way, whether
174 the object in question is a heap object. 
175
176 Depending on the outcome, this predicate determines what stack
177 the pointer/object possibly will have to be saved onto, and the
178 computation of GC liveness info.
179
180 \begin{code}
181 isFollowableArg :: CgRep -> Bool  -- True <=> points to a heap object
182 isFollowableArg PtrArg  = True
183 isFollowableArg other = False
184
185 isVoidArg :: CgRep -> Bool
186 isVoidArg VoidArg = True
187 isVoidArg other   = False
188
189 nonVoidArg :: CgRep -> Bool
190 nonVoidArg VoidArg = False
191 nonVoidArg other   = True
192
193 -- isFloatingArg is used to distinguish @Double@ and @Float@ which
194 -- cause inadvertent numeric conversions if you aren't jolly careful.
195 -- See codeGen/CgCon:cgTopRhsCon.
196
197 isFloatingArg :: CgRep -> Bool
198 isFloatingArg DoubleArg = True
199 isFloatingArg FloatArg  = True
200 isFloatingArg _         = False
201
202 isNonPtrArg :: CgRep -> Bool
203 -- Identify anything which is one word large and not a pointer.
204 isNonPtrArg NonPtrArg = True
205 isNonPtrArg other     = False
206
207 is64BitArg :: CgRep -> Bool
208 is64BitArg LongArg = True
209 is64BitArg _       = False
210 \end{code}
211
212 \begin{code}
213 separateByPtrFollowness :: [(CgRep,a)] -> ([(CgRep,a)], [(CgRep,a)])
214 -- Returns (ptrs, non-ptrs)
215 separateByPtrFollowness things
216   = sep_things things [] []
217     -- accumulating params for follow-able and don't-follow things...
218   where
219     sep_things []              bs us = (reverse bs, reverse us)
220     sep_things ((PtrArg,a):ts) bs us = sep_things ts ((PtrArg,a):bs) us
221     sep_things (t         :ts) bs us = sep_things ts bs              (t:us)
222 \end{code}
223
224 \begin{code}
225 cgRepSizeB :: CgRep -> ByteOff
226 cgRepSizeB DoubleArg = dOUBLE_SIZE
227 cgRepSizeB LongArg   = wORD64_SIZE
228 cgRepSizeB VoidArg   = 0
229 cgRepSizeB _         = wORD_SIZE
230
231 cgRepSizeW :: CgRep -> ByteOff
232 cgRepSizeW DoubleArg = dOUBLE_SIZE `quot` wORD_SIZE
233 cgRepSizeW LongArg   = wORD64_SIZE `quot` wORD_SIZE
234 cgRepSizeW VoidArg   = 0
235 cgRepSizeW _         = 1
236
237 retAddrSizeW :: WordOff
238 retAddrSizeW = 1        -- One word
239 \end{code}
240
241 %************************************************************************
242 %*                                                                      *
243 \subsubsection[SMRep-datatype]{@SMRep@---storage manager representation}
244 %*                                                                      *
245 %************************************************************************
246
247 \begin{code}
248 data SMRep
249      -- static closure have an extra static link field at the end.
250   = GenericRep          -- GC routines consult sizes in info tbl
251         Bool            -- True <=> This is a static closure.  Affects how 
252                         --          we garbage-collect it
253         !Int            -- # ptr words
254         !Int            -- # non-ptr words
255         ClosureType     -- closure type
256
257   | BlackHoleRep
258
259 data ClosureType        -- Corresponds 1-1 with the varieties of closures
260                         -- implemented by the RTS.  Compare with ghc/includes/ClosureTypes.h
261     = Constr
262     | ConstrNoCaf
263     | Fun
264     | Thunk
265     | ThunkSelector
266 \end{code}
267
268 Size of a closure header.
269
270 \begin{code}
271 fixedHdrSize :: WordOff
272 fixedHdrSize = sTD_HDR_SIZE + profHdrSize + granHdrSize
273
274 profHdrSize  :: WordOff
275 profHdrSize  | opt_SccProfilingOn   = pROF_HDR_SIZE
276              | otherwise            = 0
277
278 granHdrSize  :: WordOff
279 granHdrSize  | opt_GranMacros       = gRAN_HDR_SIZE
280              | otherwise            = 0
281
282 arrWordsHdrSize   :: ByteOff
283 arrWordsHdrSize   = fixedHdrSize*wORD_SIZE + sIZEOF_StgArrWords_NoHdr
284
285 arrPtrsHdrSize    :: ByteOff
286 arrPtrsHdrSize    = fixedHdrSize*wORD_SIZE + sIZEOF_StgMutArrPtrs_NoHdr
287 \end{code}
288
289 \begin{code}
290 -- IA64 mangler doesn't place tables next to code
291 tablesNextToCode :: Bool
292 #ifdef ia64_TARGET_ARCH
293 tablesNextToCode = False
294 #else
295 tablesNextToCode = not opt_Unregisterised
296 #endif
297 \end{code}
298
299 \begin{code}
300 isStaticRep :: SMRep -> Bool
301 isStaticRep (GenericRep is_static _ _ _) = is_static
302 isStaticRep BlackHoleRep                 = False
303 \end{code}
304
305 \begin{code}
306 #include "../includes/ClosureTypes.h"
307 -- Defines CONSTR, CONSTR_1_0 etc
308
309
310 smRepClosureType :: SMRep -> ClosureType
311 smRepClosureType (GenericRep _ _ _ ty) = ty
312 smRepClosureType BlackHoleRep          = panic "smRepClosureType: black hole"
313
314 smRepClosureTypeInt :: SMRep -> Int
315 smRepClosureTypeInt (GenericRep False 1 0 Constr) = CONSTR_1_0
316 smRepClosureTypeInt (GenericRep False 0 1 Constr) = CONSTR_0_1
317 smRepClosureTypeInt (GenericRep False 2 0 Constr) = CONSTR_2_0
318 smRepClosureTypeInt (GenericRep False 1 1 Constr) = CONSTR_1_1
319 smRepClosureTypeInt (GenericRep False 0 2 Constr) = CONSTR_0_2
320 smRepClosureTypeInt (GenericRep False _ _ Constr) = CONSTR
321
322 smRepClosureTypeInt (GenericRep False 1 0 Fun) = FUN_1_0
323 smRepClosureTypeInt (GenericRep False 0 1 Fun) = FUN_0_1
324 smRepClosureTypeInt (GenericRep False 2 0 Fun) = FUN_2_0
325 smRepClosureTypeInt (GenericRep False 1 1 Fun) = FUN_1_1
326 smRepClosureTypeInt (GenericRep False 0 2 Fun) = FUN_0_2
327 smRepClosureTypeInt (GenericRep False _ _ Fun) = FUN
328
329 smRepClosureTypeInt (GenericRep False 1 0 Thunk) = THUNK_1_0
330 smRepClosureTypeInt (GenericRep False 0 1 Thunk) = THUNK_0_1
331 smRepClosureTypeInt (GenericRep False 2 0 Thunk) = THUNK_2_0
332 smRepClosureTypeInt (GenericRep False 1 1 Thunk) = THUNK_1_1
333 smRepClosureTypeInt (GenericRep False 0 2 Thunk) = THUNK_0_2
334 smRepClosureTypeInt (GenericRep False _ _ Thunk) = THUNK
335
336 smRepClosureTypeInt (GenericRep False _ _ ThunkSelector) =  THUNK_SELECTOR
337
338 smRepClosureTypeInt (GenericRep True _ _ Constr)      = CONSTR_STATIC
339 smRepClosureTypeInt (GenericRep True _ _ ConstrNoCaf) = CONSTR_NOCAF_STATIC
340 smRepClosureTypeInt (GenericRep True _ _ Fun)         = FUN_STATIC
341 smRepClosureTypeInt (GenericRep True _ _ Thunk)       = THUNK_STATIC
342
343 smRepClosureTypeInt BlackHoleRep = BLACKHOLE
344
345 smRepClosureTypeInt rep = panic "smRepClosuretypeint"
346
347
348 -- We export these ones
349 rET_SMALL     = (RET_SMALL     :: Int)
350 rET_VEC_SMALL = (RET_VEC_SMALL :: Int)
351 rET_BIG       = (RET_BIG       :: Int)
352 rET_VEC_BIG   = (RET_VEC_BIG   :: Int)
353 \end{code}
354