“I love profunctors. They're so easy.” —beaky on #haskell
Covariant Functors
I hope we can all agree that functors are useful, and that we are all familiar with them. Just for the record, the Functor
typeclass can be thought of as follows:
class Functor f where
fmap ∷ (a → b) → f a → f b
Given a value x ∷ f a
and a function g ∷ a → b
, then fmap g x ∷ f b
. Simples!
However, Haskell's Functor
is only one of many functors in the mathematical sense. It is in fact a covariant functor, meaning that fmap
preserves the direction of the arrows:
g ∷ a → b
fmap g ∷ f a → f b
See? Both arrows point to the right.
Contravariant Functors
Let's start with a motivational example. We call a function returning a Bool
and taking one argument a Predicate
, indicating the truthiness of its argument:
type Predicate a = a → Bool
Is Predicate
a Functor
?
Is Predicate
a functor?
Let's ask lambdabot:
<liyang> @faq Is Predicate a functor?
<lambdabot> The answer is: Yes! Haskell can do that.
From Data.Functor.Contravariant
:
class Contravariant f where
contramap ∷ (b → a) → f a → f b
This characterises contravariant functors. Note that contramap
swaps the direction of the arrow, in contrast to fmap
:
g ∷ a ← b
contramap g ∷ f a → f b
Let's make a Contravariant
Predicate
:
{-# LANGUAGE UnicodeSyntax #-}
import Control.Applicative
import Data.Functor.Contravariant (Contravariant (..))
-- show
newtype Predicate a = Predicate { getPredicate ∷ a → Bool }
instance Contravariant Predicate where
contramap g (Predicate p) = Predicate (p . g)
veryOdd ∷ Predicate Integer
veryOdd = contramap (`div` 2) (Predicate odd)
main ∷ IO ()
main = print $ getPredicate veryOdd <$> [0 .. 11]
-- /show
Can you tell what the output is yet?
Examples of Contravariant Functors
{-# LANGUAGE UnicodeSyntax #-}
import Data.Function
import Data.Functor.Contravariant (Contravariant (..))
-- show
newtype Const a b = Const a
instance Contravariant (Const a) where
contramap _ (Const a) = Const a
newtype Comparison a = Comparison (a → a → Ordering) -- e.g. compare
instance Contravariant Comparison where
contramap g (Comparison comp) = Comparison (comp `on` g)
newtype Op b a = Op (a → b)
instance Contravariant (Op b) where
contramap g (Op f) = Op (f . g)
-- /show
main = return ()
The above (and more) are already provided by Data.Functor.Contravariant
.
Bifunctors
A bifunctor in the mathematical sense is a functor of two arguments; three arguments would make trifunctors…
followed by quadri-, quinque-, sexa-, and septi-functor. A multifunctor is fine too.
In Haskell this means a parametric type of kind * → * → *
. Familiar bifunctors include Either
, (,)
or even (→)
…
However, the Bifunctor
typeclass correspond only to bifunctors that are covariant in both arguments:
class Bifunctor f where
bimap ∷ (a → c) → (b → d) → f a b → f c d
g ∷ a → c
h ∷ b → d
bimap g h ∷ f a b → f c d
Both Either
and (,)
are Bifunctor
s. There are also Biapplicative
, Bifoldable
and Bitraversable
classes, if you feel inclined to investigate. Watch out for Clown
s and Joker
s popling out around the corner though.
Exercise: instance Bifunctor Either
{-# LANGUAGE UnicodeSyntax #-}
class Bifunctor f where
bimap ∷ (a → c) → (b → d) → f a b → f c d
-- show
instance Bifunctor Either where
bimap g h = either (Left . g) (Right . h)
-- /show
main = return ()
Exercise: instance Bifunctor (,)
{-# LANGUAGE UnicodeSyntax #-}
import Control.Arrow
class Bifunctor f where
bimap ∷ (a → c) → (b → d) → f a b → f c d
-- show
instance Bifunctor (,) where
bimap = (***)
-- /show
main = return ()
Profunctors
A Profunctor
is just a bifunctor that is contravariant in the first argument and covariant in the second. What's the problem?
class Profunctor f where
dimap ∷ (c → a) → (b → d) → f a b → f c d
g ∷ a ← c
h ∷ b → d
dimap g h ∷ f a b → f c d
If we only want to map over one of the two type arguments, there are:
{-# LANGUAGE UnicodeSyntax #-}
import Data.Profunctor (Profunctor (dimap))
-- show
lmap ∷ Profunctor f ⇒ (c → a) → f a b → f c b
lmap = (`dimap` id)
rmap ∷ Profunctor f ⇒ (b → d) → f a b → f a d
rmap = (id `dimap`)
-- /show
main = return ()
The simplest and most common Profunctor
is (→)
. The specialised type of dimap
would be:
dimap :: (c → a) → (b → d) → (a → b) → (c → d)
Exercise: instance Profunctors (→)
{-# LANGUAGE UnicodeSyntax #-}
class Profunctor f where
dimap ∷ (c → a) → (b → d) → f a b → f c d
-- show
instance Profunctor (→) where dimap g h f = h . f . g
-- /show
main = return ()
My First Profunctor
This is where I recognised my first Profunctor
:
data Limits a = Limits
{ step ∷ a → (a, a)
, check ∷ a → a → Bool }
This was part of the user-facing code we used in production that lets the user adjust various parameters: she can either click an up/down button—or supply a new value directly. The check
function then validates the new input with respect to the old.
If we generalise over the positive and negative argument positions,
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE UnicodeSyntax #-}
import Control.Arrow
import Data.Function
import Data.Profunctor
-- show
type Limits a = Limits' a a
data Limits' a b = Limits
{ step ∷ a → (b, b)
, check ∷ a → a → Bool }
instance Profunctor Limits' where
dimap g h Limits {..} = Limits
{ step = (h *** h) . step . g
, check = check `on` g }
maybeLimit ∷ a → Limits a → Limits (Maybe a)
maybeLimit d = dimap (maybe d id) Just
millionsLimit ∷ Limits Double → Limits Double
millionsLimit = dimap (1.0e6 *) (/ 1.0e6)
-- /show
main = return ()
Example: Containers with Keys
Consider the plethora of *WithKey functions one comes across when working with various containers, for example:
Map.map ∷ (a → b) → Map i a → Map i b
Map.mapWithKey ∷ (i → a → b) → Map i a → Map i b
Can we unify the two functions above?
<lambdabot> The answer is: Yes! Profunctors can do that.
The Control.Lens.Indexed
module provides the Indexed
Profunctor
:
newtype Indexed i a b = Indexed { runIndexed ∷ i → a → b }
Exercise: instance Profunctor (Indexed i)
{-# LANGUAGE UnicodeSyntax #-}
import Data.Profunctor
newtype Indexed i a b = Indexed { runIndexed ∷ i → a → b }
-- show
instance Profunctor (Indexed i) where
dimap g h (Indexed f) = Indexed (dimap g h . f)
-- /show
main = return ()
Together with the Indexable
class,
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UnicodeSyntax #-}
newtype Indexed i a b = Indexed { runIndexed ∷ i → a → b }
-- show
class Indexable i p where
indexed ∷ p a b → i → a → b
instance Indexable i (Indexed i) where indexed = runIndexed
instance Indexable i (→) where indexed = const
-- /show
main = return ()
we can now give a unified story for Map.map
and Map.mapWithKey
:
mapIndexable ∷ Indexable i p ⇒ p a b → Map i a → Map i b
mapIndexable ∷ Indexed i a b → Map i a → Map i b
mapIndexable ∷ (a → b) → Map i a → Map i b
Exercise: mapIndexable
{-# LANGUAGE UnicodeSyntax #-}
import Control.Lens.Indexed
import Data.Map as Map
mapIndexable ∷ Indexable i p ⇒ p a b → Map i a → Map i b
-- show
mapIndexable = Map.mapWithKey . indexed
-- /show
main = return ()
Conclusion
The UpStar
and DownStar
Profunctor
s are also worth investigating, as are the concepts of Strong
and Choice
. Homework for the reader… or let me know if you want me to extend this tutorial. :) Other comments are welcome too &c. &c.
Further Reading
- How to abstract over a “back and forth” transformation?
- Profunctors in Haskell (Warning: abstract nonsense)
- Functor on Wikipedia with sections on bifunctors and covariance versus contravariance
- Profunctor on Wikipedia