base-4.8.1.0: Basic libraries

CopyrightConor McBride and Ross Paterson 2005
LicenseBSD-style (see the LICENSE file in the distribution)
Maintainerlibraries@haskell.org
Stabilityexperimental
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Control.Applicative

Contents

Description

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.

Synopsis

Applicative functors

class Functor f => Applicative f where Source

A functor with application, providing operations to

  • embed pure expressions (pure), and
  • sequence computations and combine their results (<*>).

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:

As a consequence of these laws, the Functor instance for f will satisfy

If f is also a Monad, it should satisfy

(which implies that pure and <*> satisfy the applicative functor laws).

Minimal complete definition

pure, (<*>)

Methods

pure :: a -> f a Source

Lift a value.

(<*>) :: f (a -> b) -> f a -> f b infixl 4 Source

Sequential application.

(*>) :: f a -> f b -> f b infixl 4 Source

Sequence actions, discarding the value of the first argument.

(<*) :: f a -> f b -> f a infixl 4 Source

Sequence actions, discarding the value of the second argument.

Instances

Applicative [] Source 

Methods

pure :: a -> [a] Source

(<*>) :: [a -> b] -> [a] -> [b] Source

(*>) :: [a] -> [b] -> [b] Source

(<*) :: [a] -> [b] -> [a] Source

Applicative IO Source 

Methods

pure :: a -> IO a Source

(<*>) :: IO (a -> b) -> IO a -> IO b Source

(*>) :: IO a -> IO b -> IO b Source

(<*) :: IO a -> IO b -> IO a Source

Applicative Maybe Source 

Methods

pure :: a -> Maybe a Source

(<*>) :: Maybe (a -> b) -> Maybe a -> Maybe b Source

(*>) :: Maybe a -> Maybe b -> Maybe b Source

(<*) :: Maybe a -> Maybe b -> Maybe a Source

Applicative ReadP Source 

Methods

pure :: a -> ReadP a Source

(<*>) :: ReadP (a -> b) -> ReadP a -> ReadP b Source

(*>) :: ReadP a -> ReadP b -> ReadP b Source

(<*) :: ReadP a -> ReadP b -> ReadP a Source

Applicative ReadPrec Source 

Methods

pure :: a -> ReadPrec a Source

(<*>) :: ReadPrec (a -> b) -> ReadPrec a -> ReadPrec b Source

(*>) :: ReadPrec a -> ReadPrec b -> ReadPrec b Source

(<*) :: ReadPrec a -> ReadPrec b -> ReadPrec a Source

Applicative Last Source 

Methods

pure :: a -> Last a Source

(<*>) :: Last (a -> b) -> Last a -> Last b Source

(*>) :: Last a -> Last b -> Last b Source

(<*) :: Last a -> Last b -> Last a Source

Applicative First Source 

Methods

pure :: a -> First a Source

(<*>) :: First (a -> b) -> First a -> First b Source

(*>) :: First a -> First b -> First b Source

(<*) :: First a -> First b -> First a Source

Applicative STM Source 

Methods

pure :: a -> STM a Source

(<*>) :: STM (a -> b) -> STM a -> STM b Source

(*>) :: STM a -> STM b -> STM b Source

(<*) :: STM a -> STM b -> STM a Source

Applicative ZipList Source 

Methods

pure :: a -> ZipList a Source

(<*>) :: ZipList (a -> b) -> ZipList a -> ZipList b Source

(*>) :: ZipList a -> ZipList b -> ZipList b Source

(<*) :: ZipList a -> ZipList b -> ZipList a Source

Applicative Identity Source 

Methods

pure :: a -> Identity a Source

(<*>) :: Identity (a -> b) -> Identity a -> Identity b Source

(*>) :: Identity a -> Identity b -> Identity b Source

(<*) :: Identity a -> Identity b -> Identity a Source

Applicative ((->) a) Source 

Methods

pure :: b -> (->) a b Source

(<*>) :: (->) a (b -> c) -> (->) a b -> (->) a c Source

(*>) :: (->) a b -> (->) a c -> (->) a c Source

(<*) :: (->) a b -> (->) a c -> (->) a b Source

Applicative (Either e) Source 

Methods

pure :: a -> Either e a Source

(<*>) :: Either e (a -> b) -> Either e a -> Either e b Source

(*>) :: Either e a -> Either e b -> Either e b Source

(<*) :: Either e a -> Either e b -> Either e a Source

Monoid a => Applicative ((,) a) Source 

Methods

pure :: b -> (a, b) Source

(<*>) :: (a, b -> c) -> (a, b) -> (a, c) Source

(*>) :: (a, b) -> (a, c) -> (a, c) Source

(<*) :: (a, b) -> (a, c) -> (a, b) Source

Applicative (ST s) Source 

Methods

pure :: a -> ST s a Source

(<*>) :: ST s (a -> b) -> ST s a -> ST s b Source

(*>) :: ST s a -> ST s b -> ST s b Source

(<*) :: ST s a -> ST s b -> ST s a Source

Applicative (Proxy *) Source 

Methods

pure :: a -> Proxy * a Source

(<*>) :: Proxy * (a -> b) -> Proxy * a -> Proxy * b Source

(*>) :: Proxy * a -> Proxy * b -> Proxy * b Source

(<*) :: Proxy * a -> Proxy * b -> Proxy * a Source

Arrow a => Applicative (ArrowMonad a) Source 

Methods

pure :: b -> ArrowMonad a b Source

(<*>) :: ArrowMonad a (b -> c) -> ArrowMonad a b -> ArrowMonad a c Source

(*>) :: ArrowMonad a b -> ArrowMonad a c -> ArrowMonad a c Source

(<*) :: ArrowMonad a b -> ArrowMonad a c -> ArrowMonad a b Source

Monad m => Applicative (WrappedMonad m) Source 
Monoid m => Applicative (Const m) Source 

Methods

pure :: a -> Const m a Source

(<*>) :: Const m (a -> b) -> Const m a -> Const m b Source

(*>) :: Const m a -> Const m b -> Const m b Source

(<*) :: Const m a -> Const m b -> Const m a Source

Applicative (ST s) Source 

Methods

pure :: a -> ST s a Source

(<*>) :: ST s (a -> b) -> ST s a -> ST s b Source

(*>) :: ST s a -> ST s b -> ST s b Source

(<*) :: ST s a -> ST s b -> ST s a Source

Applicative f => Applicative (Alt * f) Source 

Methods

pure :: a -> Alt * f a Source

(<*>) :: Alt * f (a -> b) -> Alt * f a -> Alt * f b Source

(*>) :: Alt * f a -> Alt * f b -> Alt * f b Source

(<*) :: Alt * f a -> Alt * f b -> Alt * f a Source

Arrow a => Applicative (WrappedArrow a b) Source 

Methods

pure :: c -> WrappedArrow a b c Source

(<*>) :: WrappedArrow a b (c -> d) -> WrappedArrow a b c -> WrappedArrow a b d Source

(*>) :: WrappedArrow a b c -> WrappedArrow a b d -> WrappedArrow a b d Source

(<*) :: WrappedArrow a b c -> WrappedArrow a b d -> WrappedArrow a b c Source

Alternatives

class Applicative f => Alternative f where Source

A monoid on applicative functors.

If defined, some and many should be the least solutions of the equations:

  • some v = (:) <$> v <*> many v
  • many v = some v <|> pure []

Minimal complete definition

empty, (<|>)

Methods

empty :: f a Source

The identity of <|>

(<|>) :: f a -> f a -> f a infixl 3 Source

An associative binary operation

some :: f a -> f [a] Source

One or more.

many :: f a -> f [a] Source

Zero or more.

Instances

Alternative [] Source 

Methods

empty :: [a] Source

(<|>) :: [a] -> [a] -> [a] Source

some :: [a] -> [[a]] Source

many :: [a] -> [[a]] Source

Alternative Maybe Source 

Methods

empty :: Maybe a Source

(<|>) :: Maybe a -> Maybe a -> Maybe a Source

some :: Maybe a -> Maybe [a] Source

many :: Maybe a -> Maybe [a] Source

Alternative ReadP Source 

Methods

empty :: ReadP a Source

(<|>) :: ReadP a -> ReadP a -> ReadP a Source

some :: ReadP a -> ReadP [a] Source

many :: ReadP a -> ReadP [a] Source

Alternative ReadPrec Source 
Alternative STM Source 

Methods

empty :: STM a Source

(<|>) :: STM a -> STM a -> STM a Source

some :: STM a -> STM [a] Source

many :: STM a -> STM [a] Source

ArrowPlus a => Alternative (ArrowMonad a) Source 
MonadPlus m => Alternative (WrappedMonad m) Source 
Alternative f => Alternative (Alt * f) Source 

Methods

empty :: Alt * f a Source

(<|>) :: Alt * f a -> Alt * f a -> Alt * f a Source

some :: Alt * f a -> Alt * f [a] Source

many :: Alt * f a -> Alt * f [a] Source

(ArrowZero a, ArrowPlus a) => Alternative (WrappedArrow a b) Source 

Methods

empty :: WrappedArrow a b c Source

(<|>) :: WrappedArrow a b c -> WrappedArrow a b c -> WrappedArrow a b c Source

some :: WrappedArrow a b c -> WrappedArrow a b [c] Source

many :: WrappedArrow a b c -> WrappedArrow a b [c] Source

Instances

newtype Const a b Source

Constructors

Const 

Fields

Instances

Bifunctor Const Source 

Methods

bimap :: (a -> b) -> (c -> d) -> Const a c -> Const b d Source

first :: (a -> b) -> Const a c -> Const b c Source

second :: (b -> c) -> Const a b -> Const a c Source

Functor (Const m) Source 

Methods

fmap :: (a -> b) -> Const m a -> Const m b Source

(<$) :: a -> Const m b -> Const m a Source

Monoid m => Applicative (Const m) Source 

Methods

pure :: a -> Const m a Source

(<*>) :: Const m (a -> b) -> Const m a -> Const m b Source

(*>) :: Const m a -> Const m b -> Const m b Source

(<*) :: Const m a -> Const m b -> Const m a Source

Foldable (Const m) Source 

Methods

fold :: Monoid a => Const m a -> a Source

foldMap :: Monoid b => (a -> b) -> Const m a -> b Source

foldr :: (a -> b -> b) -> b -> Const m a -> b Source

foldr' :: (a -> b -> b) -> b -> Const m a -> b Source

foldl :: (b -> a -> b) -> b -> Const m a -> b Source

foldl' :: (b -> a -> b) -> b -> Const m a -> b Source

foldr1 :: (a -> a -> a) -> Const m a -> a Source

foldl1 :: (a -> a -> a) -> Const m a -> a Source

toList :: Const m a -> [a] Source

null :: Const m a -> Bool Source

length :: Const m a -> Int Source

elem :: Eq a => a -> Const m a -> Bool Source

maximum :: Ord a => Const m a -> a Source

minimum :: Ord a => Const m a -> a Source

sum :: Num a => Const m a -> a Source

product :: Num a => Const m a -> a Source

Traversable (Const m) Source 

Methods

traverse :: Applicative f => (a -> f b) -> Const m a -> f (Const m b) Source

sequenceA :: Applicative f => Const m (f a) -> f (Const m a) Source

mapM :: Monad b => (a -> b c) -> Const m a -> b (Const m c) Source

sequence :: Monad a => Const m (a b) -> a (Const m b) Source

Generic1 (Const a) Source 

Associated Types

type Rep1 (Const a :: * -> *) :: * -> * Source

Methods

from1 :: Const a b -> Rep1 (Const a) b Source

to1 :: Rep1 (Const a) b -> Const a b Source

Eq a => Eq (Const a b) Source 

Methods

(==) :: Const a b -> Const a b -> Bool

(/=) :: Const a b -> Const a b -> Bool

Ord a => Ord (Const a b) Source 

Methods

compare :: Const a b -> Const a b -> Ordering

(<) :: Const a b -> Const a b -> Bool

(<=) :: Const a b -> Const a b -> Bool

(>) :: Const a b -> Const a b -> Bool

(>=) :: Const a b -> Const a b -> Bool

max :: Const a b -> Const a b -> Const a b

min :: Const a b -> Const a b -> Const a b

Read a => Read (Const a b) Source 
Show a => Show (Const a b) Source 

Methods

showsPrec :: Int -> Const a b -> ShowS Source

show :: Const a b -> String Source

showList :: [Const a b] -> ShowS Source

Generic (Const a b) Source 

Associated Types

type Rep (Const a b) :: * -> * Source

Methods

from :: Const a b -> Rep (Const a b) x Source

to :: Rep (Const a b) x -> Const a b Source

Monoid a => Monoid (Const a b) Source 

Methods

mempty :: Const a b Source

mappend :: Const a b -> Const a b -> Const a b Source

mconcat :: [Const a b] -> Const a b Source

type Rep1 (Const a) Source 
type Rep (Const a b) Source 

newtype WrappedMonad m a Source

Constructors

WrapMonad 

Fields

Instances

Monad m => Monad (WrappedMonad m) Source 
Monad m => Functor (WrappedMonad m) Source 

Methods

fmap :: (a -> b) -> WrappedMonad m a -> WrappedMonad m b Source

(<$) :: a -> WrappedMonad m b -> WrappedMonad m a Source

Monad m => Applicative (WrappedMonad m) Source 
Generic1 (WrappedMonad m) Source 

Associated Types

type Rep1 (WrappedMonad m :: * -> *) :: * -> * Source

MonadPlus m => Alternative (WrappedMonad m) Source 
Generic (WrappedMonad m a) Source 

Associated Types

type Rep (WrappedMonad m a) :: * -> * Source

Methods

from :: WrappedMonad m a -> Rep (WrappedMonad m a) x Source

to :: Rep (WrappedMonad m a) x -> WrappedMonad m a Source

type Rep1 (WrappedMonad m) Source 
type Rep (WrappedMonad m a) Source 

newtype WrappedArrow a b c Source

Constructors

WrapArrow 

Fields

Instances

Arrow a => Functor (WrappedArrow a b) Source 

Methods

fmap :: (c -> d) -> WrappedArrow a b c -> WrappedArrow a b d Source

(<$) :: c -> WrappedArrow a b d -> WrappedArrow a b c Source

Arrow a => Applicative (WrappedArrow a b) Source 

Methods

pure :: c -> WrappedArrow a b c Source

(<*>) :: WrappedArrow a b (c -> d) -> WrappedArrow a b c -> WrappedArrow a b d Source

(*>) :: WrappedArrow a b c -> WrappedArrow a b d -> WrappedArrow a b d Source

(<*) :: WrappedArrow a b c -> WrappedArrow a b d -> WrappedArrow a b c Source

Generic1 (WrappedArrow a b) Source 

Associated Types

type Rep1 (WrappedArrow a b :: * -> *) :: * -> * Source

Methods

from1 :: WrappedArrow a b c -> Rep1 (WrappedArrow a b) c Source

to1 :: Rep1 (WrappedArrow a b) c -> WrappedArrow a b c Source

(ArrowZero a, ArrowPlus a) => Alternative (WrappedArrow a b) Source 

Methods

empty :: WrappedArrow a b c Source

(<|>) :: WrappedArrow a b c -> WrappedArrow a b c -> WrappedArrow a b c Source

some :: WrappedArrow a b c -> WrappedArrow a b [c] Source

many :: WrappedArrow a b c -> WrappedArrow a b [c] Source

Generic (WrappedArrow a b c) Source 

Associated Types

type Rep (WrappedArrow a b c) :: * -> * Source

Methods

from :: WrappedArrow a b c -> Rep (WrappedArrow a b c) x Source

to :: Rep (WrappedArrow a b c) x -> WrappedArrow a b c Source

type Rep1 (WrappedArrow a b) Source 
type Rep (WrappedArrow a b c) Source 

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 

Fields

Instances

Functor ZipList Source 

Methods

fmap :: (a -> b) -> ZipList a -> ZipList b Source

(<$) :: a -> ZipList b -> ZipList a Source

Applicative ZipList Source 

Methods

pure :: a -> ZipList a Source

(<*>) :: ZipList (a -> b) -> ZipList a -> ZipList b Source

(*>) :: ZipList a -> ZipList b -> ZipList b Source

(<*) :: ZipList a -> ZipList b -> ZipList a Source

Generic1 ZipList Source 

Associated Types

type Rep1 (ZipList :: * -> *) :: * -> * Source

Eq a => Eq (ZipList a) Source 

Methods

(==) :: ZipList a -> ZipList a -> Bool

(/=) :: ZipList a -> ZipList a -> Bool

Ord a => Ord (ZipList a) Source 

Methods

compare :: ZipList a -> ZipList a -> Ordering

(<) :: ZipList a -> ZipList a -> Bool

(<=) :: ZipList a -> ZipList a -> Bool

(>) :: ZipList a -> ZipList a -> Bool

(>=) :: ZipList a -> ZipList a -> Bool

max :: ZipList a -> ZipList a -> ZipList a

min :: ZipList a -> ZipList a -> ZipList a

Read a => Read (ZipList a) Source 
Show a => Show (ZipList a) Source 
Generic (ZipList a) Source 

Associated Types

type Rep (ZipList a) :: * -> * Source

Methods

from :: ZipList a -> Rep (ZipList a) x Source

to :: Rep (ZipList a) x -> ZipList a Source

type Rep1 ZipList Source 
type Rep (ZipList a) Source 

Utility functions

(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 Source

An infix synonym for fmap.

Examples

Convert from a Maybe Int to a Maybe String using show:

>>> show <$> Nothing
Nothing
>>> show <$> Just 3
Just "3"

Convert from an Either Int Int to an 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)

(<$) :: Functor f => a -> f b -> f a Source

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 b infixl 4 Source

A variant of <*> with the arguments reversed.

liftA :: Applicative f => (a -> b) -> f a -> f b Source

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 c Source

Lift a binary function to actions.

liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d Source

Lift a ternary function to actions.

optional :: Alternative f => f a -> f (Maybe a) Source

One or none.