[project @ 2001-05-16 12:49:59 by simonmar]
[ghc-hetmet.git] / ghc / compiler / basicTypes / MkId.lhs
index e5a2a49..dae32df 100644 (file)
@@ -31,6 +31,7 @@ module MkId (
 #include "HsVersions.h"
 
 
+import BasicTypes      ( Arity )
 import TysPrim         ( openAlphaTyVars, alphaTyVar, alphaTy, 
                          intPrimTy, realWorldStatePrimTy
                        )
@@ -38,7 +39,7 @@ import TysWiredIn     ( charTy, mkListTy )
 import PrelNames       ( pREL_ERR, pREL_GHC )
 import PrelRules       ( primOpRule )
 import Rules           ( addRule )
-import Type            ( Type, ThetaType, mkDictTy, mkDictTys, mkTyConApp, mkTyVarTys,
+import Type            ( Type, ThetaType, mkDictTy, mkPredTys, mkTyConApp, mkTyVarTys,
                          mkFunTys, mkFunTy, mkSigmaTy, splitSigmaTy, 
                          isUnLiftedType, mkForAllTys, mkTyVarTy, tyVarsOfType,
                          splitFunTys, splitForAllTys, mkPredTy
@@ -71,11 +72,12 @@ import Id           ( idType, mkGlobalId, mkVanillaGlobal,
                          mkTemplateLocals, mkTemplateLocalsNum,
                          mkTemplateLocal, idCprInfo
                        )
-import IdInfo          ( IdInfo, vanillaIdInfo, noTyGenIdInfo, noCafOrTyGenIdInfo,
-                         exactArity, setUnfoldingInfo, setCafInfo, setCprInfo,
-                         setArityInfo, setSpecInfo, 
+import IdInfo          ( IdInfo, noCafNoTyGenIdInfo,
+                         exactArity, setUnfoldingInfo, setCprInfo,
+                         setArityInfo, setSpecInfo,  setCgInfo,
                          mkStrictnessInfo, setStrictnessInfo,
-                         GlobalIdDetails(..), CafInfo(..), CprInfo(..)
+                         GlobalIdDetails(..), CafInfo(..), CprInfo(..), 
+                         CgInfo(..), setCgArity
                        )
 import FieldLabel      ( mkFieldLabel, fieldLabelName, 
                          firstFieldLabelTag, allFieldLabelTags, fieldLabelType
@@ -117,7 +119,7 @@ wiredInIds
     , rEC_CON_ERROR_ID
     , rEC_UPD_ERROR_ID
 
-       -- These two can't be defined in Haskell
+       -- These three can't be defined in Haskell
     , realWorldPrimId
     , unsafeCoerceId
     , getTagId
@@ -137,7 +139,8 @@ mkDataConId :: Name -> DataCon -> Id
 mkDataConId work_name data_con
   = mkGlobalId (DataConId data_con) work_name (dataConRepType data_con) info
   where
-    info = noCafOrTyGenIdInfo
+    info = noCafNoTyGenIdInfo
+          `setCgArity`         arity
           `setArityInfo`       exactArity arity
           `setStrictnessInfo`  strict_info
           `setCprInfo`         cpr_info
@@ -149,10 +152,22 @@ mkDataConId work_name data_con
     tycon = dataConTyCon data_con
     cpr_info | isProductTyCon tycon && 
               isDataTyCon tycon    &&
-              arity > 0                = ReturnsCPR
+              arity > 0            &&
+              arity <= mAX_CPR_SIZE    = ReturnsCPR
             | otherwise                = NoCPRInfo
        -- ReturnsCPR is only true for products that are real data types;
        -- that is, not unboxed tuples or newtypes
+
+mAX_CPR_SIZE :: Arity
+mAX_CPR_SIZE = 10
+-- We do not treat very big tuples as CPR-ish:
+--     a) for a start we get into trouble because there aren't 
+--        "enough" unboxed tuple types (a tiresome restriction, 
+--        but hard to fix), 
+--     b) more importantly, big unboxed tuples get returned mainly
+--        on the stack, and are often then allocated in the heap
+--        by the caller.  So doing CPR for them may in fact make
+--        things worse.
 \end{code}
 
 The wrapper for a constructor is an ordinary top-level binding that evaluates
@@ -199,11 +214,13 @@ mkDataConWrapId data_con
     wrap_id = mkGlobalId (DataConWrapId data_con) (dataConName data_con) wrap_ty info
     work_id = dataConId data_con
 
-    info = noCafOrTyGenIdInfo
+    info = noCafNoTyGenIdInfo
           `setUnfoldingInfo`   mkTopUnfolding (mkInlineMe wrap_rhs)
           `setCprInfo`         cpr_info
                -- The Cpr info can be important inside INLINE rhss, where the
                -- wrapper constructor isn't inlined
+          `setCgArity`         arity
+               -- The NoCaf-ness is set by noCafNoTyGenIdInfo
           `setArityInfo`       exactArity arity
                -- It's important to specify the arity, so that partial
                -- applications are treated as values
@@ -253,8 +270,8 @@ mkDataConWrapId data_con
     (tyvars, theta, ex_tyvars, ex_theta, orig_arg_tys, tycon) = dataConSig data_con
     all_tyvars   = tyvars ++ ex_tyvars
 
-    dict_tys     = mkDictTys theta
-    ex_dict_tys  = mkDictTys ex_theta
+    dict_tys     = mkPredTys theta
+    ex_dict_tys  = mkPredTys ex_theta
     all_arg_tys  = dict_tys ++ ex_dict_tys ++ orig_arg_tys
     result_ty    = mkTyConApp tycon (mkTyVarTys tyvars)
 
@@ -357,8 +374,8 @@ mkRecordSelId tycon field_label unpack_id unpackUtf8_id
 
     tycon_theta        = tyConTheta tycon      -- The context on the data decl
                                        --   eg data (Eq a, Ord b) => T a b = ...
-    dict_tys  = [mkDictTy cls tys | (cls, tys) <- tycon_theta, 
-                                   needed_dict (cls, tys)]
+    dict_tys  = [mkPredTy pred | pred <- tycon_theta, 
+                                needed_dict pred]
     needed_dict pred = or [ pred `elem` (dataConTheta dc) 
                          | (DataAlt dc, _, _) <- the_alts]
     n_dict_tys = length dict_tys
@@ -393,8 +410,8 @@ mkRecordSelId tycon field_label unpack_id unpackUtf8_id
                   mkFunTy data_ty field_tau
       
     arity = 1 + n_dict_tys + n_field_dict_tys
-    info = noTyGenIdInfo
-          `setCafInfo`         caf_info
+    info = noCafNoTyGenIdInfo
+          `setCgInfo`          (CgInfo arity caf_info)
           `setArityInfo`       exactArity arity
           `setUnfoldingInfo`   unfolding       
        -- ToDo: consider adding further IdInfo
@@ -439,9 +456,12 @@ mkRecordSelId tycon field_label unpack_id unpackUtf8_id
                    body              = mkVarApps (mkVarApps (Var the_arg_id) field_tyvars) field_dict_ids
                    strict_marks      = dataConStrictMarks data_con
                    (expr, real_args) = rebuildConArgs data_con arg_ids strict_marks body
-                                                      (length arg_ids + 1)
+                                                      unpack_base
        where
             arg_ids = mkTemplateLocalsNum field_base (dataConInstOrigArgTys data_con tyvar_tys)
+
+           unpack_base = field_base + length arg_ids
+
                                -- arity+1 avoids all shadowing
            maybe_the_arg_id  = assocMaybe (field_lbls `zip` arg_ids) field_label
            field_lbls        = dataConFieldLabels data_con
@@ -519,7 +539,8 @@ mkDictSelId name clas
     field_lbl = mkFieldLabel name tycon ty tag
     tag       = assoc "MkId.mkDictSelId" (classSelIds clas `zip` allFieldLabelTags) sel_id
 
-    info      = noCafOrTyGenIdInfo
+    info      = noCafNoTyGenIdInfo
+               `setCgArity`        1
                `setArityInfo`      exactArity 1
                `setUnfoldingInfo`  unfolding
                
@@ -563,12 +584,14 @@ mkPrimOpId prim_op
     name = mkPrimOpIdName prim_op
     id   = mkGlobalId (PrimOpId prim_op) name ty info
                
-    info = noCafOrTyGenIdInfo
+    info = noCafNoTyGenIdInfo
           `setSpecInfo`        rules
+          `setCgArity`         arity
           `setArityInfo`       exactArity arity
           `setStrictnessInfo`  strict_info
 
-    rules = addRule emptyCoreRules id (primOpRule prim_op)
+    rules = maybe emptyCoreRules (addRule emptyCoreRules id)
+               (primOpRule prim_op)
 
 
 -- For each ccall we manufacture a separate CCallOpId, giving it
@@ -594,7 +617,8 @@ mkCCallOpId uniq ccall ty
     name    = mkCCallName uniq occ_str
     prim_op = CCallOp ccall
 
-    info = noCafOrTyGenIdInfo
+    info = noCafNoTyGenIdInfo
+          `setCgArity`         arity
           `setArityInfo`       exactArity arity
           `setStrictnessInfo`  strict_info
 
@@ -613,7 +637,7 @@ mkCCallOpId uniq ccall ty
 
 \begin{code}
 mkDefaultMethodId dm_name ty
-  = mkVanillaGlobal dm_name ty noTyGenIdInfo
+  = mkVanillaGlobal dm_name ty noCafNoTyGenIdInfo
 
 mkDictFunId :: Name            -- Name to use for the dict fun;
            -> Class 
@@ -623,12 +647,9 @@ mkDictFunId :: Name                -- Name to use for the dict fun;
            -> Id
 
 mkDictFunId dfun_name clas inst_tyvars inst_tys dfun_theta
-  = mkVanillaGlobal dfun_name dfun_ty noTyGenIdInfo
+  = mkVanillaGlobal dfun_name dfun_ty noCafNoTyGenIdInfo
   where
     dfun_ty = mkSigmaTy inst_tyvars dfun_theta (mkDictTy clas inst_tys)
-    info     = noTyGenIdInfo
-             -- Type is wired-in (see comment at TcClassDcl.tcClassSig),
-             -- so do not generalise it
 
 {-  1 dec 99: disable the Mark Jones optimisation for the sake
     of compatibility with Hugs.
@@ -680,7 +701,7 @@ another gun with which to shoot yourself in the foot.
 unsafeCoerceId
   = pcMiscPrelId unsafeCoerceIdKey pREL_GHC SLIT("unsafeCoerce#") ty info
   where
-    info = noCafOrTyGenIdInfo `setUnfoldingInfo` mkCompulsoryUnfolding rhs
+    info = noCafNoTyGenIdInfo `setUnfoldingInfo` mkCompulsoryUnfolding rhs
           
 
     ty  = mkForAllTys [openAlphaTyVar,openBetaTyVar]
@@ -698,7 +719,7 @@ evaluate its argument and call the dataToTag# primitive.
 getTagId
   = pcMiscPrelId getTagIdKey pREL_GHC SLIT("getTag#") ty info
   where
-    info = noCafOrTyGenIdInfo `setUnfoldingInfo` mkCompulsoryUnfolding rhs
+    info = noCafNoTyGenIdInfo `setUnfoldingInfo` mkCompulsoryUnfolding rhs
        -- We don't provide a defn for this; you must inline it
 
     ty = mkForAllTys [alphaTyVar] (mkFunTy alphaTy intPrimTy)
@@ -716,7 +737,7 @@ nasty as-is, change it back to a literal (@Literal@).
 realWorldPrimId        -- :: State# RealWorld
   = pcMiscPrelId realWorldPrimIdKey pREL_GHC SLIT("realWorld#")
                 realWorldStatePrimTy
-                (noCafOrTyGenIdInfo `setUnfoldingInfo` mkOtherCon [])
+                (noCafNoTyGenIdInfo `setUnfoldingInfo` mkOtherCon [])
        -- The mkOtherCon makes it look that realWorld# is evaluated
        -- which in turn makes Simplify.interestingArg return True,
        -- which in turn makes INLINE things applied to realWorld# likely
@@ -769,7 +790,7 @@ aBSENT_ERROR_ID
 
 pAR_ERROR_ID
   = pcMiscPrelId parErrorIdKey pREL_ERR SLIT("parError")
-    (mkSigmaTy [openAlphaTyVar] [] openAlphaTy) noCafOrTyGenIdInfo
+    (mkSigmaTy [openAlphaTyVar] [] openAlphaTy) noCafNoTyGenIdInfo
 \end{code}
 
 
@@ -796,9 +817,9 @@ pcMiscPrelId key mod str ty info
 pc_bottoming_Id key mod name ty
  = pcMiscPrelId key mod name ty bottoming_info
  where
-    bottoming_info = noCafOrTyGenIdInfo 
+    bottoming_info = noCafNoTyGenIdInfo 
                     `setStrictnessInfo` mkStrictnessInfo ([wwStrict], True)
-                    
+
        -- these "bottom" out, no matter what their arguments
 
 generic_ERROR_ID u n = pc_bottoming_Id u pREL_ERR n errorTy