/compiler/utils/IOEnv.hs

https://github.com/pepeiborra/ghc · Haskell · 216 lines · 89 code · 53 blank · 74 comment · 2 complexity · 2317110fa4d8cf6da03701476f718c3f MD5 · raw file

  1. --
  2. -- (c) The University of Glasgow 2002-2006
  3. --
  4. -- The IO Monad with an environment
  5. --
  6. {-# LANGUAGE UndecidableInstances #-}
  7. module IOEnv (
  8. IOEnv, -- Instance of Monad
  9. -- Monad utilities
  10. module MonadUtils,
  11. -- Errors
  12. failM, failWithM,
  13. IOEnvFailure(..),
  14. -- Getting at the environment
  15. getEnv, setEnv, updEnv,
  16. runIOEnv, unsafeInterleaveM,
  17. tryM, tryAllM, tryMostM, fixM,
  18. -- I/O operations
  19. IORef, newMutVar, readMutVar, writeMutVar, updMutVar,
  20. atomicUpdMutVar, atomicUpdMutVar'
  21. ) where
  22. import Exception
  23. import Panic
  24. import Data.IORef ( IORef, newIORef, readIORef, writeIORef, modifyIORef,
  25. atomicModifyIORef )
  26. import Data.Typeable
  27. import System.IO.Unsafe ( unsafeInterleaveIO )
  28. import System.IO ( fixIO )
  29. import Control.Monad
  30. import MonadUtils
  31. ----------------------------------------------------------------------
  32. -- Defining the monad type
  33. ----------------------------------------------------------------------
  34. newtype IOEnv env a = IOEnv (env -> IO a)
  35. unIOEnv :: IOEnv env a -> (env -> IO a)
  36. unIOEnv (IOEnv m) = m
  37. instance Monad (IOEnv m) where
  38. (>>=) = thenM
  39. (>>) = thenM_
  40. return = returnM
  41. fail _ = failM -- Ignore the string
  42. instance Applicative (IOEnv m) where
  43. pure = returnM
  44. IOEnv f <*> IOEnv x = IOEnv (\ env -> f env <*> x env )
  45. instance Functor (IOEnv m) where
  46. fmap f (IOEnv m) = IOEnv (\ env -> fmap f (m env))
  47. returnM :: a -> IOEnv env a
  48. returnM a = IOEnv (\ _ -> return a)
  49. thenM :: IOEnv env a -> (a -> IOEnv env b) -> IOEnv env b
  50. thenM (IOEnv m) f = IOEnv (\ env -> do { r <- m env ;
  51. unIOEnv (f r) env })
  52. thenM_ :: IOEnv env a -> IOEnv env b -> IOEnv env b
  53. thenM_ (IOEnv m) f = IOEnv (\ env -> do { _ <- m env ; unIOEnv f env })
  54. failM :: IOEnv env a
  55. failM = IOEnv (\ _ -> throwIO IOEnvFailure)
  56. failWithM :: String -> IOEnv env a
  57. failWithM s = IOEnv (\ _ -> ioError (userError s))
  58. data IOEnvFailure = IOEnvFailure
  59. deriving Typeable
  60. instance Show IOEnvFailure where
  61. show IOEnvFailure = "IOEnv failure"
  62. instance Exception IOEnvFailure
  63. ----------------------------------------------------------------------
  64. -- Fundmantal combinators specific to the monad
  65. ----------------------------------------------------------------------
  66. ---------------------------
  67. runIOEnv :: env -> IOEnv env a -> IO a
  68. runIOEnv env (IOEnv m) = m env
  69. ---------------------------
  70. {-# NOINLINE fixM #-}
  71. -- Aargh! Not inlining fixTc alleviates a space leak problem.
  72. -- Normally fixTc is used with a lazy tuple match: if the optimiser is
  73. -- shown the definition of fixTc, it occasionally transforms the code
  74. -- in such a way that the code generator doesn't spot the selector
  75. -- thunks. Sigh.
  76. fixM :: (a -> IOEnv env a) -> IOEnv env a
  77. fixM f = IOEnv (\ env -> fixIO (\ r -> unIOEnv (f r) env))
  78. ---------------------------
  79. tryM :: IOEnv env r -> IOEnv env (Either IOEnvFailure r)
  80. -- Reflect UserError exceptions (only) into IOEnv monad
  81. -- Other exceptions are not caught; they are simply propagated as exns
  82. --
  83. -- The idea is that errors in the program being compiled will give rise
  84. -- to UserErrors. But, say, pattern-match failures in GHC itself should
  85. -- not be caught here, else they'll be reported as errors in the program
  86. -- begin compiled!
  87. tryM (IOEnv thing) = IOEnv (\ env -> tryIOEnvFailure (thing env))
  88. tryIOEnvFailure :: IO a -> IO (Either IOEnvFailure a)
  89. tryIOEnvFailure = try
  90. -- XXX We shouldn't be catching everything, e.g. timeouts
  91. tryAllM :: IOEnv env r -> IOEnv env (Either SomeException r)
  92. -- Catch *all* exceptions
  93. -- This is used when running a Template-Haskell splice, when
  94. -- even a pattern-match failure is a programmer error
  95. tryAllM (IOEnv thing) = IOEnv (\ env -> try (thing env))
  96. tryMostM :: IOEnv env r -> IOEnv env (Either SomeException r)
  97. tryMostM (IOEnv thing) = IOEnv (\ env -> tryMost (thing env))
  98. ---------------------------
  99. unsafeInterleaveM :: IOEnv env a -> IOEnv env a
  100. unsafeInterleaveM (IOEnv m) = IOEnv (\ env -> unsafeInterleaveIO (m env))
  101. ----------------------------------------------------------------------
  102. -- MonadPlus
  103. ----------------------------------------------------------------------
  104. -- For use if the user has imported Control.Monad.Error from MTL
  105. -- Requires UndecidableInstances
  106. instance MonadPlus IO => MonadPlus (IOEnv env) where
  107. mzero = IOEnv (const mzero)
  108. m `mplus` n = IOEnv (\env -> unIOEnv m env `mplus` unIOEnv n env)
  109. ----------------------------------------------------------------------
  110. -- Accessing input/output
  111. ----------------------------------------------------------------------
  112. instance MonadIO (IOEnv env) where
  113. liftIO io = IOEnv (\ _ -> io)
  114. newMutVar :: a -> IOEnv env (IORef a)
  115. newMutVar val = liftIO (newIORef val)
  116. writeMutVar :: IORef a -> a -> IOEnv env ()
  117. writeMutVar var val = liftIO (writeIORef var val)
  118. readMutVar :: IORef a -> IOEnv env a
  119. readMutVar var = liftIO (readIORef var)
  120. updMutVar :: IORef a -> (a -> a) -> IOEnv env ()
  121. updMutVar var upd = liftIO (modifyIORef var upd)
  122. -- | Atomically update the reference. Does not force the evaluation of the
  123. -- new variable contents. For strict update, use 'atomicUpdMutVar''.
  124. atomicUpdMutVar :: IORef a -> (a -> (a, b)) -> IOEnv env b
  125. atomicUpdMutVar var upd = liftIO (atomicModifyIORef var upd)
  126. -- | Strict variant of 'atomicUpdMutVar'.
  127. atomicUpdMutVar' :: IORef a -> (a -> (a, b)) -> IOEnv env b
  128. atomicUpdMutVar' var upd = do
  129. r <- atomicUpdMutVar var upd
  130. _ <- liftIO . evaluate =<< readMutVar var
  131. return r
  132. ----------------------------------------------------------------------
  133. -- Accessing the environment
  134. ----------------------------------------------------------------------
  135. getEnv :: IOEnv env env
  136. {-# INLINE getEnv #-}
  137. getEnv = IOEnv (\ env -> return env)
  138. -- | Perform a computation with a different environment
  139. setEnv :: env' -> IOEnv env' a -> IOEnv env a
  140. {-# INLINE setEnv #-}
  141. setEnv new_env (IOEnv m) = IOEnv (\ _ -> m new_env)
  142. -- | Perform a computation with an altered environment
  143. updEnv :: (env -> env') -> IOEnv env' a -> IOEnv env a
  144. {-# INLINE updEnv #-}
  145. updEnv upd (IOEnv m) = IOEnv (\ env -> m (upd env))
  146. ----------------------------------------------------------------------
  147. -- Standard combinators, but specialised for this monad
  148. -- (for efficiency)
  149. ----------------------------------------------------------------------
  150. -- {-# SPECIALIZE mapM :: (a -> IOEnv env b) -> [a] -> IOEnv env [b] #-}
  151. -- {-# SPECIALIZE mapM_ :: (a -> IOEnv env b) -> [a] -> IOEnv env () #-}
  152. -- {-# SPECIALIZE mapSndM :: (b -> IOEnv env c) -> [(a,b)] -> IOEnv env [(a,c)] #-}
  153. -- {-# SPECIALIZE sequence :: [IOEnv env a] -> IOEnv env [a] #-}
  154. -- {-# SPECIALIZE sequence_ :: [IOEnv env a] -> IOEnv env () #-}
  155. -- {-# SPECIALIZE foldlM :: (a -> b -> IOEnv env a) -> a -> [b] -> IOEnv env a #-}
  156. -- {-# SPECIALIZE foldrM :: (b -> a -> IOEnv env a) -> a -> [b] -> IOEnv env a #-}
  157. -- {-# SPECIALIZE mapAndUnzipM :: (a -> IOEnv env (b,c)) -> [a] -> IOEnv env ([b],[c]) #-}
  158. -- {-# SPECIALIZE mapAndUnzip3M :: (a -> IOEnv env (b,c,d)) -> [a] -> IOEnv env ([b],[c],[d]) #-}
  159. -- {-# SPECIALIZE zipWithM :: (a -> b -> IOEnv env c) -> [a] -> [b] -> IOEnv env [c] #-}
  160. -- {-# SPECIALIZE zipWithM_ :: (a -> b -> IOEnv env c) -> [a] -> [b] -> IOEnv env () #-}
  161. -- {-# SPECIALIZE anyM :: (a -> IOEnv env Bool) -> [a] -> IOEnv env Bool #-}
  162. -- {-# SPECIALIZE when :: Bool -> IOEnv env a -> IOEnv env () #-}
  163. -- {-# SPECIALIZE unless :: Bool -> IOEnv env a -> IOEnv env () #-}