c712eb39d9c6be9c1cee92f86785763f2d0bbfc7
[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   ) where
17
18 #include "HsVersions.h"
19
20 import qualified GHC
21
22 import TyCon    ( tyConFamInst_maybe )
23 import Type     ( pprTypeApp )
24 import GHC      ( TyThing(..), SrcSpan )
25 import Var
26 import Outputable
27
28 -- -----------------------------------------------------------------------------
29 -- Pretty-printing entities that we get from the GHC API
30
31 -- This should be a good source of sample code for using the GHC API to
32 -- inspect source code entities.
33
34 type PrintExplicitForalls = Bool
35
36 -- | Pretty-prints a 'TyThing' with its defining location.
37 pprTyThingLoc :: PrintExplicitForalls -> TyThing -> SDoc
38 pprTyThingLoc pefas tyThing 
39   = showWithLoc loc (pprTyThing pefas tyThing)
40   where loc = GHC.nameSrcSpan (GHC.getName tyThing)
41
42 -- | Pretty-prints a 'TyThing'.
43 pprTyThing :: PrintExplicitForalls -> TyThing -> SDoc
44 pprTyThing pefas (AnId id)          = pprId         pefas id
45 pprTyThing pefas (ADataCon dataCon) = pprDataConSig pefas dataCon
46 pprTyThing pefas (ATyCon tyCon)     = pprTyCon      pefas tyCon
47 pprTyThing pefas (AClass cls)       = pprClass      pefas cls
48
49 -- | Like 'pprTyThingInContext', but adds the defining location.
50 pprTyThingInContextLoc :: PrintExplicitForalls -> TyThing -> SDoc
51 pprTyThingInContextLoc pefas tyThing
52   = showWithLoc loc (pprTyThingInContext pefas tyThing)
53   where loc = GHC.nameSrcSpan (GHC.getName tyThing)
54
55 -- | Pretty-prints a 'TyThing' in context: that is, if the entity
56 -- is a data constructor, record selector, or class method, then 
57 -- the entity's parent declaration is pretty-printed with irrelevant
58 -- parts omitted.
59 pprTyThingInContext :: PrintExplicitForalls -> TyThing -> SDoc
60 pprTyThingInContext pefas (AnId id)          = pprIdInContext pefas id
61 pprTyThingInContext pefas (ADataCon dataCon) = pprDataCon pefas dataCon
62 pprTyThingInContext pefas (ATyCon tyCon)     = pprTyCon   pefas tyCon
63 pprTyThingInContext pefas (AClass cls)       = pprClass   pefas cls
64
65 -- | Pretty-prints the 'TyThing' header. For functions and data constructors
66 -- the function is equivalent to 'pprTyThing' but for type constructors
67 -- and classes it prints only the header part of the declaration.
68 pprTyThingHdr :: PrintExplicitForalls -> TyThing -> SDoc
69 pprTyThingHdr pefas (AnId id)          = pprId         pefas id
70 pprTyThingHdr pefas (ADataCon dataCon) = pprDataConSig pefas dataCon
71 pprTyThingHdr pefas (ATyCon tyCon)     = pprTyConHdr   pefas tyCon
72 pprTyThingHdr pefas (AClass cls)       = pprClassHdr   pefas cls
73         
74 pprTyConHdr pefas tyCon
75   | Just (fam_tc, tys) <- tyConFamInst_maybe tyCon
76   = ptext keyword <+> ptext SLIT("instance") <+> pprTypeApp tyCon (ppr_bndr tyCon) tys
77   | otherwise
78   = ptext keyword <+> opt_family <+> ppr_bndr tyCon <+> hsep (map ppr vars)
79   where
80     vars | GHC.isPrimTyCon tyCon || 
81            GHC.isFunTyCon tyCon = take (GHC.tyConArity tyCon) GHC.alphaTyVars
82          | otherwise = GHC.tyConTyVars tyCon
83
84     keyword | GHC.isSynTyCon tyCon = SLIT("type")
85             | GHC.isNewTyCon tyCon = SLIT("newtype")
86             | otherwise            = SLIT("data")
87
88     opt_family
89       | GHC.isOpenTyCon tyCon = ptext SLIT("family")
90       | otherwise             = empty
91
92 pprDataConSig pefas dataCon =
93   ppr_bndr dataCon <+> dcolon <+> pprType pefas (GHC.dataConType dataCon)
94
95 pprClassHdr pefas cls =
96   let (tyVars, funDeps) = GHC.classTvsFds cls
97   in ptext SLIT("class") <+> 
98      GHC.pprThetaArrow (GHC.classSCTheta cls) <+>
99      ppr_bndr cls <+>
100      hsep (map ppr tyVars) <+>
101      GHC.pprFundeps funDeps
102
103 pprIdInContext pefas id
104   | GHC.isRecordSelector id               = pprRecordSelector pefas id
105   | Just cls <- GHC.isClassOpId_maybe id  = pprClassOneMethod pefas cls id
106   | otherwise                             = pprId pefas id
107
108 pprRecordSelector pefas id
109   = pprAlgTyCon pefas tyCon show_con show_label
110   where
111         (tyCon,label) = GHC.recordSelectorFieldLabel id
112         show_con dataCon  = label `elem` GHC.dataConFieldLabels dataCon
113         show_label label' = label == label'
114
115 pprId :: PrintExplicitForalls -> Var -> SDoc
116 pprId pefas ident
117   = hang (ppr_bndr ident <+> dcolon) 2 
118         (pprType pefas (GHC.idType ident))
119
120 pprType :: PrintExplicitForalls -> GHC.Type -> SDoc
121 pprType True  ty = ppr ty
122 pprType False ty = ppr (GHC.dropForAlls ty)
123
124 pprTyCon pefas tyCon
125   | GHC.isSynTyCon tyCon
126   = if GHC.isOpenTyCon tyCon
127     then pprTyConHdr pefas tyCon <+> dcolon <+> 
128          pprType pefas (GHC.synTyConResKind tyCon)
129     else 
130       let rhs_type = GHC.synTyConType tyCon
131       in hang (pprTyConHdr pefas tyCon <+> equals) 2 (pprType pefas rhs_type)
132   | otherwise
133   = pprAlgTyCon pefas tyCon (const True) (const True)
134
135 pprAlgTyCon pefas tyCon ok_con ok_label
136   | gadt      = pprTyConHdr pefas tyCon <+> ptext SLIT("where") $$ 
137                    nest 2 (vcat (ppr_trim show_con datacons))
138   | otherwise = hang (pprTyConHdr pefas tyCon)
139                    2 (add_bars (ppr_trim show_con datacons))
140   where
141     datacons = GHC.tyConDataCons tyCon
142     gadt = any (not . GHC.isVanillaDataCon) datacons
143
144     show_con dataCon
145       | ok_con dataCon = Just (pprDataConDecl pefas gadt ok_label dataCon)
146       | otherwise      = Nothing
147
148 pprDataCon pefas dataCon = pprAlgTyCon pefas tyCon (== dataCon) (const True)
149   where tyCon = GHC.dataConTyCon dataCon
150
151 pprDataConDecl pefas gadt_style show_label dataCon
152   | not gadt_style = ppr_fields tys_w_strs
153   | otherwise      = ppr_bndr dataCon <+> dcolon <+> 
154                         sep [ ppr_tvs, GHC.pprThetaArrow theta, pp_tau ]
155   where
156     (tyvars, theta, argTypes, res_ty) = GHC.dataConSig dataCon
157     tyCon = GHC.dataConTyCon dataCon
158     labels = GHC.dataConFieldLabels dataCon
159     qualVars = filter (flip notElem (GHC.tyConTyVars tyCon)) tyvars
160     stricts = GHC.dataConStrictMarks dataCon
161     tys_w_strs = zip stricts argTypes
162
163     ppr_tvs 
164         | null qualVars = empty
165         | otherwise     = ptext SLIT("forall") <+> 
166                                 hsep (map ppr qualVars) <> dot
167
168         -- printing out the dataCon as a type signature, in GADT style
169     pp_tau = foldr add (ppr res_ty) tys_w_strs
170     add (str,ty) pp_ty = pprBangTy str ty <+> arrow <+> pp_ty
171
172     pprParendBangTy (strict,ty)
173         | GHC.isMarkedStrict strict = char '!' <> GHC.pprParendType ty
174         | otherwise                 = GHC.pprParendType ty
175
176     pprBangTy strict ty
177         | GHC.isMarkedStrict strict = char '!' <> ppr ty
178         | otherwise                 = ppr ty
179
180     maybe_show_label (lbl,(strict,tp))
181         | show_label lbl = Just (ppr lbl <+> dcolon <+> pprBangTy strict tp)
182         | otherwise      = Nothing
183
184     ppr_fields [ty1, ty2]
185         | GHC.dataConIsInfix dataCon && null labels
186         = sep [pprParendBangTy ty1, ppr dataCon, pprParendBangTy ty2]
187     ppr_fields fields
188         | null labels
189         = ppr_bndr dataCon <+> sep (map pprParendBangTy fields)
190         | otherwise
191         = ppr_bndr dataCon <+> 
192                 braces (sep (punctuate comma (ppr_trim maybe_show_label 
193                                         (zip labels fields))))
194
195 pprClass pefas cls
196   | null methods = 
197         pprClassHdr pefas cls
198   | otherwise = 
199         hang (pprClassHdr pefas cls <+> ptext SLIT("where"))
200             2 (vcat (map (pprClassMethod pefas) methods))
201   where
202         methods = GHC.classMethods cls
203
204 pprClassOneMethod pefas cls this_one = 
205   hang (pprClassHdr pefas cls <+> ptext SLIT("where"))
206         2 (vcat (ppr_trim show_meth methods))
207   where
208         methods = GHC.classMethods cls
209         show_meth id | id == this_one = Just (pprClassMethod pefas id)
210                      | otherwise      = Nothing
211
212 pprClassMethod pefas id =
213   hang (ppr_bndr id <+> dcolon) 2 (pprType pefas (classOpType id))
214   where
215   -- Here's the magic incantation to strip off the dictionary
216   -- from the class op type.  Stolen from IfaceSyn.tyThingToIfaceDecl.
217   classOpType id = GHC.funResultTy rho_ty
218      where (_sel_tyvars, rho_ty) = GHC.splitForAllTys (GHC.idType id)
219
220 ppr_trim :: (a -> Maybe SDoc) -> [a] -> [SDoc]
221 ppr_trim show xs
222   = snd (foldr go (False, []) xs)
223   where
224     go x (eliding, so_far)
225         | Just doc <- show x = (False, doc : so_far)
226         | otherwise = if eliding then (True, so_far)
227                                  else (True, ptext SLIT("...") : so_far)
228
229 add_bars []      = empty
230 add_bars [c]     = equals <+> c
231 add_bars (c:cs)  = sep ((equals <+> c) : map (char '|' <+>) cs)
232
233 -- Wrap operators in ()
234 ppr_bndr :: GHC.NamedThing a => a -> SDoc
235 ppr_bndr a = GHC.pprParenSymName a
236
237 showWithLoc :: SrcSpan -> SDoc -> SDoc
238 showWithLoc loc doc 
239     = hang doc 2 (char '\t' <> comment <+> GHC.pprDefnLoc loc)
240                 -- The tab tries to make them line up a bit
241   where
242     comment = ptext SLIT("--")
243