2 % (c) The University of Glasgow 2006
3 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
6 Storage manager representation of closures
8 This is here, rather than in ClosureInfo, just to keep nhc happy.
9 Other modules should access this info through ClosureInfo.
15 hALF_WORD_SIZE, hALF_WORD_SIZE_IN_BITS,
18 -- Argument/return representations
19 CgRep(..), nonVoidArg,
20 argMachRep, primRepToCgRep, primRepHint,
21 isFollowableArg, isVoidArg,
22 isFloatingArg, isNonPtrArg, is64BitArg,
23 separateByPtrFollowness,
24 cgRepSizeW, cgRepSizeB,
27 typeCgRep, idCgRep, tyConCgRep, typeHint,
29 -- Closure repesentation
30 SMRep(..), ClosureType(..),
32 fixedHdrSize, arrWordsHdrSize, arrPtrsHdrSize,
33 profHdrSize, thunkHdrSize,
34 smRepClosureType, smRepClosureTypeInt,
39 #include "HsVersions.h"
40 #include "../includes/MachDeps.h"
54 %************************************************************************
58 %************************************************************************
61 type WordOff = Int -- Word offset, or word count
62 type ByteOff = Int -- Byte offset, or byte count
65 StgWord is a type representing an StgWord on the target platform.
68 #if SIZEOF_HSWORD == 4
70 type StgHalfWord = Word16
71 hALF_WORD_SIZE = 2 :: ByteOff
72 hALF_WORD_SIZE_IN_BITS = 16 :: Int
73 #elif SIZEOF_HSWORD == 8
75 type StgHalfWord = Word32
76 hALF_WORD_SIZE = 4 :: ByteOff
77 hALF_WORD_SIZE_IN_BITS = 32 :: Int
79 #error unknown SIZEOF_HSWORD
84 %************************************************************************
88 %************************************************************************
90 An CgRep is an abstraction of a Type which tells the code generator
91 all it needs to know about the calling convention for arguments (and
92 results) of that type. In particular, the ArgReps of a function's
93 arguments are used to decide which of the RTS's generic apply
94 functions to call when applying an unknown function.
96 It contains more information than the back-end data type MachRep,
97 so one can easily convert from CgRep -> MachRep. (Except that
98 there's no MachRep for a VoidRep.)
101 pointers from non-pointers (we sort the pointers together
102 when building closures)
104 void from other types: a void argument is different from no argument
106 All 64-bit types map to the same CgRep, because they're passed in the
107 same register, but a PtrArg is still different from an NonPtrArg
108 because the function's entry convention has to take into account the
109 pointer-hood of arguments for the purposes of describing the stack on
110 entry to the garbage collector.
115 | PtrArg -- Word-sized Ptr
116 | NonPtrArg -- Word-sized non-pointer
117 | LongArg -- 64-bit non-pointer
118 | FloatArg -- 32-bit float
119 | DoubleArg -- 64-bit float
122 instance Outputable CgRep where
123 ppr VoidArg = ptext SLIT("V_")
124 ppr PtrArg = ptext SLIT("P_")
125 ppr NonPtrArg = ptext SLIT("I_")
126 ppr LongArg = ptext SLIT("L_")
127 ppr FloatArg = ptext SLIT("F_")
128 ppr DoubleArg = ptext SLIT("D_")
130 argMachRep :: CgRep -> MachRep
131 argMachRep PtrArg = wordRep
132 argMachRep NonPtrArg = wordRep
133 argMachRep LongArg = I64
134 argMachRep FloatArg = F32
135 argMachRep DoubleArg = F64
136 argMachRep VoidArg = panic "argMachRep:VoidRep"
138 primRepToCgRep :: PrimRep -> CgRep
139 primRepToCgRep VoidRep = VoidArg
140 primRepToCgRep PtrRep = PtrArg
141 primRepToCgRep IntRep = NonPtrArg
142 primRepToCgRep WordRep = NonPtrArg
143 primRepToCgRep Int64Rep = LongArg
144 primRepToCgRep Word64Rep = LongArg
145 primRepToCgRep AddrRep = NonPtrArg
146 primRepToCgRep FloatRep = FloatArg
147 primRepToCgRep DoubleRep = DoubleArg
149 primRepHint :: PrimRep -> MachHint
150 primRepHint VoidRep = panic "primRepHint:VoidRep"
151 primRepHint PtrRep = PtrHint
152 primRepHint IntRep = SignedHint
153 primRepHint WordRep = NoHint
154 primRepHint Int64Rep = SignedHint
155 primRepHint Word64Rep = NoHint
156 primRepHint AddrRep = PtrHint -- NB! PtrHint, but NonPtrArg
157 primRepHint FloatRep = FloatHint
158 primRepHint DoubleRep = FloatHint
160 idCgRep :: Id -> CgRep
161 idCgRep x = typeCgRep . idType $ x
163 tyConCgRep :: TyCon -> CgRep
164 tyConCgRep = primRepToCgRep . tyConPrimRep
166 typeCgRep :: Type -> CgRep
167 typeCgRep = primRepToCgRep . typePrimRep
169 typeHint :: Type -> MachHint
170 typeHint = primRepHint . typePrimRep
173 Whether or not the thing is a pointer that the garbage-collector
174 should follow. Or, to put it another (less confusing) way, whether
175 the object in question is a heap object.
177 Depending on the outcome, this predicate determines what stack
178 the pointer/object possibly will have to be saved onto, and the
179 computation of GC liveness info.
182 isFollowableArg :: CgRep -> Bool -- True <=> points to a heap object
183 isFollowableArg PtrArg = True
184 isFollowableArg other = False
186 isVoidArg :: CgRep -> Bool
187 isVoidArg VoidArg = True
188 isVoidArg other = False
190 nonVoidArg :: CgRep -> Bool
191 nonVoidArg VoidArg = False
192 nonVoidArg other = True
194 -- isFloatingArg is used to distinguish @Double@ and @Float@ which
195 -- cause inadvertent numeric conversions if you aren't jolly careful.
196 -- See codeGen/CgCon:cgTopRhsCon.
198 isFloatingArg :: CgRep -> Bool
199 isFloatingArg DoubleArg = True
200 isFloatingArg FloatArg = True
201 isFloatingArg _ = False
203 isNonPtrArg :: CgRep -> Bool
204 -- Identify anything which is one word large and not a pointer.
205 isNonPtrArg NonPtrArg = True
206 isNonPtrArg other = False
208 is64BitArg :: CgRep -> Bool
209 is64BitArg LongArg = True
214 separateByPtrFollowness :: [(CgRep,a)] -> ([(CgRep,a)], [(CgRep,a)])
215 -- Returns (ptrs, non-ptrs)
216 separateByPtrFollowness things
217 = sep_things things [] []
218 -- accumulating params for follow-able and don't-follow things...
220 sep_things [] bs us = (reverse bs, reverse us)
221 sep_things ((PtrArg,a):ts) bs us = sep_things ts ((PtrArg,a):bs) us
222 sep_things (t :ts) bs us = sep_things ts bs (t:us)
226 cgRepSizeB :: CgRep -> ByteOff
227 cgRepSizeB DoubleArg = dOUBLE_SIZE
228 cgRepSizeB LongArg = wORD64_SIZE
229 cgRepSizeB VoidArg = 0
230 cgRepSizeB _ = wORD_SIZE
232 cgRepSizeW :: CgRep -> ByteOff
233 cgRepSizeW DoubleArg = dOUBLE_SIZE `quot` wORD_SIZE
234 cgRepSizeW LongArg = wORD64_SIZE `quot` wORD_SIZE
235 cgRepSizeW VoidArg = 0
238 retAddrSizeW :: WordOff
239 retAddrSizeW = 1 -- One word
242 %************************************************************************
244 \subsubsection[SMRep-datatype]{@SMRep@---storage manager representation}
246 %************************************************************************
250 -- static closure have an extra static link field at the end.
251 = GenericRep -- GC routines consult sizes in info tbl
252 Bool -- True <=> This is a static closure. Affects how
253 -- we garbage-collect it
255 !Int -- # non-ptr words
256 ClosureType -- closure type
260 data ClosureType -- Corresponds 1-1 with the varieties of closures
261 -- implemented by the RTS. Compare with ghc/includes/ClosureTypes.h
269 Size of a closure header.
272 fixedHdrSize :: WordOff
273 fixedHdrSize = sTD_HDR_SIZE + profHdrSize + granHdrSize
275 profHdrSize :: WordOff
276 profHdrSize | opt_SccProfilingOn = pROF_HDR_SIZE
279 granHdrSize :: WordOff
280 granHdrSize | opt_GranMacros = gRAN_HDR_SIZE
283 arrWordsHdrSize :: ByteOff
284 arrWordsHdrSize = fixedHdrSize*wORD_SIZE + sIZEOF_StgArrWords_NoHdr
286 arrPtrsHdrSize :: ByteOff
287 arrPtrsHdrSize = fixedHdrSize*wORD_SIZE + sIZEOF_StgMutArrPtrs_NoHdr
289 -- Thunks have an extra header word on SMP, so the update doesn't
290 -- splat the payload.
291 thunkHdrSize :: WordOff
292 thunkHdrSize = fixedHdrSize + smp_hdr
293 where smp_hdr = sIZEOF_StgSMPThunkHeader `quot` wORD_SIZE
297 isStaticRep :: SMRep -> Bool
298 isStaticRep (GenericRep is_static _ _ _) = is_static
299 isStaticRep BlackHoleRep = False
303 #include "../includes/ClosureTypes.h"
304 -- Defines CONSTR, CONSTR_1_0 etc
306 -- krc: only called by tickyDynAlloc in CgTicky; return
307 -- Nothing for a black hole so we can at least make something work.
308 smRepClosureType :: SMRep -> Maybe ClosureType
309 smRepClosureType (GenericRep _ _ _ ty) = Just ty
310 smRepClosureType BlackHoleRep = Nothing
312 smRepClosureTypeInt :: SMRep -> Int
313 smRepClosureTypeInt (GenericRep False 1 0 Constr) = CONSTR_1_0
314 smRepClosureTypeInt (GenericRep False 0 1 Constr) = CONSTR_0_1
315 smRepClosureTypeInt (GenericRep False 2 0 Constr) = CONSTR_2_0
316 smRepClosureTypeInt (GenericRep False 1 1 Constr) = CONSTR_1_1
317 smRepClosureTypeInt (GenericRep False 0 2 Constr) = CONSTR_0_2
318 smRepClosureTypeInt (GenericRep False _ _ Constr) = CONSTR
320 smRepClosureTypeInt (GenericRep False 1 0 Fun) = FUN_1_0
321 smRepClosureTypeInt (GenericRep False 0 1 Fun) = FUN_0_1
322 smRepClosureTypeInt (GenericRep False 2 0 Fun) = FUN_2_0
323 smRepClosureTypeInt (GenericRep False 1 1 Fun) = FUN_1_1
324 smRepClosureTypeInt (GenericRep False 0 2 Fun) = FUN_0_2
325 smRepClosureTypeInt (GenericRep False _ _ Fun) = FUN
327 smRepClosureTypeInt (GenericRep False 1 0 Thunk) = THUNK_1_0
328 smRepClosureTypeInt (GenericRep False 0 1 Thunk) = THUNK_0_1
329 smRepClosureTypeInt (GenericRep False 2 0 Thunk) = THUNK_2_0
330 smRepClosureTypeInt (GenericRep False 1 1 Thunk) = THUNK_1_1
331 smRepClosureTypeInt (GenericRep False 0 2 Thunk) = THUNK_0_2
332 smRepClosureTypeInt (GenericRep False _ _ Thunk) = THUNK
334 smRepClosureTypeInt (GenericRep False _ _ ThunkSelector) = THUNK_SELECTOR
336 smRepClosureTypeInt (GenericRep True _ _ Constr) = CONSTR_STATIC
337 smRepClosureTypeInt (GenericRep True _ _ ConstrNoCaf) = CONSTR_NOCAF_STATIC
338 smRepClosureTypeInt (GenericRep True _ _ Fun) = FUN_STATIC
339 smRepClosureTypeInt (GenericRep True _ _ Thunk) = THUNK_STATIC
341 smRepClosureTypeInt BlackHoleRep = BLACKHOLE
343 smRepClosureTypeInt rep = panic "smRepClosuretypeint"
346 -- We export these ones
347 rET_SMALL = (RET_SMALL :: Int)
348 rET_BIG = (RET_BIG :: Int)