summaryrefslogtreecommitdiff
path: root/ghc/compiler
diff options
context:
space:
mode:
authorlewie <unknown>2000-02-28 21:59:33 +0000
committerlewie <unknown>2000-02-28 21:59:33 +0000
commitf8e67a2c986fe2b1d81c97874d4c9d60cb027642 (patch)
tree21cf76d0d48914955c404921f3dda022d3ca29ab /ghc/compiler
parent58b3e315987e8a422d7e4ba35c47e6a9dc8a84a7 (diff)
downloadhaskell-f8e67a2c986fe2b1d81c97874d4c9d60cb027642.tar.gz
[project @ 2000-02-28 21:59:32 by lewie]
Fix signatures w/ implicit parameter types in them (in particular, correctly handle the case where there are no type variables). Also made a few more things Outputable. Nuke outdated comment in Parser.y.
Diffstat (limited to 'ghc/compiler')
-rw-r--r--ghc/compiler/parser/Parser.y3
-rw-r--r--ghc/compiler/typecheck/TcMonoType.lhs3
-rw-r--r--ghc/compiler/typecheck/TcSimplify.lhs12
-rw-r--r--ghc/compiler/utils/FiniteMap.lhs4
4 files changed, 18 insertions, 4 deletions
diff --git a/ghc/compiler/parser/Parser.y b/ghc/compiler/parser/Parser.y
index 12a9e6ef04..5b839ec15e 100644
--- a/ghc/compiler/parser/Parser.y
+++ b/ghc/compiler/parser/Parser.y
@@ -1,6 +1,6 @@
{-
-----------------------------------------------------------------------------
-$Id: Parser.y,v 1.25 2000/02/28 09:17:54 simonmar Exp $
+$Id: Parser.y,v 1.26 2000/02/28 21:59:32 lewie Exp $
Haskell grammar.
@@ -36,7 +36,6 @@ import GlaExts
-----------------------------------------------------------------------------
Conflicts: 14 shift/reduce
(note: it's currently 21 -- JRL, 31/1/2000)
- (note2: it's currently 36, but not because of me -- SUP, 15/2/2000 :-)
8 for abiguity in 'if x then y else z + 1'
(shift parses as 'if x then y else (z + 1)', as per longest-parse rule)
diff --git a/ghc/compiler/typecheck/TcMonoType.lhs b/ghc/compiler/typecheck/TcMonoType.lhs
index ce5d681219..29ae73fab5 100644
--- a/ghc/compiler/typecheck/TcMonoType.lhs
+++ b/ghc/compiler/typecheck/TcMonoType.lhs
@@ -392,6 +392,9 @@ data TcSigInfo
SrcLoc -- Of the signature
+instance Outputable TcSigInfo where
+ ppr (TySigInfo nm id tyvars theta tau _ inst loc) =
+ ppr nm <+> ptext SLIT("::") <+> ppr tyvars <+> ppr theta <+> ptext SLIT("=>") <+> ppr tau
maybeSig :: [TcSigInfo] -> Name -> Maybe (TcSigInfo)
-- Search for a particular signature
diff --git a/ghc/compiler/typecheck/TcSimplify.lhs b/ghc/compiler/typecheck/TcSimplify.lhs
index 4de479c0c8..3bd5792b02 100644
--- a/ghc/compiler/typecheck/TcSimplify.lhs
+++ b/ghc/compiler/typecheck/TcSimplify.lhs
@@ -190,7 +190,8 @@ tcSimplify
LIE) -- Remaining wanteds; no dups
tcSimplify str local_tvs wanted_lie
-{-
+{- this is just an optimization, and interferes with implicit params,
+ disable it for now. same goes for tcSimplifyAndCheck
| isEmptyVarSet local_tvs
= returnTc (wanted_lie, EmptyMonoBinds, emptyLIE)
@@ -270,12 +271,14 @@ tcSimplifyAndCheck
TcDictBinds) -- Bindings
tcSimplifyAndCheck str local_tvs given_lie wanted_lie
+{-
| isEmptyVarSet local_tvs
-- This can happen quite legitimately; for example in
-- instance Num Int where ...
= returnTc (wanted_lie, EmptyMonoBinds)
| otherwise
+-}
= reduceContext str try_me givens wanteds `thenTc` \ (binds, frees, irreds) ->
-- Complain about any irreducible ones
@@ -292,6 +295,7 @@ tcSimplifyAndCheck str local_tvs given_lie wanted_lie
try_me inst
-- Does not constrain a local tyvar
| isEmptyVarSet (tyVarsOfInst inst `intersectVarSet` local_tvs)
+ && (isDict inst || null (getIPs inst))
= Free
-- When checking against a given signature we always reduce
@@ -432,10 +436,13 @@ data RHS
pprAvails avails = vcat (map pprAvail (eltsFM avails))
-
+
pprAvail (Avail main_id rhs ids)
= ppr main_id <> colon <+> brackets (ppr ids) <+> pprRhs rhs
+instance Outputable Avail where
+ ppr = pprAvail
+
pprRhs NoRhs = text "<no rhs>"
pprRhs (Rhs rhs b) = ppr rhs
pprRhs (PassiveScSel rhs is) = text "passive" <+> ppr rhs
@@ -503,6 +510,7 @@ reduceContext str try_me givens wanteds
text "wanted" <+> ppr wanteds,
text "----",
text "avails" <+> pprAvails avails,
+ text "frees" <+> ppr frees,
text "irreds" <+> ppr irreds,
text "----------------------"
]) $
diff --git a/ghc/compiler/utils/FiniteMap.lhs b/ghc/compiler/utils/FiniteMap.lhs
index 2346105df9..d4e49317b0 100644
--- a/ghc/compiler/utils/FiniteMap.lhs
+++ b/ghc/compiler/utils/FiniteMap.lhs
@@ -653,6 +653,10 @@ pprX (Branch key elt sz fm_l fm_r)
= parens (hcat [pprX fm_l, space,
ppr key, space, int (IF_GHC(I# sz, sz)), space,
pprX fm_r])
+#else
+-- and when not debugging the package itself...
+instance (Outputable key, Outputable elt) => Outputable (FiniteMap key elt) where
+ ppr fm = ppr (fmToList fm)
#endif
#if 0