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