summaryrefslogtreecommitdiff
path: root/compiler/GHC/Data
diff options
context:
space:
mode:
authorArtem Pelenitsyn <a.pelenitsyn@gmail.com>2020-04-25 20:12:23 +0200
committerMarge Bot <ben+marge-bot@smart-cactus.org>2020-05-04 13:19:59 -0400
commit30272412fa437ab8e7a8035db94a278e10513413 (patch)
treeff6f602e294dca766b42f8177928894d0f1ca90b /compiler/GHC/Data
parent0bf640b19d7a7ad0800152752a71c1dd4e6c696d (diff)
downloadhaskell-30272412fa437ab8e7a8035db94a278e10513413.tar.gz
Remove custom ExceptionMonad class (#18075) (updating haddock submodule accordingly)
Diffstat (limited to 'compiler/GHC/Data')
-rw-r--r--compiler/GHC/Data/IOEnv.hs20
1 files changed, 6 insertions, 14 deletions
diff --git a/compiler/GHC/Data/IOEnv.hs b/compiler/GHC/Data/IOEnv.hs
index 86f16b229b..5478af0eee 100644
--- a/compiler/GHC/Data/IOEnv.hs
+++ b/compiler/GHC/Data/IOEnv.hs
@@ -1,5 +1,6 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveFunctor #-}
+{-# LANGUAGE DerivingVia #-}
--
-- (c) The University of Glasgow 2002-2006
--
@@ -43,6 +44,8 @@ import Data.IORef ( IORef, newIORef, readIORef, writeIORef, modifyIORef,
import System.IO.Unsafe ( unsafeInterleaveIO )
import System.IO ( fixIO )
import Control.Monad
+import Control.Monad.Trans.Reader
+import Control.Monad.Catch (MonadCatch, MonadMask, MonadThrow)
import GHC.Utils.Monad
import Control.Applicative (Alternative(..))
@@ -51,7 +54,9 @@ import Control.Applicative (Alternative(..))
----------------------------------------------------------------------
-newtype IOEnv env a = IOEnv (env -> IO a) deriving (Functor)
+newtype IOEnv env a = IOEnv (env -> IO a)
+ deriving (Functor)
+ deriving (MonadThrow, MonadCatch, MonadMask, MonadIO) via (ReaderT env IO)
unIOEnv :: IOEnv env a -> (env -> IO a)
unIOEnv (IOEnv m) = m
@@ -91,16 +96,6 @@ instance Show IOEnvFailure where
instance Exception IOEnvFailure
-instance ExceptionMonad (IOEnv a) where
- gcatch act handle =
- IOEnv $ \s -> unIOEnv act s `gcatch` \e -> unIOEnv (handle e) s
- gmask f =
- IOEnv $ \s -> gmask $ \io_restore ->
- let
- g_restore (IOEnv m) = IOEnv $ \s -> io_restore (m s)
- in
- unIOEnv (f g_restore) s
-
instance ContainsDynFlags env => HasDynFlags (IOEnv env) where
getDynFlags = do env <- getEnv
return $! extractDynFlags env
@@ -176,9 +171,6 @@ instance MonadPlus (IOEnv env)
-- Accessing input/output
----------------------------------------------------------------------
-instance MonadIO (IOEnv env) where
- liftIO io = IOEnv (\ _ -> io)
-
newMutVar :: a -> IOEnv env (IORef a)
newMutVar val = liftIO (newIORef val)