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