transformers-0.5.1.0: Concrete functor and monad transformers

Copyright(c) 2007 Magnus Therning
LicenseBSD-style (see the file LICENSE)
MaintainerR.Paterson@city.ac.uk
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Control.Monad.Trans.Identity

Contents

Description

The identity monad transformer.

This is useful for functions parameterized by a monad transformer.

Synopsis

The identity monad transformer

newtype IdentityT f a Source

The trivial monad transformer, which maps a monad to an equivalent monad.

Constructors

IdentityT 

Fields

Instances

MonadTrans (IdentityT (TYPE Lifted)) 

Methods

lift :: Monad m => m a -> IdentityT (TYPE Lifted) m a Source

Monad m => Monad (IdentityT (TYPE Lifted) m) 
Functor m => Functor (IdentityT (TYPE Lifted) m) 

Methods

fmap :: (a -> b) -> IdentityT (TYPE Lifted) m a -> IdentityT (TYPE Lifted) m b Source

(<$) :: a -> IdentityT (TYPE Lifted) m b -> IdentityT (TYPE Lifted) m a Source

MonadFix m => MonadFix (IdentityT (TYPE Lifted) m) 

Methods

mfix :: (a -> IdentityT (TYPE Lifted) m a) -> IdentityT (TYPE Lifted) m a Source

MonadFail m => MonadFail (IdentityT (TYPE Lifted) m) 

Methods

fail :: String -> IdentityT (TYPE Lifted) m a Source

Applicative m => Applicative (IdentityT (TYPE Lifted) m) 
Foldable f => Foldable (IdentityT (TYPE Lifted) f) 

Methods

fold :: Monoid m => IdentityT (TYPE Lifted) f m -> m Source

foldMap :: Monoid m => (a -> m) -> IdentityT (TYPE Lifted) f a -> m Source

foldr :: (a -> b -> b) -> b -> IdentityT (TYPE Lifted) f a -> b Source

foldr' :: (a -> b -> b) -> b -> IdentityT (TYPE Lifted) f a -> b Source

foldl :: (b -> a -> b) -> b -> IdentityT (TYPE Lifted) f a -> b Source

foldl' :: (b -> a -> b) -> b -> IdentityT (TYPE Lifted) f a -> b Source

foldr1 :: (a -> a -> a) -> IdentityT (TYPE Lifted) f a -> a Source

foldl1 :: (a -> a -> a) -> IdentityT (TYPE Lifted) f a -> a Source

toList :: IdentityT (TYPE Lifted) f a -> [a] Source

null :: IdentityT (TYPE Lifted) f a -> Bool Source

length :: IdentityT (TYPE Lifted) f a -> Int Source

elem :: Eq a => a -> IdentityT (TYPE Lifted) f a -> Bool Source

maximum :: Ord a => IdentityT (TYPE Lifted) f a -> a Source

minimum :: Ord a => IdentityT (TYPE Lifted) f a -> a Source

sum :: Num a => IdentityT (TYPE Lifted) f a -> a Source

product :: Num a => IdentityT (TYPE Lifted) f a -> a Source

Traversable f => Traversable (IdentityT (TYPE Lifted) f) 

Methods

traverse :: Applicative f => (a -> f b) -> IdentityT (TYPE Lifted) f a -> f (IdentityT (TYPE Lifted) f b) Source

sequenceA :: Applicative f => IdentityT (TYPE Lifted) f (f a) -> f (IdentityT (TYPE Lifted) f a) Source

mapM :: Monad m => (a -> m b) -> IdentityT (TYPE Lifted) f a -> m (IdentityT (TYPE Lifted) f b) Source

sequence :: Monad m => IdentityT (TYPE Lifted) f (m a) -> m (IdentityT (TYPE Lifted) f a) Source

Eq1 f => Eq1 (IdentityT (TYPE Lifted) f) 

Methods

liftEq :: (a -> b -> Bool) -> IdentityT (TYPE Lifted) f a -> IdentityT (TYPE Lifted) f b -> Bool Source

Ord1 f => Ord1 (IdentityT (TYPE Lifted) f) 

Methods

liftCompare :: (a -> b -> Ordering) -> IdentityT (TYPE Lifted) f a -> IdentityT (TYPE Lifted) f b -> Ordering Source

Read1 f => Read1 (IdentityT (TYPE Lifted) f) 

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (IdentityT (TYPE Lifted) f a) Source

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [IdentityT (TYPE Lifted) f a] Source

Show1 f => Show1 (IdentityT (TYPE Lifted) f) 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> IdentityT (TYPE Lifted) f a -> ShowS Source

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [IdentityT (TYPE Lifted) f a] -> ShowS Source

MonadIO m => MonadIO (IdentityT (TYPE Lifted) m) 

Methods

liftIO :: IO a -> IdentityT (TYPE Lifted) m a Source

MonadZip m => MonadZip (IdentityT (TYPE Lifted) m) 

Methods

mzip :: IdentityT (TYPE Lifted) m a -> IdentityT (TYPE Lifted) m b -> IdentityT (TYPE Lifted) m (a, b) Source

mzipWith :: (a -> b -> c) -> IdentityT (TYPE Lifted) m a -> IdentityT (TYPE Lifted) m b -> IdentityT (TYPE Lifted) m c Source

munzip :: IdentityT (TYPE Lifted) m (a, b) -> (IdentityT (TYPE Lifted) m a, IdentityT (TYPE Lifted) m b) Source

Alternative m => Alternative (IdentityT (TYPE Lifted) m) 
MonadPlus m => MonadPlus (IdentityT (TYPE Lifted) m) 
(Eq1 f, Eq a) => Eq (IdentityT (TYPE Lifted) f a) 

Methods

(==) :: IdentityT (TYPE Lifted) f a -> IdentityT (TYPE Lifted) f a -> Bool

(/=) :: IdentityT (TYPE Lifted) f a -> IdentityT (TYPE Lifted) f a -> Bool

(Ord1 f, Ord a) => Ord (IdentityT (TYPE Lifted) f a) 
(Read1 f, Read a) => Read (IdentityT (TYPE Lifted) f a) 
(Show1 f, Show a) => Show (IdentityT (TYPE Lifted) f a) 

mapIdentityT :: (m a -> n b) -> IdentityT m a -> IdentityT n b Source

Lift a unary operation to the new monad.

Lifting other operations

liftCatch :: Catch e m a -> Catch e (IdentityT m) a Source

Lift a catchE operation to the new monad.

liftCallCC :: CallCC m a b -> CallCC (IdentityT m) a b Source

Lift a callCC operation to the new monad.