Make various assertions work when !DEBUG
[ghc-hetmet.git] / compiler / codeGen / CgUtils.hs
index c66fc9e..260248d 100644 (file)
@@ -6,6 +6,13 @@
 --
 -----------------------------------------------------------------------------
 
+{-# OPTIONS -w #-}
+-- The above warning supression flag is a temporary kludge.
+-- While working on this module you are encouraged to remove it and fix
+-- any warnings in the module. See
+--     http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings
+-- for details
+
 module CgUtils (
        addIdReps,
        cgLit,
@@ -22,12 +29,17 @@ module CgUtils (
         callerSaveVolatileRegs, get_GlobalReg_addr,
 
        cmmAndWord, cmmOrWord, cmmNegate, cmmEqWord, cmmNeWord,
+        cmmUGtWord,
        cmmOffsetExprW, cmmOffsetExprB,
        cmmRegOffW, cmmRegOffB,
        cmmLabelOffW, cmmLabelOffB,
        cmmOffsetW, cmmOffsetB,
        cmmOffsetLitW, cmmOffsetLitB,
        cmmLoadIndexW,
+        cmmConstrTag, cmmConstrTag1,
+
+        tagForCon, tagCons, isSmallFamily,
+        cmmUntag, cmmIsTagged, cmmGetTag,
 
        addToMem, addToMemE,
        mkWordCLit,
@@ -43,6 +55,7 @@ module CgUtils (
 
 import CgMonad
 import TyCon
+import DataCon
 import Id
 import Constants
 import SMRep
@@ -164,6 +177,9 @@ cmmEqWord  e1 e2 = CmmMachOp mo_wordEq  [e1, e2]
 cmmULtWord e1 e2 = CmmMachOp mo_wordULt [e1, e2]
 cmmUGeWord e1 e2 = CmmMachOp mo_wordUGe [e1, e2]
 cmmUGtWord e1 e2 = CmmMachOp mo_wordUGt [e1, e2]
+--cmmShlWord e1 e2 = CmmMachOp mo_wordShl [e1, e2]
+--cmmUShrWord e1 e2 = CmmMachOp mo_wordUShr [e1, e2]
+cmmSubWord e1 e2 = CmmMachOp mo_wordSub [e1, e2]
 
 cmmNegate :: CmmExpr -> CmmExpr
 cmmNegate (CmmLit (CmmInt n rep)) = CmmLit (CmmInt (-n) rep)
@@ -172,6 +188,57 @@ cmmNegate e                          = CmmMachOp (MO_S_Neg (cmmExprRep e)) [e]
 blankWord :: CmmStatic
 blankWord = CmmUninitialised wORD_SIZE
 
+-- Tagging --
+-- Tag bits mask
+--cmmTagBits = CmmLit (mkIntCLit tAG_BITS)
+cmmTagMask = CmmLit (mkIntCLit tAG_MASK)
+cmmPointerMask = CmmLit (mkIntCLit (complement tAG_MASK))
+
+-- Used to untag a possibly tagged pointer
+-- A static label need not be untagged
+cmmUntag e@(CmmLit (CmmLabel _)) = e
+-- Default case
+cmmUntag e = (e `cmmAndWord` cmmPointerMask)
+
+cmmGetTag e = (e `cmmAndWord` cmmTagMask)
+
+-- Test if a closure pointer is untagged
+cmmIsTagged e = (e `cmmAndWord` cmmTagMask)
+                 `cmmNeWord` CmmLit zeroCLit
+
+cmmConstrTag e = (e `cmmAndWord` cmmTagMask) `cmmSubWord` (CmmLit (mkIntCLit 1))
+-- Get constructor tag, but one based.
+cmmConstrTag1 e = e `cmmAndWord` cmmTagMask
+
+{-
+   The family size of a data type (the number of constructors)
+   can be either:
+    * small, if the family size < 2**tag_bits
+    * big, otherwise.
+
+   Small families can have the constructor tag in the tag
+   bits.
+   Big families only use the tag value 1 to represent
+   evaluatedness.
+-}
+isSmallFamily fam_size = fam_size <= mAX_PTR_TAG
+
+tagForCon con = tag
+    where
+    con_tag           = dataConTagZ con
+    fam_size   = tyConFamilySize (dataConTyCon con)
+    tag | isSmallFamily fam_size = con_tag + 1
+        | otherwise              = 1
+
+--Tag an expression, to do: refactor, this appears in some other module.
+tagCons con expr = cmmOffsetB expr (tagForCon con)
+
+-- Copied from CgInfoTbls.hs
+-- We keep the *zero-indexed* tag in the srt_len field of the info
+-- table of a data constructor.
+dataConTagZ :: DataCon -> ConTagZ
+dataConTagZ con = dataConTag con - fIRST_TAG
+
 -----------------------
 --     Making literals
 
@@ -219,11 +286,11 @@ addToMemE rep ptr n
 --
 -------------------------------------------------------------------------
 
-tagToClosure :: PackageId -> TyCon -> CmmExpr -> CmmExpr
-tagToClosure this_pkg tycon tag
+tagToClosure :: TyCon -> CmmExpr -> CmmExpr
+tagToClosure tycon tag
   = CmmLoad (cmmOffsetExprW closure_tbl tag) wordRep
   where closure_tbl = CmmLit (CmmLabel lbl)
-       lbl = mkClosureTableLabel this_pkg (tyConName tycon)
+       lbl = mkClosureTableLabel (tyConName tycon)
 
 -------------------------------------------------------------------------
 --
@@ -281,7 +348,7 @@ emitRtsCallWithResult res hint fun args safe
 
 -- Make a call to an RTS C procedure
 emitRtsCall'
-   :: CmmHintFormals
+   :: CmmFormals
    -> LitString
    -> [(CmmExpr,MachHint)]
    -> Maybe [GlobalReg]
@@ -292,11 +359,11 @@ emitRtsCall' res fun args vols safe = do
             then getSRTInfo >>= (return . CmmSafe)
             else return CmmUnsafe
   stmtsC caller_save
-  stmtC (CmmCall target res args safety)
+  stmtC (CmmCall target res args safety CmmMayReturn)
   stmtsC caller_load
   where
     (caller_save, caller_load) = callerSaveVolatileRegs vols
-    target   = CmmForeignCall fun_expr CCallConv
+    target   = CmmCallee fun_expr CCallConv
     fun_expr = mkLblExpr (mkRtsCodeLabel fun)
 
 -----------------------------------------------------------------------------
@@ -493,7 +560,7 @@ emitDataLits :: CLabel -> [CmmLit] -> Code
 emitDataLits lbl lits
   = emitData Data (CmmDataLabel lbl : map CmmStaticLit lits)
 
-mkDataLits :: CLabel -> [CmmLit] -> GenCmmTop CmmStatic info stmt
+mkDataLits :: CLabel -> [CmmLit] -> GenCmmTop CmmStatic info graph
 -- Emit a data-segment data block
 mkDataLits lbl lits
   = CmmData Data (CmmDataLabel lbl : map CmmStaticLit lits)
@@ -508,7 +575,7 @@ emitRODataLits lbl lits
         needsRelocation (CmmLabelOff _ _) = True
         needsRelocation _                 = False
 
-mkRODataLits :: CLabel -> [CmmLit] -> GenCmmTop CmmStatic info stmt
+mkRODataLits :: CLabel -> [CmmLit] -> GenCmmTop CmmStatic info graph
 mkRODataLits lbl lits
   = CmmData section (CmmDataLabel lbl : map CmmStaticLit lits)
   where section | any needsRelocation lits = RelocatableReadOnlyData
@@ -554,10 +621,10 @@ assignPtrTemp e
                            ; return (CmmReg (CmmLocal reg)) }
 
 newNonPtrTemp :: MachRep -> FCode LocalReg
-newNonPtrTemp rep = do { uniq <- newUnique; return (LocalReg uniq rep KindNonPtr) }
+newNonPtrTemp rep = do { uniq <- newUnique; return (LocalReg uniq rep GCKindNonPtr) }
 
 newPtrTemp :: MachRep -> FCode LocalReg
-newPtrTemp rep = do { uniq <- newUnique; return (LocalReg uniq rep KindPtr) }
+newPtrTemp rep = do { uniq <- newUnique; return (LocalReg uniq rep GCKindPtr) }
 
 
 -------------------------------------------------------------------------