summaryrefslogtreecommitdiff
path: root/ghc/compiler/hsSyn/HsDecls.lhs
diff options
context:
space:
mode:
authorsimonpj <unknown>2001-09-26 15:12:37 +0000
committersimonpj <unknown>2001-09-26 15:12:37 +0000
commite0d750bedbd33f7a133c8c82c35fd8db537ab649 (patch)
tree96a7a643b01ddfb956912bd4d88a4af84a56ddec /ghc/compiler/hsSyn/HsDecls.lhs
parent5cd3527da623a25b9ace2995f9d2e7f6c90c611f (diff)
downloadhaskell-e0d750bedbd33f7a133c8c82c35fd8db537ab649.tar.gz
[project @ 2001-09-26 15:12:33 by simonpj]
------------------ Simon's big commit ------------------ This commit, which I don't think I can sensibly do piecemeal, consists of the things I've been doing recently, mainly directed at making Manuel, George, and Marcin happier with RULES. Reogranise the simplifier ~~~~~~~~~~~~~~~~~~~~~~~~~ 1. The simplifier's environment is now an explicit parameter. This makes it a bit easier to figure out where it is going. 2. Constructor arguments can now be arbitrary expressions, except when the application is the RHS of a let(rec). This makes it much easier to match rules like RULES "foo" f (h x, g y) = f' x y In the simplifier, it's Simplify.mkAtomicArgs that ANF-ises a constructor application where necessary. In the occurrence analyser, there's a new piece of context info (OccEncl) to say whether a constructor app is in a place where it should be in ANF. (Unless it knows this it'll give occurrence info which will inline the argument back into the constructor app.) 3. I'm experimenting with doing the "float-past big lambda" transformation in the full laziness pass, rather than mixed in with the simplifier (was tryRhsTyLam). 4. Arrange that case (coerce (S,T) (x,y)) of ... will simplify. Previous it didn't. A local change to CoreUtils.exprIsConApp_maybe. 5. Do a better job in CoreUtils.exprEtaExpandArity when there's an error function in one branch. Phase numbers, RULES, and INLINE pragmas ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ 1. Phase numbers decrease from N towards zero (instead of increasing). This makes it easier to add new earlier phases, which is what users want to do. 2. RULES get their own phase number, N, and are disabled in phases before N. e.g. {-# RULES "foo" [2] forall x y. f (x,y) = f' x y #-} Note the [2], which says "only active in phase 2 and later". 3. INLINE and NOINLINE pragmas have a phase number to. This is now treated in just the same way as the phase number on RULE; that is, the Id is not inlined in phases earlier than N. In phase N and later the Id *may* be inlined, and here is where INLINE and NOINLINE differ: INLNE makes the RHS look small, so as soon as it *may* be inlined it probably *will* be inlined. The syntax of the phase number on an INLINE/NOINLINE pragma has changed to be like the RULES case (i.e. in square brackets). This should also make sure you examine all such phase numbers; many will need to change now the numbering is reversed. Inlining Ids is no longer affected at all by whether the Id appears on the LHS of a rule. Now it's up to the programmer to put a suitable INLINE/NOINLINE pragma to stop it being inlined too early. Implementation notes: * A new data type, BasicTypes.Activation says when a rule or inline pragma is active. Functions isAlwaysActive, isNeverActive, isActive, do the obvious thing (all in BasicTypes). * Slight change in the SimplifierSwitch data type, which led to a lot of simplifier-specific code moving from CmdLineOpts to SimplMonad; a Good Thing. * The InlinePragma in the IdInfo of an Id is now simply an Activation saying when the Id can be inlined. (It used to be a rather bizarre pair of a Bool and a (Maybe Phase), so this is much much easier to understand.) * The simplifier has a "mode" environment switch, replacing the old black list. Unfortunately the data type decl has to be in CmdLineOpts, because it's an argument to the CoreDoSimplify switch data SimplifierMode = SimplGently | SimplPhase Int Here "gently" means "no rules, no inlining". All the crucial inlining decisions are now collected together in SimplMonad (preInlineUnconditionally, postInlineUnconditionally, activeInline, activeRule). Specialisation ~~~~~~~~~~~~~~ 1. Only dictionary *functions* are made INLINE, not dictionaries that have no parameters. (This inline-dictionary-function thing is Marcin's idea and I'm still not sure whether it's a good idea. But it's definitely a Bad Idea when there are no arguments.) 2. Be prepared to specialise an INLINE function: an easy fix in Specialise.lhs But there is still a problem, which is that the INLINE wins at the call site, so we don't use the specialised version anyway. I'm still unsure whether it makes sense to SPECIALISE something you want to INLINE. Random smaller things ~~~~~~~~~~~~~~~~~~~~~~ * builtinRules (there was only one, but may be more) in PrelRules are now incorporated. They were being ignored before... * OrdList.foldOL --> OrdList.foldrOL, OrdList.foldlOL * Some tidying up of the tidyOpenTyVar, tidyTyVar functions. I've forgotten exactly what!
Diffstat (limited to 'ghc/compiler/hsSyn/HsDecls.lhs')
-rw-r--r--ghc/compiler/hsSyn/HsDecls.lhs32
1 files changed, 17 insertions, 15 deletions
diff --git a/ghc/compiler/hsSyn/HsDecls.lhs b/ghc/compiler/hsSyn/HsDecls.lhs
index 04b2af1ba3..2635995195 100644
--- a/ghc/compiler/hsSyn/HsDecls.lhs
+++ b/ghc/compiler/hsSyn/HsDecls.lhs
@@ -32,8 +32,8 @@ import PprCore ( pprCoreRule )
import HsCore ( UfExpr, UfBinder, HsIdInfo, pprHsIdInfo,
eq_ufBinders, eq_ufExpr, pprUfExpr
)
-import CoreSyn ( CoreRule(..) )
-import BasicTypes ( NewOrData(..), StrictnessMark(..) )
+import CoreSyn ( CoreRule(..), RuleName )
+import BasicTypes ( NewOrData(..), StrictnessMark(..), Activation(..) )
import ForeignCall ( CExportSpec, CCallSpec, DNCallSpec, CCallConv )
-- others:
@@ -760,7 +760,8 @@ instance Outputable FoType where
\begin{code}
data RuleDecl name pat
= HsRule -- Source rule
- FAST_STRING -- Rule name
+ RuleName -- Rule name
+ Activation
[name] -- Forall'd tyvars, filled in by the renamer with
-- tyvars mentioned in sigs; then filled out by typechecker
[RuleBndr name] -- Forall'd term vars
@@ -769,7 +770,8 @@ data RuleDecl name pat
SrcLoc
| IfaceRule -- One that's come in from an interface file; pre-typecheck
- FAST_STRING
+ RuleName
+ Activation
[UfBinder name] -- Tyvars and term vars
name -- Head of lhs
[UfExpr name] -- Args of LHS
@@ -780,13 +782,13 @@ data RuleDecl name pat
name -- Head of LHS
CoreRule
-isIfaceRuleDecl (HsRule _ _ _ _ _ _) = False
-isIfaceRuleDecl other = True
+isIfaceRuleDecl (HsRule _ _ _ _ _ _ _) = False
+isIfaceRuleDecl other = True
ifaceRuleDeclName :: RuleDecl name pat -> name
-ifaceRuleDeclName (IfaceRule _ _ n _ _ _) = n
-ifaceRuleDeclName (IfaceRuleOut n r) = n
-ifaceRuleDeclName (HsRule fs _ _ _ _ _) = pprPanic "ifaceRuleDeclName" (ppr fs)
+ifaceRuleDeclName (IfaceRule _ _ _ n _ _ _) = n
+ifaceRuleDeclName (IfaceRuleOut n r) = n
+ifaceRuleDeclName (HsRule fs _ _ _ _ _ _) = pprPanic "ifaceRuleDeclName" (ppr fs)
data RuleBndr name
= RuleBndr name
@@ -794,15 +796,15 @@ data RuleBndr name
instance (NamedThing name, Ord name) => Eq (RuleDecl name pat) where
-- Works for IfaceRules only; used when comparing interface file versions
- (IfaceRule n1 bs1 f1 es1 rhs1 _) == (IfaceRule n2 bs2 f2 es2 rhs2 _)
- = n1==n2 && f1 == f2 &&
+ (IfaceRule n1 a1 bs1 f1 es1 rhs1 _) == (IfaceRule n2 a2 bs2 f2 es2 rhs2 _)
+ = n1==n2 && f1 == f2 && a1==a2 &&
eq_ufBinders emptyEqHsEnv bs1 bs2 (\env ->
eqListBy (eq_ufExpr env) (rhs1:es1) (rhs2:es2))
instance (NamedThing name, Outputable name, Outputable pat)
=> Outputable (RuleDecl name pat) where
- ppr (HsRule name tvs ns lhs rhs loc)
- = sep [text "{-# RULES" <+> doubleQuotes (ptext name),
+ ppr (HsRule name act tvs ns lhs rhs loc)
+ = sep [text "{-# RULES" <+> doubleQuotes (ptext name) <+> ppr act,
pp_forall, ppr lhs, equals <+> ppr rhs,
text "#-}" ]
where
@@ -811,8 +813,8 @@ instance (NamedThing name, Outputable name, Outputable pat)
fsep (map ppr tvs ++ map ppr ns)
<> dot
- ppr (IfaceRule name tpl_vars fn tpl_args rhs loc)
- = hsep [ doubleQuotes (ptext name),
+ ppr (IfaceRule name act tpl_vars fn tpl_args rhs loc)
+ = hsep [ doubleQuotes (ptext name), ppr act,
ptext SLIT("__forall") <+> braces (interppSP tpl_vars),
ppr fn <+> sep (map (pprUfExpr parens) tpl_args),
ptext SLIT("=") <+> ppr rhs