Portability | portable |
---|---|
Stability | experimental |
Maintainer | libraries@haskell.org |
Safe Haskell | Trustworthy |
This module describes a structure intermediate between a functor and
a monad (technically, a strong lax monoidal functor). Compared with
monads, this interface lacks the full power of the binding operation
>>=
, but
- it has more instances.
- it is sufficient for many uses, e.g. context-free parsing, or the
Traversable
class. - instances can perform analysis of computations before they are executed, and thus produce shared optimizations.
This interface was introduced for parsers by Niklas Röjemo, because it admits more sharing than the monadic interface. The names here are mostly based on parsing work by Doaitse Swierstra.
For more details, see Applicative Programming with Effects, by Conor McBride and Ross Paterson, online at http://www.soi.city.ac.uk/~ross/papers/Applicative.html.
- class Functor f => Applicative f where
- class Applicative f => Alternative f where
- newtype Const a b = Const {
- getConst :: a
- newtype WrappedMonad m a = WrapMonad {
- unwrapMonad :: m a
- newtype WrappedArrow a b c = WrapArrow {
- unwrapArrow :: a b c
- newtype ZipList a = ZipList {
- getZipList :: [a]
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- (<$) :: Functor f => a -> f b -> f a
- (<**>) :: Applicative f => f a -> f (a -> b) -> f b
- liftA :: Applicative f => (a -> b) -> f a -> f b
- liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c
- liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d
- optional :: Alternative f => f a -> f (Maybe a)
Applicative functors
class Functor f => Applicative f whereSource
A functor with application, providing operations to
A minimal complete definition must include implementations of these functions satisfying the following laws:
- identity
-
pure
id
<*>
v = v - composition
-
pure
(.)<*>
u<*>
v<*>
w = u<*>
(v<*>
w) - homomorphism
-
pure
f<*>
pure
x =pure
(f x) - interchange
-
u
<*>
pure
y =pure
($
y)<*>
u
The other methods have the following default definitions, which may be overridden with equivalent specialized implementations:
u*>
v =pure
(const
id
)<*>
u<*>
v u<*
v =pure
const
<*>
u<*>
v
As a consequence of these laws, the Functor
instance for f
will satisfy
fmap
f x =pure
f<*>
x
If f
is also a Monad
, it should satisfy
and
pure
= return
(
(which implies that <*>
) = ap
pure
and <*>
satisfy the
applicative functor laws).
Lift a value.
(<*>) :: f (a -> b) -> f a -> f bSource
Sequential application.
(*>) :: f a -> f b -> f bSource
Sequence actions, discarding the value of the first argument.
(<*) :: f a -> f b -> f aSource
Sequence actions, discarding the value of the second argument.
Applicative [] | |
Applicative IO | |
Applicative Maybe | |
Applicative STM | |
Applicative ZipList | |
Applicative Id | |
Applicative ((->) a) | |
Applicative (Either e) | |
Monoid a => Applicative ((,) a) | |
Applicative (ST s) | |
Applicative (ST s) | |
Monad m => Applicative (WrappedMonad m) | |
Monoid m => Applicative (Const m) | |
Applicative (StateR s) | |
Applicative (StateL s) | |
Arrow a => Applicative (WrappedArrow a b) |
Alternatives
class Applicative f => Alternative f whereSource
A monoid on applicative functors.
Minimal complete definition: empty
and <|>
.
If defined, some
and many
should be the least solutions
of the equations:
The identity of <|>
(<|>) :: f a -> f a -> f aSource
An associative binary operation
One or more.
Zero or more.
Alternative [] | |
Alternative Maybe | |
Alternative STM | |
MonadPlus m => Alternative (WrappedMonad m) | |
(ArrowZero a, ArrowPlus a) => Alternative (WrappedArrow a b) |
Instances
newtype WrappedMonad m a Source
WrapMonad | |
|
Monad m => Functor (WrappedMonad m) | |
Monad m => Applicative (WrappedMonad m) | |
MonadPlus m => Alternative (WrappedMonad m) |
newtype WrappedArrow a b c Source
WrapArrow | |
|
Arrow a => Functor (WrappedArrow a b) | |
Arrow a => Applicative (WrappedArrow a b) | |
(ArrowZero a, ArrowPlus a) => Alternative (WrappedArrow a b) |
Lists, but with an Applicative
functor based on zipping, so that
f<$>
ZipList
xs1<*>
...<*>
ZipList
xsn =ZipList
(zipWithn f xs1 ... xsn)
ZipList | |
|
Utility functions
(<**>) :: Applicative f => f a -> f (a -> b) -> f bSource
A variant of <*>
with the arguments reversed.
liftA :: Applicative f => (a -> b) -> f a -> f bSource
liftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f cSource
Lift a binary function to actions.
liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f dSource
Lift a ternary function to actions.
optional :: Alternative f => f a -> f (Maybe a)Source
One or none.