semigroupoids-5.2.2: 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.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 Source #

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

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

Lift a binary function into a comonad with zipping

Instances

Apply [] Source # 

Methods

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

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

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

liftF2 :: (a -> b -> c) -> [a] -> [b] -> [c] 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 #

liftF2 :: (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c 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 #

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

Apply Q Source # 

Methods

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

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

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

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

Apply Complex Source # 

Methods

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

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

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

liftF2 :: (a -> b -> c) -> Complex a -> Complex b -> Complex c 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 #

liftF2 :: (a -> b -> c) -> Option a -> Option b -> Option c 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 #

liftF2 :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c 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 #

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

liftF2 :: (a -> b -> c) -> Identity a -> Identity b -> Identity c 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 #

liftF2 :: (a -> b -> c) -> IntMap a -> IntMap b -> IntMap c 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 #

liftF2 :: (a -> b -> c) -> Tree a -> Tree b -> Tree c 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 #

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

Apply (Either a) Source # 

Methods

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

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

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

liftF2 :: (a -> b -> c) -> Either a a -> Either a b -> Either a c 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 #

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

Monad m => Apply (WrappedMonad m) Source # 

Methods

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

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

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

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

Apply (Proxy *) Source # 

Methods

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

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

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

liftF2 :: (a -> b -> c) -> Proxy * a -> Proxy * b -> Proxy * c 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 #

liftF2 :: (a -> b -> c) -> Map k a -> Map k b -> Map k c 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 #

liftF2 :: (a -> b -> c) -> Lift f a -> Lift f b -> Lift f c 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 #

liftF2 :: (a -> b -> c) -> MaybeT m a -> MaybeT m b -> MaybeT m c 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 #

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

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

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

Methods

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

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

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

liftF2 :: (a -> b -> c) -> HashMap k a -> HashMap k b -> HashMap k c 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 #

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

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

Methods

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

(.>) :: WrappedArrow a b a -> WrappedArrow a b b -> WrappedArrow a b b Source #

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

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

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

liftF2 :: (a -> b -> c) -> Join * p a -> Join * p b -> Join * p 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 #

liftF2 :: (a -> b -> c) -> TracedT m w a -> TracedT m w b -> TracedT m w c 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 #

liftF2 :: (a -> b -> c) -> StoreT s w a -> StoreT s w b -> StoreT s w c 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 #

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

Apply (Cokleisli w a) Source # 

Methods

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

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

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

liftF2 :: (a -> b -> c) -> Cokleisli w a a -> Cokleisli w a b -> Cokleisli w a c 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 #

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

Apply (Tagged * a) Source # 

Methods

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

(.>) :: Tagged * a a -> Tagged * a b -> Tagged * a b Source #

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

liftF2 :: (a -> b -> c) -> Tagged * a a -> Tagged * a b -> Tagged * a c 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 #

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

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

liftF2 :: (a -> b -> c) -> WriterT w m a -> WriterT w m b -> WriterT w m c 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 #

liftF2 :: (a -> b -> c) -> WriterT w m a -> WriterT w m b -> WriterT w m c 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 #

liftF2 :: (a -> b -> c) -> StateT s m a -> StateT s m b -> StateT s m c 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 #

liftF2 :: (a -> b -> c) -> StateT s m a -> StateT s m b -> StateT s m c 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 #

liftF2 :: (a -> b -> c) -> ExceptT e m a -> ExceptT e m b -> ExceptT e m c 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 #

liftF2 :: (a -> b -> c) -> ErrorT e m a -> ErrorT e m b -> ErrorT e m c 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 #

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

Apply f => Apply (Static f a) Source # 

Methods

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

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

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

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

Apply ((->) LiftedRep LiftedRep m) Source # 

Methods

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

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

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

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

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

liftF2 :: (a -> b -> c) -> ReaderT * e m a -> ReaderT * e m b -> ReaderT * e m c 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 #

liftF2 :: (a -> b -> c) -> ContT * r m a -> ContT * r m b -> ContT * r m c 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 #

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

liftF2 :: (a -> b -> c) -> RWST r w s m a -> RWST r w s m b -> RWST r w s m c 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 #

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

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 #

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

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

Bindable functors

class Apply m => Bind m where Source #

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

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

Instances

Bind [] Source # 

Methods

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

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

Bind Maybe Source # 

Methods

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

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

Bind IO Source # 

Methods

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

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

Bind Q Source # 

Methods

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

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

Bind Complex Source # 

Methods

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

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

Bind Option Source # 

Methods

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

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

Bind NonEmpty Source # 

Methods

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

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

Bind Identity Source # 

Methods

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

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

Bind IntMap Source #

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

Methods

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

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

Bind Tree Source # 

Methods

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

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

Bind Seq Source # 

Methods

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

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

Bind (Either a) Source # 

Methods

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

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

Semigroup m => Bind ((,) m) Source # 

Methods

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

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

Monad m => Bind (WrappedMonad m) Source # 
Bind (Proxy *) Source # 

Methods

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

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

Ord k => Bind (Map k) Source #

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

Methods

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

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

(Functor m, Monad m) => Bind (MaybeT m) Source # 

Methods

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

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

(Apply m, Monad m) => Bind (ListT m) Source # 

Methods

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

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

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

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

Methods

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

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

Bind m => Bind (IdentityT * m) Source # 

Methods

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

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

Bind (Tagged * a) Source # 

Methods

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

join :: Tagged * a (Tagged * a a) -> Tagged * a a Source #

(Bind m, Semigroup w) => Bind (WriterT w m) Source # 

Methods

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

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

(Bind m, Semigroup w) => Bind (WriterT w m) Source # 

Methods

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

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

Bind m => Bind (StateT s m) Source # 

Methods

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

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

Bind m => Bind (StateT s m) Source # 

Methods

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

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

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

Methods

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

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

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

Methods

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

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

Bind ((->) LiftedRep LiftedRep m) Source # 

Methods

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

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

(Bind f, Bind g) => Bind (Product * f g) Source # 

Methods

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

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

Bind m => Bind (ReaderT * e m) Source # 

Methods

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

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

Bind (ContT * r m) Source # 

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

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

Biappliable bifunctors

class Bifunctor p => Biapply p where Source #

Minimal complete definition

(<<.>>)

Methods

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

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

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

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

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

Instances

Biapply (,) Source # 

Methods

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

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

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

Biapply Arg Source # 

Methods

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

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

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

Semigroup x => Biapply ((,,) x) Source # 

Methods

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

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

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

Biapply (Const *) Source # 

Methods

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

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

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

Biapply (Tagged *) Source # 

Methods

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

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

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

(Semigroup x, Semigroup y) => Biapply ((,,,) x y) Source # 

Methods

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

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

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

(Semigroup x, Semigroup y, Semigroup z) => Biapply ((,,,,) x y z) Source # 

Methods

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

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

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

Biapply p => Biapply (WrappedBifunctor * * p) Source # 

Methods

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

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

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

Apply g => Biapply (Joker * * g) Source # 

Methods

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

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

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

Biapply p => Biapply (Flip * * p) Source # 

Methods

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

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

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

Apply f => Biapply (Clown * * f) Source # 

Methods

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

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

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

(Biapply p, Biapply q) => Biapply (Product * * p q) Source # 

Methods

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

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

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

(Apply f, Biapply p) => Biapply (Tannen * * * f p) Source # 

Methods

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

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

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

(Biapply p, Apply f, Apply g) => Biapply (Biff * * * * p f g) Source # 

Methods

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

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

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