X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;ds=sidebyside;f=compiler%2Fiface%2FIfaceSyn.lhs;h=8ac4eecc87644a8be398ec02f20667ac237b3a32;hb=2a8cdc3aee5997374273e27365f92c161aca8453;hp=75ba52f64a44bff39b8992f9b614e3193a051dce;hpb=844fa86873b806594191043afdea638472f45619;p=ghc-hetmet.git diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs index 75ba52f..8ac4eec 100644 --- a/compiler/iface/IfaceSyn.lhs +++ b/compiler/iface/IfaceSyn.lhs @@ -20,7 +20,7 @@ module IfaceSyn ( IfaceInfoItem(..), IfaceRule(..), IfaceInst(..), IfaceFamInst(..), -- Misc - visibleIfConDecls, extractIfFamInsts, + visibleIfConDecls, -- Equality IfaceEq(..), (&&&), bool, eqListBy, eqMaybeBy, @@ -36,22 +36,17 @@ import CoreSyn import IfaceType import NewDemand ( StrictSig, pprIfaceStrictSig ) -import TcType ( deNoteType ) import Class ( FunDep, DefMeth, pprFundeps ) import OccName ( OccName, parenSymOcc, occNameFS, OccSet, unionOccSets, unitOccSet, occSetElts ) import UniqFM ( UniqFM, emptyUFM, addToUFM, lookupUFM ) -import Name ( Name, NamedThing(..), nameOccName, isExternalName ) import CostCentre ( CostCentre, pprCostCentreCore ) import Literal ( Literal ) import ForeignCall ( ForeignCall ) import BasicTypes ( Arity, Activation(..), StrictnessMark, OverlapFlag, - RecFlag(..), Boxity(..), - isAlwaysActive, tupleParens ) + RecFlag(..), Boxity(..), tupleParens ) import Outputable import FastString -import Maybes ( catMaybes ) -import Util ( lengthIs ) infixl 3 &&& infix 4 `eqIfExt`, `eqIfIdInfo`, `eqIfType` @@ -85,7 +80,7 @@ data IfaceDecl -- been compiled with -- different flags to the -- current compilation unit - ifFamInst :: Maybe IfaceFamInst + ifFamInst :: Maybe (IfaceTyCon, [IfaceType]) -- Just <=> instance of family } @@ -155,15 +150,11 @@ data IfaceInst -- and if the head does not change it won't be used if it wasn't before data IfaceFamInst - = IfaceFamInst { ifFamInstTyCon :: IfaceTyCon -- Family tycon - , ifFamInstTys :: [IfaceType] -- Instance types + = IfaceFamInst { ifFamInstFam :: IfaceExtName -- Family tycon + , ifFamInstTys :: [Maybe IfaceTyCon] -- Rough match types + , ifFamInstTyCon :: IfaceTyCon -- Instance decl } -extractIfFamInsts :: [IfaceDecl] -> [(IfaceFamInst, IfaceDecl)] -extractIfFamInsts decls = - [(famInst, decl) | decl@IfaceData {ifFamInst = Just famInst} <- decls] - -- !!!TODO: we also need a similar case for synonyms - data IfaceRule = IfaceRule { ifRuleName :: RuleName, @@ -330,7 +321,7 @@ pprIfaceConDecl tc con_tau = foldr1 IfaceFunTy (arg_tys ++ [tc_app]) tc_app = IfaceTyConApp (IfaceTc (LocalTop tc)) [IfaceTyVar tv | (tv,_) <- univ_tvs] - -- Gruesome, but jsut for debug print + -- Gruesome, but just for debug print instance Outputable IfaceRule where ppr (IfaceRule { ifRuleName = name, ifActivation = act, ifRuleBndrs = bndrs, @@ -345,15 +336,19 @@ instance Outputable IfaceInst where ppr (IfaceInst {ifDFun = dfun_id, ifOFlag = flag, ifInstCls = cls, ifInstTys = mb_tcs}) = hang (ptext SLIT("instance") <+> ppr flag - <+> ppr cls <+> brackets (pprWithCommas ppr_mb mb_tcs)) + <+> ppr cls <+> brackets (pprWithCommas ppr_rough mb_tcs)) 2 (equals <+> ppr dfun_id) - where - ppr_mb Nothing = dot - ppr_mb (Just tc) = ppr tc instance Outputable IfaceFamInst where - ppr (IfaceFamInst {ifFamInstTyCon = tycon, ifFamInstTys = tys}) - = ppr tycon <+> hsep (map ppr tys) + ppr (IfaceFamInst {ifFamInstFam = fam, ifFamInstTys = mb_tcs, + ifFamInstTyCon = tycon_id}) + = hang (ptext SLIT("family instance") <+> + ppr fam <+> brackets (pprWithCommas ppr_rough mb_tcs)) + 2 (equals <+> ppr tycon_id) + +ppr_rough :: Maybe IfaceTyCon -> SDoc +ppr_rough Nothing = dot +ppr_rough (Just tc) = ppr tc \end{code} @@ -384,21 +379,22 @@ pprIfaceExpr add_par e@(IfaceLam _ _) collect bs (IfaceLam b e) = collect (b:bs) e collect bs e = (reverse bs, e) --- gaw 2004 pprIfaceExpr add_par (IfaceCase scrut bndr ty [(con, bs, rhs)]) --- gaw 2004 - = add_par (sep [ptext SLIT("case") <+> char '@' <+> pprParendIfaceType ty <+> pprIfaceExpr noParens scrut <+> ptext SLIT("of") + = add_par (sep [ptext SLIT("case") <+> char '@' <+> pprParendIfaceType ty + <+> pprIfaceExpr noParens scrut <+> ptext SLIT("of") <+> ppr bndr <+> char '{' <+> ppr_con_bs con bs <+> arrow, pprIfaceExpr noParens rhs <+> char '}']) --- gaw 2004 pprIfaceExpr add_par (IfaceCase scrut bndr ty alts) --- gaw 2004 - = add_par (sep [ptext SLIT("case") <+> char '@' <+> pprParendIfaceType ty <+> pprIfaceExpr noParens scrut <+> ptext SLIT("of") + = add_par (sep [ptext SLIT("case") <+> char '@' <+> pprParendIfaceType ty + <+> pprIfaceExpr noParens scrut <+> ptext SLIT("of") <+> ppr bndr <+> char '{', nest 2 (sep (map ppr_alt alts)) <+> char '}']) -pprIfaceExpr add_par (IfaceCast expr co) = add_par (ptext SLIT("cast") <+> ppr expr <+> ppr co) +pprIfaceExpr add_par (IfaceCast expr co) + = sep [pprIfaceExpr parens expr, + nest 2 (ptext SLIT("`cast`")), + pprParendIfaceType co] pprIfaceExpr add_par (IfaceLet (IfaceNonRec b rhs) body) = add_par (sep [ptext SLIT("let {"), @@ -571,11 +567,10 @@ eqIfDecl d1@(IfaceData {}) d2@(IfaceData {}) -- over the constructors (any more), but they do scope -- over the stupid context in the IfaceConDecls where - Nothing `eqIfTc_fam` Nothing = Equal - (Just (IfaceFamInst fam1 tys1)) - `eqIfTc_fam` (Just (IfaceFamInst fam2 tys2)) = + Nothing `eqIfTc_fam` Nothing = Equal + (Just (fam1, tys1)) `eqIfTc_fam` (Just (fam2, tys2)) = fam1 `eqIfTc` fam2 &&& eqListBy eqIfType tys1 tys2 - _ `eqIfTc_fam` _ = NotEqual + _ `eqIfTc_fam` _ = NotEqual eqIfDecl d1@(IfaceSyn {}) d2@(IfaceSyn {}) = bool (ifName d1 == ifName d2) &&& @@ -754,7 +749,7 @@ type EqEnv = UniqFM FastString -- Tracks the mapping from L-variables to R-varia eqIfOcc :: EqEnv -> FastString -> FastString -> IfaceEq eqIfOcc env n1 n2 = case lookupUFM env n1 of Just n1 -> bool (n1 == n2) - Nothing -> bool (show n1 == show n2) + Nothing -> bool (n1 == n2) extendEqEnv :: EqEnv -> FastString -> FastString -> EqEnv extendEqEnv env n1 n2 | n1 == n2 = env