[project @ 1996-06-26 10:26:00 by partain]
[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, tcExtendGlobalTyVars
21   ) where
22
23
24 IMP_Ubiq()
25 IMPORT_DELOOPER(TcMLoop)  -- for paranoia checking
26
27 import Id       ( SYN_IE(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, zonkTcTyVars
32                 )
33 import TyVar    ( mkTyVar, tyVarKind, unionTyVarSets, emptyTyVarSet )
34 import Type     ( tyVarsOfTypes )
35 import TyCon    ( TyCon, tyConKind, synTyConArity )
36 import Class    ( SYN_IE(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" mkTyVar names kinds'
104         in
105         returnTc (tyvars, result)
106     )                                   `thenTc` \ (_,result) ->
107     returnTc result
108
109 tcTyVarScope names thing_inside
110   = newKindVars (length names)  `thenNF_Tc` \ kinds ->
111     tcTyVarScopeGivenKinds names kinds thing_inside
112 \end{code}
113
114
115 The Kind, TyVar, Class and TyCon envs
116 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
117
118 Extending the environments.  Notice the uses of @zipLazy@, which makes sure
119 that the knot-tied TyVars, TyCons and Classes aren't looked at too early.
120
121 \begin{code}
122 tcExtendTyConEnv :: [(RnName,Maybe Arity)] -> [TyCon] -> TcM s r -> TcM s r
123
124 tcExtendTyConEnv names_w_arities tycons scope
125   = newKindVars (length names_w_arities)        `thenNF_Tc` \ kinds ->
126     tcGetEnv                                    `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
127     let
128         tce' = addListToUFM tce [ (name, (kind, arity, tycon)) 
129                                 | ((name,arity), (kind,tycon))
130                                   <- zipEqual "tcExtendTyConEnv" names_w_arities (kinds `zipLazy` tycons)
131                                 ]
132     in
133     tcSetEnv (TcEnv tve tce' ce gve lve gtvs) scope     `thenTc` \ result ->
134     mapNF_Tc tcDefaultKind kinds                        `thenNF_Tc_`
135     returnTc result 
136
137
138 tcExtendClassEnv :: [RnName] -> [Class] -> TcM s r -> TcM s r
139 tcExtendClassEnv names classes scope
140   = newKindVars (length names)  `thenNF_Tc` \ kinds ->
141     tcGetEnv                    `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
142     let
143         ce' = addListToUFM ce (zipEqual "tcExtendClassEnv" names (kinds `zipLazy` classes))
144     in
145     tcSetEnv (TcEnv tve tce ce' gve lve gtvs) scope     `thenTc` \ result ->
146     mapNF_Tc tcDefaultKind kinds                        `thenNF_Tc_`
147     returnTc result 
148 \end{code}
149
150
151 Looking up in the environments.
152
153 \begin{code}
154 tcLookupTyVar name
155   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
156     returnNF_Tc (lookupWithDefaultUFM tve (pprPanic "tcLookupTyVar:" (ppr PprShowAll name)) name)
157
158
159 tcLookupTyCon (WiredInTyCon tc)         -- wired in tycons
160   = returnNF_Tc (kindToTcKind (tyConKind tc), synTyConArity tc, tc)
161
162 tcLookupTyCon name
163   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
164     returnNF_Tc (lookupWithDefaultUFM tce (pprPanic "tcLookupTyCon:" (ppr PprShowAll name)) name)
165
166 tcLookupTyConByKey uniq
167   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
168     let 
169        (kind, arity, tycon) =  lookupWithDefaultUFM_Directly tce 
170                                         (pprPanic "tcLookupTyCon:" (pprUnique10 uniq)) 
171                                         uniq
172     in
173     returnNF_Tc tycon
174
175 tcLookupClass name
176   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
177 --  pprTrace "tcLookupClass:" (ppCat [ppStr "Uniq:", pprUnique10 (uniqueOf name), ppStr "; avail:", ppCat (map (pprUnique10 . fst) (ufmToList ce))]) $
178 --  pprTrace "tcLookupClass:" (ppCat [ppStr "Uniq:", pprUnique (uniqueOf name), ppStr "; avail:", ppCat (map (pprUnique . fst) (ufmToList ce))]) $
179     returnNF_Tc (lookupWithDefaultUFM ce (pprPanic "tcLookupClass:" (ppr PprShowAll name)) name)
180
181 tcLookupClassByKey uniq
182   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
183     let
184         (kind, clas) = lookupWithDefaultUFM_Directly ce 
185                                 (pprPanic "tcLookupClassByKey:" (pprUnique10 uniq))
186                                 uniq
187     in
188     returnNF_Tc clas
189
190 tcGetTyConsAndClasses :: NF_TcM s ([TyCon], [Class])
191 tcGetTyConsAndClasses
192   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
193     returnNF_Tc ([tc | (_, _, tc) <- eltsUFM tce],
194                  [c  | (_, c)     <- eltsUFM ce])
195 \end{code}
196
197
198
199 Extending and consulting the value environment
200 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
201 \begin{code}
202 tcExtendGlobalValEnv ids scope
203   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
204     let
205         gve' = addListToUFM_Directly gve [(uniqueOf id, id) | id <- ids]
206     in
207     tcSetEnv (TcEnv tve tce ce gve' lve gtvs) scope
208
209 tcExtendLocalValEnv names ids scope
210   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
211     tcReadMutVar gtvs   `thenNF_Tc` \ global_tvs ->
212     let
213         lve' = addListToUFM lve (zipEqual "tcExtendLocalValEnv" names ids)
214         extra_global_tyvars = tyVarsOfTypes (map idType ids)
215         new_global_tyvars   = global_tvs `unionTyVarSets` extra_global_tyvars
216     in
217     tcNewMutVar new_global_tyvars       `thenNF_Tc` \ gtvs' ->
218
219     tcSetEnv (TcEnv tve tce ce gve lve' gtvs') scope
220 \end{code}
221
222 @tcGetGlobalTyVars@ returns a fully-zonked set of tyvars free in the environment.
223 To improve subsequent calls to the same function it writes the zonked set back into
224 the environment.
225
226 \begin{code}
227 tcGetGlobalTyVars :: NF_TcM s (TcTyVarSet s)
228 tcGetGlobalTyVars
229   = tcGetEnv                            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
230     tcReadMutVar gtvs                   `thenNF_Tc` \ global_tvs ->
231     zonkTcTyVars global_tvs             `thenNF_Tc` \ global_tvs' ->
232     tcWriteMutVar gtvs global_tvs'      `thenNF_Tc_`
233     returnNF_Tc global_tvs'
234
235 tcExtendGlobalTyVars extra_global_tvs scope
236   = tcGetEnv                            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
237     tcReadMutVar gtvs                   `thenNF_Tc` \ global_tvs ->
238     let
239         new_global_tyvars = global_tvs `unionTyVarSets` extra_global_tvs
240     in
241     tcNewMutVar new_global_tyvars       `thenNF_Tc` \ gtvs' ->
242     tcSetEnv (TcEnv tve tce ce gve lve gtvs') scope
243 \end{code}
244
245 \begin{code}
246 tcLookupLocalValue :: RnName -> NF_TcM s (Maybe (TcIdBndr s))
247 tcLookupLocalValue name
248   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
249     returnNF_Tc (lookupUFM lve name)
250
251 tcLookupLocalValueByKey :: Unique -> NF_TcM s (Maybe (TcIdBndr s))
252 tcLookupLocalValueByKey uniq
253   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
254     returnNF_Tc (lookupUFM_Directly lve uniq)
255
256 tcLookupLocalValueOK :: String -> RnName -> NF_TcM s (TcIdBndr s)
257 tcLookupLocalValueOK err name
258   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
259     returnNF_Tc (lookupWithDefaultUFM lve (panic err) name)
260
261
262 tcLookupGlobalValue :: RnName -> NF_TcM s Id
263
264 tcLookupGlobalValue (WiredInId id)      -- wired in ids
265   = returnNF_Tc id
266
267 tcLookupGlobalValue name
268   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
269     returnNF_Tc (lookupWithDefaultUFM gve def name)
270   where
271 #ifdef DEBUG
272     def = pprPanic "tcLookupGlobalValue:" (ppr PprDebug name)
273 #else
274     def = panic "tcLookupGlobalValue"
275 #endif
276
277 tcLookupGlobalValueByKey :: Unique -> NF_TcM s Id
278 tcLookupGlobalValueByKey uniq
279   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
280     returnNF_Tc (lookupWithDefaultUFM_Directly gve def uniq)
281   where
282 #ifdef DEBUG
283     def = pprPanic "tcLookupGlobalValueByKey:" (pprUnique10 uniq)
284 #else
285     def = panic "tcLookupGlobalValueByKey"
286 #endif
287
288 \end{code}
289
290
291 Constructing new Ids
292 ~~~~~~~~~~~~~~~~~~~~
293
294 \begin{code}
295 newMonoIds :: [RnName] -> Kind -> ([TcIdBndr s] -> TcM s a) -> TcM s a
296
297 newMonoIds names kind m
298   = newTyVarTys no_of_names kind        `thenNF_Tc` \ tys ->
299     tcGetUniques no_of_names            `thenNF_Tc` \ uniqs ->
300     let
301         new_ids = zipWith3Equal "newMonoIds" mk_id names uniqs tys
302
303         mk_id name uniq ty
304           = let
305                 name_str = case (getOccName name) of { Unqual n -> n; Qual m n -> n }
306             in
307             mkUserLocal name_str uniq ty (getSrcLoc name)
308     in
309     tcExtendLocalValEnv names new_ids (m new_ids)
310   where
311     no_of_names = length names
312
313 newLocalId :: FAST_STRING -> TcType s -> NF_TcM s (TcIdOcc s)
314 newLocalId name ty
315   = tcGetSrcLoc         `thenNF_Tc` \ loc ->
316     tcGetUnique         `thenNF_Tc` \ uniq ->
317     returnNF_Tc (TcId (mkUserLocal name uniq ty loc))
318
319 newLocalIds :: [FAST_STRING] -> [TcType s] -> NF_TcM s [TcIdOcc s]
320 newLocalIds names tys
321   = tcGetSrcLoc                 `thenNF_Tc` \ loc ->
322     tcGetUniques (length names) `thenNF_Tc` \ uniqs ->
323     let
324         new_ids            = zipWith3Equal "newLocalIds" mk_id names uniqs tys
325         mk_id name uniq ty = TcId (mkUserLocal name uniq ty loc)
326     in
327     returnNF_Tc new_ids
328 \end{code}
329
330