diff options
author | simonpj <unknown> | 2000-08-01 09:08:30 +0000 |
---|---|---|
committer | simonpj <unknown> | 2000-08-01 09:08:30 +0000 |
commit | fe69f3c1d6062b90635963aa414c33951bf18427 (patch) | |
tree | f7400d36260dd79dd6cb1d4bef02b0fae70d8537 /ghc/compiler/hsSyn/HsBinds.lhs | |
parent | 7185a7c33692e7b8f01a6557a34d68225501e54b (diff) | |
download | haskell-fe69f3c1d6062b90635963aa414c33951bf18427.tar.gz |
[project @ 2000-08-01 09:08:25 by simonpj]
Simon's Marktoberdorf Commits
1. Tidy up the renaming story for "system binders", such as
dictionary functions, default methods, constructor workers etc. These
are now documented in HsDecls. The main effect of the change, apart
from tidying up, is to make the *type-checker* (instead of the
renamer) generate names for dict-funs and default-methods. This is
good because Sergei's generic-class stuff generates new classes at
typecheck time.
2. Fix the CSE pass so it does not require the no-shadowing invariant.
Keith discovered that the simplifier occasionally returns a result
with shadowing. After much fiddling around (which has improved the
code in the simplifier a bit) I found that it is nearly impossible to
arrange that it really does do no-shadowing. So I gave up and fixed
the CSE pass (which is the only one to rely on it) instead.
3. Fix a performance bug in the simplifier. The change is in
SimplUtils.interestingArg. It computes whether an argment should
be considered "interesting"; if a function is applied to an interesting
argument, we are more likely to inline that function.
Consider this case
let x = 3 in f x
The 'x' argument was considered "uninteresting" for a silly reason.
Since x only occurs once, it was unconditionally substituted, but
interestingArg didn't take account of that case. Now it does.
I also made interestingArg a bit more liberal. Let's see if we
get too much inlining now.
4. In the occurrence analyser, we were choosing a bad loop breaker.
Here's the comment that's now in OccurAnal.reOrderRec
score ((bndr, rhs), _, _)
| exprIsTrivial rhs = 3 -- Practically certain to be inlined
-- Used to have also: && not (isExportedId bndr)
-- But I found this sometimes cost an extra iteration when we have
-- rec { d = (a,b); a = ...df...; b = ...df...; df = d }
-- where df is the exported dictionary. Then df makes a really
-- bad choice for loop breaker
I also increased the score for bindings with a non-functional type, so that
dictionaries have a better chance of getting inlined early
5. Add a hash code to the InScopeSet (and make it properly abstract)
This should make uniqAway a lot more robust. Simple experiments suggest
that uniqAway no longer gets into the long iteration chains that it used
to.
6. Fix a bug in the inliner that made the simplifier tend to get into
a loop where it would keep iterating ("4 iterations, bailing out" message).
In SimplUtils.mkRhsTyLam we float bindings out past a big lambda, thus:
x = /\ b -> let g = \x -> f x x
in E
becomes
g* = /\a -> \x -> f x x
x = /\ b -> let g = g* b in E
It's essential that we don't simply inling g* back into the RHS of g,
else we will be back to square 1. The inliner is meant not to do this
because there's no benefit to the inlining, but the size calculation
was a little off in CoreUnfold.
7. In SetLevels we were bogus-ly building a Subst with an empty in-scope
set, so a WARNING popped up when compiling some modules. (knights/ChessSetList
was the example that tickled it.) Now in fact the warning wasn't an error,
but the Right Thing to do is to carry down a proper Subst in SetLevels, so
that is what I have now done. It is very little more expensive.
Diffstat (limited to 'ghc/compiler/hsSyn/HsBinds.lhs')
-rw-r--r-- | ghc/compiler/hsSyn/HsBinds.lhs | 23 |
1 files changed, 13 insertions, 10 deletions
diff --git a/ghc/compiler/hsSyn/HsBinds.lhs b/ghc/compiler/hsSyn/HsBinds.lhs index db83e15794..2d72e038b8 100644 --- a/ghc/compiler/hsSyn/HsBinds.lhs +++ b/ghc/compiler/hsSyn/HsBinds.lhs @@ -236,9 +236,10 @@ data Sig name SrcLoc | ClassOpSig name -- Selector name - name -- Default-method name (if any) - Bool -- True <=> there is an explicit, programmer-supplied - -- default declaration in the class decl + (Maybe -- Nothing for source-file class signatures + (name, -- Default-method name (if any) + Bool)) -- True <=> there is an explicit, programmer-supplied + -- default declaration in the class decl (HsType name) SrcLoc @@ -269,7 +270,7 @@ instance Eq name => Eq (FixitySig name) where \begin{code} okBindSig :: NameSet -> Sig Name -> Bool -okBindSig ns (ClassOpSig _ _ _ _ _) = False +okBindSig ns (ClassOpSig _ _ _ _) = False okBindSig ns sig = sigForThisGroup ns sig okClsDclSig :: NameSet -> Sig Name -> Bool @@ -290,7 +291,7 @@ sigForThisGroup ns sig sigName :: Sig name -> Maybe name sigName (Sig n _ _) = Just n -sigName (ClassOpSig n _ _ _ _) = Just n +sigName (ClassOpSig n _ _ _) = Just n sigName (SpecSig n _ _) = Just n sigName (InlineSig n _ _) = Just n sigName (NoInlineSig n _ _) = Just n @@ -302,8 +303,8 @@ isFixitySig (FixSig _) = True isFixitySig _ = False isClassOpSig :: Sig name -> Bool -isClassOpSig (ClassOpSig _ _ _ _ _) = True -isClassOpSig _ = False +isClassOpSig (ClassOpSig _ _ _ _) = True +isClassOpSig _ = False isPragSig :: Sig name -> Bool -- Identifies pragmas @@ -316,7 +317,7 @@ isPragSig other = False \begin{code} hsSigDoc (Sig _ _ loc) = (SLIT("type signature"),loc) -hsSigDoc (ClassOpSig _ _ _ _ loc) = (SLIT("class-method type signature"), loc) +hsSigDoc (ClassOpSig _ _ _ loc) = (SLIT("class-method type signature"), loc) hsSigDoc (SpecSig _ _ loc) = (SLIT("SPECIALISE pragma"),loc) hsSigDoc (InlineSig _ _ loc) = (SLIT("INLINE pragma"),loc) hsSigDoc (NoInlineSig _ _ loc) = (SLIT("NOINLINE pragma"),loc) @@ -332,10 +333,12 @@ ppr_sig :: Outputable name => Sig name -> SDoc ppr_sig (Sig var ty _) = sep [ppr var <+> dcolon, nest 4 (ppr ty)] -ppr_sig (ClassOpSig var _ dm ty _) +ppr_sig (ClassOpSig var dm ty _) = sep [ppr var <+> pp_dm <+> dcolon, nest 4 (ppr ty)] where - pp_dm = if dm then equals else empty -- Default-method indicator + pp_dm = case dm of + Just (_, True) -> equals -- Default-method indicator + other -> empty ppr_sig (SpecSig var ty _) = sep [ hsep [text "{-# SPECIALIZE", ppr var, dcolon], |