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