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