base-4.2.0.0: Basic librariesSource codeContentsIndex
Control.Applicative
Portabilityportable
Stabilityexperimental
Maintainerlibraries@haskell.org
Contents
Applicative functors
Alternatives
Instances
Utility functions
Description

This module describes a structure intermediate between a functor and a monad: it provides pure expressions and sequencing, but no binding. (Technically, a strong lax monoidal functor.) 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.

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 recent parsing work by Doaitse Swierstra.

This class is also useful with instances of the Data.Traversable.Traversable class.

Synopsis
class Functor f => Applicative f where
pure :: a -> f a
(<*>) :: f (a -> b) -> f a -> f b
(*>) :: f a -> f b -> f b
(<*) :: f a -> f b -> f a
class Applicative f => Alternative f where
empty :: f a
(<|>) :: f a -> f a -> f a
some :: f a -> f [a]
many :: f a -> f [a]
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.

Instances should satisfy 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
ignore left value
u *> v = pure (const id) <*> u <*> v
ignore right value
u <* v = pure const <*> u <*> v

The Functor instance should satisfy

      fmap f x = pure f <*> x

If f is also a Monad, define pure = return and (<*>) = ap.

Minimal complete definition: pure and <*>.

Methods
pure :: a -> f aSource
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.
show/hide Instances
Alternatives
class Applicative f => Alternative f whereSource

A monoid on applicative functors.

Minimal complete definition: empty and <|>.

some and many should be the least solutions of the equations:

Methods
empty :: f aSource
The identity of <|>
(<|>) :: f a -> f a -> f aSource
An associative binary operation
some :: f a -> f [a]Source
One or more.
many :: f a -> f [a]Source
Zero or more.
show/hide Instances
Instances
newtype Const a b Source
Constructors
Const
getConst :: a
show/hide Instances
newtype WrappedMonad m a Source
Constructors
WrapMonad
unwrapMonad :: m a
show/hide Instances
newtype WrappedArrow a b c Source
Constructors
WrapArrow
unwrapArrow :: a b c
show/hide Instances
newtype ZipList a Source

Lists, but with an Applicative functor based on zipping, so that

f <$> ZipList xs1 <*> ... <*> ZipList xsn = ZipList (zipWithn f xs1 ... xsn)
Constructors
ZipList
getZipList :: [a]
show/hide Instances
Utility functions
(<$>) :: Functor f => (a -> b) -> f a -> f bSource
An infix synonym for fmap.
(<$) :: Functor f => a -> f b -> f aSource
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.
(<**>) :: 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
Lift a function to actions. This function may be used as a value for fmap in a Functor instance.
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.
Produced by Haddock version 2.6.0