Perspectives on Applicative

( I’m posting this here for future reference in mentoring sessions. But by all means feel free to ask questions here as well. )

Note: this post is liable to be edited heavily as a result of responses and future insights.

Perspectives on Applicative

The standard definition of the Applicative type class perhaps isn’t too easy to intuitively grasp the sense of. Luckily, other classes exist that are easier to understand and that are equivalent to it.

By equivalent I mean: any instance of Applicative is also an instance of the alternative class, and vice versa.

If you understand an alternative perspective well, and have some insight into how this alternative perspective translates to (and from) Applicative, then this might provide extra intuition for Applicative. To facilitate this, I show two equivalent classes below.

The standard perspective

The following is the standard definition of Applicative.

class Functor f => Applicative f where
  pure :: a -> f a
  (<*>) :: f (a -> b) -> f a -> f b

I will not belabour it here; your other learning resources should already cover it in detail.

The laws that all instances of this class should obey are

  • Identitypure id <*> v = v
  • Compositionpure (.) <*> u <*> v <*> w = u <*> (v <*> w)
  • Homomorphismpure f <*> pure x = pure (f x)
  • Interchangeu <*> pure y = pure ($ y) <*> u

It is widely agreed that these are ugly.

The monoidal perspective

As it turns out, some Functorial structures lend themselves to ‘merging’ in a nice way. These functors are instances of the following Monoidal type class.

class Functor f => Monoidal f where
  unit  :: f ()
  (<×>) :: f a -> f b -> f (a, b)
Example instances
instance Monoidal Maybe where
  unit :: Maybe ()
  unit = Just ()

  (<×>) :: Maybe a -> Maybe b -> Maybe (a, b)
  Just x <×> Just y = Just (x, y)
  _      <×> _      = Nothing

instance Monoid r => Monoidal ((,) r) where  -- pairs: (r, _)
  unit :: (r, ())
  unit = (mempty, ())

  (<×>) :: (r, a) -> (r, b) -> (r, (a, b))
  (m, x) <×> (n, y) = (m <> n, (x, y))

instance Monoidal ((->) e) where  -- functions: e -> _
  unit :: e -> ()
  unit = \_ -> ()

  (<×>) :: (e -> a) -> (e -> b) -> e -> (a, b)
  f <×> g = \x -> (f x, g x)

instance Monoidal [] where
  unit :: [()]
  unit = [()]

  (<×>) :: [a] -> [b] -> [(a, b)]
  xs <×> ys = [(x, y) | x <- xs, y <- ys]

This perspective emphasizes the structure combining aspect of Applicative. The structure being the f part in the types. This class is named after monoids because its methods should satisfy the following laws, which look a lot like the Monoid laws indeed:

  • Left identityunit <×> v ≅ v
  • Right identityu <×> unit ≅ u
  • Associativityu <×> (v <×> w) ≅ (u <×> v) <×> w

These definitely look a lot simpler!

The equality in these laws is not strict. We use the ≅ symbol to indicate sorta-equality: we consider (a, (b, c)) ≅ ((a, b), c) and (a, ()) ≅ a ≅ ((), a) to be true. This sloppiness with types is not necessary, but does make the laws easier to read. The equalities can be made strict through insertion in the right places of functions that convert between these types.

The lifting perspective

Consider the Functor type class:

class Functor f where
  fmap :: (a -> b) -> (f a -> f b)

It allows ‘lifting’ of unary functions, i.e. functions of one argument. Given a function, fmap will produce another function.

As it turns out, some Functors allow lifting of n-ary functions: functions of n arguments, where n can be any natural number (as opposed to just 1). These functors are instances of the following LiftA type class.

class Functor f => LiftA f where
  liftA0 ::  a                 ->  f a
  liftA1 :: (a -> b)           -> (f a -> f b)
  liftA2 :: (a -> b -> c)      -> (f a -> f b -> f c)
  liftA3 :: (a -> b -> c -> d) -> (f a -> f b -> f c -> f d)
  {- etc. -}

-- Example:
f :: Bool -> Int -> Char -> String
f p n c = let s = replicate n c in if p then map toUpper s else s
-- >>> liftA3 f (Just True) (Just 3) (Just 'a')
-- Just "AAA"
Example instances
instance LiftA Maybe where
  liftA0 x = Just x

  liftA1 f (Just x) = Just (f x)
  liftA1 f _        = Nothing

  liftA2 f (Just x) (Just y) = Just (f x y)
  liftA2 f _        _        = Nothing

  liftA3 f (Just x) (Just y) (Just z) = Just (f x y z)
  liftA3 f _        _        _        = Nothing
  -- etc.

instance Monoid r => LiftA ((,) r) where -- pairs: (r, _)
  liftA0 x                      = ( mempty     , x       )
  liftA1 f (m, x)               = ( m          , f x     )
  liftA2 f (m, x) (n, y)        = ( m <> n     , f x y   )
  liftA3 f (m, x) (n, y) (o, z) = ( m <> n <> o, f x y z )
  -- etc.

instance LiftA ((->) e) where -- functions: e -> _
  liftA0 x       = \_ -> x
  liftA1 k f     = \x -> k (f x)
  liftA2 k f g   = \x -> k (f x) (g x)
  liftA3 k f g h = \x -> k (f x) (g x) (h x)
  -- etc.

instance LiftA [] where
  liftA0 x          = [ x ]
  liftA1 f xs       = [ f x     | x <- xs                   ]
  liftA2 f xs ys    = [ f x y   | x <- xs, y <- ys          ]
  liftA3 f xs ys zs = [ f x y z | x <- xs, y <- ys, z <- zs ]
  -- etc.

This class actually isn’t expressible in Haskell, because it contains an infinite series of methods. But the pattern is obvious, no?

The types of liftA0 and liftA1 should look familiar: they are the same as the types of pure and fmap. In fact, these functions should be identical.

The number of methods might be infinite, but they are all strongly related:

  • liftA1 can be defined in terms of liftA0,
  • liftA2 can be defined in terms of liftA1,
  • liftA3 can be defined in terms of liftA2,
  • etc.

And all in the same way, with the help of some operator of type f (a -> b) -> f a -> f b :thinking:

Hence, to derive all methods of this class, it suffices to start with only liftA0/pure and this mystery operator.

3 Likes

Exercises

I promise these are worth your while. The above ‘explanation’ is not complete without them.

Note: for complicated reasons, the first 3 exercises here cannot be solved simultaneously in the same file. When you get a Duplicate instance declarations error, just comment out the conflicting instance declaration.

1. Applicative ↔️ Monoidal

Prove equivalence of Applicative and Monoidal by filling the gaps in the following two instance declarations.

instance (Functor f, Applicative f) => Monoidal f where
  unit = _
  xs <×> ys = _

instance (Functor f, Monoidal f) => Applicative f where
  pure x = _
  fs <*> xs = _
Solutions

Applicative => Monoidal

instance (Functor f, Applicative f) => Monoidal f where
  unit :: f ()
  unit = pure ()

  (<×>) :: f a -> f b -> f (a, b)
  xs <×> ys = (\x y -> (x, y)) <$> xs <*> ys

Monoidal => Applicative

instance (Functor f, Monoidal f) => Applicative f where
  pure :: a -> f a
  pure x = fmap (\_ -> x) unit

  (<*>) :: f (a -> b) -> f a -> f b
  fs <*> xs = fmap (\(f, x) -> f x) (fs <×> xs)

2. Applicative ↔️ LiftA

Prove equivalence of Applicative and LiftA by filling the gaps in the following two instance declarations.

instance (Functor f, Applicative f) => LiftA f where
  liftA0 x = _
  liftA1 f xs = _
  liftA2 f xs ys = _
  liftA3 f xs ys zs = _
  -- etc.

instance (Functor f, LiftA f) => Applicative f where
  pure x = _
  fs <*> xs = _
Solutions

Applicative => LiftA

instance (Functor f, Applicative f) => LiftA f where
  liftA0 :: a -> f a
  liftA0 = pure

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

  liftA2 :: (a -> b -> c) -> f a -> f b -> f c
  liftA2 f xs ys = f <$> xs <*> ys

  liftA3 :: (a -> b -> c -> d) -> f a -> f b -> f c -> f d
  liftA3 f xs ys zs = f <$> xs <*> ys <*> zs
  -- etc.

LiftA => Applicative

instance (Functor f, LiftA f) => Applicative f where
  pure :: a -> f a
  pure = liftA0

  (<*>) :: f (a -> b) -> f a -> f b
  fs <*> xs = liftA2 (\f x -> f x) fs xs

3. Monoidal ↔️ LiftA

Prove equivalence of Monoidal and LiftA by filling the gaps in the following two instance declarations.

instance (Functor f, Monoidal f) => LiftA f where
  liftA0 x = _
  liftA1 f xs = _
  liftA2 f xs ys = _
  liftA3 f xs ys zs = _
  -- etc.

instance (Functor f, LiftA f) => Monoidal f where
  unit = _
  xs <×> ys = _
Solutions

Monoidal => LiftA

instance (Functor f, Monoidal f) => LiftA f where
  liftA0 :: a -> f a
  liftA0 x = fmap (\_ -> x) unit

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

  liftA2 :: (a -> b -> c) -> f a -> f b -> f c
  liftA2 f xs ys = fmap (\(x, y) -> f x y) (xs <×> ys)

  liftA3 :: (a -> b -> c -> d) -> f a -> f b -> f c -> f d
  liftA3 f xs ys zs = fmap (\((x, y), z) -> f x y z) (xs <×> ys <×> zs)
  -- etc.

LiftA => Monoidal

instance (Functor f, LiftA f) => Monoidal f where
  unit :: f ()
  unit = liftA0 ()

  (<×>) :: f a -> f b -> f (a, b)
  xs <×> ys = liftA2 (\x y -> (x, y)) xs ys

4. Derive all methods of LiftA

This exercise is about the (abstract) purpose of <*>.

  1. Define some <**> :: f (a -> b) -> f a -> f b using only LiftA methods.
  2. Next, define liftA3 in terms of <**> and liftA2.
  3. Also define liftA4 using just <**> and liftA3.
  4. For good measure also define liftA6 in terms of liftA5 (and <**>).

Now f <$> as <*> bs <*> cs <*> ds <*> es <*> fs should make sense.

Solutions

<**>

(<**>) :: LiftA f => f (a -> b) -> f a -> f b
fs <**> xs = liftA2 (\f x -> f x) fs xs

liftA3

liftA3 f xs ys zs = liftA2 f xs ys <**> zs

liftA4

liftA4 :: (a -> b -> c -> d -> e) -> (f a -> f b -> f c -> f d -> f e)
liftA4 f xs ys zs qs = liftA3 f xs ys zs <**> qs

liftA6

liftA6 :: (a -> b -> c -> d -> e -> g -> h) -> (f a -> f b -> f c -> f d -> f e -> f g -> f h)
liftA6 f xs ys zs qs rs ss = liftA5 f xs ys zs qs rs <**> ss

5. (Bonus) Try to prove equivalence of the sets of laws

Assuming the Applicative laws we can verify the Monoidal laws, and vice versa.

As an example, here is a proof of the left identity Monoidal law:

  unit <×> v
= pure () <×> v                               substitution of `unit`
= (\x y -> (x, y)) <$> (pure ()) <*> v        substitution of `<×>`
= pure (\x y -> (x, y)) <*> (pure ()) <*> v   `fmap` law: `f <$> x = pure f <*> x`
= pure ((\x y -> (x, y)) ()) <*> v            homomorphism law
= fmap (\y -> ((), y)) v                      `fmap` law again
≅ fmap (\y -> y) v                            because `((), y) ≅ y`
= fmap id v                                   substitute `id`
= id v                                        functor identity law
= v                                           definition of `id`

Hence:  unit <×> v ≅ v

Some laws are easier to deduce than others, and some are straight up hard.

References & further reading

3 Likes

@MatthijsBlom , I was wondering if you’d mind providing a little bit of feedback (even high-level “yes” or “no”) re: whether we’re on the right track after having gone through these equivalence exercises:

Exercises
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}

module Main where

import Data.Tuple

main = putStrLn "Hello, World!"

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

-- <*> ::  f (a -> b)      -> f a -> f b
-- liftA2 :: (a -> b -> c) -> f a -> f b -> f c


class Functor f => Applicative' f where
  pure' :: a -> f a
  liftA2' :: (a -> b -> c) -> f a -> f b -> f c

apLift :: Applicative f => (a -> b -> c) -> f a -> f b -> f c
apLift f fa = 
  let fbc = fmap f fa
  in (<*>) fbc

liftAp :: Applicative' f => f (a -> b) -> f a -> f b
liftAp fab fa = liftA2' ($) fab fa

class Functor f => Monoidal f where
  unit :: f ()
  combine :: f a -> f b -> f (a, b)

instance (Functor f , Applicative' f) => Monoidal f where
   unit :: f ()
   unit = pure' ()  
   
   combine :: f a -> f b -> f (a, b)
   combine fa fb = liftA2' (\x y -> (x, y)) fa fb

instance (Functor f, Monoidal f) => Applicative' f where
  pure' :: a -> f a
  pure' a = fmap (const a) unit

  liftA2' :: (a -> b -> c) -> f a -> f b -> f c
  liftA2' f fa fb = fmap (uncurry f) $ combine fa fb

-- | An isomorphism witnesses a map between 'a' and 'b'
data Iso a b = Iso { from :: a -> b, to :: b -> a }

-- Some things to note:

-- | 'combine unit fa' is isomorphic to 'fa'
leftUnit :: (Functor f, Monoidal f) => Iso (f ((), a)) (f a)
leftUnit = Iso from to
  where
    --from :: f ((), a) -> f a
    from = fmap snd

c/o of working together with SimonS, ShaeE, AlexC! Y’all know who you are!

Really appreciate the guidance and mentorship you’ve been providing as I’ve been working through the Haskell track. It’s been invaluable!

If apLift is intended as a definition of liftA2 in terms of liftA1+<*>, then it is a success.

liftAp is a correct implementation of <*> in terms of LiftA methods, specifically liftA2.

I’m not sure whether Applicative' is supposed to represent LiftA or Applicative, but of course past a certain point of understanding this doesn’t matter, as they are equivalent.


combine could be eta-reduced, just like liftAp was.

Your translations between Monoidal and Applicative' are the same as mine.


What exactly are you trying to do with leftUnit?

The left identity law unit <×> v ≅ v is a statement about values, but Iso (f ((), a)) (f a) is a statement about types.

The Monoidal f constraint in leftUnit is stronger than necessary: Functor suffices. Which, by the way, suggests that the f doesn’t really participate and could be left out.

If you want local type signatures to work like this, you need to add explicit quantifiers:

leftUnit :: forall f a. (Functor f, Monoidal f) => Iso (f ((), a)) (f a)
leftUnit = Iso from to
  where
    from :: f ((), a) -> f a  -- not a type error anymore!
    from = fmap snd
    to = undefined

The type error is caused by the two f’s not referring to the same type, unless the name was explicitly introduced (with forall). Specifically, if you do not use forall, then implicit foralls are added to both signatures. This is not your fault; rather this unfortunate default behavior is kept for historical reasons (though I don’t know which ones, and whether they are still relevant).