[commit: ghc] overlapping-tyfams: Small bugfixes found from testing. (81bccef)
Richard Eisenberg
eir at cis.upenn.edu
Fri Jun 21 15:17:14 CEST 2013
Repository : http://darcs.haskell.org/ghc.git/
On branch : overlapping-tyfams
https://github.com/ghc/ghc/commit/81bccef9e977fa9bb7816a5cb1d6995414556012
>---------------------------------------------------------------
commit 81bccef9e977fa9bb7816a5cb1d6995414556012
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date: Thu Jun 20 16:34:27 2013 +0100
Small bugfixes found from testing.
>---------------------------------------------------------------
compiler/deSugar/DsMeta.hs | 12 ++++++++----
compiler/iface/IfaceSyn.lhs | 23 ++++++++++++++++-------
2 files changed, 24 insertions(+), 11 deletions(-)
diff --git a/compiler/deSugar/DsMeta.hs b/compiler/deSugar/DsMeta.hs
index a318b49..7717ff8 100644
--- a/compiler/deSugar/DsMeta.hs
+++ b/compiler/deSugar/DsMeta.hs
@@ -271,7 +271,7 @@ repFamilyDecl (L loc (FamilyDecl { fdInfo = info,
fdKindSig = opt_kind }))
= do { tc1 <- lookupLOcc tc -- See note [Binders and occurrences]
; dec <- addTyClTyVarBinds tvs $ \bndrs ->
- do { info' <- repFamilyInfo info
+ do {
; case (opt_kind, info) of
(Nothing, ClosedTypeFamily eqns) ->
do { eqns1 <- mapM repTyFamEqn eqns
@@ -282,9 +282,13 @@ repFamilyDecl (L loc (FamilyDecl { fdInfo = info,
; eqns2 <- coreList tySynEqnQTyConName eqns1
; ki1 <- repLKind ki
; repClosedFamilyKind tc1 bndrs ki1 eqns2 }
- (Nothing, _) -> repFamilyNoKind info' tc1 bndrs
- (Just ki, _) -> do { ki1 <- repLKind ki
- ; repFamilyKind info' tc1 bndrs ki1 }
+ (Nothing, _) ->
+ do { info' <- repFamilyInfo info
+ ; repFamilyNoKind info' tc1 bndrs }
+ (Just ki, _) ->
+ do { info' <- repFamilyInfo info
+ ; ki1 <- repLKind ki
+ ; repFamilyKind info' tc1 bndrs ki1 }
}
; return (loc, dec)
}
diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs
index 3c3dd87..b38e43b 100644
--- a/compiler/iface/IfaceSyn.lhs
+++ b/compiler/iface/IfaceSyn.lhs
@@ -128,10 +128,22 @@ data IfaceAT = IfaceAT IfaceDecl [IfaceAxBranch]
-- Just ds => default associated type instance from these templates
instance Outputable IfaceAxBranch where
- ppr (IfaceAxBranch { ifaxbTyVars = tvs, ifaxbLHS = pat_tys, ifaxbRHS = ty
- , ifaxbIncomps = incomps })
- = ppr tvs <+> hsep (map ppr pat_tys) <+> char '=' <+> ppr ty $$ maybe_incomps
+ ppr = pprAxBranch Nothing
+
+pprAxBranch :: Maybe IfaceTyCon -> IfaceAxBranch -> SDoc
+pprAxBranch mtycon (IfaceAxBranch { ifaxbTyVars = tvs
+ , ifaxbLHS = pat_tys
+ , ifaxbRHS = ty
+ , ifaxbIncomps = incomps })
+ = ppr tvs <+> ppr_lhs <+> char '=' <+> ppr ty $+$
+ nest 4 maybe_incomps
where
+ ppr_lhs
+ | Just tycon <- mtycon
+ = ppr (IfaceTyConApp tycon pat_tys)
+ | otherwise
+ = hsep (map ppr pat_tys)
+
maybe_incomps
| [] <- incomps
= empty
@@ -554,10 +566,7 @@ pprIfaceDecl (IfaceClass {ifCtxt = context, ifName = clas, ifTyVars = tyvars,
pprIfaceDecl (IfaceAxiom {ifName = name, ifTyCon = tycon, ifAxBranches = branches })
= hang (ptext (sLit "axiom") <+> ppr name <> colon)
- 2 (vcat $ map ppr_branch branches)
- where
- ppr_branch (IfaceAxBranch { ifaxbTyVars = tyvars, ifaxbLHS = lhs, ifaxbRHS = rhs })
- = pprIfaceTvBndrs tyvars <> dot <+> ppr (IfaceTyConApp tycon lhs) <+> text "~#" <+> ppr rhs
+ 2 (vcat $ map (pprAxBranch $ Just tycon) branches)
pprCType :: Maybe CType -> SDoc
pprCType Nothing = ptext (sLit "No C type associated")
More information about the ghc-commits
mailing list