1 -----------------------------------------------------------------------------
3 -- Pretty-printing TyThings
5 -- (c) The GHC Team 2005
7 -----------------------------------------------------------------------------
14 pprTyThingInContextLoc,
21 import GHC ( TyThing(..) )
23 import Type ( TyThing(..), tidyTopType, pprTypeApp )
30 -- -----------------------------------------------------------------------------
31 -- Pretty-printing entities that we get from the GHC API
33 -- This should be a good source of sample code for using the GHC API to
34 -- inspect source code entities.
36 type PrintExplicitForalls = Bool
38 -- | Pretty-prints a 'TyThing' with its defining location.
39 pprTyThingLoc :: PrintExplicitForalls -> TyThing -> SDoc
40 pprTyThingLoc pefas tyThing
41 = showWithLoc loc (pprTyThing pefas tyThing)
42 where loc = pprNameLoc (GHC.getName tyThing)
44 -- | Pretty-prints a 'TyThing'.
45 pprTyThing :: PrintExplicitForalls -> TyThing -> SDoc
46 pprTyThing pefas (AnId id) = pprId pefas id
47 pprTyThing pefas (ADataCon dataCon) = pprDataConSig pefas dataCon
48 pprTyThing pefas (ATyCon tyCon) = pprTyCon pefas tyCon
49 pprTyThing pefas (AClass cls) = pprClass pefas cls
51 -- | Like 'pprTyThingInContext', but adds the defining location.
52 pprTyThingInContextLoc :: PrintExplicitForalls -> TyThing -> SDoc
53 pprTyThingInContextLoc pefas tyThing
54 = showWithLoc loc (pprTyThingInContext pefas tyThing)
55 where loc = pprNameLoc (GHC.getName tyThing)
57 -- | Pretty-prints a 'TyThing' in context: that is, if the entity
58 -- is a data constructor, record selector, or class method, then
59 -- the entity's parent declaration is pretty-printed with irrelevant
61 pprTyThingInContext :: PrintExplicitForalls -> TyThing -> SDoc
62 pprTyThingInContext pefas (AnId id) = pprIdInContext pefas id
63 pprTyThingInContext pefas (ADataCon dataCon) = pprDataCon pefas dataCon
64 pprTyThingInContext pefas (ATyCon tyCon) = pprTyCon pefas tyCon
65 pprTyThingInContext pefas (AClass cls) = pprClass pefas cls
67 -- | Pretty-prints the 'TyThing' header. For functions and data constructors
68 -- the function is equivalent to 'pprTyThing' but for type constructors
69 -- and classes it prints only the header part of the declaration.
70 pprTyThingHdr :: PrintExplicitForalls -> TyThing -> SDoc
71 pprTyThingHdr pefas (AnId id) = pprId pefas id
72 pprTyThingHdr pefas (ADataCon dataCon) = pprDataConSig pefas dataCon
73 pprTyThingHdr pefas (ATyCon tyCon) = pprTyConHdr pefas tyCon
74 pprTyThingHdr pefas (AClass cls) = pprClassHdr pefas cls
76 pprTyConHdr :: PrintExplicitForalls -> TyCon -> SDoc
78 | Just (_fam_tc, tys) <- tyConFamInst_maybe tyCon
79 = ptext keyword <+> ptext (sLit "instance") <+> pprTypeApp tyCon tys
81 = ptext keyword <+> opt_family <+> opt_stupid <+> ppr_bndr tyCon <+> hsep (map ppr vars)
83 vars | GHC.isPrimTyCon tyCon ||
84 GHC.isFunTyCon tyCon = take (GHC.tyConArity tyCon) GHC.alphaTyVars
85 | otherwise = GHC.tyConTyVars tyCon
87 keyword | GHC.isSynTyCon tyCon = sLit "type"
88 | GHC.isNewTyCon tyCon = sLit "newtype"
89 | otherwise = sLit "data"
92 | GHC.isOpenTyCon tyCon = ptext (sLit "family")
95 opt_stupid -- The "stupid theta" part of the declaration
96 | isAlgTyCon tyCon = GHC.pprThetaArrow (tyConStupidTheta tyCon)
97 | otherwise = empty -- Returns 'empty' if null theta
99 pprDataConSig :: PrintExplicitForalls -> GHC.DataCon -> SDoc
100 pprDataConSig pefas dataCon =
101 ppr_bndr dataCon <+> dcolon <+> pprTypeForUser pefas (GHC.dataConType dataCon)
103 pprClassHdr :: PrintExplicitForalls -> GHC.Class -> SDoc
105 let (tyVars, funDeps) = GHC.classTvsFds cls
106 in ptext (sLit "class") <+>
107 GHC.pprThetaArrow (GHC.classSCTheta cls) <+>
109 hsep (map ppr tyVars) <+>
110 GHC.pprFundeps funDeps
112 pprIdInContext :: PrintExplicitForalls -> Var -> SDoc
113 pprIdInContext pefas id
114 | GHC.isRecordSelector id = pprRecordSelector pefas id
115 | Just cls <- GHC.isClassOpId_maybe id = pprClassOneMethod pefas cls id
116 | otherwise = pprId pefas id
118 pprRecordSelector :: PrintExplicitForalls -> Id -> SDoc
119 pprRecordSelector pefas id
120 = pprAlgTyCon pefas tyCon show_con show_label
122 (tyCon,label) = GHC.recordSelectorFieldLabel id
123 show_con dataCon = label `elem` GHC.dataConFieldLabels dataCon
124 show_label label' = label == label'
126 pprId :: PrintExplicitForalls -> Var -> SDoc
128 = hang (ppr_bndr ident <+> dcolon)
129 2 (pprTypeForUser pefas (GHC.idType ident))
131 pprTypeForUser :: PrintExplicitForalls -> GHC.Type -> SDoc
132 -- We do two things here.
133 -- a) We tidy the type, regardless
134 -- b) If PrintExplicitForAlls is True, we discard the foralls
135 -- but we do so `deeply'
136 -- Prime example: a class op might have type
137 -- forall a. C a => forall b. Ord b => stuff
138 -- Then we want to display
139 -- (C a, Ord b) => stuff
140 pprTypeForUser print_foralls ty
141 | print_foralls = ppr tidy_ty
142 | otherwise = ppr (mkPhiTy [p | (_tvs, ps) <- ctxt, p <- ps] ty')
144 tidy_ty = tidyTopType ty
145 (ctxt, ty') = tcMultiSplitSigmaTy tidy_ty
147 pprTyCon :: PrintExplicitForalls -> TyCon -> SDoc
149 | GHC.isSynTyCon tyCon
150 = if GHC.isOpenTyCon tyCon
151 then pprTyConHdr pefas tyCon <+> dcolon <+>
152 pprTypeForUser pefas (GHC.synTyConResKind tyCon)
154 let rhs_type = GHC.synTyConType tyCon
155 in hang (pprTyConHdr pefas tyCon <+> equals) 2 (pprTypeForUser pefas rhs_type)
157 = pprAlgTyCon pefas tyCon (const True) (const True)
159 pprAlgTyCon :: PrintExplicitForalls -> TyCon -> (GHC.DataCon -> Bool)
160 -> (FieldLabel -> Bool) -> SDoc
161 pprAlgTyCon pefas tyCon ok_con ok_label
162 | gadt = pprTyConHdr pefas tyCon <+> ptext (sLit "where") $$
163 nest 2 (vcat (ppr_trim show_con datacons))
164 | otherwise = hang (pprTyConHdr pefas tyCon)
165 2 (add_bars (ppr_trim show_con datacons))
167 datacons = GHC.tyConDataCons tyCon
168 gadt = any (not . GHC.isVanillaDataCon) datacons
171 | ok_con dataCon = Just (pprDataConDecl pefas gadt ok_label dataCon)
172 | otherwise = Nothing
174 pprDataCon :: PrintExplicitForalls -> GHC.DataCon -> SDoc
175 pprDataCon pefas dataCon = pprAlgTyCon pefas tyCon (== dataCon) (const True)
176 where tyCon = GHC.dataConTyCon dataCon
178 pprDataConDecl :: PrintExplicitForalls -> Bool -> (FieldLabel -> Bool)
179 -> GHC.DataCon -> SDoc
180 pprDataConDecl _ gadt_style show_label dataCon
181 | not gadt_style = ppr_fields tys_w_strs
182 | otherwise = ppr_bndr dataCon <+> dcolon <+>
183 sep [ ppr_tvs, GHC.pprThetaArrow theta, pp_tau ]
185 (tyvars, theta, argTypes, res_ty) = GHC.dataConSig dataCon
186 tyCon = GHC.dataConTyCon dataCon
187 labels = GHC.dataConFieldLabels dataCon
188 qualVars = filter (flip notElem (GHC.tyConTyVars tyCon)) tyvars
189 stricts = GHC.dataConStrictMarks dataCon
190 tys_w_strs = zip stricts argTypes
193 | null qualVars = empty
194 | otherwise = ptext (sLit "forall") <+>
195 hsep (map ppr qualVars) <> dot
197 -- printing out the dataCon as a type signature, in GADT style
198 pp_tau = foldr add (ppr res_ty) tys_w_strs
199 add str_ty pp_ty = pprParendBangTy str_ty <+> arrow <+> pp_ty
201 pprParendBangTy (strict,ty)
202 | GHC.isMarkedStrict strict = char '!' <> GHC.pprParendType ty
203 | otherwise = GHC.pprParendType ty
206 | GHC.isMarkedStrict strict = char '!' <> ppr ty
209 maybe_show_label (lbl,(strict,tp))
210 | show_label lbl = Just (ppr lbl <+> dcolon <+> pprBangTy strict tp)
211 | otherwise = Nothing
213 ppr_fields [ty1, ty2]
214 | GHC.dataConIsInfix dataCon && null labels
215 = sep [pprParendBangTy ty1, pprInfixName dataCon, pprParendBangTy ty2]
218 = ppr_bndr dataCon <+> sep (map pprParendBangTy fields)
220 = ppr_bndr dataCon <+>
221 braces (sep (punctuate comma (ppr_trim maybe_show_label
222 (zip labels fields))))
224 pprClass :: PrintExplicitForalls -> GHC.Class -> SDoc
227 pprClassHdr pefas cls
229 hang (pprClassHdr pefas cls <+> ptext (sLit "where"))
230 2 (vcat (map (pprClassMethod pefas) methods))
232 methods = GHC.classMethods cls
234 pprClassOneMethod :: PrintExplicitForalls -> GHC.Class -> Id -> SDoc
235 pprClassOneMethod pefas cls this_one
236 = hang (pprClassHdr pefas cls <+> ptext (sLit "where"))
237 2 (vcat (ppr_trim show_meth methods))
239 methods = GHC.classMethods cls
240 show_meth id | id == this_one = Just (pprClassMethod pefas id)
241 | otherwise = Nothing
243 pprClassMethod :: PrintExplicitForalls -> Id -> SDoc
244 pprClassMethod pefas id
245 = hang (ppr_bndr id <+> dcolon) 2 (pprTypeForUser pefas op_ty)
247 -- Here's the magic incantation to strip off the dictionary
248 -- from the class op type. Stolen from IfaceSyn.tyThingToIfaceDecl.
250 -- It's important to tidy it *before* splitting it up, so that if
251 -- we have class C a b where
252 -- op :: forall a. a -> b
253 -- then the inner forall on op gets renamed to a1, and we print
254 -- (when dropping foralls)
258 tidy_sel_ty = tidyTopType (GHC.idType id)
259 (_sel_tyvars, rho_ty) = GHC.splitForAllTys tidy_sel_ty
260 op_ty = GHC.funResultTy rho_ty
262 ppr_trim :: (a -> Maybe SDoc) -> [a] -> [SDoc]
264 = snd (foldr go (False, []) xs)
266 go x (eliding, so_far)
267 | Just doc <- show x = (False, doc : so_far)
268 | otherwise = if eliding then (True, so_far)
269 else (True, ptext (sLit "...") : so_far)
271 add_bars :: [SDoc] -> SDoc
273 add_bars [c] = equals <+> c
274 add_bars (c:cs) = sep ((equals <+> c) : map (char '|' <+>) cs)
276 -- Wrap operators in ()
277 ppr_bndr :: GHC.NamedThing a => a -> SDoc
278 ppr_bndr a = GHC.pprParenSymName a
280 showWithLoc :: SDoc -> SDoc -> SDoc
282 = hang doc 2 (char '\t' <> comment <+> loc)
283 -- The tab tries to make them line up a bit
285 comment = ptext (sLit "--")