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