semigroupoids-5.3.2: Semigroupoids: Category sans id

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

Data.Functor.Bind.Class

Contents

Description

This module is used to resolve the cyclic we get from defining these classes here rather than in a package upstream. Otherwise we'd get orphaned heads for many instances on the types in transformers and bifunctors.

Synopsis

Applyable functors

class Functor f => Apply f where #

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

Laws:

(.) <$> u <.> v <.> w = u <.> (v <.> w)
x <.> (f <$> y) = (. f) <$> x <.> y
f <$> (x <.> y) = (f .) <$> x <.> y

The laws imply that .> and <. really ignore their left and right results, respectively, and really return their right and left results, respectively. Specifically,

(mf <$> m) .> (nf <$> n) = nf <$> (m .> n)
(mf <$> m) <. (nf <$> n) = mf <$> (m <. n)

Minimal complete definition

(<.>) | liftF2

Methods

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

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

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

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

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

liftF2 :: (a -> b -> c) -> f a -> f b -> f c #

Lift a binary function into a comonad with zipping

Instances
Apply [] # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> [a] -> [b] -> [c] #

Apply Maybe # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c #

Apply IO # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> IO a -> IO b -> IO c #

Apply Par1 # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<.>) :: Par1 (a -> b) -> Par1 a -> Par1 b #

(.>) :: Par1 a -> Par1 b -> Par1 b #

(<.) :: Par1 a -> Par1 b -> Par1 a #

liftF2 :: (a -> b -> c) -> Par1 a -> Par1 b -> Par1 c #

Apply Q # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<.>) :: Q (a -> b) -> Q a -> Q b #

(.>) :: Q a -> Q b -> Q b #

(<.) :: Q a -> Q b -> Q a #

liftF2 :: (a -> b -> c) -> Q a -> Q b -> Q c #

Apply Complex # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<.>) :: Complex (a -> b) -> Complex a -> Complex b #

(.>) :: Complex a -> Complex b -> Complex b #

(<.) :: Complex a -> Complex b -> Complex a #

liftF2 :: (a -> b -> c) -> Complex a -> Complex b -> Complex c #

Apply Min # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<.>) :: Min (a -> b) -> Min a -> Min b #

(.>) :: Min a -> Min b -> Min b #

(<.) :: Min a -> Min b -> Min a #

liftF2 :: (a -> b -> c) -> Min a -> Min b -> Min c #

Apply Max # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<.>) :: Max (a -> b) -> Max a -> Max b #

(.>) :: Max a -> Max b -> Max b #

(<.) :: Max a -> Max b -> Max a #

liftF2 :: (a -> b -> c) -> Max a -> Max b -> Max c #

Apply First # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<.>) :: First (a -> b) -> First a -> First b #

(.>) :: First a -> First b -> First b #

(<.) :: First a -> First b -> First a #

liftF2 :: (a -> b -> c) -> First a -> First b -> First c #

Apply Last # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<.>) :: Last (a -> b) -> Last a -> Last b #

(.>) :: Last a -> Last b -> Last b #

(<.) :: Last a -> Last b -> Last a #

liftF2 :: (a -> b -> c) -> Last a -> Last b -> Last c #

Apply Option # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> Option a -> Option b -> Option c #

Apply ZipList # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> ZipList a -> ZipList b -> ZipList c #

Apply Identity # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> Identity a -> Identity b -> Identity c #

Apply First # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<.>) :: First (a -> b) -> First a -> First b #

(.>) :: First a -> First b -> First b #

(<.) :: First a -> First b -> First a #

liftF2 :: (a -> b -> c) -> First a -> First b -> First c #

Apply Last # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<.>) :: Last (a -> b) -> Last a -> Last b #

(.>) :: Last a -> Last b -> Last b #

(<.) :: Last a -> Last b -> Last a #

liftF2 :: (a -> b -> c) -> Last a -> Last b -> Last c #

Apply Dual # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<.>) :: Dual (a -> b) -> Dual a -> Dual b #

(.>) :: Dual a -> Dual b -> Dual b #

(<.) :: Dual a -> Dual b -> Dual a #

liftF2 :: (a -> b -> c) -> Dual a -> Dual b -> Dual c #

Apply Sum # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<.>) :: Sum (a -> b) -> Sum a -> Sum b #

(.>) :: Sum a -> Sum b -> Sum b #

(<.) :: Sum a -> Sum b -> Sum a #

liftF2 :: (a -> b -> c) -> Sum a -> Sum b -> Sum c #

Apply Product # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<.>) :: Product (a -> b) -> Product a -> Product b #

(.>) :: Product a -> Product b -> Product b #

(<.) :: Product a -> Product b -> Product a #

liftF2 :: (a -> b -> c) -> Product a -> Product b -> Product c #

Apply Down # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<.>) :: Down (a -> b) -> Down a -> Down b #

(.>) :: Down a -> Down b -> Down b #

(<.) :: Down a -> Down b -> Down a #

liftF2 :: (a -> b -> c) -> Down a -> Down b -> Down c #

Apply NonEmpty # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c #

Apply IntMap #

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

Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> IntMap a -> IntMap b -> IntMap c #

Apply Tree # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> Tree a -> Tree b -> Tree c #

Apply Seq # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> Seq a -> Seq b -> Seq c #

Apply (Either a) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<.>) :: Either a (a0 -> b) -> Either a a0 -> Either a b #

(.>) :: Either a a0 -> Either a b -> Either a b #

(<.) :: Either a a0 -> Either a b -> Either a a0 #

liftF2 :: (a0 -> b -> c) -> Either a a0 -> Either a b -> Either a c #

Apply (V1 :: Type -> Type) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<.>) :: V1 (a -> b) -> V1 a -> V1 b #

(.>) :: V1 a -> V1 b -> V1 b #

(<.) :: V1 a -> V1 b -> V1 a #

liftF2 :: (a -> b -> c) -> V1 a -> V1 b -> V1 c #

Apply (U1 :: Type -> Type) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<.>) :: U1 (a -> b) -> U1 a -> U1 b #

(.>) :: U1 a -> U1 b -> U1 b #

(<.) :: U1 a -> U1 b -> U1 a #

liftF2 :: (a -> b -> c) -> U1 a -> U1 b -> U1 c #

Semigroup m => Apply ((,) m) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> (m, a) -> (m, b) -> (m, c) #

Monad m => Apply (WrappedMonad m) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<.>) :: WrappedMonad m (a -> b) -> WrappedMonad m a -> WrappedMonad m b #

(.>) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m b #

(<.) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m a #

liftF2 :: (a -> b -> c) -> WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m c #

Apply (Proxy :: Type -> Type) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<.>) :: Proxy (a -> b) -> Proxy a -> Proxy b #

(.>) :: Proxy a -> Proxy b -> Proxy b #

(<.) :: Proxy a -> Proxy b -> Proxy a #

liftF2 :: (a -> b -> c) -> Proxy a -> Proxy b -> Proxy c #

Ord k => Apply (Map k) #

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

Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> Map k a -> Map k b -> Map k c #

Apply f => Apply (Lift f) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> Lift f a -> Lift f b -> Lift f c #

(Functor m, Monad m) => Apply (MaybeT m) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> MaybeT m a -> MaybeT m b -> MaybeT m c #

Apply m => Apply (ListT m) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> ListT m a -> ListT m b -> ListT m c #

(Hashable k, Eq k) => Apply (HashMap k) #

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

Instance details

Defined in Data.Functor.Bind.Class

Methods

(<.>) :: HashMap k (a -> b) -> HashMap k a -> HashMap k b #

(.>) :: HashMap k a -> HashMap k b -> HashMap k b #

(<.) :: HashMap k a -> HashMap k b -> HashMap k a #

liftF2 :: (a -> b -> c) -> HashMap k a -> HashMap k b -> HashMap k c #

Apply f => Apply (MaybeApply f) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<.>) :: 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 #

liftF2 :: (a -> b -> c) -> MaybeApply f a -> MaybeApply f b -> MaybeApply f c #

Applicative f => Apply (WrappedApplicative f) # 
Instance details

Defined in Data.Functor.Bind.Class

Apply f => Apply (Rec1 f) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<.>) :: Rec1 f (a -> b) -> Rec1 f a -> Rec1 f b #

(.>) :: Rec1 f a -> Rec1 f b -> Rec1 f b #

(<.) :: Rec1 f a -> Rec1 f b -> Rec1 f a #

liftF2 :: (a -> b -> c) -> Rec1 f a -> Rec1 f b -> Rec1 f c #

Arrow a => Apply (WrappedArrow a b) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<.>) :: WrappedArrow a b (a0 -> b0) -> WrappedArrow a b a0 -> WrappedArrow a b b0 #

(.>) :: WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b b0 #

(<.) :: WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b a0 #

liftF2 :: (a0 -> b0 -> c) -> WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b c #

Semigroup m => Apply (Const m :: Type -> Type) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> Const m a -> Const m b -> Const m c #

Apply f => Apply (Alt f) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<.>) :: Alt f (a -> b) -> Alt f a -> Alt f b #

(.>) :: Alt f a -> Alt f b -> Alt f b #

(<.) :: Alt f a -> Alt f b -> Alt f a #

liftF2 :: (a -> b -> c) -> Alt f a -> Alt f b -> Alt f c #

Biapply p => Apply (Join p) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> Join p a -> Join p b -> Join p c #

Apply w => Apply (TracedT m w) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> TracedT m w a -> TracedT m w b -> TracedT m w c #

(Apply w, Semigroup s) => Apply (StoreT s w) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> StoreT s w a -> StoreT s w b -> StoreT s w c #

(Semigroup e, Apply w) => Apply (EnvT e w) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> EnvT e w a -> EnvT e w b -> EnvT e w c #

Apply w => Apply (IdentityT w) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> IdentityT w a -> IdentityT w b -> IdentityT w c #

Apply (Tagged a) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<.>) :: Tagged a (a0 -> b) -> Tagged a a0 -> Tagged a b #

(.>) :: Tagged a a0 -> Tagged a b -> Tagged a b #

(<.) :: Tagged a a0 -> Tagged a b -> Tagged a a0 #

liftF2 :: (a0 -> b -> c) -> Tagged a a0 -> Tagged a b -> Tagged a c #

Apply f => Apply (Reverse f) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> Reverse f a -> Reverse f b -> Reverse f c #

Semigroup f => Apply (Constant f :: Type -> Type) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> Constant f a -> Constant f b -> Constant f c #

(Apply m, Semigroup w) => Apply (WriterT w m) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> WriterT w m a -> WriterT w m b -> WriterT w m c #

(Apply m, Semigroup w) => Apply (WriterT w m) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> WriterT w m a -> WriterT w m b -> WriterT w m c #

Bind m => Apply (StateT s m) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> StateT s m a -> StateT s m b -> StateT s m c #

Bind m => Apply (StateT s m) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> StateT s m a -> StateT s m b -> StateT s m c #

Apply m => Apply (ReaderT e m) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> ReaderT e m a -> ReaderT e m b -> ReaderT e m c #

(Functor m, Monad m) => Apply (ExceptT e m) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> ExceptT e m a -> ExceptT e m b -> ExceptT e m c #

(Functor m, Monad m) => Apply (ErrorT e m) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> ErrorT e m a -> ErrorT e m b -> ErrorT e m c #

Apply f => Apply (Backwards f) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> Backwards f a -> Backwards f b -> Backwards f c #

Apply f => Apply (Static f a) # 
Instance details

Defined in Data.Semigroupoid.Static

Methods

(<.>) :: Static f a (a0 -> b) -> Static f a a0 -> Static f a b #

(.>) :: Static f a a0 -> Static f a b -> Static f a b #

(<.) :: Static f a a0 -> Static f a b -> Static f a a0 #

liftF2 :: (a0 -> b -> c) -> Static f a a0 -> Static f a b -> Static f a c #

Apply ((->) m :: Type -> Type) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> (m -> a) -> (m -> b) -> m -> c #

Semigroup c => Apply (K1 i c :: Type -> Type) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<.>) :: K1 i c (a -> b) -> K1 i c a -> K1 i c b #

(.>) :: K1 i c a -> K1 i c b -> K1 i c b #

(<.) :: K1 i c a -> K1 i c b -> K1 i c a #

liftF2 :: (a -> b -> c0) -> K1 i c a -> K1 i c b -> K1 i c c0 #

(Apply f, Apply g) => Apply (f :*: g) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> (f :*: g) a -> (f :*: g) b -> (f :*: g) c #

(Apply f, Apply g) => Apply (Product f g) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> Product f g a -> Product f g b -> Product f g c #

Apply (Cokleisli w a) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<.>) :: Cokleisli w a (a0 -> b) -> Cokleisli w a a0 -> Cokleisli w a b #

(.>) :: Cokleisli w a a0 -> Cokleisli w a b -> Cokleisli w a b #

(<.) :: Cokleisli w a a0 -> Cokleisli w a b -> Cokleisli w a a0 #

liftF2 :: (a0 -> b -> c) -> Cokleisli w a a0 -> Cokleisli w a b -> Cokleisli w a c #

Apply (ContT r m) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> ContT r m a -> ContT r m b -> ContT r m c #

Apply f => Apply (M1 i t f) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<.>) :: M1 i t f (a -> b) -> M1 i t f a -> M1 i t f b #

(.>) :: M1 i t f a -> M1 i t f b -> M1 i t f b #

(<.) :: M1 i t f a -> M1 i t f b -> M1 i t f a #

liftF2 :: (a -> b -> c) -> M1 i t f a -> M1 i t f b -> M1 i t f c #

(Apply f, Apply g) => Apply (f :.: g) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

(.>) :: (f :.: g) a -> (f :.: g) b -> (f :.: g) b #

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

liftF2 :: (a -> b -> c) -> (f :.: g) a -> (f :.: g) b -> (f :.: g) c #

(Apply f, Apply g) => Apply (Compose f g) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> Compose f g a -> Compose f g b -> Compose f g c #

(Bind m, Semigroup w) => Apply (RWST r w s m) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> RWST r w s m a -> RWST r w s m b -> RWST r w s m c #

(Bind m, Semigroup w) => Apply (RWST r w s m) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> RWST r w s m a -> RWST r w s m b -> RWST r w s m c #

Wrappers

newtype WrappedApplicative f a #

Wrap an Applicative to be used as a member of Apply

Constructors

WrapApplicative 

Fields

Instances
Functor f => Functor (WrappedApplicative f) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

Applicative f => Applicative (WrappedApplicative f) # 
Instance details

Defined in Data.Functor.Bind.Class

Alternative f => Alternative (WrappedApplicative f) # 
Instance details

Defined in Data.Functor.Bind.Class

Applicative f => Apply (WrappedApplicative f) # 
Instance details

Defined in Data.Functor.Bind.Class

Alternative f => Alt (WrappedApplicative f) # 
Instance details

Defined in Data.Functor.Alt

Alternative f => Plus (WrappedApplicative f) # 
Instance details

Defined in Data.Functor.Plus

Methods

zero :: WrappedApplicative f a #

newtype MaybeApply f a #

Transform a Apply into an Applicative by adding a unit.

Constructors

MaybeApply 

Fields

Instances
Functor f => Functor (MaybeApply f) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

Apply f => Applicative (MaybeApply f) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

pure :: a -> MaybeApply f a #

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

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

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

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

Comonad f => Comonad (MaybeApply f) # 
Instance details

Defined in Data.Functor.Bind.Class

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

Defined in Data.Functor.Bind.Class

Methods

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

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

Apply f => Apply (MaybeApply f) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<.>) :: 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 #

liftF2 :: (a -> b -> c) -> MaybeApply f a -> MaybeApply f b -> MaybeApply f c #

Bindable functors

class Apply m => Bind m where #

A Monad sans return.

Minimal definition: Either join or >>-

If defining both, then the following laws (the default definitions) must hold:

join = (>>- id)
m >>- f = join (fmap f m)

Laws:

induced definition of <.>: f <.> x = f >>- (<$> x)

Finally, there are two associativity conditions:

associativity of (>>-):    (m >>- f) >>- g == m >>- (\x -> f x >>- g)
associativity of join:     join . join = join . fmap join

These can both be seen as special cases of the constraint that

associativity of (->-): (f ->- g) ->- h = f ->- (g ->- h)

Minimal complete definition

(>>-) | join

Methods

(>>-) :: m a -> (a -> m b) -> m b infixl 1 #

join :: m (m a) -> m a #

Instances
Bind [] # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: [[a]] -> [a] #

Bind Maybe # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: Maybe (Maybe a) -> Maybe a #

Bind IO # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: IO (IO a) -> IO a #

Bind Q # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(>>-) :: Q a -> (a -> Q b) -> Q b #

join :: Q (Q a) -> Q a #

Bind Complex # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: Complex (Complex a) -> Complex a #

Bind Min # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: Min (Min a) -> Min a #

Bind Max # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: Max (Max a) -> Max a #

Bind First # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: First (First a) -> First a #

Bind Last # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: Last (Last a) -> Last a #

Bind Option # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: Option (Option a) -> Option a #

Bind Identity # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: Identity (Identity a) -> Identity a #

Bind First # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: First (First a) -> First a #

Bind Last # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: Last (Last a) -> Last a #

Bind Dual # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: Dual (Dual a) -> Dual a #

Bind Sum # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: Sum (Sum a) -> Sum a #

Bind Product # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: Product (Product a) -> Product a #

Bind Down # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(>>-) :: Down a -> (a -> Down b) -> Down b #

join :: Down (Down a) -> Down a #

Bind NonEmpty # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: NonEmpty (NonEmpty a) -> NonEmpty a #

Bind IntMap #

An IntMap is not a Monad, but it is an instance of Bind

Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: IntMap (IntMap a) -> IntMap a #

Bind Tree # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: Tree (Tree a) -> Tree a #

Bind Seq # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: Seq (Seq a) -> Seq a #

Bind (Either a) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(>>-) :: Either a a0 -> (a0 -> Either a b) -> Either a b #

join :: Either a (Either a a0) -> Either a a0 #

Bind (V1 :: Type -> Type) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(>>-) :: V1 a -> (a -> V1 b) -> V1 b #

join :: V1 (V1 a) -> V1 a #

Semigroup m => Bind ((,) m) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(>>-) :: (m, a) -> (a -> (m, b)) -> (m, b) #

join :: (m, (m, a)) -> (m, a) #

Monad m => Bind (WrappedMonad m) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: WrappedMonad m (WrappedMonad m a) -> WrappedMonad m a #

Bind (Proxy :: Type -> Type) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: Proxy (Proxy a) -> Proxy a #

Ord k => Bind (Map k) #

A Map is not a Monad, but it is an instance of Bind

Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: Map k (Map k a) -> Map k a #

(Functor m, Monad m) => Bind (MaybeT m) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: MaybeT m (MaybeT m a) -> MaybeT m a #

(Apply m, Monad m) => Bind (ListT m) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: ListT m (ListT m a) -> ListT m a #

(Hashable k, Eq k) => Bind (HashMap k) #

A HashMap is not a Monad, but it is an instance of Bind

Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: HashMap k (HashMap k a) -> HashMap k a #

Bind f => Bind (Alt f) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(>>-) :: Alt f a -> (a -> Alt f b) -> Alt f b #

join :: Alt f (Alt f a) -> Alt f a #

Bind m => Bind (IdentityT m) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: IdentityT m (IdentityT m a) -> IdentityT m a #

Bind (Tagged a) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(>>-) :: Tagged a a0 -> (a0 -> Tagged a b) -> Tagged a b #

join :: Tagged a (Tagged a a0) -> Tagged a a0 #

(Bind m, Semigroup w) => Bind (WriterT w m) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: WriterT w m (WriterT w m a) -> WriterT w m a #

(Bind m, Semigroup w) => Bind (WriterT w m) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: WriterT w m (WriterT w m a) -> WriterT w m a #

Bind m => Bind (StateT s m) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: StateT s m (StateT s m a) -> StateT s m a #

Bind m => Bind (StateT s m) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: StateT s m (StateT s m a) -> StateT s m a #

Bind m => Bind (ReaderT e m) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(>>-) :: ReaderT e m a -> (a -> ReaderT e m b) -> ReaderT e m b #

join :: ReaderT e m (ReaderT e m a) -> ReaderT e m a #

(Functor m, Monad m) => Bind (ExceptT e m) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: ExceptT e m (ExceptT e m a) -> ExceptT e m a #

(Functor m, Monad m) => Bind (ErrorT e m) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: ErrorT e m (ErrorT e m a) -> ErrorT e m a #

Bind ((->) m :: Type -> Type) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(>>-) :: (m -> a) -> (a -> m -> b) -> m -> b #

join :: (m -> (m -> a)) -> m -> a #

(Bind f, Bind g) => Bind (Product f g) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: Product f g (Product f g a) -> Product f g a #

Bind (ContT r m) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: ContT r m (ContT r m a) -> ContT r m a #

(Bind m, Semigroup w) => Bind (RWST r w s m) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: RWST r w s m (RWST r w s m a) -> RWST r w s m a #

(Bind m, Semigroup w) => Bind (RWST r w s m) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

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

join :: RWST r w s m (RWST r w s m a) -> RWST r w s m a #

apDefault :: Bind f => f (a -> b) -> f a -> f b #

returning :: Functor f => f a -> (a -> b) -> f b #

Biappliable bifunctors

class Bifunctor p => Biapply p where #

Minimal complete definition

(<<.>>)

Methods

(<<.>>) :: p (a -> b) (c -> d) -> p a c -> p b d infixl 4 #

(.>>) :: p a b -> p c d -> p c d infixl 4 #

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

(<<.) :: p a b -> p c d -> p a b infixl 4 #

a <. b ≡ const <$> a <.> b
Instances
Biapply (,) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<<.>>) :: (a -> b, c -> d) -> (a, c) -> (b, d) #

(.>>) :: (a, b) -> (c, d) -> (c, d) #

(<<.) :: (a, b) -> (c, d) -> (a, b) #

Biapply Arg # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<<.>>) :: Arg (a -> b) (c -> d) -> Arg a c -> Arg b d #

(.>>) :: Arg a b -> Arg c d -> Arg c d #

(<<.) :: Arg a b -> Arg c d -> Arg a b #

Semigroup x => Biapply ((,,) x) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<<.>>) :: (x, a -> b, c -> d) -> (x, a, c) -> (x, b, d) #

(.>>) :: (x, a, b) -> (x, c, d) -> (x, c, d) #

(<<.) :: (x, a, b) -> (x, c, d) -> (x, a, b) #

Biapply (Const :: Type -> Type -> Type) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<<.>>) :: Const (a -> b) (c -> d) -> Const a c -> Const b d #

(.>>) :: Const a b -> Const c d -> Const c d #

(<<.) :: Const a b -> Const c d -> Const a b #

Biapply (Tagged :: Type -> Type -> Type) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<<.>>) :: Tagged (a -> b) (c -> d) -> Tagged a c -> Tagged b d #

(.>>) :: Tagged a b -> Tagged c d -> Tagged c d #

(<<.) :: Tagged a b -> Tagged c d -> Tagged a b #

(Semigroup x, Semigroup y) => Biapply ((,,,) x y) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<<.>>) :: (x, y, a -> b, c -> d) -> (x, y, a, c) -> (x, y, b, d) #

(.>>) :: (x, y, a, b) -> (x, y, c, d) -> (x, y, c, d) #

(<<.) :: (x, y, a, b) -> (x, y, c, d) -> (x, y, a, b) #

(Semigroup x, Semigroup y, Semigroup z) => Biapply ((,,,,) x y z) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<<.>>) :: (x, y, z, a -> b, c -> d) -> (x, y, z, a, c) -> (x, y, z, b, d) #

(.>>) :: (x, y, z, a, b) -> (x, y, z, c, d) -> (x, y, z, c, d) #

(<<.) :: (x, y, z, a, b) -> (x, y, z, c, d) -> (x, y, z, a, b) #

Biapply p => Biapply (WrappedBifunctor p) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<<.>>) :: WrappedBifunctor p (a -> b) (c -> d) -> WrappedBifunctor p a c -> WrappedBifunctor p b d #

(.>>) :: WrappedBifunctor p a b -> WrappedBifunctor p c d -> WrappedBifunctor p c d #

(<<.) :: WrappedBifunctor p a b -> WrappedBifunctor p c d -> WrappedBifunctor p a b #

Apply g => Biapply (Joker g :: Type -> Type -> Type) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<<.>>) :: Joker g (a -> b) (c -> d) -> Joker g a c -> Joker g b d #

(.>>) :: Joker g a b -> Joker g c d -> Joker g c d #

(<<.) :: Joker g a b -> Joker g c d -> Joker g a b #

Biapply p => Biapply (Flip p) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<<.>>) :: Flip p (a -> b) (c -> d) -> Flip p a c -> Flip p b d #

(.>>) :: Flip p a b -> Flip p c d -> Flip p c d #

(<<.) :: Flip p a b -> Flip p c d -> Flip p a b #

Apply f => Biapply (Clown f :: Type -> Type -> Type) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<<.>>) :: Clown f (a -> b) (c -> d) -> Clown f a c -> Clown f b d #

(.>>) :: Clown f a b -> Clown f c d -> Clown f c d #

(<<.) :: Clown f a b -> Clown f c d -> Clown f a b #

(Biapply p, Biapply q) => Biapply (Product p q) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<<.>>) :: Product p q (a -> b) (c -> d) -> Product p q a c -> Product p q b d #

(.>>) :: Product p q a b -> Product p q c d -> Product p q c d #

(<<.) :: Product p q a b -> Product p q c d -> Product p q a b #

(Apply f, Biapply p) => Biapply (Tannen f p) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<<.>>) :: Tannen f p (a -> b) (c -> d) -> Tannen f p a c -> Tannen f p b d #

(.>>) :: Tannen f p a b -> Tannen f p c d -> Tannen f p c d #

(<<.) :: Tannen f p a b -> Tannen f p c d -> Tannen f p a b #

(Biapply p, Apply f, Apply g) => Biapply (Biff p f g) # 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<<.>>) :: Biff p f g (a -> b) (c -> d) -> Biff p f g a c -> Biff p f g b d #

(.>>) :: Biff p f g a b -> Biff p f g c d -> Biff p f g c d #

(<<.) :: Biff p f g a b -> Biff p f g c d -> Biff p f g a b #