[project @ 2000-10-23 09:03:26 by simonpj]
[ghc-hetmet.git] / ghc / compiler / basicTypes / IdInfo.lhs
index c94e81b..3fe281a 100644 (file)
@@ -13,7 +13,7 @@ module IdInfo (
        vanillaIdInfo, mkIdInfo, seqIdInfo, megaSeqIdInfo,
 
        -- Zapping
-       zapFragileInfo, zapLamInfo, zapSpecPragInfo, copyIdInfo,
+       zapFragileInfo, zapLamInfo, zapSpecPragInfo, shortableIdInfo, copyIdInfo,
 
        -- Flavour
        IdFlavour(..), flavourInfo, 
@@ -45,19 +45,16 @@ module IdInfo (
        -- Inline prags
        InlinePragInfo(..), 
        inlinePragInfo, setInlinePragInfo, pprInlinePragInfo,
+       isNeverInlinePrag, neverInlinePrag,
 
        -- Occurrence info
-       OccInfo(..), isFragileOccInfo,
+       OccInfo(..), isFragileOcc, isDeadOcc, isLoopBreaker,
        InsideLam, OneBranch, insideLam, notInsideLam, oneBranch, notOneBranch,
        occInfo, setOccInfo, 
 
        -- Specialisation
        specInfo, setSpecInfo,
 
-       -- Update
-       UpdateInfo, UpdateSpec,
-       mkUpdateInfo, updateInfo, updateInfoMaybe, ppUpdateInfo, setUpdateInfo,
-
        -- CAF info
        CafInfo(..), cafInfo, setCafInfo, ppCafInfo,
 
@@ -74,7 +71,7 @@ module IdInfo (
 import CoreSyn
 import PrimOp          ( PrimOp )
 import Var              ( Id )
-import BasicTypes      ( OccInfo(..), isFragileOccInfo, seqOccInfo,
+import BasicTypes      ( OccInfo(..), isFragileOcc, isDeadOcc, seqOccInfo, isLoopBreaker,
                          InsideLam, insideLam, notInsideLam, 
                          OneBranch, oneBranch, notOneBranch,
                          Arity
@@ -83,10 +80,8 @@ import DataCon               ( DataCon )
 import FieldLabel      ( FieldLabel )
 import Demand          -- Lots of stuff
 import Outputable      
-import Maybe            ( isJust )
 
-infixl         1 `setUpdateInfo`,
-         `setDemandInfo`,
+infixl         1 `setDemandInfo`,
          `setStrictnessInfo`,
          `setSpecInfo`,
          `setArityInfo`,
@@ -126,7 +121,6 @@ data IdInfo
        strictnessInfo  :: StrictnessInfo,      -- Strictness properties
         workerInfo      :: WorkerInfo,          -- Pointer to Worker Function
        unfoldingInfo   :: Unfolding,           -- Its unfolding
-       updateInfo      :: UpdateInfo,          -- Which args should be updated
        cafInfo         :: CafInfo,
        cprInfo         :: CprInfo,             -- Function always constructs a product result
         lbvarInfo      :: LBVarInfo,           -- Info about a lambda-bound variable
@@ -184,7 +178,6 @@ setUnfoldingInfo  info uf
        -- actually increases residency significantly. 
   = info { unfoldingInfo = uf }
 
-setUpdateInfo    info ud = info { updateInfo = ud }
 setDemandInfo    info dd = info { demandInfo = dd }
 setArityInfo     info ar = info { arityInfo = ar  }
 setCafInfo        info cf = info { cafInfo = cf }
@@ -213,7 +206,6 @@ mkIdInfo flv = IdInfo {
                    workerInfo          = NoWorker,
                    strictnessInfo      = NoStrictnessInfo,
                    unfoldingInfo       = noUnfolding,
-                   updateInfo          = NoUpdateInfo,
                    cafInfo             = MayHaveCafRefs,
                    cprInfo             = NoCPRInfo,
                    lbvarInfo           = NoLBVarInfo,
@@ -285,10 +277,15 @@ data ArityInfo
                        -- function; it's already been compiled and we know its
                        -- arity for sure.
 
-  | ArityAtLeast Arity -- Arity is this or greater.  We attach this arity to 
+  | ArityAtLeast Arity -- A partial application of this Id to up to n-1 value arguments
+                       -- does essentially no work.  That is not necessarily the
+                       -- same as saying that it has n leading lambdas, because coerces
+                       -- may get in the way.
+
                        -- functions in the module being compiled.  Their arity
                        -- might increase later in the compilation process, if
                        -- an extra lambda floats up to the binding site.
+  deriving( Eq )
 
 seqArity :: ArityInfo -> ()
 seqArity a = arityLowerBound a `seq` ()
@@ -322,8 +319,19 @@ data InlinePragInfo
   = NoInlinePragInfo
   | IMustNotBeINLINEd Bool             -- True <=> came from an INLINE prag, False <=> came from a NOINLINE prag
                      (Maybe Int)       -- Phase number from pragma, if any
+  deriving( Eq )
        -- The True, Nothing case doesn't need to be recorded
 
+       -- SEE COMMENTS WITH CoreUnfold.blackListed on the
+       -- exact significance of the IMustNotBeINLINEd pragma
+
+isNeverInlinePrag :: InlinePragInfo -> Bool
+isNeverInlinePrag (IMustNotBeINLINEd _ Nothing) = True
+isNeverInlinePrag other                                = False
+
+neverInlinePrag :: InlinePragInfo
+neverInlinePrag = IMustNotBeINLINEd True{-should be False? --SDM -} Nothing
+
 instance Outputable InlinePragInfo where
   -- This is now parsed in interface files
   ppr NoInlinePragInfo = empty
@@ -360,9 +368,7 @@ There might not be a worker, even for a strict function, because:
 data WorkerInfo = NoWorker
                | HasWorker Id Arity
        -- The Arity is the arity of the *wrapper* at the moment of the
-       -- w/w split. It had better be the same as the arity of the wrapper
-       -- at the moment it is spat into the interface file.
-       -- This Arity just lets us make a (hopefully redundant) sanity check
+       -- w/w split. See comments in MkIface.ifaceId, with the 'Worker' code.
 
 seqWorker :: WorkerInfo -> ()
 seqWorker (HasWorker id _) = id `seq` ()
@@ -387,40 +393,6 @@ wrapperArity (HasWorker _ a) = a
 
 %************************************************************************
 %*                                                                     *
-\subsection[update-IdInfo]{Update-analysis info about an @Id@}
-%*                                                                     *
-%************************************************************************
-
-\begin{code}
-data UpdateInfo
-  = NoUpdateInfo
-  | SomeUpdateInfo UpdateSpec
-  deriving (Eq, Ord)
-      -- we need Eq/Ord to cross-chk update infos in interfaces
-
--- the form in which we pass update-analysis info between modules:
-type UpdateSpec = [Int]
-\end{code}
-
-\begin{code}
-mkUpdateInfo = SomeUpdateInfo
-
-updateInfoMaybe NoUpdateInfo       = Nothing
-updateInfoMaybe (SomeUpdateInfo []) = Nothing
-updateInfoMaybe (SomeUpdateInfo         u) = Just u
-\end{code}
-
-Text instance so that the update annotations can be read in.
-
-\begin{code}
-ppUpdateInfo NoUpdateInfo         = empty
-ppUpdateInfo (SomeUpdateInfo [])   = empty
-ppUpdateInfo (SomeUpdateInfo spec) = (<>) (ptext SLIT("__UA ")) (hcat (map int spec))
-  -- was "__U "; changed to avoid conflict with unfoldings.  KSW 1999-07.
-\end{code}
-
-%************************************************************************
-%*                                                                     *
 \subsection[CAF-IdInfo]{CAF-related information}
 %*                                                                     *
 %************************************************************************
@@ -568,7 +540,7 @@ zapFragileInfo info@(IdInfo {occInfo                = occ,
                             workerInfo         = wrkr,
                             specInfo           = rules, 
                             unfoldingInfo      = unfolding})
-  |  not (isFragileOccInfo occ)
+  |  not (isFragileOcc occ)
         -- We must forget about whether it was marked safe-to-inline,
        -- because that isn't necessarily true in the simplified expression.
        -- This is important because expressions may  be re-simplified
@@ -634,26 +606,60 @@ copyIdInfo is used when shorting out a top-level binding
 where f is exported.  We are going to swizzle it around to
        f = BIG
        f_local = f
-but we must be careful to combine their IdInfos right.
-The fact that things can go wrong here is a bad sign, but I can't see
-how to make it 'patently right', so copyIdInfo is derived (pretty much) by trial and error
 
-Here 'from' is f_local, 'to' is f, and the result is attached to f
+BUT (a) we must be careful about messing up rules
+    (b) we must ensure f's IdInfo ends up right
+
+(a) Messing up the rules
+~~~~~~~~~~~~~~~~~~~~
+The example that went bad on me was this one:
+       
+    iterate :: (a -> a) -> a -> [a]
+    iterate = iterateList
+    
+    iterateFB c f x = x `c` iterateFB c f (f x)
+    iterateList f x =  x : iterateList f (f x)
+    
+    {-# RULES
+    "iterate"  forall f x.     iterate f x = build (\c _n -> iterateFB c f x)
+    "iterateFB"                iterateFB (:) = iterateList
+     #-}
+
+This got shorted out to:
+
+    iterateList :: (a -> a) -> a -> [a]
+    iterateList = iterate
+    
+    iterateFB c f x = x `c` iterateFB c f (f x)
+    iterate f x =  x : iterate f (f x)
+    
+    {-# RULES
+    "iterate"  forall f x.     iterate f x = build (\c _n -> iterateFB c f x)
+    "iterateFB"                iterateFB (:) = iterate
+     #-}
+
+And now we get an infinite loop in the rule system 
+       iterate f x -> build (\cn -> iterateFB c f x
+                   -> iterateFB (:) f x
+                   -> iterate f x
+
+Tiresome solution: don't do shorting out if f has rewrite rules.
+Hence shortableIdInfo.
+
+(b) Keeping the IdInfo right
+~~~~~~~~~~~~~~~~~~~~~~~~
+We want to move strictness/worker info from f_local to f, but keep the rest.
+Hence copyIdInfo.
 
 \begin{code}
-copyIdInfo :: IdInfo   -- From
-          -> IdInfo    -- To
-          -> IdInfo    -- To, updated with stuff from From; except flavour unchanged
-copyIdInfo from to = from { flavourInfo = flavourInfo to,
-                           specInfo = specInfo to,
-                           inlinePragInfo = inlinePragInfo to
+shortableIdInfo :: IdInfo -> Bool
+shortableIdInfo info = isEmptyCoreRules (specInfo info)
+
+copyIdInfo :: IdInfo   -- f_local
+          -> IdInfo    -- f (the exported one)
+          -> IdInfo    -- New info for f
+copyIdInfo f_local f = f { strictnessInfo = strictnessInfo f_local,
+                          workerInfo     = workerInfo     f_local,
+                          cprInfo        = cprInfo        f_local
                          }
-       -- It's important to preserve the inline pragma on 'f'; e.g. consider
-       --      {-# NOINLINE f #-}
-       --      f = local
-       --
-       -- similarly, transformation rules may be attached to f
-       -- and we want to preserve them.  
-       --
-       -- On the other hand, we want the strictness info from f_local.
 \end{code}