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