Control.Applicative
Copyright | Conor McBride and Ross Paterson 2005 |
---|---|
License | BSD-style (see the LICENSE file in the distribution) |
Maintainer | [email protected] |
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 (
<*>
andliftA2
).
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).
Methods
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.
Using ApplicativeDo
: 'fs <*> as
' can be understood as the do
expression
do f <- fs a <- as pure (f a)
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 <*>
.
This became a typeclass method in 4.10.0.0. Prior to that, it was a function defined in terms of <*>
and fmap
.
Using ApplicativeDo
: 'liftA2 f as bs
' can be understood as the do
expression
do a <- as b <- bs pure (f a b)
(*>) :: f a -> f b -> f b infixl 4 Source
Sequence actions, discarding the value of the first argument.
'as *> bs
' can be understood as the do
expression
do as bs
This is a tad complicated for our ApplicativeDo
extension which will give it a Monad
constraint. For an Applicative
constraint we write it of the form
do _ <- as b <- bs pure b
(<*) :: f a -> f b -> f a infixl 4 Source
Sequence actions, discarding the value of the second argument.
Using ApplicativeDo
: 'as <* bs
' can be understood as the do
expression
do a <- as bs pure a
Instances
Applicative [] | Since: base-2.1 |
Applicative Maybe | Since: base-2.1 |
Applicative IO | Since: base-2.1 |
Applicative Par1 | Since: base-4.9.0.0 |
Applicative NonEmpty | Since: base-4.9.0.0 |
Defined in GHC.Base | |
Applicative NoIO | Since: base-4.8.0.0 |
Applicative ReadP | Since: base-4.6.0.0 |
Applicative ReadPrec | Since: base-4.6.0.0 |
Defined in Text.ParserCombinators.ReadPrec | |
Applicative Down | Since: base-4.11.0.0 |
Applicative Product | Since: base-4.8.0.0 |
Defined in Data.Semigroup.Internal | |
Applicative Sum | Since: base-4.8.0.0 |
Applicative Dual | Since: base-4.8.0.0 |
Applicative Last | Since: base-4.8.0.0 |
Applicative First | Since: base-4.8.0.0 |
Applicative STM | Since: base-4.8.0.0 |
Applicative Identity | Since: base-4.8.0.0 |
Defined in Data.Functor.Identity | |
Applicative ZipList |
f <$> ZipList xs1 <*> ... <*> ZipList xsN = ZipList (zipWithN f xs1 ... xsN) where (\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: base-2.1 |
Applicative Option | Since: base-4.9.0.0 |
Applicative Last | Since: base-4.9.0.0 |
Applicative First | Since: base-4.9.0.0 |
Applicative Max | Since: base-4.9.0.0 |
Applicative Min | Since: base-4.9.0.0 |
Applicative Complex | Since: base-4.9.0.0 |
Applicative (Either e) | Since: base-3.0 |
Defined in Data.Either | |
Applicative (U1 :: Type -> Type) | Since: base-4.9.0.0 |
Monoid a => Applicative ((,) a) |
For tuples, the ("hello ", (+15)) <*> ("world!", 2002) ("hello world!",2017) Since: base-2.1 |
Applicative (ST s) | Since: base-4.4.0.0 |
Applicative (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Arrow a => Applicative (ArrowMonad a) | Since: base-4.6.0.0 |
Defined in Control.Arrow Methodspure :: a0 -> ArrowMonad a a0 Source (<*>) :: ArrowMonad a (a0 -> b) -> ArrowMonad a a0 -> ArrowMonad a b Source liftA2 :: (a0 -> b -> c) -> ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a c Source (*>) :: ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a b Source (<*) :: ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a a0 Source | |
Monad m => Applicative (WrappedMonad m) | Since: base-2.1 |
Defined in Control.Applicative Methodspure :: 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: base-2.1 |
Applicative f => Applicative (Rec1 f) | Since: base-4.9.0.0 |
(Monoid a, Monoid b) => Applicative ((,,) a b) | Since: base-4.14.0.0 |
Defined in GHC.Base | |
Applicative f => Applicative (Alt f) | Since: base-4.8.0.0 |
Applicative f => Applicative (Ap f) | Since: base-4.12.0.0 |
Monoid m => Applicative (Const m :: Type -> Type) | Since: base-2.0.1 |
Applicative m => Applicative (Kleisli m a) | Since: base-4.14.0.0 |
Defined in Control.Arrow Methodspure :: a0 -> Kleisli m a a0 Source (<*>) :: Kleisli m a (a0 -> b) -> Kleisli m a a0 -> Kleisli m a b Source liftA2 :: (a0 -> b -> c) -> Kleisli m a a0 -> Kleisli m a b -> Kleisli m a c Source (*>) :: Kleisli m a a0 -> Kleisli m a b -> Kleisli m a b Source (<*) :: Kleisli m a a0 -> Kleisli m a b -> Kleisli m a a0 Source | |
Arrow a => Applicative (WrappedArrow a b) | Since: base-2.1 |
Defined in Control.Applicative Methodspure :: a0 -> WrappedArrow a b a0 Source (<*>) :: WrappedArrow a b (a0 -> b0) -> WrappedArrow a b a0 -> WrappedArrow a b b0 Source liftA2 :: (a0 -> b0 -> c) -> WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b c Source (*>) :: WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b b0 Source (<*) :: WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b a0 Source | |
Applicative ((->) r :: Type -> Type) | Since: base-2.1 |
Monoid c => Applicative (K1 i c :: Type -> Type) | Since: base-4.12.0.0 |
(Applicative f, Applicative g) => Applicative (f :*: g) | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
(Monoid a, Monoid b, Monoid c) => Applicative ((,,,) a b c) | Since: base-4.14.0.0 |
Defined in GHC.Base Methodspure :: a0 -> (a, b, c, a0) Source (<*>) :: (a, b, c, a0 -> b0) -> (a, b, c, a0) -> (a, b, c, b0) Source liftA2 :: (a0 -> b0 -> c0) -> (a, b, c, a0) -> (a, b, c, b0) -> (a, b, c, c0) Source (*>) :: (a, b, c, a0) -> (a, b, c, b0) -> (a, b, c, b0) Source (<*) :: (a, b, c, a0) -> (a, b, c, b0) -> (a, b, c, a0) Source | |
(Applicative f, Applicative g) => Applicative (Product f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Product Methodspure :: 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: base-4.9.0.0 |
Defined in GHC.Generics | |
(Applicative f, Applicative g) => Applicative (f :.: g) | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
(Applicative f, Applicative g) => Applicative (Compose f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Compose Methodspure :: 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:
Methods
The identity of <|>
(<|>) :: f a -> f a -> f a infixl 3 Source
An associative binary operation
One or more.
Zero or more.
Instances
Instances
The Const
functor.
Instances
Generic1 (Const a :: k -> Type) | Since: base-4.9.0.0 |
Show2 (Const :: Type -> Type -> Type) | Since: base-4.9.0.0 |
Read2 (Const :: Type -> Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes MethodsliftReadsPrec2 :: (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 :: Type -> Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Eq2 (Const :: Type -> Type -> Type) | Since: base-4.9.0.0 |
Bifunctor (Const :: Type -> Type -> Type) | Since: base-4.8.0.0 |
Bifoldable (Const :: Type -> Type -> Type) | Since: base-4.10.0.0 |
Bitraversable (Const :: Type -> Type -> Type) | Since: base-4.10.0.0 |
Defined in Data.Bitraversable Methodsbitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Const a b -> f (Const c d) Source | |
Functor (Const m :: Type -> Type) | Since: base-2.1 |
Monoid m => Applicative (Const m :: Type -> Type) | Since: base-2.0.1 |
Foldable (Const m :: Type -> Type) | Since: base-4.7.0.0 |
Defined in Data.Functor.Const Methodsfold :: Monoid m0 => Const m m0 -> m0 Source foldMap :: Monoid m0 => (a -> m0) -> Const m a -> m0 Source foldMap' :: Monoid m0 => (a -> m0) -> Const m a -> m0 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 | |
Traversable (Const m :: Type -> Type) | Since: base-4.7.0.0 |
Defined in Data.Traversable | |
Show a => Show1 (Const a :: Type -> Type) | Since: base-4.9.0.0 |
Read a => Read1 (Const a :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes MethodsliftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (Const a a0) Source liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [Const a a0] Source liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (Const a a0) Source liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [Const a a0] Source | |
Ord a => Ord1 (Const a :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Eq a => Eq1 (Const a :: Type -> Type) | Since: base-4.9.0.0 |
Contravariant (Const a :: Type -> Type) | |
Bounded a => Bounded (Const a b) | Since: base-4.9.0.0 |
Enum a => Enum (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const Methodssucc :: Const a b -> Const a b Source pred :: Const a b -> Const a b Source toEnum :: Int -> Const a b Source fromEnum :: Const a b -> Int Source enumFrom :: Const a b -> [Const a b] Source enumFromThen :: Const a b -> Const a b -> [Const a b] Source enumFromTo :: Const a b -> Const a b -> [Const a b] Source enumFromThenTo :: Const a b -> Const a b -> Const a b -> [Const a b] Source | |
Eq a => Eq (Const a b) | Since: base-4.9.0.0 |
Floating a => Floating (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const Methodsexp :: Const a b -> Const a b Source log :: Const a b -> Const a b Source sqrt :: Const a b -> Const a b Source (**) :: Const a b -> Const a b -> Const a b Source logBase :: Const a b -> Const a b -> Const a b Source sin :: Const a b -> Const a b Source cos :: Const a b -> Const a b Source tan :: Const a b -> Const a b Source asin :: Const a b -> Const a b Source acos :: Const a b -> Const a b Source atan :: Const a b -> Const a b Source sinh :: Const a b -> Const a b Source cosh :: Const a b -> Const a b Source tanh :: Const a b -> Const a b Source asinh :: Const a b -> Const a b Source acosh :: Const a b -> Const a b Source atanh :: Const a b -> Const a b Source log1p :: Const a b -> Const a b Source expm1 :: Const a b -> Const a b Source | |
Fractional a => Fractional (Const a b) | Since: base-4.9.0.0 |
Integral a => Integral (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const Methodsquot :: Const a b -> Const a b -> Const a b Source rem :: Const a b -> Const a b -> Const a b Source div :: Const a b -> Const a b -> Const a b Source mod :: Const a b -> Const a b -> Const a b Source quotRem :: Const a b -> Const a b -> (Const a b, Const a b) Source divMod :: Const a b -> Const a b -> (Const a b, Const a b) Source | |
(Typeable k, Data a, Typeable b) => Data (Const a b) | Since: base-4.10.0.0 |
Defined in Data.Data Methodsgfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Const a b -> c (Const a b) Source gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Const a b) Source toConstr :: Const a b -> Constr Source dataTypeOf :: Const a b -> DataType Source dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Const a b)) Source dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Const a b)) Source gmapT :: (forall b0. Data b0 => b0 -> b0) -> Const a b -> Const a b Source gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Const a b -> r Source gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Const a b -> r Source gmapQ :: (forall d. Data d => d -> u) -> Const a b -> [u] Source gmapQi :: Int -> (forall d. Data d => d -> u) -> Const a b -> u Source gmapM :: Monad m => (forall d. Data d => d -> m d) -> Const a b -> m (Const a b) Source gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Const a b -> m (Const a b) Source gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Const a b -> m (Const a b) Source | |
Num a => Num (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const Methods(+) :: Const a b -> Const a b -> Const a b Source (-) :: Const a b -> Const a b -> Const a b Source (*) :: Const a b -> Const a b -> Const a b Source negate :: Const a b -> Const a b Source abs :: Const a b -> Const a b Source signum :: Const a b -> Const a b Source fromInteger :: Integer -> Const a b Source | |
Ord a => Ord (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
Read a => Read (Const a b) |
This instance would be equivalent to the derived instances of the Since: base-4.8.0.0 |
Real a => Real (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const MethodstoRational :: Const a b -> Rational Source | |
RealFloat a => RealFloat (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const MethodsfloatRadix :: Const a b -> Integer Source floatDigits :: Const a b -> Int Source floatRange :: Const a b -> (Int, Int) Source decodeFloat :: Const a b -> (Integer, Int) Source encodeFloat :: Integer -> Int -> Const a b Source exponent :: Const a b -> Int Source significand :: Const a b -> Const a b Source scaleFloat :: Int -> Const a b -> Const a b Source isNaN :: Const a b -> Bool Source isInfinite :: Const a b -> Bool Source isDenormalized :: Const a b -> Bool Source isNegativeZero :: Const a b -> Bool Source | |
RealFrac a => RealFrac (Const a b) | Since: base-4.9.0.0 |
Show a => Show (Const a b) |
This instance would be equivalent to the derived instances of the Since: base-4.8.0.0 |
Ix a => Ix (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const Methodsrange :: (Const a b, Const a b) -> [Const a b] Source index :: (Const a b, Const a b) -> Const a b -> Int Source unsafeIndex :: (Const a b, Const a b) -> Const a b -> Int Source inRange :: (Const a b, Const a b) -> Const a b -> Bool Source rangeSize :: (Const a b, Const a b) -> Int Source unsafeRangeSize :: (Const a b, Const a b) -> Int Source | |
IsString a => IsString (Const a b) | Since: base-4.9.0.0 |
Defined in Data.String MethodsfromString :: String -> Const a b Source | |
Generic (Const a b) | Since: base-4.9.0.0 |
Semigroup a => Semigroup (Const a b) | Since: base-4.9.0.0 |
Monoid a => Monoid (Const a b) | Since: base-4.9.0.0 |
FiniteBits a => FiniteBits (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const MethodsfiniteBitSize :: Const a b -> Int Source countLeadingZeros :: Const a b -> Int Source countTrailingZeros :: Const a b -> Int Source | |
Bits a => Bits (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const Methods(.&.) :: Const a b -> Const a b -> Const a b Source (.|.) :: Const a b -> Const a b -> Const a b Source xor :: Const a b -> Const a b -> Const a b Source complement :: Const a b -> Const a b Source shift :: Const a b -> Int -> Const a b Source rotate :: Const a b -> Int -> Const a b Source bit :: Int -> Const a b Source setBit :: Const a b -> Int -> Const a b Source clearBit :: Const a b -> Int -> Const a b Source complementBit :: Const a b -> Int -> Const a b Source testBit :: Const a b -> Int -> Bool Source bitSizeMaybe :: Const a b -> Maybe Int Source bitSize :: Const a b -> Int Source isSigned :: Const a b -> Bool Source shiftL :: Const a b -> Int -> Const a b Source unsafeShiftL :: Const a b -> Int -> Const a b Source shiftR :: Const a b -> Int -> Const a b Source unsafeShiftR :: Const a b -> Int -> Const a b Source rotateL :: Const a b -> Int -> Const a b Source | |
Storable a => Storable (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const MethodssizeOf :: Const a b -> Int Source alignment :: Const a b -> Int Source peekElemOff :: Ptr (Const a b) -> Int -> IO (Const a b) Source pokeElemOff :: Ptr (Const a b) -> Int -> Const a b -> IO () Source peekByteOff :: Ptr b0 -> Int -> IO (Const a b) Source pokeByteOff :: Ptr b0 -> Int -> Const a b -> IO () Source | |
type Rep1 (Const a :: k -> Type) | |
Defined in Data.Functor.Const | |
type Rep (Const a b) | |
Defined in Data.Functor.Const |
newtype WrappedMonad m a Source
Constructors
WrapMonad | |
Fields
|
Instances
Monad m => Monad (WrappedMonad m) | Since: base-4.7.0.0 |
Defined in Control.Applicative 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 | |
Monad m => Functor (WrappedMonad m) | Since: base-2.1 |
Defined in Control.Applicative Methodsfmap :: (a -> b) -> WrappedMonad m a -> WrappedMonad m b Source (<$) :: a -> WrappedMonad m b -> WrappedMonad m a Source | |
Monad m => Applicative (WrappedMonad m) | Since: base-2.1 |
Defined in Control.Applicative Methodspure :: 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: base-2.1 |
Defined in Control.Applicative Methodsempty :: WrappedMonad m a Source (<|>) :: WrappedMonad m a -> WrappedMonad m a -> WrappedMonad m a Source some :: WrappedMonad m a -> WrappedMonad m [a] Source many :: WrappedMonad m a -> WrappedMonad m [a] Source | |
Generic1 (WrappedMonad m :: Type -> Type) | Since: base-4.7.0.0 |
Defined in Control.Applicative Associated Typestype Rep1 (WrappedMonad m) :: k -> Type Source Methodsfrom1 :: forall (a :: k). WrappedMonad m a -> Rep1 (WrappedMonad m) a Source to1 :: forall (a :: k). Rep1 (WrappedMonad m) a -> WrappedMonad m a Source | |
(Typeable m, Typeable a, Data (m a)) => Data (WrappedMonad m a) | Since: base-4.14.0.0 |
Defined in Data.Data Methodsgfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WrappedMonad m a -> c (WrappedMonad m a) Source gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (WrappedMonad m a) Source toConstr :: WrappedMonad m a -> Constr Source dataTypeOf :: WrappedMonad m a -> DataType Source dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (WrappedMonad m a)) Source dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (WrappedMonad m a)) Source gmapT :: (forall b. Data b => b -> b) -> WrappedMonad m a -> WrappedMonad m a Source gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WrappedMonad m a -> r Source gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WrappedMonad m a -> r Source gmapQ :: (forall d. Data d => d -> u) -> WrappedMonad m a -> [u] Source gmapQi :: Int -> (forall d. Data d => d -> u) -> WrappedMonad m a -> u Source gmapM :: Monad m0 => (forall d. Data d => d -> m0 d) -> WrappedMonad m a -> m0 (WrappedMonad m a) Source gmapMp :: MonadPlus m0 => (forall d. Data d => d -> m0 d) -> WrappedMonad m a -> m0 (WrappedMonad m a) Source gmapMo :: MonadPlus m0 => (forall d. Data d => d -> m0 d) -> WrappedMonad m a -> m0 (WrappedMonad m a) Source | |
Generic (WrappedMonad m a) | Since: base-4.7.0.0 |
Defined in Control.Applicative Associated Typestype Rep (WrappedMonad m a) :: Type -> Type Source Methodsfrom :: WrappedMonad m a -> Rep (WrappedMonad m a) x Source to :: Rep (WrappedMonad m a) x -> WrappedMonad m a Source | |
type Rep1 (WrappedMonad m :: Type -> Type) | |
Defined in Control.Applicative type Rep1 (WrappedMonad m :: Type -> Type) = D1 ('MetaData "WrappedMonad" "Control.Applicative" "base" 'True) (C1 ('MetaCons "WrapMonad" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapMonad") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 m))) | |
type Rep (WrappedMonad m a) | |
Defined in Control.Applicative type Rep (WrappedMonad m a) = D1 ('MetaData "WrappedMonad" "Control.Applicative" "base" 'True) (C1 ('MetaCons "WrapMonad" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapMonad") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (m a)))) |
newtype WrappedArrow a b c Source
Constructors
WrapArrow | |
Fields
|
Instances
Generic1 (WrappedArrow a b :: Type -> Type) | Since: base-4.7.0.0 |
Defined in Control.Applicative Associated Typestype Rep1 (WrappedArrow a b) :: k -> Type Source Methodsfrom1 :: forall (a0 :: k). WrappedArrow a b a0 -> Rep1 (WrappedArrow a b) a0 Source to1 :: forall (a0 :: k). Rep1 (WrappedArrow a b) a0 -> WrappedArrow a b a0 Source | |
Arrow a => Functor (WrappedArrow a b) | Since: base-2.1 |
Defined in Control.Applicative Methodsfmap :: (a0 -> b0) -> WrappedArrow a b a0 -> WrappedArrow a b b0 Source (<$) :: a0 -> WrappedArrow a b b0 -> WrappedArrow a b a0 Source | |
Arrow a => Applicative (WrappedArrow a b) | Since: base-2.1 |
Defined in Control.Applicative Methodspure :: a0 -> WrappedArrow a b a0 Source (<*>) :: WrappedArrow a b (a0 -> b0) -> WrappedArrow a b a0 -> WrappedArrow a b b0 Source liftA2 :: (a0 -> b0 -> c) -> WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b c Source (*>) :: WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b b0 Source (<*) :: WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b a0 Source | |
(ArrowZero a, ArrowPlus a) => Alternative (WrappedArrow a b) | Since: base-2.1 |
Defined in Control.Applicative Methodsempty :: WrappedArrow a b a0 Source (<|>) :: WrappedArrow a b a0 -> WrappedArrow a b a0 -> WrappedArrow a b a0 Source some :: WrappedArrow a b a0 -> WrappedArrow a b [a0] Source many :: WrappedArrow a b a0 -> WrappedArrow a b [a0] Source | |
(Typeable a, Typeable b, Typeable c, Data (a b c)) => Data (WrappedArrow a b c) | Since: base-4.14.0.0 |
Defined in Data.Data Methodsgfoldl :: (forall d b0. Data d => c0 (d -> b0) -> d -> c0 b0) -> (forall g. g -> c0 g) -> WrappedArrow a b c -> c0 (WrappedArrow a b c) Source gunfold :: (forall b0 r. Data b0 => c0 (b0 -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (WrappedArrow a b c) Source toConstr :: WrappedArrow a b c -> Constr Source dataTypeOf :: WrappedArrow a b c -> DataType Source dataCast1 :: Typeable t => (forall d. Data d => c0 (t d)) -> Maybe (c0 (WrappedArrow a b c)) Source dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c0 (t d e)) -> Maybe (c0 (WrappedArrow a b c)) Source gmapT :: (forall b0. Data b0 => b0 -> b0) -> WrappedArrow a b c -> WrappedArrow a b c Source gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WrappedArrow a b c -> r Source gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WrappedArrow a b c -> r Source gmapQ :: (forall d. Data d => d -> u) -> WrappedArrow a b c -> [u] Source gmapQi :: Int -> (forall d. Data d => d -> u) -> WrappedArrow a b c -> u Source gmapM :: Monad m => (forall d. Data d => d -> m d) -> WrappedArrow a b c -> m (WrappedArrow a b c) Source gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WrappedArrow a b c -> m (WrappedArrow a b c) Source gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WrappedArrow a b c -> m (WrappedArrow a b c) Source | |
Generic (WrappedArrow a b c) | Since: base-4.7.0.0 |
Defined in Control.Applicative Associated Typestype Rep (WrappedArrow a b c) :: Type -> Type Source Methodsfrom :: 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 -> Type) | |
Defined in Control.Applicative type Rep1 (WrappedArrow a b :: Type -> Type) = D1 ('MetaData "WrappedArrow" "Control.Applicative" "base" 'True) (C1 ('MetaCons "WrapArrow" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapArrow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 (a b)))) | |
type Rep (WrappedArrow a b c) | |
Defined in Control.Applicative type Rep (WrappedArrow a b c) = D1 ('MetaData "WrappedArrow" "Control.Applicative" "base" 'True) (C1 ('MetaCons "WrapArrow" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapArrow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (a b c)))) |
Lists, but with an Applicative
functor based on zipping.
Constructors
ZipList | |
Fields
|
Instances
Functor ZipList | Since: base-2.1 |
Applicative ZipList |
f <$> ZipList xs1 <*> ... <*> ZipList xsN = ZipList (zipWithN f xs1 ... xsN) where (\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: base-2.1 |
Foldable ZipList | Since: base-4.9.0.0 |
Defined in Control.Applicative Methodsfold :: Monoid m => ZipList m -> m Source foldMap :: Monoid m => (a -> m) -> ZipList a -> 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 | |
Traversable ZipList | Since: base-4.9.0.0 |
Defined in Data.Traversable | |
Alternative ZipList | Since: base-4.11.0.0 |
IsList (ZipList a) | Since: base-4.15.0.0 |
Eq a => Eq (ZipList a) | Since: base-4.7.0.0 |
Data a => Data (ZipList a) | Since: base-4.14.0.0 |
Defined in Data.Data Methodsgfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ZipList a -> c (ZipList a) Source gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ZipList a) Source toConstr :: ZipList a -> Constr Source dataTypeOf :: ZipList a -> DataType Source dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ZipList a)) Source dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ZipList a)) Source gmapT :: (forall b. Data b => b -> b) -> ZipList a -> ZipList a Source gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ZipList a -> r Source gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ZipList a -> r Source gmapQ :: (forall d. Data d => d -> u) -> ZipList a -> [u] Source gmapQi :: Int -> (forall d. Data d => d -> u) -> ZipList a -> u Source gmapM :: Monad m => (forall d. Data d => d -> m d) -> ZipList a -> m (ZipList a) Source gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ZipList a -> m (ZipList a) Source gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ZipList a -> m (ZipList a) Source | |
Ord a => Ord (ZipList a) | Since: base-4.7.0.0 |
Defined in Control.Applicative | |
Read a => Read (ZipList a) | Since: base-4.7.0.0 |
Show a => Show (ZipList a) | Since: base-4.7.0.0 |
Generic (ZipList a) | Since: base-4.7.0.0 |
Generic1 ZipList | Since: base-4.7.0.0 |
type Rep (ZipList a) | |
Defined in Control.Applicative | |
type Item (ZipList a) | |
type Rep1 ZipList | |
Defined in Control.Applicative |
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.
Using ApplicativeDo
: 'a <$ bs
' can be understood as the do
expression
do bs pure a
with an inferred Functor
constraint.
(<**>) :: Applicative f => f a -> f (a -> b) -> f b infixl 4 Source
A variant of <*>
with the arguments reversed.
Using ApplicativeDo
: 'as <**> fs
' can be understood as the do
expression
do a <- as f <- fs pure (f a)
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.
| Using ApplicativeDo
: 'liftA f as
' can be understood as the do
expression
do a <- as pure (f a)
with an inferred Functor
constraint, weaker than Applicative
.
liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d Source
Lift a ternary function to actions.
Using ApplicativeDo
: 'liftA3 f as bs cs
' can be understood as the do
expression
do a <- as b <- bs c <- cs pure (f a b c)
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.10.2/docs/html/libraries/base-4.14.1.0/Control-Applicative.html