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 | Safe |
Language | Haskell2010 |
Documentation
class Functor f 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.
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 ZipList Source # | Since: base-2.1 |
Functor Handler Source # | Since: base-4.6.0.0 |
Functor Complex Source # | Since: base-4.9.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 First Source # | Since: base-4.9.0.0 |
Functor Last Source # | Since: base-4.9.0.0 |
Functor Max Source # | Since: base-4.9.0.0 |
Functor Min Source # | Since: base-4.9.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 STM Source # | Since: base-4.3.0.0 |
Functor NoIO Source # | Since: base-4.8.0.0 |
Functor Par1 Source # | Since: base-4.9.0.0 |
Functor ArgDescr Source # | Since: base-4.6.0.0 |
Functor ArgOrder Source # | Since: base-4.6.0.0 |
Functor OptDescr Source # | Since: base-4.6.0.0 |
Functor ReadP Source # | Since: base-2.1 |
Functor ReadPrec Source # | Since: base-2.1 |
Functor IO Source # | Since: base-2.1 |
Functor NonEmpty Source # | Since: base-4.9.0.0 |
Functor Maybe Source # | Since: base-2.1 |
Functor Solo Source # | Since: base-4.15 |
Functor [] Source # | Since: base-2.1 |
Monad m => Functor (WrappedMonad m) Source # | Since: base-2.1 |
Defined in Control.Applicative fmap :: (a -> b) -> WrappedMonad m a -> WrappedMonad m b Source # (<$) :: a -> WrappedMonad m b -> WrappedMonad m a Source # | |
Arrow a => Functor (ArrowMonad a) Source # | Since: base-4.6.0.0 |
Defined in 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.1 |
Functor (Either a) Source # | Since: base-3.0 |
Functor (Proxy :: Type -> Type) Source # | Since: base-4.7.0.0 |
Functor (Arg a) Source # | Since: base-4.9.0.0 |
Functor (Array i) Source # | Since: base-2.1 |
Functor (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 |
Functor (V1 :: TYPE LiftedRep -> Type) Source # | Since: base-4.9.0.0 |
Functor (ST s) Source # | Since: base-2.1 |
Functor ((,) a) Source # | Since: base-2.1 |
Arrow a => Functor (WrappedArrow a b) Source # | Since: base-2.1 |
Defined in Control.Applicative fmap :: (a0 -> b0) -> WrappedArrow a b a0 -> WrappedArrow a b b0 Source # (<$) :: a0 -> WrappedArrow a b b0 -> WrappedArrow a b a0 Source # | |
Functor m => Functor (Kleisli m a) Source # | Since: base-4.14.0.0 |
Functor (Const m :: Type -> Type) Source # | Since: base-2.1 |
Functor f => Functor (Ap f) Source # | Since: base-4.12.0.0 |
Functor f => Functor (Alt f) Source # | Since: base-4.8.0.0 |
Functor f => Functor (Rec1 f) Source # | Since: base-4.9.0.0 |
Functor (URec (Ptr ()) :: TYPE LiftedRep -> Type) Source # | Since: base-4.9.0.0 |
Functor (URec Char :: TYPE LiftedRep -> Type) Source # | Since: base-4.9.0.0 |
Functor (URec Double :: TYPE LiftedRep -> Type) Source # | Since: base-4.9.0.0 |
Functor (URec Float :: TYPE LiftedRep -> Type) Source # | Since: base-4.9.0.0 |
Functor (URec Int :: TYPE LiftedRep -> Type) Source # | Since: base-4.9.0.0 |
Functor (URec Word :: TYPE LiftedRep -> Type) Source # | Since: base-4.9.0.0 |
Functor ((,,) a b) Source # | Since: base-4.14.0.0 |
(Functor f, Functor g) => Functor (Product f g) Source # | Since: base-4.9.0.0 |
(Functor f, Functor g) => Functor (Sum f g) Source # | Since: base-4.9.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 LiftedRep -> 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.1 |
(Functor f, Functor g) => Functor (Compose f g) Source # | Since: base-4.9.0.0 |
(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 |
class Applicative m => Monad m where Source #
The Monad
class defines the basic operations over a monad,
a concept from a branch of mathematics known as category theory.
From the perspective of a Haskell programmer, however, it is best to
think of a monad as an abstract datatype of actions.
Haskell's do
expressions provide a convenient syntax for writing
monadic expressions.
Instances of Monad
should satisfy the following:
- Left identity
return
a>>=
k = k a- Right identity
m
>>=
return
= m- Associativity
m
>>=
(\x -> k x>>=
h) = (m>>=
k)>>=
h
Furthermore, the Monad
and Applicative
operations should relate as follows:
The above laws imply:
and that pure
and (<*>
) satisfy the applicative functor laws.
The instances of Monad
for lists, Maybe
and IO
defined in the Prelude satisfy these laws.
(>>=) :: forall a b. m a -> (a -> m b) -> m b infixl 1 Source #
Sequentially compose two actions, passing any value produced by the first as an argument to the second.
'as
' can be understood as the >>=
bsdo
expression
do a <- as bs a
(>>) :: forall a b. m a -> m b -> m b infixl 1 Source #
Sequentially compose two actions, discarding any value produced by the first, like sequencing operators (such as the semicolon) in imperative languages.
'as
' can be understood as the >>
bsdo
expression
do as bs
Inject a value into the monadic type.
Instances
Monad Complex Source # | Since: base-4.9.0.0 |
Monad Identity Source # | Since: base-4.8.0.0 |
Monad First Source # | Since: base-4.8.0.0 |
Monad Last Source # | Since: base-4.8.0.0 |
Monad Down Source # | Since: base-4.11.0.0 |
Monad First Source # | Since: base-4.9.0.0 |
Monad Last Source # | Since: base-4.9.0.0 |
Monad Max Source # | Since: base-4.9.0.0 |
Monad Min Source # | Since: base-4.9.0.0 |
Monad Dual Source # | Since: base-4.8.0.0 |
Monad Product Source # | Since: base-4.8.0.0 |
Monad Sum Source # | Since: base-4.8.0.0 |
Monad STM Source # | Since: base-4.3.0.0 |
Monad NoIO Source # | Since: base-4.4.0.0 |
Monad Par1 Source # | Since: base-4.9.0.0 |
Monad ReadP Source # | Since: base-2.1 |
Monad ReadPrec Source # | Since: base-2.1 |
Monad IO Source # | Since: base-2.1 |
Monad NonEmpty Source # | Since: base-4.9.0.0 |
Monad Maybe Source # | Since: base-2.1 |
Monad Solo Source # | Since: base-4.15 |
Monad [] Source # | Since: base-2.1 |
Monad m => Monad (WrappedMonad m) Source # | Since: base-4.7.0.0 |
Defined in Control.Applicative (>>=) :: WrappedMonad m a -> (a -> WrappedMonad m b) -> WrappedMonad m b Source # (>>) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m b Source # return :: a -> WrappedMonad m a Source # | |
ArrowApply a => Monad (ArrowMonad a) Source # | Since: base-2.1 |
Defined in Control.Arrow (>>=) :: ArrowMonad a a0 -> (a0 -> ArrowMonad a b) -> ArrowMonad a b Source # (>>) :: ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a b Source # return :: a0 -> ArrowMonad a a0 Source # | |
Monad (ST s) Source # | Since: base-2.1 |
Monad (Either e) Source # | Since: base-4.4.0.0 |
Monad (Proxy :: Type -> Type) Source # | Since: base-4.7.0.0 |
Monad (U1 :: Type -> Type) Source # | Since: base-4.9.0.0 |
Monad (ST s) Source # | Since: base-2.1 |
Monoid a => Monad ((,) a) Source # | Since: base-4.9.0.0 |
Monad m => Monad (Kleisli m a) Source # | Since: base-4.14.0.0 |
Monad f => Monad (Ap f) Source # | Since: base-4.12.0.0 |
Monad f => Monad (Alt f) Source # | Since: base-4.8.0.0 |
Monad f => Monad (Rec1 f) Source # | Since: base-4.9.0.0 |
(Monoid a, Monoid b) => Monad ((,,) a b) Source # | Since: base-4.14.0.0 |
(Monad f, Monad g) => Monad (Product f g) Source # | Since: base-4.9.0.0 |
(Monad f, Monad g) => Monad (f :*: g) Source # | Since: base-4.9.0.0 |
(Monoid a, Monoid b, Monoid c) => Monad ((,,,) a b c) Source # | Since: base-4.14.0.0 |
Monad ((->) r) Source # | Since: base-2.1 |
Monad f => Monad (M1 i c f) Source # | Since: base-4.9.0.0 |