[project @ 2004-09-30 10:35:15 by simonpj]
[ghc-hetmet.git] / ghc / compiler / deSugar / DsMonad.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
3 %
4 \section[DsMonad]{@DsMonad@: monadery used in desugaring}
5
6 \begin{code}
7 module DsMonad (
8         DsM, mappM,
9         initDs, returnDs, thenDs, listDs, fixDs, mapAndUnzipDs, foldlDs,
10
11         newTyVarsDs, 
12         duplicateLocalDs, newSysLocalDs, newSysLocalsDs, newUniqueId,
13         newFailLocalDs,
14         getSrcSpanDs, putSrcSpanDs,
15         getModuleDs,
16         newUnique, 
17         UniqSupply, newUniqueSupply,
18         getDOptsDs,
19         dsLookupGlobal, dsLookupGlobalId, dsLookupTyCon, dsLookupDataCon,
20
21         DsMetaEnv, DsMetaVal(..), dsLookupMetaEnv, dsExtendMetaEnv,
22
23         dsWarn, 
24         DsWarning,
25         DsMatchContext(..)
26     ) where
27
28 #include "HsVersions.h"
29
30 import TcRnMonad
31 import HsSyn            ( HsExpr, HsMatchContext, Pat )
32 import TcIface          ( tcIfaceGlobal )
33 import HscTypes         ( TyThing(..), TypeEnv, HscEnv, 
34                           tyThingId, tyThingTyCon, tyThingDataCon  )
35 import Bag              ( emptyBag, snocBag, Bag )
36 import DataCon          ( DataCon )
37 import TyCon            ( TyCon )
38 import DataCon          ( DataCon )
39 import Id               ( mkSysLocal, setIdUnique, Id )
40 import Module           ( Module )
41 import Var              ( TyVar, setTyVarUnique )
42 import Outputable
43 import SrcLoc           ( noSrcSpan, SrcSpan )
44 import Type             ( Type )
45 import UniqSupply       ( UniqSupply, uniqsFromSupply )
46 import Name             ( Name, nameOccName )
47 import NameEnv
48 import OccName          ( occNameFS )
49 import CmdLineOpts      ( DynFlags )
50
51 import DATA_IOREF       ( newIORef, readIORef )
52
53 infixr 9 `thenDs`
54 \end{code}
55
56 Now the mondo monad magic (yes, @DsM@ is a silly name)---carry around
57 a @UniqueSupply@ and some annotations, which
58 presumably include source-file location information:
59 \begin{code}
60 type DsM result = TcRnIf DsGblEnv DsLclEnv result
61
62 -- Compatibility functions
63 fixDs    = fixM
64 thenDs   = thenM
65 returnDs = returnM
66 listDs   = sequenceM
67 foldlDs  = foldlM
68 mapAndUnzipDs = mapAndUnzipM
69
70
71 type DsWarning = (SrcSpan, SDoc)
72         -- Not quite the same as a WarnMsg, we have an SDoc here 
73         -- and we'll do the print_unqual stuff later on to turn it
74         -- into a Doc.
75
76 data DsGblEnv = DsGblEnv {
77         ds_mod     :: Module,                   -- For SCC profiling
78         ds_warns   :: IORef (Bag DsWarning),    -- Warning messages
79         ds_if_env  :: IfGblEnv                  -- Used for looking up global, 
80                                                 -- possibly-imported things
81     }
82
83 data DsLclEnv = DsLclEnv {
84         ds_meta    :: DsMetaEnv,        -- Template Haskell bindings
85         ds_loc     :: SrcSpan           -- to put in pattern-matching error msgs
86      }
87
88 -- Inside [| |] brackets, the desugarer looks 
89 -- up variables in the DsMetaEnv
90 type DsMetaEnv = NameEnv DsMetaVal
91
92 data DsMetaVal
93    = Bound Id           -- Bound by a pattern inside the [| |]. 
94                         -- Will be dynamically alpha renamed.
95                         -- The Id has type THSyntax.Var
96
97    | Splice (HsExpr Id) -- These bindings are introduced by
98                         -- the PendingSplices on a HsBracketOut
99
100 -- initDs returns the UniqSupply out the end (not just the result)
101
102 initDs  :: HscEnv
103         -> Module -> TypeEnv
104         -> DsM a
105         -> IO (a, Bag DsWarning)
106
107 initDs hsc_env mod type_env thing_inside
108   = do  { warn_var <- newIORef emptyBag
109         ; let { if_env = IfGblEnv { if_rec_types = Just (mod, return type_env) }
110               ; gbl_env = DsGblEnv { ds_mod = mod, 
111                                      ds_if_env = if_env, 
112                                      ds_warns = warn_var }
113               ; lcl_env = DsLclEnv { ds_meta = emptyNameEnv, 
114                                      ds_loc = noSrcSpan } }
115
116         ; res <- initTcRnIf 'd' hsc_env gbl_env lcl_env thing_inside
117
118         ; warns <- readIORef warn_var
119         ; return (res, warns)
120         }
121 \end{code}
122
123 And all this mysterious stuff is so we can occasionally reach out and
124 grab one or more names.  @newLocalDs@ isn't exported---exported
125 functions are defined with it.  The difference in name-strings makes
126 it easier to read debugging output.
127
128 \begin{code}
129 -- Make a new Id with the same print name, but different type, and new unique
130 newUniqueId :: Name -> Type -> DsM Id
131 newUniqueId id ty
132   = newUnique   `thenDs` \ uniq ->
133     returnDs (mkSysLocal (occNameFS (nameOccName id)) uniq ty)
134
135 duplicateLocalDs :: Id -> DsM Id
136 duplicateLocalDs old_local 
137   = newUnique   `thenDs` \ uniq ->
138     returnDs (setIdUnique old_local uniq)
139
140 newSysLocalDs, newFailLocalDs :: Type -> DsM Id
141 newSysLocalDs ty
142   = newUnique   `thenDs` \ uniq ->
143     returnDs (mkSysLocal FSLIT("ds") uniq ty)
144
145 newSysLocalsDs tys = mappM newSysLocalDs tys
146
147 newFailLocalDs ty 
148   = newUnique   `thenDs` \ uniq ->
149     returnDs (mkSysLocal FSLIT("fail") uniq ty)
150         -- The UserLocal bit just helps make the code a little clearer
151 \end{code}
152
153 \begin{code}
154 newTyVarsDs :: [TyVar] -> DsM [TyVar]
155 newTyVarsDs tyvar_tmpls 
156   = newUniqueSupply     `thenDs` \ uniqs ->
157     returnDs (zipWith setTyVarUnique tyvar_tmpls (uniqsFromSupply uniqs))
158 \end{code}
159
160 We can also reach out and either set/grab location information from
161 the @SrcSpan@ being carried around.
162
163 \begin{code}
164 getDOptsDs :: DsM DynFlags
165 getDOptsDs = getDOpts
166
167 getModuleDs :: DsM Module
168 getModuleDs = do { env <- getGblEnv; return (ds_mod env) }
169
170 getSrcSpanDs :: DsM SrcSpan
171 getSrcSpanDs = do { env <- getLclEnv; return (ds_loc env) }
172
173 putSrcSpanDs :: SrcSpan -> DsM a -> DsM a
174 putSrcSpanDs new_loc thing_inside = updLclEnv (\ env -> env {ds_loc = new_loc}) thing_inside
175
176 dsWarn :: DsWarning -> DsM ()
177 dsWarn (loc,warn) = do { env <- getGblEnv; updMutVar (ds_warns env) (`snocBag` (loc,msg)) }
178             where
179               msg = ptext SLIT("Warning:") <+> warn
180 \end{code}
181
182 \begin{code}
183 dsLookupGlobal :: Name -> DsM TyThing
184 -- Very like TcEnv.tcLookupGlobal
185 dsLookupGlobal name 
186   = do  { env <- getGblEnv
187         ; setEnvs (ds_if_env env, ())
188                   (tcIfaceGlobal name) }
189
190 dsLookupGlobalId :: Name -> DsM Id
191 dsLookupGlobalId name 
192   = dsLookupGlobal name         `thenDs` \ thing ->
193     returnDs (tyThingId thing)
194
195 dsLookupTyCon :: Name -> DsM TyCon
196 dsLookupTyCon name
197   = dsLookupGlobal name         `thenDs` \ thing ->
198     returnDs (tyThingTyCon thing)
199
200 dsLookupDataCon :: Name -> DsM DataCon
201 dsLookupDataCon name
202   = dsLookupGlobal name         `thenDs` \ thing ->
203     returnDs (tyThingDataCon thing)
204 \end{code}
205
206 \begin{code}
207 dsLookupMetaEnv :: Name -> DsM (Maybe DsMetaVal)
208 dsLookupMetaEnv name = do { env <- getLclEnv; return (lookupNameEnv (ds_meta env) name) }
209
210 dsExtendMetaEnv :: DsMetaEnv -> DsM a -> DsM a
211 dsExtendMetaEnv menv thing_inside
212   = updLclEnv (\env -> env { ds_meta = ds_meta env `plusNameEnv` menv }) thing_inside
213 \end{code}
214
215
216 %************************************************************************
217 %*                                                                      *
218 \subsection{Type synonym @EquationInfo@ and access functions for its pieces}
219 %*                                                                      *
220 %************************************************************************
221
222 \begin{code}
223 data DsMatchContext
224   = DsMatchContext (HsMatchContext Name) [Pat Id] SrcSpan
225   | NoMatchContext
226   deriving ()
227 \end{code}