[project @ 1997-09-05 16:23:41 by simonpj]
[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         tcExtendTyVarEnv, tcLookupTyVar, 
10
11         tcExtendTyConEnv, tcLookupTyCon, tcLookupTyConByKey, 
12         tcExtendClassEnv, tcLookupClass, tcLookupClassByKey,
13         tcGetTyConsAndClasses,
14
15         tcExtendGlobalValEnv, tcExtendLocalValEnv,
16         tcLookupLocalValue, tcLookupLocalValueOK, tcLookupLocalValueByKey, 
17         tcLookupGlobalValue, tcLookupGlobalValueByKey, tcLookupGlobalValueMaybe,
18         tcAddImportedIdInfo, tcExplicitLookupGlobal,
19         tcLookupGlobalValueByKeyMaybe, 
20
21         newMonoIds, newLocalIds, newLocalId,
22         tcGetGlobalTyVars, tcExtendGlobalTyVars
23   ) where
24
25
26 IMP_Ubiq()
27 #if defined(__GLASGOW_HASKELL__) && __GLASGOW_HASKELL__ <= 201
28 IMPORT_DELOOPER(TcMLoop)  -- for paranoia checking
29 #endif
30
31 import HsTypes  ( HsTyVar(..) )
32 import Id       ( SYN_IE(Id), GenId, idType, mkUserLocal, mkUserId, replaceIdInfo, getIdInfo )
33 import PragmaInfo ( PragmaInfo(..) )
34 import TcKind   ( TcKind, newKindVars, newKindVar, tcDefaultKind, kindToTcKind, Kind )
35 import TcType   ( SYN_IE(TcIdBndr), TcIdOcc(..),
36                   SYN_IE(TcType), TcMaybe, SYN_IE(TcTyVar), SYN_IE(TcTyVarSet),
37                   newTyVarTys, tcInstTyVars, zonkTcTyVars
38                 )
39 import TyVar    ( unionTyVarSets, emptyTyVarSet, tyVarSetToList, SYN_IE(TyVar) )
40 import PprType  ( GenTyVar )
41 import Type     ( tyVarsOfTypes, splitForAllTy )
42 import TyCon    ( TyCon, tyConKind, tyConArity, isSynTyCon, SYN_IE(Arity) )
43 import Class    ( SYN_IE(Class), GenClass )
44
45 import TcMonad
46
47 import IdInfo           ( noIdInfo )
48 import Name             ( Name, OccName(..), getSrcLoc, occNameString,
49                           maybeWiredInTyConName, maybeWiredInIdName, isLocallyDefined,
50                           NamedThing(..)
51                         )
52 import Pretty
53 import Unique           ( pprUnique10{-, pprUnique ToDo:rm-}, Unique, Uniquable(..) )
54 import UniqFM        
55 import Util             ( zipEqual, zipWithEqual, zipWith3Equal, zipLazy,
56                           panic, pprPanic, pprTrace
57                         )
58 import Outputable
59 \end{code}
60
61 Data type declarations
62 ~~~~~~~~~~~~~~~~~~~~~
63
64 \begin{code}
65 data TcEnv s = TcEnv
66                   (TyVarEnv s)
67                   (TyConEnv s)
68                   (ClassEnv s)
69                   (ValueEnv Id)                 -- Globals
70                   (ValueEnv (TcIdBndr s))       -- Locals
71                   (MutableVar s (TcTyVarSet s)) -- Free type variables of locals
72                                                 -- ...why mutable? see notes with tcGetGlobalTyVars
73
74 type TyVarEnv s  = UniqFM (TcKind s, TyVar)
75 type TyConEnv s  = UniqFM (TcKind s, Maybe Arity, TyCon)        -- Arity present for Synonyms only
76 type ClassEnv s  = UniqFM (TcKind s, Class)
77 type ValueEnv id = UniqFM id
78
79 initEnv :: MutableVar s (TcTyVarSet s) -> TcEnv s
80 initEnv mut = TcEnv emptyUFM emptyUFM emptyUFM emptyUFM emptyUFM mut 
81
82 getEnv_LocalIds (TcEnv _ _ _ _ ls _) = eltsUFM ls
83 getEnv_TyCons   (TcEnv _ ts _ _ _ _) = [tycon | (_, _, tycon) <- eltsUFM ts]
84 getEnv_Classes  (TcEnv _ _ cs _ _ _) = [clas  | (_, clas)     <- eltsUFM cs]
85 \end{code}
86
87 Type variable env
88 ~~~~~~~~~~~~~~~~~
89 \begin{code}
90 tcExtendTyVarEnv :: [Name] -> [(TcKind s, TyVar)] -> TcM s r -> TcM s r
91 tcExtendTyVarEnv names kinds_w_types scope
92   = tcGetEnv                                    `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
93     let
94         tve' = addListToUFM tve (zipEqual "tcTyVarScope" names kinds_w_types)
95     in
96     tcSetEnv (TcEnv tve' tce ce gve lve gtvs) scope
97 \end{code}
98
99 The Kind, TyVar, Class and TyCon envs
100 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
101
102 Extending the environments.  Notice the uses of @zipLazy@, which makes sure
103 that the knot-tied TyVars, TyCons and Classes aren't looked at too early.
104
105 \begin{code}
106 tcExtendTyConEnv :: [(Name,Maybe Arity)] -> [TyCon] -> TcM s r -> TcM s r
107
108 tcExtendTyConEnv names_w_arities tycons scope
109   = newKindVars (length names_w_arities)        `thenNF_Tc` \ kinds ->
110     tcGetEnv                                    `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
111     let
112         tce' = addListToUFM tce [ (name, (kind, arity, tycon)) 
113                                 | ((name,arity), (kind,tycon))
114                                   <- zipEqual "tcExtendTyConEnv" names_w_arities (kinds `zipLazy` tycons)
115                                 ]
116     in
117     tcSetEnv (TcEnv tve tce' ce gve lve gtvs) scope     `thenTc` \ result ->
118     mapNF_Tc tcDefaultKind kinds                        `thenNF_Tc_`
119     returnTc result 
120
121
122 tcExtendClassEnv :: [Name] -> [Class] -> TcM s r -> TcM s r
123 tcExtendClassEnv names classes scope
124   = newKindVars (length names)  `thenNF_Tc` \ kinds ->
125     tcGetEnv                    `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
126     let
127         ce' = addListToUFM ce (zipEqual "tcExtendClassEnv" names (kinds `zipLazy` classes))
128     in
129     tcSetEnv (TcEnv tve tce ce' gve lve gtvs) scope     `thenTc` \ result ->
130     mapNF_Tc tcDefaultKind kinds                        `thenNF_Tc_`
131     returnTc result 
132 \end{code}
133
134
135 Looking up in the environments.
136
137 \begin{code}
138 tcLookupTyVar name
139   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
140     returnNF_Tc (lookupWithDefaultUFM tve (pprPanic "tcLookupTyVar:" (ppr PprShowAll name)) name)
141
142
143 tcLookupTyCon name
144   =     -- Try for a wired-in tycon
145     case maybeWiredInTyConName name of {
146         Just tc | isSynTyCon tc -> returnTc (kind, Just (tyConArity tc), tc)
147                 | otherwise     -> returnTc (kind, Nothing,              tc)
148                 where {
149                   kind = kindToTcKind (tyConKind tc) 
150                 };
151
152         Nothing -> 
153
154             -- Try in the environment
155           tcGetEnv      `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
156           case lookupUFM tce name of {
157               Just stuff -> returnTc stuff;
158
159               Nothing    ->
160
161                 -- Could be that he's using a class name as a type constructor
162                case lookupUFM ce name of
163                  Just _  -> failTc (classAsTyConErr name)
164                  Nothing -> pprPanic "tcLookupTyCon:" (ppr PprDebug name)
165             } } 
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 "tcLookupTyConByKey:" (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:" (hsep [text "Uniq:", pprUnique10 (uniqueOf name), text "; avail:", hsep (map (pprUnique10 . fst) (ufmToList ce))]) $
179 --  pprTrace "tcLookupClass:" (hsep [text "Uniq:", pprUnique (uniqueOf name), text "; avail:", hsep (map (pprUnique . fst) (ufmToList ce))]) $
180     case lookupUFM ce name of
181         Just stuff -> returnTc stuff
182         Nothing    ->   -- Could be that he's using a type constructor as a class
183                         case lookupUFM tce name of
184                           Just _ ->  failTc (tyConAsClassErr name)
185                           Nothing -> pprPanic "tcLookupClass:" (ppr PprShowAll name)
186
187 tcLookupClassByKey uniq
188   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
189     let
190         (kind, clas) = lookupWithDefaultUFM_Directly ce 
191                                 (pprPanic "tcLookupClassByKey:" (pprUnique10 uniq))
192                                 uniq
193     in
194     returnNF_Tc clas
195
196 tcGetTyConsAndClasses :: NF_TcM s ([TyCon], [Class])
197 tcGetTyConsAndClasses
198   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
199     returnNF_Tc ([tc | (_, _, tc) <- eltsUFM tce],
200                  [c  | (_, c)     <- eltsUFM ce])
201 \end{code}
202
203
204
205 Extending and consulting the value environment
206 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
207 \begin{code}
208 tcExtendGlobalValEnv ids scope
209   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
210     let
211         gve' = addListToUFM_Directly gve [(uniqueOf id, id) | id <- ids]
212     in
213     tcSetEnv (TcEnv tve tce ce gve' lve gtvs) scope
214
215 tcExtendLocalValEnv names ids scope
216   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
217     tcReadMutVar gtvs   `thenNF_Tc` \ global_tvs ->
218     let
219         lve' = addListToUFM lve (zipEqual "tcExtendLocalValEnv" names ids)
220         extra_global_tyvars = tyVarsOfTypes (map idType ids)
221         new_global_tyvars   = global_tvs `unionTyVarSets` extra_global_tyvars
222     in
223     tcNewMutVar new_global_tyvars       `thenNF_Tc` \ gtvs' ->
224
225     tcSetEnv (TcEnv tve tce ce gve lve' gtvs') scope
226 \end{code}
227
228 @tcGetGlobalTyVars@ returns a fully-zonked set of tyvars free in the environment.
229 To improve subsequent calls to the same function it writes the zonked set back into
230 the environment.
231
232 \begin{code}
233 tcGetGlobalTyVars :: NF_TcM s (TcTyVarSet s)
234 tcGetGlobalTyVars
235   = tcGetEnv                            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
236     tcReadMutVar gtvs                   `thenNF_Tc` \ global_tvs ->
237     zonkTcTyVars global_tvs             `thenNF_Tc` \ global_tvs' ->
238     tcWriteMutVar gtvs global_tvs'      `thenNF_Tc_` 
239     returnNF_Tc global_tvs'
240
241 tcExtendGlobalTyVars extra_global_tvs scope
242   = tcGetEnv                            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
243     tcReadMutVar gtvs                   `thenNF_Tc` \ global_tvs ->
244     let
245         new_global_tyvars = global_tvs `unionTyVarSets` extra_global_tvs
246     in
247     tcNewMutVar new_global_tyvars       `thenNF_Tc` \ gtvs' ->
248     tcSetEnv (TcEnv tve tce ce gve lve gtvs') scope
249 \end{code}
250
251 \begin{code}
252 tcLookupLocalValue :: Name -> NF_TcM s (Maybe (TcIdBndr s))
253 tcLookupLocalValue name
254   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
255     returnNF_Tc (lookupUFM lve name)
256
257 tcLookupLocalValueByKey :: Unique -> NF_TcM s (Maybe (TcIdBndr s))
258 tcLookupLocalValueByKey uniq
259   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
260     returnNF_Tc (lookupUFM_Directly lve uniq)
261
262 tcLookupLocalValueOK :: String -> Name -> NF_TcM s (TcIdBndr s)
263 tcLookupLocalValueOK err name
264   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
265     returnNF_Tc (lookupWithDefaultUFM lve (panic err) name)
266
267
268 tcLookupGlobalValue :: Name -> NF_TcM s Id
269 tcLookupGlobalValue name
270   = case maybeWiredInIdName name of
271         Just id -> returnNF_Tc id
272         Nothing -> tcGetEnv             `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
273                    returnNF_Tc (lookupWithDefaultUFM gve def name)
274   where
275     def = pprPanic "tcLookupGlobalValue:" (ppr PprDebug name)
276
277 tcLookupGlobalValueMaybe :: Name -> NF_TcM s (Maybe Id)
278 tcLookupGlobalValueMaybe name
279   = case maybeWiredInIdName name of
280         Just id -> returnNF_Tc (Just id)
281         Nothing -> tcGetEnv             `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
282                    returnNF_Tc (lookupUFM gve name)
283
284
285 tcLookupGlobalValueByKey :: Unique -> NF_TcM s Id
286 tcLookupGlobalValueByKey uniq
287   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
288     returnNF_Tc (lookupWithDefaultUFM_Directly gve def uniq)
289   where
290 #ifdef DEBUG
291     def = pprPanic "tcLookupGlobalValueByKey:" (pprUnique10 uniq)
292 #else
293     def = panic "tcLookupGlobalValueByKey"
294 #endif
295
296 tcLookupGlobalValueByKeyMaybe :: Unique -> NF_TcM s (Maybe Id)
297 tcLookupGlobalValueByKeyMaybe uniq
298   = tcGetEnv            `thenNF_Tc` \ (TcEnv tve tce ce gve lve gtvs) ->
299     returnNF_Tc (lookupUFM_Directly gve uniq)
300
301
302 -- Non-monadic version, environment given explicitly
303 tcExplicitLookupGlobal :: TcEnv s -> Name -> Maybe Id
304 tcExplicitLookupGlobal (TcEnv tve tce ce gve lve gtvs) name
305   = case maybeWiredInIdName name of
306         Just id -> Just id
307         Nothing -> lookupUFM gve name
308
309         -- Extract the IdInfo from an IfaceSig imported from an interface file
310 tcAddImportedIdInfo :: TcEnv s -> Id -> Id
311 tcAddImportedIdInfo unf_env id
312   | isLocallyDefined id         -- Don't look up locally defined Ids, because they
313                                 -- have explicit local definitions, so we get a black hole!
314   = id
315   | otherwise
316   = id `replaceIdInfo` new_info
317         -- The Id must be returned without a data dependency on maybe_id
318   where
319     new_info = -- pprTrace "tcAdd" (ppr PprDebug id) $
320                case tcExplicitLookupGlobal unf_env (getName id) of
321                      Nothing          -> noIdInfo
322                      Just imported_id -> getIdInfo imported_id
323                 -- ToDo: could check that types are the same
324 \end{code}
325
326
327 Constructing new Ids
328 ~~~~~~~~~~~~~~~~~~~~
329
330 \begin{code}
331 -- Uses the Name as the Name of the Id
332 newMonoIds :: [Name] -> Kind -> ([TcIdBndr s] -> TcM s a) -> TcM s a
333
334 newMonoIds names kind m
335   = newTyVarTys no_of_names kind        `thenNF_Tc` \ tys ->
336     let
337         new_ids       = zipWithEqual "newMonoIds" mk_id names tys
338         mk_id name ty = mkUserId name ty NoPragmaInfo
339     in
340     tcExtendLocalValEnv names new_ids (m new_ids)
341   where
342     no_of_names = length names
343
344 newLocalId :: OccName -> TcType s -> NF_TcM s (TcIdBndr s)
345 newLocalId name ty
346   = tcGetSrcLoc         `thenNF_Tc` \ loc ->
347     tcGetUnique         `thenNF_Tc` \ uniq ->
348     returnNF_Tc (mkUserLocal name uniq ty loc)
349
350 newLocalIds :: [OccName] -> [TcType s] -> NF_TcM s [TcIdBndr s]
351 newLocalIds names tys
352   = tcGetSrcLoc                 `thenNF_Tc` \ loc ->
353     tcGetUniques (length names) `thenNF_Tc` \ uniqs ->
354     let
355         new_ids            = zipWith3Equal "newLocalIds" mk_id names uniqs tys
356         mk_id name uniq ty = mkUserLocal name uniq ty loc
357     in
358     returnNF_Tc new_ids
359 \end{code}
360
361 \begin{code}
362 classAsTyConErr name sty
363   = hcat [ptext SLIT("Class used as a type constructor: "), ppr sty name]
364
365 tyConAsClassErr name sty
366   = hcat [ptext SLIT("Type constructor used as a class: "), ppr sty name]
367 \end{code}