fa7945c26f8dbce23e7fd6481ba2733034c569d4
[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 {-# OPTIONS -w #-}
13 -- The above warning supression flag is a temporary kludge.
14 -- While working on this module you are encouraged to remove it and fix
15 -- any warnings in the module. See
16 --     http://hackage.haskell.org/trac/ghc/wiki/CodingStyle#Warnings
17 -- for details
18
19 module SMRep (
20         -- Words and bytes
21         StgWord, StgHalfWord, 
22         hALF_WORD_SIZE, hALF_WORD_SIZE_IN_BITS,
23         WordOff, ByteOff,
24
25         -- Argument/return representations
26         CgRep(..), nonVoidArg,
27         argMachRep, primRepToCgRep, primRepHint,
28         isFollowableArg, isVoidArg, 
29         isFloatingArg, is64BitArg,
30         separateByPtrFollowness,
31         cgRepSizeW, cgRepSizeB,
32         retAddrSizeW,
33
34         typeCgRep, idCgRep, tyConCgRep, typeHint,
35
36         -- Closure repesentation
37         SMRep(..), ClosureType(..),
38         isStaticRep,
39         fixedHdrSize, arrWordsHdrSize, arrPtrsHdrSize,
40         profHdrSize, thunkHdrSize,
41         smRepClosureType, smRepClosureTypeInt,
42
43         rET_SMALL, rET_BIG
44     ) where
45
46 #include "HsVersions.h"
47 #include "../includes/MachDeps.h"
48
49 import Id
50 import Type
51 import TyCon
52 import MachOp
53 import StaticFlags
54 import Constants
55 import Outputable
56
57 import Data.Word
58 \end{code}
59
60
61 %************************************************************************
62 %*                                                                      *
63                 Words and bytes
64 %*                                                                      *
65 %************************************************************************
66
67 \begin{code}
68 type WordOff = Int      -- Word offset, or word count
69 type ByteOff = Int      -- Byte offset, or byte count
70 \end{code}
71
72 StgWord is a type representing an StgWord on the target platform.
73
74 \begin{code}
75 #if SIZEOF_HSWORD == 4
76 type StgWord     = Word32
77 type StgHalfWord = Word16
78 hALF_WORD_SIZE = 2 :: ByteOff
79 hALF_WORD_SIZE_IN_BITS = 16 :: Int
80 #elif SIZEOF_HSWORD == 8
81 type StgWord     = Word64
82 type StgHalfWord = Word32
83 hALF_WORD_SIZE = 4 :: ByteOff
84 hALF_WORD_SIZE_IN_BITS = 32 :: Int
85 #else
86 #error unknown SIZEOF_HSWORD
87 #endif
88 \end{code}
89
90
91 %************************************************************************
92 %*                                                                      *
93                         CgRep
94 %*                                                                      *
95 %************************************************************************
96
97 An CgRep is an abstraction of a Type which tells the code generator
98 all it needs to know about the calling convention for arguments (and
99 results) of that type.  In particular, the ArgReps of a function's
100 arguments are used to decide which of the RTS's generic apply
101 functions to call when applying an unknown function.
102
103 It contains more information than the back-end data type MachRep,
104 so one can easily convert from CgRep -> MachRep.  (Except that
105 there's no MachRep for a VoidRep.)
106
107 It distinguishes 
108         pointers from non-pointers (we sort the pointers together
109         when building closures)
110
111         void from other types: a void argument is different from no argument
112
113 All 64-bit types map to the same CgRep, because they're passed in the
114 same register, but a PtrArg is still different from an NonPtrArg
115 because the function's entry convention has to take into account the
116 pointer-hood of arguments for the purposes of describing the stack on
117 entry to the garbage collector.
118
119 \begin{code}
120 data CgRep 
121   = VoidArg     -- Void
122   | PtrArg      -- Word-sized Ptr
123   | NonPtrArg   -- Word-sized non-pointer
124   | LongArg     -- 64-bit non-pointer
125   | FloatArg    -- 32-bit float
126   | DoubleArg   -- 64-bit float
127   deriving Eq
128
129 instance Outputable CgRep where
130     ppr VoidArg   = ptext SLIT("V_")
131     ppr PtrArg    = ptext SLIT("P_")
132     ppr NonPtrArg = ptext SLIT("I_")
133     ppr LongArg   = ptext SLIT("L_")
134     ppr FloatArg  = ptext SLIT("F_")
135     ppr DoubleArg = ptext SLIT("D_")
136
137 argMachRep :: CgRep -> MachRep
138 argMachRep PtrArg    = wordRep
139 argMachRep NonPtrArg = wordRep
140 argMachRep LongArg   = I64
141 argMachRep FloatArg  = F32
142 argMachRep DoubleArg = F64
143 argMachRep VoidArg   = panic "argMachRep:VoidRep"
144
145 primRepToCgRep :: PrimRep -> CgRep
146 primRepToCgRep VoidRep    = VoidArg
147 primRepToCgRep PtrRep     = PtrArg
148 primRepToCgRep IntRep     = NonPtrArg
149 primRepToCgRep WordRep    = NonPtrArg
150 primRepToCgRep Int64Rep   = LongArg
151 primRepToCgRep Word64Rep  = LongArg
152 primRepToCgRep AddrRep    = NonPtrArg
153 primRepToCgRep FloatRep   = FloatArg
154 primRepToCgRep DoubleRep  = DoubleArg
155
156 primRepHint :: PrimRep -> MachHint
157 primRepHint VoidRep     = panic "primRepHint:VoidRep"
158 primRepHint PtrRep      = PtrHint
159 primRepHint IntRep      = SignedHint
160 primRepHint WordRep     = NoHint
161 primRepHint Int64Rep    = SignedHint
162 primRepHint Word64Rep   = NoHint
163 primRepHint AddrRep     = PtrHint -- NB! PtrHint, but NonPtrArg
164 primRepHint FloatRep    = FloatHint
165 primRepHint DoubleRep   = FloatHint
166
167 idCgRep :: Id -> CgRep
168 idCgRep x = typeCgRep . idType $ x
169
170 tyConCgRep :: TyCon -> CgRep
171 tyConCgRep = primRepToCgRep . tyConPrimRep
172
173 typeCgRep :: Type -> CgRep
174 typeCgRep = primRepToCgRep . typePrimRep 
175
176 typeHint :: Type -> MachHint
177 typeHint = primRepHint . typePrimRep
178 \end{code}
179
180 Whether or not the thing is a pointer that the garbage-collector
181 should follow. Or, to put it another (less confusing) way, whether
182 the object in question is a heap object. 
183
184 Depending on the outcome, this predicate determines what stack
185 the pointer/object possibly will have to be saved onto, and the
186 computation of GC liveness info.
187
188 \begin{code}
189 isFollowableArg :: CgRep -> Bool  -- True <=> points to a heap object
190 isFollowableArg PtrArg  = True
191 isFollowableArg other = False
192
193 isVoidArg :: CgRep -> Bool
194 isVoidArg VoidArg = True
195 isVoidArg other   = False
196
197 nonVoidArg :: CgRep -> Bool
198 nonVoidArg VoidArg = False
199 nonVoidArg other   = True
200
201 -- isFloatingArg is used to distinguish @Double@ and @Float@ which
202 -- cause inadvertent numeric conversions if you aren't jolly careful.
203 -- See codeGen/CgCon:cgTopRhsCon.
204
205 isFloatingArg :: CgRep -> Bool
206 isFloatingArg DoubleArg = True
207 isFloatingArg FloatArg  = True
208 isFloatingArg _         = False
209
210 is64BitArg :: CgRep -> Bool
211 is64BitArg LongArg = True
212 is64BitArg _       = False
213 \end{code}
214
215 \begin{code}
216 separateByPtrFollowness :: [(CgRep,a)] -> ([(CgRep,a)], [(CgRep,a)])
217 -- Returns (ptrs, non-ptrs)
218 separateByPtrFollowness things
219   = sep_things things [] []
220     -- accumulating params for follow-able and don't-follow things...
221   where
222     sep_things []              bs us = (reverse bs, reverse us)
223     sep_things ((PtrArg,a):ts) bs us = sep_things ts ((PtrArg,a):bs) us
224     sep_things (t         :ts) bs us = sep_things ts bs              (t:us)
225 \end{code}
226
227 \begin{code}
228 cgRepSizeB :: CgRep -> ByteOff
229 cgRepSizeB DoubleArg = dOUBLE_SIZE
230 cgRepSizeB LongArg   = wORD64_SIZE
231 cgRepSizeB VoidArg   = 0
232 cgRepSizeB _         = wORD_SIZE
233
234 cgRepSizeW :: CgRep -> ByteOff
235 cgRepSizeW DoubleArg = dOUBLE_SIZE `quot` wORD_SIZE
236 cgRepSizeW LongArg   = wORD64_SIZE `quot` wORD_SIZE
237 cgRepSizeW VoidArg   = 0
238 cgRepSizeW _         = 1
239
240 retAddrSizeW :: WordOff
241 retAddrSizeW = 1        -- One word
242 \end{code}
243
244 %************************************************************************
245 %*                                                                      *
246 \subsubsection[SMRep-datatype]{@SMRep@---storage manager representation}
247 %*                                                                      *
248 %************************************************************************
249
250 \begin{code}
251 data SMRep
252      -- static closure have an extra static link field at the end.
253   = GenericRep          -- GC routines consult sizes in info tbl
254         Bool            -- True <=> This is a static closure.  Affects how 
255                         --          we garbage-collect it
256         !Int            --  # ptr words
257         !Int            --  # non-ptr words
258         ClosureType     -- closure type
259
260   | BlackHoleRep
261
262 data ClosureType        -- Corresponds 1-1 with the varieties of closures
263                         -- implemented by the RTS.  Compare with ghc/includes/ClosureTypes.h
264     = Constr
265     | ConstrNoCaf
266     | Fun
267     | Thunk
268     | ThunkSelector
269 \end{code}
270
271 Size of a closure header.
272
273 \begin{code}
274 fixedHdrSize :: WordOff
275 fixedHdrSize = sTD_HDR_SIZE + profHdrSize + granHdrSize
276
277 profHdrSize  :: WordOff
278 profHdrSize  | opt_SccProfilingOn   = pROF_HDR_SIZE
279              | otherwise            = 0
280
281 granHdrSize  :: WordOff
282 granHdrSize  | opt_GranMacros       = gRAN_HDR_SIZE
283              | otherwise            = 0
284
285 arrWordsHdrSize   :: ByteOff
286 arrWordsHdrSize   = fixedHdrSize*wORD_SIZE + sIZEOF_StgArrWords_NoHdr
287
288 arrPtrsHdrSize    :: ByteOff
289 arrPtrsHdrSize    = fixedHdrSize*wORD_SIZE + sIZEOF_StgMutArrPtrs_NoHdr
290
291 -- Thunks have an extra header word on SMP, so the update doesn't 
292 -- splat the payload.
293 thunkHdrSize :: WordOff
294 thunkHdrSize = fixedHdrSize + smp_hdr
295         where smp_hdr = sIZEOF_StgSMPThunkHeader `quot` wORD_SIZE
296 \end{code}
297
298 \begin{code}
299 isStaticRep :: SMRep -> Bool
300 isStaticRep (GenericRep is_static _ _ _) = is_static
301 isStaticRep BlackHoleRep                 = False
302 \end{code}
303
304 \begin{code}
305 #include "../includes/ClosureTypes.h"
306 -- Defines CONSTR, CONSTR_1_0 etc
307
308 -- krc: only called by tickyDynAlloc in CgTicky; return
309 -- Nothing for a black hole so we can at least make something work.
310 smRepClosureType :: SMRep -> Maybe ClosureType
311 smRepClosureType (GenericRep _ _ _ ty) = Just ty
312 smRepClosureType BlackHoleRep          = Nothing
313
314 smRepClosureTypeInt :: SMRep -> StgHalfWord
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     :: StgHalfWord)
350 rET_BIG       = (RET_BIG       :: StgHalfWord)
351 \end{code}
352