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