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