semigroupoids-3.0.1: Haskell 98 semigroupoids: Category sans id

Portabilityportable
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellNone

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.

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.

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

An infix synonym for fmap.

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

Replace the contents of a functor uniformly with a constant value.

Apply - a strong lax semimonoidal endofunctor

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

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

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 
Functor ((->) m) => Apply ((->) m) 
Functor (Either a) => Apply (Either a) 
(Functor ((,) m), Semigroup m) => Apply ((,) m) 
(Functor (Const m), Semigroup m) => Apply (Const m) 
(Functor (WrappedMonad m), Monad m) => Apply (WrappedMonad m) 
(Functor (Map k), Ord k) => Apply (Map k)

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

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