{-# LANGUAGE TupleSections #-} -- | Extend a monad with a modifiable environment module Mini.Transformers.StateT ( -- * Type StateT ( StateT ), -- * Runner runStateT, -- * Operations get, modify, put, ) where import Control.Applicative ( Alternative ( empty, (<|>) ), ) import Control.Monad ( ap, liftM, (>=>), ) import Mini.Transformers.Class ( MonadTrans ( lift ), ) {- - Type -} -- | A transformer with state /s/, inner monad /m/, return /a/ newtype StateT s m a = StateT { runStateT :: s -> m (a, s) -- ^ Unwrap a 'StateT' computation with an initial state } instance (Monad m) => Functor (StateT s m) where fmap = liftM instance (Monad m) => Applicative (StateT s m) where pure a = StateT $ pure . (a,) (<*>) = ap instance (Monad m, Alternative m) => Alternative (StateT s m) where empty = StateT $ const empty m <|> n = StateT $ \s -> runStateT m s <|> runStateT n s instance (Monad m) => Monad (StateT s m) where m >>= k = StateT $ runStateT m >=> (\(a, s) -> runStateT (k a) s) instance MonadTrans (StateT s) where lift m = StateT $ \s -> (,s) <$> m {- - Operations -} -- | Fetch the current state get :: (Monad m) => StateT s m s get = StateT $ \s -> pure (s, s) -- | Update the current state with an operation modify :: (Monad m) => (s -> s) -> StateT s m () modify f = StateT $ pure . ((),) . f -- | Overwrite the current state with a value put :: (Monad m) => s -> StateT s m () put = StateT . const . pure . ((),)