summaryrefslogtreecommitdiff
path: root/ghc/compiler/parser/Parser.y
diff options
context:
space:
mode:
authorsimonpj <unknown>1999-11-01 17:10:57 +0000
committersimonpj <unknown>1999-11-01 17:10:57 +0000
commit30b5ebe424ebae69b162ac3fc547eb14d898535f (patch)
treefe090b3adee37ca6ac6efc06e1903ffed5d6ffff /ghc/compiler/parser/Parser.y
parentddddb042fb266dc114273db94c3b2b04ada6346b (diff)
downloadhaskell-30b5ebe424ebae69b162ac3fc547eb14d898535f.tar.gz
[project @ 1999-11-01 17:09:54 by simonpj]
A regrettably-gigantic commit that puts in place what Simon PJ has been up to for the last month or so, on and off. The basic idea was to restore unfoldings to *occurrences* of variables without introducing a space leak. I wanted to make sure things improved relative to 4.04, and that proved depressingly hard. On the way I discovered several quite serious bugs in the simplifier. Here's a summary of what's gone on. ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ * No commas between for-alls in RULES. This makes the for-alls have the same syntax as in types. * Arrange that simplConArgs works in one less pass than before. This exposed a bug: a bogus call to completeBeta. * Add a top-level flag in CoreUnfolding, used in callSiteInline * Extend w/w to use etaExpandArity, so it does eta/coerce expansion * Implement inline phases. The meaning of the inline pragmas is described in CoreUnfold.lhs. You can say things like {#- INLINE 2 build #-} to mean "inline build in phase 2" * Don't float anything out of an INLINE. Don't float things to top level unless they also escape a value lambda. [see comments with SetLevels.lvlMFE Without at least one of these changes, I found that {-# INLINE concat #-} concat = __inline (/\a -> foldr (++) []) was getting floated to concat = __inline( /\a -> lvl a ) lvl = ...inlined version of foldr... Subsequently I found that not floating constants out of an INLINE gave really bad code like __inline (let x = e in \y -> ...) so I now let things float out of INLINE * Implement the "reverse-mapping" idea for CSE; actually it turned out to be easier to implement it in SetLevels, and may benefit full laziness too. * It's a good idea to inline inRange. Consider index (l,h) i = case inRange (l,h) i of True -> l+i False -> error inRange itself isn't strict in h, but if it't inlined then 'index' *does* become strict in h. Interesting! * Big change to the way unfoldings and occurrence info is propagated in the simplifier The plan is described in Subst.lhs with the Subst type Occurrence info is now in a separate IdInfo field than user pragmas * I found that (coerce T (coerce S (\x.e))) y didn't simplify in one round. First we get to (\x.e) y and only then do the beta. Solution: cancel the coerces in the continuation * Amazingly, CoreUnfold wasn't counting the cost of a function an application. * Disable rules in initial simplifier run. Otherwise full laziness doesn't get a chance to lift out a MFE before a rule (e.g. fusion) zaps it. queens is a case in point * Improve float-out stuff significantly. The big change is that if we have \x -> ... /\a -> ...let p = ..a.. in let q = ...p... where p's rhs doesn't x, we abstract a from p, so that we can get p past x. (We did that before.) But we also substitute (p a) for p in q, and then we can do the same thing for q. (We didn't do that, so q got stuck.) This is much better. It involves doing a substitution "as we go" in SetLevels, though.
Diffstat (limited to 'ghc/compiler/parser/Parser.y')
-rw-r--r--ghc/compiler/parser/Parser.y14
1 files changed, 9 insertions, 5 deletions
diff --git a/ghc/compiler/parser/Parser.y b/ghc/compiler/parser/Parser.y
index 239e64ba4f..cc76e5de7d 100644
--- a/ghc/compiler/parser/Parser.y
+++ b/ghc/compiler/parser/Parser.y
@@ -1,6 +1,6 @@
{-
-----------------------------------------------------------------------------
-$Id: Parser.y,v 1.14 1999/09/01 14:08:19 sof Exp $
+$Id: Parser.y,v 1.15 1999/11/01 17:10:23 simonpj Exp $
Haskell grammar.
@@ -367,8 +367,8 @@ decl :: { RdrBinding }
: signdecl { $1 }
| fixdecl { $1 }
| valdef { RdrValBinding $1 }
- | '{-# INLINE' srcloc qvar '#-}' { RdrSig (InlineSig $3 $2) }
- | '{-# NOINLINE' srcloc qvar '#-}' { RdrSig (NoInlineSig $3 $2) }
+ | '{-# INLINE' srcloc opt_phase qvar '#-}' { RdrSig (InlineSig $4 $3 $2) }
+ | '{-# NOINLINE' srcloc opt_phase qvar '#-}' { RdrSig (NoInlineSig $4 $3 $2) }
| '{-# SPECIALISE' srcloc qvar '::' sigtypes '#-}'
{ foldr1 RdrAndBindings
(map (\t -> RdrSig (SpecSig $3 t $2)) $5) }
@@ -376,6 +376,10 @@ decl :: { RdrBinding }
{ RdrSig (SpecInstSig $4 $2) }
| '{-# RULES' rules '#-}' { $2 }
+opt_phase :: { Maybe Int }
+ : INTEGER { Just (fromInteger $1) }
+ | {- empty -} { Nothing }
+
sigtypes :: { [RdrNameHsType] }
: sigtype { [ $1 ] }
| sigtypes ',' sigtype { $3 : $1 }
@@ -443,11 +447,11 @@ rule_forall :: { [RdrNameRuleBndr] }
rule_var_list :: { [RdrNameRuleBndr] }
: rule_var { [$1] }
- | rule_var ',' rule_var_list { $1 : $3 }
+ | rule_var rule_var_list { $1 : $2 }
rule_var :: { RdrNameRuleBndr }
: varid { RuleBndr $1 }
- | varid '::' ctype { RuleBndrSig $1 $3 }
+ | '(' varid '::' ctype ')' { RuleBndrSig $2 $4 }
-----------------------------------------------------------------------------
-- Foreign import/export