X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2FhsSyn%2FHsDecls.lhs;h=070079e6a6cbb0a4ee9735bb63225aeb67129453;hp=8ff39857c610ab4d4af4e3ef09c914af3818651a;hb=afef39736dcde6f4947a6f362f9e6b3586933db4;hpb=0065d5ab628975892cea1ec7303f968c3338cbe1 diff --git a/compiler/hsSyn/HsDecls.lhs b/compiler/hsSyn/HsDecls.lhs index 8ff3985..070079e 100644 --- a/compiler/hsSyn/HsDecls.lhs +++ b/compiler/hsSyn/HsDecls.lhs @@ -21,6 +21,7 @@ module HsDecls ( isClassDecl, isSynDecl, isDataDecl, countTyClDecls, conDetailsTys, + instDeclATs, collectRuleBndrSigTys, ) where @@ -341,7 +342,8 @@ data TyClDecl name tcdCtxt :: LHsContext name, -- Context tcdLName :: Located name, -- Type constructor tcdTyVars :: [LHsTyVarBndr name], -- Type variables - tcdKindSig :: Maybe Kind, -- Optional kind sig; + tcdTyPats :: Maybe [LHsType name], -- Type patterns + tcdKindSig:: Maybe Kind, -- Optional kind sig; -- (only for the 'where' form) tcdCons :: [LConDecl name], -- Data constructors @@ -367,7 +369,10 @@ data TyClDecl name tcdTyVars :: [LHsTyVarBndr name], -- Class type variables tcdFDs :: [Located (FunDep name)], -- Functional deps tcdSigs :: [LSig name], -- Methods' signatures - tcdMeths :: LHsBinds name -- Default methods + tcdMeths :: LHsBinds name, -- Default methods + tcdATs :: [LTyClDecl name] -- Associated types; ie + -- only 'TyData' + -- and 'TySynonym' } data NewOrData @@ -406,8 +411,9 @@ tyClDeclNames :: Eq name => TyClDecl name -> [Located name] tyClDeclNames (TySynonym {tcdLName = name}) = [name] tyClDeclNames (ForeignType {tcdLName = name}) = [name] -tyClDeclNames (ClassDecl {tcdLName = cls_name, tcdSigs = sigs}) - = cls_name : [n | L _ (TypeSig n _) <- sigs] +tyClDeclNames (ClassDecl {tcdLName = cls_name, tcdSigs = sigs, tcdATs = ats}) + = cls_name : + concatMap (tyClDeclNames . unLoc) ats ++ [n | L _ (TypeSig n _) <- sigs] tyClDeclNames (TyData {tcdLName = tc_name, tcdCons = cons}) = tc_name : conDeclsNames (map unLoc cons) @@ -442,38 +448,51 @@ instance OutputableBndr name = hsep [ptext SLIT("foreign import type dotnet"), ppr ltycon] ppr (TySynonym {tcdLName = ltycon, tcdTyVars = tyvars, tcdSynRhs = mono_ty}) - = hang (ptext SLIT("type") <+> pp_decl_head [] ltycon tyvars <+> equals) + = hang (ptext SLIT("type") <+> pp_decl_head [] ltycon tyvars Nothing <+> equals) 4 (ppr mono_ty) ppr (TyData {tcdND = new_or_data, tcdCtxt = context, tcdLName = ltycon, - tcdTyVars = tyvars, tcdKindSig = mb_sig, tcdCons = condecls, - tcdDerivs = derivings}) - = pp_tydecl (ppr new_or_data <+> pp_decl_head (unLoc context) ltycon tyvars <+> ppr_sig mb_sig) + tcdTyVars = tyvars, tcdTyPats = typats, tcdKindSig = mb_sig, + tcdCons = condecls, tcdDerivs = derivings}) + = pp_tydecl (ppr new_or_data <+> + pp_decl_head (unLoc context) ltycon tyvars typats <+> + ppr_sig mb_sig) (pp_condecls condecls) derivings where ppr_sig Nothing = empty ppr_sig (Just kind) = dcolon <+> pprKind kind - ppr (ClassDecl {tcdCtxt = context, tcdLName = lclas, tcdTyVars = tyvars, tcdFDs = fds, - tcdSigs = sigs, tcdMeths = methods}) - | null sigs -- No "where" part + ppr (ClassDecl {tcdCtxt = context, tcdLName = lclas, tcdTyVars = tyvars, + tcdFDs = fds, + tcdSigs = sigs, tcdMeths = methods, tcdATs = ats}) + | null sigs && null ats -- No "where" part = top_matter | otherwise -- Laid out = sep [hsep [top_matter, ptext SLIT("where {")], - nest 4 (sep [sep (map ppr_sig sigs), ppr methods, char '}'])] + nest 4 (sep [ sep (map ppr_semi ats) + , sep (map ppr_semi sigs) + , pprLHsBinds methods + , char '}'])] where - top_matter = ptext SLIT("class") <+> pp_decl_head (unLoc context) lclas tyvars <+> pprFundeps (map unLoc fds) - ppr_sig sig = ppr sig <> semi + top_matter = ptext SLIT("class") + <+> pp_decl_head (unLoc context) lclas tyvars Nothing + <+> pprFundeps (map unLoc fds) + ppr_semi decl = ppr decl <> semi pp_decl_head :: OutputableBndr name => HsContext name -> Located name -> [LHsTyVarBndr name] + -> Maybe [LHsType name] -> SDoc -pp_decl_head context thing tyvars +pp_decl_head context thing tyvars Nothing -- no explicit type patterns = hsep [pprHsContext context, ppr thing, interppSP tyvars] +pp_decl_head context thing _ (Just typats) -- explicit type patterns + = hsep [ pprHsContext context, ppr thing + , hsep (map (pprParendHsType.unLoc) typats)] + pp_condecls cs@(L _ ConDecl{ con_res = ResTyGADT _ } : _) -- In GADT syntax = hang (ptext SLIT("where")) 2 (vcat (map ppr cs)) pp_condecls cs -- In H98 syntax @@ -569,13 +588,13 @@ pprConDecl (ConDecl con expl tvs cxt details ResTyH98) ppr_details con (PrefixCon tys) = hsep (pprHsVar con : map ppr tys) ppr_details con (RecCon fields) = ppr con <+> ppr_fields fields -pprConDecl (ConDecl con expl tvs cxt details (ResTyGADT res_ty)) - = sep [pprHsForAll expl tvs cxt, ppr con <+> ppr_details details] +pprConDecl (ConDecl con expl tvs cxt (PrefixCon arg_tys) (ResTyGADT res_ty)) + = ppr con <+> dcolon <+> + sep [pprHsForAll expl tvs cxt, ppr (foldr mk_fun_ty res_ty arg_tys)] where - ppr_details (PrefixCon arg_tys) = dcolon <+> ppr (foldr mk_fun_ty res_ty arg_tys) - ppr_details (RecCon fields) = ppr fields <+> dcolon <+> ppr res_ty - mk_fun_ty a b = noLoc (HsFunTy a b) +pprConDecl (ConDecl con expl tvs cxt (RecCon fields) (ResTyGADT res_ty)) + = sep [pprHsForAll expl tvs cxt, ppr con <+> ppr fields <+> dcolon <+> ppr res_ty] ppr_fields fields = braces (sep (punctuate comma (map ppr_field fields))) ppr_field (n, ty) = ppr n <+> dcolon <+> ppr ty @@ -595,14 +614,21 @@ data InstDecl name -- Using a polytype means that the renamer conveniently -- figures out the quantified type variables for us. (LHsBinds name) - [LSig name] -- User-supplied pragmatic info + [LSig name] -- User-supplied pragmatic info + [LTyClDecl name]-- Associated types instance (OutputableBndr name) => Outputable (InstDecl name) where - ppr (InstDecl inst_ty binds uprags) + ppr (InstDecl inst_ty binds uprags ats) = vcat [hsep [ptext SLIT("instance"), ppr inst_ty, ptext SLIT("where")], + nest 4 (ppr ats), nest 4 (ppr uprags), nest 4 (pprLHsBinds binds) ] + +-- Extract the declarations of associated types from an instance +-- +instDeclATs :: InstDecl name -> [LTyClDecl name] +instDeclATs (InstDecl _ _ _ ats) = ats \end{code} %************************************************************************ @@ -645,10 +671,10 @@ instance (OutputableBndr name) type LForeignDecl name = Located (ForeignDecl name) data ForeignDecl name - = ForeignImport (Located name) (LHsType name) ForeignImport Bool -- defines name - | ForeignExport (Located name) (LHsType name) ForeignExport Bool -- uses name + = ForeignImport (Located name) (LHsType name) ForeignImport -- defines name + | ForeignExport (Located name) (LHsType name) ForeignExport -- uses name --- specification of an imported external entity in dependence on the calling +-- Specification Of an imported external entity in dependence on the calling -- convention -- data ForeignImport = -- import of a C entity @@ -698,10 +724,10 @@ data FoType = DNType -- In due course we'll add subtype stuff -- instance OutputableBndr name => Outputable (ForeignDecl name) where - ppr (ForeignImport n ty fimport _) = + ppr (ForeignImport n ty fimport) = ptext SLIT("foreign import") <+> ppr fimport <+> ppr n <+> dcolon <+> ppr ty - ppr (ForeignExport n ty fexport _) = + ppr (ForeignExport n ty fexport) = ptext SLIT("foreign export") <+> ppr fexport <+> ppr n <+> dcolon <+> ppr ty