0f70df5f42057c5b0557927d8205e13a88c0a847
[ghc-hetmet.git] / ghc / compiler / hsSyn / HsTypes.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 \section[HsTypes]{Abstract syntax: user-defined types}
5
6 \begin{code}
7 module HsTypes (
8         HsType(..), MonoUsageAnn(..), HsTyVar(..),
9         HsContext, HsClassAssertion, HsPred(..)
10
11         , mkHsForAllTy, mkHsUsForAllTy
12         , getTyVarName, replaceTyVarName
13         , pprParendHsType
14         , pprForAll, pprHsContext, pprHsClassAssertion, pprHsPred
15         , cmpHsType, cmpHsTypes, cmpHsContext, cmpHsPred
16     ) where
17
18 #include "HsVersions.h"
19
20 import Type             ( Kind, UsageAnn(..) )
21 import PprType          ( {- instance Outputable Kind -} )
22 import Outputable
23 import Util             ( thenCmp, cmpList )
24 \end{code}
25
26 This is the syntax for types as seen in type signatures.
27
28 \begin{code}
29 type HsContext name = [HsPred name]
30 type HsClassAssertion name = (name, [HsType name])
31 -- The type is usually a type variable, but it
32 -- doesn't have to be when reading interface files
33 data HsPred name =
34     HsPClass name [HsType name]
35   | HsPIParam name (HsType name)
36
37 data HsType name
38   = HsForAllTy          (Maybe [HsTyVar name])  -- Nothing for implicitly quantified signatures
39                         (HsContext name)
40                         (HsType name)
41
42   | MonoTyVar           name            -- Type variable
43
44   | MonoTyApp           (HsType name)
45                         (HsType name)
46
47   | MonoFunTy           (HsType name) -- function type
48                         (HsType name)
49
50   | MonoListTy          (HsType name)   -- Element type
51
52   | MonoTupleTy         [HsType name]   -- Element types (length gives arity)
53                         Bool            -- boxed?
54
55   -- these next two are only used in interfaces
56   | MonoDictTy          name    -- Class
57                         [HsType name]
58
59   | MonoUsgTy           (MonoUsageAnn name)
60                         (HsType name)
61
62   | MonoUsgForAllTy     name
63                         (HsType name)
64
65 data MonoUsageAnn name
66   = MonoUsOnce
67   | MonoUsMany
68   | MonoUsVar name
69   
70
71 -- Combine adjacent for-alls. 
72 -- The following awkward situation can happen otherwise:
73 --      f :: forall a. ((Num a) => Int)
74 -- might generate HsForAll (Just [a]) [] (HsForAll Nothing [Num a] t)
75 -- Then a isn't discovered as ambiguous, and we abstract the AbsBinds wrt []
76 -- but the export list abstracts f wrt [a].  Disaster.
77 --
78 -- A valid type must have one for-all at the top of the type, or of the fn arg types
79
80 mkHsForAllTy (Just []) [] ty = ty       -- Explicit for-all with no tyvars
81 mkHsForAllTy mtvs1     [] (HsForAllTy mtvs2 ctxt ty) = mkHsForAllTy (mtvs1 `plus` mtvs2) ctxt ty
82                                                      where
83                                                        mtvs1       `plus` Nothing     = mtvs1
84                                                        Nothing     `plus` mtvs2       = mtvs2 
85                                                        (Just tvs1) `plus` (Just tvs2) = Just (tvs1 ++ tvs2)
86 mkHsForAllTy tvs ctxt ty = HsForAllTy tvs ctxt ty
87
88 mkHsUsForAllTy uvs ty = foldr (\ uv ty -> MonoUsgForAllTy uv ty)
89                               ty uvs
90
91 data HsTyVar name
92   = UserTyVar name
93   | IfaceTyVar name Kind
94         -- *** NOTA BENE *** A "monotype" in a pragma can have
95         -- for-alls in it, (mostly to do with dictionaries).  These
96         -- must be explicitly Kinded.
97
98 getTyVarName (UserTyVar n)    = n
99 getTyVarName (IfaceTyVar n _) = n
100
101 replaceTyVarName :: HsTyVar name1 -> name2 -> HsTyVar name2
102 replaceTyVarName (UserTyVar n)    n' = UserTyVar n'
103 replaceTyVarName (IfaceTyVar n k) n' = IfaceTyVar n' k
104 \end{code}
105
106
107 %************************************************************************
108 %*                                                                      *
109 \subsection{Pretty printing}
110 %*                                                                      *
111 %************************************************************************
112
113 \begin{code}
114
115 instance (Outputable name) => Outputable (HsType name) where
116     ppr ty = pprHsType ty
117
118 instance (Outputable name) => Outputable (HsTyVar name) where
119     ppr (UserTyVar name)       = ppr name
120     ppr (IfaceTyVar name kind) = hsep [ppr name, dcolon, ppr kind]
121
122 -- Better to see those for-alls
123 -- pprForAll []  = empty
124 pprForAll tvs = ptext SLIT("forall") <+> interppSP tvs <> ptext SLIT(".")
125
126 pprHsContext :: (Outputable name) => HsContext name -> SDoc
127 pprHsContext []    = empty
128 pprHsContext context = parens (hsep (punctuate comma (map pprHsPred context))) <+> ptext SLIT("=>")
129
130 pprHsClassAssertion :: (Outputable name) => HsClassAssertion name -> SDoc
131 pprHsClassAssertion (clas, tys)
132   = ppr clas <+> hsep (map pprParendHsType tys)
133
134 pprHsPred :: (Outputable name) => HsPred name -> SDoc
135 pprHsPred (HsPClass clas tys)
136   = ppr clas <+> hsep (map pprParendHsType tys)
137 pprHsPred (HsPIParam n ty)
138   = hsep [char '?' <> ppr n, text "::", ppr ty]
139 \end{code}
140
141 \begin{code}
142 pREC_TOP = (0 :: Int)
143 pREC_FUN = (1 :: Int)
144 pREC_CON = (2 :: Int)
145
146 maybeParen :: Bool -> SDoc -> SDoc
147 maybeParen True  p = parens p
148 maybeParen False p = p
149         
150 -- printing works more-or-less as for Types
151
152 pprHsType, pprParendHsType :: (Outputable name) => HsType name -> SDoc
153
154 pprHsType ty       = ppr_mono_ty pREC_TOP ty
155 pprParendHsType ty = ppr_mono_ty pREC_CON ty
156
157 ppr_mono_ty ctxt_prec (HsForAllTy maybe_tvs ctxt ty)
158   = maybeParen (ctxt_prec >= pREC_FUN) $
159     sep [pp_tvs, pprHsContext ctxt, pprHsType ty]
160   where
161     pp_tvs = case maybe_tvs of
162                 Just tvs -> pprForAll tvs
163                 Nothing  -> text "{- implicit forall -}"
164
165 ppr_mono_ty ctxt_prec (MonoTyVar name)
166   = ppr name
167
168 ppr_mono_ty ctxt_prec (MonoFunTy ty1 ty2)
169   = let p1 = ppr_mono_ty pREC_FUN ty1
170         p2 = ppr_mono_ty pREC_TOP ty2
171     in
172     maybeParen (ctxt_prec >= pREC_FUN)
173                (sep [p1, (<>) (ptext SLIT("-> ")) p2])
174
175 ppr_mono_ty ctxt_prec (MonoTupleTy tys True)
176  = parens (sep (punctuate comma (map ppr tys)))
177 ppr_mono_ty ctxt_prec (MonoTupleTy tys False)
178  = ptext SLIT("(#") <> sep (punctuate comma (map ppr tys)) <> ptext SLIT("#)")
179
180 ppr_mono_ty ctxt_prec (MonoListTy ty)
181  = brackets (ppr_mono_ty pREC_TOP ty)
182
183 ppr_mono_ty ctxt_prec (MonoTyApp fun_ty arg_ty)
184   = maybeParen (ctxt_prec >= pREC_CON)
185                (hsep [ppr_mono_ty pREC_FUN fun_ty, ppr_mono_ty pREC_CON arg_ty])
186
187 ppr_mono_ty ctxt_prec (MonoDictTy clas tys)
188   = ppr clas <+> hsep (map (ppr_mono_ty pREC_CON) tys)
189
190 ppr_mono_ty ctxt_prec ty@(MonoUsgForAllTy _ _)
191   = maybeParen (ctxt_prec >= pREC_FUN) $
192     sep [ ptext SLIT("__fuall") <+> brackets pp_uvars <+> ptext SLIT("=>"),
193           ppr_mono_ty pREC_TOP sigma
194         ]
195   where
196     (uvars,sigma) = split [] ty
197     pp_uvars      = interppSP uvars
198
199     split uvs (MonoUsgForAllTy uv ty') = split (uv:uvs) ty'
200     split uvs ty'                      = (reverse uvs,ty')
201
202 ppr_mono_ty ctxt_prec (MonoUsgTy u ty)
203   = maybeParen (ctxt_prec >= pREC_CON) $
204     ptext SLIT("__u") <+> pp_ua <+> ppr_mono_ty pREC_CON ty
205   where
206     pp_ua = case u of
207               MonoUsOnce   -> ptext SLIT("-")
208               MonoUsMany   -> ptext SLIT("!")
209               MonoUsVar uv -> ppr uv
210 \end{code}
211
212
213 %************************************************************************
214 %*                                                                      *
215 \subsection{Comparison}
216 %*                                                                      *
217 %************************************************************************
218
219 We do define a specialised equality for these \tr{*Type} types; used
220 in checking interfaces.  Most any other use is likely to be {\em
221 wrong}, so be careful!
222
223 \begin{code}
224 cmpHsTyVar   :: (a -> a -> Ordering) -> HsTyVar a   -> HsTyVar a   -> Ordering
225 cmpHsType    :: (a -> a -> Ordering) -> HsType a    -> HsType a    -> Ordering
226 cmpHsTypes   :: (a -> a -> Ordering) -> [HsType a]  -> [HsType a]  -> Ordering
227 cmpHsContext :: (a -> a -> Ordering) -> HsContext a -> HsContext a -> Ordering
228 cmpHsPred    :: (a -> a -> Ordering) -> HsPred a    -> HsPred a    -> Ordering
229
230 cmpHsTyVar cmp (UserTyVar v1)    (UserTyVar v2)    = v1 `cmp` v2
231 cmpHsTyVar cmp (IfaceTyVar v1 _) (IfaceTyVar v2 _) = v1 `cmp` v2
232 cmpHsTyVar cmp (UserTyVar _)     other             = LT
233 cmpHsTyVar cmp other1            other2            = GT
234
235 cmpHsTypes cmp [] []   = EQ
236 cmpHsTypes cmp [] tys2 = LT
237 cmpHsTypes cmp tys1 [] = GT
238 cmpHsTypes cmp (ty1:tys1) (ty2:tys2) = cmpHsType cmp ty1 ty2 `thenCmp` cmpHsTypes cmp tys1 tys2
239
240 cmpHsType cmp (HsForAllTy tvs1 c1 t1) (HsForAllTy tvs2 c2 t2)
241   = cmpMaybe (cmpList (cmpHsTyVar cmp)) tvs1 tvs2       `thenCmp`
242     cmpHsContext cmp c1 c2                              `thenCmp`
243     cmpHsType cmp t1 t2
244
245 cmpHsType cmp (MonoTyVar n1) (MonoTyVar n2)
246   = cmp n1 n2
247
248 cmpHsType cmp (MonoTupleTy tys1 b1) (MonoTupleTy tys2 b2)
249   = (b1 `compare` b2) `thenCmp` cmpHsTypes cmp tys1 tys2
250
251 cmpHsType cmp (MonoListTy ty1) (MonoListTy ty2)
252   = cmpHsType cmp ty1 ty2
253
254 cmpHsType cmp (MonoTyApp fun_ty1 arg_ty1) (MonoTyApp fun_ty2 arg_ty2)
255   = cmpHsType cmp fun_ty1 fun_ty2 `thenCmp` cmpHsType cmp arg_ty1 arg_ty2
256
257 cmpHsType cmp (MonoFunTy a1 b1) (MonoFunTy a2 b2)
258   = cmpHsType cmp a1 a2 `thenCmp` cmpHsType cmp b1 b2
259
260 cmpHsType cmp (MonoDictTy c1 tys1)   (MonoDictTy c2 tys2)
261   = cmp c1 c2 `thenCmp` cmpHsTypes cmp tys1 tys2
262
263 cmpHsType cmp (MonoUsgTy u1 ty1) (MonoUsgTy u2 ty2)
264   = cmpUsg cmp u1 u2 `thenCmp` cmpHsType cmp ty1 ty2
265
266 cmpHsType cmp ty1 ty2 -- tags must be different
267   = let tag1 = tag ty1
268         tag2 = tag ty2
269     in
270     if tag1 _LT_ tag2 then LT else GT
271   where
272     tag (MonoTyVar n1)                  = (ILIT(1) :: FAST_INT)
273     tag (MonoTupleTy tys1 _)            = ILIT(2)
274     tag (MonoListTy ty1)                = ILIT(3)
275     tag (MonoTyApp tc1 tys1)            = ILIT(4)
276     tag (MonoFunTy a1 b1)               = ILIT(5)
277     tag (MonoDictTy c1 tys1)            = ILIT(6)
278     tag (MonoUsgTy c1 ty1)              = ILIT(7)
279     tag (MonoUsgForAllTy uv1 ty1)       = ILIT(8)
280     tag (HsForAllTy _ _ _)              = ILIT(9)
281
282 -------------------
283 cmpHsContext cmp a b
284   = cmpList (cmpHsPred cmp) a b
285
286 cmpHsPred cmp (HsPClass c1 tys1) (HsPClass c2 tys2)
287   = cmp c1 c2 `thenCmp` cmpHsTypes cmp tys1 tys2
288 cmpHsPred cmp (HsPIParam n1 ty1) (HsPIParam n2 ty2)
289   = cmp n1 n2 `thenCmp` cmpHsType cmp ty1 ty2
290 cmpHsPred cmp (HsPClass _ _) (HsPIParam _ _) = LT
291 cmpHsPred cmp _              _               = GT
292
293 cmpUsg cmp  MonoUsOnce     MonoUsOnce    = EQ
294 cmpUsg cmp  MonoUsMany     MonoUsMany    = EQ
295 cmpUsg cmp (MonoUsVar u1) (MonoUsVar u2) = cmp u1 u2
296
297 cmpUsg cmp ua1 ua2  -- tags must be different
298   = let tag1 = tag ua1
299         tag2 = tag ua2
300     in
301         if tag1 _LT_ tag2 then LT else GT
302   where
303     tag MonoUsOnce       = (ILIT(1) :: FAST_INT)
304     tag MonoUsMany       = ILIT(2)
305     tag (MonoUsVar    _) = ILIT(3)
306
307 -- Should be in Maybes, I guess
308 cmpMaybe cmp Nothing  Nothing  = EQ
309 cmpMaybe cmp Nothing  (Just x) = LT
310 cmpMaybe cmp (Just x)  Nothing = GT
311 cmpMaybe cmp (Just x) (Just y) = x `cmp` y
312 \end{code}