X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2Fmain%2FPprTyThing.hs;h=7c50680deffda06650ce5679b77ec0d285973a07;hp=51144ecda034c7b2c66e3f216924ac8eecef5ff2;hb=ad94d40948668032189ad22a0ad741ac1f645f50;hpb=cd290fc88d35d5a32c994664baa56a5eae250e9e diff --git a/compiler/main/PprTyThing.hs b/compiler/main/PprTyThing.hs index 51144ec..7c50680 100644 --- a/compiler/main/PprTyThing.hs +++ b/compiler/main/PprTyThing.hs @@ -6,7 +6,15 @@ -- ----------------------------------------------------------------------------- +{-# OPTIONS -w #-} +-- The above warning supression flag is a temporary kludge. +-- While working on this module you are encouraged to remove it and fix +-- any warnings in the module. See +-- http://hackage.haskell.org/trac/ghc/wiki/CodingStyle#Warnings +-- for details + module PprTyThing ( + PrintExplicitForalls, pprTyThing, pprTyThingInContext, pprTyThingLoc, @@ -18,8 +26,10 @@ module PprTyThing ( import qualified GHC -import GHC ( TyThing(..), SrcLoc ) -import DataCon ( dataConResTys ) +import TyCon ( tyConFamInst_maybe ) +import Type ( pprTypeApp ) +import GHC ( TyThing(..), SrcSpan ) +import Var import Outputable -- ----------------------------------------------------------------------------- @@ -28,46 +38,51 @@ import Outputable -- This should be a good source of sample code for using the GHC API to -- inspect source code entities. +type PrintExplicitForalls = Bool + -- | Pretty-prints a 'TyThing' with its defining location. -pprTyThingLoc :: Bool -> TyThing -> SDoc -pprTyThingLoc exts tyThing - = showWithLoc loc (pprTyThing exts tyThing) - where loc = GHC.nameSrcLoc (GHC.getName tyThing) +pprTyThingLoc :: PrintExplicitForalls -> TyThing -> SDoc +pprTyThingLoc pefas tyThing + = showWithLoc loc (pprTyThing pefas tyThing) + where loc = GHC.nameSrcSpan (GHC.getName tyThing) -- | Pretty-prints a 'TyThing'. -pprTyThing :: Bool -> TyThing -> SDoc -pprTyThing exts (AnId id) = pprId exts id -pprTyThing exts (ADataCon dataCon) = pprDataConSig exts dataCon -pprTyThing exts (ATyCon tyCon) = pprTyCon exts tyCon -pprTyThing exts (AClass cls) = pprClass exts cls - +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 + -- | Like 'pprTyThingInContext', but adds the defining location. -pprTyThingInContextLoc :: Bool -> TyThing -> SDoc -pprTyThingInContextLoc exts tyThing - = showWithLoc loc (pprTyThingInContext exts tyThing) - where loc = GHC.nameSrcLoc (GHC.getName tyThing) +pprTyThingInContextLoc :: PrintExplicitForalls -> TyThing -> SDoc +pprTyThingInContextLoc pefas tyThing + = showWithLoc loc (pprTyThingInContext pefas tyThing) + where loc = GHC.nameSrcSpan (GHC.getName tyThing) -- | 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 :: Bool -> TyThing -> SDoc -pprTyThingInContext exts (AnId id) = pprIdInContext exts id -pprTyThingInContext exts (ADataCon dataCon) = pprDataCon exts dataCon -pprTyThingInContext exts (ATyCon tyCon) = pprTyCon exts tyCon -pprTyThingInContext exts (AClass cls) = pprClass exts cls +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 -- | Pretty-prints the 'TyThing' header. For functions and data constructors -- the function is equivalent to 'pprTyThing' but for type constructors -- and classes it prints only the header part of the declaration. -pprTyThingHdr :: Bool -> TyThing -> SDoc -pprTyThingHdr exts (AnId id) = pprId exts id -pprTyThingHdr exts (ADataCon dataCon) = pprDataConSig exts dataCon -pprTyThingHdr exts (ATyCon tyCon) = pprTyConHdr exts tyCon -pprTyThingHdr exts (AClass cls) = pprClassHdr exts cls +pprTyThingHdr :: PrintExplicitForalls -> TyThing -> SDoc +pprTyThingHdr pefas (AnId id) = pprId pefas id +pprTyThingHdr pefas (ADataCon dataCon) = pprDataConSig pefas dataCon +pprTyThingHdr pefas (ATyCon tyCon) = pprTyConHdr pefas tyCon +pprTyThingHdr pefas (AClass cls) = pprClassHdr pefas cls -pprTyConHdr exts tyCon = - addFamily (ptext keyword) <+> ppr_bndr tyCon <+> hsep (map ppr vars) +pprTyConHdr pefas tyCon + | Just (fam_tc, tys) <- tyConFamInst_maybe tyCon + = ptext keyword <+> ptext SLIT("instance") <+> pprTypeApp tyCon (ppr_bndr tyCon) tys + | otherwise + = ptext keyword <+> opt_family <+> ppr_bndr tyCon <+> hsep (map ppr vars) where vars | GHC.isPrimTyCon tyCon || GHC.isFunTyCon tyCon = take (GHC.tyConArity tyCon) GHC.alphaTyVars @@ -77,14 +92,14 @@ pprTyConHdr exts tyCon = | GHC.isNewTyCon tyCon = SLIT("newtype") | otherwise = SLIT("data") - addFamily keytext - | GHC.isOpenTyCon tyCon = keytext <> ptext SLIT(" family") - | otherwise = keytext + opt_family + | GHC.isOpenTyCon tyCon = ptext SLIT("family") + | otherwise = empty -pprDataConSig exts dataCon = - ppr_bndr dataCon <+> dcolon <+> pprType exts (GHC.dataConType dataCon) +pprDataConSig pefas dataCon = + ppr_bndr dataCon <+> dcolon <+> pprType pefas (GHC.dataConType dataCon) -pprClassHdr exts cls = +pprClassHdr pefas cls = let (tyVars, funDeps) = GHC.classTvsFds cls in ptext SLIT("class") <+> GHC.pprThetaArrow (GHC.classSCTheta cls) <+> @@ -92,61 +107,62 @@ pprClassHdr exts cls = hsep (map ppr tyVars) <+> GHC.pprFundeps funDeps -pprIdInContext exts id - | GHC.isRecordSelector id = pprRecordSelector exts id - | Just cls <- GHC.isClassOpId_maybe id = pprClassOneMethod exts cls id - | otherwise = pprId exts id +pprIdInContext pefas id + | GHC.isRecordSelector id = pprRecordSelector pefas id + | Just cls <- GHC.isClassOpId_maybe id = pprClassOneMethod pefas cls id + | otherwise = pprId pefas id -pprRecordSelector exts id - = pprAlgTyCon exts tyCon show_con show_label +pprRecordSelector pefas id + = pprAlgTyCon pefas tyCon show_con show_label where (tyCon,label) = GHC.recordSelectorFieldLabel id show_con dataCon = label `elem` GHC.dataConFieldLabels dataCon show_label label' = label == label' -pprId exts id - = hang (ppr_bndr id <+> dcolon) 2 - (pprType exts (GHC.idType id)) +pprId :: PrintExplicitForalls -> Var -> SDoc +pprId pefas ident + = hang (ppr_bndr ident <+> dcolon) 2 + (pprType pefas (GHC.idType ident)) +pprType :: PrintExplicitForalls -> GHC.Type -> SDoc pprType True ty = ppr ty pprType False ty = ppr (GHC.dropForAlls ty) -pprTyCon exts tyCon +pprTyCon pefas tyCon | GHC.isSynTyCon tyCon = if GHC.isOpenTyCon tyCon - then pprTyConHdr exts tyCon <+> dcolon <+> - pprType exts (GHC.synTyConResKind tyCon) + then pprTyConHdr pefas tyCon <+> dcolon <+> + pprType pefas (GHC.synTyConResKind tyCon) else let rhs_type = GHC.synTyConType tyCon - in hang (pprTyConHdr exts tyCon <+> equals) 2 (pprType exts rhs_type) + in hang (pprTyConHdr pefas tyCon <+> equals) 2 (pprType pefas rhs_type) | otherwise - = pprAlgTyCon exts tyCon (const True) (const True) + = pprAlgTyCon pefas tyCon (const True) (const True) -pprAlgTyCon exts tyCon ok_con ok_label - | gadt = pprTyConHdr exts tyCon <+> ptext SLIT("where") $$ +pprAlgTyCon pefas tyCon ok_con ok_label + | gadt = pprTyConHdr pefas tyCon <+> ptext SLIT("where") $$ nest 2 (vcat (ppr_trim show_con datacons)) - | otherwise = hang (pprTyConHdr exts tyCon) + | otherwise = hang (pprTyConHdr pefas tyCon) 2 (add_bars (ppr_trim show_con datacons)) where datacons = GHC.tyConDataCons tyCon gadt = any (not . GHC.isVanillaDataCon) datacons show_con dataCon - | ok_con dataCon = Just (pprDataConDecl exts gadt ok_label dataCon) + | ok_con dataCon = Just (pprDataConDecl pefas gadt ok_label dataCon) | otherwise = Nothing -pprDataCon exts dataCon = pprAlgTyCon exts tyCon (== dataCon) (const True) +pprDataCon pefas dataCon = pprAlgTyCon pefas tyCon (== dataCon) (const True) where tyCon = GHC.dataConTyCon dataCon -pprDataConDecl exts gadt_style show_label dataCon +pprDataConDecl pefas gadt_style show_label dataCon | not gadt_style = ppr_fields tys_w_strs | otherwise = ppr_bndr dataCon <+> dcolon <+> sep [ ppr_tvs, GHC.pprThetaArrow theta, pp_tau ] where - (tyvars, theta, argTypes) = GHC.dataConSig dataCon + (tyvars, theta, argTypes, res_ty) = GHC.dataConSig dataCon tyCon = GHC.dataConTyCon dataCon labels = GHC.dataConFieldLabels dataCon - res_tys = dataConResTys dataCon qualVars = filter (flip notElem (GHC.tyConTyVars tyCon)) tyvars stricts = GHC.dataConStrictMarks dataCon tys_w_strs = zip stricts argTypes @@ -157,8 +173,7 @@ pprDataConDecl exts gadt_style show_label dataCon hsep (map ppr qualVars) <> dot -- printing out the dataCon as a type signature, in GADT style - pp_tau = foldr add pp_res_ty tys_w_strs - pp_res_ty = GHC.pprTypeApp (ppr_bndr tyCon) res_tys + pp_tau = foldr add (ppr res_ty) tys_w_strs add (str,ty) pp_ty = pprBangTy str ty <+> arrow <+> pp_ty pprParendBangTy (strict,ty) @@ -184,25 +199,25 @@ pprDataConDecl exts gadt_style show_label dataCon braces (sep (punctuate comma (ppr_trim maybe_show_label (zip labels fields)))) -pprClass exts cls +pprClass pefas cls | null methods = - pprClassHdr exts cls + pprClassHdr pefas cls | otherwise = - hang (pprClassHdr exts cls <+> ptext SLIT("where")) - 2 (vcat (map (pprClassMethod exts) methods)) + hang (pprClassHdr pefas cls <+> ptext SLIT("where")) + 2 (vcat (map (pprClassMethod pefas) methods)) where methods = GHC.classMethods cls -pprClassOneMethod exts cls this_one = - hang (pprClassHdr exts cls <+> ptext SLIT("where")) +pprClassOneMethod pefas cls this_one = + 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 exts id) + show_meth id | id == this_one = Just (pprClassMethod pefas id) | otherwise = Nothing -pprClassMethod exts id = - hang (ppr_bndr id <+> dcolon) 2 (pprType exts (classOpType id)) +pprClassMethod pefas id = + hang (ppr_bndr id <+> dcolon) 2 (pprType pefas (classOpType id)) where -- Here's the magic incantation to strip off the dictionary -- from the class op type. Stolen from IfaceSyn.tyThingToIfaceDecl. @@ -226,7 +241,7 @@ add_bars (c:cs) = sep ((equals <+> c) : map (char '|' <+>) cs) ppr_bndr :: GHC.NamedThing a => a -> SDoc ppr_bndr a = GHC.pprParenSymName a -showWithLoc :: SrcLoc -> SDoc -> SDoc +showWithLoc :: SrcSpan -> SDoc -> SDoc showWithLoc loc doc = hang doc 2 (char '\t' <> comment <+> GHC.pprDefnLoc loc) -- The tab tries to make them line up a bit