2 % (c) The University of Glasgow 2006
3 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
6 @DsMonad@: monadery used in desugaring
10 DsM, mapM, mapAndUnzipM,
11 initDs, initDsTc, fixDs,
12 foldlM, foldrM, ifOptM,
13 Applicative(..),(<$>),
16 duplicateLocalDs, newSysLocalDs, newSysLocalsDs, newUniqueId,
18 getSrcSpanDs, putSrcSpanDs,
21 UniqSupply, newUniqueSupply,
22 getDOptsDs, getGhcModeDs, doptDs,
23 dsLookupGlobal, dsLookupGlobalId, dsLookupTyCon, dsLookupDataCon,
26 DsMetaEnv, DsMetaVal(..), dsLookupMetaEnv, dsExtendMetaEnv,
29 DsWarning, warnDs, failWithDs,
33 EquationInfo(..), MatchResult(..), DsWrapper, idDsWrapper,
65 %************************************************************************
67 Data types for the desugarer
69 %************************************************************************
73 = DsMatchContext (HsMatchContext Name) SrcSpan
78 = EqnInfo { eqn_pats :: [Pat Id], -- The patterns for an eqn
79 eqn_rhs :: MatchResult } -- What to do after match
81 instance Outputable EquationInfo where
82 ppr (EqnInfo pats _) = ppr pats
84 type DsWrapper = CoreExpr -> CoreExpr
85 idDsWrapper :: DsWrapper
88 -- The semantics of (match vs (EqnInfo wrap pats rhs)) is the MatchResult
89 -- \fail. wrap (case vs of { pats -> rhs fail })
90 -- where vs are not bound by wrap
93 -- A MatchResult is an expression with a hole in it
96 CanItFail -- Tells whether the failure expression is used
97 (CoreExpr -> DsM CoreExpr)
98 -- Takes a expression to plug in at the
99 -- failure point(s). The expression should
102 data CanItFail = CanFail | CantFail
104 orFail :: CanItFail -> CanItFail -> CanItFail
105 orFail CantFail CantFail = CantFail
110 %************************************************************************
114 %************************************************************************
116 Now the mondo monad magic (yes, @DsM@ is a silly name)---carry around
117 a @UniqueSupply@ and some annotations, which
118 presumably include source-file location information:
120 type DsM result = TcRnIf DsGblEnv DsLclEnv result
122 -- Compatibility functions
123 fixDs :: (a -> DsM a) -> DsM a
126 type DsWarning = (SrcSpan, SDoc)
127 -- Not quite the same as a WarnMsg, we have an SDoc here
128 -- and we'll do the print_unqual stuff later on to turn it
131 data DsGblEnv = DsGblEnv {
132 ds_mod :: Module, -- For SCC profiling
133 ds_unqual :: PrintUnqualified,
134 ds_msgs :: IORef Messages, -- Warning messages
135 ds_if_env :: (IfGblEnv, IfLclEnv) -- Used for looking up global,
136 -- possibly-imported things
139 data DsLclEnv = DsLclEnv {
140 ds_meta :: DsMetaEnv, -- Template Haskell bindings
141 ds_loc :: SrcSpan -- to put in pattern-matching error msgs
144 -- Inside [| |] brackets, the desugarer looks
145 -- up variables in the DsMetaEnv
146 type DsMetaEnv = NameEnv DsMetaVal
149 = Bound Id -- Bound by a pattern inside the [| |].
150 -- Will be dynamically alpha renamed.
151 -- The Id has type THSyntax.Var
153 | Splice (HsExpr Id) -- These bindings are introduced by
154 -- the PendingSplices on a HsBracketOut
157 -> Module -> GlobalRdrEnv -> TypeEnv
160 -- Print errors and warnings, if any arise
162 initDs hsc_env mod rdr_env type_env thing_inside
163 = do { msg_var <- newIORef (emptyBag, emptyBag)
164 ; let dflags = hsc_dflags hsc_env
165 ; (ds_gbl_env, ds_lcl_env) <- mkDsEnvs dflags mod rdr_env type_env msg_var
167 ; either_res <- initTcRnIf 'd' hsc_env ds_gbl_env ds_lcl_env $
168 tryM thing_inside -- Catch exceptions (= errors during desugaring)
170 -- Display any errors and warnings
171 -- Note: if -Werror is used, we don't signal an error here.
172 ; msgs <- readIORef msg_var
173 ; printErrorsAndWarnings dflags msgs
175 ; let final_res | errorsFound dflags msgs = Nothing
176 | otherwise = case either_res of
177 Right res -> Just res
178 Left exn -> pprPanic "initDs" (text (show exn))
179 -- The (Left exn) case happens when the thing_inside throws
180 -- a UserError exception. Then it should have put an error
181 -- message in msg_var, so we just discard the exception
185 initDsTc :: DsM a -> TcM a
186 initDsTc thing_inside
187 = do { this_mod <- getModule
188 ; tcg_env <- getGblEnv
189 ; msg_var <- getErrsVar
191 ; let type_env = tcg_type_env tcg_env
192 rdr_env = tcg_rdr_env tcg_env
193 ; ds_envs <- liftIO $ mkDsEnvs dflags this_mod rdr_env type_env msg_var
194 ; setEnvs ds_envs thing_inside }
196 mkDsEnvs :: DynFlags -> Module -> GlobalRdrEnv -> TypeEnv -> IORef Messages -> IO (DsGblEnv, DsLclEnv)
197 mkDsEnvs dflags mod rdr_env type_env msg_var
198 = do -- TODO: unnecessarily monadic
199 let if_genv = IfGblEnv { if_rec_types = Just (mod, return type_env) }
200 if_lenv = mkIfLclEnv mod (ptext (sLit "GHC error in desugarer lookup in") <+> ppr mod)
201 gbl_env = DsGblEnv { ds_mod = mod,
202 ds_if_env = (if_genv, if_lenv),
203 ds_unqual = mkPrintUnqualified dflags rdr_env,
205 lcl_env = DsLclEnv { ds_meta = emptyNameEnv,
208 return (gbl_env, lcl_env)
211 %************************************************************************
213 Operations in the monad
215 %************************************************************************
217 And all this mysterious stuff is so we can occasionally reach out and
218 grab one or more names. @newLocalDs@ isn't exported---exported
219 functions are defined with it. The difference in name-strings makes
220 it easier to read debugging output.
223 -- Make a new Id with the same print name, but different type, and new unique
224 newUniqueId :: Name -> Type -> DsM Id
225 newUniqueId id = mkSysLocalM (occNameFS (nameOccName id))
227 duplicateLocalDs :: Id -> DsM Id
228 duplicateLocalDs old_local = do
230 return (setIdUnique old_local uniq)
232 newSysLocalDs, newFailLocalDs :: Type -> DsM Id
233 newSysLocalDs = mkSysLocalM (fsLit "ds")
234 newFailLocalDs = mkSysLocalM (fsLit "fail")
236 newSysLocalsDs :: [Type] -> DsM [Id]
237 newSysLocalsDs tys = mapM newSysLocalDs tys
240 We can also reach out and either set/grab location information from
241 the @SrcSpan@ being carried around.
244 getDOptsDs :: DsM DynFlags
245 getDOptsDs = getDOpts
247 doptDs :: DynFlag -> TcRnIf gbl lcl Bool
250 getGhcModeDs :: DsM GhcMode
251 getGhcModeDs = getDOptsDs >>= return . ghcMode
253 getModuleDs :: DsM Module
254 getModuleDs = do { env <- getGblEnv; return (ds_mod env) }
256 getSrcSpanDs :: DsM SrcSpan
257 getSrcSpanDs = do { env <- getLclEnv; return (ds_loc env) }
259 putSrcSpanDs :: SrcSpan -> DsM a -> DsM a
260 putSrcSpanDs new_loc thing_inside = updLclEnv (\ env -> env {ds_loc = new_loc}) thing_inside
262 warnDs :: SDoc -> DsM ()
263 warnDs warn = do { env <- getGblEnv
264 ; loc <- getSrcSpanDs
265 ; let msg = mkWarnMsg loc (ds_unqual env)
266 (ptext (sLit "Warning:") <+> warn)
267 ; updMutVar (ds_msgs env) (\ (w,e) -> (w `snocBag` msg, e)) }
269 failWithDs :: SDoc -> DsM a
271 = do { env <- getGblEnv
272 ; loc <- getSrcSpanDs
273 ; let msg = mkErrMsg loc (ds_unqual env) err
274 ; updMutVar (ds_msgs env) (\ (w,e) -> (w, e `snocBag` msg))
279 instance MonadThings (IOEnv (Env DsGblEnv DsLclEnv)) where
280 lookupThing = dsLookupGlobal
282 dsLookupGlobal :: Name -> DsM TyThing
283 -- Very like TcEnv.tcLookupGlobal
285 = do { env <- getGblEnv
286 ; setEnvs (ds_if_env env)
287 (tcIfaceGlobal name) }
289 dsLookupGlobalId :: Name -> DsM Id
290 dsLookupGlobalId name
291 = tyThingId <$> dsLookupGlobal name
293 dsLookupTyCon :: Name -> DsM TyCon
295 = tyThingTyCon <$> dsLookupGlobal name
297 dsLookupDataCon :: Name -> DsM DataCon
299 = tyThingDataCon <$> dsLookupGlobal name
301 dsLookupClass :: Name -> DsM Class
303 = tyThingClass <$> dsLookupGlobal name
307 dsLookupMetaEnv :: Name -> DsM (Maybe DsMetaVal)
308 dsLookupMetaEnv name = do { env <- getLclEnv; return (lookupNameEnv (ds_meta env) name) }
310 dsExtendMetaEnv :: DsMetaEnv -> DsM a -> DsM a
311 dsExtendMetaEnv menv thing_inside
312 = updLclEnv (\env -> env { ds_meta = ds_meta env `plusNameEnv` menv }) thing_inside