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