{-# LANGUAGE CPP #-}
#include "containers.h"
{-# OPTIONS_HADDOCK hide #-}
module Utils.Containers.Internal.State where
import Prelude hiding (
#if MIN_VERSION_base(4,8,0)
Applicative
#endif
)
import Control.Monad (ap)
import Control.Applicative (Applicative(..), liftA)
newtype State s a = State {forall s a. State s a -> s -> (s, a)
runState :: s -> (s, a)}
instance Functor (State s) where
fmap :: forall a b. (a -> b) -> State s a -> State s b
fmap = (a -> b) -> State s a -> State s b
forall (f :: * -> *) a b. Applicative f => (a -> b) -> f a -> f b
liftA
instance Monad (State s) where
{-# INLINE return #-}
{-# INLINE (>>=) #-}
return :: forall a. a -> State s a
return = a -> State s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
State s a
m >>= :: forall a b. State s a -> (a -> State s b) -> State s b
>>= a -> State s b
k = (s -> (s, b)) -> State s b
forall s a. (s -> (s, a)) -> State s a
State ((s -> (s, b)) -> State s b) -> (s -> (s, b)) -> State s b
forall a b. (a -> b) -> a -> b
$ \ s
s -> case State s a -> s -> (s, a)
forall s a. State s a -> s -> (s, a)
runState State s a
m s
s of
(s
s', a
x) -> State s b -> s -> (s, b)
forall s a. State s a -> s -> (s, a)
runState (a -> State s b
k a
x) s
s'
instance Applicative (State s) where
{-# INLINE pure #-}
pure :: forall a. a -> State s a
pure a
x = (s -> (s, a)) -> State s a
forall s a. (s -> (s, a)) -> State s a
State ((s -> (s, a)) -> State s a) -> (s -> (s, a)) -> State s a
forall a b. (a -> b) -> a -> b
$ \ s
s -> (s
s, a
x)
<*> :: forall a b. State s (a -> b) -> State s a -> State s b
(<*>) = State s (a -> b) -> State s a -> State s b
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
ap
execState :: State s a -> s -> a
execState :: forall s a. State s a -> s -> a
execState State s a
m s
x = (s, a) -> a
forall a b. (a, b) -> b
snd (State s a -> s -> (s, a)
forall s a. State s a -> s -> (s, a)
runState State s a
m s
x)