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