in-other-words-0.2.1.1: A higher-order effect system where the sky's the limit
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Trans.List.Church

Documentation

newtype ListT (m :: Type -> Type) a Source #

Constructors

ListT 

Fields

  • unListT :: forall r. (a -> m r -> m r) -> m r -> m r -> m r
     

Instances

Instances details
MonadTrans ListT Source # 
Instance details

Defined in Control.Monad.Trans.List.Church

Methods

lift :: Monad m => m a -> ListT m a #

MonadBase b m => MonadBase b (ListT m) Source # 
Instance details

Defined in Control.Monad.Trans.List.Church

Methods

liftBase :: b α -> ListT m α #

Monoid s => ThreadsEff ListT (ListenPrim s) Source # 
Instance details

Defined in Control.Monad.Trans.List.Church

Methods

threadEff :: Monad m => (forall x. ListenPrim s m x -> m x) -> ListenPrim s (ListT m) a -> ListT m a Source #

ThreadsEff ListT (Regional s) Source # 
Instance details

Defined in Control.Monad.Trans.List.Church

Methods

threadEff :: Monad m => (forall x. Regional s m x -> m x) -> Regional s (ListT m) a -> ListT m a Source #

ThreadsEff ListT (ReaderPrim i) Source # 
Instance details

Defined in Control.Monad.Trans.List.Church

Methods

threadEff :: Monad m => (forall x. ReaderPrim i m x -> m x) -> ReaderPrim i (ListT m) a -> ListT m a Source #

Functor s => ThreadsEff ListT (Optional s) Source # 
Instance details

Defined in Control.Monad.Trans.List.Church

Methods

threadEff :: Monad m => (forall x. Optional s m x -> m x) -> Optional s (ListT m) a -> ListT m a Source #

ThreadsEff ListT (Unravel p) Source # 
Instance details

Defined in Control.Monad.Trans.List.Church

Methods

threadEff :: Monad m => (forall x. Unravel p m x -> m x) -> Unravel p (ListT m) a -> ListT m a Source #

Monoid s => ThreadsEff ListT (WriterPrim s) Source # 
Instance details

Defined in Control.Monad.Trans.List.Church

Methods

threadEff :: Monad m => (forall x. WriterPrim s m x -> m x) -> WriterPrim s (ListT m) a -> ListT m a Source #

Monad (ListT m) Source # 
Instance details

Defined in Control.Monad.Trans.List.Church

Methods

(>>=) :: ListT m a -> (a -> ListT m b) -> ListT m b #

(>>) :: ListT m a -> ListT m b -> ListT m b #

return :: a -> ListT m a #

Functor (ListT m) Source # 
Instance details

Defined in Control.Monad.Trans.List.Church

Methods

fmap :: (a -> b) -> ListT m a -> ListT m b #

(<$) :: a -> ListT m b -> ListT m a #

MonadFail m => MonadFail (ListT m) Source # 
Instance details

Defined in Control.Monad.Trans.List.Church

Methods

fail :: String -> ListT m a #

Applicative (ListT m) Source # 
Instance details

Defined in Control.Monad.Trans.List.Church

Methods

pure :: a -> ListT m a #

(<*>) :: ListT m (a -> b) -> ListT m a -> ListT m b #

liftA2 :: (a -> b -> c) -> ListT m a -> ListT m b -> ListT m c #

(*>) :: ListT m a -> ListT m b -> ListT m b #

(<*) :: ListT m a -> ListT m b -> ListT m a #

MonadIO m => MonadIO (ListT m) Source # 
Instance details

Defined in Control.Monad.Trans.List.Church

Methods

liftIO :: IO a -> ListT m a #

MonadThrow m => MonadThrow (ListT m) Source # 
Instance details

Defined in Control.Monad.Trans.List.Church

Methods

throwM :: Exception e => e -> ListT m a #

MonadCatch m => MonadCatch (ListT m) Source # 
Instance details

Defined in Control.Monad.Trans.List.Church

Methods

catch :: Exception e => ListT m a -> (e -> ListT m a) -> ListT m a #

cons :: a -> ListT m a -> ListT m a Source #

cull :: ListT m a -> ListT m a Source #

choose :: ListT m a -> ListT m a -> ListT m a Source #

call :: ListT m a -> ListT m a Source #

data LoseOrCutfail Source #

Constructors

Lost 
Cutfailed 

newtype LayeredListT m a Source #

Constructors

LayeredListT 

split :: Monad m => ListT m a -> ListT m (Maybe (a, ListT m a)) Source #

runListT :: (Alternative f, Monad m) => ListT m a -> m (f a) Source #