[project @ 2002-02-14 13:59:22 by simonpj]
[ghc-hetmet.git] / ghc / compiler / codeGen / CgCon.lhs
index f14ecab..3b91214 100644 (file)
@@ -22,7 +22,7 @@ import StgSyn
 
 import AbsCUtils       ( getAmodeRep )
 import CgBindery       ( getArgAmodes, bindNewToNode,
-                         bindArgsToRegs, newTempAmodeAndIdInfo,
+                         bindArgsToRegs, 
                          idInfoToAmode, stableAmodeIdInfo,
                          heapIdInfo, CgIdInfo, bindNewToStack
                        )
@@ -31,7 +31,6 @@ import CgStackery     ( mkTaggedVirtStkOffsets, freeStackSlots,
                        )
 import CgUsages                ( getRealSp, getVirtSp, setRealAndVirtualSp,
                          getSpRelOffset )
-import CgClosure       ( cgTopRhsClosure )
 import CgRetConv       ( assignRegs )
 import Constants       ( mAX_INTLIKE, mIN_INTLIKE, mAX_CHARLIKE, mIN_CHARLIKE,
                          mIN_UPD_SIZE )
@@ -39,23 +38,23 @@ import CgHeapery    ( allocDynClosure, inPlaceAllocDynClosure )
 import CgTailCall      ( performReturn, mkStaticAlgReturnCode, doTailCall,
                          mkUnboxedTupleReturnCode )
 import CLabel          ( mkClosureLabel )
-import ClosureInfo     ( mkClosureLFInfo, mkConLFInfo, mkLFArgument,
-                         layOutDynCon, layOutDynClosure,
-                         layOutStaticClosure, closureSize
+import ClosureInfo     ( mkConLFInfo, mkLFArgument, closureLFInfo,
+                         layOutDynConstr, layOutDynClosure,
+                         layOutStaticConstr, closureSize, mkStaticClosure
                        )
 import CostCentre      ( currentOrSubsumedCCS, dontCareCCS, CostCentreStack,
                          currentCCS )
-import DataCon         ( DataCon, dataConName, dataConTag, dataConTyCon,
-                         isUnboxedTupleCon, isNullaryDataCon, dataConId, dataConWrapId
+import DataCon         ( DataCon, dataConName, dataConTag, 
+                         isUnboxedTupleCon, isNullaryDataCon, dataConId, 
+                         dataConWrapId, dataConRepArity
                        )
-import Id              ( Id, idName, idType, idPrimRep )
-import Name            ( nameModule, isLocallyDefinedName )
+import Id              ( Id, idName, idPrimRep )
 import Literal         ( Literal(..) )
 import PrelInfo                ( maybeCharLikeCon, maybeIntLikeCon )
 import PrimRep         ( PrimRep(..), isFollowableRep )
 import Unique          ( Uniquable(..) )
 import Util
-import Panic           ( assertPanic, trace )
+import Outputable
 \end{code}
 
 %************************************************************************
@@ -68,38 +67,37 @@ import Panic                ( assertPanic, trace )
 cgTopRhsCon :: Id              -- Name of thing bound to this RHS
            -> DataCon          -- Id
            -> [StgArg]         -- Args
+           -> SRT
            -> FCode (Id, CgIdInfo)
-cgTopRhsCon id con args
-  = ASSERT(not dynamic_con_or_args)    -- checks for litlit args too
-    (
+cgTopRhsCon id con args srt
+  = ASSERT( not (isDllConApp con args) )       -- checks for litlit args too
+    ASSERT( args `lengthIs` dataConRepArity con )
+
        -- LAY IT OUT
     getArgAmodes args          `thenFC` \ amodes ->
 
     let
-       (closure_info, amodes_w_offsets)
-         = layOutStaticClosure name getAmodeRep amodes lf_info
+       name          = idName id
+       lf_info       = closureLFInfo closure_info
+       closure_label = mkClosureLabel name
+       (closure_info, amodes_w_offsets) 
+               = layOutStaticConstr name con getAmodeRep amodes
     in
 
        -- BUILD THE OBJECT
-    absC (CStaticClosure
-           closure_label               -- Labelled with the name on lhs of defn
-           closure_info                -- Closure is static
-           top_ccc
-           (map fst amodes_w_offsets)) -- Sorted into ptrs first, then nonptrs
-
-    ) `thenC`
+    absC (mkStaticClosure
+           closure_info
+           dontCareCCS                 -- because it's static data
+           (map fst amodes_w_offsets)  -- Sorted into ptrs first, then nonptrs
+           (nonEmptySRT srt)           -- has CAF refs
+         )                                     `thenC`
+               -- NOTE: can't use idCafInfo instead of nonEmptySRT above,
+               -- because top-level constructors that were floated by
+               -- CorePrep don't have CafInfo attached.  The SRT is more
+               -- reliable.
 
        -- RETURN
     returnFC (id, stableAmodeIdInfo id (CLbl closure_label PtrRep) lf_info)
-  where
-    lf_info        = mkConLFInfo    con
-    closure_label   = mkClosureLabel name
-    name            = idName id
-
-    top_ccc = mkCCostCentreStack dontCareCCS -- because it's static data
-
-    -- stuff needed by the assert pred only.
-    dynamic_con_or_args = isDllConApp con args
 \end{code}
 
 %************************************************************************
@@ -170,8 +168,6 @@ buildDynCon binder cc con [arg_amode]
   | maybeIntLikeCon con && in_range_int_lit arg_amode
   = returnFC (stableAmodeIdInfo binder (CIntLike arg_amode) (mkConLFInfo con))
   where
-    (temp_amode, temp_id_info) = newTempAmodeAndIdInfo binder (mkConLFInfo con)
-
     in_range_int_lit (CLit (MachInt val)) = val <= mAX_INTLIKE && val >= mIN_INTLIKE
     in_range_int_lit _other_amode        = False
 
@@ -179,8 +175,6 @@ buildDynCon binder cc con [arg_amode]
   | maybeCharLikeCon con && in_range_char_lit arg_amode
   = returnFC (stableAmodeIdInfo binder (CCharLike arg_amode) (mkConLFInfo con))
   where
-    (temp_amode, temp_id_info) = newTempAmodeAndIdInfo binder (mkConLFInfo con)
-
     in_range_char_lit (CLit (MachChar val)) = val <= mAX_CHARLIKE && val >= mIN_CHARLIKE
     in_range_char_lit _other_amode         = False
 \end{code}
@@ -193,7 +187,7 @@ buildDynCon binder ccs con args
     returnFC (heapIdInfo binder hp_off lf_info)
   where
     (closure_info, amodes_w_offsets)
-      = layOutDynClosure (idName binder) getAmodeRep args lf_info
+      = layOutDynClosure (idName binder) getAmodeRep args lf_info NoC_SRT
     lf_info = mkConLFInfo con
 
     use_cc     -- cost-centre to stick in the object
@@ -227,7 +221,9 @@ bindConArgs con args
     mapCs bind_arg args_w_offsets
    where
      bind_arg (arg, offset) = bindNewToNode arg offset mkLFArgument
-     (_, args_w_offsets) = layOutDynCon con idPrimRep args
+     (_, args_w_offsets)    = layOutDynConstr bogus_name con idPrimRep args
+
+bogus_name = panic "bindConArgs"
 \end{code}
 
 Unboxed tuples are handled slightly differently - the object is
@@ -242,8 +238,8 @@ bindUnboxedTupleComponents
 
 bindUnboxedTupleComponents args
  =  -- Assign as many components as possible to registers
-    let (arg_regs, leftovers) = assignRegs [] (map idPrimRep args)
-       (reg_args, stk_args) = splitAt (length arg_regs) args
+    let (arg_regs, _leftovers) = assignRegs [] (map idPrimRep args)
+       (reg_args, stk_args)   = splitAtList arg_regs args
     in
 
     -- Allocate the rest on the stack (ToDo: separate out pointers)
@@ -277,7 +273,8 @@ sure the @amodes@ passed don't conflict with each other.
 cgReturnDataCon :: DataCon -> [CAddrMode] -> Code
 
 cgReturnDataCon con amodes
-  = getEndOfBlockInfo  `thenFC` \ (EndOfBlockInfo args_sp sequel) ->
+  = ASSERT( amodes `lengthIs` dataConRepArity con )
+    getEndOfBlockInfo  `thenFC` \ (EndOfBlockInfo args_sp sequel) ->
 
     case sequel of
 
@@ -344,11 +341,9 @@ cgReturnDataCon con amodes
           setEndOfBlockInfo (EndOfBlockInfo new_sp (OnStack new_sp)) $
           performReturn (AbsCNop) (mkStaticAlgReturnCode con)
 
-       where (closure_info, stuff) 
-                 = layOutDynClosure (dataConName con) 
-                       getAmodeRep amodes lf_info
-
-             lf_info = mkConLFInfo con
+       where
+          (closure_info, stuff) 
+                 = layOutDynConstr (dataConName con) con getAmodeRep amodes
 
       other_sequel     -- The usual case