class Functor (t :: * -> *) where
fmap :: (a -> b) -> t a -> t b
Notice that we’re explicitly writing KindSignatures
(enabled by default in GHC2021
)
for emphasis. (Note: If you/we have not considered kinds yet, now is a good
time to go back through.)
Two laws that each instance
type T
should
satisfy (writing “≡” to mean “equivalent”):
fmap id
≡ id
fmap (f . g)
≡ fmap f . fmap g
Recall mapMaybe
from before:
instance Functor Maybe where
-- fmap :: (a -> b) -> Maybe a -> Maybe b
fmap f Nothing = Nothing
fmap f (Just x) = Just $ f x
instance Functor [] where
-- fmap :: (a -> b) -> [] a -> [] b
fmap :: (a -> b) -> [a] -> [b]
fmap = map
The pair constructor (,)
has kind
* -> * -> *
. So, to be a Functor
, need
to partially apply it to one type argument.
The type signature for fmap
in the class definition
refers to bound type variables a
and b
. So we
should think a bit before choosing new variables. One option is to
choose some other variable, say x
or fst
:
instance Functor ((,) fst) where
-- fmap :: (a -> b) -> (,) fst a -> (,) fst b
-- fmap :: (a -> b) -> (fst, a) -> (fst, b)
This is fine, but an alternative is to use a
as the
first argument to the pair type and then rename the a
and
b
in the fmap
signature to b
and
b'
, respectively. I prefer this setup, because it is common
to refer to the component types of a pair with variables a
and b
, and the similarity between variables b
and b'
helps to remember their relationship.
instance Functor ((,) a) where
-- fmap :: (b -> b') -> (,) a b -> (,) a b'
fmap :: (b -> b') -> (a, b) -> (a, b')
fmap f (a, b) = (a, f b)
data Either a b
= Left a
| Right b
A very general mapping function would take a function for each variant:
mapEither :: (a -> a') -> (b -> b') -> Either a b -> Either a' b'
mapEither f g (Left a) = Left $ f a
mapEither f g (Right b) = Right $ g b
But the type of this function doesn’t fit the requirements of
fmap
. To make something involving Either
a
Functor
, like (,)
need to partially apply
Either
to one type argument. So, must implement
“mapRight
”:
instance Functor (Either a) where
fmap :: (b -> b') -> Either a b -> Either a b'
fmap f (Left a) = Left a
fmap f (Right b) = Right $ f b
This is still useful — transform only Right
values while
simply propagating Left
values (often used to represent
errors) — but it won’t help in a situation where Left
values need to be transformed as well.
Note: Consider the following seemingly
equivalent definition — the Left
equation uses a variable
left_a
to match the values Left a
:
instance Functor (Either a) where
fmap :: (b -> b') -> Either a b -> Either a b'
fmap f (Right b) = Right $ f b
fmap f left_a = left_a
This version does does not typecheck, however, because Haskell
assigns only one type to every expression. The variable
left_a
is assigned type Either a b
, but what
is needed on the right-hand side is an Either a b'
. The
value bound to left_a
(Left a
for
some a
) can be assigned the desired type, but the
variable binding that value has been assigned a different
type.
instance Functor ((->) t) where
-- fmap :: (a -> b) -> ((->) t) a -> ((->) t) b
-- fmap :: (a -> b) -> (t -> a) -> (t -> b)
fmap :: (a -> b) -> (t -> a) -> t -> b
-- fmap f g = \t -> f (g t)
-- fmap f g = f . g
fmap = (.)
newtype
(Redux)Here’s a really simple wrapper type.
data Box a = Box a
Recall (or consider for the first time) that we often use newtype
, rather
than data
, to define datatypes with exactly one
one-argument constructor…
newtype Box a = Box a
… and that we can use record type syntax to automatically derive accessor, or projection, functions.
newtype Box a =
Box { unbox :: a }
Even without using record type syntax, we could have, of course,
written our own unbox
function. Although it is certainly
nice to have these projection functions automatically derived, the
“real” reason we will often define wrapper types (with record type
constructors) in what follows is to work around the rule that, for each
type class, there can be at most one instance per
type.
But while we’re here, let’s observe that Box
is a
Functor
.
instance Functor Box where
fmap :: (a -> b) -> Box a -> Box b
-- fmap f (Box a) = Box (f a)
-- fmap f box = Box (f (unbox box))
-- fmap f box = (Box . f . unbox) box
fmap f = Box . f . unbox
This Box
type is defined in the standard library (Data.Functor.Identity)
with different names:
newtype Identity a = Identity { runIdentity :: a }
type AssocList k v = [(k, v)]
type AssocList k v = [] (k, v)
type AssocList k v = [] ((,) k v)
What if we want to fmap
a function over an association
list of type AssocList k v
? If the function
(k,v) -> b
needs both the key and value, the
Functor
interface doesn’t help. But what if the function
v -> b
transforms only the values in each pair
and keep the keys the same? We would like the composition of
the behavior of fmap
for lists (i.e. map
) and
for pairs (in the Functor ((,) a)
instance above). We can
define a wrapper type for this composition.
newtype AssocList k v =
BoxAssocList { unboxAssocList :: [(k, v)] }
AssocList
is a Functor
via a combination of
fmap
for lists and fmap
for pairs:
instance Functor (AssocList k) where
-- fmap :: (a -> b) -> (AssocList k) a -> (AssfocList k) b
-- fmap :: (a -> b) -> AssocList k a -> AssocList k b
-- fmap f (BoxAssocList kvs) = BoxAssocList $ map (fmap f) kvs
-- fmap f box = BoxAssocList $ map (fmap f) (unboxAssocList box)
-- fmap f box = BoxAssocList $ map (fmap f) . unboxAssocList $ box
fmap f = BoxAssocList . map (fmap f) . unboxAssocList
AssocList
composes []
and (,)
,
but there are other types (of kind * -> *
) we might like
to compose as well. We can factor out this pattern of composition with a
more general wrapper type:
newtype Compose f g x =
Compose { getCompose :: f (g x) }
instance (Functor f, Functor g) => Functor (Compose f g) where
fmap :: (a -> b) -> Compose f g a -> Compose f g b
-- fmap f (Compose x) = Compose (fmap (fmap f) x)
fmap f = Compose . fmap (fmap f) . getCompose
And then:
type AssocList k v =
Compose [] ((,) k) v
Or:
type AssocList k =
Compose [] ((,) k)
Note that Compose
is defined in Data.Functor.Compose
.
Here’s an example association list…
> zip "ABCDE" [0..]
[('A',0),('B',1),('C',2),('D',3),('E',4)]
One way to access the “composition of fmap
s”
functionality is to wrap our association list in Compose
,
do the fmap
, then unwrap it:
> import Data.Functor.Compose
> getCompose $ fmap (+1) $ Compose $ zip "ABCDE" [0..]
[('A',1),('B',2),('C',3),('D',4),('E',5)]
For this association-list example, we are composing the
[]
and (,) Int
types. But this composition
works for any types t1
and t2
that are in
Functor
. For example, the composition of []
and []
:
> getCompose $ fmap (+1) $ Compose $ [ [], [0], [1,2], [3..5] ]
[[],[1],[2,3],[4,5,6]]
And Maybe
and []
:
> getCompose $ fmap (+1) $ Compose $ Just [0..5]
Just [1,2,3,4,5,6]
And []
and Maybe
:
> getCompose $ fmap (+1) $ Compose $ map Just [0..5]
[Just 1,Just 2,Just 3,Just 4,Just 5,Just 6]
Remember mapListMaybe
and
mapMaybeList
?
We don’t need to worry about this…
> :set -fprint-explicit-foralls
> :k Compose
Compose :: forall {k1} {k2}. (k1 -> *) -> (k2 -> k1) -> k2 -> *
… but kinds can be polymorphic! This facility is based on Giving Haskell a Promotion.
The Functor
class is defined in
Data.Functor
and exposed by Prelude
. As
alluded to in the “Monad
Roadmap”, there is an infix operator defined to be
fmap
.
(<$>) = fmap
The expression f <$> x
, which resembles the
function application f x
, is equivalent to
fmap f $ x
.