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