X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2FbasicTypes%2FBasicTypes.lhs;h=9b21399c48e31f5295dddbca96efcd334d92c505;hp=f782da3e96751b808114c1fe28b9421a31070e66;hb=72462499b891d5779c19f3bda03f96e24f9554ae;hpb=cae75f82226638691cfa1e85fc168f4b65ddce4d diff --git a/compiler/basicTypes/BasicTypes.lhs b/compiler/basicTypes/BasicTypes.lhs index f782da3..9b21399 100644 --- a/compiler/basicTypes/BasicTypes.lhs +++ b/compiler/basicTypes/BasicTypes.lhs @@ -18,6 +18,8 @@ module BasicTypes( Version, bumpVersion, initialVersion, Arity, + + FunctionOrData(..), WarningTxt(..), @@ -30,6 +32,8 @@ module BasicTypes( RecFlag(..), isRec, isNonRec, boolToRecFlag, + RuleName, + TopLevelFlag(..), isTopLevel, isNotTopLevel, OverlapFlag(..), @@ -50,8 +54,12 @@ module BasicTypes( StrictnessMark(..), isMarkedUnboxed, isMarkedStrict, CompilerPhase, - Activation(..), isActive, isNeverActive, isAlwaysActive, - InlineSpec(..), defaultInlineSpec, alwaysInlineSpec, neverInlineSpec, + Activation(..), isActive, isNeverActive, isAlwaysActive, isEarlyActive, + RuleMatchInfo(..), isConLike, isFunLike, + InlinePragma(..), defaultInlinePragma, neverInlinePragma, dfunInlinePragma, + isDefaultInlinePragma, isInlinePragma, + inlinePragmaActivation, inlinePragmaRuleMatchInfo, + setInlinePragmaActivation, setInlinePragmaRuleMatchInfo, SuccessFlag(..), succeeded, failed, successIf ) where @@ -70,6 +78,21 @@ import Outputable type Arity = Int \end{code} +%************************************************************************ +%* * +\subsection[FunctionOrData]{FunctionOrData} +%* * +%************************************************************************ + +\begin{code} +data FunctionOrData = IsFunction | IsData + deriving (Eq, Ord) + +instance Outputable FunctionOrData where + ppr IsFunction = text "(function)" + ppr IsData = text "(data)" +\end{code} + %************************************************************************ %* * @@ -96,13 +119,14 @@ initialVersion = 1 \begin{code} -- reason/explanation from a WARNING or DEPRECATED pragma -data WarningTxt = WarningTxt FastString - | DeprecatedTxt FastString +data WarningTxt = WarningTxt [FastString] + | DeprecatedTxt [FastString] deriving Eq instance Outputable WarningTxt where - ppr (WarningTxt w) = doubleQuotes (ftext w) - ppr (DeprecatedTxt d) = text "Deprecated:" <+> doubleQuotes (ftext d) + ppr (WarningTxt ws) = doubleQuotes (vcat (map ftext ws)) + ppr (DeprecatedTxt ds) = text "Deprecated:" <+> + doubleQuotes (vcat (map ftext ds)) \end{code} %************************************************************************ @@ -129,6 +153,15 @@ instance Outputable name => Outputable (IPName name) where ppr (IPName n) = char '?' <> ppr n -- Ordinary implicit parameters \end{code} +%************************************************************************ +%* * + Rules +%* * +%************************************************************************ + +\begin{code} +type RuleName = FastString +\end{code} %************************************************************************ %* * @@ -372,17 +405,20 @@ the base of the module hierarchy. So it seemed simpler to put the defn of OccInfo here, safely at the bottom \begin{code} +-- | Identifier occurrence information data OccInfo - = NoOccInfo -- Many occurrences, or unknown + = NoOccInfo -- ^ There are many occurrences, or unknown occurences - | IAmDead -- Marks unused variables. Sometimes useful for + | IAmDead -- ^ Marks unused variables. Sometimes useful for -- lambda and case-bound variables. - | OneOcc -- Occurs exactly once, not inside a rule + | OneOcc !InsideLam !OneBranch - !InterestingCxt + !InterestingCxt -- ^ Occurs exactly once, not inside a rule + -- | This identifier breaks a loop of mutually recursive functions. The field + -- marks whether it is only a loop breaker due to a reference in a rule | IAmALoopBreaker -- Note [LoopBreaker OccInfo] !RulesOnly -- True <=> This is a weak or rules-only loop breaker -- See OccurAnal Note [Weak loop breakers] @@ -549,35 +585,129 @@ data Activation = NeverActive | ActiveAfter CompilerPhase -- Active in this phase and later deriving( Eq ) -- Eq used in comparing rules in HsDecls -data InlineSpec - = Inline - Activation -- Says during which phases inlining is allowed - Bool -- True <=> make the RHS look small, so that when inlining - -- is enabled, it will definitely actually happen - deriving( Eq ) +data RuleMatchInfo = ConLike -- See Note [CONLIKE pragma] + | FunLike + deriving( Eq ) + +data InlinePragma -- Note [InlinePragma] + = InlinePragma + { inl_inline :: Bool -- True <=> INLINE, + -- False <=> no pragma at all, or NOINLINE + , inl_act :: Activation -- Says during which phases inlining is allowed + , inl_rule :: RuleMatchInfo -- Should the function be treated like a constructor? + } deriving( Eq ) +\end{code} + +Note [InlinePragma] +~~~~~~~~~~~~~~~~~~~ +This data type mirrors what you can write in an INLINE or NOINLINE pragma in +the source program. + +If you write nothing at all, you get defaultInlinePragma: + inl_inline = False + inl_act = AlwaysActive + inl_rule = FunLike -defaultInlineSpec, alwaysInlineSpec, neverInlineSpec :: InlineSpec +It's not possible to get that combination by *writing* something, so +if an Id has defaultInlinePragma it means the user didn't specify anything. -defaultInlineSpec = Inline AlwaysActive False -- Inlining is OK, but not forced -alwaysInlineSpec = Inline AlwaysActive True -- INLINE always -neverInlineSpec = Inline NeverActive False -- NOINLINE +Note [CONLIKE pragma] +~~~~~~~~~~~~~~~~~~~~~ +The ConLike constructor of a RuleMatchInfo is aimed at the following. +Consider first + {-# RULE "r/cons" forall a as. r (a:as) = f (a+1) #-} + g b bs = let x = b:bs in ..x...x...(r x)... +Now, the rule applies to the (r x) term, because GHC "looks through" +the definition of 'x' to see that it is (b:bs). + +Now consider + {-# RULE "r/f" forall v. r (f v) = f (v+1) #-} + g v = let x = f v in ..x...x...(r x)... +Normally the (r x) would *not* match the rule, because GHC would be +scared about duplicating the redex (f v), so it does not "look +through" the bindings. + +However the CONLIKE modifier says to treat 'f' like a constructor in +this situation, and "look through" the unfolding for x. So (r x) +fires, yielding (f (v+1)). + +This is all controlled with a user-visible pragma: + {-# NOINLINE CONLIKE [1] f #-} + +The main effects of CONLIKE are: + + - The occurrence analyser (OccAnal) and simplifier (Simplify) treat + CONLIKE thing like constructors, by ANF-ing them + + - New function coreUtils.exprIsExpandable is like exprIsCheap, but + additionally spots applications of CONLIKE functions + + - A CoreUnfolding has a field that caches exprIsExpandable + + - The rule matcher consults this field. See + Note [Expanding variables] in Rules.lhs. + +\begin{code} +isConLike :: RuleMatchInfo -> Bool +isConLike ConLike = True +isConLike _ = False + +isFunLike :: RuleMatchInfo -> Bool +isFunLike FunLike = True +isFunLike _ = False + +defaultInlinePragma, neverInlinePragma, dfunInlinePragma :: InlinePragma +defaultInlinePragma + = InlinePragma { inl_act = AlwaysActive, inl_rule = FunLike, inl_inline = False } +neverInlinePragma + = InlinePragma { inl_act = NeverActive, inl_rule = FunLike, inl_inline = False } +dfunInlinePragma + = InlinePragma { inl_act = AlwaysActive, inl_rule = ConLike, inl_inline = False } + + +isDefaultInlinePragma :: InlinePragma -> Bool +isDefaultInlinePragma (InlinePragma { inl_act = activation + , inl_rule = match_info + , inl_inline = inline }) + = not inline && isAlwaysActive activation && isFunLike match_info + +isInlinePragma :: InlinePragma -> Bool +isInlinePragma prag = inl_inline prag + +inlinePragmaActivation :: InlinePragma -> Activation +inlinePragmaActivation (InlinePragma { inl_act = activation }) = activation + +inlinePragmaRuleMatchInfo :: InlinePragma -> RuleMatchInfo +inlinePragmaRuleMatchInfo (InlinePragma { inl_rule = info }) = info + +setInlinePragmaActivation :: InlinePragma -> Activation -> InlinePragma +setInlinePragmaActivation prag activation = prag { inl_act = activation } + +setInlinePragmaRuleMatchInfo :: InlinePragma -> RuleMatchInfo -> InlinePragma +setInlinePragmaRuleMatchInfo prag info = prag { inl_rule = info } instance Outputable Activation where - ppr NeverActive = ptext (sLit "NEVER") ppr AlwaysActive = ptext (sLit "ALWAYS") + ppr NeverActive = ptext (sLit "NEVER") ppr (ActiveBefore n) = brackets (char '~' <> int n) ppr (ActiveAfter n) = brackets (int n) - -instance Outputable InlineSpec where - ppr (Inline act is_inline) - | is_inline = ptext (sLit "INLINE") - <> case act of - AlwaysActive -> empty - _ -> ppr act - | otherwise = ptext (sLit "NOINLINE") - <> case act of - NeverActive -> empty - _ -> ppr act + +instance Outputable RuleMatchInfo where + ppr ConLike = ptext (sLit "CONLIKE") + ppr FunLike = ptext (sLit "FUNLIKE") + +instance Outputable InlinePragma where + ppr (InlinePragma { inl_inline = inline, inl_act = activation, inl_rule = info }) + = pp_inline <+> pp_info <+> pp_activation + where + pp_inline | inline = ptext (sLit "INLINE") + | otherwise = ptext (sLit "NOINLINE") + pp_info | isFunLike info = empty + | otherwise = ppr info + pp_activation + | inline && isAlwaysActive activation = empty + | not inline && isNeverActive activation = empty + | otherwise = ppr activation isActive :: CompilerPhase -> Activation -> Bool isActive _ NeverActive = False @@ -585,11 +715,15 @@ isActive _ AlwaysActive = True isActive p (ActiveAfter n) = p <= n isActive p (ActiveBefore n) = p > n -isNeverActive, isAlwaysActive :: Activation -> Bool +isNeverActive, isAlwaysActive, isEarlyActive :: Activation -> Bool isNeverActive NeverActive = True isNeverActive _ = False isAlwaysActive AlwaysActive = True isAlwaysActive _ = False + +isEarlyActive AlwaysActive = True +isEarlyActive (ActiveBefore {}) = True +isEarlyActive _ = False \end{code}