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.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 Identity 
Functor ZipList 
Functor Handler 
Functor First 
Functor Last 
Functor Maybe 
Functor Id 
Functor Put 
Functor Digit 
Functor Node 
Functor Elem 
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) 
Ix i => Functor (Array i) 
Functor (StateL s) 
Functor (StateR s) 
Functor (Const m) 
Monad m => Functor (WrappedMonad m) 
Arrow a => Functor (ArrowMonad a) 
Functor (Proxy *) 
Functor (StateL s) 
Functor (StateR s) 
Functor m => Functor (IdentityT m) 
Functor (State s) 
Functor (Map k) 
Functor (Arg a) 
Functor f => Functor (Reverse f)

Derived instance.

Functor f => Functor (Backwards f)

Derived instance.

Functor m => Functor (MaybeT m) 
Functor m => Functor (ListT m) 
Functor f => Functor (Lift f) 
Functor (Constant a) 
Functor (HashMap k) 
Functor f => Functor (MaybeApply f) 
Functor f => Functor (WrappedApplicative f) 
Arrow a => Functor (WrappedArrow a b) 
Functor f => Functor (Alt * f) 
Bifunctor p => Functor (Join * p) 
Functor w => Functor (TracedT m w) 
Functor w => Functor (StoreT s w) 
Functor w => Functor (EnvT e w) 
Functor (Cokleisli w a) 
Functor (Tagged k s) 
(Functor f, Functor g) => Functor (Sum f g) 
(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) 
Bifunctor p => Functor (WrappedBifunctor * * p a) 
Functor g => Functor (Joker k * g a) 
Bifunctor p => Functor (Flip * * p a) 
Functor (Clown * k f a) 
Functor m => Functor (RWST r w s m) 
Functor m => Functor (RWST r w s m) 
(Functor f, Bifunctor p) => Functor (Tannen * * * f p a) 
(Bifunctor p, Functor g) => Functor (Biff * * k * p f g a) 

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

An infix synonym for fmap.

Examples

Convert from a Maybe Int to a Maybe String using show:

>>> show <$> Nothing
Nothing
>>> show <$> Just 3
Just "3"

Convert from an Either Int Int to an Either Int String using show:

>>> show <$> Left 17
Left 17
>>> show <$> Right 17
Right "17"

Double each element of a list:

>>> (*2) <$> [1,2,3]
[2,4,6]

Apply even to the second element of a pair:

>>> even <$> (2,2)
(2,True)

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

Flipped version of <$.

Examples

Replace the contents of a Maybe Int with a constant String:

>>> Nothing $> "foo"
Nothing
>>> Just 90210 $> "foo"
Just "foo"

Replace the contents of an Either Int Int with a constant String, resulting in an Either Int String:

>>> Left 8675309 $> "foo"
Left 8675309
>>> Right 8675309 $> "foo"
Right "foo"

Replace each element of a list with a constant String:

>>> [1,2,3] $> "foo"
["foo","foo","foo"]

Replace the second element of a pair with a constant String:

>>> (1,2) $> "foo"
(1,"foo")

Since: 4.7.0.0

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

(<..>) :: 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