base-4.10.1.0: Basic libraries

CopyrightConor McBride and Ross Paterson 2005
LicenseBSD-style (see the LICENSE file in the distribution)
Maintainer[email protected]
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 (<*> and liftA2).

A minimal complete definition must include implementations of pure and of either <*> or liftA2. If it defines both, then they must behave the same as their default definitions:

(<*>) = liftA2 id liftA2 f x y = f <$> x <*> y

Further, any definition must satisfy the following:

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

It may be useful to note that supposing

forall x y. p (q x y) = f x . g y

it follows from the above that

liftA2 p (liftA2 q u v) = liftA2 f u . liftA2 g v

If f is also a Monad, it should satisfy

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

Minimal complete definition

pure, ((<*>) | liftA2)

Methods

pure :: a -> f a Source #

Lift a value.

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

Sequential application.

A few functors support an implementation of <*> that is more efficient than the default one.

liftA2 :: (a -> b -> c) -> f a -> f b -> f c Source #

Lift a binary function to actions.

Some functors support an implementation of liftA2 that is more efficient than the default one. In particular, if fmap is an expensive operation, it is likely better to use liftA2 than to fmap over the structure and then use <*>.

(*>) :: 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 [] #

Since: 2.1

Methods

pure :: a -> [a] Source #

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

liftA2 :: (a -> b -> c) -> [a] -> [b] -> [c] Source #

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

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

Applicative Maybe #

Since: 2.1

Methods

pure :: a -> Maybe a Source #

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

liftA2 :: (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c Source #

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

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

Applicative IO #

Since: 2.1

Methods

pure :: a -> IO a Source #

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

liftA2 :: (a -> b -> c) -> IO a -> IO b -> IO c Source #

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

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

Applicative Par1 #

Since: 4.9.0.0

Methods

pure :: a -> Par1 a Source #

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

liftA2 :: (a -> b -> c) -> Par1 a -> Par1 b -> Par1 c Source #

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

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

Applicative ReadP #

Since: 4.6.0.0

Methods

pure :: a -> ReadP a Source #

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

liftA2 :: (a -> b -> c) -> ReadP a -> ReadP b -> ReadP c Source #

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

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

Applicative ReadPrec #

Since: 4.6.0.0

Methods

pure :: a -> ReadPrec a Source #

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

liftA2 :: (a -> b -> c) -> ReadPrec a -> ReadPrec b -> ReadPrec c 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 #

liftA2 :: (a -> b -> c) -> Last a -> Last b -> Last c 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 #

liftA2 :: (a -> b -> c) -> First a -> First b -> First c Source #

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

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

Applicative Product #

Since: 4.8.0.0

Methods

pure :: a -> Product a Source #

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

liftA2 :: (a -> b -> c) -> Product a -> Product b -> Product c Source #

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

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

Applicative Sum #

Since: 4.8.0.0

Methods

pure :: a -> Sum a Source #

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

liftA2 :: (a -> b -> c) -> Sum a -> Sum b -> Sum c Source #

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

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

Applicative Dual #

Since: 4.8.0.0

Methods

pure :: a -> Dual a Source #

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

liftA2 :: (a -> b -> c) -> Dual a -> Dual b -> Dual c Source #

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

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

Applicative STM #

Since: 4.8.0.0

Methods

pure :: a -> STM a Source #

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

liftA2 :: (a -> b -> c) -> STM a -> STM b -> STM c Source #

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

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

Applicative Identity #

Since: 4.8.0.0

Methods

pure :: a -> Identity a Source #

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

liftA2 :: (a -> b -> c) -> Identity a -> Identity b -> Identity c Source #

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

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

Applicative ZipList #
f '<$>' 'ZipList' xs1 '<*>' ... '<*>' 'ZipList' xsN

ZipList (zipWithN f xs1 ... xsN)

where zipWithN refers to the zipWith function of the appropriate arity (zipWith, zipWith3, zipWith4, ...). For example:

(\a b c -> stimes c [a, b]) <$> ZipList "abcd" <*> ZipList "567" <*> ZipList [1..]
    = ZipList (zipWith3 (\a b c -> stimes c [a, b]) "abcd" "567" [1..])
    = ZipList {getZipList = ["a5","b6b6","c7c7c7"]}

Since: 2.1

Methods

pure :: a -> ZipList a Source #

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

liftA2 :: (a -> b -> c) -> ZipList a -> ZipList b -> ZipList c Source #

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

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

Applicative NonEmpty #

Since: 4.9.0.0

Methods

pure :: a -> NonEmpty a Source #

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

liftA2 :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c Source #

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

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

Applicative Option #

Since: 4.9.0.0

Methods

pure :: a -> Option a Source #

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

liftA2 :: (a -> b -> c) -> Option a -> Option b -> Option c Source #

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

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

Applicative Last #

Since: 4.9.0.0

Methods

pure :: a -> Last a Source #

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

liftA2 :: (a -> b -> c) -> Last a -> Last b -> Last c Source #

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

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

Applicative First #

Since: 4.9.0.0

Methods

pure :: a -> First a Source #

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

liftA2 :: (a -> b -> c) -> First a -> First b -> First c Source #

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

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

Applicative Max #

Since: 4.9.0.0

Methods

pure :: a -> Max a Source #

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

liftA2 :: (a -> b -> c) -> Max a -> Max b -> Max c Source #

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

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

Applicative Min #

Since: 4.9.0.0

Methods

pure :: a -> Min a Source #

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

liftA2 :: (a -> b -> c) -> Min a -> Min b -> Min c Source #

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

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

Applicative Complex #

Since: 4.9.0.0

Methods

pure :: a -> Complex a Source #

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

liftA2 :: (a -> b -> c) -> Complex a -> Complex b -> Complex c Source #

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

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

Applicative (Either e) #

Since: 3.0

Methods

pure :: a -> Either e a Source #

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

liftA2 :: (a -> b -> c) -> Either e a -> Either e b -> Either e c Source #

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

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

Applicative (U1 *) #

Since: 4.9.0.0

Methods

pure :: a -> U1 * a Source #

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

liftA2 :: (a -> b -> c) -> U1 * a -> U1 * b -> U1 * c Source #

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

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

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

For tuples, the Monoid constraint on a determines how the first values merge. For example, Strings concatenate:

("hello ", (+15)) <*> ("world!", 2002)
("hello world!",2017)

Since: 2.1

Methods

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

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

liftA2 :: (a -> b -> c) -> (a, a) -> (a, b) -> (a, c) Source #

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

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

Applicative (ST s) #

Since: 4.4.0.0

Methods

pure :: a -> ST s a Source #

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

liftA2 :: (a -> b -> c) -> ST s a -> ST s b -> ST s c Source #

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

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

Applicative (Proxy *) #

Since: 4.7.0.0

Methods

pure :: a -> Proxy * a Source #

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

liftA2 :: (a -> b -> c) -> Proxy * a -> Proxy * b -> Proxy * c Source #

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

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

Arrow a => Applicative (ArrowMonad a) #

Since: 4.6.0.0

Methods

pure :: a -> ArrowMonad a a Source #

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

liftA2 :: (a -> b -> c) -> ArrowMonad a a -> ArrowMonad a b -> ArrowMonad a c 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) #

Since: 2.1

Methods

pure :: a -> WrappedMonad m a Source #

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

liftA2 :: (a -> b -> c) -> WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m c Source #

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

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

Applicative (ST s) #

Since: 2.1

Methods

pure :: a -> ST s a Source #

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

liftA2 :: (a -> b -> c) -> ST s a -> ST s b -> ST s c Source #

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

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

Applicative f => Applicative (Rec1 * f) #

Since: 4.9.0.0

Methods

pure :: a -> Rec1 * f a Source #

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

liftA2 :: (a -> b -> c) -> Rec1 * f a -> Rec1 * f b -> Rec1 * f c Source #

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

(<*) :: Rec1 * f a -> Rec1 * f b -> Rec1 * f 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 #

liftA2 :: (a -> b -> c) -> Alt * f a -> Alt * f b -> Alt * f c 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) #

Since: 2.0.1

Methods

pure :: a -> Const * m a Source #

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

liftA2 :: (a -> b -> c) -> Const * m a -> Const * m b -> Const * m c 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) #

Since: 2.1

Methods

pure :: a -> WrappedArrow a b a Source #

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

liftA2 :: (a -> b -> c) -> WrappedArrow a b a -> WrappedArrow a b b -> WrappedArrow a b c 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 ((->) LiftedRep LiftedRep a) #

Since: 2.1

Methods

pure :: a -> (LiftedRep -> LiftedRep) a a Source #

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

liftA2 :: (a -> b -> c) -> (LiftedRep -> LiftedRep) a a -> (LiftedRep -> LiftedRep) a b -> (LiftedRep -> LiftedRep) a c Source #

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

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

(Applicative f, Applicative g) => Applicative ((:*:) * f g) #

Since: 4.9.0.0

Methods

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

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

liftA2 :: (a -> b -> c) -> (* :*: f) g a -> (* :*: f) g b -> (* :*: f) g c 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 (Product * f g) #

Since: 4.9.0.0

Methods

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

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

liftA2 :: (a -> b -> c) -> Product * f g a -> Product * f g b -> Product * f g c 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 (M1 * i c f) #

Since: 4.9.0.0

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 #

liftA2 :: (a -> b -> c) -> M1 * i c f a -> M1 * i c f b -> M1 * i c f c 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 ((:.:) * * f g) #

Since: 4.9.0.0

Methods

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

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

liftA2 :: (a -> b -> c) -> (* :.: *) f g a -> (* :.: *) f g b -> (* :.: *) f g c 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 (Compose * * f g) #

Since: 4.9.0.0

Methods

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

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

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

Since: 2.1

Methods

empty :: [a] Source #

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

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

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

Alternative Maybe #

Since: 2.1

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 #

Since: 4.9.0.0

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 ReadP #

Since: 4.6.0.0

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 #

Since: 4.6.0.0

Alternative STM #

Since: 4.8.0.0

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 #

Since: 4.9.0.0

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 (U1 *) #

Since: 4.9.0.0

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 (Proxy *) #

Since: 4.9.0.0

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

Since: 4.6.0.0

MonadPlus m => Alternative (WrappedMonad m) #

Since: 2.1

Alternative f => Alternative (Rec1 * f) #

Since: 4.9.0.0

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

Since: 2.1

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

Since: 4.9.0.0

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 g) => Alternative (Product * f g) #

Since: 4.9.0.0

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 => Alternative (M1 * i c f) #

Since: 4.9.0.0

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

Since: 4.9.0.0

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 (Compose * * f g) #

Since: 4.9.0.0

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

Generic1 k (Const k a) # 

Associated Types

type Rep1 (Const k a) (f :: Const k a -> *) :: k -> * Source #

Methods

from1 :: f a -> Rep1 (Const k a) f a Source #

to1 :: Rep1 (Const k a) f a -> f a Source #

Show2 (Const *) #

Since: 4.9.0.0

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

Since: 4.9.0.0

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 #

liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Const * a b) Source #

liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Const * a b] Source #

Ord2 (Const *) #

Since: 4.9.0.0

Methods

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

Eq2 (Const *) #

Since: 4.9.0.0

Methods

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

Bifunctor (Const *) #

Since: 4.8.0.0

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 #

Bifoldable (Const *) #

Since: 4.10.0.0

Methods

bifold :: Monoid m => Const * m m -> m Source #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Const * a b -> m Source #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Const * a b -> c Source #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Const * a b -> c Source #

Bitraversable (Const *) #

Since: 4.10.0.0

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Const * a b -> f (Const * c d) Source #

Functor (Const * m) #

Since: 2.1

Methods

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

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

Monoid m => Applicative (Const * m) #

Since: 2.0.1

Methods

pure :: a -> Const * m a Source #

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

liftA2 :: (a -> b -> c) -> Const * m a -> Const * m b -> Const * m c Source #

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

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

Foldable (Const * m) #

Since: 4.7.0.0

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

Since: 4.7.0.0

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 #

Show a => Show1 (Const * a) #

Since: 4.9.0.0

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

Since: 4.9.0.0

Methods

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

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

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Const * a a) Source #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Const * a a] Source #

Ord a => Ord1 (Const * a) #

Since: 4.9.0.0

Methods

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

Eq a => Eq1 (Const * a) #

Since: 4.9.0.0

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 #

(Typeable * k3, Data a, Typeable k3 b) => Data (Const k3 a b) #

Since: 4.10.0.0

Methods

gfoldl :: (forall d c. Data d => c (d -> c) -> d -> c c) -> (forall g. g -> c g) -> Const k3 a b -> c (Const k3 a b) Source #

gunfold :: (forall c r. Data c => c (c -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Const k3 a b) Source #

toConstr :: Const k3 a b -> Constr Source #

dataTypeOf :: Const k3 a b -> DataType Source #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Const k3 a b)) Source #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Const k3 a b)) Source #

gmapT :: (forall c. Data c => c -> c) -> Const k3 a b -> Const k3 a b Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Const k3 a b -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Const k3 a b -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Const k3 a b -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Const k3 a b -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Const k3 a b -> m (Const k3 a b) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Const k3 a b -> m (Const k3 a b) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Const k3 a b -> m (Const k3 a b) 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

Since: 4.8.0.0

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

Since: 4.8.0.0

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

Since: 4.9.0.0

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

Since: 4.9.0.0

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 k (Const k a) # 
type Rep1 k (Const k a) = D1 k (MetaData "Const" "Data.Functor.Const" "base" True) (C1 k (MetaCons "Const" PrefixI True) (S1 k (MetaSel (Just Symbol "getConst") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 k 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) # 
Monad m => Functor (WrappedMonad m) #

Since: 2.1

Methods

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

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

Monad m => Applicative (WrappedMonad m) #

Since: 2.1

Methods

pure :: a -> WrappedMonad m a Source #

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

liftA2 :: (a -> b -> c) -> WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m c Source #

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

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

MonadPlus m => Alternative (WrappedMonad m) #

Since: 2.1

Generic1 * (WrappedMonad m) # 

Associated Types

type Rep1 (WrappedMonad m) (f :: WrappedMonad m -> *) :: k -> * Source #

Methods

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

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

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

Generic1 * (WrappedArrow a b) # 

Associated Types

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

Methods

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

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

Arrow a => Functor (WrappedArrow a b) #

Since: 2.1

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

Since: 2.1

Methods

pure :: a -> WrappedArrow a b a Source #

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

liftA2 :: (a -> b -> c) -> WrappedArrow a b a -> WrappedArrow a b b -> WrappedArrow a b c 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 #

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

Since: 2.1

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.

Constructors

ZipList 

Fields

Instances

Functor ZipList # 

Methods

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

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

Applicative ZipList #
f '<$>' 'ZipList' xs1 '<*>' ... '<*>' 'ZipList' xsN

ZipList (zipWithN f xs1 ... xsN)

where zipWithN refers to the zipWith function of the appropriate arity (zipWith, zipWith3, zipWith4, ...). For example:

(\a b c -> stimes c [a, b]) <$> ZipList "abcd" <*> ZipList "567" <*> ZipList [1..]
    = ZipList (zipWith3 (\a b c -> stimes c [a, b]) "abcd" "567" [1..])
    = ZipList {getZipList = ["a5","b6b6","c7c7c7"]}

Since: 2.1

Methods

pure :: a -> ZipList a Source #

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

liftA2 :: (a -> b -> c) -> ZipList a -> ZipList b -> ZipList c 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 #

Since: 4.9.0.0

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 #

Eq a => Eq (ZipList a) # 

Methods

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

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

Ord a => Ord (ZipList a) # 
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 #

Generic1 * ZipList # 

Associated Types

type Rep1 ZipList (f :: ZipList -> *) :: k -> * Source #

Methods

from1 :: f a -> Rep1 ZipList f a Source #

to1 :: Rep1 ZipList f a -> f a Source #

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

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 infixl 4 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.

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.