X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Fmain%2FPprTyThing.hs;h=d859784fad746f86a03fcd25c05175128bdffbfb;hb=3deca8f44135bd1a146902f498189af00dd4d7b4;hp=16f5181af8b5cc6b2d8c7aed715563208f690a09;hpb=f12d4af480bc8fea6a44777199c9a32f60f444b9;p=ghc-hetmet.git diff --git a/compiler/main/PprTyThing.hs b/compiler/main/PprTyThing.hs index 16f5181..d859784 100644 --- a/compiler/main/PprTyThing.hs +++ b/compiler/main/PprTyThing.hs @@ -9,25 +9,25 @@ module PprTyThing ( PrintExplicitForalls, pprTyThing, - pprTyThingInContext, + pprTyThingInContext, pprTyThingParent_maybe, pprTyThingLoc, pprTyThingInContextLoc, pprTyThingHdr, pprTypeForUser ) where -#include "HsVersions.h" - import qualified GHC import GHC ( TyThing(..) ) +import DataCon +import Id +import IdInfo import TyCon -import Type ( TyThing(..), tidyTopType, pprTypeApp ) import TcType import Var import Name import Outputable -import Pretty ( Doc ) +import FastString -- ----------------------------------------------------------------------------- -- Pretty-printing entities that we get from the GHC API @@ -37,6 +37,12 @@ import Pretty ( Doc ) type PrintExplicitForalls = Bool +type ShowMe = Name -> Bool +-- The ShowMe function says which sub-components to print +-- True <=> print +-- False <=> elide to "..." + +---------------------------- -- | Pretty-prints a 'TyThing' with its defining location. pprTyThingLoc :: PrintExplicitForalls -> TyThing -> SDoc pprTyThingLoc pefas tyThing @@ -45,26 +51,41 @@ pprTyThingLoc pefas tyThing -- | Pretty-prints a 'TyThing'. pprTyThing :: PrintExplicitForalls -> TyThing -> SDoc -pprTyThing pefas (AnId id) = pprId pefas id -pprTyThing pefas (ADataCon dataCon) = pprDataConSig pefas dataCon -pprTyThing pefas (ATyCon tyCon) = pprTyCon pefas tyCon -pprTyThing pefas (AClass cls) = pprClass pefas cls +pprTyThing pefas thing = ppr_ty_thing pefas (const True) thing --- | Like 'pprTyThingInContext', but adds the defining location. -pprTyThingInContextLoc :: PrintExplicitForalls -> TyThing -> SDoc -pprTyThingInContextLoc pefas tyThing - = showWithLoc loc (pprTyThingInContext pefas tyThing) - where loc = pprNameLoc (GHC.getName tyThing) +ppr_ty_thing :: PrintExplicitForalls -> ShowMe -> TyThing -> SDoc +ppr_ty_thing pefas _ (AnId id) = pprId pefas id +ppr_ty_thing pefas _ (ADataCon dataCon) = pprDataConSig pefas dataCon +ppr_ty_thing pefas show_me (ATyCon tyCon) = pprTyCon pefas show_me tyCon +ppr_ty_thing pefas show_me (AClass cls) = pprClass pefas show_me cls -- | Pretty-prints a 'TyThing' in context: that is, if the entity -- is a data constructor, record selector, or class method, then -- the entity's parent declaration is pretty-printed with irrelevant -- parts omitted. pprTyThingInContext :: PrintExplicitForalls -> TyThing -> SDoc -pprTyThingInContext pefas (AnId id) = pprIdInContext pefas id -pprTyThingInContext pefas (ADataCon dataCon) = pprDataCon pefas dataCon -pprTyThingInContext pefas (ATyCon tyCon) = pprTyCon pefas tyCon -pprTyThingInContext pefas (AClass cls) = pprClass pefas cls +pprTyThingInContext pefas thing + | Just parent <- pprTyThingParent_maybe thing + = ppr_ty_thing pefas (== GHC.getName thing) parent + | otherwise + = pprTyThing pefas thing + +-- | Like 'pprTyThingInContext', but adds the defining location. +pprTyThingInContextLoc :: PrintExplicitForalls -> TyThing -> SDoc +pprTyThingInContextLoc pefas tyThing + = showWithLoc (pprNameLoc (GHC.getName tyThing)) + (pprTyThingInContext pefas tyThing) + +pprTyThingParent_maybe :: TyThing -> Maybe TyThing +-- (pprTyThingParent_maybe x) returns (Just p) +-- when pprTyThingInContext sould print a declaration for p +-- (albeit with some "..." in it) when asked to show x +pprTyThingParent_maybe (ADataCon dc) = Just (ATyCon (dataConTyCon dc)) +pprTyThingParent_maybe (AnId id) = case idDetails id of + RecSelId { sel_tycon = tc } -> Just (ATyCon tc) + ClassOpId cls -> Just (AClass cls) + _other -> Nothing +pprTyThingParent_maybe _other = Nothing -- | Pretty-prints the 'TyThing' header. For functions and data constructors -- the function is equivalent to 'pprTyThing' but for type constructors @@ -75,10 +96,10 @@ pprTyThingHdr pefas (ADataCon dataCon) = pprDataConSig pefas dataCon pprTyThingHdr pefas (ATyCon tyCon) = pprTyConHdr pefas tyCon pprTyThingHdr pefas (AClass cls) = pprClassHdr pefas cls -pprTyConHdr :: PrintExplicitForalls -> TyCon -> PprStyle -> Doc +pprTyConHdr :: PrintExplicitForalls -> TyCon -> SDoc pprTyConHdr _ tyCon | Just (_fam_tc, tys) <- tyConFamInst_maybe tyCon - = ptext keyword <+> ptext SLIT("instance") <+> pprTypeApp tyCon (ppr_bndr tyCon) tys + = ptext keyword <+> ptext (sLit "instance") <+> pprTypeApp tyCon tys | otherwise = ptext keyword <+> opt_family <+> opt_stupid <+> ppr_bndr tyCon <+> hsep (map ppr vars) where @@ -86,45 +107,32 @@ pprTyConHdr _ tyCon GHC.isFunTyCon tyCon = take (GHC.tyConArity tyCon) GHC.alphaTyVars | otherwise = GHC.tyConTyVars tyCon - keyword | GHC.isSynTyCon tyCon = SLIT("type") - | GHC.isNewTyCon tyCon = SLIT("newtype") - | otherwise = SLIT("data") + keyword | GHC.isSynTyCon tyCon = sLit "type" + | GHC.isNewTyCon tyCon = sLit "newtype" + | otherwise = sLit "data" opt_family - | GHC.isOpenTyCon tyCon = ptext SLIT("family") + | GHC.isFamilyTyCon tyCon = ptext (sLit "family") | otherwise = empty opt_stupid -- The "stupid theta" part of the declaration | isAlgTyCon tyCon = GHC.pprThetaArrow (tyConStupidTheta tyCon) | otherwise = empty -- Returns 'empty' if null theta -pprDataConSig :: PrintExplicitForalls -> GHC.DataCon -> PprStyle -> Doc -pprDataConSig pefas dataCon = - ppr_bndr dataCon <+> dcolon <+> pprTypeForUser pefas (GHC.dataConType dataCon) - -pprClassHdr :: PrintExplicitForalls -> GHC.Class -> PprStyle -> Doc -pprClassHdr _ cls = - let (tyVars, funDeps) = GHC.classTvsFds cls - in ptext SLIT("class") <+> - GHC.pprThetaArrow (GHC.classSCTheta cls) <+> - ppr_bndr cls <+> - hsep (map ppr tyVars) <+> - GHC.pprFundeps funDeps - -pprIdInContext :: PrintExplicitForalls -> Var -> PprStyle -> Doc -pprIdInContext pefas id - | GHC.isRecordSelector id = pprRecordSelector pefas id - | Just cls <- GHC.isClassOpId_maybe id = pprClassOneMethod pefas cls id - | otherwise = pprId pefas id - -pprRecordSelector :: PrintExplicitForalls -> Id -> PprStyle -> Doc -pprRecordSelector pefas id - = pprAlgTyCon pefas tyCon show_con show_label +pprDataConSig :: PrintExplicitForalls -> GHC.DataCon -> SDoc +pprDataConSig pefas dataCon + = ppr_bndr dataCon <+> dcolon <+> pprTypeForUser pefas (GHC.dataConType dataCon) + +pprClassHdr :: PrintExplicitForalls -> GHC.Class -> SDoc +pprClassHdr _ cls + = ptext (sLit "class") <+> + GHC.pprThetaArrow (GHC.classSCTheta cls) <+> + ppr_bndr cls <+> + hsep (map ppr tyVars) <+> + GHC.pprFundeps funDeps where - (tyCon,label) = GHC.recordSelectorFieldLabel id - show_con dataCon = label `elem` GHC.dataConFieldLabels dataCon - show_label label' = label == label' - + (tyVars, funDeps) = GHC.classTvsFds cls + pprId :: PrintExplicitForalls -> Var -> SDoc pprId pefas ident = hang (ppr_bndr ident <+> dcolon) @@ -141,28 +149,26 @@ pprTypeForUser :: PrintExplicitForalls -> GHC.Type -> SDoc -- (C a, Ord b) => stuff pprTypeForUser print_foralls ty | print_foralls = ppr tidy_ty - | otherwise = ppr (mkPhiTy [p | (_tvs, ps) <- ctxt, p <- ps] ty') + | otherwise = ppr (mkPhiTy ctxt ty') where tidy_ty = tidyTopType ty - (ctxt, ty') = tcMultiSplitSigmaTy tidy_ty + (_, ctxt, ty') = tcSplitSigmaTy tidy_ty -pprTyCon :: PrintExplicitForalls -> TyCon -> PprStyle -> Doc -pprTyCon pefas tyCon +pprTyCon :: PrintExplicitForalls -> ShowMe -> TyCon -> SDoc +pprTyCon pefas show_me tyCon | GHC.isSynTyCon tyCon - = if GHC.isOpenTyCon tyCon + = if GHC.isFamilyTyCon tyCon then pprTyConHdr pefas tyCon <+> dcolon <+> pprTypeForUser pefas (GHC.synTyConResKind tyCon) else let rhs_type = GHC.synTyConType tyCon in hang (pprTyConHdr pefas tyCon <+> equals) 2 (pprTypeForUser pefas rhs_type) | otherwise - = pprAlgTyCon pefas tyCon (const True) (const True) + = pprAlgTyCon pefas show_me tyCon -pprAlgTyCon :: PrintExplicitForalls -> TyCon -> (GHC.DataCon -> Bool) - -> (FieldLabel -> Bool) -> PprStyle - -> Doc -pprAlgTyCon pefas tyCon ok_con ok_label - | gadt = pprTyConHdr pefas tyCon <+> ptext SLIT("where") $$ +pprAlgTyCon :: PrintExplicitForalls -> ShowMe -> TyCon -> SDoc +pprAlgTyCon pefas show_me tyCon + | gadt = pprTyConHdr pefas tyCon <+> ptext (sLit "where") $$ nest 2 (vcat (ppr_trim show_con datacons)) | otherwise = hang (pprTyConHdr pefas tyCon) 2 (add_bars (ppr_trim show_con datacons)) @@ -170,53 +176,40 @@ pprAlgTyCon pefas tyCon ok_con ok_label datacons = GHC.tyConDataCons tyCon gadt = any (not . GHC.isVanillaDataCon) datacons - show_con dataCon - | ok_con dataCon = Just (pprDataConDecl pefas gadt ok_label dataCon) - | otherwise = Nothing + ok_con dc = show_me (dataConName dc) || any show_me (dataConFieldLabels dc) + show_con dc + | ok_con dc = Just (pprDataConDecl pefas show_me gadt dc) + | otherwise = Nothing -pprDataCon :: PrintExplicitForalls -> GHC.DataCon -> PprStyle -> Doc -pprDataCon pefas dataCon = pprAlgTyCon pefas tyCon (== dataCon) (const True) - where tyCon = GHC.dataConTyCon dataCon - -pprDataConDecl :: PrintExplicitForalls -> Bool -> (FieldLabel -> Bool) - -> GHC.DataCon -> PprStyle - -> Doc -pprDataConDecl _ gadt_style show_label dataCon +pprDataConDecl :: PrintExplicitForalls -> ShowMe -> Bool -> GHC.DataCon -> SDoc +pprDataConDecl pefas show_me gadt_style dataCon | not gadt_style = ppr_fields tys_w_strs | otherwise = ppr_bndr dataCon <+> dcolon <+> - sep [ ppr_tvs, GHC.pprThetaArrow theta, pp_tau ] + sep [ pp_foralls, GHC.pprThetaArrow theta, pp_tau ] + -- Printing out the dataCon as a type signature, in GADT style where - (tyvars, theta, argTypes, res_ty) = GHC.dataConSig dataCon - tyCon = GHC.dataConTyCon dataCon - labels = GHC.dataConFieldLabels dataCon - qualVars = filter (flip notElem (GHC.tyConTyVars tyCon)) tyvars - stricts = GHC.dataConStrictMarks dataCon - tys_w_strs = zip stricts argTypes - - ppr_tvs - | null qualVars = empty - | otherwise = ptext SLIT("forall") <+> - hsep (map ppr qualVars) <> dot - - -- printing out the dataCon as a type signature, in GADT style + (forall_tvs, theta, tau) = tcSplitSigmaTy (GHC.dataConUserType dataCon) + (arg_tys, res_ty) = tcSplitFunTys tau + labels = GHC.dataConFieldLabels dataCon + stricts = GHC.dataConStrictMarks dataCon + tys_w_strs = zip stricts arg_tys + pp_foralls | pefas = GHC.pprForAll forall_tvs + | otherwise = empty + pp_tau = foldr add (ppr res_ty) tys_w_strs add str_ty pp_ty = pprParendBangTy str_ty <+> arrow <+> pp_ty - pprParendBangTy (strict,ty) - | GHC.isMarkedStrict strict = char '!' <> GHC.pprParendType ty - | otherwise = GHC.pprParendType ty + pprParendBangTy (bang,ty) = ppr bang <> GHC.pprParendType ty - pprBangTy strict ty - | GHC.isMarkedStrict strict = char '!' <> ppr ty - | otherwise = ppr ty + pprBangTy bang ty = ppr bang <> ppr ty maybe_show_label (lbl,(strict,tp)) - | show_label lbl = Just (ppr lbl <+> dcolon <+> pprBangTy strict tp) - | otherwise = Nothing + | show_me lbl = Just (ppr lbl <+> dcolon <+> pprBangTy strict tp) + | otherwise = Nothing ppr_fields [ty1, ty2] | GHC.dataConIsInfix dataCon && null labels - = sep [pprParendBangTy ty1, ppr dataCon, pprParendBangTy ty2] + = sep [pprParendBangTy ty1, pprInfixName dataCon, pprParendBangTy ty2] ppr_fields fields | null labels = ppr_bndr dataCon <+> sep (map pprParendBangTy fields) @@ -225,26 +218,19 @@ pprDataConDecl _ gadt_style show_label dataCon braces (sep (punctuate comma (ppr_trim maybe_show_label (zip labels fields)))) -pprClass :: PrintExplicitForalls -> GHC.Class -> PprStyle -> Doc -pprClass pefas cls - | null methods = - pprClassHdr pefas cls - | otherwise = - hang (pprClassHdr pefas cls <+> ptext SLIT("where")) - 2 (vcat (map (pprClassMethod pefas) methods)) - where - methods = GHC.classMethods cls - -pprClassOneMethod :: PrintExplicitForalls -> GHC.Class -> Id -> PprStyle -> Doc -pprClassOneMethod pefas cls this_one - = hang (pprClassHdr pefas cls <+> ptext SLIT("where")) - 2 (vcat (ppr_trim show_meth methods)) +pprClass :: PrintExplicitForalls -> ShowMe -> GHC.Class -> SDoc +pprClass pefas show_me cls + | null methods + = pprClassHdr pefas cls + | otherwise + = hang (pprClassHdr pefas cls <+> ptext (sLit "where")) + 2 (vcat (ppr_trim show_meth methods)) where - methods = GHC.classMethods cls - show_meth id | id == this_one = Just (pprClassMethod pefas id) - | otherwise = Nothing + methods = GHC.classMethods cls + show_meth id | show_me (idName id) = Just (pprClassMethod pefas id) + | otherwise = Nothing -pprClassMethod :: PrintExplicitForalls -> Id -> PprStyle -> Doc +pprClassMethod :: PrintExplicitForalls -> Id -> SDoc pprClassMethod pefas id = hang (ppr_bndr id <+> dcolon) 2 (pprTypeForUser pefas op_ty) where @@ -270,9 +256,9 @@ ppr_trim show xs go x (eliding, so_far) | Just doc <- show x = (False, doc : so_far) | otherwise = if eliding then (True, so_far) - else (True, ptext SLIT("...") : so_far) + else (True, ptext (sLit "...") : so_far) -add_bars :: [SDoc] -> PprStyle -> Doc +add_bars :: [SDoc] -> SDoc add_bars [] = empty add_bars [c] = equals <+> c add_bars (c:cs) = sep ((equals <+> c) : map (char '|' <+>) cs) @@ -286,5 +272,5 @@ showWithLoc loc doc = hang doc 2 (char '\t' <> comment <+> loc) -- The tab tries to make them line up a bit where - comment = ptext SLIT("--") + comment = ptext (sLit "--")