[project @ 2002-06-18 13:58:22 by simonpj]
[ghc-hetmet.git] / ghc / compiler / codeGen / CgExpr.lhs
index 6905285..2894de2 100644 (file)
@@ -1,7 +1,7 @@
 %
 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
 %
-% $Id: CgExpr.lhs,v 1.44 2001/09/26 15:11:50 simonpj Exp $
+% $Id: CgExpr.lhs,v 1.49 2002/06/18 13:58:23 simonpj Exp $
 %
 %********************************************************
 %*                                                     *
@@ -41,13 +41,13 @@ import Id           ( idPrimRep, idType, Id )
 import VarSet
 import PrimOp          ( primOpOutOfLine, getPrimOpResultInfo, PrimOp(..), PrimOpResultInfo(..) )
 import PrimRep         ( PrimRep(..), isFollowableRep )
-import TyCon           ( maybeTyConSingleCon,
-                         isUnboxedTupleTyCon, isEnumerationTyCon )
+import TyCon           ( isUnboxedTupleTyCon, isEnumerationTyCon )
 import Type            ( Type, typePrimRep, tyConAppArgs, tyConAppTyCon, repType )
 import Maybes          ( maybeToBool )
 import ListSetOps      ( assocMaybe )
 import Unique          ( mkBuiltinUnique )
 import BasicTypes      ( TopLevelFlag(..), RecFlag(..) )
+import Util             ( lengthIs )
 import Outputable
 \end{code}
 
@@ -150,9 +150,7 @@ cgExpr x@(StgOpApp op@(StgPrimOp primop) args res_ty)
   = tailCallPrimOp primop args
 
   | otherwise
-  = ASSERT(primop /= SeqOp) -- can't handle SeqOp
-
-    getArgAmodes args  `thenFC` \ arg_amodes ->
+  = getArgAmodes args  `thenFC` \ arg_amodes ->
 
     case (getPrimOpResultInfo primop) of
 
@@ -257,7 +255,7 @@ centre.
 cgExpr (StgSCC cc expr)
   = ASSERT(sccAbleCostCentre cc)
     costCentresC
-       SLIT("SET_CCC")
+       FSLIT("SET_CCC")
        [mkCCostCentre cc, mkIntCLit (if isSccCountCostCentre cc then 1 else 0)]
     `thenC`
     cgExpr expr
@@ -318,21 +316,27 @@ mkRhsClosure      bndr cc bi srt
                         [(con, params, use_mask,
                            (StgApp selectee [{-no args-}]))]
                         StgNoDefault))
-  |  the_fv == scrutinee                       -- Scrutinee is the only free variable
-  && maybeToBool maybe_offset                  -- Selectee is a component of the tuple
+  |  the_fv == scrutinee               -- Scrutinee is the only free variable
+  && maybeToBool maybe_offset          -- Selectee is a component of the tuple
   && offset_into_int <= mAX_SPEC_SELECTEE_SIZE -- Offset is small enough
-  = ASSERT(is_single_constructor)
+  = -- NOT TRUE: ASSERT(is_single_constructor)
+    -- The simplifier may have statically determined that the single alternative
+    -- is the only possible case and eliminated the others, even if there are
+    -- other constructors in the datatype.  It's still ok to make a selector
+    -- thunk in this case, because we *know* which constructor the scrutinee
+    -- will evaluate to.
     cgStdRhsClosure bndr cc bi [the_fv] [] body lf_info [StgVarArg the_fv]
   where
     lf_info              = mkSelectorLFInfo (idType bndr) offset_into_int 
                                                (isUpdatable upd_flag)
-    (_, params_w_offsets) = layOutDynConstr bogus_name con idPrimRep params    -- Just want the layout
+    (_, params_w_offsets) = layOutDynConstr bogus_name con idPrimRep params
+                               -- Just want the layout
     maybe_offset         = assocMaybe params_w_offsets selectee
     Just the_offset      = maybe_offset
     offset_into_int       = the_offset - fixedHdrSize
-    is_single_constructor = maybeToBool (maybeTyConSingleCon tycon)
     bogus_name           = panic "mkRhsClosure"
 \end{code}
+
 Ap thunks
 ~~~~~~~~~
 
@@ -356,7 +360,7 @@ mkRhsClosure        bndr cc bi srt
                []                      -- No args; a thunk
                body@(StgApp fun_id args)
 
-  | length args + 1 == arity
+  | args `lengthIs` (arity-1)
        && all isFollowableRep (map idPrimRep fvs) 
        && isUpdatable upd_flag
        && arity <= mAX_SPEC_AP_SIZE