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 |
Control.Monad.Instances
Description
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.
Minimal complete definition
Methods
fmap :: (a -> b) -> f a -> f b Source #
Using ApplicativeDo
: '
' can be understood as
the fmap
f asdo
expression
do a <- as pure (f a)
with an inferred Functor
constraint.
Instances
Functor [] # | Since: base-2.1 |
Functor Maybe # | Since: base-2.1 |
Functor IO # | Since: base-2.1 |
Functor Par1 # | Since: base-4.9.0.0 |
Functor NonEmpty # | Since: base-4.9.0.0 |
Functor NoIO # | Since: base-4.8.0.0 |
Functor ReadP # | Since: base-2.1 |
Functor ReadPrec # | Since: base-2.1 |
Functor Down # | Since: base-4.11.0.0 |
Functor Product # | Since: base-4.8.0.0 |
Functor Sum # | Since: base-4.8.0.0 |
Functor Dual # | Since: base-4.8.0.0 |
Functor Last # | Since: base-4.8.0.0 |
Functor First # | Since: base-4.8.0.0 |
Functor STM # | Since: base-4.3.0.0 |
Functor Handler # | Since: base-4.6.0.0 |
Functor Identity # | Since: base-4.8.0.0 |
Functor ZipList # | Since: base-2.1 |
Functor ArgDescr # | Since: base-4.6.0.0 |
Functor OptDescr # | Since: base-4.6.0.0 |
Functor ArgOrder # | Since: base-4.6.0.0 |
Functor Option # | Since: base-4.9.0.0 |
Functor Last # | Since: base-4.9.0.0 |
Functor First # | Since: base-4.9.0.0 |
Functor Max # | Since: base-4.9.0.0 |
Functor Min # | Since: base-4.9.0.0 |
Functor Complex # | Since: base-4.9.0.0 |
Functor (Either a) # | Since: base-3.0 |
Functor (V1 :: Type -> Type) # | Since: base-4.9.0.0 |
Functor (U1 :: Type -> Type) # | Since: base-4.9.0.0 |
Functor ((,) a) # | Since: base-2.1 |
Functor (ST s) # | Since: base-2.1 |
Functor (Array i) # | Since: base-2.1 |
Functor (Proxy :: Type -> Type) # | Since: base-4.7.0.0 |
Arrow a => Functor (ArrowMonad a) # | Since: base-4.6.0.0 |
Defined in Control.Arrow Methods fmap :: (a0 -> b) -> ArrowMonad a a0 -> ArrowMonad a b Source # (<$) :: a0 -> ArrowMonad a b -> ArrowMonad a a0 Source # | |
Monad m => Functor (WrappedMonad m) # | Since: base-2.1 |
Defined in Control.Applicative Methods fmap :: (a -> b) -> WrappedMonad m a -> WrappedMonad m b Source # (<$) :: a -> WrappedMonad m b -> WrappedMonad m a Source # | |
Functor (ST s) # | Since: base-2.1 |
Functor (Arg a) # | Since: base-4.9.0.0 |
Functor f => Functor (Rec1 f) # | Since: base-4.9.0.0 |
Functor (URec Char :: Type -> Type) # | Since: base-4.9.0.0 |
Functor (URec Double :: Type -> Type) # | Since: base-4.9.0.0 |
Functor (URec Float :: Type -> Type) # | Since: base-4.9.0.0 |
Functor (URec Int :: Type -> Type) # | Since: base-4.9.0.0 |
Functor (URec Word :: Type -> Type) # | Since: base-4.9.0.0 |
Functor (URec (Ptr ()) :: Type -> Type) # | Since: base-4.9.0.0 |
Functor ((,,) a b) # | Since: base-4.14.0.0 |
Functor f => Functor (Alt f) # | Since: base-4.8.0.0 |
Functor f => Functor (Ap f) # | Since: base-4.12.0.0 |
Functor (Const m :: Type -> Type) # | Since: base-2.1 |
Functor m => Functor (Kleisli m a) # | Since: base-4.14.0.0 |
Arrow a => Functor (WrappedArrow a b) # | Since: base-2.1 |
Defined in Control.Applicative Methods fmap :: (a0 -> b0) -> WrappedArrow a b a0 -> WrappedArrow a b b0 Source # (<$) :: a0 -> WrappedArrow a b b0 -> WrappedArrow a b a0 Source # | |
Functor ((->) r :: Type -> Type) # | Since: base-2.1 |
Functor (K1 i c :: Type -> Type) # | Since: base-4.9.0.0 |
(Functor f, Functor g) => Functor (f :+: g) # | Since: base-4.9.0.0 |
(Functor f, Functor g) => Functor (f :*: g) # | Since: base-4.9.0.0 |
Functor ((,,,) a b c) # | Since: base-4.14.0.0 |
(Functor f, Functor g) => Functor (Sum f g) # | Since: base-4.9.0.0 |
(Functor f, Functor g) => Functor (Product f g) # | Since: base-4.9.0.0 |
Functor f => Functor (M1 i c f) # | Since: base-4.9.0.0 |
(Functor f, Functor g) => Functor (f :.: g) # | Since: base-4.9.0.0 |
(Functor f, Functor g) => Functor (Compose f g) # | 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.
Minimal complete definition
Methods
(>>=) :: 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 [] # | Since: base-2.1 |
Monad Maybe # | Since: base-2.1 |
Monad IO # | Since: base-2.1 |
Monad Par1 # | Since: base-4.9.0.0 |
Monad NonEmpty # | Since: base-4.9.0.0 |
Monad NoIO # | Since: base-4.4.0.0 |
Monad ReadP # | Since: base-2.1 |
Monad ReadPrec # | Since: base-2.1 |
Monad Down # | Since: base-4.11.0.0 |
Monad Product # | Since: base-4.8.0.0 |
Monad Sum # | Since: base-4.8.0.0 |
Monad Dual # | Since: base-4.8.0.0 |
Monad Last # | Since: base-4.8.0.0 |
Monad First # | Since: base-4.8.0.0 |
Monad STM # | Since: base-4.3.0.0 |
Monad Identity # | Since: base-4.8.0.0 |
Monad Option # | Since: base-4.9.0.0 |
Monad Last # | Since: base-4.9.0.0 |
Monad First # | Since: base-4.9.0.0 |
Monad Max # | Since: base-4.9.0.0 |
Monad Min # | Since: base-4.9.0.0 |
Monad Complex # | Since: base-4.9.0.0 |
Monad (Either e) # | Since: base-4.4.0.0 |
Monad (U1 :: Type -> Type) # | Since: base-4.9.0.0 |
Monoid a => Monad ((,) a) # | Since: base-4.9.0.0 |
Monad (ST s) # | Since: base-2.1 |
Monad (Proxy :: Type -> Type) # | Since: base-4.7.0.0 |
ArrowApply a => Monad (ArrowMonad a) # | Since: base-2.1 |
Defined in Control.Arrow Methods (>>=) :: 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 m => Monad (WrappedMonad m) # | Since: base-4.7.0.0 |
Defined in Control.Applicative Methods (>>=) :: 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 # | |
Monad (ST s) # | Since: base-2.1 |
Monad f => Monad (Rec1 f) # | Since: base-4.9.0.0 |
(Monoid a, Monoid b) => Monad ((,,) a b) # | Since: base-4.14.0.0 |
Monad f => Monad (Alt f) # | Since: base-4.8.0.0 |
Monad f => Monad (Ap f) # | Since: base-4.12.0.0 |
Monad m => Monad (Kleisli m a) # | Since: base-4.14.0.0 |
Monad ((->) r :: Type -> Type) # | Since: base-2.1 |
(Monad f, Monad g) => Monad (f :*: g) # | Since: base-4.9.0.0 |
(Monoid a, Monoid b, Monoid c) => Monad ((,,,) a b c) # | Since: base-4.14.0.0 |
(Monad f, Monad g) => Monad (Product f g) # | Since: base-4.9.0.0 |
Monad f => Monad (M1 i c f) # | Since: base-4.9.0.0 |