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