semigroupoids-1.2.2.3: Haskell 98 semigroupoids: Category sans id

Portabilityportable
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>

Data.Functor.Bind

Contents

Description

NB: The definitions exported through Data.Functor.Apply need to be included here because otherwise the instances for the transformers package have orphaned heads.

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, Data.Maybe.Maybe and System.IO.IO satisfy these laws.

Methods

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

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

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 [] 
Functor IO 
Functor Id 
Functor ZipList 
Functor Maybe 
Functor FingerTree 
Functor Digit 
Functor Node 
Functor Elem 
Functor Id 
Functor Tree 
Functor Seq 
Functor ViewL 
Functor ViewR 
Functor IntMap 
Functor Option 
Functor NonEmpty 
Functor Identity 
Functor ((->) r) 
Functor (Either a) 
Functor ((,) a) 
Functor (StateL s) 
Functor (StateR s) 
Functor (Const m) 
Monad m => Functor (WrappedMonad m) 
Functor (State s) 
Functor (Map k) 
Functor m => Functor (MaybeT m) 
Functor m => Functor (ListT m) 
Functor m => Functor (IdentityT m) 
Functor f => Functor (MaybeApply f) 
Functor f => Functor (WrappedApplicative f) 
Functor f => Functor (Act f) 
Arrow a => Functor (WrappedArrow a b) 
Functor (Cokleisli w a) 
Functor m => Functor (WriterT w m) 
Functor m => Functor (WriterT w m) 
Functor m => Functor (StateT s m) 
Functor m => Functor (StateT s m) 
Functor m => Functor (ReaderT r m) 
Functor m => Functor (ErrorT e m) 
Functor (ContT r m) 
(Functor f, Functor g) => Functor (Compose f g) 
(Functor f, Functor g) => Functor (Product f g) 
Functor f => Functor (Static f a) 
Functor m => Functor (RWST r w s m) 
Functor m => Functor (RWST r w s m) 

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

An infix synonym for fmap.

($>) :: Functor f => f a -> b -> f bSource

TODO: move into Data.Functor

Applyable functors

class Functor f => Apply f whereSource

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

Laws:

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

Methods

(<.>) :: f (a -> b) -> f a -> f bSource

(.>) :: f a -> f b -> f bSource

a .> b = const id $ a . b

(<.) :: f a -> f b -> f aSource

Instances

Apply [] 
Apply IO 
Apply ZipList 
Apply Maybe 
Apply Tree 
Apply Seq 
Apply IntMap

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

Apply Option 
Apply NonEmpty 
Apply Identity 
Apply ((->) m) 
Apply (Either a) 
Semigroup m => Apply ((,) m) 
Semigroup m => Apply (Const m) 
Monad m => Apply (WrappedMonad m) 
Ord k => Apply (Map k)

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

(Bind m, Monad m) => Apply (MaybeT m) 
Apply m => Apply (ListT m) 
Apply w => Apply (IdentityT w) 
Apply f => Apply (MaybeApply f) 
Applicative f => Apply (WrappedApplicative f) 
Arrow a => Apply (WrappedArrow a b) 
Apply (Cokleisli w a) 
(Apply m, Semigroup w) => Apply (WriterT w m) 
(Apply m, Semigroup w) => Apply (WriterT w m) 
Bind m => Apply (StateT s m) 
Bind m => Apply (StateT s m) 
Apply m => Apply (ReaderT e m) 
(Bind m, Monad m) => Apply (ErrorT e m) 
Apply (ContT r m) 
(Apply f, Apply g) => Apply (Compose f g) 
(Apply f, Apply g) => Apply (Product f g) 
Apply f => Apply (Static f a) 
(Bind m, Semigroup w) => Apply (RWST r w s m) 
(Bind m, Semigroup w) => Apply (RWST r w s m) 

(<..>) :: Apply w => w a -> w (a -> b) -> w bSource

A variant of <.> with the arguments reversed.

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

Lift a binary function into a comonad with zipping

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

Lift a ternary function into a comonad with zipping

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 whereSource

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)

Methods

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

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

Instances

Bind [] 
Bind IO 
Bind Maybe 
Bind Tree 
Bind Seq 
Bind IntMap

An IntMap is a Applicative, but it is an instance of Bind

Bind Option 
Bind NonEmpty 
Bind Identity 
Bind ((->) m) 
Bind (Either a) 
Semigroup m => Bind ((,) m) 
Monad m => Bind (WrappedMonad m) 
Ord k => Bind (Map k)

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

(Bind m, Monad m) => Bind (MaybeT m) 
(Bind m, Monad m) => Bind (ListT m) 
Bind m => Bind (IdentityT m) 
(Bind m, Semigroup w) => Bind (WriterT w m) 
(Bind m, Semigroup w) => Bind (WriterT w m) 
Bind m => Bind (StateT s m) 
Bind m => Bind (StateT s m) 
Bind m => Bind (ReaderT e m) 
(Bind m, Monad m) => Bind (ErrorT e m) 
Bind (ContT r m) 
(Bind f, Bind g) => Bind (Product f g) 
(Bind m, Semigroup w) => Bind (RWST r w s m) 
(Bind m, Semigroup w) => Bind (RWST r w s m) 

(-<<) :: Bind m => (a -> m b) -> m a -> m bSource

(-<-) :: Bind m => (b -> m c) -> (a -> m b) -> a -> m cSource

(->-) :: Bind m => (a -> m b) -> (b -> m c) -> a -> m cSource

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

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