-- | -- Module: Control.ContStuff.Simple -- Copyright: (c) 2010 Ertugrul Soeylemez -- License: BSD3 -- Maintainer: Ertugrul Soeylemez -- Stability: experimental -- -- This module provides all the transformers from -- "Control.ContStuff.Trans", but with a simplified interface, hiding -- the underlying CPS machinery. {-# LANGUAGE RankNTypes, TypeFamilies #-} module Control.ContStuff.Simple ( -- * Choice/nondeterminism ChoiceT, choice, findAll, findAll_, findFirst, findFirst_, T.listA, listChoiceT, maybeChoiceT, -- * Exceptions EitherT, evalEitherT, testEitherT, MaybeT, evalMaybeT, testMaybeT, -- * Reader ReaderT, runReaderT, -- * State StateT, evalStateT, execStateT, -- * Writer WriterT, runWriterT, evalWriterT, execWriterT, -- * Reexports module Control.Applicative, module Control.ContStuff.Classes, module Control.Monad ) where import qualified Control.ContStuff.Trans as T import Control.Applicative import Control.ContStuff.Classes import Control.ContStuff.Instances () import Control.ContStuff.Trans (ReaderT, runReaderT) import Control.Monad import Data.Monoid ------------- -- ChoiceT -- ------------- type ChoiceT m a = forall r i. T.ChoiceT r i m a choice :: [a] -> ChoiceT m a choice xs = T.choice xs findAll :: (Alternative f, Applicative m) => ChoiceT m a -> m (f a) findAll c = T.findAll c findAll_ :: Applicative m => ChoiceT m a -> m () findAll_ c = T.findAll_ c findFirst :: (Alternative f, Applicative m) => ChoiceT m a -> m (f a) findFirst c = T.findFirst c findFirst_ :: Applicative m => ChoiceT m a -> m () findFirst_ c = T.findFirst_ c listChoiceT :: Applicative m => ChoiceT m a -> m [a] listChoiceT c = T.listChoiceT c maybeChoiceT :: Applicative m => ChoiceT m a -> m (Maybe a) maybeChoiceT c = T.maybeChoiceT c ------------- -- EitherT -- ------------- type EitherT e m a = forall r. T.EitherT r e m a evalEitherT :: Applicative m => EitherT e m a -> m (Either e a) evalEitherT c = T.evalEitherT c testEitherT :: Applicative m => EitherT e m a -> m Bool testEitherT c = T.testEitherT c ------------ -- MaybeT -- ------------ type MaybeT m a = forall r. T.MaybeT r m a evalMaybeT :: Applicative m => MaybeT m a -> m (Maybe a) evalMaybeT c = T.evalMaybeT c testMaybeT :: Applicative m => MaybeT m a -> m Bool testMaybeT c = T.testMaybeT c ------------ -- StateT -- ------------ type StateT s m a = forall r. T.StateT r s m a evalStateT :: Applicative m => s -> StateT s m a -> m a evalStateT s0 c = T.evalStateT s0 c execStateT :: Applicative m => s -> StateT s m a -> m s execStateT s0 c = T.execStateT s0 c ------------- -- WriterT -- ------------- type WriterT w m a = forall r. T.OldWriterT r w m a runWriterT :: (Applicative m, Monoid w) => WriterT w m a -> m (a, w) runWriterT c = T.runOldWriterT c evalWriterT :: (Applicative m, Monoid w) => WriterT w m a -> m a evalWriterT c = fmap fst . T.runOldWriterT $ c execWriterT :: (Applicative m, Monoid w) => WriterT w m a -> m w execWriterT c = fmap snd . T.runOldWriterT $ c