[project @ 1996-07-25 20:43:49 by partain]
[ghc-hetmet.git] / ghc / compiler / absCSyn / HeapOffs.lhs
index 79000d9..0958307 100644 (file)
@@ -1,5 +1,5 @@
 %
-% (c) The GRASP/AQUA Project, Glasgow University, 1992-1995
+% (c) The GRASP/AQUA Project, Glasgow University, 1992-1996
 %
 \section[HeapOffs]{Abstract C: heap offsets}
 
@@ -12,11 +12,7 @@ INTERNAL MODULE: should be accessed via @AbsCSyn.hi@.
 #include "HsVersions.h"
 
 module HeapOffs (
-#ifndef DPH
        HeapOffset,
-#else
-       HeapOffset(..), -- DPH needs to do a little peaking inside this thing.
-#endif {- Data Parallel Haskell -}
 
        zeroOff, intOff, fixedHdrSize, totHdrSize, varHdrSize,
        maxOff, addOff, subOff,
@@ -27,23 +23,23 @@ module HeapOffs (
        intOffsetIntoGoods,
 
 #if ! OMIT_NATIVE_CODEGEN
-       hpRelToInt, 
+       hpRelToInt,
 #endif
 
-       VirtualHeapOffset(..), HpRelOffset(..),
-       VirtualSpAOffset(..), VirtualSpBOffset(..),
-       SpARelOffset(..), SpBRelOffset(..)
-    ) where 
+       SYN_IE(VirtualHeapOffset), SYN_IE(HpRelOffset),
+       SYN_IE(VirtualSpAOffset), SYN_IE(VirtualSpBOffset),
+       SYN_IE(SpARelOffset), SYN_IE(SpBRelOffset)
+    ) where
 
-import ClosureInfo     -- esp. about SMReps
-import SMRep           
+IMP_Ubiq(){-uitous-}
 #if ! OMIT_NATIVE_CODEGEN
-import MachDesc
+IMPORT_DELOOPER(AbsCLoop)              ( fixedHdrSizeInWords, varHdrSizeInWords )
 #endif
-import Maybes          ( catMaybes, Maybe(..) )
-import Outputable
+
+import Maybes          ( catMaybes )
+import SMRep
 import Unpretty                -- ********** NOTE **********
-import Util
+import Util            ( panic )
 \end{code}
 
 %************************************************************************
@@ -63,7 +59,7 @@ import Util
     * Node, the ptr to the closure, pts at its info-ptr field
 -}
 data HeapOffset
-  = MkHeapOffset       
+  = MkHeapOffset
 
        FAST_INT        -- this many words...
 
@@ -88,13 +84,8 @@ data HeapOffset
 
   deriving () -- but: see `eqOff` below
 
-#if defined(__GLASGOW_HASKELL__)
 data SMRep__Int = SMRI_ SMRep Int#
 #define SMRI(a,b) (SMRI_ a b)
-#else
-type SMRep__Int = (SMRep, Int)
-#define SMRI(a,b) (a, b)
-#endif
 
 type VirtualHeapOffset = HeapOffset
 type VirtualSpAOffset  = Int
@@ -113,7 +104,7 @@ intOff IBOX(n) = MkHeapOffset n ILIT(0) [] []
 
 fixedHdrSize = MkHeapOffset ILIT(0) ILIT(1) [] []
 
-totHdrSize sm_rep 
+totHdrSize sm_rep
   = if isSpecRep sm_rep -- Tot hdr size for a spec rep is just FixedHdrSize
     then MkHeapOffset ILIT(0) ILIT(1) [] []
     else MkHeapOffset ILIT(0) ILIT(0) [] [SMRI(sm_rep, ILIT(1))]
@@ -150,7 +141,7 @@ maxOff off1@(MkHeapOffset int_offs1 fixhdr_offs1 varhdr_offs1 tothdr_offs1)
     else
         MaxHeapOffset off1 off2
   where
-    -- Normalise, by realising that each tot-hdr is really a 
+    -- Normalise, by realising that each tot-hdr is really a
     -- var-hdr plus a fixed-hdr
     n_tothdr1    = total_of tothdr_offs1
     real_fixed1  = fixhdr_offs1 _ADD_ n_tothdr1
@@ -215,7 +206,7 @@ add_HdrSizes offs1 [] = offs1
 add_HdrSizes as@(off1@(SMRI(rep1,n1)) : offs1) bs@(off2@(SMRI(rep2,n2)) : offs2)
   = if rep1 `ltSMRepHdr` rep2 then
             off1 : (add_HdrSizes offs1 bs)
-    else 
+    else
     if rep2 `ltSMRepHdr` rep1 then
             off2 : (add_HdrSizes as offs2)
     else
@@ -278,22 +269,22 @@ pprHeapOffset :: PprStyle -> HeapOffset -> Unpretty
 pprHeapOffset sty ZeroHeapOffset = uppChar '0'
 
 pprHeapOffset sty (MaxHeapOffset off1 off2)
-  = uppBesides [uppPStr SLIT("STG_MAX"), uppLparen,
-               pprHeapOffset sty off1, uppComma, pprHeapOffset sty off2,
-              uppRparen]
+  = uppBeside (uppPStr SLIT("STG_MAX"))
+      (uppParens (uppBesides [pprHeapOffset sty off1, uppComma, pprHeapOffset sty off2]))
+
 pprHeapOffset sty (AddHeapOffset off1 off2)
-  = uppBesides [uppLparen, pprHeapOffset sty off1, uppChar '+',
-                       pprHeapOffset sty off2, uppRparen]
+  = uppParens (uppBesides [pprHeapOffset sty off1, uppChar '+',
+                       pprHeapOffset sty off2])
 pprHeapOffset sty (SubHeapOffset off1 off2)
-  = uppBesides [uppLparen, pprHeapOffset sty off1, uppChar '-',
-                       pprHeapOffset sty off2, uppRparen]
+  = uppParens (uppBesides [pprHeapOffset sty off1, uppChar '-',
+                       pprHeapOffset sty off2])
 
 pprHeapOffset sty (MkHeapOffset int_offs fxdhdr_offs varhdr_offs tothdr_offs)
   = pprHeapOffsetPieces sty int_offs fxdhdr_offs varhdr_offs tothdr_offs
 \end{code}
 
 \begin{code}
-pprHeapOffsetPieces :: PprStyle 
+pprHeapOffsetPieces :: PprStyle
                    -> FAST_INT         -- Words
                    -> FAST_INT         -- Fixed hdrs
                    -> [SMRep__Int]     -- Var hdrs
@@ -323,20 +314,18 @@ pprHeapOffsetPieces sty int_offs fxdhdr_offs varhdr_offs tothdr_offs
     case (catMaybes [pp_tothdr_offs, pp_varhdr_offs, pp_fxdhdr_offs, pp_int_offs]) of
        []   -> uppChar '0'
        [pp] -> pp      -- Each blob is parenthesised if necessary
-       pps  -> uppBesides [ uppLparen, uppIntersperse (uppChar '+') pps, uppRparen ]
+       pps  -> uppParens (uppIntersperse (uppChar '+') pps)
   where
     pp_hdrs hdr_pp [] = Nothing
     pp_hdrs hdr_pp [SMRI(rep, n)] | n _EQ_ ILIT(1) = Just (uppBeside (uppStr (show rep)) hdr_pp)
-    pp_hdrs hdr_pp hdrs = Just (uppBesides [ uppLparen,
-                                           uppInterleave (uppChar '+')
-                                               (map (pp_hdr hdr_pp) hdrs),
-                                           uppRparen ])
+    pp_hdrs hdr_pp hdrs = Just (uppParens (uppInterleave (uppChar '+')
+                                               (map (pp_hdr hdr_pp) hdrs)))
 
     pp_hdr :: Unpretty -> SMRep__Int -> Unpretty
     pp_hdr pp_str (SMRI(rep, n))
       = if n _EQ_ ILIT(1) then
          uppBeside (uppStr (show rep)) pp_str
-        else
+       else
          uppBesides [uppInt IBOX(n), uppChar '*', uppStr (show rep), pp_str]
 \end{code}
 
@@ -368,20 +357,20 @@ intOffsetIntoGoods anything_else = Nothing
 \begin{code}
 #if ! OMIT_NATIVE_CODEGEN
 
-hpRelToInt :: Target -> HeapOffset -> Int
+hpRelToInt :: HeapOffset -> Int
 
-hpRelToInt target (MaxHeapOffset left right)
-  = (hpRelToInt target left) `max` (hpRelToInt target right)
+hpRelToInt ZeroHeapOffset = 0
 
-hpRelToInt target (SubHeapOffset left right)
-  = (hpRelToInt target left) - (hpRelToInt target right)
+hpRelToInt (MaxHeapOffset left right)
+  = hpRelToInt left `max` hpRelToInt right
 
-hpRelToInt target (AddHeapOffset left right)
-  = (hpRelToInt target left) + (hpRelToInt target right)
+hpRelToInt (SubHeapOffset left right)
+  = hpRelToInt left - hpRelToInt right
 
-hpRelToInt target ZeroHeapOffset = 0
+hpRelToInt (AddHeapOffset left right)
+  = hpRelToInt left + hpRelToInt right
 
-hpRelToInt target (MkHeapOffset base fhs vhs ths)
+hpRelToInt (MkHeapOffset base fhs vhs ths)
   = let
        vhs_pieces, ths_pieces :: [Int]
        fhs_off, vhs_off, ths_off :: Int
@@ -395,8 +384,8 @@ hpRelToInt target (MkHeapOffset base fhs vhs ths)
     in
     IBOX(base) + fhs_off + vhs_off + ths_off
   where
-    fhs_size   = (fixedHeaderSize target) :: Int
-    vhs_size r = (varHeaderSize target r) :: Int
+    fhs_size   = fixedHdrSizeInWords
+    vhs_size r = varHdrSizeInWords r
 
 #endif
 \end{code}