X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2Fmain%2FPprTyThing.hs;h=c9e0b2afc57ae8513e9c29c6d9fc2868878a55e0;hp=7c50680deffda06650ce5679b77ec0d285973a07;hb=d83e1ac43a43dc30c7e4f5b64f7b77e32d31886d;hpb=ad94d40948668032189ad22a0ad741ac1f645f50 diff --git a/compiler/main/PprTyThing.hs b/compiler/main/PprTyThing.hs index 7c50680..c9e0b2a 100644 --- a/compiler/main/PprTyThing.hs +++ b/compiler/main/PprTyThing.hs @@ -6,31 +6,26 @@ -- ----------------------------------------------------------------------------- -{-# 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, pprTyThingInContextLoc, - pprTyThingHdr + pprTyThingHdr, + pprTypeForUser ) where -#include "HsVersions.h" - import qualified GHC -import TyCon ( tyConFamInst_maybe ) -import Type ( pprTypeApp ) -import GHC ( TyThing(..), SrcSpan ) +import GHC ( TyThing(..) ) +import TyCon +import Type ( TyThing(..), tidyTopType, pprTypeApp ) +import TcType import Var +import Name import Outputable +import FastString -- ----------------------------------------------------------------------------- -- Pretty-printing entities that we get from the GHC API @@ -44,7 +39,7 @@ type PrintExplicitForalls = Bool pprTyThingLoc :: PrintExplicitForalls -> TyThing -> SDoc pprTyThingLoc pefas tyThing = showWithLoc loc (pprTyThing pefas tyThing) - where loc = GHC.nameSrcSpan (GHC.getName tyThing) + where loc = pprNameLoc (GHC.getName tyThing) -- | Pretty-prints a 'TyThing'. pprTyThing :: PrintExplicitForalls -> TyThing -> SDoc @@ -57,7 +52,7 @@ pprTyThing pefas (AClass cls) = pprClass pefas cls pprTyThingInContextLoc :: PrintExplicitForalls -> TyThing -> SDoc pprTyThingInContextLoc pefas tyThing = showWithLoc loc (pprTyThingInContext pefas tyThing) - where loc = GHC.nameSrcSpan (GHC.getName tyThing) + where loc = pprNameLoc (GHC.getName tyThing) -- | Pretty-prints a 'TyThing' in context: that is, if the entity -- is a data constructor, record selector, or class method, then @@ -77,41 +72,50 @@ 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 pefas tyCon - | Just (fam_tc, tys) <- tyConFamInst_maybe tyCon - = ptext keyword <+> ptext SLIT("instance") <+> pprTypeApp tyCon (ppr_bndr tyCon) tys + +pprTyConHdr :: PrintExplicitForalls -> TyCon -> SDoc +pprTyConHdr _ 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) + = ptext keyword <+> opt_family <+> opt_stupid <+> ppr_bndr tyCon <+> hsep (map ppr vars) where vars | GHC.isPrimTyCon 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.isOpenTyCon 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 -> SDoc pprDataConSig pefas dataCon = - ppr_bndr dataCon <+> dcolon <+> pprType pefas (GHC.dataConType dataCon) + ppr_bndr dataCon <+> dcolon <+> pprTypeForUser pefas (GHC.dataConType dataCon) -pprClassHdr pefas cls = +pprClassHdr :: PrintExplicitForalls -> GHC.Class -> SDoc +pprClassHdr _ cls = let (tyVars, funDeps) = GHC.classTvsFds cls - in ptext SLIT("class") <+> + in ptext (sLit "class") <+> GHC.pprThetaArrow (GHC.classSCTheta cls) <+> ppr_bndr cls <+> hsep (map ppr tyVars) <+> GHC.pprFundeps funDeps +pprIdInContext :: PrintExplicitForalls -> Var -> SDoc 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 -> SDoc pprRecordSelector pefas id = pprAlgTyCon pefas tyCon show_con show_label where @@ -121,26 +125,41 @@ pprRecordSelector pefas 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) + = hang (ppr_bndr ident <+> dcolon) + 2 (pprTypeForUser pefas (GHC.idType ident)) + +pprTypeForUser :: PrintExplicitForalls -> GHC.Type -> SDoc +-- We do two things here. +-- a) We tidy the type, regardless +-- b) If PrintExplicitForAlls is True, we discard the foralls +-- but we do so `deeply' +-- Prime example: a class op might have type +-- forall a. C a => forall b. Ord b => stuff +-- Then we want to display +-- (C a, Ord b) => stuff +pprTypeForUser print_foralls ty + | print_foralls = ppr tidy_ty + | otherwise = ppr (mkPhiTy [p | (_tvs, ps) <- ctxt, p <- ps] ty') + where + tidy_ty = tidyTopType ty + (ctxt, ty') = tcMultiSplitSigmaTy tidy_ty +pprTyCon :: PrintExplicitForalls -> TyCon -> SDoc pprTyCon pefas tyCon | GHC.isSynTyCon tyCon = if GHC.isOpenTyCon tyCon then pprTyConHdr pefas tyCon <+> dcolon <+> - pprType pefas (GHC.synTyConResKind tyCon) + pprTypeForUser pefas (GHC.synTyConResKind tyCon) else let rhs_type = GHC.synTyConType tyCon - in hang (pprTyConHdr pefas tyCon <+> equals) 2 (pprType pefas rhs_type) + in hang (pprTyConHdr pefas tyCon <+> equals) 2 (pprTypeForUser pefas rhs_type) | otherwise = pprAlgTyCon pefas tyCon (const True) (const True) +pprAlgTyCon :: PrintExplicitForalls -> TyCon -> (GHC.DataCon -> Bool) + -> (FieldLabel -> Bool) -> SDoc pprAlgTyCon pefas tyCon ok_con ok_label - | gadt = pprTyConHdr pefas tyCon <+> ptext SLIT("where") $$ + | 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)) @@ -152,10 +171,13 @@ pprAlgTyCon pefas tyCon ok_con ok_label | ok_con dataCon = Just (pprDataConDecl pefas gadt ok_label dataCon) | otherwise = Nothing +pprDataCon :: PrintExplicitForalls -> GHC.DataCon -> SDoc pprDataCon pefas dataCon = pprAlgTyCon pefas tyCon (== dataCon) (const True) where tyCon = GHC.dataConTyCon dataCon -pprDataConDecl pefas gadt_style show_label dataCon +pprDataConDecl :: PrintExplicitForalls -> Bool -> (FieldLabel -> Bool) + -> GHC.DataCon -> SDoc +pprDataConDecl _ 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 ] @@ -169,12 +191,12 @@ pprDataConDecl pefas gadt_style show_label dataCon ppr_tvs | null qualVars = empty - | otherwise = ptext SLIT("forall") <+> + | otherwise = ptext (sLit "forall") <+> hsep (map ppr qualVars) <> dot -- printing out the dataCon as a type signature, in GADT style pp_tau = foldr add (ppr res_ty) tys_w_strs - add (str,ty) pp_ty = pprBangTy str ty <+> arrow <+> pp_ty + add str_ty pp_ty = pprParendBangTy str_ty <+> arrow <+> pp_ty pprParendBangTy (strict,ty) | GHC.isMarkedStrict strict = char '!' <> GHC.pprParendType ty @@ -199,30 +221,43 @@ pprDataConDecl pefas gadt_style show_label dataCon braces (sep (punctuate comma (ppr_trim maybe_show_label (zip labels fields)))) +pprClass :: PrintExplicitForalls -> GHC.Class -> SDoc pprClass pefas cls | null methods = pprClassHdr pefas cls | otherwise = - hang (pprClassHdr pefas cls <+> ptext SLIT("where")) + hang (pprClassHdr pefas cls <+> ptext (sLit "where")) 2 (vcat (map (pprClassMethod pefas) methods)) where methods = GHC.classMethods cls -pprClassOneMethod pefas cls this_one = - hang (pprClassHdr pefas cls <+> ptext SLIT("where")) - 2 (vcat (ppr_trim show_meth methods)) +pprClassOneMethod :: PrintExplicitForalls -> GHC.Class -> Id -> SDoc +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 pefas id) | otherwise = Nothing -pprClassMethod pefas id = - hang (ppr_bndr id <+> dcolon) 2 (pprType pefas (classOpType id)) +pprClassMethod :: PrintExplicitForalls -> Id -> SDoc +pprClassMethod pefas id + = hang (ppr_bndr id <+> dcolon) 2 (pprTypeForUser pefas op_ty) where -- Here's the magic incantation to strip off the dictionary -- from the class op type. Stolen from IfaceSyn.tyThingToIfaceDecl. - classOpType id = GHC.funResultTy rho_ty - where (_sel_tyvars, rho_ty) = GHC.splitForAllTys (GHC.idType id) + -- + -- It's important to tidy it *before* splitting it up, so that if + -- we have class C a b where + -- op :: forall a. a -> b + -- then the inner forall on op gets renamed to a1, and we print + -- (when dropping foralls) + -- class C a b where + -- op :: a1 -> b + + tidy_sel_ty = tidyTopType (GHC.idType id) + (_sel_tyvars, rho_ty) = GHC.splitForAllTys tidy_sel_ty + op_ty = GHC.funResultTy rho_ty ppr_trim :: (a -> Maybe SDoc) -> [a] -> [SDoc] ppr_trim show xs @@ -231,8 +266,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] -> SDoc add_bars [] = empty add_bars [c] = equals <+> c add_bars (c:cs) = sep ((equals <+> c) : map (char '|' <+>) cs) @@ -241,10 +277,10 @@ add_bars (c:cs) = sep ((equals <+> c) : map (char '|' <+>) cs) ppr_bndr :: GHC.NamedThing a => a -> SDoc ppr_bndr a = GHC.pprParenSymName a -showWithLoc :: SrcSpan -> SDoc -> SDoc +showWithLoc :: SDoc -> SDoc -> SDoc showWithLoc loc doc - = hang doc 2 (char '\t' <> comment <+> GHC.pprDefnLoc loc) + = hang doc 2 (char '\t' <> comment <+> loc) -- The tab tries to make them line up a bit where - comment = ptext SLIT("--") + comment = ptext (sLit "--")