[project @ 1996-04-20 10:37:06 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, tyVarKind, 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           ( pprUnique10, pprUnique{-ToDo:rm-} )
45 import UniqFM        
46 import Util             ( zipWithEqual, zipWith3Equal, zipLazy, panic, pprPanic, pprTrace{-ToDo:rm-} )
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 (pprPanic "tcLookupTyVar:" (ppr PprShowAll name)) 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 (pprPanic "tcLookupTyCon:" (ppr PprShowAll name)) 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:" (pprUnique10 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 --  pprTrace "tcLookupClass:" (ppCat [ppStr "Uniq:", pprUnique10 (uniqueOf name), ppStr "; avail:", ppCat (map (pprUnique10 . fst) (ufmToList ce))]) $
176 --  pprTrace "tcLookupClass:" (ppCat [ppStr "Uniq:", pprUnique (uniqueOf name), ppStr "; avail:", ppCat (map (pprUnique . fst) (ufmToList ce))]) $
177     returnNF_Tc (lookupWithDefaultUFM ce (pprPanic "tcLookupClass:" (ppr PprShowAll name)) name)
178
179 tcLookupClassByKey uniq
180   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
181     let
182         (kind, clas) = lookupWithDefaultUFM_Directly ce 
183                                 (pprPanic "tcLookupClassByKey:" (pprUnique10 uniq))
184                                 uniq
185     in
186     returnNF_Tc clas
187 \end{code}
188
189
190
191 Extending and consulting the value environment
192 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
193 \begin{code}
194 tcExtendGlobalValEnv ids scope
195   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
196     let
197         gve' = addListToUFM_Directly gve [(uniqueOf id, id) | id <- ids]
198     in
199     tcSetEnv (TcEnv tve tce ce gve' lve gtvs) scope
200
201 tcExtendLocalValEnv names ids scope
202   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
203     tcReadMutVar gtvs   `thenNF_Tc` \ global_tvs ->
204     let
205         lve' = addListToUFM lve (names `zip` ids)
206         extra_global_tyvars = tyVarsOfTypes (map idType ids)
207         new_global_tyvars   = global_tvs `unionTyVarSets` extra_global_tyvars
208     in
209     tcNewMutVar new_global_tyvars       `thenNF_Tc` \ gtvs' ->
210
211     tcSetEnv (TcEnv tve tce ce gve lve' gtvs') scope
212 \end{code}
213
214 @tcGetGlobalTyVars@ returns a fully-zonked set of tyvars free in the environment.
215 To improve subsequent calls to the same function it writes the zonked set back into
216 the environment.
217
218 \begin{code}
219 tcGetGlobalTyVars :: NF_TcM s (TcTyVarSet s)
220 tcGetGlobalTyVars
221   = tcGetEnv                            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
222     tcReadMutVar gtvs                   `thenNF_Tc` \ global_tvs ->
223     zonkTcTyVars global_tvs             `thenNF_Tc` \ global_tvs' ->
224     tcWriteMutVar gtvs global_tvs'      `thenNF_Tc_`
225     returnNF_Tc global_tvs'
226 \end{code}
227
228 \begin{code}
229 tcLookupLocalValue :: RnName -> NF_TcM s (Maybe (TcIdBndr s))
230 tcLookupLocalValue name
231   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
232     returnNF_Tc (lookupUFM lve name)
233
234 tcLookupLocalValueByKey :: Unique -> NF_TcM s (Maybe (TcIdBndr s))
235 tcLookupLocalValueByKey uniq
236   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
237     returnNF_Tc (lookupUFM_Directly lve uniq)
238
239 tcLookupLocalValueOK :: String -> RnName -> NF_TcM s (TcIdBndr s)
240 tcLookupLocalValueOK err name
241   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
242     returnNF_Tc (lookupWithDefaultUFM lve (panic err) name)
243
244
245 tcLookupGlobalValue :: RnName -> NF_TcM s Id
246
247 tcLookupGlobalValue (WiredInId id)      -- wired in ids
248   = returnNF_Tc id
249
250 tcLookupGlobalValue name
251   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
252     returnNF_Tc (lookupWithDefaultUFM gve def name)
253   where
254 #ifdef DEBUG
255     def = pprPanic "tcLookupGlobalValue:" (ppr PprDebug name)
256 #else
257     def = panic "tcLookupGlobalValue"
258 #endif
259
260 tcLookupGlobalValueByKey :: Unique -> NF_TcM s Id
261 tcLookupGlobalValueByKey uniq
262   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
263     returnNF_Tc (lookupWithDefaultUFM_Directly gve def uniq)
264   where
265 #ifdef DEBUG
266     def = pprPanic "tcLookupGlobalValueByKey:" (pprUnique10 uniq)
267 #else
268     def = panic "tcLookupGlobalValueByKey"
269 #endif
270
271 \end{code}
272
273
274 Constructing new Ids
275 ~~~~~~~~~~~~~~~~~~~~
276
277 \begin{code}
278 newMonoIds :: [RnName] -> Kind -> ([TcIdBndr s] -> TcM s a) -> TcM s a
279
280 newMonoIds names kind m
281   = newTyVarTys no_of_names kind        `thenNF_Tc` \ tys ->
282     tcGetUniques no_of_names            `thenNF_Tc` \ uniqs ->
283     let
284         new_ids = zipWith3Equal mk_id names uniqs tys
285
286         mk_id name uniq ty
287           = let
288                 name_str = case (getOccName name) of { Unqual n -> n }
289             in
290             mkUserLocal name_str uniq ty (getSrcLoc name)
291     in
292     tcExtendLocalValEnv names new_ids (m new_ids)
293   where
294     no_of_names = length names
295
296 newLocalId :: FAST_STRING -> TcType s -> NF_TcM s (TcIdOcc s)
297 newLocalId name ty
298   = tcGetSrcLoc         `thenNF_Tc` \ loc ->
299     tcGetUnique         `thenNF_Tc` \ uniq ->
300     returnNF_Tc (TcId (mkUserLocal name uniq ty loc))
301
302 newLocalIds :: [FAST_STRING] -> [TcType s] -> NF_TcM s [TcIdOcc s]
303 newLocalIds names tys
304   = tcGetSrcLoc                 `thenNF_Tc` \ loc ->
305     tcGetUniques (length names) `thenNF_Tc` \ uniqs ->
306     let
307         new_ids            = zipWith3Equal mk_id names uniqs tys
308         mk_id name uniq ty = TcId (mkUserLocal name uniq ty loc)
309     in
310     returnNF_Tc new_ids
311 \end{code}
312
313