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