61a14ef2056ee1d068c3931944044427176c6ae8
[ghc-hetmet.git] / ghc / compiler / rename / RnTypes.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 \section[RnSource]{Main pass of renamer}
5
6 \begin{code}
7 module RnTypes (  rnHsType, rnHsSigType, rnHsTypeFVs, rnHsSigTypeFVs, rnContext ) where
8
9 import CmdLineOpts      ( DynFlag(Opt_WarnMisc, Opt_WarnUnusedMatches) )
10
11 import HsSyn
12 import RdrHsSyn ( RdrNameContext, RdrNameHsType, extractHsTyRdrTyVars, extractHsCtxtRdrTyVars )
13 import RnHsSyn  ( RenamedContext, RenamedHsType, extractHsTyNames, tupleTyCon_name )
14 import RnEnv    ( lookupOccRn, newIPName, bindTyVarsRn )
15 import RnMonad
16
17 import PrelInfo ( cCallishClassKeys )
18 import RdrName  ( elemRdrEnv )
19 import NameSet  ( FreeVars )
20 import Unique   ( Uniquable(..) )
21
22 import List             ( nub )
23 import ListSetOps       ( removeDupsEq )
24 import Outputable
25
26 #include "HsVersions.h"
27 \end{code}
28
29 These type renamers are in a separate module, rather than in (say) RnSource,
30 to break several loop.
31
32 %*********************************************************
33 %*                                                      *
34 \subsection{Renaming types}
35 %*                                                      *
36 %*********************************************************
37
38 \begin{code}
39 rnHsTypeFVs :: SDoc -> RdrNameHsType -> RnMS (RenamedHsType, FreeVars)
40 rnHsTypeFVs doc_str ty 
41   = rnHsType doc_str ty         `thenRn` \ ty' ->
42     returnRn (ty', extractHsTyNames ty')
43
44 rnHsSigTypeFVs :: SDoc -> RdrNameHsType -> RnMS (RenamedHsType, FreeVars)
45 rnHsSigTypeFVs doc_str ty
46   = rnHsSigType doc_str ty      `thenRn` \ ty' ->
47     returnRn (ty', extractHsTyNames ty')
48
49 rnHsSigType :: SDoc -> RdrNameHsType -> RnMS RenamedHsType
50         -- rnHsSigType is used for source-language type signatures,
51         -- which use *implicit* universal quantification.
52 rnHsSigType doc_str ty
53   = rnHsType (text "In the type signature for" <+> doc_str) ty
54 \end{code}
55
56 rnHsType is here because we call it from loadInstDecl, and I didn't
57 want a gratuitous knot.
58
59 \begin{code}
60 rnHsType :: SDoc -> RdrNameHsType -> RnMS RenamedHsType
61
62 rnHsType doc (HsForAllTy Nothing ctxt ty)
63         -- Implicit quantifiction in source code (no kinds on tyvars)
64         -- Given the signature  C => T  we universally quantify 
65         -- over FV(T) \ {in-scope-tyvars} 
66   = getLocalNameEnv             `thenRn` \ name_env ->
67     let
68         mentioned_in_tau  = extractHsTyRdrTyVars ty
69         mentioned_in_ctxt = extractHsCtxtRdrTyVars ctxt
70         mentioned         = nub (mentioned_in_tau ++ mentioned_in_ctxt)
71         forall_tyvars     = filter (not . (`elemRdrEnv` name_env)) mentioned
72     in
73     rnForAll doc (map UserTyVar forall_tyvars) ctxt ty
74
75 rnHsType doc (HsForAllTy (Just forall_tyvars) ctxt tau)
76         -- Explicit quantification.
77         -- Check that the forall'd tyvars are actually 
78         -- mentioned in the type, and produce a warning if not
79   = let
80         mentioned_in_tau                = extractHsTyRdrTyVars tau
81         mentioned_in_ctxt               = extractHsCtxtRdrTyVars ctxt
82         mentioned                       = nub (mentioned_in_tau ++ mentioned_in_ctxt)
83         forall_tyvar_names              = hsTyVarNames forall_tyvars
84
85         -- Explicitly quantified but not mentioned in ctxt or tau
86         warn_guys                       = filter (`notElem` mentioned) forall_tyvar_names
87     in
88     mapRn_ (forAllWarn doc tau) warn_guys       `thenRn_`
89     rnForAll doc forall_tyvars ctxt tau
90
91 rnHsType doc (HsTyVar tyvar)
92   = lookupOccRn tyvar           `thenRn` \ tyvar' ->
93     returnRn (HsTyVar tyvar')
94
95 rnHsType doc (HsOpTy ty1 opname ty2)
96   = lookupOccRn opname  `thenRn` \ name' ->
97     rnHsType doc ty1    `thenRn` \ ty1' ->
98     rnHsType doc ty2    `thenRn` \ ty2' -> 
99     returnRn (HsOpTy ty1' name' ty2')
100
101 rnHsType doc (HsNumTy i)
102   | i == 1    = returnRn (HsNumTy i)
103   | otherwise = failWithRn (HsNumTy i)
104                            (ptext SLIT("Only unit numeric type pattern is valid"))
105
106 rnHsType doc (HsFunTy ty1 ty2)
107   = rnHsType doc ty1    `thenRn` \ ty1' ->
108         -- Might find a for-all as the arg of a function type
109     rnHsType doc ty2    `thenRn` \ ty2' ->
110         -- Or as the result.  This happens when reading Prelude.hi
111         -- when we find return :: forall m. Monad m -> forall a. a -> m a
112     returnRn (HsFunTy ty1' ty2')
113
114 rnHsType doc (HsListTy ty)
115   = rnHsType doc ty                             `thenRn` \ ty' ->
116     returnRn (HsListTy ty')
117
118 -- Unboxed tuples are allowed to have poly-typed arguments.  These
119 -- sometimes crop up as a result of CPR worker-wrappering dictionaries.
120 rnHsType doc (HsTupleTy (HsTupCon _ boxity arity) tys)
121         -- Don't do lookupOccRn, because this is built-in syntax
122         -- so it doesn't need to be in scope
123   = mapRn (rnHsType doc) tys            `thenRn` \ tys' ->
124     returnRn (HsTupleTy (HsTupCon tup_name boxity arity) tys')
125   where
126     tup_name = tupleTyCon_name boxity arity
127   
128
129 rnHsType doc (HsAppTy ty1 ty2)
130   = rnHsType doc ty1            `thenRn` \ ty1' ->
131     rnHsType doc ty2            `thenRn` \ ty2' ->
132     returnRn (HsAppTy ty1' ty2')
133
134 rnHsType doc (HsPredTy pred)
135   = rnPred doc pred     `thenRn` \ pred' ->
136     returnRn (HsPredTy pred')
137
138 rnHsTypes doc tys = mapRn (rnHsType doc) tys
139 \end{code}
140
141 \begin{code}
142 rnForAll doc forall_tyvars ctxt ty
143   = bindTyVarsRn doc forall_tyvars      $ \ new_tyvars ->
144     rnContext doc ctxt                  `thenRn` \ new_ctxt ->
145     rnHsType doc ty                     `thenRn` \ new_ty ->
146     returnRn (mkHsForAllTy (Just new_tyvars) new_ctxt new_ty)
147 \end{code}
148
149 \begin{code}
150 rnContext :: SDoc -> RdrNameContext -> RnMS RenamedContext
151 rnContext doc ctxt
152   = mapRn rn_pred ctxt          `thenRn` \ theta ->
153
154         -- Check for duplicate assertions
155         -- If this isn't an error, then it ought to be:
156     ifOptRn Opt_WarnMisc (
157         let
158             (_, dups) = removeDupsEq theta
159                 -- We only have equality, not ordering
160         in
161         mapRn (addWarnRn . dupClassAssertWarn theta) dups
162     )                           `thenRn_`
163
164     returnRn theta
165   where
166         --Someone discovered that @CCallable@ and @CReturnable@
167         -- could be used in contexts such as:
168         --      foo :: CCallable a => a -> PrimIO Int
169         -- Doing this utterly wrecks the whole point of introducing these
170         -- classes so we specifically check that this isn't being done.
171     rn_pred pred = rnPred doc pred                              `thenRn` \ pred'->
172                    checkRn (not (bad_pred pred'))
173                            (naughtyCCallContextErr pred')       `thenRn_`
174                    returnRn pred'
175
176     bad_pred (HsClassP clas _) = getUnique clas `elem` cCallishClassKeys
177     bad_pred other             = False
178
179
180 rnPred doc (HsClassP clas tys)
181   = lookupOccRn clas            `thenRn` \ clas_name ->
182     rnHsTypes doc tys           `thenRn` \ tys' ->
183     returnRn (HsClassP clas_name tys')
184
185 rnPred doc (HsIParam n ty)
186   = newIPName n                 `thenRn` \ name ->
187     rnHsType doc ty             `thenRn` \ ty' ->
188     returnRn (HsIParam name ty')
189 \end{code}
190
191 \end{code}
192 \begin{code}
193 forAllWarn doc ty tyvar
194   = ifOptRn Opt_WarnUnusedMatches       $
195     getModeRn                           `thenRn` \ mode ->
196     case mode of {
197 #ifndef DEBUG
198              InterfaceMode -> returnRn () ; -- Don't warn of unused tyvars in interface files
199                                             -- unless DEBUG is on, in which case it is slightly
200                                             -- informative.  They can arise from mkRhsTyLam,
201 #endif                                      -- leading to (say)         f :: forall a b. [b] -> [b]
202              other ->
203                 addWarnRn (
204                    sep [ptext SLIT("The universally quantified type variable") <+> quotes (ppr tyvar),
205                    nest 4 (ptext SLIT("does not appear in the type") <+> quotes (ppr ty))]
206                    $$
207                    doc
208                 )
209           }
210
211 dupClassAssertWarn ctxt (assertion : dups)
212   = sep [hsep [ptext SLIT("Duplicate class assertion"), 
213                quotes (ppr assertion),
214                ptext SLIT("in the context:")],
215          nest 4 (pprHsContext ctxt <+> ptext SLIT("..."))]
216
217 naughtyCCallContextErr (HsClassP clas _)
218   = sep [ptext SLIT("Can't use class") <+> quotes (ppr clas), 
219          ptext SLIT("in a context")]
220 \end{code}