selective-0.7: Selective applicative functors
Copyright(c) Andrey Mokhov 2018-2023
LicenseMIT (see the file LICENSE)
Maintainerandrey.mokhov@gmail.com
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Selective.Trans.Except

Description

This is a library for selective applicative functors, or just selective functors for short, an abstraction between applicative functors and monads, introduced in this paper: https://www.staff.ncl.ac.uk/andrey.mokhov/selective-functors.pdf.

This module defines a newtype around ExceptT from transformers with less restrictive Applicative, Selective, and Alternative implementations. It supplies an instance Selective f => Selective (ExceptT e f), which makes ExceptT a bona-fide Selective transformer.

The API follows the API from the transformers package, so it can be used as a drop-in replacement. The documentation can be found in the transformers package.

Synopsis

Documentation

newtype ExceptT e f a Source #

A newtype wrapper around ExceptT from transformers that provides less restrictive Applicative, Selective and Alternative instances.

Constructors

ExceptT 

Fields

Instances

Instances details
(Selective f, MonadFail f) => MonadFail (ExceptT e f) Source # 
Instance details

Defined in Control.Selective.Trans.Except

Methods

fail :: String -> ExceptT e f a #

(Selective f, MonadFix f) => MonadFix (ExceptT e f) Source # 
Instance details

Defined in Control.Selective.Trans.Except

Methods

mfix :: (a -> ExceptT e f a) -> ExceptT e f a #

(Selective f, MonadIO f) => MonadIO (ExceptT e f) Source # 
Instance details

Defined in Control.Selective.Trans.Except

Methods

liftIO :: IO a -> ExceptT e f a #

(Selective f, MonadZip f) => MonadZip (ExceptT e f) Source # 
Instance details

Defined in Control.Selective.Trans.Except

Methods

mzip :: ExceptT e f a -> ExceptT e f b -> ExceptT e f (a, b) #

mzipWith :: (a -> b -> c) -> ExceptT e f a -> ExceptT e f b -> ExceptT e f c #

munzip :: ExceptT e f (a, b) -> (ExceptT e f a, ExceptT e f b) #

Foldable f => Foldable (ExceptT e f) Source # 
Instance details

Defined in Control.Selective.Trans.Except

Methods

fold :: Monoid m => ExceptT e f m -> m #

foldMap :: Monoid m => (a -> m) -> ExceptT e f a -> m #

foldMap' :: Monoid m => (a -> m) -> ExceptT e f a -> m #

foldr :: (a -> b -> b) -> b -> ExceptT e f a -> b #

foldr' :: (a -> b -> b) -> b -> ExceptT e f a -> b #

foldl :: (b -> a -> b) -> b -> ExceptT e f a -> b #

foldl' :: (b -> a -> b) -> b -> ExceptT e f a -> b #

foldr1 :: (a -> a -> a) -> ExceptT e f a -> a #

foldl1 :: (a -> a -> a) -> ExceptT e f a -> a #

toList :: ExceptT e f a -> [a] #

null :: ExceptT e f a -> Bool #

length :: ExceptT e f a -> Int #

elem :: Eq a => a -> ExceptT e f a -> Bool #

maximum :: Ord a => ExceptT e f a -> a #

minimum :: Ord a => ExceptT e f a -> a #

sum :: Num a => ExceptT e f a -> a #

product :: Num a => ExceptT e f a -> a #

(Eq e, Eq1 f) => Eq1 (ExceptT e f) Source # 
Instance details

Defined in Control.Selective.Trans.Except

Methods

liftEq :: (a -> b -> Bool) -> ExceptT e f a -> ExceptT e f b -> Bool #

(Ord e, Ord1 f) => Ord1 (ExceptT e f) Source # 
Instance details

Defined in Control.Selective.Trans.Except

Methods

liftCompare :: (a -> b -> Ordering) -> ExceptT e f a -> ExceptT e f b -> Ordering #

(Read e, Read1 f) => Read1 (ExceptT e f) Source # 
Instance details

Defined in Control.Selective.Trans.Except

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (ExceptT e f a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [ExceptT e f a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (ExceptT e f a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [ExceptT e f a] #

(Show e, Show1 f) => Show1 (ExceptT e f) Source # 
Instance details

Defined in Control.Selective.Trans.Except

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> ExceptT e f a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [ExceptT e f a] -> ShowS #

Contravariant f => Contravariant (ExceptT e f) Source # 
Instance details

Defined in Control.Selective.Trans.Except

Methods

contramap :: (a' -> a) -> ExceptT e f a -> ExceptT e f a' #

(>$) :: b -> ExceptT e f b -> ExceptT e f a #

Traversable f => Traversable (ExceptT e f) Source # 
Instance details

Defined in Control.Selective.Trans.Except

Methods

traverse :: Applicative f0 => (a -> f0 b) -> ExceptT e f a -> f0 (ExceptT e f b) #

sequenceA :: Applicative f0 => ExceptT e f (f0 a) -> f0 (ExceptT e f a) #

mapM :: Monad m => (a -> m b) -> ExceptT e f a -> m (ExceptT e f b) #

sequence :: Monad m => ExceptT e f (m a) -> m (ExceptT e f a) #

(Selective f, Monoid e) => Alternative (ExceptT e f) Source # 
Instance details

Defined in Control.Selective.Trans.Except

Methods

empty :: ExceptT e f a #

(<|>) :: ExceptT e f a -> ExceptT e f a -> ExceptT e f a #

some :: ExceptT e f a -> ExceptT e f [a] #

many :: ExceptT e f a -> ExceptT e f [a] #

Selective f => Applicative (ExceptT e f) Source # 
Instance details

Defined in Control.Selective.Trans.Except

Methods

pure :: a -> ExceptT e f a #

(<*>) :: ExceptT e f (a -> b) -> ExceptT e f a -> ExceptT e f b #

liftA2 :: (a -> b -> c) -> ExceptT e f a -> ExceptT e f b -> ExceptT e f c #

(*>) :: ExceptT e f a -> ExceptT e f b -> ExceptT e f b #

(<*) :: ExceptT e f a -> ExceptT e f b -> ExceptT e f a #

Functor f => Functor (ExceptT e f) Source # 
Instance details

Defined in Control.Selective.Trans.Except

Methods

fmap :: (a -> b) -> ExceptT e f a -> ExceptT e f b #

(<$) :: a -> ExceptT e f b -> ExceptT e f a #

(Selective f, Monad f) => Monad (ExceptT e f) Source # 
Instance details

Defined in Control.Selective.Trans.Except

Methods

(>>=) :: ExceptT e f a -> (a -> ExceptT e f b) -> ExceptT e f b #

(>>) :: ExceptT e f a -> ExceptT e f b -> ExceptT e f b #

return :: a -> ExceptT e f a #

(Selective f, Monoid e, Monad f) => MonadPlus (ExceptT e f) Source # 
Instance details

Defined in Control.Selective.Trans.Except

Methods

mzero :: ExceptT e f a #

mplus :: ExceptT e f a -> ExceptT e f a -> ExceptT e f a #

Selective f => Selective (ExceptT e f) Source # 
Instance details

Defined in Control.Selective.Trans.Except

Methods

select :: ExceptT e f (Either a b) -> ExceptT e f (a -> b) -> ExceptT e f b Source #

(Read1 f, Read e, Read a) => Read (ExceptT e f a) Source # 
Instance details

Defined in Control.Selective.Trans.Except

Methods

readsPrec :: Int -> ReadS (ExceptT e f a) #

readList :: ReadS [ExceptT e f a] #

readPrec :: ReadPrec (ExceptT e f a) #

readListPrec :: ReadPrec [ExceptT e f a] #

(Show1 f, Show e, Show a) => Show (ExceptT e f a) Source # 
Instance details

Defined in Control.Selective.Trans.Except

Methods

showsPrec :: Int -> ExceptT e f a -> ShowS #

show :: ExceptT e f a -> String #

showList :: [ExceptT e f a] -> ShowS #

(Eq1 f, Eq e, Eq a) => Eq (ExceptT e f a) Source # 
Instance details

Defined in Control.Selective.Trans.Except

Methods

(==) :: ExceptT e f a -> ExceptT e f a -> Bool #

(/=) :: ExceptT e f a -> ExceptT e f a -> Bool #

(Ord1 f, Ord e, Ord a) => Ord (ExceptT e f a) Source # 
Instance details

Defined in Control.Selective.Trans.Except

Methods

compare :: ExceptT e f a -> ExceptT e f a -> Ordering #

(<) :: ExceptT e f a -> ExceptT e f a -> Bool #

(<=) :: ExceptT e f a -> ExceptT e f a -> Bool #

(>) :: ExceptT e f a -> ExceptT e f a -> Bool #

(>=) :: ExceptT e f a -> ExceptT e f a -> Bool #

max :: ExceptT e f a -> ExceptT e f a -> ExceptT e f a #

min :: ExceptT e f a -> ExceptT e f a -> ExceptT e f a #

wrap :: ExceptT e m a -> ExceptT e m a Source #

Inject an ExceptT value into the newtype wrapper.

except :: Monad m => Either e a -> ExceptT e m a Source #

mapExcept :: (Either e a -> Either e' b) -> Except e a -> Except e' b Source #

withExcept :: (e -> e') -> Except e a -> Except e' a Source #

runExceptT :: ExceptT e m a -> m (Either e a) Source #

mapExceptT :: (m (Either e a) -> n (Either e' b)) -> ExceptT e m a -> ExceptT e' n b Source #

withExceptT :: Functor m => (e -> e') -> ExceptT e m a -> ExceptT e' m a Source #

throwE :: Monad m => e -> ExceptT e m a Source #

catchE :: Monad m => ExceptT e m a -> (e -> ExceptT e' m a) -> ExceptT e' m a Source #

liftCallCC :: CallCC m (Either e a) (Either e b) -> CallCC (ExceptT e m) a b Source #

liftListen :: Monad m => Listen w m (Either e a) -> Listen w (ExceptT e m) a Source #

liftPass :: Monad m => Pass w m (Either e a) -> Pass w (ExceptT e m) a Source #