Chapter 21: Traversable

21.1 Traversable

In this chapter, we will:

  • explain the Traversable typeclass and its canonical functions;

  • explore examples of Traversable in practical use;

  • tidy up some code using this typeclass;

  • and, of course, write some Traversable instances.

21.2 The Traversable type class definition

Let’s look at the type class definition for Traversable:

class (Functor t, Foldable t) => Traversable (t :: * -> *) where

  traverse   :: Applicative f   =>   (a -> f b)  ->  t a  ->  f (t b)
  traverse f = sequenceA . fmap f

  mapM       :: Monad m         =>   (a -> m b)  ->  t a  ->  m (t b)
  mapM = traverse

  sequenceA  :: Applicative f   =>      t (f a)  ->  f (t a)
  sequenceA = traverse id

  sequence   :: Monad m         =>      t (m a)  ->  m (t a)
  sequence = sequenceA

  {-# MINIMAL traverse | sequenceA #-}


instance Traversable []
instance Traversable Maybe
instance Traversable (Either a)
instance Traversable ((,) a)

Notice that the constraint of Applicative is a property of some of the class methods, rather than the type class itself.

Let’s look more closely at the type signature for traverse:

class (Functor t, Foldable t) => Traversable t where
  traverse :: Applicative f => (a -> f b) -> t a -> f (t b)
  -- fmap  ::                  (a -> b)   -> f a -> f b
  --                                    b ~ t c
  --                           (a -> t c) -> f a -> f (t c)

The a -> t c could be a function like Leaf, an effectful function. The function a -> t c would inject this t effect while acting on a, preserving the structure of f while doing so. For traverse, it flips the f and t so the result is t (f c).

What does traverse do? It maps each element within a structure to an action, evaluates those actions from left to right, and collects the results.

What does “collects the results” mean, here?

21.3 sequenceA

Alright, what is sequenceA, really?

You can see from the type signature that sequenceA is flipping two contexts or structures:

sequenceA :: ( Traversable t
             , Applicative f )
          => t (f a) -> f (t a)

sequenceA doesn’t allow you to apply any function to the a value inside the structure by itself; it only flips the layers of structure around.

An experiment in GHCi:

·∾ :doc sequenceA
 Evaluate each action in the structure from
 left to right, and collect the results. For
 a version that ignores the results see
 'Data.Foldable.sequenceA_'.

·∾ :{
 ⋮ sequenceA [ putStrLn "one" >> getLine
 ⋮           , putStrLn "two" >> getLine
 ⋮           , putStrLn "three" >> getLine ]
 ⋮ :}
one
1
two
2
three
3
["1","2","3"]

Some examples from this section.

-- Compare these...
·∾ sum [1,2,3]
6

·∾ fmap sum [Just 1, Just 2, Just 3]
[1,2,3]

·∾ (fmap . fmap) sum Just [1,2,3]
Just 6

·∾ fmap sum (fmap Just [1,2,3])
[1,2,3]

·∾ fmap product [Just 1, Just 2, Nothing]
[1,2,1]


-- ...to these...
·∾ fmap Just [1,2,3]
[Just 1,Just 2,Just 3]

·∾ sequenceA $ fmap Just [1,2,3]
Just [1,2,3]

·∾ sequenceA [Just 1, Just 2, Just 3]
Just [1,2,3]

·∾ sequenceA [Just 1, Just 2, Nothing]
Nothing

·∾ fmap sum $ sequenceA [Just 1, Just 2, Just 3]
Just 6

·∾ fmap product (sequenceA [Just 1, Just 2, Nothing])
Nothing


-- It's worth mentioning that
-- Data.Maybe.catMaybes offers a different
-- way of handling a list of Maybe values...
·∾ import Data.Maybe

·∾ catMaybes [Just 1, Just 2, Just 3]
[1,2,3]

·∾ catMaybes [Just 1, Just 2, Nothing]
[1,2]

·∾ let xs = [Just 1, Just 2, Just 3, Nothing]

·∾ sum $ catMaybes xs
6

·∾ fmap sum $ sequenceA xs
Nothing

-- Using catMaybes allows you to sum (or
-- otherwise process) the list of Maybe values
-- even if there's potentially a Nothing value
-- lurking within.

21.4 traverse

Let’s look at the type of traverse:

·∾ :type traverse
traverse :: (Traversable t, Applicative f)
         => (a -> f b) -> t a -> f (t b)

You might notice a similarity between that and the types of fmap and (flip bind):

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

(flip (>>=)) :: Monad m
             => (a -> m b) -> m a -> m b

traverse     :: (Traversable t, Applicative f)
             => (a -> f b) -> t a -> f (t b)

traverse is similar to fmap, except that it also allows you to run applicative effects while you’re rebuilding the data structure, which also changes the result type.

In this usage, applicative is almost the same as monad, except that effects cannot depend on previous results.

Here’s an example someone gave me from IRC that illustrates this:

·∾ traverse (\s -> putStrLn s >> getLine) ["hello", "hi", "aloha"]
hello
Chris
hi
Bonjour!
aloha
Aloha!
["Chris","Bonjour!","Aloha!"]

·∾ mapM (\s -> putStrLn s >> getLine ) ["hello", "hi", "aloha"]
hello
Chris
hi
Bounjour!
aloha
Alohahaha
["Chris","Bounjour!","Alohahaha"]

Since I’ve been using mapM for a while I found this a useful comparison.

You’ve already seen that traverse is fmap composed with sequenceA. Here are a few examples of that:

·∾ fmap Just [1,2,3]
[Just 1,Just 2,Just 3]

·∾ sequenceA $ fmap Just [1,2,3]
Just [1,2,3]

·∾ sequenceA . fmap Just $ [1,2,3]
Just [1,2,3]

·∾ traverse Just [1,2,3]
Just [1,2,3]

The general idea is that anytime you’re using sequenceA . fmap f you can use traverse to achieve the same result in one step.

21.5 So, what’s Traversable for?

In a literal sense, anytime you need to flip two type constructors around, or map something and then flip them around, that’s probably Traversable.

·∾ f = undefined :: a -> Maybe b

·∾ xs = undefined :: [a]

·∾ :type map f xs
map f xs :: [Maybe b]

·∾ :type sequenceA $ map f xs
sequenceA $ map f xs :: Maybe [a]

It’s usually better to use traverse whenever we see a sequence or sequenceA combined with a map or fmap.

·∾ :type sequenceA $ map f xs
sequenceA $ map f xs :: Maybe [a]

·∾ :type traverse f xs
traverse f xs :: Maybe [b]

21.6 Morse code revisited

The expression (sequence .) . fmap is so hard to read that the authors included a translation in the book. Just don’t write code like that in the first place, it’s awful.

21.7 Axing tedious code

import Control.Monad ((<=<))
-- 21.7 Axing tedious code
-- This figure is not runnable
-- page 840



-- Thanks for the great example, Alex
data Query = Query
data SomeObj = SomeObj
data IoOnlyObj = IoOnlyObj
data Err = Err


-- There's a decoder function that makes some
-- object from String
decodeFn :: String -> Either Err SomeObj
decodeFn = undefined


-- There's a query, that runs agains the DB
-- and returns an array of strings
fetchFn :: Query -> IO [String]
fetchFn = undefined


-- an additional "context initializer", that also has IO
makeIoOnlyObj :: [SomeObj] -> IO [(SomeObj, IoOnlyObj)]
makeIoOnlyObj = undefined


-- before
pipelineFn :: Query -> IO (Either Err [(SomeObj, IoOnlyObj)])
pipelineFn query = do
  a <- fetchFn query
  case sequence (map decodeFn a) of
    (Left err) -> return $ Left $ err
    (Right res) -> do
      a <- makeIoOnlyObj res
      return $ Right a

{-
 - The objective was to clean up this code. A
 - few things made them suspicious:
 -
 - 1. The use of sequence and map.
 - 2. Manually casing on the result of the
 -    sequence and the map.
 - 3. Binding monadically over the Either only
 -    to perform another monadic (IO) action
 -    inside of that.
 -
 - We pared the pipeline function down to
 - this:
 -}


pipelineFn' :: Query -> IO (Either Err [(SomeObj, IoOnlyObj)])
pipelineFn' query = do
  a <- fetchFn query
  traverse makeIoOnlyObj (mapM decodeFn a)


-- We can make it pointfree if we want to.
pipelineFn'' :: Query -> IO (Either Err [(SomeObj, IoOnlyObj)])
pipelineFn'' =
  ( traverse makeIoOnlyObj . mapM decodeFn =<< ) . fetchFn


-- ...and since mapM is just traverse with a
-- slightly different type:
pipelineFn''' :: Query -> IO (Either Err [(SomeObj, IoOnlyObj)])
pipelineFn''' =
  ( traverse makeIoOnlyObj . traverse decodeFn =<< ) . fetchFn


-- Finally, since hlint won't stop yelling at me...
pipelineFn'''' :: Query -> IO (Either Err [(SomeObj, IoOnlyObj)])
pipelineFn'''' =
  traverse makeIoOnlyObj . traverse decodeFn <=< fetchFn

21.8 Do all the things

Here, have some more code! Get ready for a really long compile time if you try to run this. Also, what is this supposed to even do? How do I use it? What is a bytestring? What’s wreq?

#!/usr/bin/env stack
{- stack script
   --resolver lts-16.27
   --install-ghc
   --package wreq
   --package bytestring
-}
module HttpStuff where
import Data.ByteString.Lazy hiding (map)
import Network.Wreq


-- replace with other websites if desired or needed
urls :: [String]
urls = [ "http://httpbin.org/ip"
       , "http://httpbin.org/bytes/5"
       ]


mappingGet :: [IO (Response ByteString)]
mappingGet = map get urls


traversedUrls :: IO [Response ByteString]
traversedUrls = traverse get urls

21.10 Traversable Laws

21.10.1 traverse

  1. Naturality t . traverse f \(=\) traverse (t . f)

  2. Identity traverse Identity \(=\) Identity This is another way of saying that a traversable instance cannot add or inject any structure or effects.

  3. Composition traverse (Compose . fmap g . f) \(=\) Compose . fmap (traverse g) . traverse f

21.10.2 sequenceA

  1. Naturality t . sequenceA \(=\) sequenceA . fmap t

  2. Identity sequenceA . fmap Identity \(=\) Identity

  3. Composition sequenceA . fmap Compose \(=\) Compose . fmap sequenceA . sequenceA

21.12 Chapter Exercises

21.12.1 Traversable instances

Write a Traversable instance for the datatype provided, filling in any required superclasses. Use QuickCheck to validate your instances.

Identity

Write a Traversable instance for Identity:

newtype Identity a = Identity a
  deriving (Eq, Ord, Show)


instance Traversable Identity where
  traverse = undefined

Constant

newtype Constant a b =
  Constant { getConstant :: a }

Maybe

data Optional a = Nada | Yep a

List

data List a = Nil | Cons a (List a)

Three

data Three a b c = Three a b c

Pair

data Pair a b = Pair a b

Big

When you have more than one value of type b, use Monoid and Applicative for the Foldable and Traversable instances, respectively:

data Big a b = Big a b b

Bigger

Same as for Big:

data Bigger a b = Bigger a b b b

S

This may be difficult. To make it easier, we’ll give you the constraints and QuickCheck instances:

{-# LANGUAGE FlexibleContexts #-}
module SkiFree where
import Test.QuickCheck
import Test.QuickCheck.Checkers


data S n a = S (n a) a deriving (Eq, Show)


instance ( Functor n
         , Arbitrary (n a)
         , Arbitrary a )
         => Arbitrary (S n a)
where
  arbitrary = S <$> arbitrary <*> arbitrary


instance ( Applicative n
         , Testable (n Property)
         , Eq a
         , Eq (n a)
         , EqProp a)
         => EqProp (S n a)
 where
   (=-=) = eq


instance Traversable n => Traversable (S n) where
  traverse = undefined


main = sample' (arbitrary :: Gen (S [] Int))

21.12.2 Instances for Tree

This might be hard. Write the following instances for Tree:

data Tree a
  = Empty
  | Leaf a
  | Node (Tree a) a (Tree a)
  deriving (Eq, Show)

instance Functor Tree where
  fmap = undefined


-- foldMap is a bit easier and looks more natural,
-- but you can do foldr, too, for extra credit.
instance Foldable Tree where
  foldMap = undefined


instance Traversable Tree where
  traverse = undefined

Hints

  1. For foldMap, think Functor but with some Monoid thrown in.

  2. For traverse, think Functor but with some Functor thrown in. (Not a typo.)