Control.Applicative
| Copyright | Conor McBride and Ross Paterson 2005 |
|---|---|
| License | BSD-style (see the LICENSE file in the distribution) |
| Maintainer | libraries@haskell.org |
| Stability | stable |
| 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
Traversableclass. - 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 :: Type -> Type) 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 into the Structure.
Examples
>>> pure 1 :: Maybe Int Just 1
>>> pure 'z' :: [Char] "z"
>>> pure (pure ":D") :: Maybe [String] Just [":D"]
(<*>) :: 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.
Example
Used in combination with (<$>), (<*>) can be used to build a record.
>>> data MyState = MyState {arg1 :: Foo, arg2 :: Bar, arg3 :: Baz}
>>> produceFoo :: Applicative f => f Foo >>> produceBar :: Applicative f => f Bar >>> produceBaz :: Applicative f => f Baz
>>> mkState :: Applicative f => f MyState >>> mkState = MyState <$> produceFoo <*> produceBar <*> produceBaz
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.
Example
>>> liftA2 (,) (Just 3) (Just 5) Just (3,5)
>>> liftA2 (+) [1, 2, 3] [4, 5, 6] [5,6,7,6,7,8,7,8,9]
(*>) :: f a -> f b -> f b infixl 4 Source
Sequence actions, discarding the value of the first argument.
Examples
If used in conjunction with the Applicative instance for Maybe, you can chain Maybe computations, with a possible "early return" in case of Nothing.
>>> Just 2 *> Just 3 Just 3
>>> Nothing *> Just 3 Nothing
Of course a more interesting use case would be to have effectful computations instead of just returning pure values.
>>> import Data.Char
>>> import GHC.Internal.Text.ParserCombinators.ReadP
>>> let p = string "my name is " *> munch1 isAlpha <* eof
>>> readP_to_S p "my name is Simon"
[("Simon","")]
(<*) :: f a -> f b -> f a infixl 4 Source
Sequence actions, discarding the value of the second argument.
Instances
| Applicative Complex Source | Since: base-4.9.0.0 |
| Applicative First Source | Since: base-4.9.0.0 |
| Applicative Last Source | Since: base-4.9.0.0 |
| Applicative Max Source | Since: base-4.9.0.0 |
| Applicative Min Source | Since: base-4.9.0.0 |
| Applicative NonEmpty Source | Since: base-4.9.0.0 |
Defined in GHC.Internal.Base | |
| Applicative STM Source | Since: base-4.8.0.0 |
| Applicative Identity Source | Since: base-4.8.0.0 |
Defined in GHC.Internal.Data.Functor.Identity | |
| Applicative First Source | Since: base-4.8.0.0 |
| Applicative Last Source | Since: base-4.8.0.0 |
| Applicative Down Source | Since: base-4.11.0.0 |
| Applicative Dual Source | Since: base-4.8.0.0 |
| Applicative Product Source | Since: base-4.8.0.0 |
Defined in GHC.Internal.Data.Semigroup.Internal | |
| Applicative Sum Source | Since: base-4.8.0.0 |
| Applicative ZipList Source |
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 |
Defined in GHC.Internal.Functor.ZipList | |
| Applicative NoIO Source | Since: base-4.8.0.0 |
| Applicative Par1 Source | Since: base-4.9.0.0 |
| Applicative Q Source | |
| Applicative P Source | Since: base-4.5.0.0 |
| Applicative ReadP Source | Since: base-4.6.0.0 |
| Applicative ReadPrec Source | Since: base-4.6.0.0 |
Defined in GHC.Internal.Text.ParserCombinators.ReadPrec | |
| Applicative IO Source | Since: base-2.1 |
| Applicative Maybe Source | Since: base-2.1 |
| Applicative Solo Source | Since: base-4.15 |
| Applicative [] Source | Since: base-2.1 |
| Monad m => Applicative (WrappedMonad m) Source | 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 | |
| Arrow a => Applicative (ArrowMonad a) Source | Since: base-4.6.0.0 |
Defined in GHC.Internal.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 | |
| Applicative (ST s) Source | Since: base-2.1 |
| Applicative (Either e) Source | Since: base-3.0 |
Defined in GHC.Internal.Data.Either | |
| Applicative (StateL s) Source | Since: base-4.0 |
Defined in GHC.Internal.Data.Functor.Utils | |
| Applicative (StateR s) Source | Since: base-4.0 |
Defined in GHC.Internal.Data.Functor.Utils | |
| Applicative (Proxy :: Type -> Type) Source | Since: base-4.7.0.0 |
| Applicative (U1 :: Type -> Type) Source | Since: base-4.9.0.0 |
| Applicative (ST s) Source | Since: base-4.4.0.0 |
| Monoid a => Applicative ((,) a) Source |
For tuples, the ("hello ", (+15)) <*> ("world!", 2002)
("hello world!",2017)
Since: base-2.1 |
| Arrow a => Applicative (WrappedArrow a b) Source | 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 m => Applicative (Kleisli m a) Source | Since: base-4.14.0.0 |
Defined in GHC.Internal.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 | |
| Monoid m => Applicative (Const m :: Type -> Type) Source | Since: base-2.0.1 |
Defined in GHC.Internal.Data.Functor.Const | |
| Monad m => Applicative (StateT s m) Source | Since: base-4.18.0.0 |
| Applicative f => Applicative (Ap f) Source | Since: base-4.12.0.0 |
| Applicative f => Applicative (Alt f) Source | Since: base-4.8.0.0 |
| (Generic1 f, Applicative (Rep1 f)) => Applicative (Generically1 f) Source | Since: base-4.17.0.0 |
Defined in GHC.Internal.Generics Methodspure :: a -> Generically1 f a Source (<*>) :: Generically1 f (a -> b) -> Generically1 f a -> Generically1 f b Source liftA2 :: (a -> b -> c) -> Generically1 f a -> Generically1 f b -> Generically1 f c Source (*>) :: Generically1 f a -> Generically1 f b -> Generically1 f b Source (<*) :: Generically1 f a -> Generically1 f b -> Generically1 f a Source | |
| Applicative f => Applicative (Rec1 f) Source | Since: base-4.9.0.0 |
| (Monoid a, Monoid b) => Applicative ((,,) a b) Source | Since: base-4.14.0.0 |
Defined in GHC.Internal.Base | |
| (Applicative f, Applicative g) => Applicative (Product f g) Source | 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 g) => Applicative (f :*: g) Source | Since: base-4.9.0.0 |
Defined in GHC.Internal.Generics | |
| Monoid c => Applicative (K1 i c :: Type -> Type) Source | Since: base-4.12.0.0 |
| (Monoid a, Monoid b, Monoid c) => Applicative ((,,,) a b c) Source | Since: base-4.14.0.0 |
Defined in GHC.Internal.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 ((->) r) Source | Since: base-2.1 |
| (Applicative f, Applicative g) => Applicative (Compose f g) Source | 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 | |
| (Applicative f, Applicative g) => Applicative (f :.: g) Source | Since: base-4.9.0.0 |
Defined in GHC.Internal.Generics | |
| Applicative f => Applicative (M1 i c f) Source | Since: base-4.9.0.0 |
Defined in GHC.Internal.Generics | |
Alternatives
class Applicative f => Alternative (f :: Type -> Type) where Source
A monoid on applicative functors.
If defined, some and many should be the least solutions of the equations:
Examples
>>> Nothing <|> Just 42 Just 42
>>> [1, 2] <|> [3, 4] [1,2,3,4]
>>> empty <|> print (2^15) 32768
Methods
The identity of <|>
empty <|> a == a a <|> empty == a
(<|>) :: f a -> f a -> f a infixl 3 Source
An associative binary operation
One or more.
Examples
>>> some (putStr "la") lalalalalalalalala... * goes on forever *
>>> some Nothing nothing
>>> take 5 <$> some (Just 1) * hangs forever *
Note that this function can be used with Parsers based on Applicatives. In that case some parser will attempt to parse parser one or more times until it fails.
Zero or more.
Examples
>>> many (putStr "la") lalalalalalalalala... * goes on forever *
>>> many Nothing Just []
>>> take 5 <$> many (Just 1) * hangs forever *
Note that this function can be used with Parsers based on Applicatives. In that case many parser will attempt to parse parser zero or more times until it fails.
Instances
Instances
newtype Const a (b :: k) Source
The Const functor.
Examples
>>> fmap (++ "World") (Const "Hello") Const "Hello"
Because we ignore the second type parameter to Const, the Applicative instance, which has (<*>) :: Monoid m => Const m (a -> b) -> Const m a -> Const m b essentially turns into Monoid m => m -> m -> m, which is (<>)
>>> Const [1, 2, 3] <*> Const [4, 5, 6] Const [1,2,3,4,5,6]
Instances
| Generic1 (Const a :: k -> Type) Source | |||||
Defined in GHC.Internal.Data.Functor.Const Associated Types
| |||||
| Bifoldable (Const :: Type -> Type -> Type) Source | Since: base-4.10.0.0 |
||||
| Bifoldable1 (Const :: Type -> Type -> Type) Source | |||||
Defined in Data.Bifoldable1 | |||||
| Bifunctor (Const :: Type -> Type -> Type) Source | Since: base-4.8.0.0 |
||||
| Bitraversable (Const :: Type -> Type -> Type) Source | 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 | |||||
| Eq2 (Const :: Type -> Type -> Type) Source | Since: base-4.9.0.0 |
||||
| Ord2 (Const :: Type -> Type -> Type) Source | Since: base-4.9.0.0 |
||||
Defined in Data.Functor.Classes | |||||
| Read2 (Const :: Type -> Type -> Type) Source | 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 | |||||
| Show2 (Const :: Type -> Type -> Type) Source | Since: base-4.9.0.0 |
||||
| Eq a => Eq1 (Const a :: Type -> Type) Source | Since: base-4.9.0.0 |
||||
| Ord a => Ord1 (Const a :: Type -> Type) Source | Since: base-4.9.0.0 |
||||
Defined in Data.Functor.Classes | |||||
| Read a => Read1 (Const a :: Type -> Type) Source | 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 | |||||
| Show a => Show1 (Const a :: Type -> Type) Source | Since: base-4.9.0.0 |
||||
| Contravariant (Const a :: Type -> Type) Source | |||||
| Monoid m => Applicative (Const m :: Type -> Type) Source | Since: base-2.0.1 |
||||
Defined in GHC.Internal.Data.Functor.Const | |||||
| Functor (Const m :: Type -> Type) Source | Since: base-2.1 |
||||
| Foldable (Const m :: Type -> Type) Source | Since: base-4.7.0.0 |
||||
Defined in GHC.Internal.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) Source | Since: base-4.7.0.0 |
||||
Defined in GHC.Internal.Data.Traversable | |||||
| Monoid a => Monoid (Const a b) Source | Since: base-4.9.0.0 |
||||
| Semigroup a => Semigroup (Const a b) Source | Since: base-4.9.0.0 |
||||
| Bits a => Bits (Const a b) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.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 | |||||
| FiniteBits a => FiniteBits (Const a b) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Data.Functor.Const MethodsfiniteBitSize :: Const a b -> Int Source countLeadingZeros :: Const a b -> Int Source countTrailingZeros :: Const a b -> Int Source | |||||
| (Typeable k, Data a, Typeable b) => Data (Const a b) Source | Since: base-4.10.0.0 |
||||
Defined in GHC.Internal.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 | |||||
| IsString a => IsString (Const a b) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Data.String MethodsfromString :: String -> Const a b Source | |||||
| Bounded a => Bounded (Const a b) Source | Since: base-4.9.0.0 |
||||
| Enum a => Enum (Const a b) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.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 | |||||
| Floating a => Floating (Const a b) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.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 | |||||
| RealFloat a => RealFloat (Const a b) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.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 | |||||
| Storable a => Storable (Const a b) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.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 | |||||
| Generic (Const a b) Source | |||||
Defined in GHC.Internal.Data.Functor.Const Associated Types
| |||||
| Ix a => Ix (Const a b) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.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 | |||||
| Num a => Num (Const a b) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.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 | |||||
| Read a => Read (Const a b) Source |
This instance would be equivalent to the derived instances of the Since: base-4.8.0.0 |
||||
| Fractional a => Fractional (Const a b) Source | Since: base-4.9.0.0 |
||||
| Integral a => Integral (Const a b) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.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 | |||||
| Real a => Real (Const a b) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Data.Functor.Const MethodstoRational :: Const a b -> Rational Source | |||||
| RealFrac a => RealFrac (Const a b) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Data.Functor.Const | |||||
| Show a => Show (Const a b) Source |
This instance would be equivalent to the derived instances of the Since: base-4.8.0.0 |
||||
| Eq a => Eq (Const a b) Source | Since: base-4.9.0.0 |
||||
| Ord a => Ord (Const a b) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Data.Functor.Const | |||||
| type Rep1 (Const a :: k -> Type) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Data.Functor.Const | |||||
| type Rep (Const a b) Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Data.Functor.Const | |||||
newtype WrappedMonad (m :: Type -> Type) a Source
Constructors
| WrapMonad | |
Fields
| |
Instances
| Generic1 (WrappedMonad m :: Type -> Type) Source | |||||
Defined in Control.Applicative Associated Types
Methodsfrom1 :: WrappedMonad m a -> Rep1 (WrappedMonad m) a Source to1 :: Rep1 (WrappedMonad m) a -> WrappedMonad m a Source | |||||
| MonadPlus m => Alternative (WrappedMonad m) Source | 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 | |||||
| Monad m => Applicative (WrappedMonad m) Source | 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 | |||||
| Monad m => Functor (WrappedMonad m) Source | 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 => Monad (WrappedMonad m) Source | 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 | |||||
| (Typeable m, Typeable a, Data (m a)) => Data (WrappedMonad m a) Source | Since: base-4.14.0.0 |
||||
Defined in Control.Applicative 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) Source | |||||
Defined in Control.Applicative Associated Types
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) Source | Since: base-4.7.0.0 |
||||
Defined in Control.Applicative type Rep1 (WrappedMonad m :: Type -> Type) = D1 ('MetaData "WrappedMonad" "Control.Applicative" "base-4.21.0.0-8e62" 'True) (C1 ('MetaCons "WrapMonad" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapMonad") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 m))) | |||||
| type Rep (WrappedMonad m a) Source | Since: base-4.7.0.0 |
||||
Defined in Control.Applicative type Rep (WrappedMonad m a) = D1 ('MetaData "WrappedMonad" "Control.Applicative" "base-4.21.0.0-8e62" 'True) (C1 ('MetaCons "WrapMonad" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapMonad") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (m a)))) | |||||
newtype WrappedArrow (a :: Type -> Type -> Type) b c Source
Constructors
| WrapArrow | |
Fields
| |
Instances
| Generic1 (WrappedArrow a b :: Type -> Type) Source | |||||
Defined in Control.Applicative Associated Types
Methodsfrom1 :: WrappedArrow a b a0 -> Rep1 (WrappedArrow a b) a0 Source to1 :: Rep1 (WrappedArrow a b) a0 -> WrappedArrow a b a0 Source | |||||
| (ArrowZero a, ArrowPlus a) => Alternative (WrappedArrow a b) Source | 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 | |||||
| Arrow a => Applicative (WrappedArrow a b) Source | 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 | |||||
| Arrow a => Functor (WrappedArrow a b) Source | 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 | |||||
| (Typeable a, Typeable b, Typeable c, Data (a b c)) => Data (WrappedArrow a b c) Source | Since: base-4.14.0.0 |
||||
Defined in Control.Applicative 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) Source | |||||
Defined in Control.Applicative Associated Types
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) Source | Since: base-4.7.0.0 |
||||
Defined in Control.Applicative type Rep1 (WrappedArrow a b :: Type -> Type) = D1 ('MetaData "WrappedArrow" "Control.Applicative" "base-4.21.0.0-8e62" 'True) (C1 ('MetaCons "WrapArrow" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapArrow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 (a b)))) | |||||
| type Rep (WrappedArrow a b c) Source | Since: base-4.7.0.0 |
||||
Defined in Control.Applicative type Rep (WrappedArrow a b c) = D1 ('MetaData "WrappedArrow" "Control.Applicative" "base-4.21.0.0-8e62" '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.
Examples
In contrast to the Applicative for List:
>>> (+) <$> [1, 2, 3] <*> [4, 5, 6] [5,6,7,6,7,8,7,8,9]
The Applicative instance of ZipList applies the operation by pairing up the elements, analogous to zipWithN
>>> (+) <$> ZipList [1, 2, 3] <*> ZipList [4, 5, 6]
ZipList {getZipList = [5,7,9]}
>>> (,,,) <$> ZipList [1, 2] <*> ZipList [3, 4] <*> ZipList [5, 6] <*> ZipList [7, 8]
ZipList {getZipList = [(1,3,5,7),(2,4,6,8)]}
>>> ZipList [(+1), (^2), (/ 2)] <*> ZipList [5, 5, 5]
ZipList {getZipList = [6.0,25.0,2.5]}
Constructors
| ZipList | |
Fields
| |
Instances
| Alternative ZipList Source | Since: base-4.11.0.0 |
||||
| Applicative ZipList Source |
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 |
||||
Defined in GHC.Internal.Functor.ZipList | |||||
| Functor ZipList Source | Since: base-2.1 |
||||
| Foldable ZipList Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Functor.ZipList 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 Source | Since: base-4.9.0.0 |
||||
Defined in GHC.Internal.Functor.ZipList | |||||
| Generic1 ZipList Source | |||||
Defined in GHC.Internal.Functor.ZipList Associated Types
| |||||
| Data a => Data (ZipList a) Source | Since: base-4.14.0.0 |
||||
Defined in GHC.Internal.Functor.ZipList 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 | |||||
| Generic (ZipList a) Source | |||||
Defined in GHC.Internal.Functor.ZipList Associated Types
| |||||
| IsList (ZipList a) Source | Since: base-4.15.0.0 |
||||
| Read a => Read (ZipList a) Source | Since: base-4.7.0.0 |
||||
| Show a => Show (ZipList a) Source | Since: base-4.7.0.0 |
||||
| Eq a => Eq (ZipList a) Source | Since: base-4.7.0.0 |
||||
| Ord a => Ord (ZipList a) Source | Since: base-4.7.0.0 |
||||
Defined in GHC.Internal.Functor.ZipList | |||||
| type Rep1 ZipList Source | Since: base-4.7.0.0 |
||||
Defined in GHC.Internal.Functor.ZipList | |||||
| type Rep (ZipList a) Source | Since: base-4.7.0.0 |
||||
Defined in GHC.Internal.Functor.ZipList | |||||
| type Item (ZipList a) Source | |||||
Defined in GHC.Internal.IsList | |||||
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.
Examples
Perform a computation with Maybe and replace the result with a constant value if it is Just:
>>> 'a' <$ Just 2 Just 'a' >>> 'a' <$ Nothing Nothing
(<**>) :: Applicative f => f a -> f (a -> b) -> f b infixl 4 Source
A variant of <*> with the types of the arguments reversed. It differs from flip (<*>) in that the effects are resolved in the order the arguments are presented.
Examples
>>> (<**>) (print 1) (id <$ print 2) 1 2
>>> flip (<*>) (print 1) (id <$ print 2) 2 1
>>> ZipList [4, 5, 6] <**> ZipList [(+1), (*2), (/3)]
ZipList {getZipList = [5.0,10.0,2.0]}
liftA :: Applicative f => (a -> b) -> f a -> f b Source
Lift a function to actions. Equivalent to Functor's fmap but implemented using only Applicative's methods: liftA f a = pure f <*> a
As such this function may be used to implement a Functor instance from an Applicative one.
Examples
Using the Applicative instance for Lists:
>>> liftA (+1) [1, 2] [2,3]
Or the Applicative instance for Maybe
>>> liftA (+1) (Just 3) Just 4
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.
It is useful for modelling any computation that is allowed to fail.
Examples
Using the Alternative instance of Control.Monad.Except, the following functions:
>>> import Control.Monad.Except
>>> canFail = throwError "it failed" :: Except String Int >>> final = return 42 :: Except String Int
Can be combined by allowing the first function to fail:
>>> runExcept $ canFail *> final Left "it failed"
>>> runExcept $ optional canFail *> final Right 42
asum :: (Foldable t, Alternative f) => t (f a) -> f a Source
The sum of a collection of actions using (<|>), generalizing concat.
asum is just like msum, but generalised to Alternative.
Examples
Basic usage:
>>> asum [Just "Hello", Nothing, Just "World"] Just "Hello"
© The University of Glasgow and others
Licensed under a BSD-style license (see top of the page).
https://downloads.haskell.org/~ghc/9.12.1/docs/libraries/base-4.21.0.0-8e62/Control-Applicative.html