X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2Fmain%2FPprTyThing.hs;h=dfa713fdc0b13276cc52d5ee9ba06ed3cf7e602d;hp=c379d972d968d681a6f4471b76922d7701c4ac4b;hb=215ce9f15215399ce30ae55c9521087847d78646;hpb=700dad75ea40342455b7f75d348e1dcd83fc3755 diff --git a/compiler/main/PprTyThing.hs b/compiler/main/PprTyThing.hs index c379d97..dfa713f 100644 --- a/compiler/main/PprTyThing.hs +++ b/compiler/main/PprTyThing.hs @@ -1,10 +1,3 @@ -{-# 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/Commentary/CodingStyle#Warnings --- for details - ----------------------------------------------------------------------------- -- -- Pretty-printing TyThings @@ -23,18 +16,15 @@ module PprTyThing ( pprTypeForUser ) where -#include "HsVersions.h" - import qualified GHC -import GHC ( TyThing(..) ) -import TyCon ( tyConFamInst_maybe, isAlgTyCon, tyConStupidTheta ) -import Type ( TyThing(..), tidyTopType, pprTypeApp ) -import TcType ( tcMultiSplitSigmaTy, mkPhiTy ) -import SrcLoc ( SrcSpan ) +import GHC ( TyThing(..) ) +import TyCon +import TcType import Var import Name import Outputable +import FastString -- ----------------------------------------------------------------------------- -- Pretty-printing entities that we get from the GHC API @@ -81,10 +71,11 @@ 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 tys | otherwise = ptext keyword <+> opt_family <+> opt_stupid <+> ppr_bndr tyCon <+> hsep (map ppr vars) where @@ -92,34 +83,38 @@ pprTyConHdr pefas 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 <+> 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 @@ -148,6 +143,7 @@ pprTypeForUser print_foralls ty tidy_ty = tidyTopType ty (ctxt, ty') = tcMultiSplitSigmaTy tidy_ty +pprTyCon :: PrintExplicitForalls -> TyCon -> SDoc pprTyCon pefas tyCon | GHC.isSynTyCon tyCon = if GHC.isOpenTyCon tyCon @@ -159,8 +155,10 @@ pprTyCon pefas tyCon | 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)) @@ -172,10 +170,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 ] @@ -189,20 +190,16 @@ 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 = 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) @@ -210,7 +207,7 @@ pprDataConDecl pefas gadt_style show_label dataCon 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) @@ -219,23 +216,26 @@ 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 :: PrintExplicitForalls -> GHC.Class -> Id -> SDoc pprClassOneMethod pefas cls this_one - = hang (pprClassHdr pefas cls <+> ptext SLIT("where")) + = 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 :: PrintExplicitForalls -> Id -> SDoc pprClassMethod pefas id = hang (ppr_bndr id <+> dcolon) 2 (pprTypeForUser pefas op_ty) where @@ -261,8 +261,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) @@ -276,5 +277,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 "--")