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