Principled Casts in Haskell

TL;DR I continue trying to implement a routing library, but instead end up learning about Typeable, writing about orphan instances, reading and (so far) failing to understand type-magic and sending my first Haskell PR.

I remember when I was starting Clojure, one of the big catchphrases was that everything was opt in. A type system, inheritance, multiple dispatch, &c. On the other hand, there were actually plenty of things that weren’t opt-in: Java itself, polymorphism, reflection and so on.

Haskell is another opt-in language. The basic type system and language is a requisite, but there’s still a phenomenal number of things to opt into. Equality is opt in, Hashable is opt in, as we saw in the previous article, polymorphism through existential types is opt-in. Next, we’re going to see “opt-in” type casts, and hopefully you’ll see how they’re better than what you can achieve in Java or C#.

{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
import qualified Network.Wai as Wai
import qualified Network.HTTP.Types as H

So, the question I asked last time was, how can I tell if two RequestConditionBoxs are equal? To do that, we’re going to want to make RequestConditions themselves implement equality.

(As an aside: the whole of the functionality of the last post might have been better implemented using good old functions or possibly the reader monad. However, I always wanted the conditions to be instances of Eq and Show. That’s not going to be possible with that approach.)

class (Show rc, Eq rc) => RequestCondition rc where
  isMatch :: Wai.Request -> rc -> Bool
data RequestConditionBox where
  RC :: (RequestCondition rc) => rc -> RequestConditionBox
  deriving (Show)

Oops, that isn’t going to work: you can’t derive Show on a GADT. So delete it. We’ll need to implement Eq and Show for RequestConditionBox. (I’m going to skip Show.)

instance Eq RequestConditionBox where
  (==) (RC a) (RC b) = a == b

Small problem: a and b are different types. And Eq only allows you to test that two members of the same type are equal. We need some way of checking that the two types are equal. Now, you can test for type equality in a type precondition but I can’t see how I could make that work. We need something more like

testEqual :: (Eq a, Eq b) => a -> b -> Bool

Only right now we have no idea how to implement it.

He’s My Typeable

George Pollard pointed me to an experimental class called Typeable. As I alluded to earlier, it’s opt-in, although I think the opt-in nature is more to do with the fact that it’s not standardized yet than that there are types that can’t logically have a typeclass instance.

Typeable looks like a pretty unpromising typeclass:

typeRep# :: Proxy# a -> TypeRep

Actually, it’s more than just unpromising, it looks positively hostile. What are those hashes? Well, it turns out that hash is a valid character in an identifier if you enable the MagicHash extension. As a convention, GHC uses it to represent unboxed types. Unboxed means exactly the same thing as it does in C# and Java: something that doesn’t have a garbage collected pointer around it. This is a very deep rabbit-hole that I’m just going to carefully step around right now.

Actually, I’m going to skip pretty much everything except to notice that Data.Typeable exports a rather useful function called cast.

cast :: (Typeable a, Typeable b) => a -> Maybe b

Yep, that’s exactly what as does in C#. I’ll skip over the implementation, because it’s slightly scary and I’d need to get into unsafeCoerce. One thing I can’t tell is if this code is actually run at runtime or whether it’s possible for the compiler to optimize it out. After all, the types of a and b are known at compile time.

With that, we can actually test if two values of different types are equal:

testEqual :: (Typeable a, Eq a, Typeable b, Eq b) => a -> b -> Bool
testEqual x y = fromMaybe False $ (== x) <$> cast y

Reading from right to left:

  • cast y
  • map (<$>) the maybe with (== x)
  • this gives us Nothing if x and y are different types, and Just (x==y) if they’re the same.
  • finally, we use fromMaybe to strip off the Just and replace Nothing with False

Orphan Black

To use testEqual, we need to make our RequestConditions typeable

class (Typeable rc, Show rc, Eq rc) => RequestCondition rc where
  isMatch :: W.Request -> rc -> Bool

How do we implement it? Well, we don’t. Typeable is special. Not only is it derivable, the compiler requires you use the deriving version. And that needs an extension:

-- Put this up at the top
{-# LANGUAGE DeriveDataTypeable #-}
newtype And rc = And [rc] deriving Typeable

Unfortunately, H.HttpVersion doesn’t implement Typeable. Luckily we can implement it ourselves. But, you guessed it, we need another extension:

-- Put this up at the top
{-# LANGUAGE StandaloneDeriving #-}
deriving instance Typeable H.HttpVersion

We’re probably alright here, but what we’ve done is, in general, ridiculously dangerous. We’ve implemented an instance in a library that is neither the library that declares the typeclass, nor the library that declares the type. This is known as an orphan instance and will have seasoned Haskellers gathering with torches and pitchforks around your codebase. The reason for this is that, while typeclasses provide the power of ruby’s mixins, orphan instances provide the problems. (They call it “incoherence”, and they mean it.)

While we’re on the subject, you’ll probably have already noticed that when you add projects into your cabal file, you pull in the world, Maven style. This is pretty horrific, but the reason for this is orphan instances. For instance, the functionality of the semigroups package looks pretty small: it just exposes a couple of typeclasses. But when you take a look at what is an instance just of Semigroup you’ll see a whole list of types that the semigroups package needs just to compile. Semigroups itself has defines to try to ameliorate this situation but the truth is that it’s just too much work (at least given cabal in its current design) to enforce small dependency lists and coherence.

Long story short, it’d probably be best to just expose Typeable from the library, so I’ve sent a pull request. (As everyone knows, open source software collaboration is a variable experience. But even at my beginner level, it is possible to make small contributions.)

The Equalizer

Remember last time I mentioned that we could destructure existential types? Now we can actually use this.

equalRC1 :: RequestConditionBox -> RequestConditionBox -> Bool
equalRC1 (RC a) (RC b) = testEqual a b

That looks pretty promising. But we haven’t handled the case where a or b are themselves a RequestConditionBox

equalRC2 :: RequestConditionBox -> RequestConditionBox -> Bool
equalRC2 a1@(RC a) b1@(RC b) = eq3 (cast a) (cast b)
  where eq3 (Just x) _ = equalRC2 x b1
        eq3 _ (Just y) = equalRC2 a1 y
        eq3 _ _ = testEqual a b

Well, that’s kind of fun, but an alternative formulation is arguably better:

infixl 3 <|!> -- Left associative, use same precedence as <|>
(<|!>) :: Maybe a -> a -> a
(<|!>) = flip fromMaybe
equalRC4 :: (Typeable a, Eq a) => a -> RequestConditionBox -> Bool
equalRC4 x (RC y) = a <|> b <|!> c
  where a = equalRC3 x <$> (cast y)
        b = equalRC3 y <$> (cast x)
        c = testEqual x y

<|> is a fairly general function, but in general it means “take the first valid parameter”. Its type is

(<|>) :: Alternative f => f a -> f a -> f a

Here, just remember that Maybe is an Alternative. I’ve also introduced my own infix operator <|!> to get me out of Maybe land. (Hey, I don’t even need an extension for this!)

We now have a vastly better implementation of Eq:

instance Eq RequestConditionBox where
  (==) == equalRC4

(Aside: there’s a very interesting looking function in Data.Typeable called gcast that I thought could be useful here, but I couldn’t figure it out, so everything here stays at the cast level.)

Designed By An Idiot In London

Let’s load what we’re got into a REPL.

> :m + Main
> :m + Data.List
> :m + Network.HTTP.Types
> let td = [RC methodGet, RC methodGet, RC (RC methodGet), RC http10, RC http11]
> nub td

gives us

[RC "GET",RC HTTP/1.0,RC HTTP/1.1]

Well, that’s demonstrated that Eq works. But it also demonstrates something else: Eq isn’t actually what we wanted in the first place. Really we want to be unifying to [RC "GET",RC HTTP/1.1]. To do that, we’re going to have to rip up everything we’ve done so far and start again.

FOOTNOTE: Elise Huard pointed me to the AdvancedOverlap page on the wiki, which details techniques for branching your code by typeclass rather than type. In practice, I decided to just make everything an instance of Eq, which isn’t so much of a problem given the problem domain I’m working within.

Published by

Julian Birch

Full time dad, does a bit of coding on the side.

Leave a comment