3286b32d5deb29684db37d9b5df67de62f4240bd
[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, pprTyThingParent_maybe,
13         pprTyThingLoc,
14         pprTyThingInContextLoc,
15         pprTyThingHdr,
16         pprTypeForUser
17   ) where
18
19 import qualified GHC
20
21 import GHC ( TyThing(..) )
22 import DataCon
23 import Id
24 import IdInfo
25 import TyCon
26 import TcType
27 import Name
28 import Outputable
29 import FastString
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 type ShowMe = Name -> Bool
40 -- The ShowMe function says which sub-components to print
41 --   True  <=> print
42 --   False <=> elide to "..."
43
44 ----------------------------
45 -- | Pretty-prints a 'TyThing' with its defining location.
46 pprTyThingLoc :: PrintExplicitForalls -> TyThing -> SDoc
47 pprTyThingLoc pefas tyThing
48   = showWithLoc loc (pprTyThing pefas tyThing)
49   where loc = pprNameLoc (GHC.getName tyThing)
50
51 -- | Pretty-prints a 'TyThing'.
52 pprTyThing :: PrintExplicitForalls -> TyThing -> SDoc
53 pprTyThing pefas thing = ppr_ty_thing pefas (const True) thing
54
55 ppr_ty_thing :: PrintExplicitForalls -> ShowMe -> TyThing -> SDoc
56 ppr_ty_thing pefas _     (AnId id)          = pprId         pefas id
57 ppr_ty_thing pefas _     (ADataCon dataCon) = pprDataConSig pefas dataCon
58 ppr_ty_thing pefas show_me (ATyCon tyCon)   = pprTyCon      pefas show_me tyCon
59 ppr_ty_thing _     _       (ACoAxiom _  )   = error "ppr_ty_thing (ACoCon)"  -- BAY
60 ppr_ty_thing pefas show_me (AClass cls)     = pprClass      pefas show_me cls
61
62 -- | Pretty-prints a 'TyThing' in context: that is, if the entity
63 -- is a data constructor, record selector, or class method, then
64 -- the entity's parent declaration is pretty-printed with irrelevant
65 -- parts omitted.
66 pprTyThingInContext :: PrintExplicitForalls -> TyThing -> SDoc
67 pprTyThingInContext pefas thing
68   | Just parent <- pprTyThingParent_maybe thing
69   = ppr_ty_thing pefas (== GHC.getName thing) parent
70   | otherwise
71   = pprTyThing pefas thing
72
73 -- | Like 'pprTyThingInContext', but adds the defining location.
74 pprTyThingInContextLoc :: PrintExplicitForalls -> TyThing -> SDoc
75 pprTyThingInContextLoc pefas tyThing
76   = showWithLoc (pprNameLoc (GHC.getName tyThing))
77                 (pprTyThingInContext pefas tyThing)
78
79 pprTyThingParent_maybe :: TyThing -> Maybe TyThing
80 -- (pprTyThingParent_maybe x) returns (Just p)
81 -- when pprTyThingInContext sould print a declaration for p
82 -- (albeit with some "..." in it) when asked to show x
83 pprTyThingParent_maybe (ADataCon dc) = Just (ATyCon (dataConTyCon dc))
84 pprTyThingParent_maybe (AnId id)     = case idDetails id of
85                                          RecSelId { sel_tycon = tc } -> Just (ATyCon tc)
86                                          ClassOpId cls               -> Just (AClass cls)
87                                          _other                      -> Nothing
88 pprTyThingParent_maybe _other = Nothing
89
90 -- | Pretty-prints the 'TyThing' header. For functions and data constructors
91 -- the function is equivalent to 'pprTyThing' but for type constructors
92 -- and classes it prints only the header part of the declaration.
93 pprTyThingHdr :: PrintExplicitForalls -> TyThing -> SDoc
94 pprTyThingHdr pefas (AnId id)          = pprId         pefas id
95 pprTyThingHdr pefas (ADataCon dataCon) = pprDataConSig pefas dataCon
96 pprTyThingHdr pefas (ATyCon tyCon)     = pprTyConHdr   pefas tyCon
97 pprTyThingHdr _     (ACoAxiom _)       = error "pprTyThingHdr (ACoCon)" -- BAY
98 pprTyThingHdr pefas (AClass cls)       = pprClassHdr   pefas cls
99
100 pprTyConHdr :: PrintExplicitForalls -> TyCon -> SDoc
101 pprTyConHdr _ tyCon
102   | Just (_fam_tc, tys) <- tyConFamInst_maybe tyCon
103   = ptext keyword <+> ptext (sLit "instance") <+> pprTypeApp tyCon tys
104   | otherwise
105   = ptext keyword <+> opt_family <+> opt_stupid <+> ppr_bndr tyCon <+> hsep (map ppr vars)
106   where
107     vars | GHC.isPrimTyCon tyCon ||
108            GHC.isFunTyCon tyCon = take (GHC.tyConArity tyCon) GHC.alphaTyVars
109          | otherwise = GHC.tyConTyVars tyCon
110
111     keyword | GHC.isSynTyCon tyCon = sLit "type"
112             | GHC.isNewTyCon tyCon = sLit "newtype"
113             | otherwise            = sLit "data"
114
115     opt_family
116       | GHC.isFamilyTyCon tyCon = ptext (sLit "family")
117       | otherwise             = empty
118
119     opt_stupid  -- The "stupid theta" part of the declaration
120         | isAlgTyCon tyCon = GHC.pprThetaArrowTy (tyConStupidTheta tyCon)
121         | otherwise        = empty      -- Returns 'empty' if null theta
122
123 pprDataConSig :: PrintExplicitForalls -> GHC.DataCon -> SDoc
124 pprDataConSig pefas dataCon
125   = ppr_bndr dataCon <+> dcolon <+> pprTypeForUser pefas (GHC.dataConType dataCon)
126
127 pprClassHdr :: PrintExplicitForalls -> GHC.Class -> SDoc
128 pprClassHdr _ cls
129   = ptext (sLit "class") <+>
130     GHC.pprThetaArrowTy (GHC.classSCTheta cls) <+>
131     ppr_bndr cls <+>
132     hsep (map ppr tyVars) <+>
133     GHC.pprFundeps funDeps
134   where
135      (tyVars, funDeps) = GHC.classTvsFds cls
136
137 pprId :: PrintExplicitForalls -> Var -> SDoc
138 pprId pefas ident
139   = hang (ppr_bndr ident <+> dcolon)
140          2 (pprTypeForUser pefas (GHC.idType ident))
141
142 pprTypeForUser :: PrintExplicitForalls -> GHC.Type -> SDoc
143 -- We do two things here.
144 -- a) We tidy the type, regardless
145 -- b) If PrintExplicitForAlls is True, we discard the foralls
146 --      but we do so `deeply'
147 -- Prime example: a class op might have type
148 --      forall a. C a => forall b. Ord b => stuff
149 -- Then we want to display
150 --      (C a, Ord b) => stuff
151 pprTypeForUser print_foralls ty
152   | print_foralls = ppr tidy_ty
153   | otherwise     = ppr (mkPhiTy ctxt ty')
154   where
155     tidy_ty     = tidyTopType ty
156     (_, ctxt, ty') = tcSplitSigmaTy tidy_ty
157
158 pprTyCon :: PrintExplicitForalls -> ShowMe -> TyCon -> SDoc
159 pprTyCon pefas show_me tyCon
160   | GHC.isSynTyCon tyCon
161   = if GHC.isFamilyTyCon tyCon
162     then pprTyConHdr pefas tyCon <+> dcolon <+> 
163          pprTypeForUser pefas (GHC.synTyConResKind tyCon)
164     else
165       let rhs_type = GHC.synTyConType tyCon
166       in hang (pprTyConHdr pefas tyCon <+> equals) 2 (pprTypeForUser pefas rhs_type)
167   | otherwise
168   = pprAlgTyCon pefas show_me tyCon
169
170 pprAlgTyCon :: PrintExplicitForalls -> ShowMe -> TyCon -> SDoc
171 pprAlgTyCon pefas show_me tyCon
172   | gadt      = pprTyConHdr pefas tyCon <+> ptext (sLit "where") $$
173                    nest 2 (vcat (ppr_trim show_con datacons))
174   | otherwise = hang (pprTyConHdr pefas tyCon)
175                    2 (add_bars (ppr_trim show_con datacons))
176   where
177     datacons = GHC.tyConDataCons tyCon
178     gadt = any (not . GHC.isVanillaDataCon) datacons
179
180     ok_con dc = show_me (dataConName dc) || any show_me (dataConFieldLabels dc)
181     show_con dc
182       | ok_con dc = Just (pprDataConDecl pefas show_me gadt dc)
183       | otherwise = Nothing
184
185 pprDataConDecl :: PrintExplicitForalls -> ShowMe -> Bool -> GHC.DataCon -> SDoc
186 pprDataConDecl pefas show_me gadt_style dataCon
187   | not gadt_style = ppr_fields tys_w_strs
188   | otherwise      = ppr_bndr dataCon <+> dcolon <+>
189                         sep [ pp_foralls, GHC.pprThetaArrowTy theta, pp_tau ]
190         -- Printing out the dataCon as a type signature, in GADT style
191   where
192     (forall_tvs, theta, tau) = tcSplitSigmaTy (GHC.dataConUserType dataCon)
193     (arg_tys, res_ty)        = tcSplitFunTys tau
194     labels     = GHC.dataConFieldLabels dataCon
195     stricts    = GHC.dataConStrictMarks dataCon
196     tys_w_strs = zip stricts arg_tys
197     pp_foralls | pefas     = GHC.pprForAll forall_tvs
198                | otherwise = empty
199
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 (bang,ty) = ppr bang <> GHC.pprParendType ty
204
205     pprBangTy bang ty = ppr bang <> ppr ty
206
207     maybe_show_label (lbl,(strict,tp))
208         | show_me lbl = Just (ppr lbl <+> dcolon <+> pprBangTy strict tp)
209         | otherwise   = Nothing
210
211     ppr_fields [ty1, ty2]
212         | GHC.dataConIsInfix dataCon && null labels
213         = sep [pprParendBangTy ty1, pprInfixName dataCon, pprParendBangTy ty2]
214     ppr_fields fields
215         | null labels
216         = ppr_bndr dataCon <+> sep (map pprParendBangTy fields)
217         | otherwise
218         = ppr_bndr dataCon <+>
219                 braces (sep (punctuate comma (ppr_trim maybe_show_label
220                                         (zip labels fields))))
221
222 pprClass :: PrintExplicitForalls -> ShowMe -> GHC.Class -> SDoc
223 pprClass pefas show_me cls
224   | null methods
225   = pprClassHdr pefas cls
226   | otherwise
227   = hang (pprClassHdr pefas cls <+> ptext (sLit "where"))
228        2 (vcat (ppr_trim show_meth methods))
229   where
230     methods = GHC.classMethods cls
231     show_meth id | show_me (idName id) = Just (pprClassMethod pefas id)
232                  | otherwise           = Nothing
233
234 pprClassMethod :: PrintExplicitForalls -> Id -> SDoc
235 pprClassMethod pefas id
236   = hang (ppr_bndr id <+> dcolon) 2 (pprTypeForUser pefas op_ty)
237   where
238   -- Here's the magic incantation to strip off the dictionary
239   -- from the class op type.  Stolen from IfaceSyn.tyThingToIfaceDecl.
240   --
241   -- It's important to tidy it *before* splitting it up, so that if
242   -- we have    class C a b where
243   --              op :: forall a. a -> b
244   -- then the inner forall on op gets renamed to a1, and we print
245   -- (when dropping foralls)
246   --            class C a b where
247   --              op :: a1 -> b
248
249   tidy_sel_ty = tidyTopType (GHC.idType id)
250   (_sel_tyvars, rho_ty) = GHC.splitForAllTys tidy_sel_ty
251   op_ty = GHC.funResultTy rho_ty
252
253 ppr_trim :: (a -> Maybe SDoc) -> [a] -> [SDoc]
254 ppr_trim show xs
255   = snd (foldr go (False, []) xs)
256   where
257     go x (eliding, so_far)
258         | Just doc <- show x = (False, doc : so_far)
259         | otherwise = if eliding then (True, so_far)
260                                  else (True, ptext (sLit "...") : so_far)
261
262 add_bars :: [SDoc] -> SDoc
263 add_bars []      = empty
264 add_bars [c]     = equals <+> c
265 add_bars (c:cs)  = sep ((equals <+> c) : map (char '|' <+>) cs)
266
267 -- Wrap operators in ()
268 ppr_bndr :: GHC.NamedThing a => a -> SDoc
269 ppr_bndr a = GHC.pprParenSymName a
270
271 showWithLoc :: SDoc -> SDoc -> SDoc
272 showWithLoc loc doc
273     = hang doc 2 (char '\t' <> comment <+> loc)
274                 -- The tab tries to make them line up a bit
275   where
276     comment = ptext (sLit "--")
277