semigroupoids-5.0.1: 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:

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 
Apply IO Source 
Apply Identity Source 
Apply ZipList Source 
Apply Maybe Source 
Apply IntMap Source

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

Apply Tree Source 
Apply Seq Source 
Apply Option Source 
Apply NonEmpty Source 
Apply ((->) m) Source 
Apply (Either a) Source 
Semigroup m => Apply ((,) m) Source 
Semigroup m => Apply (Const m) Source 
Monad m => Apply (WrappedMonad m) Source 
Apply w => Apply (IdentityT w) Source 
Ord k => Apply (Map k) Source

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

Apply f => Apply (Reverse f) Source 
Apply f => Apply (Backwards f) Source 
(Functor m, Monad m) => Apply (MaybeT m) Source 
Apply m => Apply (ListT m) Source 
Apply f => Apply (Lift f) Source 
Semigroup f => Apply (Constant f) Source 
Apply f => Apply (MaybeApply f) Source 
Applicative f => Apply (WrappedApplicative f) Source 
Arrow a => Apply (WrappedArrow a b) Source 
Biapply p => Apply (Join * p) Source 
Apply w => Apply (TracedT m w) Source 
(Apply w, Semigroup s) => Apply (StoreT s w) Source 
(Semigroup e, Apply w) => Apply (EnvT e w) Source 
Apply (Cokleisli w a) Source 
(Apply f, Apply g) => Apply (Product f g) Source 
(Apply f, Apply g) => Apply (Compose f g) Source 
(Apply m, Semigroup w) => Apply (WriterT w m) Source 
(Apply m, Semigroup w) => Apply (WriterT w m) Source 
(Functor m, Monad m) => Apply (ErrorT e m) Source 
(Functor m, Monad m) => Apply (ExceptT e m) Source 
Bind m => Apply (StateT s m) Source 
Bind m => Apply (StateT s m) Source 
Apply m => Apply (ReaderT e m) Source 
Apply (ContT r m) Source 
Apply f => Apply (Static f a) Source 
(Bind m, Semigroup w) => Apply (RWST r w s m) Source 
(Bind m, Semigroup w) => Apply (RWST r w s m) Source 

Wrappers

newtype MaybeApply f a Source

Transform a Apply into an Applicative by adding a unit.

Constructors

MaybeApply 

Fields

runMaybeApply :: Either (f a) a
 

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 
Bind IO Source 
Bind Identity Source 
Bind Maybe Source 
Bind IntMap Source

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

Bind Tree Source 
Bind Seq Source 
Bind Option Source 
Bind NonEmpty Source 
Bind ((->) m) Source 
Bind (Either a) Source 
Semigroup m => Bind ((,) m) Source 
Monad m => Bind (WrappedMonad m) Source 
Bind m => Bind (IdentityT m) Source 
Ord k => Bind (Map k) Source

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

(Functor m, Monad m) => Bind (MaybeT m) Source 
(Apply m, Monad m) => Bind (ListT m) Source 
(Bind f, Bind g) => Bind (Product f g) Source 
(Bind m, Semigroup w) => Bind (WriterT w m) Source 
(Bind m, Semigroup w) => Bind (WriterT w m) Source 
(Functor m, Monad m) => Bind (ErrorT e m) Source 
(Functor m, Monad m) => Bind (ExceptT e m) Source 
Bind m => Bind (StateT s m) Source 
Bind m => Bind (StateT s m) Source 
Bind m => Bind (ReaderT e m) Source 
Bind (ContT r m) Source 
(Bind m, Semigroup w) => Bind (RWST r w s m) Source 
(Bind m, Semigroup w) => Bind (RWST r w s m) 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