semigroupoids-5.0.0.4: Semigroupoids: Category sans id

Copyright(C) 2011-2015 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Data.Functor.Apply

Contents

Description

 

Synopsis

Functors

class Functor f where

The Functor class is used for types that can be mapped over. Instances of Functor should satisfy the following laws:

fmap id  ==  id
fmap (f . g)  ==  fmap f . fmap g

The instances of Functor for lists, Maybe and IO satisfy these laws.

Minimal complete definition

fmap

Methods

fmap :: (a -> b) -> f a -> f b

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

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.

Instances

Functor [] 

Methods

fmap :: (a -> b) -> [a] -> [b]

(<$) :: a -> [b] -> [a]

Functor IO 

Methods

fmap :: (a -> b) -> IO a -> IO b

(<$) :: a -> IO b -> IO a

Functor Id 

Methods

fmap :: (a -> b) -> Id a -> Id b

(<$) :: a -> Id b -> Id a

Functor Identity 

Methods

fmap :: (a -> b) -> Identity a -> Identity b

(<$) :: a -> Identity b -> Identity a

Functor ZipList 

Methods

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

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

Functor Handler 

Methods

fmap :: (a -> b) -> Handler a -> Handler b

(<$) :: a -> Handler b -> Handler a

Functor First 

Methods

fmap :: (a -> b) -> First a -> First b

(<$) :: a -> First b -> First a

Functor Last 

Methods

fmap :: (a -> b) -> Last a -> Last b

(<$) :: a -> Last b -> Last a

Functor Maybe 

Methods

fmap :: (a -> b) -> Maybe a -> Maybe b

(<$) :: a -> Maybe b -> Maybe a

Functor Id 

Methods

fmap :: (a -> b) -> Id a -> Id b

(<$) :: a -> Id b -> Id a

Functor Put 

Methods

fmap :: (a -> b) -> Put a -> Put b

(<$) :: a -> Put b -> Put a

Functor Digit 

Methods

fmap :: (a -> b) -> Digit a -> Digit b

(<$) :: a -> Digit b -> Digit a

Functor Node 

Methods

fmap :: (a -> b) -> Node a -> Node b

(<$) :: a -> Node b -> Node a

Functor Elem 

Methods

fmap :: (a -> b) -> Elem a -> Elem b

(<$) :: a -> Elem b -> Elem a

Functor FingerTree 

Methods

fmap :: (a -> b) -> FingerTree a -> FingerTree b

(<$) :: a -> FingerTree b -> FingerTree a

Functor IntMap 

Methods

fmap :: (a -> b) -> IntMap a -> IntMap b

(<$) :: a -> IntMap b -> IntMap a

Functor Tree 

Methods

fmap :: (a -> b) -> Tree a -> Tree b

(<$) :: a -> Tree b -> Tree a

Functor Seq 

Methods

fmap :: (a -> b) -> Seq a -> Seq b

(<$) :: a -> Seq b -> Seq a

Functor ViewL 

Methods

fmap :: (a -> b) -> ViewL a -> ViewL b

(<$) :: a -> ViewL b -> ViewL a

Functor ViewR 

Methods

fmap :: (a -> b) -> ViewR a -> ViewR b

(<$) :: a -> ViewR b -> ViewR a

Functor Min 

Methods

fmap :: (a -> b) -> Min a -> Min b

(<$) :: a -> Min b -> Min a

Functor Max 

Methods

fmap :: (a -> b) -> Max a -> Max b

(<$) :: a -> Max b -> Max a

Functor First 

Methods

fmap :: (a -> b) -> First a -> First b

(<$) :: a -> First b -> First a

Functor Last 

Methods

fmap :: (a -> b) -> Last a -> Last b

(<$) :: a -> Last b -> Last a

Functor Option 

Methods

fmap :: (a -> b) -> Option a -> Option b

(<$) :: a -> Option b -> Option a

Functor NonEmpty 

Methods

fmap :: (a -> b) -> NonEmpty a -> NonEmpty b

(<$) :: a -> NonEmpty b -> NonEmpty a

Functor ((->) r) 

Methods

fmap :: (a -> b) -> (r -> a) -> r -> b

(<$) :: a -> (r -> b) -> r -> a

Functor (Either a) 

Methods

fmap :: (b -> c) -> Either a b -> Either a c

(<$) :: b -> Either a c -> Either a b

Functor ((,) a) 

Methods

fmap :: (b -> c) -> (a, b) -> (a, c)

(<$) :: b -> (a, c) -> (a, b)

Ix i => Functor (Array i) 

Methods

fmap :: (a -> b) -> Array i a -> Array i b

(<$) :: a -> Array i b -> Array i a

Functor (StateL s) 

Methods

fmap :: (a -> b) -> StateL s a -> StateL s b

(<$) :: a -> StateL s b -> StateL s a

Functor (StateR s) 

Methods

fmap :: (a -> b) -> StateR s a -> StateR s b

(<$) :: a -> StateR s b -> StateR s a

Functor (Const m) 

Methods

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

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

Monad m => Functor (WrappedMonad m) 

Methods

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

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

Arrow a => Functor (ArrowMonad a) 

Methods

fmap :: (b -> c) -> ArrowMonad a b -> ArrowMonad a c

(<$) :: b -> ArrowMonad a c -> ArrowMonad a b

Functor (Proxy *) 

Methods

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

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

Functor (StateL s) 

Methods

fmap :: (a -> b) -> StateL s a -> StateL s b

(<$) :: a -> StateL s b -> StateL s a

Functor (StateR s) 

Methods

fmap :: (a -> b) -> StateR s a -> StateR s b

(<$) :: a -> StateR s b -> StateR s a

Bifunctor p => Functor (Join p) 

Methods

fmap :: (a -> b) -> Join p a -> Join p b

(<$) :: a -> Join p b -> Join p a

Functor m => Functor (IdentityT m) 

Methods

fmap :: (a -> b) -> IdentityT m a -> IdentityT m b

(<$) :: a -> IdentityT m b -> IdentityT m a

Functor (State s) 

Methods

fmap :: (a -> b) -> State s a -> State s b

(<$) :: a -> State s b -> State s a

Functor (Map k) 

Methods

fmap :: (a -> b) -> Map k a -> Map k b

(<$) :: a -> Map k b -> Map k a

Functor (Arg a) 

Methods

fmap :: (b -> c) -> Arg a b -> Arg a c

(<$) :: b -> Arg a c -> Arg a b

Functor f => Functor (Reverse f)

Derived instance.

Methods

fmap :: (a -> b) -> Reverse f a -> Reverse f b

(<$) :: a -> Reverse f b -> Reverse f a

Functor f => Functor (Backwards f)

Derived instance.

Methods

fmap :: (a -> b) -> Backwards f a -> Backwards f b

(<$) :: a -> Backwards f b -> Backwards f a

Functor m => Functor (MaybeT m) 

Methods

fmap :: (a -> b) -> MaybeT m a -> MaybeT m b

(<$) :: a -> MaybeT m b -> MaybeT m a

Functor m => Functor (ListT m) 

Methods

fmap :: (a -> b) -> ListT m a -> ListT m b

(<$) :: a -> ListT m b -> ListT m a

Functor f => Functor (Lift f) 

Methods

fmap :: (a -> b) -> Lift f a -> Lift f b

(<$) :: a -> Lift f b -> Lift f a

Functor (Constant a) 

Methods

fmap :: (b -> c) -> Constant a b -> Constant a c

(<$) :: b -> Constant a c -> Constant a b

Functor (HashMap k) 

Methods

fmap :: (a -> b) -> HashMap k a -> HashMap k b

(<$) :: a -> HashMap k b -> HashMap k a

Functor f => Functor (MaybeApply f) 

Methods

fmap :: (a -> b) -> MaybeApply f a -> MaybeApply f b

(<$) :: a -> MaybeApply f b -> MaybeApply f a

Functor f => Functor (WrappedApplicative f) 

Methods

fmap :: (a -> b) -> WrappedApplicative f a -> WrappedApplicative f b

(<$) :: a -> WrappedApplicative f b -> WrappedApplicative f a

Arrow a => Functor (WrappedArrow a b) 

Methods

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

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

Functor f => Functor (Alt * f) 

Methods

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

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

Bifunctor p => Functor (WrappedBifunctor p a) 

Methods

fmap :: (b -> c) -> WrappedBifunctor p a b -> WrappedBifunctor p a c

(<$) :: b -> WrappedBifunctor p a c -> WrappedBifunctor p a b

Functor g => Functor (Joker g a) 

Methods

fmap :: (b -> c) -> Joker g a b -> Joker g a c

(<$) :: b -> Joker g a c -> Joker g a b

Bifunctor p => Functor (Flip p a) 

Methods

fmap :: (b -> c) -> Flip p a b -> Flip p a c

(<$) :: b -> Flip p a c -> Flip p a b

Functor (Clown f a) 

Methods

fmap :: (b -> c) -> Clown f a b -> Clown f a c

(<$) :: b -> Clown f a c -> Clown f a b

(Functor f, Functor g) => Functor (Coproduct f g) 

Methods

fmap :: (a -> b) -> Coproduct f g a -> Coproduct f g b

(<$) :: a -> Coproduct f g b -> Coproduct f g a

Functor w => Functor (TracedT m w) 

Methods

fmap :: (a -> b) -> TracedT m w a -> TracedT m w b

(<$) :: a -> TracedT m w b -> TracedT m w a

Functor w => Functor (StoreT s w) 

Methods

fmap :: (a -> b) -> StoreT s w a -> StoreT s w b

(<$) :: a -> StoreT s w b -> StoreT s w a

Functor w => Functor (EnvT e w) 

Methods

fmap :: (a -> b) -> EnvT e w a -> EnvT e w b

(<$) :: a -> EnvT e w b -> EnvT e w a

Functor (Cokleisli w a) 

Methods

fmap :: (b -> c) -> Cokleisli w a b -> Cokleisli w a c

(<$) :: b -> Cokleisli w a c -> Cokleisli w a b

Functor (Tagged k s) 

Methods

fmap :: (a -> b) -> Tagged k s a -> Tagged k s b

(<$) :: a -> Tagged k s b -> Tagged k s a

(Functor f, Functor g) => Functor (Sum f g) 

Methods

fmap :: (a -> b) -> Sum f g a -> Sum f g b

(<$) :: a -> Sum f g b -> Sum f g a

(Functor f, Functor g) => Functor (Product f g) 

Methods

fmap :: (a -> b) -> Product f g a -> Product f g b

(<$) :: a -> Product f g b -> Product f g a

(Functor f, Functor g) => Functor (Compose f g) 

Methods

fmap :: (a -> b) -> Compose f g a -> Compose f g b

(<$) :: a -> Compose f g b -> Compose f g a

Functor m => Functor (WriterT w m) 

Methods

fmap :: (a -> b) -> WriterT w m a -> WriterT w m b

(<$) :: a -> WriterT w m b -> WriterT w m a

Functor m => Functor (WriterT w m) 

Methods

fmap :: (a -> b) -> WriterT w m a -> WriterT w m b

(<$) :: a -> WriterT w m b -> WriterT w m a

Functor m => Functor (ErrorT e m) 

Methods

fmap :: (a -> b) -> ErrorT e m a -> ErrorT e m b

(<$) :: a -> ErrorT e m b -> ErrorT e m a

Functor m => Functor (ExceptT e m) 

Methods

fmap :: (a -> b) -> ExceptT e m a -> ExceptT e m b

(<$) :: a -> ExceptT e m b -> ExceptT e m a

Functor m => Functor (StateT s m) 

Methods

fmap :: (a -> b) -> StateT s m a -> StateT s m b

(<$) :: a -> StateT s m b -> StateT s m a

Functor m => Functor (StateT s m) 

Methods

fmap :: (a -> b) -> StateT s m a -> StateT s m b

(<$) :: a -> StateT s m b -> StateT s m a

Functor m => Functor (ReaderT r m) 

Methods

fmap :: (a -> b) -> ReaderT r m a -> ReaderT r m b

(<$) :: a -> ReaderT r m b -> ReaderT r m a

Functor (ContT r m) 

Methods

fmap :: (a -> b) -> ContT r m a -> ContT r m b

(<$) :: a -> ContT r m b -> ContT r m a

Functor f => Functor (Static f a) 

Methods

fmap :: (b -> c) -> Static f a b -> Static f a c

(<$) :: b -> Static f a c -> Static f a b

(Functor f, Bifunctor p) => Functor (Tannen f p a) 

Methods

fmap :: (b -> c) -> Tannen f p a b -> Tannen f p a c

(<$) :: b -> Tannen f p a c -> Tannen f p a b

(Bifunctor p, Functor g) => Functor (Biff p f g a) 

Methods

fmap :: (b -> c) -> Biff p f g a b -> Biff p f g a c

(<$) :: b -> Biff p f g a c -> Biff p f g a b

Functor m => Functor (RWST r w s m) 

Methods

fmap :: (a -> b) -> RWST r w s m a -> RWST r w s m b

(<$) :: a -> RWST r w s m b -> RWST r w s m a

Functor m => Functor (RWST r w s m) 

Methods

fmap :: (a -> b) -> RWST r w s m a -> RWST r w s m b

(<$) :: a -> RWST r w s m b -> RWST r w s m a

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

An infix synonym for fmap.

Examples

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

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

Convert from an Either Int Int to an Either Int String using show:

>>> show <$> Left 17
Left 17
>>> show <$> Right 17
Right "17"

Double each element of a list:

>>> (*2) <$> [1,2,3]
[2,4,6]

Apply even to the second element of a pair:

>>> even <$> (2,2)
(2,True)

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

Flipped version of <$.

Examples

Replace the contents of a Maybe Int with a constant String:

>>> Nothing $> "foo"
Nothing
>>> Just 90210 $> "foo"
Just "foo"

Replace the contents of an Either Int Int with a constant String, resulting in an Either Int String:

>>> Left 8675309 $> "foo"
Left 8675309
>>> Right 8675309 $> "foo"
Right "foo"

Replace each element of a list with a constant String:

>>> [1,2,3] $> "foo"
["foo","foo","foo"]

Replace the second element of a pair with a constant String:

>>> (1,2) $> "foo"
(1,"foo")

Since: 4.7.0.0

Apply - a strong lax semimonoidal endofunctor

class Functor f => Apply f where Source

A strong lax semi-monoidal endofunctor. This is equivalent to an Applicative without pure.

Laws:

associative composition: (.) <$> u <.> v <.> w = u <.> (v <.> w)

Minimal complete definition

(<.>)

Methods

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

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

a  .> b = const id <$> a <.> b

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

a <. b = const <$> a <.> b

Instances

Apply [] Source 

Methods

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

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

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

Apply IO Source 

Methods

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

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

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

Apply Identity Source 

Methods

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

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

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

Apply ZipList Source 

Methods

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

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

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

Apply Maybe Source 

Methods

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

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

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

Apply IntMap Source

An IntMap is not Applicative, but it is an instance of Apply

Methods

(<.>) :: IntMap (a -> b) -> IntMap a -> IntMap b Source

(.>) :: IntMap a -> IntMap b -> IntMap b Source

(<.) :: IntMap a -> IntMap b -> IntMap a Source

Apply Tree Source 

Methods

(<.>) :: Tree (a -> b) -> Tree a -> Tree b Source

(.>) :: Tree a -> Tree b -> Tree b Source

(<.) :: Tree a -> Tree b -> Tree a Source

Apply Seq Source 

Methods

(<.>) :: Seq (a -> b) -> Seq a -> Seq b Source

(.>) :: Seq a -> Seq b -> Seq b Source

(<.) :: Seq a -> Seq b -> Seq a Source

Apply Option Source 

Methods

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

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

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

Apply NonEmpty Source 

Methods

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

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

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

Apply ((->) m) Source 

Methods

(<.>) :: (m -> a -> b) -> (m -> a) -> m -> b Source

(.>) :: (m -> a) -> (m -> b) -> m -> b Source

(<.) :: (m -> a) -> (m -> b) -> m -> a Source

Apply (Either a) Source 

Methods

(<.>) :: Either a (b -> c) -> Either a b -> Either a c Source

(.>) :: Either a b -> Either a c -> Either a c Source

(<.) :: Either a b -> Either a c -> Either a b Source

Semigroup m => Apply ((,) m) Source 

Methods

(<.>) :: (m, a -> b) -> (m, a) -> (m, b) Source

(.>) :: (m, a) -> (m, b) -> (m, b) Source

(<.) :: (m, a) -> (m, b) -> (m, a) Source

Semigroup m => Apply (Const m) Source 

Methods

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

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

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

Monad m => Apply (WrappedMonad m) Source 
Biapply p => Apply (Join p) Source 

Methods

(<.>) :: Join p (a -> b) -> Join p a -> Join p b Source

(.>) :: Join p a -> Join p b -> Join p b Source

(<.) :: Join p a -> Join p b -> Join p a Source

Apply w => Apply (IdentityT w) Source 

Methods

(<.>) :: IdentityT w (a -> b) -> IdentityT w a -> IdentityT w b Source

(.>) :: IdentityT w a -> IdentityT w b -> IdentityT w b Source

(<.) :: IdentityT w a -> IdentityT w b -> IdentityT w a Source

Ord k => Apply (Map k) Source

A Map is not Applicative, but it is an instance of Apply

Methods

(<.>) :: Map k (a -> b) -> Map k a -> Map k b Source

(.>) :: Map k a -> Map k b -> Map k b Source

(<.) :: Map k a -> Map k b -> Map k a Source

Apply f => Apply (Reverse f) Source 

Methods

(<.>) :: Reverse f (a -> b) -> Reverse f a -> Reverse f b Source

(.>) :: Reverse f a -> Reverse f b -> Reverse f b Source

(<.) :: Reverse f a -> Reverse f b -> Reverse f a Source

Apply f => Apply (Backwards f) Source 

Methods

(<.>) :: Backwards f (a -> b) -> Backwards f a -> Backwards f b Source

(.>) :: Backwards f a -> Backwards f b -> Backwards f b Source

(<.) :: Backwards f a -> Backwards f b -> Backwards f a Source

(Functor m, Monad m) => Apply (MaybeT m) Source 

Methods

(<.>) :: MaybeT m (a -> b) -> MaybeT m a -> MaybeT m b Source

(.>) :: MaybeT m a -> MaybeT m b -> MaybeT m b Source

(<.) :: MaybeT m a -> MaybeT m b -> MaybeT m a Source

Apply m => Apply (ListT m) Source 

Methods

(<.>) :: ListT m (a -> b) -> ListT m a -> ListT m b Source

(.>) :: ListT m a -> ListT m b -> ListT m b Source

(<.) :: ListT m a -> ListT m b -> ListT m a Source

Apply f => Apply (Lift f) Source 

Methods

(<.>) :: Lift f (a -> b) -> Lift f a -> Lift f b Source

(.>) :: Lift f a -> Lift f b -> Lift f b Source

(<.) :: Lift f a -> Lift f b -> Lift f a Source

Semigroup f => Apply (Constant f) Source 

Methods

(<.>) :: Constant f (a -> b) -> Constant f a -> Constant f b Source

(.>) :: Constant f a -> Constant f b -> Constant f b Source

(<.) :: Constant f a -> Constant f b -> Constant f a Source

Apply f => Apply (MaybeApply f) Source 

Methods

(<.>) :: MaybeApply f (a -> b) -> MaybeApply f a -> MaybeApply f b Source

(.>) :: MaybeApply f a -> MaybeApply f b -> MaybeApply f b Source

(<.) :: MaybeApply f a -> MaybeApply f b -> MaybeApply f a Source

Applicative f => Apply (WrappedApplicative f) Source 
Arrow a => Apply (WrappedArrow a b) Source 

Methods

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

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

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

Apply w => Apply (TracedT m w) Source 

Methods

(<.>) :: TracedT m w (a -> b) -> TracedT m w a -> TracedT m w b Source

(.>) :: TracedT m w a -> TracedT m w b -> TracedT m w b Source

(<.) :: TracedT m w a -> TracedT m w b -> TracedT m w a Source

(Apply w, Semigroup s) => Apply (StoreT s w) Source 

Methods

(<.>) :: StoreT s w (a -> b) -> StoreT s w a -> StoreT s w b Source

(.>) :: StoreT s w a -> StoreT s w b -> StoreT s w b Source

(<.) :: StoreT s w a -> StoreT s w b -> StoreT s w a Source

(Semigroup e, Apply w) => Apply (EnvT e w) Source 

Methods

(<.>) :: EnvT e w (a -> b) -> EnvT e w a -> EnvT e w b Source

(.>) :: EnvT e w a -> EnvT e w b -> EnvT e w b Source

(<.) :: EnvT e w a -> EnvT e w b -> EnvT e w a Source

Apply (Cokleisli w a) Source 

Methods

(<.>) :: Cokleisli w a (b -> c) -> Cokleisli w a b -> Cokleisli w a c Source

(.>) :: Cokleisli w a b -> Cokleisli w a c -> Cokleisli w a c Source

(<.) :: Cokleisli w a b -> Cokleisli w a c -> Cokleisli w a b Source

(Apply f, Apply g) => Apply (Product f g) Source 

Methods

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

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

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

(Apply f, Apply g) => Apply (Compose f g) Source 

Methods

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

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

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

(Apply m, Semigroup w) => Apply (WriterT w m) Source 

Methods

(<.>) :: WriterT w m (a -> b) -> WriterT w m a -> WriterT w m b Source

(.>) :: WriterT w m a -> WriterT w m b -> WriterT w m b Source

(<.) :: WriterT w m a -> WriterT w m b -> WriterT w m a Source

(Apply m, Semigroup w) => Apply (WriterT w m) Source 

Methods

(<.>) :: WriterT w m (a -> b) -> WriterT w m a -> WriterT w m b Source

(.>) :: WriterT w m a -> WriterT w m b -> WriterT w m b Source

(<.) :: WriterT w m a -> WriterT w m b -> WriterT w m a Source

(Functor m, Monad m) => Apply (ErrorT e m) Source 

Methods

(<.>) :: ErrorT e m (a -> b) -> ErrorT e m a -> ErrorT e m b Source

(.>) :: ErrorT e m a -> ErrorT e m b -> ErrorT e m b Source

(<.) :: ErrorT e m a -> ErrorT e m b -> ErrorT e m a Source

(Functor m, Monad m) => Apply (ExceptT e m) Source 

Methods

(<.>) :: ExceptT e m (a -> b) -> ExceptT e m a -> ExceptT e m b Source

(.>) :: ExceptT e m a -> ExceptT e m b -> ExceptT e m b Source

(<.) :: ExceptT e m a -> ExceptT e m b -> ExceptT e m a Source

Bind m => Apply (StateT s m) Source 

Methods

(<.>) :: StateT s m (a -> b) -> StateT s m a -> StateT s m b Source

(.>) :: StateT s m a -> StateT s m b -> StateT s m b Source

(<.) :: StateT s m a -> StateT s m b -> StateT s m a Source

Bind m => Apply (StateT s m) Source 

Methods

(<.>) :: StateT s m (a -> b) -> StateT s m a -> StateT s m b Source

(.>) :: StateT s m a -> StateT s m b -> StateT s m b Source

(<.) :: StateT s m a -> StateT s m b -> StateT s m a Source

Apply m => Apply (ReaderT e m) Source 

Methods

(<.>) :: ReaderT e m (a -> b) -> ReaderT e m a -> ReaderT e m b Source

(.>) :: ReaderT e m a -> ReaderT e m b -> ReaderT e m b Source

(<.) :: ReaderT e m a -> ReaderT e m b -> ReaderT e m a Source

Apply (ContT r m) Source 

Methods

(<.>) :: ContT r m (a -> b) -> ContT r m a -> ContT r m b Source

(.>) :: ContT r m a -> ContT r m b -> ContT r m b Source

(<.) :: ContT r m a -> ContT r m b -> ContT r m a Source

Apply f => Apply (Static f a) Source 

Methods

(<.>) :: Static f a (b -> c) -> Static f a b -> Static f a c Source

(.>) :: Static f a b -> Static f a c -> Static f a c Source

(<.) :: Static f a b -> Static f a c -> Static f a b Source

(Bind m, Semigroup w) => Apply (RWST r w s m) Source 

Methods

(<.>) :: RWST r w s m (a -> b) -> RWST r w s m a -> RWST r w s m b Source

(.>) :: RWST r w s m a -> RWST r w s m b -> RWST r w s m b Source

(<.) :: RWST r w s m a -> RWST r w s m b -> RWST r w s m a Source

(Bind m, Semigroup w) => Apply (RWST r w s m) Source 

Methods

(<.>) :: RWST r w s m (a -> b) -> RWST r w s m a -> RWST r w s m b Source

(.>) :: RWST r w s m a -> RWST r w s m b -> RWST r w s m b Source

(<.) :: RWST r w s m a -> RWST r w s m b -> RWST r w s m a Source

(<..>) :: Apply w => w a -> w (a -> b) -> w b infixl 4 Source

A variant of <.> with the arguments reversed.

liftF2 :: Apply w => (a -> b -> c) -> w a -> w b -> w c Source

Lift a binary function into a comonad with zipping

liftF3 :: Apply w => (a -> b -> c -> d) -> w a -> w b -> w c -> w d Source

Lift a ternary function into a comonad with zipping

Wrappers

newtype WrappedApplicative f a Source

Wrap an Applicative to be used as a member of Apply

Constructors

WrapApplicative 

Fields

Instances

Functor f => Functor (WrappedApplicative f) Source 

Methods

fmap :: (a -> b) -> WrappedApplicative f a -> WrappedApplicative f b

(<$) :: a -> WrappedApplicative f b -> WrappedApplicative f a

Applicative f => Applicative (WrappedApplicative f) Source 
Alternative f => Alternative (WrappedApplicative f) Source 
Applicative f => Apply (WrappedApplicative f) Source 
Alternative f => Alt (WrappedApplicative f) Source 
Alternative f => Plus (WrappedApplicative f) Source 

newtype MaybeApply f a Source

Transform a Apply into an Applicative by adding a unit.

Constructors

MaybeApply 

Fields

Instances

Functor f => Functor (MaybeApply f) Source 

Methods

fmap :: (a -> b) -> MaybeApply f a -> MaybeApply f b

(<$) :: a -> MaybeApply f b -> MaybeApply f a

Apply f => Applicative (MaybeApply f) Source 

Methods

pure :: a -> MaybeApply f a

(<*>) :: MaybeApply f (a -> b) -> MaybeApply f a -> MaybeApply f b

(*>) :: MaybeApply f a -> MaybeApply f b -> MaybeApply f b

(<*) :: MaybeApply f a -> MaybeApply f b -> MaybeApply f a

Comonad f => Comonad (MaybeApply f) Source 

Methods

extract :: MaybeApply f a -> a

duplicate :: MaybeApply f a -> MaybeApply f (MaybeApply f a)

extend :: (MaybeApply f a -> b) -> MaybeApply f a -> MaybeApply f b

Extend f => Extend (MaybeApply f) Source 

Methods

duplicated :: MaybeApply f a -> MaybeApply f (MaybeApply f a) Source

extended :: (MaybeApply f a -> b) -> MaybeApply f a -> MaybeApply f b Source

Apply f => Apply (MaybeApply f) Source 

Methods

(<.>) :: MaybeApply f (a -> b) -> MaybeApply f a -> MaybeApply f b Source

(.>) :: MaybeApply f a -> MaybeApply f b -> MaybeApply f b Source

(<.) :: MaybeApply f a -> MaybeApply f b -> MaybeApply f a Source