Skip to content

Commit

Permalink
Add some standard functions on state transformers
Browse files Browse the repository at this point in the history
  • Loading branch information
useronym committed Mar 13, 2018
1 parent ae1c193 commit 46d9769
Showing 1 changed file with 16 additions and 0 deletions.
16 changes: 16 additions & 0 deletions Control/Monad/Indexed/State.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE RecordWildCards #-}
-----------------------------------------------------------------------------
-- |
-- Module : Control.Monad.Indexed.State
Expand All @@ -16,6 +17,9 @@ module Control.Monad.Indexed.State
, igets
, IxStateT(..)
, IxState(..)
, lift
, evalIxStateT
, execIxStateT
) where

#if __GLASGOW_HASKELL__ < 709
Expand Down Expand Up @@ -90,6 +94,18 @@ instance IxMonadFix IxState where

newtype IxStateT m i j a = IxStateT { runIxStateT :: i -> m (a, j) }

-- | Lift a computation from the inner monad.
lift :: Monad m => m a -> IxStateT m i i a
lift ma = IxStateT $ (\i -> ma >>= \a -> return (a, i))

-- | Evaluate a computation in the monad from some initial state. Returns the resulting value.
evalIxStateT :: Monad m => IxStateT m i j a -> i -> m a
evalIxStateT IxStateT{..} i = runIxStateT i >>= return . fst

-- | Evaluate a computation in the monad from some initial state. Returns the final state.
execIxStateT :: Monad m => IxStateT m i j a -> i -> m j
execIxStateT IxStateT{..} i = runIxStateT i >>= return . snd

instance Monad m => Functor (IxStateT m i j) where
fmap = imap

Expand Down

0 comments on commit 46d9769

Please sign in to comment.