Copyright | (c) The University of Glasgow 2001 |
---|---|
License | BSD-style (see the file libraries/base/LICENSE) |
Maintainer | libraries@haskell.org |
Stability | provisional |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
A type f
is a Functor if it provides a function fmap
which, given any types a
and b
,
lets you apply any function of type (a -> b)
to turn an f a
into an f b
, preserving the
structure of f
.
Examples
>>>
fmap show (Just 1) -- (a -> b) -> f a -> f b
Just "1" -- (Int -> String) -> Maybe Int -> Maybe String
>>>
fmap show Nothing -- (a -> b) -> f a -> f b
Nothing -- (Int -> String) -> Maybe Int -> Maybe String
>>>
fmap show [1,2,3] -- (a -> b) -> f a -> f b
["1","2","3"] -- (Int -> String) -> [Int] -> [String]
>>>
fmap show [] -- (a -> b) -> f a -> f b
[] -- (Int -> String) -> [Int] -> [String]
The fmap
function is also available as the infix operator <$>
:
>>>
fmap show (Just 1) -- (Int -> String) -> Maybe Int -> Maybe String
Just "1"
>>>
show <$> (Just 1) -- (Int -> String) -> Maybe Int -> Maybe String
Just "1"
Synopsis
Documentation
class Functor (f :: Type -> Type) where Source #
A type f
is a Functor if it provides a function fmap
which, given any types a
and b
lets you apply any function from (a -> b)
to turn an f a
into an f b
, preserving the
structure of f
. Furthermore f
needs to adhere to the following:
Note, that the second law follows from the free theorem of the type fmap
and
the first law, so you need only check that the former condition holds.
See these articles by School of Haskell or
David Luposchainsky
for an explanation.
fmap :: (a -> b) -> f a -> f b Source #
fmap
is used to apply a function of type (a -> b)
to a value of type f a
,
where f is a functor, to produce a value of type f b
.
Note that for any type constructor with more than one parameter (e.g., Either
),
only the last type parameter can be modified with fmap
(e.g., b
in `Either a b`).
Some type constructors with two parameters or more have a
instance that allows
both the last and the penultimate parameters to be mapped over.Bifunctor
Examples
Convert from a
to a Maybe
IntMaybe String
using show
:
>>>
fmap show Nothing
Nothing>>>
fmap show (Just 3)
Just "3"
Convert from an
to an
Either
Int IntEither Int String
using show
:
>>>
fmap show (Left 17)
Left 17>>>
fmap show (Right 17)
Right "17"
Double each element of a list:
>>>
fmap (*2) [1,2,3]
[2,4,6]
Apply even
to the second element of a pair:
>>>
fmap even (2,2)
(2,True)
It may seem surprising that the function is only applied to the last element of the tuple
compared to the list example above which applies it to every element in the list.
To understand, remember that tuples are type constructors with multiple type parameters:
a tuple of 3 elements (a,b,c)
can also be written (,,) a b c
and its Functor
instance
is defined for Functor ((,,) a b)
(i.e., only the third parameter is free to be mapped over
with fmap
).
It explains why fmap
can be used with tuples containing values of different types as in the
following example:
>>>
fmap even ("hello", 1.0, 4)
("hello",1.0,True)
Instances
Functor NonEmpty Source # | @since base-4.9.0.0 |
Functor STM Source # | @since base-4.3.0.0 |
Functor Handler Source # | @since base-4.6.0.0 |
Functor Identity Source # | @since base-4.8.0.0 |
Functor First Source # | @since base-4.8.0.0 |
Functor Last Source # | @since base-4.8.0.0 |
Functor Down Source # | @since base-4.11.0.0 |
Functor Dual Source # | @since base-4.8.0.0 |
Functor Product Source # | @since base-4.8.0.0 |
Functor Sum Source # | @since base-4.8.0.0 |
Functor ZipList Source # | @since base-2.01 |
Functor NoIO Source # | @since base-4.8.0.0 |
Functor Par1 Source # | @since base-4.9.0.0 |
Functor ReadP Source # | @since base-2.01 |
Functor ReadPrec Source # | @since base-2.01 |
Functor IO Source # | @since base-2.01 |
Functor Maybe Source # | @since base-2.01 |
Functor Solo Source # | @since base-4.15 |
Functor [] Source # | @since base-2.01 |
Functor (Array i) Source # | @since base-2.01 |
Arrow a => Functor (ArrowMonad a) Source # | @since base-4.6.0.0 |
Defined in GHC.Internal.Control.Arrow fmap :: (a0 -> b) -> ArrowMonad a a0 -> ArrowMonad a b Source # (<$) :: a0 -> ArrowMonad a b -> ArrowMonad a a0 Source # | |
Functor (ST s) Source # | @since base-2.01 |
Functor (Either a) Source # | @since base-3.0 |
Functor (StateL s) Source # | @since base-4.0 |
Functor (StateR s) Source # | @since base-4.0 |
Functor (Proxy :: Type -> Type) Source # | @since base-4.7.0.0 |
Functor (U1 :: Type -> Type) Source # | @since base-4.9.0.0 |
Functor (V1 :: Type -> Type) Source # | @since base-4.9.0.0 |
Functor (ST s) Source # | @since base-2.01 |
Functor ((,) a) Source # | @since base-2.01 |
Functor m => Functor (Kleisli m a) Source # | @since base-4.14.0.0 |
Functor (Const m :: Type -> Type) Source # | @since base-2.01 |
Monad m => Functor (StateT s m) Source # | @since base-4.18.0.0 |
Functor f => Functor (Ap f) Source # | @since base-4.12.0.0 |
Functor f => Functor (Alt f) Source # | @since base-4.8.0.0 |
(Generic1 f, Functor (Rep1 f)) => Functor (Generically1 f) Source # | @since base-4.17.0.0 |
Defined in GHC.Internal.Generics fmap :: (a -> b) -> Generically1 f a -> Generically1 f b Source # (<$) :: a -> Generically1 f b -> Generically1 f a Source # | |
Functor f => Functor (Rec1 f) Source # | @since base-4.9.0.0 |
Functor (URec (Ptr ()) :: Type -> Type) Source # | @since base-4.9.0.0 |
Functor (URec Char :: Type -> Type) Source # | @since base-4.9.0.0 |
Functor (URec Double :: Type -> Type) Source # | @since base-4.9.0.0 |
Functor (URec Float :: Type -> Type) Source # | @since base-4.9.0.0 |
Functor (URec Int :: Type -> Type) Source # | @since base-4.9.0.0 |
Functor (URec Word :: Type -> Type) Source # | @since base-4.9.0.0 |
Functor ((,,) a b) Source # | @since base-4.14.0.0 |
(Functor f, Functor g) => Functor (f :*: g) Source # | @since base-4.9.0.0 |
(Functor f, Functor g) => Functor (f :+: g) Source # | @since base-4.9.0.0 |
Functor (K1 i c :: Type -> Type) Source # | @since base-4.9.0.0 |
Functor ((,,,) a b c) Source # | @since base-4.14.0.0 |
Functor ((->) r) Source # | @since base-2.01 |
(Functor f, Functor g) => Functor (f :.: g) Source # | @since base-4.9.0.0 |
Functor f => Functor (M1 i c f) Source # | @since base-4.9.0.0 |
Functor ((,,,,) a b c d) Source # | @since base-4.18.0.0 |
Functor ((,,,,,) a b c d e) Source # | @since base-4.18.0.0 |
Functor ((,,,,,,) a b c d e f) Source # | @since base-4.18.0.0 |
($>) :: Functor f => f a -> b -> f b infixl 4 Source #
Flipped version of <$
.
@since base-4.7.0.0
Examples
Replace the contents of a
with a constant
Maybe
Int
String
:
>>>
Nothing $> "foo"
Nothing
>>>
Just 90210 $> "foo"
Just "foo"
Replace the contents of an
with a constant Either
Int
Int
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")
(<$>) :: 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
to a Maybe
Int
using Maybe
String
show
:
>>>
show <$> Nothing
Nothing
>>>
show <$> Just 3
Just "3"
Convert from an
to an
Either
Int
Int
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)
unzip :: Functor f => f (a, b) -> (f a, f b) Source #
Generalization of Data.List.
unzip
.
Examples
>>>
unzip (Just ("Hello", "World"))
(Just "Hello",Just "World")
>>>
unzip [("I", "love"), ("really", "haskell")]
(["I","really"],["love","haskell"])
@since base-4.19.0.0
void :: Functor f => f a -> f () Source #
discards or ignores the result of evaluation, such
as the return value of an void
valueIO
action.
Examples
Replace the contents of a
with unit:Maybe
Int
>>>
void Nothing
Nothing
>>>
void (Just 3)
Just ()
Replace the contents of an
with unit, resulting in an Either
Int
Int
: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