Once you’ve grokked traversable’s you’ll wonder how you ever lived without them. Trying to gain intuition about them by staring at the type signature never brought me much joy. So in this post we’ll take a different approach and invent them ourselves by solving a real problem. This will help us get to that “aha” moment where we finally understand how they work and when to use them.

The scenario

Imagine we’re working for an e-commerce site where we sell one-time offers, such that when all the stock is sold we never have anymore. When a user places an order we must check the stock levels. If there is availability we temporarily reserve the amount they requested before letting them proceed to the checkout.

Our specific task is to write a createCheckout function that will take a Basket and try to reserve the items in it. If they can be successfully reserved it will create a Checkout which includes the total price of the items along with other metadata we might need to take the payment.

Our domain model looks something like this.

type BasketItem = 
    { ItemId: ItemId
      Quantity: float }

type Basket = 
    { Id: BasketId; 
      Items: BasketItem list }

type ReservedBasketItem =
    { ItemId: ItemId
      Price: float }

type Checkout = 
    { Id: CheckoutId
      BasketId: BasketId
      Price: float }

The createCheckout function will return Checkout option . It will return Some if all of the items are available and None if any of them aren’t. A better implementation would return Result and detail the specific errors, but we’ll use option to keep the example simple.

let createCheckout (basket: Basket): Checkout option

Fortunately for us, someone else has already written a function which can reserve a BasketItem if it is in stock, which looks like this.

let reserveBasketItem (item: BasketItem): ReservedBasketItem option

Again, this will return None if there are not enough items in stock.

Our first implementation

So it seems that all we need to do is write a function that calls reserveBasketItem for each item in the basket. If they all succeed then it calculates the total price in order to create the Checkout . Let’s try it.

let createCheckout basket =
    let reservedItems =
        basket.Items |> List.map reserveBasketItem

    let totalPrice =
        reservedItems
        |> List.sumBy (fun item -> item.Price)

    { Id = CheckoutId "some-checkout-id"
      BasketId = basket.Id
      Price = totalPrice }

Here we’re just mapping over the items in the basket to reserve each one and then summing their individual prices to get the total basket price. Seems straight forward, except that’s not going to compile, because it’s not quite right.

The problem is that reservedItems has the type list<option<ReservedBasketItem>> but we need it to be option<list<ReservedBasketItem>> , where it is None if any one of the reservations fail. That way we’d only be able to calculate the total price and create the Checkout if all of the items are available. Let’s imagine we’ve written such a function called reserveItems that does return this type instead and updated createCheckout to use it.

let reserveItems (items: BasketItem list): option<list<ReservedBasketItem>>

let createCheckout basket =
    let reservedItems = basket.Items |> reserveItems

    reservedItems
    |> Option.map
        (fun items ->
            { Id = CheckoutId "some-checkout-id"
              BasketId = basket.Id
              Price = items |> List.sumBy (fun x -> x.Price) })

That’s better! Now if the items are all reserved and reservedItems returns Some then we can access the list of ReservedBasketItem and use them to create the Checkout . If any of the items can’t be reserved then reservedItems returns None and the Option.map just short circuits meaning createCheckout will also return None , as we wanted.

So we’ve reduced the task to implementing reserveItems . We’ve already seen that we can’t just call List.map reserveBasketItem because that gives us a list<option<ReservedBasketItem>> and so the list and the option are the wrong way around. We need a way to invert them.

An invertor 🙃

Let’s invent a function called invert that converts list<option<ReservedBasketItem>> into option<list<ReservedBasketItem>> . If we can do that then we can implement reserveItems like this.

let invert (reservedItems: list<option<ReservedBasketItem>>) : option<list<ReservedBasketItem>>

let reserveItems (items: BasketItem list) : option<list<ReservedBasketItem>> =
    items 
    |> List.map reserveBasketItem 
    |> invert

In order to implement invert let’s start off by pattern matching on the list.

let invert (reservedItems: list<option<ReservedBasketItem>>) : option<list<ReservedBasketItem>> =
    match reservedItems with
    | head :: tail -> // do something when the list isn't empty
    | [] -> // do something when the list is empty

So we’ve got two cases to deal with, when the list has at least one item and when the list is empty. Let’s start with the base case because it’s trivial. If the list is empty then it doesn’t contain any failures, so we should just return Some [] .

In the non empty case then we’ve got to do something with head which is a ReservedBaskedItem option and tail which is a list<option<ReservedBasketItem>> . Well we know that our goal is to turn list<option<ReservedBasketItem>> into option<list<ReservedBaskedItem>> , so we can just recursively call invert on the tail to do this.

let rec invert (reservedItems: list<option<ReservedBasketItem>>) : option<list<ReservedBasketItem>> =
    match reservedItems with
    | head :: tail -> 
        let invertedTail = invert tail
        // Need to recombine the head and the inverted tail
    | [] -> Some []

Now we just need a way to combine a ReservedBasketItem option with a option<list<ReservedBasketItem>> . If neither of these were wrapped in an option then we would just “cons” them using the :: operator, so let’s write a consOptions function which does this but for option arguments.

let consOptions (head: option 'a) (tail: option<list<'a>>): option<list<'a>> = 
    match head, tail with 
    | Some h, Some t -> Some (h :: t) 
    | _ -> None

Nothing too complicated going on here. Simply check if both the head and tail are Some and if so cons them with :: operator and wrap that in a Some . Otherwise if either one is None then return None .

Putting it all together we can finally implement invert like this.

let rec invert (reservedItems: list<option<'a>>) : option<list<'a>> =
    match reservedItems with
    | head :: tail -> consOptions head (invert tail)
    | [] -> Some []

We’ve also been able to make it completely generic on the type inside the list as it doesn’t depend on ReservedBasketItem in any way.

An Applicative clean up 🧽

If you’re familiar with applicatives, perhaps because you’ve followed this series and read Grokking Applicatives then you might have spotted that consOptions looks sort of like a specialised version of apply . What consOptions is trying to do is take some values that are wrapped in options and apply them to a function, in this case cons.

Let’s make use of apply and clean up invert .

let rec invert list =
    // An alias for :: so we can pass it as a function below
    let cons head tail = head :: tail

    match list with
    | head :: tail -> Some cons |> apply head |> apply (invert tail)
    | [] -> Some []

In fact, a proper Applicative instance should also have a pure function. All pure does is create a default value for the Applicative . In the case of option

pure is just Some . Let’s use pure to replace the Some uses.

let rec invert list =
    let cons head tail = head :: tail

    match list with
    | head :: tail -> pure cons |> apply head |> apply (invert tail)
    | [] -> pure []

This might not seem like much of a change, but what we’ve done is eliminate all direct dependencies on option . In theory this could work with any applicative, such as Result or Validation and what it would do is go from list<Applicative<_>> to Applicative<list<_>> . In practice however F# doesn’t quite allow such an abstraction and so we have to create a version of invert for each applicative type we want to use it with.

You can technically get around this with statically resolved type parameters. I would recommend checking out FSharpPlus if you want this abstraction rather than rolling it yourself though.

You just discovered

sequence 👏

invert is usually called sequence and it’s one of the functions that a Traversable type gives us. As we can see sequence takes a collection of wrapped values like an option and turns it into wrapped collection instead. You can think of sequence as flipping the two types over.

sequence works for all sorts of other type combinations too. For example you can take a list<Result<'a>> and flip it into a Result<list<'a>> . You can even use it with different collection types and some that don’t even seem like typical collections, for instance you could go from Result<option<'a>, 'e> to option<Result<'a, 'e>> .

Test yourself on

sequence 🧑‍🏫 See if you can implement sequence for list<Result<_>> to Result<list<_>> .

module Result =
    let apply a f =
        match f, a with
        | Ok g, Ok x -> g x |> Ok
        | Error e, Ok _ -> e |> Error
        | Ok _, Error e -> e |> Error
        | Error e1, Error _ -> e1 |> Error

    let pure = Ok

let rec sequence list =
    let cons head tail = head :: tail

    match list with
    | head :: tail -> Result.pure cons |> Result.apply head |> Result.apply (sequence tail)
    | [] -> Result.pure []

That’s right, it’s exactly the same as for the list<option<_>> providing we use the applicative Result.apply and Result.pure functions for Result . I’ve included their definitions too in a Result module above.

There’s still more land to discover 🏞

Let’s go back to our original program and see how it looks with our new sequence discovery.

let createCheckout basket =
    let reservedItems = 
        basket.Items 
        |> List.map reserveBasketItem 
        |> sequence

    reservedItems
    |> Option.map
        (fun items ->
            { Id = CheckoutId "some-checkout-id"
              BasketId = basket.Id
              Price = items |> Seq.sumBy (fun x -> x.Price) })

It’s pretty good, but we have to make two passes over the basket.Items when creating reservedItems . In the first pass we try and reserve each item and then in the second pass we combine all of those reservations together to determine whether the whole operation succeed or not. It would be nice if we could do that in one go.

Let’s see if we can do it all within sequence . That means that we’ll need to pass the reserveBasketItem function to sequence and we’ll end up with the following signature.

let sequence (f: 'a -> 'b option) (list: 'a list): option<list<'b>>

So we start with a list and we want to apply the function f to each element of it. Although, rather than just mapping over the list and returning list<option<'b>> we want to accumulate all of the option values into a single option<list<'b>> where it is None if for any element f produces a None .

let rec sequence f list =
    let cons head tail = head :: tail

    match list with
    | head :: tail -> Some cons |> apply (f head) |> apply (sequence tail f)
    | [] -> Some []

This is basically the same as before, except now we just apply f to head and pass it into the recursive call in order to also transform the tail elements. All we’ve done is combine the operation that generates the option values with the act of combining them together into a single option of the list.

You just discovered

traverse 🙌 It turns out we typically call the function traverse when we combine both the sequencing and the mapping at the same time. So a Traversable actually has two functions associated with it called sequence and traverse . In fact, sequence is just a special case of traverse where we supply the identity function, id , for f . So we could actually write it like this.

let sequence = traverse id

With traverse in place we can finally finish off our task and write checkoutBasket nicely like this.

let createCheckout basket =
    basket.Items 
    |> traverse reserveBasketItem
    |> Option.map
        (fun items ->
            { Id = CheckoutId "some-checkout-id"
              BasketId = basket.Id
              Price = items |> Seq.sumBy (fun x -> x.Price) })

Test yourself on

traverse 🧑‍🏫 See if you can implement traverse when the input is option<'a> and the function is 'a -> Result<'b, 'c> , so that it returns a Result<option<'b>, 'c> .

module Result =
    let apply a f =
        match f, a with
        | Ok g, Ok x -> g x |> Ok
        | Error e, Ok _ -> e |> Error
        | Ok _, Error e -> e |> Error
        | Error e1, Error _ -> e1 |> Error

    let pure = Ok

let traverse f opt =
    match opt with
    | Some x -> Result.pure Some |> Result.apply (f x)
    | None -> Result.pure None

Here I’ve included the definitions of apply and pure for Result and then implemented traverse using those. Hopefully this makes it clearer which parts of the traverse operation relate to the outer option type and which ones relate to the inner Result type.

One concrete use case for this transformation might be if we’re trying to write a parser. The parser function might say parse string into Result<int, ParseError> but we have to hand a string option . Of course we could pattern match on the option ourselves and then only run the parser in the Some case, but we could also write myOptionalValue |> traverse parseInt .

Another interesting case is when we’re dealing with a regular function, say string which just converts the argument to a string. See if you can figure out what traverse should look like in this case. Specifically, if we want to write [1; 2; 3] |> traverse string and have it output ["1"; "2"; "3"] .

module Identity = 
    let apply a f = f a
    let pure f = f

let rec traverse list f =
    let cons head tail = head :: tail

    match list with
    | head :: tail -> Identity.pure cons |> Identity.apply (f head) |> Identity.apply (traverse tail f)
    | [] -> Identity.pure []

I’ve written this in the same style as the others by extracting an Identity functor/applicative. Identity is actually the degenerate case for an applicative because all apply does is call the function with the argument and all pure does is return the function unaltered. So there is no wrapping going on like with the other applicatives. This is interesting though because traverse now has the type list<'a> -> ('a -> 'b) -> list<'b> , which you might recognise from Grokking Functors as map . So map is actually a special case of traverse when the inner type is just the Identity applicative.

Spotting

Traversable in the wild 🐾 Whenever you’ve got some collection of values wrapped in something like option or Result and what you actually need is an option<list<'a>> or Result<list<'a>, 'e> etc then sequence is probably what you need to use. Similarly, if you have to run a computation over a collection that produces wrapped values then you can use traverse and combine the mapping and flipping into one operation.

Warning, two types of error handling ahead ⚠️

When we’re sequencing a list<option<_>> we only need to know that at least one of the elements is None in order to return None . However, when working with something like list<Result<'a, 'e>> then we might actually care about gathering up all of the errors. As we pointed out in Grokking Applicative Validation there can be applicative instances that either short circuit on the first error or accumulate all errors. The same applies here with Traversable . Let’s quickly run some experiments in the F# REPL with FSharpPlus to see how it handles things.

> [Ok 1; Error "first error"; Error "second error"] |> sequence;;
val it : Result<int list, string> = Error "first error"

[Success 1; Failure ["first error"]; Failure ["second error"]] |> sequence;;
val it : Validation<string list, int list> =
  Failure ["first error"; "second error"]

In the first case, when using Result we see that it just returns the first error it encounters, while with Validation it actually accumulates all the errors for us.

What did we learn 🧑‍🎓

Traversable is more powerful version of map that is particularly useful when we have a computation that either needs to be run (or has already been run) over a list of values and we want to treat it as a failure if any single one fails. We can also grok it by realising that it flips the two outer types over. We use traverse when we still need to run the computation and sequence when we’ve been given the list of computation results instead.

This post is also available on DEV.