X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2FdeSugar%2FDsMonad.lhs;h=a83a1f4a7b44dedd2bcdff86979edd844f90d111;hb=c8208e89a8b71bf761cdf10b3416f0c1150b4f59;hp=bea0247f85be7e4f949a3cbd5cd9fbe129517ce8;hpb=ce3cab1dc3f3d03d43cf1b8cfc848c1ccaa00a84;p=ghc-hetmet.git diff --git a/ghc/compiler/deSugar/DsMonad.lhs b/ghc/compiler/deSugar/DsMonad.lhs index bea0247..a83a1f4 100644 --- a/ghc/compiler/deSugar/DsMonad.lhs +++ b/ghc/compiler/deSugar/DsMonad.lhs @@ -1,5 +1,5 @@ % -% (c) The GRASP/AQUA Project, Glasgow University, 1992-1996 +% (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 % \section[DsMonad]{@DsMonad@: monadery used in desugaring} @@ -13,34 +13,34 @@ module DsMonad ( duplicateLocalDs, newSysLocalDs, newSysLocalsDs, newFailLocalDs, getSrcLocDs, putSrcLocDs, - getModuleAndGroupDs, getUniqueDs, - extendEnvDs, lookupEnvDs, - DsIdEnv, + getModuleDs, + getUniqueDs, + getDOptsDs, + dsLookupGlobalValue, dsWarn, DsWarnings, - DsMatchContext(..), DsMatchKind(..), pprDsWarnings + DsMatchContext(..) ) where #include "HsVersions.h" -import Bag ( emptyBag, snocBag, bagToList, Bag ) -import BasicTypes ( Module ) +import HsSyn ( HsMatchContext ) +import Bag ( emptyBag, snocBag, Bag ) import ErrUtils ( WarnMsg ) -import HsSyn ( OutPat ) -import MkId ( mkSysLocal ) -import Id ( mkIdWithNewUniq, - lookupIdEnv, growIdEnvList, IdEnv, Id - ) +import Id ( mkSysLocal, setIdUnique, Id ) +import Module ( Module ) +import Var ( TyVar, setTyVarUnique ) import Outputable import SrcLoc ( noSrcLoc, SrcLoc ) import TcHsSyn ( TypecheckedPat ) import Type ( Type ) -import TyVar ( cloneTyVar, TyVar ) -import UniqSupply ( splitUniqSupply, getUnique, getUniques, +import UniqSupply ( initUs_, splitUniqSupply, uniqFromSupply, uniqsFromSupply, UniqSM, UniqSupply ) -import Unique ( Unique ) -import Util ( zipWithEqual, panic ) +import Unique ( Unique ) +import Util ( zipWithEqual ) +import Name ( Name ) +import CmdLineOpts ( DynFlags ) infixr 9 `thenDs` \end{code} @@ -50,49 +50,49 @@ a @UniqueSupply@ and some annotations, which presumably include source-file location information: \begin{code} type DsM result = - UniqSupply - -> SrcLoc -- to put in pattern-matching error msgs - -> (Module, Group) -- module + group name : for SCC profiling - -> DsIdEnv + DynFlags + -> UniqSupply + -> (Name -> Id) -- Lookup well-known Ids + -> SrcLoc -- to put in pattern-matching error msgs + -> Module -- module: for SCC profiling -> DsWarnings -> (result, DsWarnings) type DsWarnings = Bag WarnMsg -- The desugarer reports matches which are -- completely shadowed or incomplete patterns -type Group = FAST_STRING - {-# INLINE andDs #-} {-# INLINE thenDs #-} {-# INLINE returnDs #-} -- initDs returns the UniqSupply out the end (not just the result) -initDs :: UniqSupply - -> DsIdEnv - -> (Module, Group) -- module name: for profiling; (group name: from switches) +initDs :: DynFlags + -> UniqSupply + -> (Name -> Id) + -> Module -- module name: for profiling -> DsM a -> (a, DsWarnings) -initDs init_us env module_and_group action - = action init_us noSrcLoc module_and_group env emptyBag +initDs dflags init_us lookup mod action + = action dflags init_us lookup noSrcLoc mod emptyBag thenDs :: DsM a -> (a -> DsM b) -> DsM b andDs :: (a -> a -> a) -> DsM a -> DsM a -> DsM a -thenDs m1 m2 us loc mod_and_grp env warns +thenDs m1 m2 dflags us genv loc mod warns = case splitUniqSupply us of { (s1, s2) -> - case (m1 s1 loc mod_and_grp env warns) of { (result, warns1) -> - m2 result s2 loc mod_and_grp env warns1}} + case (m1 dflags s1 genv loc mod warns) of { (result, warns1) -> + m2 result dflags s2 genv loc mod warns1}} -andDs combiner m1 m2 us loc mod_and_grp env warns +andDs combiner m1 m2 dflags us genv loc mod warns = case splitUniqSupply us of { (s1, s2) -> - case (m1 s1 loc mod_and_grp env warns) of { (result1, warns1) -> - case (m2 s2 loc mod_and_grp env warns1) of { (result2, warns2) -> + case (m1 dflags s1 genv loc mod warns) of { (result1, warns1) -> + case (m2 dflags s2 genv loc mod warns1) of { (result2, warns2) -> (combiner result1 result2, warns2) }}} returnDs :: a -> DsM a -returnDs result us loc mod_and_grp env warns = (result, warns) +returnDs result dflags us genv loc mod warns = (result, warns) listDs :: [DsM a] -> DsM [a] listDs [] = returnDs [] @@ -115,7 +115,6 @@ foldlDs k z [] = returnDs z foldlDs k z (x:xs) = k z x `thenDs` \ r -> foldlDs k r xs - mapAndUnzipDs :: (a -> DsM (b, c)) -> [a] -> DsM ([b], [c]) mapAndUnzipDs f [] = returnDs ([], []) @@ -139,37 +138,44 @@ functions are defined with it. The difference in name-strings makes it easier to read debugging output. \begin{code} -newLocalDs :: FAST_STRING -> Type -> DsM Id -newLocalDs nm ty us loc mod_and_grp env warns - = case (getUnique us) of { assigned_uniq -> - (mkSysLocal nm assigned_uniq ty loc, warns) } +newSysLocalDs, newFailLocalDs :: Type -> DsM Id +newSysLocalDs ty dflags us genv loc mod warns + = case uniqFromSupply us of { assigned_uniq -> + (mkSysLocal SLIT("ds") assigned_uniq ty, warns) } + +newSysLocalsDs tys = mapDs newSysLocalDs tys -newSysLocalDs = newLocalDs SLIT("ds") -newSysLocalsDs tys = mapDs (newLocalDs SLIT("ds")) tys -newFailLocalDs = newLocalDs SLIT("fail") +newFailLocalDs ty dflags us genv loc mod warns + = case uniqFromSupply us of { assigned_uniq -> + (mkSysLocal SLIT("fail") assigned_uniq ty, warns) } + -- The UserLocal bit just helps make the code a little clearer getUniqueDs :: DsM Unique -getUniqueDs us loc mod_and_grp env warns - = case (getUnique us) of { assigned_uniq -> +getUniqueDs dflags us genv loc mod warns + = case (uniqFromSupply us) of { assigned_uniq -> (assigned_uniq, warns) } +getDOptsDs :: DsM DynFlags +getDOptsDs dflags us genv loc mod warns + = (dflags, warns) + duplicateLocalDs :: Id -> DsM Id -duplicateLocalDs old_local us loc mod_and_grp env warns - = case (getUnique us) of { assigned_uniq -> - (mkIdWithNewUniq old_local assigned_uniq, warns) } +duplicateLocalDs old_local dflags us genv loc mod warns + = case uniqFromSupply us of { assigned_uniq -> + (setIdUnique old_local assigned_uniq, warns) } cloneTyVarsDs :: [TyVar] -> DsM [TyVar] -cloneTyVarsDs tyvars us loc mod_and_grp env warns - = case (getUniques (length tyvars) us) of { uniqs -> - (zipWithEqual "cloneTyVarsDs" cloneTyVar tyvars uniqs, warns) } +cloneTyVarsDs tyvars dflags us genv loc mod warns + = case uniqsFromSupply (length tyvars) us of { uniqs -> + (zipWithEqual "cloneTyVarsDs" setTyVarUnique tyvars uniqs, warns) } \end{code} \begin{code} newTyVarsDs :: [TyVar] -> DsM [TyVar] -newTyVarsDs tyvar_tmpls us loc mod_and_grp env warns - = case (getUniques (length tyvar_tmpls) us) of { uniqs -> - (zipWithEqual "newTyVarsDs" cloneTyVar tyvar_tmpls uniqs, warns) } +newTyVarsDs tyvar_tmpls dflags us genv loc mod warns + = case uniqsFromSupply (length tyvar_tmpls) us of { uniqs -> + (zipWithEqual "newTyVarsDs" setTyVarUnique tyvar_tmpls uniqs, warns) } \end{code} We can also reach out and either set/grab location information from @@ -177,66 +183,43 @@ the @SrcLoc@ being carried around. \begin{code} uniqSMtoDsM :: UniqSM a -> DsM a -uniqSMtoDsM u_action us loc mod_and_grp env warns - = (u_action us, warns) +uniqSMtoDsM u_action dflags us genv loc mod warns + = (initUs_ us u_action, warns) getSrcLocDs :: DsM SrcLoc -getSrcLocDs us loc mod_and_grp env warns +getSrcLocDs dflags us genv loc mod warns = (loc, warns) putSrcLocDs :: SrcLoc -> DsM a -> DsM a -putSrcLocDs new_loc expr us old_loc mod_and_grp env warns - = expr us new_loc mod_and_grp env warns +putSrcLocDs new_loc expr dflags us genv old_loc mod warns + = expr dflags us genv new_loc mod warns dsWarn :: WarnMsg -> DsM () -dsWarn warn us loc mod_and_grp env warns = ((), warns `snocBag` warn) +dsWarn warn dflags us genv loc mod warns = ((), warns `snocBag` warn) \end{code} \begin{code} -getModuleAndGroupDs :: DsM (FAST_STRING, FAST_STRING) -getModuleAndGroupDs us loc mod_and_grp env warns - = (mod_and_grp, warns) +getModuleDs :: DsM Module +getModuleDs dflags us genv loc mod warns = (mod, warns) \end{code} \begin{code} -type DsIdEnv = IdEnv Id - -extendEnvDs :: [(Id, Id)] -> DsM a -> DsM a - -extendEnvDs pairs then_do us loc mod_and_grp old_env warns - = then_do us loc mod_and_grp (growIdEnvList old_env pairs) warns - -lookupEnvDs :: Id -> DsM Id -lookupEnvDs id us loc mod_and_grp env warns - = (case (lookupIdEnv env id) of - Nothing -> id - Just xx -> xx, - warns) +dsLookupGlobalValue :: Name -> DsM Id +dsLookupGlobalValue name dflags us genv loc mod warns + = (genv name, warns) \end{code} + %************************************************************************ %* * -%* type synonym EquationInfo and access functions for its pieces * +\subsection{Type synonym @EquationInfo@ and access functions for its pieces} %* * %************************************************************************ \begin{code} data DsMatchContext - = DsMatchContext DsMatchKind [TypecheckedPat] SrcLoc + = DsMatchContext HsMatchContext [TypecheckedPat] SrcLoc | NoMatchContext deriving () - -data DsMatchKind - = FunMatch Id - | CaseMatch - | LambdaMatch - | PatBindMatch - | DoBindMatch - | ListCompMatch - | LetMatch - deriving () - -pprDsWarnings :: DsWarnings -> SDoc -pprDsWarnings warns = vcat (bagToList warns) \end{code}