X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2Futils%2FIOEnv.hs;h=1f1dd8fec40b361a7e4e4db5a6bd3f48299b7804;hp=9332a8b36378c2631c31dbe86ea9389817d479a0;hb=b2bd63f99d643f6b3eb30bb72bb9ae26d4183252;hpb=1f3a7730cd7f831344d2a3b74a0ce700c382e858 diff --git a/compiler/utils/IOEnv.hs b/compiler/utils/IOEnv.hs index 9332a8b..1f1dd8f 100644 --- a/compiler/utils/IOEnv.hs +++ b/compiler/utils/IOEnv.hs @@ -3,6 +3,7 @@ -- -- The IO Monad with an environment -- +{-# LANGUAGE UndecidableInstances #-} module IOEnv ( IOEnv, -- Instance of Monad @@ -12,6 +13,7 @@ module IOEnv ( -- Errors failM, failWithM, + IOEnvFailure(..), -- Getting at the environment getEnv, setEnv, updEnv, @@ -20,15 +22,19 @@ module IOEnv ( tryM, tryAllM, tryMostM, fixM, -- I/O operations - IORef, newMutVar, readMutVar, writeMutVar, updMutVar + IORef, newMutVar, readMutVar, writeMutVar, updMutVar, + atomicUpdMutVar, atomicUpdMutVar' ) where import Exception import Panic -import Data.IORef ( IORef, newIORef, readIORef, writeIORef, modifyIORef ) +import Data.IORef ( IORef, newIORef, readIORef, writeIORef, modifyIORef, + atomicModifyIORef ) +import Data.Typeable import System.IO.Unsafe ( unsafeInterleaveIO ) import System.IO ( fixIO ) +import Control.Monad import MonadUtils ---------------------------------------------------------------------- @@ -62,15 +68,21 @@ thenM (IOEnv m) f = IOEnv (\ env -> do { r <- m env ; unIOEnv (f r) env }) thenM_ :: IOEnv env a -> IOEnv env b -> IOEnv env b -thenM_ (IOEnv m) f = IOEnv (\ env -> do { m env ; unIOEnv f env }) +thenM_ (IOEnv m) f = IOEnv (\ env -> do { _ <- m env ; unIOEnv f env }) failM :: IOEnv env a -failM = IOEnv (\ _ -> ioError (userError "IOEnv failure")) +failM = IOEnv (\ _ -> throwIO IOEnvFailure) failWithM :: String -> IOEnv env a failWithM s = IOEnv (\ _ -> ioError (userError s)) +data IOEnvFailure = IOEnvFailure + deriving Typeable +instance Show IOEnvFailure where + show IOEnvFailure = "IOEnv failure" + +instance Exception IOEnvFailure ---------------------------------------------------------------------- -- Fundmantal combinators specific to the monad @@ -95,7 +107,7 @@ fixM f = IOEnv (\ env -> fixIO (\ r -> unIOEnv (f r) env)) --------------------------- -tryM :: IOEnv env r -> IOEnv env (Either IOException r) +tryM :: IOEnv env r -> IOEnv env (Either IOEnvFailure r) -- Reflect UserError exceptions (only) into IOEnv monad -- Other exceptions are not caught; they are simply propagated as exns -- @@ -103,7 +115,10 @@ tryM :: IOEnv env r -> IOEnv env (Either IOException r) -- to UserErrors. But, say, pattern-match failures in GHC itself should -- not be caught here, else they'll be reported as errors in the program -- begin compiled! -tryM (IOEnv thing) = IOEnv (\ env -> tryUser (thing env)) +tryM (IOEnv thing) = IOEnv (\ env -> tryIOEnvFailure (thing env)) + +tryIOEnvFailure :: IO a -> IO (Either IOEnvFailure a) +tryIOEnvFailure = try -- XXX We shouldn't be catching everything, e.g. timeouts tryAllM :: IOEnv env r -> IOEnv env (Either SomeException r) @@ -121,6 +136,16 @@ unsafeInterleaveM (IOEnv m) = IOEnv (\ env -> unsafeInterleaveIO (m env)) ---------------------------------------------------------------------- +-- MonadPlus +---------------------------------------------------------------------- + +-- For use if the user has imported Control.Monad.Error from MTL +-- Requires UndecidableInstances +instance MonadPlus IO => MonadPlus (IOEnv env) where + mzero = IOEnv (const mzero) + m `mplus` n = IOEnv (\env -> unIOEnv m env `mplus` unIOEnv n env) + +---------------------------------------------------------------------- -- Accessing input/output ---------------------------------------------------------------------- @@ -139,6 +164,17 @@ readMutVar var = liftIO (readIORef var) updMutVar :: IORef a -> (a -> a) -> IOEnv env () updMutVar var upd = liftIO (modifyIORef var upd) +-- | Atomically update the reference. Does not force the evaluation of the +-- new variable contents. For strict update, use 'atomicUpdMutVar''. +atomicUpdMutVar :: IORef a -> (a -> (a, b)) -> IOEnv env b +atomicUpdMutVar var upd = liftIO (atomicModifyIORef var upd) + +-- | Strict variant of 'atomicUpdMutVar'. +atomicUpdMutVar' :: IORef a -> (a -> (a, b)) -> IOEnv env b +atomicUpdMutVar' var upd = do + r <- atomicUpdMutVar var upd + _ <- liftIO . evaluate =<< readMutVar var + return r ---------------------------------------------------------------------- -- Accessing the environment