semigroupoids-4.3: Semigroupoids: Category sans id

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

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.

Minimal complete definition

fmap

Methods

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

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

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 Handler 
Functor STM 
Functor ReadPrec 
Functor ReadP 
Functor Maybe 
Functor Put 
Functor Identity 
Functor Digit 
Functor Node 
Functor Elem 
Functor Id 
Functor FingerTree 
Functor IntMap 
Functor Tree 
Functor Seq 
Functor ViewL 
Functor ViewR 
Functor Min 
Functor Max 
Functor First 
Functor Last 
Functor Option 
Functor NonEmpty 
Functor ((->) r) 
Functor (Either a) 
Functor ((,) a) 
Functor (ST s) 
Functor (StateL s) 
Functor (StateR s) 
Functor (Const m) 
Monad m => Functor (WrappedMonad m) 
Functor (ST s) 
Arrow a => Functor (ArrowMonad a) 
Functor (Proxy *) 
Functor m => Functor (IdentityT m) 
Functor (State s) 
Functor (Map k) 
Functor m => Functor (MaybeT m) 
Functor m => Functor (ListT m) 
Functor (HashMap k) 
Functor f => Functor (MaybeApply f) 
Functor f => Functor (WrappedApplicative f) 
Arrow a => Functor (WrappedArrow a b) 
(Functor f, Functor g) => Functor (Coproduct f g) 
Functor w => Functor (TracedT m w) 
Functor w => Functor (StoreT s w) 
Functor w => Functor (EnvT e w) 
Functor (Cokleisli w a) 
(Functor f, Functor g) => Functor (Product f g) 
(Functor f, Functor g) => Functor (Compose f g) 
Functor m => Functor (WriterT w m) 
Functor m => Functor (WriterT w m) 
Functor m => Functor (ErrorT e m) 
Functor m => Functor (ExceptT e m) 
Functor m => Functor (StateT s m) 
Functor m => Functor (StateT s m) 
Functor m => Functor (ReaderT r m) 
Functor (ContT r m) 
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 infixl 4

An infix synonym for fmap.

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

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

Apply - a strong lax semimonoidal endofunctor

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

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

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

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

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

A variant of <.> with the arguments reversed.

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

Lift a binary function into a comonad with zipping

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

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