7702e31d652ec61e903d4366a71c73c1f4bf8006
[ghc-hetmet.git] / ghc / compiler / typecheck / TcEnv.lhs
1 \begin{code}
2 #include "HsVersions.h"
3
4 module TcEnv(
5         TcEnv, 
6
7         initEnv, getEnv_LocalIds, getEnv_TyCons, getEnv_Classes,
8         
9         tcTyVarScope, tcTyVarScopeGivenKinds, tcLookupTyVar, 
10
11         tcExtendTyConEnv, tcLookupTyCon, tcLookupTyConByKey, 
12         tcExtendClassEnv, tcLookupClass, tcLookupClassByKey,
13         tcGetTyConsAndClasses,
14
15         tcExtendGlobalValEnv, tcExtendLocalValEnv,
16         tcLookupLocalValue, tcLookupLocalValueOK, tcLookupLocalValueByKey, 
17         tcLookupGlobalValue, tcLookupGlobalValueByKey,
18
19         newMonoIds, newLocalIds, newLocalId,
20         tcGetGlobalTyVars
21   ) where
22
23
24 import Ubiq
25 import TcMLoop  -- for paranoia checking
26
27 import Id       ( Id(..), GenId, idType, mkUserLocal )
28 import TcHsSyn  ( TcIdBndr(..), TcIdOcc(..) )
29 import TcKind   ( TcKind, newKindVars, tcDefaultKind, kindToTcKind )
30 import TcType   ( TcType(..), TcMaybe, TcTyVar(..), TcTyVarSet(..),
31                   newTyVarTys, tcInstTyVars, tcInstType, zonkTcTyVars
32                 )
33 import TyVar    ( mkTyVar, tyVarKind, unionTyVarSets, emptyTyVarSet )
34 import Type     ( tyVarsOfTypes )
35 import TyCon    ( TyCon, Arity(..), tyConKind, synTyConArity )
36 import Class    ( Class(..), GenClass, classSig )
37
38 import TcMonad          hiding ( rnMtoTcM )
39
40 import Name             ( getOccName, getSrcLoc, Name{-instance NamedThing-} )
41 import PprStyle
42 import Pretty
43 import RnHsSyn          ( RnName(..) )
44 import Type             ( splitForAllTy )
45 import Unique           ( pprUnique10, pprUnique{-ToDo:rm-} )
46 import UniqFM        
47 import Util             ( zipEqual, zipWithEqual, zipWith3Equal, zipLazy,
48                           panic, pprPanic, pprTrace{-ToDo:rm-}
49                         )
50 \end{code}
51
52 Data type declarations
53 ~~~~~~~~~~~~~~~~~~~~~
54
55 \begin{code}
56 data TcEnv s = TcEnv
57                   (TyVarEnv s)
58                   (TyConEnv s)
59                   (ClassEnv s)
60                   (ValueEnv Id)                 -- Globals
61                   (ValueEnv (TcIdBndr s))       -- Locals
62                   (MutableVar s (TcTyVarSet s)) -- Free type variables of locals
63                                                 -- ...why mutable? see notes with tcGetGlobalTyVars
64
65 type TyVarEnv s  = UniqFM (TcKind s, TyVar)
66 type TyConEnv s  = UniqFM (TcKind s, Maybe Arity, TyCon)        -- Arity present for Synonyms only
67 type ClassEnv s  = UniqFM (TcKind s, Class)
68 type ValueEnv id = UniqFM id
69
70 initEnv :: MutableVar s (TcTyVarSet s) -> TcEnv s
71 initEnv mut = TcEnv emptyUFM emptyUFM emptyUFM emptyUFM emptyUFM mut 
72
73 getEnv_LocalIds (TcEnv _ _ _ _ ls _) = eltsUFM ls
74 getEnv_TyCons   (TcEnv _ ts _ _ _ _) = [tycon | (_, _, tycon) <- eltsUFM ts]
75 getEnv_Classes  (TcEnv _ _ cs _ _ _) = [clas  | (_, clas)     <- eltsUFM cs]
76 \end{code}
77
78 Making new TcTyVars, with knot tying!
79 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
80 \begin{code}
81 tcTyVarScopeGivenKinds 
82         :: [Name]               -- Names of some type variables
83         -> [TcKind s]
84         -> ([TyVar] -> TcM s a) -- Thing to type check in their scope
85         -> TcM s a              -- Result
86
87 tcTyVarScopeGivenKinds names kinds thing_inside
88   = fixTc (\ ~(rec_tyvars, _) ->
89                 -- Ok to look at names, kinds, but not tyvars!
90
91         tcGetEnv                                `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
92         let
93             tve' = addListToUFM tve (zipEqual "tcTyVarScopeGivenKinds" names (kinds `zipLazy` rec_tyvars))
94         in
95         tcSetEnv (TcEnv tve' tce ce gve lve gtvs) 
96                  (thing_inside rec_tyvars)      `thenTc` \ result ->
97  
98                 -- Get the tyvar's Kinds from their TcKinds
99         mapNF_Tc tcDefaultKind kinds            `thenNF_Tc` \ kinds' ->
100
101                 -- Construct the real TyVars
102         let
103           tyvars             = zipWithEqual "tcTyVarScopeGivenKinds" mk_tyvar names kinds'
104           mk_tyvar name kind = mkTyVar name (uniqueOf name) kind
105         in
106         returnTc (tyvars, result)
107     )                                   `thenTc` \ (_,result) ->
108     returnTc result
109
110 tcTyVarScope names thing_inside
111   = newKindVars (length names)  `thenNF_Tc` \ kinds ->
112     tcTyVarScopeGivenKinds names kinds thing_inside
113 \end{code}
114
115
116 The Kind, TyVar, Class and TyCon envs
117 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
118
119 Extending the environments.  Notice the uses of @zipLazy@, which makes sure
120 that the knot-tied TyVars, TyCons and Classes aren't looked at too early.
121
122 \begin{code}
123 tcExtendTyConEnv :: [(RnName,Maybe Arity)] -> [TyCon] -> TcM s r -> TcM s r
124
125 tcExtendTyConEnv names_w_arities tycons scope
126   = newKindVars (length names_w_arities)        `thenNF_Tc` \ kinds ->
127     tcGetEnv                                    `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
128     let
129         tce' = addListToUFM tce [ (name, (kind, arity, tycon)) 
130                                 | ((name,arity), (kind,tycon))
131                                   <- zipEqual "tcExtendTyConEnv" names_w_arities (kinds `zipLazy` tycons)
132                                 ]
133     in
134     tcSetEnv (TcEnv tve tce' ce gve lve gtvs) scope     `thenTc` \ result ->
135     mapNF_Tc tcDefaultKind kinds                        `thenNF_Tc_`
136     returnTc result 
137
138
139 tcExtendClassEnv :: [RnName] -> [Class] -> TcM s r -> TcM s r
140 tcExtendClassEnv names classes scope
141   = newKindVars (length names)  `thenNF_Tc` \ kinds ->
142     tcGetEnv                    `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
143     let
144         ce' = addListToUFM ce (zipEqual "tcExtendClassEnv" names (kinds `zipLazy` classes))
145     in
146     tcSetEnv (TcEnv tve tce ce' gve lve gtvs) scope     `thenTc` \ result ->
147     mapNF_Tc tcDefaultKind kinds                        `thenNF_Tc_`
148     returnTc result 
149 \end{code}
150
151
152 Looking up in the environments.
153
154 \begin{code}
155 tcLookupTyVar name
156   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
157     returnNF_Tc (lookupWithDefaultUFM tve (pprPanic "tcLookupTyVar:" (ppr PprShowAll name)) name)
158
159
160 tcLookupTyCon (WiredInTyCon tc)         -- wired in tycons
161   = returnNF_Tc (kindToTcKind (tyConKind tc), synTyConArity tc, tc)
162
163 tcLookupTyCon name
164   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
165     returnNF_Tc (lookupWithDefaultUFM tce (pprPanic "tcLookupTyCon:" (ppr PprShowAll name)) name)
166
167 tcLookupTyConByKey uniq
168   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
169     let 
170        (kind, arity, tycon) =  lookupWithDefaultUFM_Directly tce 
171                                         (pprPanic "tcLookupTyCon:" (pprUnique10 uniq)) 
172                                         uniq
173     in
174     returnNF_Tc tycon
175
176 tcLookupClass name
177   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
178 --  pprTrace "tcLookupClass:" (ppCat [ppStr "Uniq:", pprUnique10 (uniqueOf name), ppStr "; avail:", ppCat (map (pprUnique10 . fst) (ufmToList ce))]) $
179 --  pprTrace "tcLookupClass:" (ppCat [ppStr "Uniq:", pprUnique (uniqueOf name), ppStr "; avail:", ppCat (map (pprUnique . fst) (ufmToList ce))]) $
180     returnNF_Tc (lookupWithDefaultUFM ce (pprPanic "tcLookupClass:" (ppr PprShowAll name)) name)
181
182 tcLookupClassByKey uniq
183   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
184     let
185         (kind, clas) = lookupWithDefaultUFM_Directly ce 
186                                 (pprPanic "tcLookupClassByKey:" (pprUnique10 uniq))
187                                 uniq
188     in
189     returnNF_Tc clas
190
191 tcGetTyConsAndClasses :: NF_TcM s ([TyCon], [Class])
192 tcGetTyConsAndClasses
193   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
194     returnNF_Tc ([tc | (_, _, tc) <- eltsUFM tce],
195                  [c  | (_, c)     <- eltsUFM ce])
196 \end{code}
197
198
199
200 Extending and consulting the value environment
201 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
202 \begin{code}
203 tcExtendGlobalValEnv ids scope
204   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
205     let
206         gve' = addListToUFM_Directly gve [(uniqueOf id, id) | id <- ids]
207     in
208     tcSetEnv (TcEnv tve tce ce gve' lve gtvs) scope
209
210 tcExtendLocalValEnv names ids scope
211   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
212     tcReadMutVar gtvs   `thenNF_Tc` \ global_tvs ->
213     let
214         lve' = addListToUFM lve (zipEqual "tcExtendLocalValEnv" names ids)
215         extra_global_tyvars = tyVarsOfTypes (map idType ids)
216         new_global_tyvars   = global_tvs `unionTyVarSets` extra_global_tyvars
217     in
218     tcNewMutVar new_global_tyvars       `thenNF_Tc` \ gtvs' ->
219
220     tcSetEnv (TcEnv tve tce ce gve lve' gtvs') scope
221 \end{code}
222
223 @tcGetGlobalTyVars@ returns a fully-zonked set of tyvars free in the environment.
224 To improve subsequent calls to the same function it writes the zonked set back into
225 the environment.
226
227 \begin{code}
228 tcGetGlobalTyVars :: NF_TcM s (TcTyVarSet s)
229 tcGetGlobalTyVars
230   = tcGetEnv                            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
231     tcReadMutVar gtvs                   `thenNF_Tc` \ global_tvs ->
232     zonkTcTyVars global_tvs             `thenNF_Tc` \ global_tvs' ->
233     tcWriteMutVar gtvs global_tvs'      `thenNF_Tc_`
234     returnNF_Tc global_tvs'
235 \end{code}
236
237 \begin{code}
238 tcLookupLocalValue :: RnName -> NF_TcM s (Maybe (TcIdBndr s))
239 tcLookupLocalValue name
240   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
241     returnNF_Tc (lookupUFM lve name)
242
243 tcLookupLocalValueByKey :: Unique -> NF_TcM s (Maybe (TcIdBndr s))
244 tcLookupLocalValueByKey uniq
245   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
246     returnNF_Tc (lookupUFM_Directly lve uniq)
247
248 tcLookupLocalValueOK :: String -> RnName -> NF_TcM s (TcIdBndr s)
249 tcLookupLocalValueOK err name
250   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
251     returnNF_Tc (lookupWithDefaultUFM lve (panic err) name)
252
253
254 tcLookupGlobalValue :: RnName -> NF_TcM s Id
255
256 tcLookupGlobalValue (WiredInId id)      -- wired in ids
257   = returnNF_Tc id
258
259 tcLookupGlobalValue name
260   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
261     returnNF_Tc (lookupWithDefaultUFM gve def name)
262   where
263 #ifdef DEBUG
264     def = pprPanic "tcLookupGlobalValue:" (ppr PprDebug name)
265 #else
266     def = panic "tcLookupGlobalValue"
267 #endif
268
269 tcLookupGlobalValueByKey :: Unique -> NF_TcM s Id
270 tcLookupGlobalValueByKey uniq
271   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
272     returnNF_Tc (lookupWithDefaultUFM_Directly gve def uniq)
273   where
274 #ifdef DEBUG
275     def = pprPanic "tcLookupGlobalValueByKey:" (pprUnique10 uniq)
276 #else
277     def = panic "tcLookupGlobalValueByKey"
278 #endif
279
280 \end{code}
281
282
283 Constructing new Ids
284 ~~~~~~~~~~~~~~~~~~~~
285
286 \begin{code}
287 newMonoIds :: [RnName] -> Kind -> ([TcIdBndr s] -> TcM s a) -> TcM s a
288
289 newMonoIds names kind m
290   = newTyVarTys no_of_names kind        `thenNF_Tc` \ tys ->
291     tcGetUniques no_of_names            `thenNF_Tc` \ uniqs ->
292     let
293         new_ids = zipWith3Equal "newMonoIds" mk_id names uniqs tys
294
295         mk_id name uniq ty
296           = let
297                 name_str = case (getOccName name) of { Unqual n -> n }
298             in
299             mkUserLocal name_str uniq ty (getSrcLoc name)
300     in
301     tcExtendLocalValEnv names new_ids (m new_ids)
302   where
303     no_of_names = length names
304
305 newLocalId :: FAST_STRING -> TcType s -> NF_TcM s (TcIdOcc s)
306 newLocalId name ty
307   = tcGetSrcLoc         `thenNF_Tc` \ loc ->
308     tcGetUnique         `thenNF_Tc` \ uniq ->
309     returnNF_Tc (TcId (mkUserLocal name uniq ty loc))
310
311 newLocalIds :: [FAST_STRING] -> [TcType s] -> NF_TcM s [TcIdOcc s]
312 newLocalIds names tys
313   = tcGetSrcLoc                 `thenNF_Tc` \ loc ->
314     tcGetUniques (length names) `thenNF_Tc` \ uniqs ->
315     let
316         new_ids            = zipWith3Equal "newLocalIds" mk_id names uniqs tys
317         mk_id name uniq ty = TcId (mkUserLocal name uniq ty loc)
318     in
319     returnNF_Tc new_ids
320 \end{code}
321
322