remove empty dir
[ghc-hetmet.git] / compiler / codeGen / SMRep.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 \section[SMRep]{Storage manager representations of closure}
5
6 This is here, rather than in ClosureInfo, just to keep nhc happy.
7 Other modules should access this info through ClosureInfo.
8
9 \begin{code}
10 module SMRep (
11         -- Words and bytes
12         StgWord, StgHalfWord, 
13         hALF_WORD_SIZE, hALF_WORD_SIZE_IN_BITS,
14         WordOff, ByteOff,
15
16         -- Argument/return representations
17         CgRep(..), nonVoidArg,
18         argMachRep, primRepToCgRep, primRepHint,
19         isFollowableArg, isVoidArg, 
20         isFloatingArg, isNonPtrArg, is64BitArg,
21         separateByPtrFollowness,
22         cgRepSizeW, cgRepSizeB,
23         retAddrSizeW,
24
25         typeCgRep, idCgRep, tyConCgRep, typeHint,
26
27         -- Closure repesentation
28         SMRep(..), ClosureType(..),
29         isStaticRep,
30         fixedHdrSize, arrWordsHdrSize, arrPtrsHdrSize,
31         profHdrSize, thunkHdrSize,
32         tablesNextToCode,
33         smRepClosureType, smRepClosureTypeInt,
34
35         rET_SMALL, rET_VEC_SMALL, rET_BIG, rET_VEC_BIG
36     ) where
37
38 #include "HsVersions.h"
39 #include "../includes/MachDeps.h"
40
41 import Id               ( Id, idType )
42 import Type             ( Type, typePrimRep, PrimRep(..) )
43 import TyCon            ( TyCon, tyConPrimRep )
44 import MachOp--         ( MachRep(..), MachHint(..), wordRep )
45 import StaticFlags      ( opt_SccProfilingOn, opt_GranMacros,
46                           opt_Unregisterised )
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 = typeCgRep . idType
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 isNonPtrArg :: CgRep -> Bool
204 -- Identify anything which is one word large and not a pointer.
205 isNonPtrArg NonPtrArg = True
206 isNonPtrArg other     = False
207
208 is64BitArg :: CgRep -> Bool
209 is64BitArg LongArg = True
210 is64BitArg _       = False
211 \end{code}
212
213 \begin{code}
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...
219   where
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)
223 \end{code}
224
225 \begin{code}
226 cgRepSizeB :: CgRep -> ByteOff
227 cgRepSizeB DoubleArg = dOUBLE_SIZE
228 cgRepSizeB LongArg   = wORD64_SIZE
229 cgRepSizeB VoidArg   = 0
230 cgRepSizeB _         = wORD_SIZE
231
232 cgRepSizeW :: CgRep -> ByteOff
233 cgRepSizeW DoubleArg = dOUBLE_SIZE `quot` wORD_SIZE
234 cgRepSizeW LongArg   = wORD64_SIZE `quot` wORD_SIZE
235 cgRepSizeW VoidArg   = 0
236 cgRepSizeW _         = 1
237
238 retAddrSizeW :: WordOff
239 retAddrSizeW = 1        -- One word
240 \end{code}
241
242 %************************************************************************
243 %*                                                                      *
244 \subsubsection[SMRep-datatype]{@SMRep@---storage manager representation}
245 %*                                                                      *
246 %************************************************************************
247
248 \begin{code}
249 data SMRep
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
254         !Int            --  # ptr words
255         !Int            --  # non-ptr words
256         ClosureType     -- closure type
257
258   | BlackHoleRep
259
260 data ClosureType        -- Corresponds 1-1 with the varieties of closures
261                         -- implemented by the RTS.  Compare with ghc/includes/ClosureTypes.h
262     = Constr
263     | ConstrNoCaf
264     | Fun
265     | Thunk
266     | ThunkSelector
267 \end{code}
268
269 Size of a closure header.
270
271 \begin{code}
272 fixedHdrSize :: WordOff
273 fixedHdrSize = sTD_HDR_SIZE + profHdrSize + granHdrSize
274
275 profHdrSize  :: WordOff
276 profHdrSize  | opt_SccProfilingOn   = pROF_HDR_SIZE
277              | otherwise            = 0
278
279 granHdrSize  :: WordOff
280 granHdrSize  | opt_GranMacros       = gRAN_HDR_SIZE
281              | otherwise            = 0
282
283 arrWordsHdrSize   :: ByteOff
284 arrWordsHdrSize   = fixedHdrSize*wORD_SIZE + sIZEOF_StgArrWords_NoHdr
285
286 arrPtrsHdrSize    :: ByteOff
287 arrPtrsHdrSize    = fixedHdrSize*wORD_SIZE + sIZEOF_StgMutArrPtrs_NoHdr
288
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
294 \end{code}
295
296 \begin{code}
297 -- IA64 mangler doesn't place tables next to code
298 tablesNextToCode :: Bool
299 #if defined(ia64_TARGET_ARCH) || defined(powerpc64_TARGET_ARCH)
300 tablesNextToCode = False
301 #else
302 tablesNextToCode = not opt_Unregisterised
303 #endif
304 \end{code}
305
306 \begin{code}
307 isStaticRep :: SMRep -> Bool
308 isStaticRep (GenericRep is_static _ _ _) = is_static
309 isStaticRep BlackHoleRep                 = False
310 \end{code}
311
312 \begin{code}
313 #include "../includes/ClosureTypes.h"
314 -- Defines CONSTR, CONSTR_1_0 etc
315
316
317 smRepClosureType :: SMRep -> ClosureType
318 smRepClosureType (GenericRep _ _ _ ty) = ty
319 smRepClosureType BlackHoleRep          = panic "smRepClosureType: black hole"
320
321 smRepClosureTypeInt :: SMRep -> Int
322 smRepClosureTypeInt (GenericRep False 1 0 Constr) = CONSTR_1_0
323 smRepClosureTypeInt (GenericRep False 0 1 Constr) = CONSTR_0_1
324 smRepClosureTypeInt (GenericRep False 2 0 Constr) = CONSTR_2_0
325 smRepClosureTypeInt (GenericRep False 1 1 Constr) = CONSTR_1_1
326 smRepClosureTypeInt (GenericRep False 0 2 Constr) = CONSTR_0_2
327 smRepClosureTypeInt (GenericRep False _ _ Constr) = CONSTR
328
329 smRepClosureTypeInt (GenericRep False 1 0 Fun) = FUN_1_0
330 smRepClosureTypeInt (GenericRep False 0 1 Fun) = FUN_0_1
331 smRepClosureTypeInt (GenericRep False 2 0 Fun) = FUN_2_0
332 smRepClosureTypeInt (GenericRep False 1 1 Fun) = FUN_1_1
333 smRepClosureTypeInt (GenericRep False 0 2 Fun) = FUN_0_2
334 smRepClosureTypeInt (GenericRep False _ _ Fun) = FUN
335
336 smRepClosureTypeInt (GenericRep False 1 0 Thunk) = THUNK_1_0
337 smRepClosureTypeInt (GenericRep False 0 1 Thunk) = THUNK_0_1
338 smRepClosureTypeInt (GenericRep False 2 0 Thunk) = THUNK_2_0
339 smRepClosureTypeInt (GenericRep False 1 1 Thunk) = THUNK_1_1
340 smRepClosureTypeInt (GenericRep False 0 2 Thunk) = THUNK_0_2
341 smRepClosureTypeInt (GenericRep False _ _ Thunk) = THUNK
342
343 smRepClosureTypeInt (GenericRep False _ _ ThunkSelector) =  THUNK_SELECTOR
344
345 smRepClosureTypeInt (GenericRep True _ _ Constr)      = CONSTR_STATIC
346 smRepClosureTypeInt (GenericRep True _ _ ConstrNoCaf) = CONSTR_NOCAF_STATIC
347 smRepClosureTypeInt (GenericRep True _ _ Fun)         = FUN_STATIC
348 smRepClosureTypeInt (GenericRep True _ _ Thunk)       = THUNK_STATIC
349
350 smRepClosureTypeInt BlackHoleRep = BLACKHOLE
351
352 smRepClosureTypeInt rep = panic "smRepClosuretypeint"
353
354
355 -- We export these ones
356 rET_SMALL     = (RET_SMALL     :: Int)
357 rET_VEC_SMALL = (RET_VEC_SMALL :: Int)
358 rET_BIG       = (RET_BIG       :: Int)
359 rET_VEC_BIG   = (RET_VEC_BIG   :: Int)
360 \end{code}
361