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