[project @ 1998-11-26 09:17:22 by sof]
[ghc-hetmet.git] / ghc / compiler / absCSyn / HeapOffs.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1996
3 %
4 \section[HeapOffs]{Abstract C: heap offsets}
5
6 Part of ``Abstract C.''  Heap offsets---main point: they are {\em
7 symbolic}---are sufficiently turgid that they get their own module.
8
9 INTERNAL MODULE: should be accessed via @AbsCSyn.hi@.
10
11 \begin{code}
12 module HeapOffs (
13         HeapOffset,
14
15         zeroOff, intOff, fixedHdrSize, totHdrSize, varHdrSize,
16         maxOff, addOff, subOff,
17         isZeroOff, possiblyEqualHeapOffset,
18
19         pprHeapOffset,
20
21         intOffsetIntoGoods,
22
23 #if ! OMIT_NATIVE_CODEGEN
24         hpRelToInt,
25 #endif
26
27         VirtualHeapOffset, HpRelOffset,
28         VirtualSpAOffset, VirtualSpBOffset,
29         SpARelOffset, SpBRelOffset
30     ) where
31
32 #include "HsVersions.h"
33
34 #if ! OMIT_NATIVE_CODEGEN
35 import {-# SOURCE #-} MachMisc
36 #endif
37
38 import Maybes           ( catMaybes )
39 import SMRep
40 import Util             ( panic )
41 import Outputable
42 import GlaExts          ( Int(..), Int#, (+#), negateInt#, (<=#), (>=#), (==#) )
43 \end{code}
44
45 %************************************************************************
46 %*                                                                      *
47 \subsection[Offsets-Heap-and-others]{Offsets, Heap and otherwise}
48 %*                                                                      *
49 %************************************************************************
50
51 \begin{code}
52 {-
53     < fixed-hdr-size> < var-hdr-size  >
54     ---------------------------------------------------------------------
55     |info|    |      |   |  |  |   |  | ptrs... | nonptrs ... | slop.... |
56     ---------------------------------------------------------------------
57     <------------- header ------------>
58
59     * Node, the ptr to the closure, pts at its info-ptr field
60 -}
61 data HeapOffset
62   = MkHeapOffset
63
64         FAST_INT        -- this many words...
65
66         FAST_INT        -- PLUS: this many FixedHdrSizes
67
68         [SMRep__Int]    -- PLUS: for each elem in this list:
69                         --      "Int" VarHdrSizes for rep "SMRep"
70                         -- *sorted* by SMRep
71                         -- We never have any SpecReps in here, because their
72                         --      VarHdrSize is zero
73
74         [SMRep__Int]    -- PLUS: for each elem in this list:
75                         --      "Int" TotHdrSizes for rep "SMRep"
76                         -- *sorted* by SMRep
77                         -- We never have any SpecReps in here, because
78                         --      their TotHdrSize is just FixedHdrSize
79
80   | MaxHeapOffset HeapOffset HeapOffset
81   | SubHeapOffset HeapOffset HeapOffset
82   | AddHeapOffset HeapOffset HeapOffset
83   | ZeroHeapOffset
84
85   deriving () -- but: see `eqOff` below
86
87 data SMRep__Int = SMRI_ SMRep Int#
88 #define SMRI(a,b) (SMRI_ a b)
89
90 type VirtualHeapOffset  = HeapOffset
91 type VirtualSpAOffset   = Int
92 type VirtualSpBOffset   = Int
93
94 type HpRelOffset        = HeapOffset
95 type SpARelOffset       = Int
96 type SpBRelOffset       = Int
97 \end{code}
98
99 Interface fns for HeapOffsets:
100 \begin{code}
101 zeroOff = ZeroHeapOffset
102
103 intOff IBOX(n) = MkHeapOffset n ILIT(0) [] []
104
105 fixedHdrSize = MkHeapOffset ILIT(0) ILIT(1) [] []
106
107 totHdrSize sm_rep
108   = if isSpecRep sm_rep -- Tot hdr size for a spec rep is just FixedHdrSize
109     then MkHeapOffset ILIT(0) ILIT(1) [] []
110     else MkHeapOffset ILIT(0) ILIT(0) [] [SMRI(sm_rep, ILIT(1))]
111
112 varHdrSize sm_rep
113   = if isSpecRep sm_rep
114     then zeroOff
115     else MkHeapOffset ILIT(0) ILIT(0) [SMRI(sm_rep, ILIT(1))] []
116 \end{code}
117
118 %************************************************************************
119 %*                                                                      *
120 \subsubsection[Heap-offset-arithmetic]{Heap offset arithmetic}
121 %*                                                                      *
122 %************************************************************************
123
124 \begin{code}
125 -- For maxOff we do our best when we have something simple to deal with
126 maxOff ZeroHeapOffset off2 = off2
127 maxOff off1 ZeroHeapOffset = off1
128 maxOff off1@(MkHeapOffset int_offs1 fixhdr_offs1 varhdr_offs1 tothdr_offs1)
129        off2@(MkHeapOffset int_offs2 fixhdr_offs2 varhdr_offs2 tothdr_offs2)
130   = if (int_offs1 _LE_ int_offs2) &&
131        (real_fixed1 _LE_ real_fixed2) &&
132        (all negative_or_zero difference_of_real_varhdrs)
133     then
134          off2
135     else
136     if (int_offs2 _LE_ int_offs1) &&
137        (real_fixed2 _LE_ real_fixed1) &&
138        (all positive_or_zero difference_of_real_varhdrs)
139     then
140          off1
141     else
142          MaxHeapOffset off1 off2
143   where
144     -- Normalise, by realising that each tot-hdr is really a
145     -- var-hdr plus a fixed-hdr
146     n_tothdr1    = total_of tothdr_offs1
147     real_fixed1  = fixhdr_offs1 _ADD_ n_tothdr1
148     real_varhdr1 = add_HdrSizes varhdr_offs1 tothdr_offs1
149
150     n_tothdr2    = total_of tothdr_offs2
151     real_fixed2  = fixhdr_offs2 _ADD_ n_tothdr2
152     real_varhdr2 = add_HdrSizes varhdr_offs2 tothdr_offs2
153
154     -- Take the difference of the normalised var-hdrs
155     difference_of_real_varhdrs
156       = add_HdrSizes real_varhdr1 (map negate_HdrSize real_varhdr2)
157       where
158         negate_HdrSize :: SMRep__Int -> SMRep__Int
159         negate_HdrSize SMRI(rep,n) = SMRI(rep, (_NEG_ n))
160
161     positive_or_zero SMRI(rep,n) = n _GE_ ILIT(0)
162     negative_or_zero SMRI(rep,n) = n _LE_ ILIT(0)
163
164     total_of []                 = ILIT(0)
165     total_of (SMRI(rep,n):offs) = n _ADD_ total_of offs
166
167 maxOff other_off1 other_off2 = MaxHeapOffset other_off1 other_off2
168
169 ------------------------------------------------------------------
170
171 subOff off1 ZeroHeapOffset = off1
172 subOff off1
173        (MkHeapOffset int_offs2 fxdhdr_offs2 varhdr_offs2 tothdr_offs2)
174   = addOff off1
175           (MkHeapOffset (_NEG_ int_offs2)
176                         (_NEG_ fxdhdr_offs2)
177                         (map negate_HdrSize varhdr_offs2)
178                         (map negate_HdrSize tothdr_offs2))
179   where
180     negate_HdrSize :: SMRep__Int -> SMRep__Int
181     negate_HdrSize SMRI(rep,n) = SMRI(rep,(_NEG_ n))
182
183 subOff other_off1 other_off2 = SubHeapOffset other_off1 other_off2
184
185 ------------------------------------------------------------------
186
187 addOff ZeroHeapOffset off2 = off2
188 addOff off1 ZeroHeapOffset = off1
189 addOff (MkHeapOffset int_offs1 fxdhdr_offs1 varhdr_offs1 tothdr_offs1)
190        (MkHeapOffset int_offs2 fxdhdr_offs2 varhdr_offs2 tothdr_offs2)
191   = MkHeapOffset
192         (int_offs1    _ADD_ int_offs2)
193         (fxdhdr_offs1 _ADD_ fxdhdr_offs2)
194         (add_HdrSizes varhdr_offs1 varhdr_offs2)
195         (add_HdrSizes tothdr_offs1 tothdr_offs2)
196
197 addOff other_off1 other_off2 = AddHeapOffset other_off1 other_off2
198
199 ------------------------------------------------------------------
200 -- not exported:
201 --
202 add_HdrSizes :: [SMRep__Int] -> [SMRep__Int] -> [SMRep__Int]
203
204 add_HdrSizes [] offs2 = offs2
205 add_HdrSizes offs1 [] = offs1
206 add_HdrSizes as@(off1@(SMRI(rep1,n1)) : offs1) bs@(off2@(SMRI(rep2,n2)) : offs2)
207   = if rep1 `ltSMRepHdr` rep2 then
208              off1 : (add_HdrSizes offs1 bs)
209     else
210     if rep2 `ltSMRepHdr` rep1 then
211              off2 : (add_HdrSizes as offs2)
212     else
213     let
214         n1_plus_n2 = n1 _ADD_ n2
215     in
216     -- So they are the same rep
217     if n1_plus_n2 _EQ_ ILIT(0) then
218         add_HdrSizes offs1 offs2
219     else
220         (SMRI(rep1, n1_plus_n2)) : (add_HdrSizes offs1 offs2)
221 \end{code}
222
223 \begin{code}
224 isZeroOff :: HeapOffset -> Bool
225 isZeroOff ZeroHeapOffset = True
226 isZeroOff (MaxHeapOffset off1 off2) = isZeroOff off1 && isZeroOff off2
227
228 isZeroOff (AddHeapOffset off1 off2) = isZeroOff off1 && isZeroOff off2
229         -- This assumes that AddHeapOffset only has positive arguments
230
231 isZeroOff (MkHeapOffset int_offs fxdhdr_offs varhdr_offs tothdr_offs)
232   = int_offs _EQ_ ILIT(0) && fxdhdr_offs _EQ_ ILIT(0) &&
233     null varhdr_offs && null tothdr_offs
234
235 isZeroOff (SubHeapOffset off1 off2) = panic "Can't say if a SubHeapOffset is zero"
236 \end{code}
237
238 @possiblyEqualHeapOffset@ tells if two heap offsets might be equal.
239 It has to be conservative, but the situation in which it is used
240 (@doSimultaneously@) makes it likely to give a good answer.
241
242 \begin{code}
243 possiblyEqualHeapOffset :: HeapOffset -> HeapOffset -> Bool
244 possiblyEqualHeapOffset o1 o2
245  = case (o1 `subOff` o2) of
246
247         SubHeapOffset _ _ -> True                       -- Very conservative
248
249         diff              -> not (isZeroOff diff)       -- Won't be any SubHeapOffsets in diff
250                                                         -- NB: this claim depends on the use of
251                                                         -- heap offsets, so this defn might need
252                                                         -- to be elaborated.
253
254 \end{code}
255
256 %************************************************************************
257 %*                                                                      *
258 \subsection[HeapOffs-printing]{Printing heap offsets}
259 %*                                                                      *
260 %************************************************************************
261
262 IMPORTANT: @pprHeapOffset@ and @pprHeapOffsetPieces@ guarantee to
263 print either a single value, or a parenthesised value.  No need for
264 the caller to parenthesise.
265
266 \begin{code}
267 pprHeapOffset :: HeapOffset -> SDoc
268
269 pprHeapOffset ZeroHeapOffset = char '0'
270
271 pprHeapOffset (MaxHeapOffset off1 off2)
272   = (<>) (ptext SLIT("STG_MAX"))
273       (parens (hcat [pprHeapOffset off1, comma, pprHeapOffset off2]))
274
275 pprHeapOffset (AddHeapOffset off1 off2)
276   = parens (hcat [pprHeapOffset off1, char '+',
277                         pprHeapOffset off2])
278 pprHeapOffset (SubHeapOffset off1 off2)
279   = parens (hcat [pprHeapOffset off1, char '-',
280                         pprHeapOffset off2])
281
282 pprHeapOffset (MkHeapOffset int_offs fxdhdr_offs varhdr_offs tothdr_offs)
283   = pprHeapOffsetPieces int_offs fxdhdr_offs varhdr_offs tothdr_offs
284 \end{code}
285
286 \begin{code}
287 pprHeapOffsetPieces :: FAST_INT         -- Words
288                     -> FAST_INT         -- Fixed hdrs
289                     -> [SMRep__Int]     -- Var hdrs
290                     -> [SMRep__Int]     -- Tot hdrs
291                     -> SDoc
292
293 pprHeapOffsetPieces n ILIT(0) [] [] = int IBOX(n) -- Deals with zero case too
294
295 pprHeapOffsetPieces int_offs fxdhdr_offs varhdr_offs tothdr_offs
296   = let pp_int_offs =
297             if int_offs _EQ_ ILIT(0)
298             then Nothing
299             else Just (int IBOX(int_offs))
300
301         pp_fxdhdr_offs =
302             if fxdhdr_offs _EQ_ ILIT(0) then
303                 Nothing
304             else if fxdhdr_offs _EQ_ ILIT(1) then
305                 Just (ptext SLIT("_FHS"))
306             else
307                 Just (hcat [text "(", ptext SLIT("_FHS*"), int IBOX(fxdhdr_offs), text ")"])
308
309         pp_varhdr_offs = pp_hdrs (ptext SLIT("_VHS")) varhdr_offs
310
311         pp_tothdr_offs = pp_hdrs (ptext SLIT("_HS")) tothdr_offs
312     in
313     case (catMaybes [pp_tothdr_offs, pp_varhdr_offs, pp_fxdhdr_offs, pp_int_offs]) of
314         []   -> char '0'
315         [pp] -> pp      -- Each blob is parenthesised if necessary
316         pps  -> text "(" <> (hcat (punctuate (char '+') pps)) <> text ")"
317   where
318     pp_hdrs hdr_pp [] = Nothing
319     pp_hdrs hdr_pp [SMRI(rep, n)] | n _EQ_ ILIT(1) = Just ((<>) (text (show rep)) hdr_pp)
320     pp_hdrs hdr_pp hdrs = Just (parens (hsep (punctuate (char '+')
321                                                 (map (pp_hdr hdr_pp) hdrs))))
322
323     pp_hdr :: SDoc -> SMRep__Int -> SDoc
324     pp_hdr pp_str (SMRI(rep, n))
325       = if n _EQ_ ILIT(1) then
326           (<>) (text (show rep)) pp_str
327         else
328           hcat [int IBOX(n), char '*', text (show rep), pp_str]
329 \end{code}
330
331 %************************************************************************
332 %*                                                                      *
333 \subsection[HeapOffs-conversion]{Converting heap offsets to words}
334 %*                                                                      *
335 %************************************************************************
336
337 @intOffsetIntoGoods@ and @hpRelToInt@ convert HeapOffsets into Ints.
338
339 @intOffsetIntoGoods@ {\em tries} to convert a HeapOffset in a SPEC
340 closure into an Int, returning the (0-origin) index from the beginning
341 of the ``goods'' in the closure.  [SPECs don't have VHSs, by
342 definition, so the index is merely ignoring the FHS].
343
344 @hpRelToInt@ is for the native code-generator(s); it is courtesy of
345 Jon Hill and the DAP code generator.  We've just abstracted away some
346 of the implementation-dependent bits.
347
348 \begin{code}
349 intOffsetIntoGoods :: HeapOffset -> Maybe Int
350
351 intOffsetIntoGoods (MkHeapOffset n ILIT(1){-FHS-} [{-no VHSs-}] [{-no totHSs-}])
352   = Just IBOX(n)
353 intOffsetIntoGoods anything_else = Nothing
354 \end{code}
355
356 \begin{code}
357 #if ! OMIT_NATIVE_CODEGEN
358
359 hpRelToInt :: HeapOffset -> Int
360
361 hpRelToInt ZeroHeapOffset = 0
362
363 hpRelToInt (MaxHeapOffset left right)
364   = hpRelToInt left `max` hpRelToInt right
365
366 hpRelToInt (SubHeapOffset left right)
367   = hpRelToInt left - hpRelToInt right
368
369 hpRelToInt (AddHeapOffset left right)
370   = hpRelToInt left + hpRelToInt right
371
372 hpRelToInt (MkHeapOffset base fhs vhs ths)
373   = let
374         vhs_pieces, ths_pieces :: [Int]
375         fhs_off, vhs_off, ths_off :: Int
376
377         vhs_pieces = map (\ (SMRI(r, n)) -> vhs_size r * IBOX(n)) vhs
378         ths_pieces = map (\ (SMRI(r, n)) -> (fhs_size + vhs_size r) * IBOX(n)) ths
379
380         fhs_off = fhs_size * IBOX(fhs)
381         vhs_off = sum vhs_pieces
382         ths_off = sum ths_pieces
383     in
384     IBOX(base) + fhs_off + vhs_off + ths_off
385   where
386     fhs_size   = fixedHdrSizeInWords
387     vhs_size r = varHdrSizeInWords r
388
389 #endif
390 \end{code}