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