transformers-0.5.6.2: Concrete functor and monad transformers
Copyright(c) Ross Paterson 2010
LicenseBSD-style (see the file LICENSE)
MaintainerR.Paterson@city.ac.uk
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Control.Applicative.Lift

Description

Adding a new kind of pure computation to an applicative functor.

Synopsis

Lifting an applicative

data Lift f a Source #

Applicative functor formed by adding pure computations to a given applicative functor.

Constructors

Pure a 
Other (f a) 

Instances

Instances details
Functor f => Functor (Lift f) # 
Instance details

Defined in Control.Applicative.Lift

Methods

fmap :: (a -> b) -> Lift f a -> Lift f b Source #

(<$) :: a -> Lift f b -> Lift f a Source #

Applicative f => Applicative (Lift f) #

A combination is Pure only if both parts are.

Instance details

Defined in Control.Applicative.Lift

Methods

pure :: a -> Lift f a Source #

(<*>) :: Lift f (a -> b) -> Lift f a -> Lift f b Source #

liftA2 :: (a -> b -> c) -> Lift f a -> Lift f b -> Lift f c Source #

(*>) :: Lift f a -> Lift f b -> Lift f b Source #

(<*) :: Lift f a -> Lift f b -> Lift f a Source #

Foldable f => Foldable (Lift f) # 
Instance details

Defined in Control.Applicative.Lift

Methods

fold :: Monoid m => Lift f m -> m Source #

foldMap :: Monoid m => (a -> m) -> Lift f a -> m Source #

foldMap' :: Monoid m => (a -> m) -> Lift f a -> m Source #

foldr :: (a -> b -> b) -> b -> Lift f a -> b Source #

foldr' :: (a -> b -> b) -> b -> Lift f a -> b Source #

foldl :: (b -> a -> b) -> b -> Lift f a -> b Source #

foldl' :: (b -> a -> b) -> b -> Lift f a -> b Source #

foldr1 :: (a -> a -> a) -> Lift f a -> a Source #

foldl1 :: (a -> a -> a) -> Lift f a -> a Source #

toList :: Lift f a -> [a] Source #

null :: Lift f a -> Bool Source #

length :: Lift f a -> Int Source #

elem :: Eq a => a -> Lift f a -> Bool Source #

maximum :: Ord a => Lift f a -> a Source #

minimum :: Ord a => Lift f a -> a Source #

sum :: Num a => Lift f a -> a Source #

product :: Num a => Lift f a -> a Source #

Traversable f => Traversable (Lift f) # 
Instance details

Defined in Control.Applicative.Lift

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Lift f a -> f0 (Lift f b) Source #

sequenceA :: Applicative f0 => Lift f (f0 a) -> f0 (Lift f a) Source #

mapM :: Monad m => (a -> m b) -> Lift f a -> m (Lift f b) Source #

sequence :: Monad m => Lift f (m a) -> m (Lift f a) Source #

Eq1 f => Eq1 (Lift f) # 
Instance details

Defined in Control.Applicative.Lift

Methods

liftEq :: (a -> b -> Bool) -> Lift f a -> Lift f b -> Bool Source #

Ord1 f => Ord1 (Lift f) # 
Instance details

Defined in Control.Applicative.Lift

Methods

liftCompare :: (a -> b -> Ordering) -> Lift f a -> Lift f b -> Ordering Source #

Read1 f => Read1 (Lift f) # 
Instance details

Defined in Control.Applicative.Lift

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Lift f a) Source #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Lift f a] Source #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Lift f a) Source #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Lift f a] Source #

Show1 f => Show1 (Lift f) # 
Instance details

Defined in Control.Applicative.Lift

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Lift f a -> ShowS Source #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Lift f a] -> ShowS Source #

Alternative f => Alternative (Lift f) #

A combination is Pure only either part is.

Instance details

Defined in Control.Applicative.Lift

Methods

empty :: Lift f a Source #

(<|>) :: Lift f a -> Lift f a -> Lift f a Source #

some :: Lift f a -> Lift f [a] Source #

many :: Lift f a -> Lift f [a] Source #

(Eq1 f, Eq a) => Eq (Lift f a) # 
Instance details

Defined in Control.Applicative.Lift

Methods

(==) :: Lift f a -> Lift f a -> Bool #

(/=) :: Lift f a -> Lift f a -> Bool #

(Ord1 f, Ord a) => Ord (Lift f a) # 
Instance details

Defined in Control.Applicative.Lift

Methods

compare :: Lift f a -> Lift f a -> Ordering #

(<) :: Lift f a -> Lift f a -> Bool #

(<=) :: Lift f a -> Lift f a -> Bool #

(>) :: Lift f a -> Lift f a -> Bool #

(>=) :: Lift f a -> Lift f a -> Bool #

max :: Lift f a -> Lift f a -> Lift f a #

min :: Lift f a -> Lift f a -> Lift f a #

(Read1 f, Read a) => Read (Lift f a) # 
Instance details

Defined in Control.Applicative.Lift

(Show1 f, Show a) => Show (Lift f a) # 
Instance details

Defined in Control.Applicative.Lift

Methods

showsPrec :: Int -> Lift f a -> ShowS Source #

show :: Lift f a -> String Source #

showList :: [Lift f a] -> ShowS Source #

unLift :: Applicative f => Lift f a -> f a Source #

Projection to the other functor.

mapLift :: (f a -> g a) -> Lift f a -> Lift g a Source #

Apply a transformation to the other computation.

elimLift :: (a -> r) -> (f a -> r) -> Lift f a -> r Source #

Eliminator for Lift.

Collecting errors

type Errors e = Lift (Constant e) Source #

An applicative functor that collects a monoid (e.g. lists) of errors. A sequence of computations fails if any of its components do, but unlike monads made with ExceptT from Control.Monad.Trans.Except, these computations continue after an error, collecting all the errors.

runErrors :: Errors e a -> Either e a Source #

Extractor for computations with accumulating errors.

failure :: e -> Errors e a Source #

Report an error.

eitherToErrors :: Either e a -> Errors e a Source #

Convert from Either to Errors (inverse of runErrors).