State.hs revision 3f69b6948966979163bdfe8331c38833d5d90ecd
0c27b3fe77ac1d5094ba3521e8142d9e7973133fMark Andrews{- |
ca44fe49bec16436cd95ace0af2e244f2096b284Brian WellingtonModule : $Header$
0c27b3fe77ac1d5094ba3521e8142d9e7973133fMark AndrewsDescription : State type from Control.Monad.State but no class MonadState
0c27b3fe77ac1d5094ba3521e8142d9e7973133fMark AndrewsCopyright : C. Maeder and Uni Bremen 2002-2005
0c27b3fe77ac1d5094ba3521e8142d9e7973133fMark AndrewsLicense : similar to LGPL, see HetCATS/LICENSE.txt or LIZENZ.txt
ca44fe49bec16436cd95ace0af2e244f2096b284Brian Wellington
70e5a7403f0e0a3bd292b8287c5fed5772c15270Automatic UpdaterMaintainer : Christian.Maeder@dfki.de
ca44fe49bec16436cd95ace0af2e244f2096b284Brian WellingtonStability : experimental
ca44fe49bec16436cd95ace0af2e244f2096b284Brian WellingtonPortability : portable
ca44fe49bec16436cd95ace0af2e244f2096b284Brian Wellington
ca44fe49bec16436cd95ace0af2e244f2096b284Brian WellingtonState type from Control.Monad.State but no class MonadState
ca44fe49bec16436cd95ace0af2e244f2096b284Brian Wellington
ca44fe49bec16436cd95ace0af2e244f2096b284Brian WellingtonThis module may be replaced by the (non-nhc98 module) Control.Monad.State
ca44fe49bec16436cd95ace0af2e244f2096b284Brian Wellington
ca44fe49bec16436cd95ace0af2e244f2096b284Brian Wellington-}
ca44fe49bec16436cd95ace0af2e244f2096b284Brian Wellington
ca44fe49bec16436cd95ace0af2e244f2096b284Brian Wellington
ca44fe49bec16436cd95ace0af2e244f2096b284Brian Wellingtonmodule Common.Lib.State where
ca44fe49bec16436cd95ace0af2e244f2096b284Brian Wellington
ca44fe49bec16436cd95ace0af2e244f2096b284Brian Wellington-- ---------------------------------------------------------------------------
ca44fe49bec16436cd95ace0af2e244f2096b284Brian Wellington-- Our fixed state monad
ca44fe49bec16436cd95ace0af2e244f2096b284Brian Wellingtonnewtype State s a = State { runState :: s -> (a, s) }
ca44fe49bec16436cd95ace0af2e244f2096b284Brian Wellington
ca44fe49bec16436cd95ace0af2e244f2096b284Brian Wellingtoninstance Functor (State s) where
ca44fe49bec16436cd95ace0af2e244f2096b284Brian Wellington fmap f m = State $ \s -> let
ca44fe49bec16436cd95ace0af2e244f2096b284Brian Wellington (a, s') = runState m s
ca44fe49bec16436cd95ace0af2e244f2096b284Brian Wellington in (f a, s')
ca44fe49bec16436cd95ace0af2e244f2096b284Brian Wellington
instance Monad (State s) where
return a = State $ \s -> (a, s)
m >>= k = State $ \s -> let
(a, s') = runState m s
in runState (k a) s'
-- put and get are non-overloaded here!
get :: State s s
get = State $ \s -> (s, s)
put :: s -> State s ()
put s = State $ \_ -> ((), s)
modify :: (s -> s) -> State s ()
modify f = get >>= put . f
gets :: (s -> a) -> State s a
gets f = fmap f get
evalState :: State s a -> s -> a
evalState m = fst . runState m
execState :: State s a -> s -> s
execState m = snd . runState m
mapState :: ((a, s) -> (b, s)) -> State s a -> State s b
mapState f m = State $ f . runState m
withState :: (s -> s) -> State s a -> State s a
withState f m = State $ runState m . f