base-4.10.0.0: Basic libraries

Copyright(c) The University of Glasgow 2001
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org
Stabilityprovisional
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Functor

Description

Functors: uniform action over a parameterized type, generalizing the map function on lists.

Synopsis

Documentation

class Functor f where Source #

The Functor class is used for types that can be mapped over. Instances of Functor should satisfy the following laws:

fmap id  ==  id
fmap (f . g)  ==  fmap f . fmap g

The instances of Functor for lists, Maybe and IO satisfy these laws.

Minimal complete definition

fmap

Methods

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

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

Replace all locations in the input with the same value. The default definition is fmap . const, but this may be overridden with a more efficient version.

Instances

Functor [] Source #

Since: 2.1

Methods

fmap :: (a -> b) -> [a] -> [b] Source #

(<$) :: a -> [b] -> [a] Source #

Functor Maybe Source #

Since: 2.1

Methods

fmap :: (a -> b) -> Maybe a -> Maybe b Source #

(<$) :: a -> Maybe b -> Maybe a Source #

Functor IO Source #

Since: 2.1

Methods

fmap :: (a -> b) -> IO a -> IO b Source #

(<$) :: a -> IO b -> IO a Source #

Functor Par1 Source # 

Methods

fmap :: (a -> b) -> Par1 a -> Par1 b Source #

(<$) :: a -> Par1 b -> Par1 a Source #

Functor ReadP Source #

Since: 2.1

Methods

fmap :: (a -> b) -> ReadP a -> ReadP b Source #

(<$) :: a -> ReadP b -> ReadP a Source #

Functor ReadPrec Source #

Since: 2.1

Methods

fmap :: (a -> b) -> ReadPrec a -> ReadPrec b Source #

(<$) :: a -> ReadPrec b -> ReadPrec a Source #

Functor Last Source # 

Methods

fmap :: (a -> b) -> Last a -> Last b Source #

(<$) :: a -> Last b -> Last a Source #

Functor First Source # 

Methods

fmap :: (a -> b) -> First a -> First b Source #

(<$) :: a -> First b -> First a Source #

Functor Product Source #

Since: 4.8.0.0

Methods

fmap :: (a -> b) -> Product a -> Product b Source #

(<$) :: a -> Product b -> Product a Source #

Functor Sum Source #

Since: 4.8.0.0

Methods

fmap :: (a -> b) -> Sum a -> Sum b Source #

(<$) :: a -> Sum b -> Sum a Source #

Functor Dual Source #

Since: 4.8.0.0

Methods

fmap :: (a -> b) -> Dual a -> Dual b Source #

(<$) :: a -> Dual b -> Dual a Source #

Functor STM Source #

Since: 4.3.0.0

Methods

fmap :: (a -> b) -> STM a -> STM b Source #

(<$) :: a -> STM b -> STM a Source #

Functor Handler Source #

Since: 4.6.0.0

Methods

fmap :: (a -> b) -> Handler a -> Handler b Source #

(<$) :: a -> Handler b -> Handler a Source #

Functor Identity Source #

Since: 4.8.0.0

Methods

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

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

Functor ZipList Source # 

Methods

fmap :: (a -> b) -> ZipList a -> ZipList b Source #

(<$) :: a -> ZipList b -> ZipList a Source #

Functor ArgDescr Source #

Since: 4.6.0.0

Methods

fmap :: (a -> b) -> ArgDescr a -> ArgDescr b Source #

(<$) :: a -> ArgDescr b -> ArgDescr a Source #

Functor OptDescr Source #

Since: 4.6.0.0

Methods

fmap :: (a -> b) -> OptDescr a -> OptDescr b Source #

(<$) :: a -> OptDescr b -> OptDescr a Source #

Functor ArgOrder Source #

Since: 4.6.0.0

Methods

fmap :: (a -> b) -> ArgOrder a -> ArgOrder b Source #

(<$) :: a -> ArgOrder b -> ArgOrder a Source #

Functor NonEmpty Source #

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> NonEmpty a -> NonEmpty b Source #

(<$) :: a -> NonEmpty b -> NonEmpty a Source #

Functor Option Source #

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> Option a -> Option b Source #

(<$) :: a -> Option b -> Option a Source #

Functor Last Source #

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> Last a -> Last b Source #

(<$) :: a -> Last b -> Last a Source #

Functor First Source #

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> First a -> First b Source #

(<$) :: a -> First b -> First a Source #

Functor Max Source #

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> Max a -> Max b Source #

(<$) :: a -> Max b -> Max a Source #

Functor Min Source #

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> Min a -> Min b Source #

(<$) :: a -> Min b -> Min a Source #

Functor Complex Source # 

Methods

fmap :: (a -> b) -> Complex a -> Complex b Source #

(<$) :: a -> Complex b -> Complex a Source #

Functor (Either a) Source #

Since: 3.0

Methods

fmap :: (a -> b) -> Either a a -> Either a b Source #

(<$) :: a -> Either a b -> Either a a Source #

Functor (V1 *) Source # 

Methods

fmap :: (a -> b) -> V1 * a -> V1 * b Source #

(<$) :: a -> V1 * b -> V1 * a Source #

Functor (U1 *) Source #

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> U1 * a -> U1 * b Source #

(<$) :: a -> U1 * b -> U1 * a Source #

Functor ((,) a) Source #

Since: 2.1

Methods

fmap :: (a -> b) -> (a, a) -> (a, b) Source #

(<$) :: a -> (a, b) -> (a, a) Source #

Functor (ST s) Source #

Since: 2.1

Methods

fmap :: (a -> b) -> ST s a -> ST s b Source #

(<$) :: a -> ST s b -> ST s a Source #

Functor (Proxy *) Source #

Since: 4.7.0.0

Methods

fmap :: (a -> b) -> Proxy * a -> Proxy * b Source #

(<$) :: a -> Proxy * b -> Proxy * a Source #

Arrow a => Functor (ArrowMonad a) Source #

Since: 4.6.0.0

Methods

fmap :: (a -> b) -> ArrowMonad a a -> ArrowMonad a b Source #

(<$) :: a -> ArrowMonad a b -> ArrowMonad a a Source #

Monad m => Functor (WrappedMonad m) Source #

Since: 2.1

Methods

fmap :: (a -> b) -> WrappedMonad m a -> WrappedMonad m b Source #

(<$) :: a -> WrappedMonad m b -> WrappedMonad m a Source #

Functor (ST s) Source #

Since: 2.1

Methods

fmap :: (a -> b) -> ST s a -> ST s b Source #

(<$) :: a -> ST s b -> ST s a Source #

Functor (Arg a) Source #

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> Arg a a -> Arg a b Source #

(<$) :: a -> Arg a b -> Arg a a Source #

Functor f => Functor (Rec1 * f) Source # 

Methods

fmap :: (a -> b) -> Rec1 * f a -> Rec1 * f b Source #

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

Functor (URec * Char) Source # 

Methods

fmap :: (a -> b) -> URec * Char a -> URec * Char b Source #

(<$) :: a -> URec * Char b -> URec * Char a Source #

Functor (URec * Double) Source # 

Methods

fmap :: (a -> b) -> URec * Double a -> URec * Double b Source #

(<$) :: a -> URec * Double b -> URec * Double a Source #

Functor (URec * Float) Source # 

Methods

fmap :: (a -> b) -> URec * Float a -> URec * Float b Source #

(<$) :: a -> URec * Float b -> URec * Float a Source #

Functor (URec * Int) Source # 

Methods

fmap :: (a -> b) -> URec * Int a -> URec * Int b Source #

(<$) :: a -> URec * Int b -> URec * Int a Source #

Functor (URec * Word) Source # 

Methods

fmap :: (a -> b) -> URec * Word a -> URec * Word b Source #

(<$) :: a -> URec * Word b -> URec * Word a Source #

Functor (URec * (Ptr ())) Source # 

Methods

fmap :: (a -> b) -> URec * (Ptr ()) a -> URec * (Ptr ()) b Source #

(<$) :: a -> URec * (Ptr ()) b -> URec * (Ptr ()) a Source #

Functor f => Functor (Alt * f) Source # 

Methods

fmap :: (a -> b) -> Alt * f a -> Alt * f b Source #

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

Functor (Const * m) Source #

Since: 2.1

Methods

fmap :: (a -> b) -> Const * m a -> Const * m b Source #

(<$) :: a -> Const * m b -> Const * m a Source #

Arrow a => Functor (WrappedArrow a b) Source #

Since: 2.1

Methods

fmap :: (a -> b) -> WrappedArrow a b a -> WrappedArrow a b b Source #

(<$) :: a -> WrappedArrow a b b -> WrappedArrow a b a Source #

Functor ((->) LiftedRep LiftedRep r) Source #

Since: 2.1

Methods

fmap :: (a -> b) -> (LiftedRep -> LiftedRep) r a -> (LiftedRep -> LiftedRep) r b Source #

(<$) :: a -> (LiftedRep -> LiftedRep) r b -> (LiftedRep -> LiftedRep) r a Source #

Functor (K1 * i c) Source # 

Methods

fmap :: (a -> b) -> K1 * i c a -> K1 * i c b Source #

(<$) :: a -> K1 * i c b -> K1 * i c a Source #

(Functor g, Functor f) => Functor ((:+:) * f g) Source # 

Methods

fmap :: (a -> b) -> (* :+: f) g a -> (* :+: f) g b Source #

(<$) :: a -> (* :+: f) g b -> (* :+: f) g a Source #

(Functor g, Functor f) => Functor ((:*:) * f g) Source # 

Methods

fmap :: (a -> b) -> (* :*: f) g a -> (* :*: f) g b Source #

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

(Functor f, Functor g) => Functor (Sum * f g) Source #

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> Sum * f g a -> Sum * f g b Source #

(<$) :: a -> Sum * f g b -> Sum * f g a Source #

(Functor f, Functor g) => Functor (Product * f g) Source #

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> Product * f g a -> Product * f g b Source #

(<$) :: a -> Product * f g b -> Product * f g a Source #

Functor f => Functor (M1 * i c f) Source # 

Methods

fmap :: (a -> b) -> M1 * i c f a -> M1 * i c f b Source #

(<$) :: a -> M1 * i c f b -> M1 * i c f a Source #

(Functor g, Functor f) => Functor ((:.:) * * f g) Source # 

Methods

fmap :: (a -> b) -> (* :.: *) f g a -> (* :.: *) f g b Source #

(<$) :: a -> (* :.: *) f g b -> (* :.: *) f g a Source #

(Functor f, Functor g) => Functor (Compose * * f g) Source #

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> Compose * * f g a -> Compose * * f g b Source #

(<$) :: a -> Compose * * f g b -> Compose * * f g a Source #

(<$) :: Functor f => a -> f b -> f a infixl 4 Source #

Replace all locations in the input with the same value. The default definition is fmap . const, but this may be overridden with a more efficient version.

($>) :: Functor f => f a -> b -> f b infixl 4 Source #

Flipped version of <$.

Examples

Replace the contents of a Maybe Int with a constant String:

>>> Nothing $> "foo"
Nothing
>>> Just 90210 $> "foo"
Just "foo"

Replace the contents of an Either Int Int with a constant String, resulting in an Either Int String:

>>> Left 8675309 $> "foo"
Left 8675309
>>> Right 8675309 $> "foo"
Right "foo"

Replace each element of a list with a constant String:

>>> [1,2,3] $> "foo"
["foo","foo","foo"]

Replace the second element of a pair with a constant String:

>>> (1,2) $> "foo"
(1,"foo")

Since: 4.7.0.0

(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 Source #

An infix synonym for fmap.

The name of this operator is an allusion to $. Note the similarities between their types:

 ($)  ::              (a -> b) ->   a ->   b
(<$>) :: Functor f => (a -> b) -> f a -> f b

Whereas $ is function application, <$> is function application lifted over a Functor.

Examples

Convert from a Maybe Int to a Maybe String using show:

>>> show <$> Nothing
Nothing
>>> show <$> Just 3
Just "3"

Convert from an Either Int Int to an Either Int String using show:

>>> show <$> Left 17
Left 17
>>> show <$> Right 17
Right "17"

Double each element of a list:

>>> (*2) <$> [1,2,3]
[2,4,6]

Apply even to the second element of a pair:

>>> even <$> (2,2)
(2,True)

void :: Functor f => f a -> f () Source #

void value discards or ignores the result of evaluation, such as the return value of an IO action.

Examples

Replace the contents of a Maybe Int with unit:

>>> void Nothing
Nothing
>>> void (Just 3)
Just ()

Replace the contents of an Either Int Int with unit, resulting in an Either Int '()':

>>> void (Left 8675309)
Left 8675309
>>> void (Right 8675309)
Right ()

Replace every element of a list with unit:

>>> void [1,2,3]
[(),(),()]

Replace the second element of a pair with unit:

>>> void (1,2)
(1,())

Discard the result of an IO action:

>>> mapM print [1,2]
1
2
[(),()]
>>> void $ mapM print [1,2]
1
2