878b83f699bdf34e5556f3659bf37b1f9178b840
[ghc-base.git] / Control / Monad / State.hs
1 -----------------------------------------------------------------------------
2 -- |
3 -- Module      :  Control.Monad.State
4 -- Copyright   :  (c) Andy Gill 2001,
5 --                (c) Oregon Graduate Institute of Science and Technology, 2001
6 -- License     :  BSD-style (see the file libraries/core/LICENSE)
7 -- 
8 -- Maintainer  :  libraries@haskell.org
9 -- Stability   :  experimental
10 -- Portability :  non-portable ( requires mulit-parameter type classes,
11 --                               requires functional dependencies )
12 --
13 -- State monads.
14 --
15 --        Inspired by the paper
16 --        \em{Functional Programming with Overloading and
17 --            Higher-Order Polymorphism},
18 --          \A[HREF="http://www.cse.ogi.edu/~mpj"]{Mark P Jones},
19 --                Advanced School of Functional Programming, 1995.}
20 -----------------------------------------------------------------------------
21
22 module Control.Monad.State (
23         MonadState(..),
24         modify,
25         gets,
26         State(..),
27         runState,
28         evalState,
29         execState,
30         mapState,
31         withState,
32         StateT(..),
33         runStateT,
34         evalStateT,
35         execStateT,
36         mapStateT,
37         withStateT,
38         module Control.Monad,
39         module Control.Monad.Fix,
40         module Control.Monad.Trans,
41   ) where
42
43 import Prelude
44
45 import Control.Monad
46 import Control.Monad.Fix
47 import Control.Monad.Trans
48 import Control.Monad.Reader
49 import Control.Monad.Writer
50
51 -- ---------------------------------------------------------------------------
52 -- MonadState class
53 --
54 --  get: returns the state from the internals of the monad.
55 --  put: changes (replaces) the state inside the monad.
56
57 class (Monad m) => MonadState s m | m -> s where
58         get :: m s
59         put :: s -> m ()
60
61 -- Monadic state transformer.
62 --
63 --      Maps an old state to a new state inside a state monad.
64 --      The old state is thrown away.}
65 --
66 --        Main> :t modify ((+1) :: Int -> Int)
67 --        modify (...) :: (MonadState Int a) => a ()
68 --
69 --      This says that modify (+1) acts over any
70 --      Monad that is a member of the MonadState class,
71 --      with an Int state.
72
73 modify :: (MonadState s m) => (s -> s) -> m ()
74 modify f = do
75         s <- get
76         put (f s)
77
78 -- Get part of the state
79 --
80 --      gets specific component of the state,
81 --      using a projection function supplied.
82         
83 gets :: (MonadState s m) => (s -> a) -> m a
84 gets f = do
85         s <- get
86         return (f s)
87
88 -- ---------------------------------------------------------------------------
89 -- Our parameterizable state monad
90
91 newtype State s a = State { runState :: s -> (a, s) }
92
93 -- The State Monad structure is paramterized over just the state.
94
95 instance Functor (State s) where
96         fmap f m = State $ \s -> let
97                 (a, s') = runState m s
98                 in (f a, s')
99
100 instance Monad (State s) where
101         return a = State $ \s -> (a, s)
102         m >>= k  = State $ \s -> let
103                 (a, s') = runState m s
104                 in runState (k a) s'
105
106 instance MonadFix (State s) where
107         mfix f = State $ \s -> let (a, s') = runState (f a) s in (a, s')
108
109 instance MonadState s (State s) where
110         get   = State $ \s -> (s, s)
111         put s = State $ \_ -> ((), s)
112
113
114 evalState :: State s a -> s -> a
115 evalState m s = fst (runState m s)
116
117 execState :: State s a -> s -> s
118 execState m s = snd (runState m s)
119
120 mapState :: ((a, s) -> (b, s)) -> State s a -> State s b
121 mapState f m = State $ f . runState m
122
123 withState :: (s -> s) -> State s a -> State s a
124 withState f m = State $ runState m . f
125
126 -- ---------------------------------------------------------------------------
127 -- Our parameterizable state monad, with an inner monad
128
129 newtype StateT s m a = StateT { runStateT :: s -> m (a,s) }
130
131 --The StateT Monad structure is parameterized over two things:
132 --
133 --   * s - The state.
134 --   * m - The inner monad.
135
136 -- Here are some examples of use:
137
138 -- (Parser from ParseLib with Hugs)
139 --   type Parser a = StateT String [] a
140 --      ==> StateT (String -> [(a,String)])
141 -- For example, item can be written as:
142 --      item = do (x:xs) <- get
143 --                put xs
144 --                return x
145
146 --   type BoringState s a = StateT s Indentity a
147 --      ==> StateT (s -> Identity (a,s))
148 --
149 --   type StateWithIO s a = StateT s IO a
150 --      ==> StateT (s -> IO (a,s))
151 --
152 --   type StateWithErr s a = StateT s Maybe a
153 --      ==> StateT (s -> Maybe (a,s))
154
155 instance (Monad m) => Functor (StateT s m) where
156         fmap f m = StateT $ \s -> do
157                 (x, s') <- runStateT m s
158                 return (f x, s')
159
160 instance (Monad m) => Monad (StateT s m) where
161         return a = StateT $ \s -> return (a, s)
162         m >>= k  = StateT $ \s -> do
163                 (a, s') <- runStateT m s
164                 runStateT (k a) s'
165         fail str = StateT $ \_ -> fail str
166
167 instance (MonadPlus m) => MonadPlus (StateT s m) where
168         mzero       = StateT $ \_ -> mzero
169         m `mplus` n = StateT $ \s -> runStateT m s `mplus` runStateT n s
170
171 instance (MonadFix m) => MonadFix (StateT s m) where
172         mfix f = StateT $ \s -> mfix $ \ ~(a, _) -> runStateT (f a) s
173
174 instance (Monad m) => MonadState s (StateT s m) where
175         get   = StateT $ \s -> return (s, s)
176         put s = StateT $ \_ -> return ((), s)
177
178 instance MonadTrans (StateT s) where
179         lift m = StateT $ \s -> do
180                 a <- m
181                 return (a, s)
182
183 instance (MonadIO m) => MonadIO (StateT s m) where
184         liftIO = lift . liftIO
185
186 instance (MonadReader r m) => MonadReader r (StateT s m) where
187         ask       = lift ask
188         local f m = StateT $ \s -> local f (runStateT m s)
189
190 instance (MonadWriter w m) => MonadWriter w (StateT s m) where
191         tell     = lift . tell
192         listen m = StateT $ \s -> do
193                 ((a, s'), w) <- listen (runStateT m s)
194                 return ((a, w), s')
195         pass   m = StateT $ \s -> pass $ do
196                 ((a, f), s') <- runStateT m s
197                 return ((a, s'), f)
198
199
200 evalStateT :: (Monad m) => StateT s m a -> s -> m a
201 evalStateT m s = do
202         (a, _) <- runStateT m s
203         return a
204
205 execStateT :: (Monad m) => StateT s m a -> s -> m s
206 execStateT m s = do
207         (_, s') <- runStateT m s
208         return s'
209
210 mapStateT :: (m (a, s) -> n (b, s)) -> StateT s m a -> StateT s n b
211 mapStateT f m = StateT $ f . runStateT m
212
213 withStateT :: (s -> s) -> StateT s m a -> StateT s m a
214 withStateT f m = StateT $ runStateT m . f
215
216 -- ---------------------------------------------------------------------------
217 -- MonadState instances for other monad transformers
218
219 instance (MonadState s m) => MonadState s (ReaderT r m) where
220         get = lift get
221         put = lift . put
222
223 instance (Monoid w, MonadState s m) => MonadState s (WriterT w m) where
224         get = lift get
225         put = lift . put