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