Control.Applicative

Control.Applicative

Copyright Conor McBride and Ross Paterson 2005
License BSD-style (see the LICENSE file in the distribution)
Maintainer libraries@haskell.org
Stability experimental
Portability portable
Safe Haskell Trustworthy
Language Haskell2010

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.

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 []

Methods

pure :: a -> [a] Source

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

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

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

Applicative Maybe

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 IO

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 U1

Methods

pure :: a -> U1 a Source

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

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

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

Applicative Par1

Methods

pure :: a -> Par1 a Source

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

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

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

Applicative ReadP

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

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

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

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 Product

Methods

pure :: a -> Product a Source

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

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

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

Applicative Sum

Methods

pure :: a -> Sum a Source

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

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

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

Applicative Dual

Methods

pure :: a -> Dual a Source

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

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

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

Applicative STM

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

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 Complex

Methods

pure :: a -> Complex a Source

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

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

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

Applicative NonEmpty

Methods

pure :: a -> NonEmpty a Source

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

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

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

Applicative Option

Methods

pure :: a -> Option a Source

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

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

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

Applicative Last

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

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 Max

Methods

pure :: a -> Max a Source

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

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

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

Applicative Min

Methods

pure :: a -> Min a Source

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

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

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

Applicative Identity

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)

Methods

pure :: a -> a -> a Source

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

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

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

Applicative (Either e)

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

Applicative f => Applicative (Rec1 f)

Methods

pure :: a -> Rec1 f a Source

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

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

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

Monoid a => Applicative ((,) a)

Methods

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

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

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

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

Applicative (ST s)

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 *)

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)

Methods

pure :: a -> ArrowMonad a a Source

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

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

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

Monad m => Applicative (WrappedMonad m)

Methods

pure :: a -> WrappedMonad m a Source

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

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

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

Applicative (ST s)

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 g) => Applicative ((:*:) f g)

Methods

pure :: a -> (f :*: g) a Source

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

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

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

(Applicative f, Applicative g) => Applicative ((:.:) f g)

Methods

pure :: a -> (f :.: g) a Source

(<*>) :: (f :.: g) (a -> b) -> (f :.: g) a -> (f :.: g) b Source

(*>) :: (f :.: g) a -> (f :.: g) b -> (f :.: g) b Source

(<*) :: (f :.: g) a -> (f :.: g) b -> (f :.: g) a Source

Applicative f => Applicative (Alt * f)

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

Monoid m => Applicative (Const * m)

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

Arrow a => Applicative (WrappedArrow a b)

Methods

pure :: a -> WrappedArrow a b a Source

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

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

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

Applicative f => Applicative (M1 i c f)

Methods

pure :: a -> M1 i c f a Source

(<*>) :: M1 i c f (a -> b) -> M1 i c f a -> M1 i c f b Source

(*>) :: M1 i c f a -> M1 i c f b -> M1 i c f b Source

(<*) :: M1 i c f a -> M1 i c f b -> M1 i c f a Source

(Applicative f, Applicative g) => Applicative (Product * f g)

Methods

pure :: a -> Product * f g a Source

(<*>) :: Product * f g (a -> b) -> Product * f g a -> Product * f g b Source

(*>) :: Product * f g a -> Product * f g b -> Product * f g b Source

(<*) :: Product * f g a -> Product * f g b -> Product * f g a Source

(Applicative f, Applicative g) => Applicative (Compose * * f g)

Methods

pure :: a -> Compose * * f g a Source

(<*>) :: Compose * * f g (a -> b) -> Compose * * f g a -> Compose * * f g b Source

(*>) :: Compose * * f g a -> Compose * * f g b -> Compose * * f g b Source

(<*) :: Compose * * f g a -> Compose * * f g b -> Compose * * f g a 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 []

Methods

empty :: [a] Source

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

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

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

Alternative Maybe

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 IO

Methods

empty :: IO a Source

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

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

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

Alternative U1

Methods

empty :: U1 a Source

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

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

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

Alternative ReadP

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
Alternative STM

Methods

empty :: STM a Source

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

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

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

Alternative Option

Methods

empty :: Option a Source

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

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

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

Alternative f => Alternative (Rec1 f)

Methods

empty :: Rec1 f a Source

(<|>) :: Rec1 f a -> Rec1 f a -> Rec1 f a Source

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

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

Alternative (Proxy *)

Methods

empty :: Proxy * a Source

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

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

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

ArrowPlus a => Alternative (ArrowMonad a)

Methods

empty :: ArrowMonad a a Source

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

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

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

MonadPlus m => Alternative (WrappedMonad m)
(Alternative f, Alternative g) => Alternative ((:*:) f g)

Methods

empty :: (f :*: g) a Source

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

some :: (f :*: g) a -> (f :*: g) [a] Source

many :: (f :*: g) a -> (f :*: g) [a] Source

(Alternative f, Applicative g) => Alternative ((:.:) f g)

Methods

empty :: (f :.: g) a Source

(<|>) :: (f :.: g) a -> (f :.: g) a -> (f :.: g) a Source

some :: (f :.: g) a -> (f :.: g) [a] Source

many :: (f :.: g) a -> (f :.: g) [a] Source

Alternative f => Alternative (Alt * f)

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)

Methods

empty :: WrappedArrow a b a Source

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

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

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

Alternative f => Alternative (M1 i c f)

Methods

empty :: M1 i c f a Source

(<|>) :: M1 i c f a -> M1 i c f a -> M1 i c f a Source

some :: M1 i c f a -> M1 i c f [a] Source

many :: M1 i c f a -> M1 i c f [a] Source

(Alternative f, Alternative g) => Alternative (Product * f g)

Methods

empty :: Product * f g a Source

(<|>) :: Product * f g a -> Product * f g a -> Product * f g a Source

some :: Product * f g a -> Product * f g [a] Source

many :: Product * f g a -> Product * f g [a] Source

(Alternative f, Applicative g) => Alternative (Compose * * f g)

Methods

empty :: Compose * * f g a Source

(<|>) :: Compose * * f g a -> Compose * * f g a -> Compose * * f g a Source

some :: Compose * * f g a -> Compose * * f g [a] Source

many :: Compose * * f g a -> Compose * * f g [a] Source

Instances

newtype Const a b Source

The Const functor.

Constructors

Const

Fields

Instances

Bifunctor (Const *)

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

Show2 (Const *)

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> Const * a b -> ShowS Source

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [Const * a b] -> ShowS Source

Read2 (Const *)

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Const * a b) Source

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Const * a b] Source

Ord2 (Const *)

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> Const * a c -> Const * b d -> Ordering Source

Eq2 (Const *)

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> Const * a c -> Const * b d -> Bool Source

Functor (Const * m)

Methods

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

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

Monoid m => Applicative (Const * m)

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)

Methods

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

foldMap :: Monoid m => (a -> m) -> Const * m a -> m 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)

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 m => (a -> m b) -> Const * m a -> m (Const * m b) Source

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

Generic1 (Const * a)

Associated Types

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

Methods

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

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

Show a => Show1 (Const * a)

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Const * a a -> ShowS Source

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Const * a a] -> ShowS Source

Read a => Read1 (Const * a)

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Const * a a) Source

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Const * a a] Source

Ord a => Ord1 (Const * a)

Methods

liftCompare :: (a -> b -> Ordering) -> Const * a a -> Const * a b -> Ordering Source

Eq a => Eq1 (Const * a)

Methods

liftEq :: (a -> b -> Bool) -> Const * a a -> Const * a b -> Bool Source

Bounded a => Bounded (Const k a b)

Methods

minBound :: Const k a b Source

maxBound :: Const k a b Source

Enum a => Enum (Const k a b)

Methods

succ :: Const k a b -> Const k a b Source

pred :: Const k a b -> Const k a b Source

toEnum :: Int -> Const k a b Source

fromEnum :: Const k a b -> Int Source

enumFrom :: Const k a b -> [Const k a b] Source

enumFromThen :: Const k a b -> Const k a b -> [Const k a b] Source

enumFromTo :: Const k a b -> Const k a b -> [Const k a b] Source

enumFromThenTo :: Const k a b -> Const k a b -> Const k a b -> [Const k a b] Source

Eq a => Eq (Const k a b)

Methods

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

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

Floating a => Floating (Const k a b)

Methods

pi :: Const k a b Source

exp :: Const k a b -> Const k a b Source

log :: Const k a b -> Const k a b Source

sqrt :: Const k a b -> Const k a b Source

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

logBase :: Const k a b -> Const k a b -> Const k a b Source

sin :: Const k a b -> Const k a b Source

cos :: Const k a b -> Const k a b Source

tan :: Const k a b -> Const k a b Source

asin :: Const k a b -> Const k a b Source

acos :: Const k a b -> Const k a b Source

atan :: Const k a b -> Const k a b Source

sinh :: Const k a b -> Const k a b Source

cosh :: Const k a b -> Const k a b Source

tanh :: Const k a b -> Const k a b Source

asinh :: Const k a b -> Const k a b Source

acosh :: Const k a b -> Const k a b Source

atanh :: Const k a b -> Const k a b Source

log1p :: Const k a b -> Const k a b Source

expm1 :: Const k a b -> Const k a b Source

log1pexp :: Const k a b -> Const k a b Source

log1mexp :: Const k a b -> Const k a b Source

Fractional a => Fractional (Const k a b)

Methods

(/) :: Const k a b -> Const k a b -> Const k a b Source

recip :: Const k a b -> Const k a b Source

fromRational :: Rational -> Const k a b Source

Integral a => Integral (Const k a b)

Methods

quot :: Const k a b -> Const k a b -> Const k a b Source

rem :: Const k a b -> Const k a b -> Const k a b Source

div :: Const k a b -> Const k a b -> Const k a b Source

mod :: Const k a b -> Const k a b -> Const k a b Source

quotRem :: Const k a b -> Const k a b -> (Const k a b, Const k a b) Source

divMod :: Const k a b -> Const k a b -> (Const k a b, Const k a b) Source

toInteger :: Const k a b -> Integer Source

Num a => Num (Const k a b)

Methods

(+) :: Const k a b -> Const k a b -> Const k a b Source

(-) :: Const k a b -> Const k a b -> Const k a b Source

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

negate :: Const k a b -> Const k a b Source

abs :: Const k a b -> Const k a b Source

signum :: Const k a b -> Const k a b Source

fromInteger :: Integer -> Const k a b Source

Ord a => Ord (Const k a b)

Methods

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

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

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

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

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

max :: Const k a b -> Const k a b -> Const k a b Source

min :: Const k a b -> Const k a b -> Const k a b Source

Read a => Read (Const k a b)

This instance would be equivalent to the derived instances of the Const newtype if the runConst field were removed

Real a => Real (Const k a b)

Methods

toRational :: Const k a b -> Rational Source

RealFloat a => RealFloat (Const k a b)

Methods

floatRadix :: Const k a b -> Integer Source

floatDigits :: Const k a b -> Int Source

floatRange :: Const k a b -> (Int, Int) Source

decodeFloat :: Const k a b -> (Integer, Int) Source

encodeFloat :: Integer -> Int -> Const k a b Source

exponent :: Const k a b -> Int Source

significand :: Const k a b -> Const k a b Source

scaleFloat :: Int -> Const k a b -> Const k a b Source

isNaN :: Const k a b -> Bool Source

isInfinite :: Const k a b -> Bool Source

isDenormalized :: Const k a b -> Bool Source

isNegativeZero :: Const k a b -> Bool Source

isIEEE :: Const k a b -> Bool Source

atan2 :: Const k a b -> Const k a b -> Const k a b Source

RealFrac a => RealFrac (Const k a b)

Methods

properFraction :: Integral b => Const k a b -> (b, Const k a b) Source

truncate :: Integral b => Const k a b -> b Source

round :: Integral b => Const k a b -> b Source

ceiling :: Integral b => Const k a b -> b Source

floor :: Integral b => Const k a b -> b Source

Show a => Show (Const k a b)

This instance would be equivalent to the derived instances of the Const newtype if the runConst field were removed

Methods

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

show :: Const k a b -> String Source

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

Ix a => Ix (Const k a b)

Methods

range :: (Const k a b, Const k a b) -> [Const k a b] Source

index :: (Const k a b, Const k a b) -> Const k a b -> Int Source

unsafeIndex :: (Const k a b, Const k a b) -> Const k a b -> Int

inRange :: (Const k a b, Const k a b) -> Const k a b -> Bool Source

rangeSize :: (Const k a b, Const k a b) -> Int Source

unsafeRangeSize :: (Const k a b, Const k a b) -> Int

IsString a => IsString (Const * a b)

Methods

fromString :: String -> Const * a b Source

Generic (Const k a b)

Associated Types

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

Methods

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

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

Semigroup a => Semigroup (Const k a b)

Methods

(<>) :: Const k a b -> Const k a b -> Const k a b Source

sconcat :: NonEmpty (Const k a b) -> Const k a b Source

stimes :: Integral b => b -> Const k a b -> Const k a b Source

Monoid a => Monoid (Const k a b)

Methods

mempty :: Const k a b Source

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

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

FiniteBits a => FiniteBits (Const k a b)
Bits a => Bits (Const k a b)

Methods

(.&.) :: Const k a b -> Const k a b -> Const k a b Source

(.|.) :: Const k a b -> Const k a b -> Const k a b Source

xor :: Const k a b -> Const k a b -> Const k a b Source

complement :: Const k a b -> Const k a b Source

shift :: Const k a b -> Int -> Const k a b Source

rotate :: Const k a b -> Int -> Const k a b Source

zeroBits :: Const k a b Source

bit :: Int -> Const k a b Source

setBit :: Const k a b -> Int -> Const k a b Source

clearBit :: Const k a b -> Int -> Const k a b Source

complementBit :: Const k a b -> Int -> Const k a b Source

testBit :: Const k a b -> Int -> Bool Source

bitSizeMaybe :: Const k a b -> Maybe Int Source

bitSize :: Const k a b -> Int Source

isSigned :: Const k a b -> Bool Source

shiftL :: Const k a b -> Int -> Const k a b Source

unsafeShiftL :: Const k a b -> Int -> Const k a b Source

shiftR :: Const k a b -> Int -> Const k a b Source

unsafeShiftR :: Const k a b -> Int -> Const k a b Source

rotateL :: Const k a b -> Int -> Const k a b Source

rotateR :: Const k a b -> Int -> Const k a b Source

popCount :: Const k a b -> Int Source

Storable a => Storable (Const k a b)

Methods

sizeOf :: Const k a b -> Int Source

alignment :: Const k a b -> Int Source

peekElemOff :: Ptr (Const k a b) -> Int -> IO (Const k a b) Source

pokeElemOff :: Ptr (Const k a b) -> Int -> Const k a b -> IO () Source

peekByteOff :: Ptr b -> Int -> IO (Const k a b) Source

pokeByteOff :: Ptr b -> Int -> Const k a b -> IO () Source

peek :: Ptr (Const k a b) -> IO (Const k a b) Source

poke :: Ptr (Const k a b) -> Const k a b -> IO () Source

type Rep1 (Const * a)
type Rep1 (Const * a) = D1 (MetaData "Const" "Data.Functor.Const" "base" True) (C1 (MetaCons "Const" PrefixI True) (S1 (MetaSel (Just Symbol "getConst") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep (Const k a b)
type Rep (Const k a b) = D1 (MetaData "Const" "Data.Functor.Const" "base" True) (C1 (MetaCons "Const" PrefixI True) (S1 (MetaSel (Just Symbol "getConst") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype WrappedMonad m a Source

Constructors

WrapMonad

Fields

Instances

Monad m => Monad (WrappedMonad m)

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

fail :: String -> WrappedMonad m a Source

Monad m => Functor (WrappedMonad m)

Methods

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

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

Monad m => Applicative (WrappedMonad m)

Methods

pure :: a -> WrappedMonad m a Source

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

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

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

Generic1 (WrappedMonad m)

Associated Types

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

Methods

from1 :: WrappedMonad m a -> Rep1 (WrappedMonad m) a Source

to1 :: Rep1 (WrappedMonad m) a -> WrappedMonad m a Source

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

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)
type Rep1 (WrappedMonad m) = D1 (MetaData "WrappedMonad" "Control.Applicative" "base" True) (C1 (MetaCons "WrapMonad" PrefixI True) (S1 (MetaSel (Just Symbol "unwrapMonad") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 m)))
type Rep (WrappedMonad m a)
type Rep (WrappedMonad m a) = D1 (MetaData "WrappedMonad" "Control.Applicative" "base" True) (C1 (MetaCons "WrapMonad" PrefixI True) (S1 (MetaSel (Just Symbol "unwrapMonad") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (m a))))

newtype WrappedArrow a b c Source

Constructors

WrapArrow

Fields

Instances

Arrow a => Functor (WrappedArrow a b)

Methods

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

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

Arrow a => Applicative (WrappedArrow a b)

Methods

pure :: a -> WrappedArrow a b a Source

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

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

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

Generic1 (WrappedArrow a b)

Associated Types

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

Methods

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

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

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

Methods

empty :: WrappedArrow a b a Source

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

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

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

Generic (WrappedArrow a b c)

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)
type Rep1 (WrappedArrow a b) = D1 (MetaData "WrappedArrow" "Control.Applicative" "base" True) (C1 (MetaCons "WrapArrow" PrefixI True) (S1 (MetaSel (Just Symbol "unwrapArrow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 (a b))))
type Rep (WrappedArrow a b c)
type Rep (WrappedArrow a b c) = D1 (MetaData "WrappedArrow" "Control.Applicative" "base" True) (C1 (MetaCons "WrapArrow" PrefixI True) (S1 (MetaSel (Just Symbol "unwrapArrow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (a b c))))

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

Methods

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

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

Applicative ZipList

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

Foldable ZipList

Methods

fold :: Monoid m => ZipList m -> m Source

foldMap :: Monoid m => (a -> m) -> ZipList a -> m Source

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

foldr' :: (a -> b -> b) -> b -> ZipList a -> b Source

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

foldl' :: (b -> a -> b) -> b -> ZipList a -> b Source

foldr1 :: (a -> a -> a) -> ZipList a -> a Source

foldl1 :: (a -> a -> a) -> ZipList a -> a Source

toList :: ZipList a -> [a] Source

null :: ZipList a -> Bool Source

length :: ZipList a -> Int Source

elem :: Eq a => a -> ZipList a -> Bool Source

maximum :: Ord a => ZipList a -> a Source

minimum :: Ord a => ZipList a -> a Source

sum :: Num a => ZipList a -> a Source

product :: Num a => ZipList a -> a Source

Traversable ZipList

Methods

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

sequenceA :: Applicative f => ZipList (f a) -> f (ZipList a) Source

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

sequence :: Monad m => ZipList (m a) -> m (ZipList a) Source

Generic1 ZipList

Associated Types

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

Methods

from1 :: ZipList a -> Rep1 ZipList a Source

to1 :: Rep1 ZipList a -> ZipList a Source

Eq a => Eq (ZipList a)

Methods

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

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

Ord a => Ord (ZipList a)

Methods

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

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

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

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

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

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

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

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

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
type Rep1 ZipList = D1 (MetaData "ZipList" "Control.Applicative" "base" True) (C1 (MetaCons "ZipList" PrefixI True) (S1 (MetaSel (Just Symbol "getZipList") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 [])))
type Rep (ZipList a)
type Rep (ZipList a) = D1 (MetaData "ZipList" "Control.Applicative" "base" True) (C1 (MetaCons "ZipList" PrefixI True) (S1 (MetaSel (Just Symbol "getZipList") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [a])))

Utility functions

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

An infix synonym for fmap.

The name of this operator is an allusion to $. Note the similarities between their types:

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

Whereas $ is function application, <$> is function application lifted over a Functor.

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.

© The University of Glasgow and others
Licensed under a BSD-style license (see top of the page).
https://downloads.haskell.org/~ghc/8.0.1/docs/html/libraries/base-4.9.0.0/Control-Applicative.html

在线笔记
App下载
App下载

扫描二维码

下载编程狮App

公众号
微信公众号

编程狮公众号

意见反馈
返回顶部