comonad-5.0.3: Comonads

Copyright(C) 2008-2015 Edward Kmett
(C) 2004 Dave Menendez
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Control.Comonad

Contents

Description

 

Synopsis

Comonads

class Functor w => Comonad w where Source #

There are two ways to define a comonad:

I. Provide definitions for extract and extend satisfying these laws:

extend extract      = id
extract . extend f  = f
extend f . extend g = extend (f . extend g)

In this case, you may simply set fmap = liftW.

These laws are directly analogous to the laws for monads and perhaps can be made clearer by viewing them as laws stating that Cokleisli composition must be associative, and has extract for a unit:

f =>= extract   = f
extract =>= f   = f
(f =>= g) =>= h = f =>= (g =>= h)

II. Alternately, you may choose to provide definitions for fmap, extract, and duplicate satisfying these laws:

extract . duplicate      = id
fmap extract . duplicate = id
duplicate . duplicate    = fmap duplicate . duplicate

In this case you may not rely on the ability to define fmap in terms of liftW.

You may of course, choose to define both duplicate and extend. In that case you must also satisfy these laws:

extend f  = fmap f . duplicate
duplicate = extend id
fmap f    = extend (f . extract)

These are the default definitions of extend and duplicate and the definition of liftW respectively.

Minimal complete definition

extract, (duplicate | extend)

Methods

extract :: w a -> a Source #

extract . fmap f = f . extract

duplicate :: w a -> w (w a) Source #

extend :: (w a -> b) -> w a -> w b Source #

Instances

Comonad NonEmpty Source # 
Comonad Identity Source # 
Comonad Tree Source # 

Methods

extract :: Tree a -> a Source #

duplicate :: Tree a -> Tree (Tree a) Source #

extend :: (Tree a -> b) -> Tree a -> Tree b Source #

Comonad ((,) e) Source # 

Methods

extract :: (e, a) -> a Source #

duplicate :: (e, a) -> (e, (e, a)) Source #

extend :: ((e, a) -> b) -> (e, a) -> (e, b) Source #

Comonad (Arg e) Source # 

Methods

extract :: Arg e a -> a Source #

duplicate :: Arg e a -> Arg e (Arg e a) Source #

extend :: (Arg e a -> b) -> Arg e a -> Arg e b Source #

Comonad (Tagged * s) Source # 

Methods

extract :: Tagged * s a -> a Source #

duplicate :: Tagged * s a -> Tagged * s (Tagged * s a) Source #

extend :: (Tagged * s a -> b) -> Tagged * s a -> Tagged * s b Source #

Comonad w => Comonad (IdentityT * w) Source # 

Methods

extract :: IdentityT * w a -> a Source #

duplicate :: IdentityT * w a -> IdentityT * w (IdentityT * w a) Source #

extend :: (IdentityT * w a -> b) -> IdentityT * w a -> IdentityT * w b Source #

Comonad w => Comonad (EnvT e w) Source # 

Methods

extract :: EnvT e w a -> a Source #

duplicate :: EnvT e w a -> EnvT e w (EnvT e w a) Source #

extend :: (EnvT e w a -> b) -> EnvT e w a -> EnvT e w b Source #

Comonad w => Comonad (StoreT s w) Source # 

Methods

extract :: StoreT s w a -> a Source #

duplicate :: StoreT s w a -> StoreT s w (StoreT s w a) Source #

extend :: (StoreT s w a -> b) -> StoreT s w a -> StoreT s w b Source #

(Comonad w, Monoid m) => Comonad (TracedT m w) Source # 

Methods

extract :: TracedT m w a -> a Source #

duplicate :: TracedT m w a -> TracedT m w (TracedT m w a) Source #

extend :: (TracedT m w a -> b) -> TracedT m w a -> TracedT m w b Source #

Monoid m => Comonad ((->) LiftedRep LiftedRep m) Source # 

Methods

extract :: (LiftedRep -> LiftedRep) m a -> a Source #

duplicate :: (LiftedRep -> LiftedRep) m a -> (LiftedRep -> LiftedRep) m ((LiftedRep -> LiftedRep) m a) Source #

extend :: ((LiftedRep -> LiftedRep) m a -> b) -> (LiftedRep -> LiftedRep) m a -> (LiftedRep -> LiftedRep) m b Source #

(Comonad f, Comonad g) => Comonad (Sum * f g) Source # 

Methods

extract :: Sum * f g a -> a Source #

duplicate :: Sum * f g a -> Sum * f g (Sum * f g a) Source #

extend :: (Sum * f g a -> b) -> Sum * f g a -> Sum * f g b Source #

liftW :: Comonad w => (a -> b) -> w a -> w b Source #

A suitable default definition for fmap for a Comonad. Promotes a function to a comonad.

You can only safely use to define fmap if your Comonad defined extend, not just duplicate, since defining extend in terms of duplicate uses fmap!

fmap f = liftW f = extend (f . extract)

wfix :: Comonad w => w (w a -> a) -> a Source #

Comonadic fixed point à la David Menendez

cfix :: Comonad w => (w a -> a) -> w a Source #

Comonadic fixed point à la Dominic Orchard

kfix :: ComonadApply w => w (w a -> a) -> w a Source #

Comonadic fixed point à la Kenneth Foner:

This is the evaluate function from his "Getting a Quick Fix on Comonads" talk.

(=>=) :: Comonad w => (w a -> b) -> (w b -> c) -> w a -> c infixr 1 Source #

Left-to-right Cokleisli composition

(=<=) :: Comonad w => (w b -> c) -> (w a -> b) -> w a -> c infixr 1 Source #

Right-to-left Cokleisli composition

(<<=) :: Comonad w => (w a -> b) -> w a -> w b infixr 1 Source #

extend in operator form

(=>>) :: Comonad w => w a -> (w a -> b) -> w b infixl 1 Source #

extend with the arguments swapped. Dual to >>= for a Monad.

Combining Comonads

class Comonad w => ComonadApply w where Source #

ComonadApply is to Comonad like Applicative is to Monad.

Mathematically, it is a strong lax symmetric semi-monoidal comonad on the category Hask of Haskell types. That it to say that w is a strong lax symmetric semi-monoidal functor on Hask, where both extract and duplicate are symmetric monoidal natural transformations.

Laws:

(.) <$> u <@> v <@> w = u <@> (v <@> w)
extract (p <@> q) = extract p (extract q)
duplicate (p <@> q) = (<@>) <$> duplicate p <@> duplicate q

If our type is both a ComonadApply and Applicative we further require

(<*>) = (<@>)

Finally, if you choose to define (<@) and (@>), the results of your definitions should match the following laws:

a @> b = const id <$> a <@> b
a <@ b = const <$> a <@> b

Methods

(<@>) :: w (a -> b) -> w a -> w b infixl 4 Source #

(<@>) :: Applicative w => w (a -> b) -> w a -> w b infixl 4 Source #

(@>) :: w a -> w b -> w b infixl 4 Source #

(<@) :: w a -> w b -> w a infixl 4 Source #

Instances

ComonadApply NonEmpty Source # 

Methods

(<@>) :: NonEmpty (a -> b) -> NonEmpty a -> NonEmpty b Source #

(@>) :: NonEmpty a -> NonEmpty b -> NonEmpty b Source #

(<@) :: NonEmpty a -> NonEmpty b -> NonEmpty a Source #

ComonadApply Identity Source # 

Methods

(<@>) :: Identity (a -> b) -> Identity a -> Identity b Source #

(@>) :: Identity a -> Identity b -> Identity b Source #

(<@) :: Identity a -> Identity b -> Identity a Source #

ComonadApply Tree Source # 

Methods

(<@>) :: Tree (a -> b) -> Tree a -> Tree b Source #

(@>) :: Tree a -> Tree b -> Tree b Source #

(<@) :: Tree a -> Tree b -> Tree a Source #

Semigroup m => ComonadApply ((,) m) Source # 

Methods

(<@>) :: (m, a -> b) -> (m, a) -> (m, b) Source #

(@>) :: (m, a) -> (m, b) -> (m, b) Source #

(<@) :: (m, a) -> (m, b) -> (m, a) Source #

ComonadApply w => ComonadApply (IdentityT * w) Source # 

Methods

(<@>) :: IdentityT * w (a -> b) -> IdentityT * w a -> IdentityT * w b Source #

(@>) :: IdentityT * w a -> IdentityT * w b -> IdentityT * w b Source #

(<@) :: IdentityT * w a -> IdentityT * w b -> IdentityT * w a Source #

(Semigroup e, ComonadApply w) => ComonadApply (EnvT e w) Source # 

Methods

(<@>) :: EnvT e w (a -> b) -> EnvT e w a -> EnvT e w b Source #

(@>) :: EnvT e w a -> EnvT e w b -> EnvT e w b Source #

(<@) :: EnvT e w a -> EnvT e w b -> EnvT e w a Source #

(ComonadApply w, Semigroup s) => ComonadApply (StoreT s w) Source # 

Methods

(<@>) :: StoreT s w (a -> b) -> StoreT s w a -> StoreT s w b Source #

(@>) :: StoreT s w a -> StoreT s w b -> StoreT s w b Source #

(<@) :: StoreT s w a -> StoreT s w b -> StoreT s w a Source #

(ComonadApply w, Monoid m) => ComonadApply (TracedT m w) Source # 

Methods

(<@>) :: TracedT m w (a -> b) -> TracedT m w a -> TracedT m w b Source #

(@>) :: TracedT m w a -> TracedT m w b -> TracedT m w b Source #

(<@) :: TracedT m w a -> TracedT m w b -> TracedT m w a Source #

Monoid m => ComonadApply ((->) LiftedRep LiftedRep m) Source # 

Methods

(<@>) :: (LiftedRep -> LiftedRep) m (a -> b) -> (LiftedRep -> LiftedRep) m a -> (LiftedRep -> LiftedRep) m b Source #

(@>) :: (LiftedRep -> LiftedRep) m a -> (LiftedRep -> LiftedRep) m b -> (LiftedRep -> LiftedRep) m b Source #

(<@) :: (LiftedRep -> LiftedRep) m a -> (LiftedRep -> LiftedRep) m b -> (LiftedRep -> LiftedRep) m a Source #

(<@@>) :: ComonadApply w => w a -> w (a -> b) -> w b infixl 4 Source #

A variant of <@> with the arguments reversed.

liftW2 :: ComonadApply w => (a -> b -> c) -> w a -> w b -> w c Source #

Lift a binary function into a Comonad with zipping

liftW3 :: ComonadApply w => (a -> b -> c -> d) -> w a -> w b -> w c -> w d Source #

Lift a ternary function into a Comonad with zipping

Cokleisli Arrows

newtype Cokleisli w a b Source #

The Cokleisli Arrows of a given Comonad

Constructors

Cokleisli 

Fields

Instances

Comonad w => Arrow (Cokleisli w) Source # 

Methods

arr :: (b -> c) -> Cokleisli w b c #

first :: Cokleisli w b c -> Cokleisli w (b, d) (c, d) #

second :: Cokleisli w b c -> Cokleisli w (d, b) (d, c) #

(***) :: Cokleisli w b c -> Cokleisli w b' c' -> Cokleisli w (b, b') (c, c') #

(&&&) :: Cokleisli w b c -> Cokleisli w b c' -> Cokleisli w b (c, c') #

Comonad w => ArrowChoice (Cokleisli w) Source # 

Methods

left :: Cokleisli w b c -> Cokleisli w (Either b d) (Either c d) #

right :: Cokleisli w b c -> Cokleisli w (Either d b) (Either d c) #

(+++) :: Cokleisli w b c -> Cokleisli w b' c' -> Cokleisli w (Either b b') (Either c c') #

(|||) :: Cokleisli w b d -> Cokleisli w c d -> Cokleisli w (Either b c) d #

Comonad w => ArrowApply (Cokleisli w) Source # 

Methods

app :: Cokleisli w (Cokleisli w b c, b) c #

ComonadApply w => ArrowLoop (Cokleisli w) Source # 

Methods

loop :: Cokleisli w (b, d) (c, d) -> Cokleisli w b c #

Comonad w => Category * (Cokleisli w) Source # 

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

Monad (Cokleisli w a) Source # 

Methods

(>>=) :: Cokleisli w a a -> (a -> Cokleisli w a b) -> Cokleisli w a b #

(>>) :: Cokleisli w a a -> Cokleisli w a b -> Cokleisli w a b #

return :: a -> Cokleisli w a a #

fail :: String -> Cokleisli w a a #

Functor (Cokleisli w a) Source # 

Methods

fmap :: (a -> b) -> Cokleisli w a a -> Cokleisli w a b #

(<$) :: a -> Cokleisli w a b -> Cokleisli w a a #

Applicative (Cokleisli w a) Source # 

Methods

pure :: a -> Cokleisli w a a #

(<*>) :: Cokleisli w a (a -> b) -> Cokleisli w a a -> Cokleisli w a b #

liftA2 :: (a -> b -> c) -> Cokleisli w a a -> Cokleisli w a b -> Cokleisli w a c #

(*>) :: Cokleisli w a a -> Cokleisli w a b -> Cokleisli w a b #

(<*) :: Cokleisli w a a -> Cokleisli w a b -> Cokleisli w a a #

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

Since: 2.1

Methods

fmap :: (a -> b) -> [a] -> [b] #

(<$) :: a -> [b] -> [a] #

Functor Maybe

Since: 2.1

Methods

fmap :: (a -> b) -> Maybe a -> Maybe b #

(<$) :: a -> Maybe b -> Maybe a #

Functor IO

Since: 2.1

Methods

fmap :: (a -> b) -> IO a -> IO b #

(<$) :: a -> IO b -> IO a #

Functor Par1 

Methods

fmap :: (a -> b) -> Par1 a -> Par1 b #

(<$) :: a -> Par1 b -> Par1 a #

Functor Complex 

Methods

fmap :: (a -> b) -> Complex a -> Complex b #

(<$) :: a -> Complex b -> Complex a #

Functor Min

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> Min a -> Min b #

(<$) :: a -> Min b -> Min a #

Functor Max

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> Max a -> Max b #

(<$) :: a -> Max b -> Max a #

Functor First

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> First a -> First b #

(<$) :: a -> First b -> First a #

Functor Last

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> Last a -> Last b #

(<$) :: a -> Last b -> Last a #

Functor Option

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> Option a -> Option b #

(<$) :: a -> Option b -> Option a #

Functor NonEmpty

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> NonEmpty a -> NonEmpty b #

(<$) :: a -> NonEmpty b -> NonEmpty a #

Functor ZipList 

Methods

fmap :: (a -> b) -> ZipList a -> ZipList b #

(<$) :: a -> ZipList b -> ZipList a #

Functor Identity

Since: 4.8.0.0

Methods

fmap :: (a -> b) -> Identity a -> Identity b #

(<$) :: a -> Identity b -> Identity a #

Functor Dual

Since: 4.8.0.0

Methods

fmap :: (a -> b) -> Dual a -> Dual b #

(<$) :: a -> Dual b -> Dual a #

Functor Sum

Since: 4.8.0.0

Methods

fmap :: (a -> b) -> Sum a -> Sum b #

(<$) :: a -> Sum b -> Sum a #

Functor Product

Since: 4.8.0.0

Methods

fmap :: (a -> b) -> Product a -> Product b #

(<$) :: a -> Product b -> Product a #

Functor First 

Methods

fmap :: (a -> b) -> First a -> First b #

(<$) :: a -> First b -> First a #

Functor Last 

Methods

fmap :: (a -> b) -> Last a -> Last b #

(<$) :: a -> Last b -> Last a #

Functor Tree 

Methods

fmap :: (a -> b) -> Tree a -> Tree b #

(<$) :: a -> Tree b -> Tree a #

Functor Seq 

Methods

fmap :: (a -> b) -> Seq a -> Seq b #

(<$) :: a -> Seq b -> Seq a #

Functor FingerTree 

Methods

fmap :: (a -> b) -> FingerTree a -> FingerTree b #

(<$) :: a -> FingerTree b -> FingerTree a #

Functor Digit 

Methods

fmap :: (a -> b) -> Digit a -> Digit b #

(<$) :: a -> Digit b -> Digit a #

Functor Node 

Methods

fmap :: (a -> b) -> Node a -> Node b #

(<$) :: a -> Node b -> Node a #

Functor Elem 

Methods

fmap :: (a -> b) -> Elem a -> Elem b #

(<$) :: a -> Elem b -> Elem a #

Functor ViewL 

Methods

fmap :: (a -> b) -> ViewL a -> ViewL b #

(<$) :: a -> ViewL b -> ViewL a #

Functor ViewR 

Methods

fmap :: (a -> b) -> ViewR a -> ViewR b #

(<$) :: a -> ViewR b -> ViewR a #

Functor (Either a)

Since: 3.0

Methods

fmap :: (a -> b) -> Either a a -> Either a b #

(<$) :: a -> Either a b -> Either a a #

Functor (V1 *) 

Methods

fmap :: (a -> b) -> V1 * a -> V1 * b #

(<$) :: a -> V1 * b -> V1 * a #

Functor (U1 *)

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> U1 * a -> U1 * b #

(<$) :: a -> U1 * b -> U1 * a #

Functor ((,) a)

Since: 2.1

Methods

fmap :: (a -> b) -> (a, a) -> (a, b) #

(<$) :: a -> (a, b) -> (a, a) #

Functor (Array i)

Since: 2.1

Methods

fmap :: (a -> b) -> Array i a -> Array i b #

(<$) :: a -> Array i b -> Array i a #

Functor (Arg a)

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> Arg a a -> Arg a b #

(<$) :: a -> Arg a b -> Arg a a #

Monad m => Functor (WrappedMonad m)

Since: 2.1

Methods

fmap :: (a -> b) -> WrappedMonad m a -> WrappedMonad m b #

(<$) :: a -> WrappedMonad m b -> WrappedMonad m a #

Arrow a => Functor (ArrowMonad a)

Since: 4.6.0.0

Methods

fmap :: (a -> b) -> ArrowMonad a a -> ArrowMonad a b #

(<$) :: a -> ArrowMonad a b -> ArrowMonad a a #

Functor (Proxy *)

Since: 4.7.0.0

Methods

fmap :: (a -> b) -> Proxy * a -> Proxy * b #

(<$) :: a -> Proxy * b -> Proxy * a #

Functor (State s) 

Methods

fmap :: (a -> b) -> State s a -> State s b #

(<$) :: a -> State s b -> State s a #

Functor f => Functor (Rec1 * f) 

Methods

fmap :: (a -> b) -> Rec1 * f a -> Rec1 * f b #

(<$) :: a -> Rec1 * f b -> Rec1 * f a #

Functor (URec * Char) 

Methods

fmap :: (a -> b) -> URec * Char a -> URec * Char b #

(<$) :: a -> URec * Char b -> URec * Char a #

Functor (URec * Double) 

Methods

fmap :: (a -> b) -> URec * Double a -> URec * Double b #

(<$) :: a -> URec * Double b -> URec * Double a #

Functor (URec * Float) 

Methods

fmap :: (a -> b) -> URec * Float a -> URec * Float b #

(<$) :: a -> URec * Float b -> URec * Float a #

Functor (URec * Int) 

Methods

fmap :: (a -> b) -> URec * Int a -> URec * Int b #

(<$) :: a -> URec * Int b -> URec * Int a #

Functor (URec * Word) 

Methods

fmap :: (a -> b) -> URec * Word a -> URec * Word b #

(<$) :: a -> URec * Word b -> URec * Word a #

Functor (URec * (Ptr ())) 

Methods

fmap :: (a -> b) -> URec * (Ptr ()) a -> URec * (Ptr ()) b #

(<$) :: a -> URec * (Ptr ()) b -> URec * (Ptr ()) a #

Arrow a => Functor (WrappedArrow a b)

Since: 2.1

Methods

fmap :: (a -> b) -> WrappedArrow a b a -> WrappedArrow a b b #

(<$) :: a -> WrappedArrow a b b -> WrappedArrow a b a #

Functor (Const * m)

Since: 2.1

Methods

fmap :: (a -> b) -> Const * m a -> Const * m b #

(<$) :: a -> Const * m b -> Const * m a #

Functor f => Functor (Alt * f) 

Methods

fmap :: (a -> b) -> Alt * f a -> Alt * f b #

(<$) :: a -> Alt * f b -> Alt * f a #

Functor (Tagged k s) 

Methods

fmap :: (a -> b) -> Tagged k s a -> Tagged k s b #

(<$) :: a -> Tagged k s b -> Tagged k s a #

Functor f => Functor (Reverse * f)

Derived instance.

Methods

fmap :: (a -> b) -> Reverse * f a -> Reverse * f b #

(<$) :: a -> Reverse * f b -> Reverse * f a #

Functor m => Functor (IdentityT * m) 

Methods

fmap :: (a -> b) -> IdentityT * m a -> IdentityT * m b #

(<$) :: a -> IdentityT * m b -> IdentityT * m a #

Functor f => Functor (Backwards * f)

Derived instance.

Methods

fmap :: (a -> b) -> Backwards * f a -> Backwards * f b #

(<$) :: a -> Backwards * f b -> Backwards * f a #

Functor (Cokleisli w a) # 

Methods

fmap :: (a -> b) -> Cokleisli w a a -> Cokleisli w a b #

(<$) :: a -> Cokleisli w a b -> Cokleisli w a a #

Functor w => Functor (EnvT e w) # 

Methods

fmap :: (a -> b) -> EnvT e w a -> EnvT e w b #

(<$) :: a -> EnvT e w b -> EnvT e w a #

Functor w => Functor (StoreT s w) # 

Methods

fmap :: (a -> b) -> StoreT s w a -> StoreT s w b #

(<$) :: a -> StoreT s w b -> StoreT s w a #

Functor w => Functor (TracedT m w) # 

Methods

fmap :: (a -> b) -> TracedT m w a -> TracedT m w b #

(<$) :: a -> TracedT m w b -> TracedT m w a #

Functor ((->) LiftedRep LiftedRep r)

Since: 2.1

Methods

fmap :: (a -> b) -> (LiftedRep -> LiftedRep) r a -> (LiftedRep -> LiftedRep) r b #

(<$) :: a -> (LiftedRep -> LiftedRep) r b -> (LiftedRep -> LiftedRep) r a #

Functor (K1 * i c) 

Methods

fmap :: (a -> b) -> K1 * i c a -> K1 * i c b #

(<$) :: a -> K1 * i c b -> K1 * i c a #

(Functor g, Functor f) => Functor ((:+:) * f g) 

Methods

fmap :: (a -> b) -> (* :+: f) g a -> (* :+: f) g b #

(<$) :: a -> (* :+: f) g b -> (* :+: f) g a #

(Functor g, Functor f) => Functor ((:*:) * f g) 

Methods

fmap :: (a -> b) -> (* :*: f) g a -> (* :*: f) g b #

(<$) :: a -> (* :*: f) g b -> (* :*: f) g a #

(Functor f, Functor g) => Functor (Product * f g)

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> Product * f g a -> Product * f g b #

(<$) :: a -> Product * f g b -> Product * f g a #

(Functor f, Functor g) => Functor (Sum * f g)

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> Sum * f g a -> Sum * f g b #

(<$) :: a -> Sum * f g b -> Sum * f g a #

Functor m => Functor (ReaderT * r m) 

Methods

fmap :: (a -> b) -> ReaderT * r m a -> ReaderT * r m b #

(<$) :: a -> ReaderT * r m b -> ReaderT * r m a #

Functor f => Functor (M1 * i c f) 

Methods

fmap :: (a -> b) -> M1 * i c f a -> M1 * i c f b #

(<$) :: a -> M1 * i c f b -> M1 * i c f a #

(Functor g, Functor f) => Functor ((:.:) * * f g) 

Methods

fmap :: (a -> b) -> (* :.: *) f g a -> (* :.: *) f g b #

(<$) :: a -> (* :.: *) f g b -> (* :.: *) f g a #

(Functor f, Functor g) => Functor (Compose * * f g)

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> Compose * * f g a -> Compose * * f g b #

(<$) :: a -> Compose * * f g b -> Compose * * f g a #

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

An infix synonym for fmap.

The name of this operator is an allusion to $. Note the similarities between their types:

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

Whereas $ is function application, <$> is function application lifted over a Functor.

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