Ever wondered why sum types are called sum types? Or maybe you’ve always wondered why the <*> operator uses exactly these symbols? And what do these things have to do with Semirings? Read this article and find out!

We all know and use Monoids and Semigroups. They’re super useful and come with properties that we can directly utilize to gain a higher level of abstractions at very little cost. Sometimes, however, certain types can have multiple Monoid or Semigroup instances. An easy example are the various numeric types where both multiplication and addition form two completely lawful monoid instances.

In abstract algebra there is a an algebraic class for types with two Monoid instances that interact in a certain way. These are called Semirings (sometimes also Rig) and they are defined as two Monoids with some special laws that define the interactions between them. Because they are often used to describe numeric data types we usually classify them as Additive and Multiplicative. Just like with numeric types the laws of Semiring state that multiplication has to distribute over addition and multiplying a value with the additive identity (i.e. zero) absorbs the value and becomes zero.

There are different ways to encode this as type classes and different libraries handle this differently, but let’s look at how the Scala library algebra handles this. Specifically, it defines a separate AdditiveSemigroup and MultiplicativeSemigroup and goes from there.


class AdditiveSemigroup a where
  (+) :: a -> a -> a

class AdditiveMonoid a where
  zero :: a

class MultiplicativeSemigroup a where
  (*) :: a -> a -> a

class MultiplicativeMonoid a where
  one :: a

A Semiring is then just an AdditiveMonoid coupled with a MultiplicativeMonoid with the following extra laws:

  1. Additive commutativity, i.e. x + y === y + x
  2. Right distributivity, i.e. (x + y) * z === (x * z) + (y * z)
  3. Left distributivity, i.e. x * (y + z) === (x * y) + (x * z)
  4. Right absorption, i.e. x * zero === zero
  5. Left absorption, i.e. zero * x === zero

To define it as a type class, we simply extend from both additive and multiplicative monoid:

class (MultiplicativeMonoid a, AdditiveMonoid a) => Semiring a

Now we have a Semiring class, that we can use with the various numeric types like Int, Number, BigInt etc, but what else is a Semiring and why dedicate a whole blog post to it?

It turns out a lot of interesting things can be Semirings, including Booleans, Sets and animations.

One very interesting thing I’d like to point out is that we can form a Semiring homomorphism from types to their number of possible inhabitants. What the hell is that? Well, bear with me for a while and I’ll try to explain step by step.

Cardinality

Okay, so let’s start with what I mean by cardinality. Every type has a specific number of values it can possibly have, e.g. a Boolean has cardinality of 2, because it has two possible values: true and false.

So Boolean has two, how many do other primitive types have? Int has 2^32 and Number has 2^64. So far so good, that makes sense, what about something like String? String is an unbounded type and therefore theoretically has infinite number of different inhabitants (practically of course, we don’t have infinite memory, so the actual number may vary depending on your system).

For what other types can we determine their cardinality? Well a couple of easy ones are Unit, which has exactly one value it can take and also Void, which is the “bottom” type in Haskell, which means it has 0 possible values. I.e you can never instantiate a value of Void, which gives it a cardinality of 0.

That’s neat, maybe we can encode this in actual code. We could create a type class that should be able to give us the number of inhabitants for any type we give it. Since we lack dependent types we can’t give a type as an input to a function, so instead we just pass a value of a to the function:

class Cardinality a where
  cardinality :: a -> BigInt

Awesome! Now let’s try to define some instances for this type class. We don’t actually need the value passed to cardinality so we’ll just ignore it:

instance booleanCardinality :: Cardinality Boolean where
  cardinality _ = BigInt.fromInt 2

instance intCardinality :: Cardinality Int where
  cardinality _ = pow (BigInt.fromInt 2) (BigInt.fromInt 32)

instance numberCardinality :: Cardinality Number where
  cardinality _ = pow (BigInt.fromInt 2) (BigInt.fromInt 64)

instance unitCardinality :: Cardinality Unit where 
  cardinality _ = BigInt.fromInt 1

instance voidCardinality :: Cardinality Void where
  cardinality _ = BigInt.fromInt 0

Alright, this is cool, let’s try it out in the REPL! To do so, we’ll use undefined, which can be any type at all and annotate it using the type we want.

> cardinality (undefined :: Int)
4294967296

> cardinality (undefined :: Unit)
1

> cardinality (undefined :: Number)
18446744073709551616

Cool, but this is all very simple, what about things like ADTs? Can we encode them in this way as well? Turns out, we can, we just have to figure out how to handle the basic product and sum types. To do so, let’s look at an example of both types. First, we’ll look at a simple product type: (Boolean, Int8).

How many inhabitants does this type have? Well, we know Boolean has 2 and Int8 has 256. So we have the numbers from -127 to 128 once with true and once again with false. That gives us 512 unique instances. Hmmm….

512 seems to be double 256, so maybe the simple solution is to just multiply the number of inhabitants of the first type with the number of inhabitants of the second type. If you try this with other examples, you’ll see that it’s exactly true, awesome! Let’s encode that fact in a type class instance:

instance tupleCardinality :: (Cardinality a, Cardinality b) => Cardinality (a, b) where
  cardinality _ = cardinality (undefined :: a) * cardinality (undefined :: b)

Great, now let’s look at an example of a simple sum type: Either[Boolean, Int8]. Here the answer seems even more straight forward, since a value of this type can either be one or the other, we should just be able to add the number of inhabitants of one side with the number of inhabitants of the other side. So Either[Boolean, Int8] should have 2 + 256 = 258 number of inhabitants. Cool!

Let’s also code that up and try and confirm what we learned in the REPL:

instance eitherCardinality :: (Cardinality a, Cardinality b) => Cardinality (Either a b) where
  cardinality _ = cardinality (undefined :: a) + cardinality (undefined :: b)
> cardinality (undefined :: (Boolean, Int8))
512

> cardinality (undefined :: (Either Boolean Int8))
258

> cardinality (undefined :: (Either Int (Boolean, Unit)))
4294967298

So using sum types seem to add the number of inhabitants whereas product types seem to multiply the number of inhabitants. That makes a lot of sense given their names!

So what about that homomorphism we talked about earlier? Well, a homomorphism is a structure-preserving mapping function between two algebraic structures of the same sort (in this case a semiring).

This means that for any two values x and y and the homomorphism f, we get

  1. f(x * y) === f(x) * f(y)
  2. f(x + y) === f(x) + f(y)

Now this might seem fairly abstract, but it applies exactly to what we just did. If we “add” two types of Int8 and Boolean, we get an Either Int8 Boolean and if we apply the homomorphism function, cardinality to it, we get the value 258. This is the same as first calling cardinality on Int8 and then adding that to the result of calling cardinality on Boolean.

And of course the same applies to multiplication and product types. However, we’re still missing something from a valid semiring, we only talked about multiplication and addition, but not about their respective identities.

What we did see, though is that Unit has exactly one inhabitant and Void has exactly zero. So maybe we can use these two types to get a fully formed Semiring?

Let’s try it out! If Unit is one then a product type of any type with Unit should be equivalent to just the first type.

Turns out, it is, we can easily go from something like (Int, Unit) to Int and back without losing anything and the number of inhabitants also stay exactly the same.

> cardinality (undefined :: Int)
4294967296

> cardinality (undefined :: (Unit, Int))
4294967296

> cardinality (undefined :: (Unit, (Unit, Int)))
4294967296

Okay, not bad, but how about Void? Given that it is the identity for addition, any type summed with Void should be equivalent to that type. Is Either Void a equivalent to a? It is! Since Void doesn’t have any values an Either Void a can only be a Right and therefore only an a, so these are in fact equivalent types.

We also have to check for the absorption law that says that any value mutliplied with the additive identity zero should be equivalent to zero. Since Void is our zero a product type like (Int, Void) should be equivalent to Void. This also holds, given the fact that we can’t construct a Void so we can never construct a tuple that expects a value of type Void either.

Let’s see if this translates to the number of possible inhabitants as well:

Additive Identity:

> cardinality (undefined :: (Either Void Boolean))
2

> cardinality (undefined :: (Either Void (Int8, Boolean)))
258

Absorption:

> cardinality (undefined :: (Void, Boolean))
0

> cardinality (undefined :: (Void, Number))
0

Nice! The only thing left now is distributivity. In type form this means that (a, (Either b c)) should be equal to Either (a, b), (a, c). If we think about it, these two types should also be exactly equivalent, woohoo!

> cardinality (undefined :: (Boolean, (Either Int8 Int16))
131584

> cardinality (undefined :: (Either (Boolean, Int8), (Boolean, Int16)))
131584

Higher kinded algebraic structures

Some of you might have heard of the Semigroupal or Apply type class. But why is it called that, and what is its relation to a Semigroup? Let’s find out!

First, let’s have a look at Semigroupal:

class Semigroupal f where
  product :: forall a b. f a -> f b -> f (a, b)

It seems to bear some similarity to Semigroup, we have two values which we somehow combine, and it also shares Semigroups associativity requirement.

So far so good, but the name product seems a bit weird. It makes sense given we combine the A and the B in a tuple, which is a product type, but if we’re using products, maybe this isn’t a generic Semigroupal but actually a multiplicative one? Let’s fix this and rename it!

class MultiplicativeSemigroupal f where
  product :: forall a b. f a -> f b -> f (a, b)

Next, let us have a look at what an additive Semigroupal might look like. Surely, the only thing we’d have to change is going from a product type to a sum type:

class AdditiveSemigroupal f where
  sum :: forall a b. f a -> f b -> f (Either a b)

Pretty interesting so far, can we top this and add identities to make Monoidals? Surely we can! For addition this should again be Void and Unit for multiplication:

class (AdditiveSemigroupal f) => AdditiveMonoidal f where
  void :: f Void

class (MultiplicativeSemigroupal f) => MultiplicativeMonoidal f where
  unit :: f Unit

So now we have these fancy type classes, but how are they actually useful? Well, I’m going to make the claim that these type classes already exist in most preludes today, just under different names.

Let’s first look at the AdditiveMonoidal. It is defined by two methods, void which returns an f Void and sum which takes an f a and an f b to create an f (Either a b).

What type class in the Prelude could be similar? First, we’ll look at the sum function and try to find a counterpart for AdditiveSemigroupal. Since we gave the lower kinded versions of these type classes symbolic operators, why don’t we do the same thing for AdditiveSemigroupal?

Since it is additive it should probably contain a + somewhere and it should also show that it’s inside some type constructor.

(<+>) :: forall f a b. f a -> f b -> f (Either a b)

Oh! The <+> function already exists in some libraries as an alias for alt which can be found on Alt, but it’s sort of different, it takes two f as and returns an f a, not quite what we have here.

Or is it? These two functions are actually the same, and we can define them in terms of one another as long as we have a functor:

sum :: forall f a b. f a -> f b -> f (Either a b)

alt :: forall f a. (Functor f) => f a -> f a -> f a
alt x y =
  let feitheraa = sum x y
  in map merge feitheraa

So our AdditiveSemigroupal is equivalent to Alt, so probably AdditiveMonoidal is equivalent to Plus, right?

Indeed, and we can show that quite easily.

Plus adds an empty function with the following definition:

empty :: forall a. f a

This function uses a universal quantifier for a, which means that it works for any a, which then means that it cannot actually include any particular a and is therefore equivalent to f Void which is what we have for AdditiveMonoidal.

Excellent, so we found counterparts for the additive type classes, and we’ve already talked about MultiplicativeSemigroupal. So the only thing left to find out is the counterpart of MultiplicativeMonoidal.

I’m going to spoil the fun and make the claim that Applicative is that counterpart. Applicative adds pure, which takes an a and returns an f a. MultiplicativeMonoidal adds unit, which takes no parameters and returns an f Unit. So how can we go from one to another? Well the answer is again using a functor:

unit :: f Unit

pure :: forall a. a => f a
pure a = imap (const a) (const ()) unit

Applicative uses a covariant functor, but in general we could use invariant and contravariant structures as well. Applicative also uses <*> as an alias for using product together with map, which seems like further evidence that our intuition that its a multiplicative type class is correct.

So in the larger ecosystem right now we have <+> and <*>, is there also a type class that combines both similar to how Semiring combines + and *?

There is, it is called Alternative, it extends Applicative and Plus and if we were super consistent we’d call it a Semiringal:

class (MultiplicativeMonoidal f, AdditiveMonoidal f) => Semiringal f

Excellent, now we’ve got both Semiring and a higher kinded version of it.

If it were available, we could derive a Semiring for any Alternative the same we can derive a Monoid for any Plus or Applicative. We could also lift any Semiring back into Alternative, by using Const, just like we can lift Monoids into Applicative using Const.

To end this blog post, we’ll have a very quick look on how to do that.


instance constSemiringal :: Semiring a => Semiringal (Const a) where
  sum fb fc =
    Const ((unwrap fb) + (unwrap fc))

  product fb fc =
    Const ((unwrap fb) * (unwrap fc))

  unit = Const one

  void = Const zero

Conclusion

Rings and Semirings are very interesting algebraic structures and even if we didn’t know about them we’ve probably been using them for quite some time. This blog post aimed to show how Applicative and Plus relate to Monoid and how algebraic data types form a semiring and how these algebraic structures are pervasive throughout Haskell and other functional programming languages. For me personally, realizing how all of this ties together and form some really satisfying symmetry was really mind blowing and I hope this blog post can give some good insight on recognizing these interesting similarities throughout the prelude and other libraries based on different mathematical abstractions. For further material on this topic, you can check out this talk.

Addendum

This article glossed over commutativity in the type class encodings. Commutativity is very important law for semrings and the code should show that. However, since this post already contained a lot of different type class definitions, adding extra commutative type class definitions that do nothing but add laws felt like it would distract from what is trying to be taught.

Moreover I focused on the cardinality of only the types we need, but for completions sake, we could also add instances of Cardinality for things like A -> B , Maybe a or These a b. These are:

  cardinality (undefined :: (a -> b)) === 
    pow (cardinality (undefined :: B)) (cardinality (undefined :: a))

  cardinality (undefined :: (Maybe a)) ===
    cardinality (undefined :: a) + 1

  cardinality (undefined :: (These a b)) ===
    (cardinality (undefined :: a)) + (cardinality (undefined :: b)) + (cardinality (undefined :: a)) * (cardinality (undefined :: b))

MonadError is a very old type class, hackage shows me it was originally added in 2001, long before I had ever begun doing functional programming, just check the hackage page. In this blog post I’d like to rethink the way we use MonadError today. It’s usually used to signal that a type might be capable of error handling and is basically like a type class encoding of Eithers ability to short circuit. That makes it pretty useful for building computations from sequences of values that may fail and then halt the computation or to catch those errors in order to resume the computation. It’s also parametrized by its error type, making it one of the most common example of multi-parameter type classes. Some very common instances include Either and IO, but there are a ton more.

We can divide instances into 3 loosely defined groups:

First we have simple data types like Either, Maybe or These (with Validat not having a Monad instance).

Secondly we’ve got IO or Aff in PureScript and similar types. These are used to suspend side effects which might have errors and therefore need to be able to handle these.

Thirdly and least importantly, we have monad transformers, which get their instances from their respective underlying monads. Since they basically just propagate their underlying instances we’re only going to talk about the first two groups for now.

The simple data types all define MonadError instances, but I wager they’re not actually used as much. This is because MonadError doesn’t actually allow us to deconstruct e.g. an Either to actually handle the errors. We’ll see more on that later, next let’s look at the IO-like types and their instances.

IO currently defines a MonadError IOException IO, in PureScript we have MonadError Error (Aff eff). This means that they’re fully able to raise and catch errors that might be thrown during evaluation of encapsulated side effects. Using MonadError with these effect types seems a lot more sensical at first, as you can’t escape IO even when you handle errors, so it looks like it makes sense to stay within IO due to the side effect capture.

The problem I see with MonadError is that it does not address the fundamental difference between these two types of instances. I can pattern match an Maybe a with a default value to get back an a. With IO that is just not possible. So these two groups of types are pretty different, when does it actually make sense to abstract over both of them? Well, it turns out there a few instances where it might be useful, but as we’ll see later, I’m proposing something that will be equally useful to both groups.

Now before we continue, let’s look at the MonadError type class in a bit more detail. MonadError currently comprises two parts, throwing and catching errors. To begin let’s have a look at the throw part, sometimes also called MonadThrow:

class (Monad m) => MonadError e m | m -> e where
  throwError :: e -> m a

This looks fine for now, but one thing that strikes me is that the m type seems to “swallow” errors. If we look at m a we have no clue that it might actually yield an error of type e, that fact is not required to be represented at all. However, that’s not a really big issue, so now let’s look at the catch part:

class (Monad m) => MonadError e m | m -> e where
  ...
  catchError :: m a -> (e -> m a) -> m a

Immediately I have a few questions, if the errors are handled, why does it return the exact same type? Furthermore if this is really supposed to handle errors, what happens if I have errors in the e -> m a function? This is even more blatant in the try function:

try :: forall m e a. MonadError e m => m a -> m (Either e a)

Here there is no way the outer m still has any errors, so why does it have the same type? Shouldn’t we represent the fact that we handled all the errors in the type system? This means you can’t actually observe that the errors are now inside Either. That leads to this being fully legal code:

try (try (try (try (Just 42))))

Another example that demonstrates this is the fact that calling handleError, which looks like this:

handleError :: forall m e a. MonadError e m => m a -> (e -> a) -> m a

also returns an m a. This method takes a pure function e -> a and thus can not fail during recovery like catchError, yet it still doesn’t give us any sign that it doesn’t throw errors. For IO-like types this is somewhat excusable as something like an unexceptional IO is still very uncommon, but for simple data types like Either or Maybe that function should just return an A, since that’s the only thing it can be. Just like with attempt, we can infinitely chain calls to handleError, as it will never change the type.

Ideally our type system should stop us from being able to write this nonsensical code and give us a way to show anyone reading the code that we’ve already handled errors. Now I’m not saying that the functions on MonadError aren’t useful, but only that they could be more constrained and thus more accurate in their representation.

For this purpose let’s try to write a different MonadError type class, one that’s designed to leverage the type system to show when values are error-free, we’ll call it MonadBlunder for now.

To mitigate the problems with MonadError we have a few options, the first one I’d like to present is using two different type constructors to represent types that might fail and types that are guaranteed not to. So instead of only a single type constructor our MonadBlunder class will have two:

class MonadBlunder f g e where

Our type class now has the shape (* -> *) -> (* -> *) -> * -> *, which is quite a handful, but I believe we can justify its usefulness. The first type parameter f will represent our error-handling type, which will be able to yield values of type e. The second type parameter g will represent a corresponding type that does not allow any errors and can therefore guarantee that computations of the form g a will always yield a value of type a.

Now that we figured out the shape, let’s see what we can actually do with it. For throwing errors, we’ll create a throwError function that should return a value inside f, as it will obviously be able to yield an error.

class MonadBlunder f g e where
  throwError :: forall a. e -> f a

This definition looks identical to the one defined one MonadError so let’s move on to error-handling. For handled errors, we want to return a value inside g, so our catchError function should indeed return a g a:

class MonadBlunder f g e where
  ...

  catchError :: forall a. f a -> (e -> f a) -> g a
}

Looks good so far, right? Well, we still have the problem that the function e -> f a might return an erronous value, so if we want to guarantee that the result won’t have any errors, we’ll have to change that to g a as well:

class MonadBlunder f g e where
  ...

  catchError :: forall a. f a -> (e -> g a) -> g a
}

And now we’re off to a pretty good start, we fixed one short coming of MonadError with this approach.

Another approach, maybe more obvious to some, might be to require the type constructor to take two arguments, one for the value and one for the error type. Let’s see if we can define throwError on top of it:

class MonadBlunder b where
  throwError :: forall e a. e -> b e a
  ...
}

This looks pretty similar to what we already have, though now we have the guarantee that our type doesn’t actually “hide” the error-type somewhere. Next up is catchError. Ideally after we handled the error we should again get back a type that signals that it doesn’t have any errors. We can do exactly that by choosing an unhabited type like Void as our error-type:

class MonadBlunder b where
  ...

  catchError :: forall e a. b e a -> (e -> b Void a) -> b Void a
}

And this approach works as well, however now we’ve forced the two type parameter shape onto implementors. This MonadBlunder has the following kind (* -> * -> *) -> *. This means we can very easily define instances for types with two type parameters like Either. However, one issue might be that it’s much easier to fit a type with two type parameters onto a type class that expects a single type constructor (* -> *) than to do it the other way around.

For example try to implement the above MonadBlunder for the standard IO. It’s not going to be simple, whereas with the first encoding we can easily encode both Either and IO. For this reason, I will continue this article with the first encoding using the two different type constructors.

Next we’re going to look at laws we can define to make sense of the behaviour we want. The first two laws should be fairly obvious. If we bind over a value created by throwError it shouldn’t propogate:

throwError e >>= f === throwError e

Next we’re going to formulate a law that states, that raising an error and then immediatly handling it with a given function should be equivalent to just calling that function on the error value:

throwError e `catchError` f === f e

Another law could state that handling errors for a pure value lifted into the F context does nothing and is equal to the pure value in the G context:

pure a `catchError` f === pure a

Those should be good for now, but we’ll be able to find more when we add more derived functions to our type class. Also note that none of the laws are set in stone, these are just the ones I came up with for now, it’s completely possible that we’ll need to revise these in the future.

Now let’s focus on adding extra functions to our type class. MonadError offer us a bunch of derived methods that can be really useful. For most of those however we need access to methods like bind for both f and g, so before we figure out derived combinators, let’s revisit how exactly we define the type class.

The easiest would be to give both f and g a Monad constraint and move on. But then we’d have two type classes that both define a throwError function extends Monad, and we wouldn’t be able to use them together, since that would cause ambiguities and as I’ve said before, the functions on MonadError are useful in some cases.

Instead, since I don’t really like duplication and the fact that we’re not going to deprecate MonadError overnight, I decided to extend MonadBlunder from MonadError for the F type, to get access to the throwError function. If throwError and catchError were instead separated into separate type classes (as is currently the case in the PureScript prelude), we could extend only the throwError part. This also allows us to define laws that our counterparts of functions like try and ensure are consistent with the ones defined on MonadError. So the type signature now looks like this:

class (MonadError f e, Monad g) => MonadBlunder f g e | f -> e, f -> g where
  ...

Now since this means that any instance of MonadBlunder will also have an instance of MonadError on f, we might want to rename the functions we’ve got so far. Here’s a complete definition of what we’ve come up with with throwError removed and catchError renamed to catchBlunder:

class (MonadError f e, Monad g) => MonadBlunder f g e | f -> e, f -> g where
  catchBlunder :: forall a. f a -> (e -> g a) -> g a

Now let us go back to defining more derived functions for MonadBlunder. The easiest probably being handleError, so let’s see if we can come up with a good alternative:

handleBlunder :: forall f g e a. MonadBlunder f g e => f a -> (e -> a) -> g a
handleBlunder fa f = catchBlunder fa (pure . f) 

This one is almost exactly like catchBlunder, but takes a function from e to a instead of to g a. We can easily reuse catchBlunder by using pure to go back to e -> g a.

Next another function that’s really useful is try. Our alternative, let’s call it endeavor for now, should return a value in g instead, which doesn’t have a MonadError instance and therefore can not make any additional calls to endeavor:

endeavor :: forall f g e a. MonadBlunder f g e => f a -> g (Either e a)
endeavor fa =
  handleBlunder (map Right fa) Left
}

The implementation is fairly straightforward as well, we just handle all the errors my lifting them into the left side of an Either and map successful values to the right side of Either.

Next, let’s look at the dual to try, sometimes called absolve or rethrow. For MonadError it turns an f (Either e a) back into an f, but we’re going to use our unexceptional type again:

absolve :: forall f g e a. MonadBlunder f g e => g (Either e a) -> f a

But looking at this signature, we quickly realize that we need a way to get back to f a from g a. So we’re going to add another function to our minimal definition:

class (MonadError f e, Monad g) => MonadBlunder f g e | f -> e, f -> g, g -> f where
  catchBlunder :: forall a. f a -> (e -> g a) -> g a
  accept :: g ~> f

This function accept, allows us to lift any value without errors into a context where errors might be present.

We can now formulate a law that values in g never stop propagating, so bind should always work, we do this by specifying that calling handleBlunder after calling accept on any g a, is never going to actually change the value:

(accept ga) `handleBlunder` f === ga

Now we can go back to implementing the absolve function:

absolve :: forall f g e a. MonadBlunder f g e => g (Either e a) -> f a
absolve gea = accept gea >>= (either throwError pure)

Now that we’ve got the equivalent of both try and rethrow, let’s add a law that states that the two should cancel each other out:

absolve (endeavor fa) === fa

We can also add laws so that handleBlunder and endeavor are consistent with their counterparts now that we have accept:

accept (fa `handleBlunder` f) === fa `handleError` f


accept (endeavor fa) === try fa

One nice thing about try, is that it’s really easy to add a derivative combinator that doesn’t go to f e a, but to the isomorphic monad transformer ExceptT f e a. We can do the exact same thing with endeavor:

endeavorT :: forall f g e a. MonadBlunder f g e => f a -> ExceptT g e a
endeavorT fa = ExceptT (endeavor fa)

One last combinator I’d like to “port” from MonadError is the ensure function. ensure turns a successful value into an error if it does not satisfy a given predicate. We’re going to name the counterpart assure:

assure :: forall f g e a. MonadBlunder f g e => g a -> (a -> e) -> (a -> Bool) -> f a
assure ga error predicate =
  accept ga >>= (\a -> 
    if predicate a then pure a else throwError (error a))

This plays nicely with the rest of our combinators and we can again add a law that dictates it must be consistent with ensure:

ensure (accept ga) error predicate === assure ga error predicate

Now we have a great base to work with with laws that should guarantee principled and sensible behaviour. Next we’ll actually start defining some instances for our type class.

The easiest definitions are for Either and Maybe, though I’m not going to cover both, as the instances for Option can simply be derived by Either Unit aand I’m going to link to the code at the end. For Either e a, when we handle all errors of type e, all we end up with is a, so the corresponding g type for our instance should be Identity. That leaves us with the following definition:

instance MonadBlunder (Either e) Identity e where
  catchBlunder :: forall a. Either e a -> (e -> Identity a) -> Identity a
  catchBlunder fa f = case fa of
    Left e -> f e
    Right a -> Identity a

  accept :: Identity ~> Either e
  accept = Right . runIdentity

Fairly straightforward, as Identity a is just a, but with this instance we can already see a small part of the power we gain over MonadError. When we handle errors with handleBlunder, we’re no longer “stuck” inside the Either Monad, but instead have a guarantee that our value is free of errors. Sometimes it’ll make sense to stay inside Either, but we can easily get back into Either, so we have full control over what we want to do.

Next up, we’ll look at IO and the type that inspired this whole blog post UIO. UIO is equivalent to an IO type where all errors are handled and is short for “unexceptional IO”. This would also work for IO types who use two type parameters IO e a where the first represents the error type and the second the actual value. There you’d choose IO e a as the f type and IO Void a as the g type. IO Void a there is equivalent to UIO a.

As one might expect, you can not simply go from IO a to UIO a, but we’ll need to go from IO a to UIO (Either e a) instead, which if you look at it, is exactly the definition of endeavor. Now let’s have a look at how the MonadBlunder instance for IO and UIO looks:

instance MonadBlunder IO UIO IOException where
  catchBlunder :: forall a. IO a -> (e -> a) -> UIO a
  catchBlunder fa f =
    unsafeFromIO (fa `catchError` (accept . f))

  accept :: UIO ~> IO
  accept = runUIO

And voila! We’ve got a fully working implementation that will allow us to switch between these two types whenever we have a guarantee that all errors are handled. This makes a lot of things much simpler. For example, if one wants to use bracket with UIO, you just need to bind to the finalizer, as bind is always guaranteed to not short-circuit.

We can also define instances for ExceptT and MaybeT (being isomorphic to ExceptT f Unit a), where the corresponding unexceptional type is just the outer f, so endeavor is just a call to run:

instance MonadBlunder (ExceptT e f) f e where
  catchBlunder :: forall a. ExceptT e f a -> (e -> f a) -> f a
  catchBlunder efa f =
    runExceptT efa >>= (\eea -> case eea of
      Left e -> f e
      Right a -> pure a
    )

  accept :: f ~> ExceptT f e
  accept = lift

Finally, it’s also possible to create instances for other standard monad transformers like WriterT, ReaderT or StateT as long as their underlying monads themselves have instances for MonadBlunder, as is typical in mtl. As their implementations are very similar we’ll only show the StateT transformer instance:

instance (MonadBlunder f g e) => MonadBlunder (StateT s f) (StateT s g) e where
  catchBlunder :: forall a. StateT s f a -> (e -> StateT s g a) -> StateT s g a
  catchBlunder sfa f =
    StateT (\s -> runStateT sfa s `catchBlunder` ((runStateT s) . f))

  accept :: StateT s g ~> StateT s f
  accept = mapStateT accept 

In practice this means we can call catchBlunder on things like StateT s IO a and get back a StateT s UIO a. Pretty neat!

Conclusion

In this article, I’ve tried to present the argument that MonadError is insufficient for principled error handling. We also tried to build a solution that deals with the shortcomings described earlier. Thereby it seeks not to replace, but to expand on MonadError to get a great variety of error handling capabilities. I believe the MonadBlunder type class, or whatever it will be renamed to, has the potential to be a great addition to the functional community at large.

You can find the full code here.

Note again, that none of this is final or set in stone and before it arrives anywhere might still change a lot, especially in regards to naming (which I’m not really happy with at the moment), so if you have any feedback of any sorts, please do chime in! Would love to hear your thoughts and thank you for reading this far!

The following is a blog post written for PureScript, but should be able to work with Haskell with only very few modifications.

The Tagless Final encoding has gained some steam recently, with some people hailing 2017 as the year of Tagless Final. Being conceptually similar to the Free Monad, different comparisons have been brought up and the one trade-off that always comes up is the lack or the difficulty of inspection of tagless final programs and in fact, I couldn’t find a single example on the web. This seems to make sense, as programs in the tagless final encoding aren’t values, like programs expressed in terms of free structures. However, in this blog post, I’d like to dispell the myth that inspecting and optimizing tagless final programs is more difficult than using Free.

To start with, this blog post is gonna use a different tagless final encoding not based on type classes, but records instead. This allows us to treat interpreters as values. This technique is described here.

Without further ado, let’s get into it, starting with our example algebra, a very simple key-value store:

newtype KVStore f = KVStore 
  { put :: String -> String -> f Unit
  , get :: String -> f (Maybe String)
  }

To get the easiest example out of the way, here’s how to achieve parallelism in a tagless final program:

program :: forall f m. Parallel m f => KVStore f -> f (Maybe String)
program (KVStore k) = do
  k.put "A" a
  x <- (<>) <$> k.get "B" `parApply` k.get "C"
  k.put "X" (fromMaybe "-" x)
  pure x

This programs makes use of the Parallel type class, that allows us to make use of the parApply combinator to use independent computations with a related Applicative type. This is already much simpler than doing the same thing with Free and FreeApplicative. For more info on Parallel check out the docs here.

However this is kind of like cheating, we’re not really inspecting the structure of our program at all, so let’s look at an example where we actually have access to the structure to do optimizations with.

Let’s say we have the following program:

program :: forall f. Apply f => KVStore f -> f (List String)
program mouse (KVStore k) = (\f s _ t -> catMaybes (f : s : t : Nil)) <$>
  k.get "Cats" <*> k.get "Dogs" <*> k.put "Mice" "42" <*> k.get "Cats"

Not a very exciting program, but it has some definite optimization potential. Right now, if our KVStore implementation is an asynchronous one with a network boundary, our program will make 4 network requests sequentially if interpreted with the standard Apply instance of something like Aff. We also have a duplicate request with the "Cats"-key.

So let’s look at what we could potentially do about this. The first thing we should do, is extract the static information. The easiest way to do so, is to interpret it into something we can use using a Monoid. This is essentially equivalent to the analyze function commonly found on FreeApplicative.

Getting this done, is actually quite simple, as we can use Const as our Applicative data type, whenever the lefthand side of Const is a Monoid. I.e. if m has a Monoid instance, Const m a has an Applicative instance. You can read more about Const here.

import Prelude
import Data.StrMap as M
import Data.Set as S
import Data.Const

analysisInterpreter :: KVStore (Const (Tuple (S.Set String) (M.StrMap String)))
analysisInterpreter = KVStore
  { put : \key value -> Const $ tuple2 S.empty (M.singleton key value)
  , get : \key -> Const $ tuple2 (S.singleton key) M.empty
  }

(Const (program analysisInterpreter))

By using a Tuple of Set and Map as our Monoid, we now get all the unique keys for our get and put operations. Next, we can use this information to recreate our program in an optimized way.

optimizedProgram :: forall f. Apply f => KVStore f -> f (List String)
optimizedProgram (KVStore k) = 
  let (Const (Tuple gets puts)) = program analysisInterpreter
  in traverse (\(Tuple k v) -> k.put k v) (fromFoldable puts) *> traverse k.get (fromFoldable gets)

And we got our first very simple optimization. It’s not much, but we can imagine the power of this technique. For example, if we were using something like GraphQL, we could sum all of our get requests into one large request, so only one network roundtrip is made. We could imagine similar things for other use cases, e.g. if we’re querying a bunch of team members that all belong to the same team, it might make sense to just make one request to all the team’s members instead of requesting them all individually.

Other more complex optimizations could involve writing a new interpreter with the information we gained from our static analysis. One could also precompute some of the computations and then create a new interpreter with those computations in mind.

Embedding our Applicative program inside a larger monadic program is also trivial:

program :: forall f. Apply f => String -> KVStore f -> f (List String)
program mouse (KVStore k) = (\f s _ t -> catMaybes (f : s : t)) <$>
  k.get "Cats" <*> k.get "Dogs" <*> k.put "Mice" mouse <*> k.get "Cats"

optimizedProgram :: forall f. Apply f => String -> KVStore f -> f (List String)
optimizedProgram mouse (KVStore k) = 
  let (Const (Tuple gets puts)) = program mouse analysisInterpreter
  in traverse (\(Tuple k v) -> k.put k v) (fromFoldable puts) *> traverse k.get (fromFoldable gets)

monadicProgram :: forall f. Bind f => KVStore f -> f Unit
monadicProgram (KVStore k) = do
  mouse <- k.get "Mice"
  list <- optimizedProgram (fromMaybe "64" mouse) k
  k.put "Birds" (fromMaybe "128" (head list))

Here we refactor our optimizedProgram to take an extra parameter mouse. Then in our larger monadicProgram, we perform a get operation and then apply its result to optimizedProgram.

So now we have a way to optimize our one specific program, next we should see if we can introduce some abstraction.

First we’ll have to look at the shape of a generic program, they usually are functions from an interpreter algebra f to an expression inside the type constructor f, such as f a.

type Program alg a = forall f. Applicative f => alg f -> f a

The program is only defined by the algebra and the resulting a, so it should work for all type constructors f.

optimize :: forall alg f a m. Applicative f
         => Monoid m 
         => Program alg a
         -> alg (Const m)
         -> m -> f a
         -> alg f
         -> f a
optimize program extract restructure =
  let (Const m) = program extract
  in restructure m

Now we should be able to express our original optimization with this new generic approach:

optimizedProgram :: forall f. Apply f => String -> KVStore f -> f (List String)
optimizedProgram mouse (KVStore k) =
  optimize program analysisInterpreter (\(Tuple gets puts) -> 
  traverse (\(Tuple k v) -> k.put k v) (fromFoldable puts) *> traverse k.get (fromFoldable gets))

So far so good, we’ve managed to write a function to generically optimize tagless final programs. However, one of the main advantages of tagless final is that implementation and logic should be separate concerns. With what we have right now, we’re violating the separation, by mixing the optimization part with the program logic part. Our optimization should be handled by the interpreter, just as the sequencing of individual steps of a monadic program is the job of the target Monad instance.

One way to go forward, is to create a typeclass that requires certain algebras to be optimizable. This typeclass could be written using the generic function we wrote before, so let’s see what we can come up with:

type OptimizerReqs alg f m =
  { extract :: alg (Const m)
  , rebuild :: m -> alg f -> f (alg f)
  }

class (Monad f, Monoid m) <= Optimizer alg f m | alg -> f , f -> m where
  reqs :: OptimizerReqs alg f m

optimize :: forall alg f m a. Optimizer alg f m
         => Program alg a
         -> alg f
         -> f a
optimize prog interpreter =
  let (Const m2) = prog (reqs :: OptimizerReqs alg f m).extract
  in (reqs.rebuild m2 interpreter) >>= prog

This might look a bit daunting at first, but we’ll go through it bit by bit. First we define our type class Optimizer parameterized by an algebra alg :: (* -> *) -> * and a type constructor f :: * -> *. This means we can define different optimizations for different algebras and different target types. For example, we might want a different optimization for a production Optimizer KVStore (EitherT Task e) m and a testing Optimizer KVStore Identity m. Next, for our interpreter we need a Monoid m for our static analysis, so we parametrize the Optimizer with an extra parameter m.

The next two functions should seem familiar, the extract function defines an interpreter to get an m out of our program. The rebuild function takes that value of m and the interpreter and produces an f alg f, which can be understood as an f of an interpreter. This means that we can statically analyze a program and then use the result of that to create a new optimized interpreter and this is exactly what the optimize function does. This is also why we needed the Monad constraint on f, we could also get away with returning just a new interpreter alg f from the rebuild method and get away with an Applicative constraint, but we can do more different things this way.

Let’s see what our program would look like with this new functionality:

monadicProgram :: forall f m. Optimizer KVStore f m => KVStore f -> f Unit
monadicProgram (KVStore k) = do
  mouse <- k.get "Mice"
  list <- optimize (program $ fromMaybe "64" mouse) (KVStore k)
  k.put "Birds" (fromMaybe "128" (head list))

Looking good so far, now all we need to run this is an actual instance of Optimizer. We’ll use the standard Aff for this and for simplicity our new optimization will only look at the get operations:

extract :: KVStore (Const (S.Set String))
extract = KVStore 
  { get : \key -> Const $ S.singleton key
  , put : \_ _ -> Const $ S.empty
  }

rebuild :: forall e. S.Set String -> KVStore (Aff e) -> Aff e (KVStore (Aff e))
rebuild gs (KVStore interp) = 
  precomputed <#> (\m -> KVStore $ interp
        { get = \key -> case (M.lookup key m) of
            Just a -> pure $ Just a
            Nothing -> interp.get key
        })
  where 
    tupleList :: Aff e (List (Maybe (Tuple String String)))
    tupleList =
          parTraverse (\key -> interp.get key <#> (\m -> m <#> \s -> key /\ s)) (fromFoldable gs)
    precomputed :: Aff e (M.Map String String)
    precomputed = tupleList <#> (M.fromFoldable <<< catMaybes)


instance kvStoreAffOptimizer :: Optimizer KVStore (Aff e) (S.Set String) where
  reqs = { extract , rebuild }

Our Monoid type is just a simple Set String here, as the extract function will only extract the get operations inside the Set. Then with the rebuild we build up our new interpreter. First we want to precompute all the values of the program. To do so, we just run all the operations in parallel and put them into a Map, while discarding values where the get operation returned Nothing. Now when we have that precomputed Map, we’ll create a new interpreter with it, that will check if the key given to get operation is in the precomputed Map instead of performing an actual request. We can then lift the value into a Aff e (Maybe String). For all the put operations, we’ll simply run the interpreter.

Now we should have a great optimizer for KVStore programs interpreted into an Aff. Let’s see how we did by interpreting into a silly implementation that only prints whenever you use one of the operations:

testInterpreter :: forall e. KVStore (Aff e)
testInterpreter = KVStore
  { put : \_ value -> do
      liftEff $ unsafeCoerceEff $ log $ "Put something " <> value
      pure unit
  , get : \key -> do
      liftEff $ unsafeCoerceEff $ log $ "Hit network for " <> key
      pure $ Just $ key <> "!"
  }

Now let’s run our program with this interpreter and the optimizations!

launchAff $ monadicProgram testInterpreter
// Hit network for Mice
// Hit network for Cats
// Hit network for Dogs
// Put something: Mice!
// Put something: Cats!

And it works, we’ve now got a principled way to write programs that can then be potentially optimized.

Conclusion

Designing a way to completely separate the problem description from the actual problem solution is fairly difficult. The tagless final encoding allows us one such fairly simple way. Using the technique described in this blog post, we should be able to have even more control over the problem solution by inspecting the structure of our program statically.

Another thing we haven’t covered here, are programs with multiple algebras, which is quite a bit more complex as you can surely imagine, maybe that will be the topic of a follow up blog post.

The code for this blog post can be found here, if people find it useful enough, I’ll publish and document it!

What kind of problems and techniques would you like to see with regards to tagless final? Would love to hear from you in the comments!

Today I’d like us to build our own Reactive Mobile Framework. A Reactive UI Framework should allow us to build apps declaratively by manipulating User Event Streams.

Now we’re not going to write such a Framework from scratch, but we’d like to use an existing Framework and create some Bindings, so that we can use it reactively. Examples for these types of wrappers are RxCocoa for the Cocoa and Cocoa Touch Frameworks, RxBinding for Android or RxSwing for the Java Swing toolkit.

First we have to choose the UI Framework we’re going to work with. I’ve spent a lot of time working with mobile Reactive Frameworks, so for today, I’d like to create some Bindings for the Xamarin.Forms toolkit. Xamarin.Forms is a cross-platform UI Framework that lets you create native UIs for both Android and iOS, by leveraging the .NET Framework. We’re going to write our code in F#, since it just supports the functional paradigm a lot better.

Now without further ado let’s identify what exactly it takes to create such a Wrapper.

Firstly, we’ll need to have a way to create an event stream from user interactions, for example, we should be able to create an event stream from a toggle or checkbox, that emits boolean values. We’ll call these interactions event sources, some frameworks like RxBinding will only support bindings for event sources.

Next, we will need a way to take event streams and bind them to a View. An easy example is a function that takes a stream of Strings and binds them to a Label. We’ll call these event sinks, since that’s where our streams will go into.

So one of the easiest programs we can imagine with this kind of setup is a Switch that emits boolean values that then get mapped to some kind of text which finally gets bound to a Label. I made a small diagram to illustrate what’s happening:

SimpleMarbles

Alright, now let’s get codin’! The first thing we’re gonna do is create the source function for the Switch. The function will accept a Switch and return an Observable<bool>. Creating new Observables is fairly straight forward. Let’s look at a small example:

Observable.Create(fun (o: IObserver<int>) ->
        o.OnNext(1)
        o.OnNext(2)
        o.OnError("Damn")
        o.OnNext(4)
        o.OnCompleted
)

We use the Observable.Create function and call the OnNext, OnError and OnCompleted functions to emit values and errors.

Now that we know how to create Observables, let’s finally create one for the Switch:

module RxForms =
    let fromSwitch (s: Switch) = Observable.Create(fun (o: IObserver<bool>) ->
        s.Toggled.Subscribe(fun t -> o.OnNext(t.Value)))
        

Here we again create an Observable that emits the value of the Switch everytime it’s toggled. We don’t need to call OnError or OnCompleted, since the Switch won’t error out or stop emitting. Yay! We created our first source binding! We placed in a module called RxForms, where we’ll place all of our binding functions from now on.

Okay, so let’s continue by defining a sink. We’ll call our function bindLabel and it’ll take an Observable<string> and a Label and it’ll return a Subscription.

let bindEntry (l: Label) (o: IObservable<string>) =
    o |> Observable.subscribe(fun s -> l.Text <- s)
        

Now that we’ve created functions to extract sources and bind to sinks, we have a basis on which we could expand and wrap around all of the Xamarin.Forms widgets. So go! No time to lose, the Api has dozens of Views to wrap, but first let’s see if our cute little program actually works. Here’s the code:

type App() =
    inherit Application()
    
    let stack = 
        StackLayout(VerticalOptions = LayoutOptions.Center)
    let switch = Switch()
    let label = Label()

    let switchEvents = 
        RxForms.fromSwitch switch |> Observable.map (fun b -> if b then "On" else "Off")

    let subscription = 
        switchEvents |> RxForms.bindLabel label

    do stack.Children.Add(switch)
    do stack.Children.Add(label)
    do base.MainPage <- ContentPage(Content = stack)

We’re using the simplest layout With a StackLayout and then create both a Switch and a Label and then use our functions to wire everything up. Here’s how this would look on iOS:

SwitchGif

Notice, though, that we currently have to handle the subscription manually. If we fleshed out our Framework, we could create a mechanism, that unsubscribes automatically, whenever the bound view get’s destroyed (This is what RxCocoa’s DisposeBag does, maybe we’ll implement this in another article).

I could probably end this article here, but let’s look at a few more examples. First, some easy stuff:

let fromButton (b: Button) = Observable.Create(fun (o: IObserver<unit>) -> 
    b.Clicked.Subscribe(fun _ -> o.OnNext( () )))
   
let bindEntry (e: Entry) (o: IObservable<string>) =
    o |> Observable.subscribe(fun s -> e.Text <- s) 
    
let bindListView (list: ListView) (o: IObservable<List<_>>) =
    o |> Observable.subscribe(fun ts -> list.ItemsSource <- ts) 

With these, we can easily use Buttons, ListViews and Entrys (Entrys are simple Textfields). So let’s use these new widgets to create the most over used example app: The Todo app! Yaaaay! The Todo app is great though, because it usually demonstrates how to handle state.

One option for implementing such an app would be to add both a Button and an Entry and combine them, but Entry also offers a Event that emits once the user ends input. Let’s add a function to extract such a source:

let fromEntryCompleted (e: Entry) = Observable.Create(fun (o: IObserver<_>) -> 
    e.Completed.Subscribe(fun s -> o.OnNext(e.Text)))

We’ll start by adding both an Entry and a ListView and extracting an Observable<string> from the Entry:

type App() =
    inherit Application()

    let stack = 
        StackLayout(Padding = Thickness(0.0, 40.0, 0.0, 0.0))
    let editText = 
        Entry(Placeholder = "What needs to be done?", Margin = Thickness(10.0, 0.0))
    let listView = 
        ListView(Margin = Thickness(10.0, 0.0))

    let submittedTodos = 
        RxForms.fromEntryCompleted editText

Now what we’d like to accumulate these todos into a list of todos, a List<string>. To do that, we’ll use the scan operator, which is like a reducer, but emits all the intermediary values. Once again, I made a diagram to explain this (a picture speak a thousand words).

ScanMarbles

So every time our Entry completes, we add a new item to our list. This is how that looks in code:

let todoLists = 
    Observable.scan (fun acc cur -> acc |> List.append [cur]) [] submittedTodos

let subscription = 
    todoLists |> RxForms.bindListView listView

And with that, we’re done right? Well not quite, since now every time we submit a Todo, our Entry doesn’t clear, which kinda sucks. So we need to write another binding for Entrys. However, I’m going to leave that as an exercise for you, dear reader! Instead, here’s a gif on how it should look in the end (I’ll upload the final code, just in case you get stuck).

TodoGif

Conclusion

So that’s it for now, I hope, that with your help, we can bring Reactive Programming to more and more UI Frameworks. Me, personally, I’d really like to see a full fledged Library made out of what we started in this article. In case you have any questions, I’d love to hear them, so just post them in the comments down below. The full code of this article can be found here. Happy Coding everyone!

What makes a language functional? Well, that’s a good question! Some people say that lambdas make a language a functional language. Others say it’s the ability to bind functions to variables. But that in itself isn’t really all it takes right? After all, we could do this with function pointers in C! And I don’t think many would claim C is a functional language, right?

In this article I’ll try to go over some specific features that I personally think make or break a functional programming language. Now pay in mind, that a lot of this is going to be fairly subjective, but I’d love to hear your thoughts in the comments!

So without further ado here’s what we will take a look at throughout this article (in order of most to last important to functional programming):

  • First Class Functions
  • Immutability
  • Recursion
  • Expression-Oriented Programming
  • Currying
  • Lazy Evaluation
  • Algebraic Data Types
  • Other topics (Higher Kinded Types, Existential Types)

First class functions

Most languages support this nowadays, Java 8 brought First Class functions to the language and C++ also included them in C++11. Having functions be first class basically only really means that you can use them the same way you would use any other value, like being able to bind functions to variables and pass them around your application.

Now there have been a lot of different names for what is basically just a couple of concepts, so we’ll try and go through them shortly.

Anonymous Functions AKA Lambda Expressions

Lambdas and anonymous functions are essentially the same thing, it’s just a function that doesn’t have a binding to an identifier. So they’re just easy ways for creating functions, in the same sense that some languages allow literals for Arrays or dictionaries. Anonymous functions originate in Alonzo Church’s Lambda Calculus, hence the name. Here’s an example in python: With that we’ve defined a variable holding a function that will square a given number when applied. Pretty straight forward!

Lexical Closures

Now closures are often confused with lambdas and it’s not difficult to understand why. All closures are anonymous functions, but it doesn’t work vice versa. Closures are special functions, that close over the environment where it was created, meaning it can gain access to values not in its parameter list. Very similar to how methods can access instance variables. You’ve probably already heard of the saying “Closures are the poor man’s objects”. Let’s take a look at an example in Kotlin: In this snippet we can see that the function passed to forEach gets access to the sum variable and can even modify it. So closures and lambdas go hand in hand, then what’s the deal with Higher order functions?

Higher Order Functions

Most of you have probably already used Higher Order Functions. HOFs are just functions that take another function as a parameter. So any function that takes a callback function could be considered a HOF. Other very notable example include functions like map, filter reduce. Here’s an example for a filter-function in Swift: Here predicate is a function that takes a parameter of type T and returns a Bool depending on if the element matches the predicate or not. You’ll find many of these HOFs in most functional languages and it’s almost an absolut must for doing any kind of functional programming.

Immutability

Immutability plays a big part in FP, a small subset of functional languages are so called “pure” functional languages. Purity means, that absolutely everything is immutable. Examples for this are Haskell, Elm and (as the name suggests) PureScript.

So on the one side we’ve got languages where everything is immutable, but on the other side we also have languages where immutability is unavailable. JavaScript has often been touted as a functional language, butit didn’t have any way to make variables immutable until ES6 and even then it’s only limited to local variables and there’s still no way to declare instance variables to be immutable (unless you’re using Object.freeze). Other languages where immutability is also lacking are Python and Ruby.

Now this is not the only metric for how much a given language supports immutability. Another is of course, how much the language encourages you to write immutable code. In Java and C# for example you need to add an extra keyword to make a value immutable (C# also doesn’t allow Type Inference on immutable values).

Put this in contrast to Rust:

It’s quite clear which programming language wants to encourage you to use immutable values. Some compilers (like Rust and Swift) also emit a warning if you use a mutable variable, but don’t mutate it.

Lots of functional languages also offer a way to copy an Object or Record, but with one or multiple values modified. This makes creating a new value almost exactly as easy as modifying the original. Here’s an example of what that might look like in Elm:

Another thing to consider is something traditionally called “const correctness”, which means that you can’t mutate parts of a value if it’s declared immutable. For example this is legal in Java: Where as the equivalent would throw a compiler error in C++.

Now the last thing to consider is whether or not your language supports performant immutable data structures. Languages like Kotlin and Swift support simple readonly data structures, that are the same as their mutual counterpart, but not being able to modify it.

Other more functional languages offer us special collections that are optimized for immutability. These immutable data structures have operators that can modify and return a copy of the original. Most of the time, however we don’t even need to copy most of the collection and can instead reuse it, because we don’t need to worry about subsequent code making changes to our data. So there’s no need to defensively copy the whole structure, saving both memory and time! This is called data sharing and is a huge benefit of immutable data structures.

The coolest collections come from the late Scala community leader Phil Bagwell (R.I.P.), essentially they offer amortized O(1) lookups, insertions and deletions on Vectors and HashMaps. You can find these data structures in Clojures and Scalas standard library as well as in libraries such as Immutable.js. There’s a lot of super interesting stuff to talk about, so if you’re interested check out this great series on how these data structures actually work.

Recursion

Most if not all of modern programming languages support the notion of recursion However it plays a much bigger part in functional programming than in imperative programming. That is because when programming in a functional way, iterating over data structure recursively is not just much more elegant, but also the only way to iterate without invoking side-effects.

In order for this to be efficient, most functional languages offer an optimization technique called “Tail Call Optimization”. With this technique it’s possible for recursive functions to not increase the size of the call stack. In other words: the compiler more or less replaces the original function with the equivalent of an imperative loop.

Going into too much detail here would break the scope of the article, so here’s the gist of it: if the last thing you do (i.e. the “tail” position) in a function is a recursive call to itself, the compiler can optimize this to act like iteration instead of recursion.

So if you want to do functional programming in your language without having to worry about stack overflows, your language should probably provide some form of TCO.

Some languages make writing tail recursive functions a lot easier by giving you a way to mark them as such. For example Scala supports a way explicitly annotate a function as tail recursive and let the compiler throw an error when it isn’t.

This guarantees that an error is issued whenever tail call optimization cannot be performed by the compiler.

Expression-Oriented Programming

To understand Expression-Oriented programming we first need to define the difference between expressions and statements. This is best explained by contrasting return types of different functions. For example a void type means the method is probably a statement, since it doesn’t a result. Everything else is an expression and yields a value when computed. Typically the former looks something like list.sort() while expressions look like sorted = sort(list).

To put it simply, in Expression-Oriented programming languages everything is an expression! Which means that everything has a return value. This is something we aspire to because statements always have side effects and should be avoided as much as possible in functional programming.

Rust, Ruby, Kotlin and more functional languages like Scala, Elm, Haskell or F# all use this paradigm. This means that for example the if-construct always returns a result:

Another neat example are Scala’s “for-expressions” which involve some syntactical sugar that looks very similar to for-loops found in imperative languages.

Currying

Currying is when you break down a function that takes multiple parameters into a series of functions each taking a parameter and returning a new function. A simple example would be this:

I’ve written in depth about the workings and advantages of Currying and the most often confused technique of partial application in an earlier article. Both Currying and partial application are very useful tools in the functional programming world and most functional languages make it very easy to do so. For example in Haskell or one of the different ML-derived languages, it’s mostly impossible to even write an uncurried version of functions. Functions are just curried by default! Here’s some Haskell code: The type signature of the add function is Integer -> Integer -> Integer, meaning it takes an Int and returns a function that takes an Int and returns an Int. This allows us to just pass one argument to the add function and get another generic function that adds the passed argument. Different languages handle this differently, but it’s a pretty important tool in the functional programmers toolkit!

Scala for example lets you partially apply functions easily by passing an underscore _ as a function parameter. Swift is a rather curious example, because it supported a very way of writing curried functions, but has since deprecated them without any real replacement.

Lazy evaluation

Lazy evaluation is a technique to defer the computation of expressions to when they are really needed. This is in contrast to eager evaluation, where every expression is evaluated immediately. Lazy evaluation can be very beneficial when programming in a functional way. Let’s look at an example of eager evaluation in JavaScript:

In this example each operation returns a new copy immediately once called. What we’d like to do is use higher-order functions like map and filter instead of manually fusing passes, but without having to create intermediate data structures and having to iterate the structure multiple times. This can be solved quite handily using lazy evaluation.

So now let’s have a look at equivalent code using lazy evaluation: Wait a minute… it’s the same basic code! Well yeah it is, the truly interesting stuff is happening behind the scenes, but this code can demonstrate a few things.

Firstly, we no longer create intermediate copys of the list, in fact nothing even gets computed untill we access the first element by calling the head method. Secondly, since we’re only accessing the first element of the list, all the operations are only applied once and we can save a lot of execution time. We do not need to evaluate the whole list, when all we want to do is print out the first element.

In Haskell lazy evaluation is the default, but in most other functional languages it’s opt in. Examples for these are the various Lisps, Scala and F#.

Algebraic Data Types

Algebraic data types? Aw man, what’s this fancy maths stuff? I just want to program cool stuff! Alright! I won’t go into too much detail here, so bear with me for a moment! Okay, so most functional languages allow you to define simple data types. These ADTs are simple data cointainers that can be defined recursively. They can be easily constructed and deconstructed and usually come with built in structural equality checking.

All of this allows us to utilize a technique called “Pattern matching”. Pattern matching is a kind of switch-case on steroids, it can do type-testing, it can check exhaustiveness and it can destructure it’s arguments. Let’s have a look at an example written in Scala:

This is just a rather simple example, but I’m sure you can imagine how powerful the match expression can be. An ADT can be anything by the way, from Tuples to Lists, to Records. So Pattern matching is extremely useful because we can decompose any kind of data structure by its shape instead of its contents.

With pattern matching navigating and decomposing data structures becomes very convenient, with a compact syntax.

Other advanced features

There’s two other things I’d like to atleast give a mention, they’re both fairly complex and probably warrant a whole article just to get a good understanding. Furthermore they’re both features of a type system, which might be interesting in staticly typed languages, but no so much for dynamic ones.

Higher kinded Types

The first feature is the ability to create “Higher Kinded Types”, which can be seen as providing a way to is the ability to generically abstract over things that take type parameters Here’s an example with a Functor in Scala: Here F[_] could be anything that takes a generic parameter, so Option[T] or List[T] would both be fine.

Existential Types

The other feature is called “Existential Types” can be used for several different purposes, but what they do is to ‘hide’ a type parameter for outside use. Sometimes you don’t care about the actual type but only that it exists. Existential types can make this a reality without making the type parameter covariant.

Conclusion

Now I’d like to conclude without telling you which language is a functional language or which one isn’t. The line is probably more blurred than not and it’s impossible to find some objective criteria for a functional language. We could argue for ages about what or what doesn’t constitute one and how we should weigh these features on a scale from 1 to 100, instead I think we’ve got a fair overview of features functional programmers use everyday.

My hope is that after reading this article, you understand that lambdas aren’t the only criteria and what else might play a role in programming in a functional way. Yes we can do functional programming in almost any language, but in most that would be more cumbersome than we’d like and we should probably strive to use the right tool for the right job. Once you try out a language that has a lot of these “functional” features, you’ll probably find programming with pure functions a lot more pleasant. And I hope you guys can also enjoy functional programming more once you’ve got a hold on some of these cool features.