base-4.8.1.0: Basic libraries

Copyright(c) Andy Gill 2001, (c) Oregon Graduate Institute of Science and Technology 2001
LicenseBSD-style (see the file LICENSE)
Maintainerross@soi.city.ac.uk
Stabilityexperimental
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Functor.Identity

Description

The identity functor and monad.

This trivial type constructor serves two purposes:

  • It can be used with functions parameterized by functor or monad classes.
  • It can be used as a base monad to which a series of monad transformers may be applied to construct a composite monad. Most monad transformer modules include the special case of applying the transformer to Identity. For example, State s is an abbreviation for StateT s Identity.

Since: 4.8.0.0

Synopsis

Documentation

newtype Identity a Source

Identity functor and monad. (a non-strict monad)

Since: 4.8.0.0

Constructors

Identity 

Fields

Instances

Monad Identity Source 
Functor Identity Source 

Methods

fmap :: (a -> b) -> Identity a -> Identity b Source

(<$) :: a -> Identity b -> Identity a Source

MonadFix Identity Source 

Methods

mfix :: (a -> Identity a) -> Identity a Source

Applicative Identity Source 

Methods

pure :: a -> Identity a Source

(<*>) :: Identity (a -> b) -> Identity a -> Identity b Source

(*>) :: Identity a -> Identity b -> Identity b Source

(<*) :: Identity a -> Identity b -> Identity a Source

Foldable Identity Source 

Methods

fold :: Monoid m => Identity m -> m Source

foldMap :: Monoid m => (a -> m) -> Identity a -> m Source

foldr :: (a -> b -> b) -> b -> Identity a -> b Source

foldr' :: (a -> b -> b) -> b -> Identity a -> b Source

foldl :: (b -> a -> b) -> b -> Identity a -> b Source

foldl' :: (b -> a -> b) -> b -> Identity a -> b Source

foldr1 :: (a -> a -> a) -> Identity a -> a Source

foldl1 :: (a -> a -> a) -> Identity a -> a Source

toList :: Identity a -> [a] Source

null :: Identity a -> Bool Source

length :: Identity a -> Int Source

elem :: Eq a => a -> Identity a -> Bool Source

maximum :: Ord a => Identity a -> a Source

minimum :: Ord a => Identity a -> a Source

sum :: Num a => Identity a -> a Source

product :: Num a => Identity a -> a Source

Traversable Identity Source 

Methods

traverse :: Applicative f => (a -> f b) -> Identity a -> f (Identity b) Source

sequenceA :: Applicative f => Identity (f a) -> f (Identity a) Source

mapM :: Monad m => (a -> m b) -> Identity a -> m (Identity b) Source

sequence :: Monad m => Identity (m a) -> m (Identity a) Source

Generic1 Identity Source 

Associated Types

type Rep1 (Identity :: * -> *) :: * -> * Source

MonadZip Identity Source 

Methods

mzip :: Identity a -> Identity b -> Identity (a, b) Source

mzipWith :: (a -> b -> c) -> Identity a -> Identity b -> Identity c Source

munzip :: Identity (a, b) -> (Identity a, Identity b) Source

Eq a => Eq (Identity a) Source 

Methods

(==) :: Identity a -> Identity a -> Bool

(/=) :: Identity a -> Identity a -> Bool

Data a => Data (Identity a) Source 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Identity a -> c (Identity a) Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Identity a) Source

toConstr :: Identity a -> Constr Source

dataTypeOf :: Identity a -> DataType Source

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Identity a)) Source

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Identity a)) Source

gmapT :: (forall b. Data b => b -> b) -> Identity a -> Identity a Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Identity a -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Identity a -> r Source

gmapQ :: (forall d. Data d => d -> u) -> Identity a -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> Identity a -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Identity a -> m (Identity a) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Identity a -> m (Identity a) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Identity a -> m (Identity a) Source

Ord a => Ord (Identity a) Source 

Methods

compare :: Identity a -> Identity a -> Ordering

(<) :: Identity a -> Identity a -> Bool

(<=) :: Identity a -> Identity a -> Bool

(>) :: Identity a -> Identity a -> Bool

(>=) :: Identity a -> Identity a -> Bool

max :: Identity a -> Identity a -> Identity a

min :: Identity a -> Identity a -> Identity a

Read a => Read (Identity a) Source

This instance would be equivalent to the derived instances of the Identity newtype if the runIdentity field were removed

Show a => Show (Identity a) Source

This instance would be equivalent to the derived instances of the Identity newtype if the runIdentity field were removed

Generic (Identity a) Source 

Associated Types

type Rep (Identity a) :: * -> * Source

Methods

from :: Identity a -> Rep (Identity a) x Source

to :: Rep (Identity a) x -> Identity a Source

type Rep1 Identity Source 
type Rep (Identity a) Source