module Control.Monad.Supply
( MonadSupply (..)
, SupplyT
, Supply
, evalSupplyT
, evalSupply
, runSupplyT
, runSupply
, supplies
) where
import Control.Monad.Identity
import Control.Monad.State
import Control.Monad.Error
import Control.Monad.Reader
import Control.Monad.Writer
class Monad m => MonadSupply s m | m -> s where
supply :: m s
peek :: m s
exhausted :: m Bool
newtype SupplyT s m a = SupplyT (StateT [s] m a)
deriving (Functor, Monad, MonadTrans, MonadIO)
newtype Supply s a = Supply (SupplyT s Identity a)
deriving (Functor, Monad, MonadSupply s)
instance Monad m => MonadSupply s (SupplyT s m) where
supply = SupplyT $ do (x:xs) <- get
put xs
return x
peek = SupplyT $ gets head
exhausted = SupplyT $ gets null
instance (Error e,MonadSupply s m) => MonadSupply s (ErrorT e m) where
supply = lift supply
peek = lift peek
exhausted = lift exhausted
instance MonadSupply s m => MonadSupply s (StateT st m) where
supply = lift supply
peek = lift peek
exhausted = lift exhausted
instance MonadSupply s m => MonadSupply s (ReaderT r m) where
supply = lift supply
peek = lift peek
exhausted = lift exhausted
instance (Monoid w, MonadSupply s m) => MonadSupply s (WriterT w m) where
supply = lift supply
peek = lift peek
exhausted = lift exhausted
instance (Monoid a) => Monoid (Supply s a) where
mempty = return mempty
m1 `mappend` m2 = do
x1 <- m1
x2 <- m2
return (x1 `mappend` x2)
supplies :: MonadSupply s m => Int -> m [s]
supplies n = replicateM n supply
evalSupplyT :: Monad m => SupplyT s m a -> [s] -> m a
evalSupplyT (SupplyT s) = evalStateT s
evalSupply :: Supply s a -> [s] -> a
evalSupply (Supply s) = runIdentity . evalSupplyT s
runSupplyT :: Monad m => SupplyT s m a -> [s] -> m (a,[s])
runSupplyT (SupplyT s) = runStateT s
runSupply :: Supply s a -> [s] -> (a,[s])
runSupply (Supply s) = runIdentity . runSupplyT s