f323c1be1dd83e75a4ed84b2cb20ef5b7a47fcb4
[ghc-hetmet.git] / compiler / codeGen / SMRep.lhs
1 %
2 % (c) The University of Glasgow 2006
3 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
4 %
5
6 Storage manager representation of closures
7
8 This is here, rather than in ClosureInfo, just to keep nhc happy.
9 Other modules should access this info through ClosureInfo.
10
11 \begin{code}
12 module SMRep (
13         -- Words and bytes
14         StgWord, StgHalfWord, 
15         hALF_WORD_SIZE, hALF_WORD_SIZE_IN_BITS,
16         WordOff, ByteOff,
17
18         -- Argument/return representations
19         CgRep(..), nonVoidArg,
20         argMachRep, primRepToCgRep, primRepHint,
21         isFollowableArg, isVoidArg, 
22         isFloatingArg, is64BitArg,
23         separateByPtrFollowness,
24         cgRepSizeW, cgRepSizeB,
25         retAddrSizeW,
26
27         typeCgRep, idCgRep, tyConCgRep, typeHint,
28
29         -- Closure repesentation
30         SMRep(..), ClosureType(..),
31         isStaticRep,
32         fixedHdrSize, arrWordsHdrSize, arrPtrsHdrSize,
33         profHdrSize, thunkHdrSize,
34         smRepClosureType, smRepClosureTypeInt,
35
36         rET_SMALL, rET_BIG
37     ) where
38
39 #include "HsVersions.h"
40 #include "../includes/MachDeps.h"
41
42 import Id
43 import Type
44 import TyCon
45 import MachOp
46 import StaticFlags
47 import Constants
48 import Outputable
49
50 import Data.Word
51 \end{code}
52
53
54 %************************************************************************
55 %*                                                                      *
56                 Words and bytes
57 %*                                                                      *
58 %************************************************************************
59
60 \begin{code}
61 type WordOff = Int      -- Word offset, or word count
62 type ByteOff = Int      -- Byte offset, or byte count
63 \end{code}
64
65 StgWord is a type representing an StgWord on the target platform.
66
67 \begin{code}
68 #if SIZEOF_HSWORD == 4
69 type StgWord     = Word32
70 type StgHalfWord = Word16
71 hALF_WORD_SIZE = 2 :: ByteOff
72 hALF_WORD_SIZE_IN_BITS = 16 :: Int
73 #elif SIZEOF_HSWORD == 8
74 type StgWord     = Word64
75 type StgHalfWord = Word32
76 hALF_WORD_SIZE = 4 :: ByteOff
77 hALF_WORD_SIZE_IN_BITS = 32 :: Int
78 #else
79 #error unknown SIZEOF_HSWORD
80 #endif
81 \end{code}
82
83
84 %************************************************************************
85 %*                                                                      *
86                         CgRep
87 %*                                                                      *
88 %************************************************************************
89
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.
95
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.)
99
100 It distinguishes 
101         pointers from non-pointers (we sort the pointers together
102         when building closures)
103
104         void from other types: a void argument is different from no argument
105
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.
111
112 \begin{code}
113 data CgRep 
114   = VoidArg     -- Void
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
120   deriving Eq
121
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_")
129
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"
137
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
148
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
159
160 idCgRep :: Id -> CgRep
161 idCgRep x = typeCgRep . idType $ x
162
163 tyConCgRep :: TyCon -> CgRep
164 tyConCgRep = primRepToCgRep . tyConPrimRep
165
166 typeCgRep :: Type -> CgRep
167 typeCgRep = primRepToCgRep . typePrimRep 
168
169 typeHint :: Type -> MachHint
170 typeHint = primRepHint . typePrimRep
171 \end{code}
172
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. 
176
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.
180
181 \begin{code}
182 isFollowableArg :: CgRep -> Bool  -- True <=> points to a heap object
183 isFollowableArg PtrArg  = True
184 isFollowableArg other = False
185
186 isVoidArg :: CgRep -> Bool
187 isVoidArg VoidArg = True
188 isVoidArg other   = False
189
190 nonVoidArg :: CgRep -> Bool
191 nonVoidArg VoidArg = False
192 nonVoidArg other   = True
193
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.
197
198 isFloatingArg :: CgRep -> Bool
199 isFloatingArg DoubleArg = True
200 isFloatingArg FloatArg  = True
201 isFloatingArg _         = False
202
203 is64BitArg :: CgRep -> Bool
204 is64BitArg LongArg = True
205 is64BitArg _       = False
206 \end{code}
207
208 \begin{code}
209 separateByPtrFollowness :: [(CgRep,a)] -> ([(CgRep,a)], [(CgRep,a)])
210 -- Returns (ptrs, non-ptrs)
211 separateByPtrFollowness things
212   = sep_things things [] []
213     -- accumulating params for follow-able and don't-follow things...
214   where
215     sep_things []              bs us = (reverse bs, reverse us)
216     sep_things ((PtrArg,a):ts) bs us = sep_things ts ((PtrArg,a):bs) us
217     sep_things (t         :ts) bs us = sep_things ts bs              (t:us)
218 \end{code}
219
220 \begin{code}
221 cgRepSizeB :: CgRep -> ByteOff
222 cgRepSizeB DoubleArg = dOUBLE_SIZE
223 cgRepSizeB LongArg   = wORD64_SIZE
224 cgRepSizeB VoidArg   = 0
225 cgRepSizeB _         = wORD_SIZE
226
227 cgRepSizeW :: CgRep -> ByteOff
228 cgRepSizeW DoubleArg = dOUBLE_SIZE `quot` wORD_SIZE
229 cgRepSizeW LongArg   = wORD64_SIZE `quot` wORD_SIZE
230 cgRepSizeW VoidArg   = 0
231 cgRepSizeW _         = 1
232
233 retAddrSizeW :: WordOff
234 retAddrSizeW = 1        -- One word
235 \end{code}
236
237 %************************************************************************
238 %*                                                                      *
239 \subsubsection[SMRep-datatype]{@SMRep@---storage manager representation}
240 %*                                                                      *
241 %************************************************************************
242
243 \begin{code}
244 data SMRep
245      -- static closure have an extra static link field at the end.
246   = GenericRep          -- GC routines consult sizes in info tbl
247         Bool            -- True <=> This is a static closure.  Affects how 
248                         --          we garbage-collect it
249         !Int            --  # ptr words
250         !Int            --  # non-ptr words
251         ClosureType     -- closure type
252
253   | BlackHoleRep
254
255 data ClosureType        -- Corresponds 1-1 with the varieties of closures
256                         -- implemented by the RTS.  Compare with ghc/includes/ClosureTypes.h
257     = Constr
258     | ConstrNoCaf
259     | Fun
260     | Thunk
261     | ThunkSelector
262 \end{code}
263
264 Size of a closure header.
265
266 \begin{code}
267 fixedHdrSize :: WordOff
268 fixedHdrSize = sTD_HDR_SIZE + profHdrSize + granHdrSize
269
270 profHdrSize  :: WordOff
271 profHdrSize  | opt_SccProfilingOn   = pROF_HDR_SIZE
272              | otherwise            = 0
273
274 granHdrSize  :: WordOff
275 granHdrSize  | opt_GranMacros       = gRAN_HDR_SIZE
276              | otherwise            = 0
277
278 arrWordsHdrSize   :: ByteOff
279 arrWordsHdrSize   = fixedHdrSize*wORD_SIZE + sIZEOF_StgArrWords_NoHdr
280
281 arrPtrsHdrSize    :: ByteOff
282 arrPtrsHdrSize    = fixedHdrSize*wORD_SIZE + sIZEOF_StgMutArrPtrs_NoHdr
283
284 -- Thunks have an extra header word on SMP, so the update doesn't 
285 -- splat the payload.
286 thunkHdrSize :: WordOff
287 thunkHdrSize = fixedHdrSize + smp_hdr
288         where smp_hdr = sIZEOF_StgSMPThunkHeader `quot` wORD_SIZE
289 \end{code}
290
291 \begin{code}
292 isStaticRep :: SMRep -> Bool
293 isStaticRep (GenericRep is_static _ _ _) = is_static
294 isStaticRep BlackHoleRep                 = False
295 \end{code}
296
297 \begin{code}
298 #include "../includes/ClosureTypes.h"
299 -- Defines CONSTR, CONSTR_1_0 etc
300
301 -- krc: only called by tickyDynAlloc in CgTicky; return
302 -- Nothing for a black hole so we can at least make something work.
303 smRepClosureType :: SMRep -> Maybe ClosureType
304 smRepClosureType (GenericRep _ _ _ ty) = Just ty
305 smRepClosureType BlackHoleRep          = Nothing
306
307 smRepClosureTypeInt :: SMRep -> StgHalfWord
308 smRepClosureTypeInt (GenericRep False 1 0 Constr) = CONSTR_1_0
309 smRepClosureTypeInt (GenericRep False 0 1 Constr) = CONSTR_0_1
310 smRepClosureTypeInt (GenericRep False 2 0 Constr) = CONSTR_2_0
311 smRepClosureTypeInt (GenericRep False 1 1 Constr) = CONSTR_1_1
312 smRepClosureTypeInt (GenericRep False 0 2 Constr) = CONSTR_0_2
313 smRepClosureTypeInt (GenericRep False _ _ Constr) = CONSTR
314
315 smRepClosureTypeInt (GenericRep False 1 0 Fun) = FUN_1_0
316 smRepClosureTypeInt (GenericRep False 0 1 Fun) = FUN_0_1
317 smRepClosureTypeInt (GenericRep False 2 0 Fun) = FUN_2_0
318 smRepClosureTypeInt (GenericRep False 1 1 Fun) = FUN_1_1
319 smRepClosureTypeInt (GenericRep False 0 2 Fun) = FUN_0_2
320 smRepClosureTypeInt (GenericRep False _ _ Fun) = FUN
321
322 smRepClosureTypeInt (GenericRep False 1 0 Thunk) = THUNK_1_0
323 smRepClosureTypeInt (GenericRep False 0 1 Thunk) = THUNK_0_1
324 smRepClosureTypeInt (GenericRep False 2 0 Thunk) = THUNK_2_0
325 smRepClosureTypeInt (GenericRep False 1 1 Thunk) = THUNK_1_1
326 smRepClosureTypeInt (GenericRep False 0 2 Thunk) = THUNK_0_2
327 smRepClosureTypeInt (GenericRep False _ _ Thunk) = THUNK
328
329 smRepClosureTypeInt (GenericRep False _ _ ThunkSelector) =  THUNK_SELECTOR
330
331 smRepClosureTypeInt (GenericRep True _ _ Constr)      = CONSTR_STATIC
332 smRepClosureTypeInt (GenericRep True _ _ ConstrNoCaf) = CONSTR_NOCAF_STATIC
333 smRepClosureTypeInt (GenericRep True _ _ Fun)         = FUN_STATIC
334 smRepClosureTypeInt (GenericRep True _ _ Thunk)       = THUNK_STATIC
335
336 smRepClosureTypeInt BlackHoleRep = BLACKHOLE
337
338 smRepClosureTypeInt rep = panic "smRepClosuretypeint"
339
340
341 -- We export these ones
342 rET_SMALL     = (RET_SMALL     :: StgHalfWord)
343 rET_BIG       = (RET_BIG       :: StgHalfWord)
344 \end{code}
345