Blog

Type-safe error handling with Shapeless coproducts in Scala

Xebia Background Header Wave

Introduction

Error handling is often not given the attention that it deserves. Coming from imperative languages, it’s super easy to throw exceptions all over the place. Still, because it’s easy, it doesn’t mean it’s a good practice. It breaks referential transparency, making it difficult to reason about code. Java has checked exceptions, but that is not making the problem disappear, as it still breaks referential transparency. There are many more reasons why “just throwing exceptions” is not a good practice, but I’ll not go into that today. My concern with using exceptions is that, in many cases, we are not talking about the “exceptional” part embedded in the word “exception”.

Let’s have a look at the Cambridge definition of the word “exception”. If we look at technical exceptions, I can fully agree with the last part of the definition:

Exception: "Someone or something that is not included in a rule, group, or list or that does not behave in the expected way."
Cambridge Dictionary

Hereby are a few examples of unexpected behaviours due to technical issues:

  • While saving data to a database, the connection goes down, failing to persist the data.
  • While uploading images to a server, the connection gets interrupted, failing to send the image entirely.
  • While processing a Kafka message, the client gets killed, failing to process the message.

These are all examples of processes that somehow did not behave expectedly. The exception here is due to a technical issue. Looking at a pure domain, however, many exceptions are not exceptions.

Below you can find a few examples of everyday situations that did not behave expectedly:

  • Before registering a new user, we validate the data and realize that a field is missing, sending back a 400 bad request to the client.
  • While processing a financial transaction, the system suspects
    something is off, informs the users that something went wrong and
    automatically notifies the fraud team to investigate the transaction.
  • When trying to pay with a gift card, the system notices that there’s
    not enough balance on the gift card to complete the order, and the user is informed accordingly.

The above examples are part of domains where we anticipate that these situations can happen and are therefore expected. Even though the chance of them happening might be small, these are still situations we expect to happen. Instead of misusing exceptions, we can make errors part of our domain and introduce the concept of a domain error. The advantage of using a different type (i.e. anything that is not inheriting from Throwable) is that we need to handle them explicitly. There’s no way we can throw them; therefore, we cannot use any try/catch construction. There’s, however, a downside when using sealed traits.

In this article, we’ll be creating a straightforward command-line app to divide numbers. We’ll go through a few iterations of code, and I’ll show you the problems we will run into and how Shapeless coproducts can help us out.

Domain errors are everywhere

Why would we want to use domain errors again? Let’s have a look at the method below:

def divide(x: Int, y: Int) = x / y

The above code is concise and readable, but we do not inform the consumer of our method that it can produce errors. Dividing by zero should not be possible. An ArithmeticException will be thrown if the consumer dares to try. However, that doesn’t make much sense. We already know that we can’t divide by zero, so that’s not an exception. It’s part of our domain, and we should inform our fellow programmers that we do not allow divisions by zero. Making it explicit will help our colleagues understand that the method requires error handling. We should always strive to create error handlers that are total functions. This way, the compiler can help us if we accidentally do not handle all errors. Otherwise, you’ll lose any benefit, and you can just as well use exceptions.

Why sealed traits are not the best option

A common way to deal with errors is using a sealed trait. Looking at our little “number dividing” command-line app, we know that we can run into at least two issues:

  • Converting input from the command line into a number can go wrong
  • Dividing by zero is not possible

By introducing a sealed trait, we could document these errors in our codebase as follows:

sealed trait DomainError
case object DivideByZeroError extends DomainError
case class ParseNumberError(value: String) extends DomainError

By using traits, we need to start thinking about structuring the error hierarchy.

  • Do all domain errors inherit from a root? (e.g. DomainError in the above example)
  • Do we introduce subdomains of errors that might or might not have a common ancestor? (e.g. per endpoint, per functionality, or maybe something else?)

In either case, we will not be delighted.

In the first scenario, we will not be able to accurately describe which errors we might get back the moment we start composing methods. As all errors inherit from DomainError, we will be unable to understand which errors can actually occur. See the example below for further details.

sealed trait DomainError
case class ErrorA() extends DomainError
case class ErrorB() extends DomainError
case class ErrorC() extends DomainError

object SomeClass {
  def methodA(s: String): Either[ErrorA, String] = if (s.isEmpty) Left(ErrorA()) else Right(s)
  def methodB(s: String): Either[ErrorB, Int] = s.toIntOption.fold[Either[ErrorB, Int]](Left(ErrorB()))(Right.apply)

  // This method has to return DomainError and is no longer accurate, as it can only ever return ErrorA or ErrorB.
  def methodAB(s: String): Either[DomainError, Int] = methodA(s).flatMap(methodB)
}

In the second scenario, we will have difficulties composing methods. The moment subdomains start interacting, we will need to cast them to a new error that is known by the other subdomain. Meaning we will start introducing duplication per interaction, as a DivideByZeroError in domain A, which will also need to exist in domain B once they start interacting. We could "solve" the problem by introducing a common ancestor, but that would lead us to the problem of the previous scenario.

The lack of visibility on which errors are returning is not something to overlook. A method returning DomainError in a codebase where we could have hundreds of domain errors defined provides no help whatsoever. The consumer of our approach would have to inspect our code to understand which domain errors can actually occur. At the same time, our compiler can no longer help us out if we accidentally forget about an error case. Total functions become useless if we start including cases that can never appear. In large codebases, it’s also impossible to go through numerous layers of code to figure out what will be returned. This slows you down as a programmer and, at the same time, gives you nothing but a gut feeling. Did you check everything thoroughly? Would it be possible that you have overlooked an error case? Just think about automatically updating dependencies, and you’ll quickly realize that you would need to continuously go through 3rd party code to figure out what you can expect from an error perspective.

Let errors become first-class citizens! If we can make everything explicit, we don’t run into any of the above problems. If dependencies get updated, and new error cases were introduced, then you’ll automatically run into compile errors, as our full function handling the errors is no longer covering all cases. No time wasted. And you know exactly where to fix what. Unfortunately, in Scala 2.x, there is no class or type class that we could use:

  • The Option type class deals with the optionality of a single type. We, however, already know that a method could likely produce more
    than a single error. When composing methods, the likeliness will
    increase even more.
  • The Either type class has a left and right projection, where the left
    can be used for error cases. Its left projection has only space for a
    single type, while we need more.
  • The List type class can store multiple values, but only for a single
    type.

We need some kind of structure EitherN that allows us to return numerous error types instead that can be unrelated and do not need a common ancestor. This is exactly what we are going to achieve with Shapeless coproducts.

What is an HList?

To handle different errors, we would need a List structure that can store different types and not lose any type-safety. Let’s have a look at the HList type class. It provides a way to create a list of more than a single type. Remember that the List type class in Scala always provides a list of a specific type (e.g. List[Int]). With HList, we can create lists of more than a single type.

See the example below for a list that contains multiple values (1, "world", 1.5) of different types (String, Int, Double):

import shapeless.HNil
import shapeless.::
val hlist: String :: Int :: String :: Double :: HNil = "hello" :: 1 :: "world" :: 1.5 :: HNil

What is a coproduct?

Coproduct is a special kind of HList. You can think of it as an Either in Scala, with an arbitrary number of choices.

import shapeless.{:+:, CNil, Coproduct}

type MyType = String :+: Int :+: Double :+: CNil
val coproduct: MyType = Coproduct[MyType](1.5)

In the code above, the coproduct will either contain a String, Int or a Double value.

Iterations

Let’s play with code, go through 7 iterations, and try to improve the code each
time as much as possible.

Iteration 1: No error handling

Let’s go back to our divide app and start without thinking about any error handling at all:

import scala.io.StdIn.readLine

object DivideAppIteration1 extends App {
  // Can throw an ArithmeticException when dividing by zero.
  def divide(x: Double, y: Double): Double = x / y

  // Potential IOException when using readLine.
  val x0 = readLine
  val y0 = readLine

  // Potential parse errors when converting String to Double.
  val x = x0.toInt
  val y = y0.toInt

  println(divide(x, y))
}

We already know that this code is not resilient:

  • We are not preventing division by zero.
  • We are not catching parse errors.
  • We are not catching the potential IOException that can occur.

Did you know that readLine can throw an IOException? It’s not obvious at all from the actual method signature:

def readLine(): String = in.readLine()

By diving one level deeper, we’ll see the following Java code:

public String readLine() throws IOException {
  return readLine(false, null);
}

This perfectly demonstrates the need to make errors first-class citizens of a program. By not knowing explicitly which error cases can occur, you will run into runtime errors or have to scan each line of code yourself. Not only in your code but also in all the libraries you might use. Not really an option if you like to get things done…

Iteration 2: Using Either

Let’s have another go at our application and make it a bit more robust by using the Either type class:

import scala.io.StdIn.readLine
import scala.util.Try

object DivideAppIteration2 extends App {
  // Using sealed traits to distinguish the type of errors
  sealed trait DomainError

  case object DivideByZeroError extends DomainError

  case class ParseNumberError(value: String) extends DomainError

  // Dividing an error now explicitly shows what kind of error it could produce.
  def divide(x: Double, y: Double): Either[DomainError, Double] =
    if (y == 0) Left(DivideByZeroError)
    else Right(x / y)

  // This now, unfortunately became an Object due to the mixing of DomainError and IOException
  def runDivide: Either[Object, Double] = for {
    x0 <- Try(readLine).fold(Left.apply, Right.apply)
    y0 <- Try(readLine).fold(Left.apply, Right.apply)
    x <- x0.toDoubleOption
           .fold[Either[ParseNumberError, Double]](Left(ParseNumberError(x0)))(Right.apply)
    y <- y0.toDoubleOption
           .fold[Either[ParseNumberError, Double]](Left(ParseNumberError(y0)))(Right.apply)
    r <- divide(x, y)
  } yield r

  runDivide.fold(
    // As err is of type Object, we cannot create any sensible error handler based on the type
    err => println(s"An error occurred: $err"),
    result => println(s"Result: $result")
  )
}

Even though the above code runs fine, the runDivide method has turned into an untyped mess. Object does not accurately describe what kind of
errors we can expect. This is because DomainError and IOException have only Object in common from an inheritance point of view.

Iteration 3: Creating type-safety with coproducts

Let’s have a look at how we can improve type-safety with Shapeless coproducts:

import shapeless.{:+:, CNil, Coproduct}

import java.io.IOException
import scala.io.StdIn.readLine
import scala.util.Try

object DivideAppIteration3 extends App {
  // Notice that creating a sealed trait error hierarchy is no longer necessary.
  case object DivideByZeroError

  case class ParseNumberError(input: String)

  // Definition of the errors that can occur
  type TryDivideError = DivideByZeroError.type :+: CNil
  type TryReadLineError = IOException :+: CNil
  type TryParseNumberError = ParseNumberError :+: CNil

  def tryDivide(x: Double, y: Double): Either[TryDivideError, Double] =
    if (y == 0) Left(Coproduct(DivideByZeroError))
    else Right(x / y)

  def tryReadLine = Try(readLine).fold[Either[TryReadLineError, String]](
    ex => Left(Coproduct(new IOException(ex))),
    Right.apply
  )

  def tryParseDouble(s: String) =
    s.toDoubleOption.fold[Either[TryParseNumberError, Double]](
      Left(Coproduct(ParseNumberError(s)))
    )(Right.apply)

  type RunDivideError = TryReadLineError :+: TryParseNumberError :+: TryDivideError :+: CNil

  // Yes! We now have an actual error type that accurately describes the error cases.
  def runDivide: Either[RunDivideError, Double] = for {
    x0 <- tryReadLine.left.map(Coproduct[RunDivideError](_))
    y0 <- tryReadLine.left.map(Coproduct[RunDivideError](_))
     x <- tryParseDouble(x0).left.map(Coproduct[RunDivideError](_))
     y <- tryParseDouble(y0).left.map(Coproduct[RunDivideError](_))
     r <- tryDivide(x, y).left.map(Coproduct[RunDivideError](_))
  } yield r

  runDivide.fold(println, println)
}

Each method still explicitly describes what its error signature is. The big difference is that we have now introduced a new coproduct RunDivideError that is either one of the coproducts that each particular method produces (either a TryReadLineError, TryParseNumberError or TryDivideError or):

// Each individual error defined.
type TryDivideError = DivideByZeroError.type :+: CNil
type TryParseNumberError = ParseNumberError :+: CNil
type TryReadLineError = IOException :+: CNil

// A composition of errors we expect for the divide 'flow'.
type RunDivideError = TryDivideError :+: TryReadLineError :+: TryParseNumberError :+: CNil

To return a RunDivideError, we must ensure that every method’s result is widened. We can do that by wrapping the result in a new coproduct like:

Coproduct[RunDivideError](resultOfTheMethod) // Widens the type returned from the method.

There’s a slight “gotcha” here. As coproducts are nothing more than a special kind of HList, defining RunDivideErrors below means we could have duplicate types in our error channel. This isn’t necessarily a problem, but it would be at least good to mention it.

TryDivideError :+: TryReadLineError :+: TryParseNumberError :+: CNil

Let’s create a simple example that quickly illustrates the potential issue of type duplication and how we can solve it:

import shapeless.{:+:, CNil, Coproduct}

// Error definitions, there's a bit of overlap on the types.
type Method1Error = String :+: Int :+: CNil
type Method2Error = String :+: Double :+: CNil
type Method3Error = String :+: Int :+: Double :+: CNil

def method1 = Coproduct[Method1Error]("error 1")
def method2 = Coproduct[Method2Error]("error 2")
def method3 = Coproduct[Method3Error]("error 3")

// Wrapping in a new coproduct.
type StringErrors = Method1Error :+: Method2Error :+: Method3Error :+: CNil
val result1: String :+: Int :+: String :+: Double :+: String :+: Int :+: Double :+: CNil = Coproduct[StringErrors](method1).adjoined
val result2: String :+: Int :+: String :+: Double :+: String :+: Int :+: Double :+: CNil = Coproduct[StringErrors](method2).adjoined
val result3: String :+: Int :+: String :+: Double :+: String :+: Int :+: Double :+: CNil = Coproduct[StringErrors](method3).adjoined

// Embedding in an existing coproduct.
type StringError = String :+: Int :+: Double :+: CNil
val result4: String :+: Int :+: Double :+: CNil = method1.embed[StringError]
val result5: String :+: Int :+: Double :+: CNil = method2.embed[StringError]
val result6: String :+: Int :+: Double :+: CNil = method3.embed[StringError]

In the example above, you can see that there’s quite a difference between the two approaches.

Wrapping the result in a new coproduct creates a bigger coproduct:

String :+: Int :+: String :+: Double :+: String :+: Int :+: Double :+: CNil

Embedding flattens the coproduct and only returns the unique types:

String :+: Int :+: Double :+: CNil

Notice that the adjoined method is used to turn the type StringErrors into a flattened coproduct to demonstrate that there’s type duplication.

Iteration 4: Embedding coproducts

We’re only interested in a flattened representation of our domain errors for our app, so instead of wrapping coproducts, we’ll use the embed function.

import shapeless.ops.adjoin.Adjoin
import shapeless.{:+:, CNil, Coproduct, Poly1}

import java.io.IOException
import scala.io.StdIn.readLine
import scala.util.Try

object DivideAppIteration4 extends App {
  case object DivideByZeroError

  case class ParseNumberError(input: String)

  type TryDivideError = DivideByZeroError.type :+: CNil

  def tryDivide(x: Double, y: Double): Either[TryDivideError, Double] =
    if (y == 0) Left(Coproduct(DivideByZeroError))
    else Right(x / y)

  type TryReadLineError = IOException :+: CNil

  // Fold on Try will always give us a Throwable and is no longer an IOException.
  // For educational purposes I'm not going to bother doing anything about this and
  // I'll just wrap the exception into an IOException again.
  def tryReadLine = Try(readLine).fold[Either[TryReadLineError, String]](
    ex => Left(Coproduct(new IOException(ex))),
    Right.apply
  )

  type TryParseNumberError = ParseNumberError :+: CNil

  def tryParseDouble(s: String) =
    s.toDoubleOption.fold[Either[TryParseNumberError, Double]](
      Left(Coproduct(ParseNumberError(s)))
    )(Right.apply)

  // Flattens the types.
  val runDivideError = Adjoin[TryReadLineError :+: TryParseNumberError :+: TryDivideError]
  // Uses the resulting Out as our type signature.
  type RunDivideError = runDivideError.Out

  // We're now using the embed method instead.
  def runDivide: Either[RunDivideError, Double] = for {
    x0 <- tryReadLine.left.map(_.embed[RunDivideError])
    y0 <- tryReadLine.left.map(_.embed[RunDivideError])
    x <- tryParseDouble(x0).left.map(_.embed[RunDivideError])
    y <- tryParseDouble(y0).left.map(_.embed[RunDivideError])
    r <- tryDivide(x, y).left.map(_.embed[RunDivideError])
  } yield r

  // An error handler to demonstrate how we could deal with errors.
  object errorHandler extends Poly1 {
    implicit def ioException = at[IOException] { e =>
      println(s"An IOException occurred: ${e.getMessage}")
    }

    implicit def parseDoubleError = at[ParseNumberError] { e =>
      println(s"Cannot parse '${e.input}' as an integer")
    }

    implicit def divideByZeroError = at[DivideByZeroError.type] { _ =>
      println("Cannot divide by zero")
    }
  }

  runDivide.fold(_.fold(errorHandler), println)
}

There’s still a bit of noise in the code above. For a start, we have to widen the type for every method invocation. This doesn’t compose too well. Let’s see what happens when we try to read the line and parse the input as a new composition:

def runDivide: Either[RunDivideError, Int] = for {
  x <- tryReadLine
         .leftMap(_.embed[RunDivideError])
         .flatMap(tryParseInt(_).leftMap(_.embed[RunDivideError]))
  y <- tryReadLine
         .leftMap(_.embed[RunDivideError])
         .flatMap(tryParseInt(_).leftMap(_.embed[RunDivideError]))
  r <- tryDivide(x, y).leftMap(_.embed[RunDivideError])
} yield r

That doesn’t look too nice, to be honest. It’s not only cumbersome to widen our types by hand all the time, but it also introduces noise that makes it challenging to reason over our program.

Iteration 5: Reducing noise by introducing a syntax helper

How can we reduce the noise in the previous example? One way of solving this would be to let the methods already do the embedding themselves:

import DivideAppIteration5Syntax.EitherSyntax
import shapeless.ops.adjoin.Adjoin
import shapeless.ops.coproduct.Basis
import shapeless.{:+:, CNil, Coproduct, Poly1}

import java.io.IOException
import scala.io.StdIn.readLine
import scala.util.Try

object DivideAppIteration5Syntax {
  implicit class EitherSyntax[E <: Coproduct, B](either: Either[E, B]) {
    def leftMap[A1](f: E => A1): Either[A1, B] = either match {
      case Left(l) => Left(f(l))
      case _ => either.asInstanceOf[Either[A1, B]]
    }

    def leftEmbed[Super <: Coproduct](implicit basis: Basis[Super, E]): Either[Super, B] = 
      leftMap(_.embed)
  }
}

object DivideAppIteration5 extends App {
  case object DivideByZeroError
  case class ParseNumberError(input: String)

  type TryDivideError = DivideByZeroError.type :+: CNil
  def tryDivide[Super <: Coproduct](x: Double, y: Double)(implicit
    basis: Basis[Super, TryDivideError]
  ): Either[Super, Double] =
    if (y == 0) Left(Coproduct[TryDivideError](DivideByZeroError).embed[Super])
    else Right(x / y)

  type TryReadLineError = IOException :+: CNil
  def tryReadLine[Super <: Coproduct](implicit
    basis: Basis[Super, TryReadLineError]
  ): Either[Super, String] = 
    Try(readLine)
      .fold[Either[TryReadLineError, String]](
        ex => Left(Coproduct(new IOException(ex))),
        Right.apply
      )
      .leftEmbed[Super]

  type TryParseNumberError = ParseNumberError :+: CNil
  def tryParseNumber[Super <: Coproduct](
    s: String
  )(implicit basis: Basis[Super, TryParseNumberError]): Either[Super, Double] =
    s.toDoubleOption
     .fold[Either[TryParseNumberError, Double]](
       Left(Coproduct(ParseNumberError(s)))
     )(Right.apply)
     .leftEmbed[Super]

  val runDivideError = Adjoin[TryReadLineError :+: TryParseNumberError :+: TryDivideError]
  type RunDivideError = runDivideError.Out

  def runDivide: Either[RunDivideError, Double] = for {
    x <- tryReadLine[RunDivideError].flatMap(tryParseNumber[RunDivideError])
    y <- tryReadLine[RunDivideError].flatMap(tryParseNumber[RunDivideError])
    r <- tryDivide[RunDivideError](x, y)
  } yield r

  object errorHandler extends Poly1 {
    implicit def ioException = at[IOException] { e =>
      println(s"An IOException occurred: ${e.getMessage}")
    }
    implicit def parseNumberError = at[ParseNumberError] { e =>
      println(s"Cannot parse '${e.input}' as a number")
    }
    implicit def divideByZeroError = at[DivideByZeroError.type] { _ =>
      println("Cannot divide by zero")
    }
  }

  runDivide.fold(_.fold(errorHandler), println)
}

Even though this looks much better than previous versions, it would be great if we could eliminate the redundant RunDivideError that we have to pass to every single method when composing the methods.

Iteration 6: Reducing noise by moving the implicits

Can we reduce the noise even more? Yes, we can if we start moving the implicits around. We can do this rather simple by adding the implicits in the runDivide signature:

import DivideAppIteration6Syntax.EitherSyntax
import shapeless.ops.adjoin.Adjoin
import shapeless.ops.coproduct.Basis
import shapeless.{:+:, CNil, Coproduct, Poly1}

import java.io.IOException
import scala.io.StdIn.readLine
import scala.util.Try

object DivideAppIteration6Syntax {
  implicit class EitherSyntax[E <: Coproduct, B](either: Either[E, B]) {
    def leftMap[A1](f: E => A1): Either[A1, B] = either match {
      case Left(l) => Left(f(l))
     case _ => either.asInstanceOf[Either[A1, B]]
    }

    def leftEmbed[Super <: Coproduct](implicit basis: Basis[Super, E]): Either[Super, B] =
      leftMap(_.embed)
  }
}

object DivideAppIteration6 extends App {
  case object DivideByZeroError
  case class ParseNumberError(input: String)

  type TryDivideError = DivideByZeroError.type :+: CNil
  def tryDivide[Super <: Coproduct](x: Double, y: Double)(implicit
    basis: Basis[Super, TryDivideError]
  ): Either[Super, Double] =
    if (y == 0) Left(Coproduct[TryDivideError](DivideByZeroError).embed[Super])
    else Right(x / y)

  type TryReadLineError = IOException :+: CNil
  def tryReadLine[Super <: Coproduct](implicit
    basis: Basis[Super, TryReadLineError]
  ): Either[Super, String] = 
    Try(readLine)
      .fold[Either[TryReadLineError, String]](
        ex => Left(Coproduct(new IOException(ex))),
        Right.apply
      )
      .leftEmbed[Super]

  type TryParseNumberError = ParseNumberError :+: CNil
  def tryParseNumber[Super <: Coproduct](
    s: String
  )(implicit basis: Basis[Super, TryParseNumberError]): Either[Super, Double] =
    s.toDoubleOption
     .fold[Either[TryParseNumberError, Double]](
        Left(Coproduct(ParseNumberError(s)))
     )(Right.apply)
     .leftEmbed[Super]

  val runDivideError = Adjoin[TryReadLineError :+: TryParseNumberError :+: TryDivideError]
  type RunDivideError = runDivideError.Out

  def runDivide(implicit
    b1: Basis[RunDivideError, TryReadLineError],
    b2: Basis[RunDivideError, TryParseNumberError],
    b3: Basis[RunDivideError, TryDivideError]
  ): Either[RunDivideError, Double] =
    for {
      x <- tryReadLine.flatMap(tryParseNumber(_))
      y <- tryReadLine.flatMap(tryParseNumber(_))
      r <- tryDivide(x, y)
    } yield r

  object errorHandler extends Poly1 {
    implicit def ioException = at[IOException] { e =>
      println(s"An IOException occurred: ${e.getMessage}")
    }
    implicit def parseNumberError = at[ParseNumberError] { e =>
      println(s"Cannot parse '${e.input}' as a number")
    }
    implicit def divideByZeroError = at[DivideByZeroError.type] { _ =>
      println("Cannot divide by zero")
    }
  }

  runDivide.fold(_.fold(errorHandler), println)
}

Unfortunately, we have to write tryParseNumber(_) for the type inference to work, and we cannot simply pass tryParseNumber as a function.

Iteration 7: Turning it into a REST API

The beauty of a functional program is that we can describe what our program should do, independent of our technology stack. In this last iteration, you’ll see how quickly we can turn our command-line app into a simple REST API, without much effort. We’ll use the Akka HTTP hello-world example as our base, but you can use any framework.

import DivideAppIteration6Syntax.EitherSyntax
import akka.actor.typed.ActorSystem
import akka.actor.typed.scaladsl.Behaviors
import akka.http.scaladsl.Http
import akka.http.scaladsl.model.StatusCodes.{BadRequest, InternalServerError, OK}
import akka.http.scaladsl.model._
import akka.http.scaladsl.server.Directives._
import shapeless.ops.adjoin.Adjoin
import shapeless.ops.coproduct.Basis
import shapeless.{:+:, CNil, Coproduct, Poly1}

import scala.io.StdIn

object DivideAppIteration7Syntax {
  implicit class EitherSyntax[E <: Coproduct, B](either: Either[E, B]) {
    def leftMap[A1](f: E => A1): Either[A1, B] = either match {
      case Left(l) => Left(f(l))
      case _ => either.asInstanceOf[Either[A1, B]]
    }

    def leftEmbed[Super <: Coproduct](implicit basis: Basis[Super, E]): Either[Super, B] =
      leftMap(_.embed)
    }
}

object DivideAppIteration7WebApp {
  case object DivideByZeroError
  case class ParseNumberError(input: String)

  type TryDivideError = DivideByZeroError.type :+: CNil
  def tryDivide[Super <: Coproduct](x: Double, y: Double)(implicit
    basis: Basis[Super, TryDivideError]
  ): Either[Super, Double] =
    if (y == 0) Left(Coproduct[TryDivideError](DivideByZeroError).embed[Super])
    else Right(x / y)

  type TryParseNumberError = ParseNumberError :+: CNil
  def tryParseNumber[Super <: Coproduct](
    s: String
  )(implicit basis: Basis[Super, TryParseNumberError]): Either[Super, Double] =
    s.toDoubleOption
     .fold[Either[TryParseNumberError, Double]](
       Left(Coproduct(ParseNumberError(s)))
     )(Right.apply)
     .leftEmbed[Super]

  val runDivideError = Adjoin[TryParseNumberError :+: TryDivideError]
  type RunDivideError = runDivideError.Out

  def runDivide(x: String, y: String)(implicit
    b1: Basis[RunDivideError, TryParseNumberError],
    b2: Basis[RunDivideError, TryDivideError]
  ): Either[RunDivideError, Double] =
    for {
      a <- tryParseNumber(x)
      b <- tryParseNumber(y)
      r <- tryDivide(a, b)
    } yield r

  object divideEndpointErrorHandler extends Poly1 {
    implicit def parseNumberError = at[ParseNumberError] { e =>
      complete(HttpResponse(BadRequest, entity = "Invalid number specified"))
    }
    implicit def divideByZeroError = at[DivideByZeroError.type] { _ =>
      complete(HttpResponse(InternalServerError, entity = "Cannot divide by zero"))
    }
  }

  def divideEndpointSuccessHandler = (d: Double) => complete(HttpResponse(OK, entity = d.toString))

  def main(args: Array[String]): Unit = {
    implicit val system = ActorSystem(Behaviors.empty, "my-system")
    // needed for the future flatMap/onComplete in the end
    implicit val executionContext = system.executionContext

    val tryDivideEnpointError = Adjoin[TryParseNumberError :+: TryDivideError]
    type TryDivideEndpointError = tryDivideEnpointError.Out
    val divideRoute =
      path("divide") {
        get {
          // Normally you would leverage Akka's built-in functionality to parse strings.
          // As I would not like to diverge from our existing application, I decided to
          // keep doing the parsing our selves, and use the divideEndpointErrorHandler
          // to convert our errors to HTTP responses.
          parameters("x", "y").apply { case (x, y) =>
          runDivide(x, y).fold(_.fold(divideEndpointErrorHandler), divideEndpointSuccessHandler)
        }
      }
    }

  val bindingFuture = Http().newServerAt("localhost", 8080).bind(divideRoute)

  println(
    s"Server now online. Please navigate to http://localhost:8080/divide\nPress RETURN to stop..."
  )
  StdIn.readLine() // Let it run until user presses return
  bindingFuture
    .flatMap(_.unbind()) // Trigger unbinding from the port
    .onComplete(_ => system.terminate()) // Shutdown when done
  }
}

Conclusion

We have looked at Shapeless coproducts and saw that it is a union type (e.g. it can return more than a single type). This can be handy when a method can return more than a single error. In this article, we’ve created a simple command-line application and went through quite a few iterations of improvements. With little to no change, we saw how easy it is to move the code from our command-line application to a REST API due to functional composition.

The great question remains: Should I use Shapeless coproducts in my codebase?

The answer to that is: It depends

  • Suppose I was still on Scala 2.x. In that case, I’d try to get the codebase to Scala 3.0. This migration should be quite straightforward if you are on 2.13.8 (keep in mind that the most effortless migration is to 3.0 instead of a later 3.x release). Using native union types in Scala 3.x is a better solution as it doesn’t pollute the code in such an unfortunate way. I’ll do a follow-up soon with the same code in Scala 3.x, and you’ll see what a breeze it is to use.
  • If you’re still bound to Scala 2, using Shapeless could be a great way to create a type-safe error channel.

Whether having a type-safe error channel (i.e. “effects tracking”) is good or bad is heavily debated:

I’m still not entirely sure where I stand here. I think that making errors explicit just to make them explicit is not a good practice. However, I see value in making explicit errors that need to be accounted for upstream (i.e. by the callee or even higher up in the chain). As in many cases, whether it makes sense depends on what you try to do.

Questions?

Get in touch with us to learn more about the subject and related solutions

Explore related posts