Tutorial: Transparent interfaces in Haskell

This post presents a nifty trick that makes use of type families, datakinds and GADTs.

Have you ever wanted to take a JSON -object and access it in Haskell with minimal effort of only specifying what you're expecting from the value? Then you're on the right page.

{-# LANGUAGE TypeFamilies, DataKinds, GADTs #-}
module InterfaceTutorial where

As a starting point you need some interface "outwards" from Haskell. For example, you might have JSON objects, some presentation of values.

data JsValue = VArray [JsValue]
             | VNum Double
             | VString String
               deriving (Show)

data JsType = TArray | TNum | TString

The JsType is there but it's not used in this article. Idea of this structure is to be the "type" for the structure and illustrate that what we're going to build is not that type.

Specifically this post is about terms that map into types.

type FooI = 'AsDouble
foo :: TypeOf FooI
foo = 1.4

You'll be able to make a structure that maps some interface declaration into Haskell types and then associates that with a representation that you're interested about.

foo_val :: JsValue
foo_val = toJs (term :: JsTypeMapTerm FooI) foo

foo_dec :: Maybe (TypeOf FooI)
foo_dec = fromJs (term :: JsTypeMapTerm FooI) foo_val

There could be several reasons why this might be convenient. You could use this when writing a runtime library for an interpreter. Or if you need to encode/decode things in files or even to query databases. Alternatively it could be useful if you just need some distance between a foreign function interface and your Haskell application.

Here's an another example in whole, note that the interface descriptor is going to determine how the structure is interpreted as a type, not the representation that we're converting it to.

type BaaI = 'AsList AsString
bar :: TypeOf BaaI
bar = [
    "Your dynamic programming language implementation",
    "is my Haskell runtime"]

bar_val :: JsValue
bar_val = toJs (term :: JsTypeMapTerm BaaI) bar

bar_dec :: Maybe (TypeOf BaaI)
bar_dec = fromJs (term :: JsTypeMapTerm BaaI) bar_val

Now lets go through how this is built.

Interface descriptors

The thing that everything else builds up on is this mapping. It tells how the interface is constructed.

data JsTypeMap
    = AsDouble
    | AsInteger
    | AsList JsTypeMap
    | AsString
    deriving (Show)

Next we have this type-level function that assigns a type to each term that we built.

type family TypeOf j where
    TypeOf 'AsDouble   = Double
    TypeOf 'AsInteger  = Integer
    TypeOf ('AsList a) = [TypeOf a]
    TypeOf 'AsString   = String

..That's it. Well not entirely.

The ' takes a term and produces a type of that name. That's in short what DataKind extension brings in.

Unfortunately we do not have an automated way to drop a lifted type back into a term. For that reason we need this kind of a tool to construct a term that "mirrors" the structure of the type-level term.

data JsTypeMapTerm :: JsTypeMap -> * where
    TermDouble  :: JsTypeMapTerm 'AsDouble
    TermInteger :: JsTypeMapTerm 'AsInteger
    TermString  :: JsTypeMapTerm 'AsString
    TermList    :: JsTypeMapTerm a -> JsTypeMapTerm ('AsList a)

With the JsTypeMapTerm we can lower the type-level term and produce the conversion functions, first from Js representation to Haskell representation.

fromJs :: JsTypeMapTerm a -> JsValue -> Maybe (TypeOf a)
fromJs TermDouble   (VNum a)    = Just a
fromJs TermInteger  (VNum a)    = Just (floor a)
fromJs TermString   (VString a) = Just a
fromJs (TermList a) (VArray xs) = sequence (fmap (fromJs a) xs)
fromJs _            _           = Nothing

Then from Haskell representation to Js representation.

toJs :: JsTypeMapTerm a -> TypeOf a -> JsValue
toJs TermDouble   num    = VNum num
toJs TermInteger  num    = VNum (fromIntegral num)
toJs TermString   string = VString string
toJs (TermList a) xs     = VArray (fmap (toJs a) xs)

To be able to write the type-level term back into a term, we're going to use typeclasses for that.

class Term a where
    term :: JsTypeMapTerm a

instance Term 'AsDouble where
    term = TermDouble

instance Term 'AsInteger where
    term = TermInteger

instance Term 'AsString where
    term = TermString

instance Term a => Term ('AsList a) where
    term = TermList term

This last structure is responsible for the: term :: JsTypeMapTerm 'a. It can be also used to encode the schema and write it out from your application.

Not too pretty, but checks out

Currently this style of programming is quite verbose, but some post-Haskell language will eventually do it much better. For instance, it's already a joke if it gets compared to Idris or Agda where you just implement in the following functions directly:

TypeOf : JsTypeMap -> Type
fromJs : (i:JsTypeMap) -> TypeOf i -> JsValue
toJs   : (i:JsTypeMap) -> JsValue -> TypeOf i

This trick is definitely worthwhile to know if you want to use Haskell to conveniently interface with something through some protocol.

Update 2020-07-29: Posted this to r/haskell because it might be a good motivation for Purescript developers to notice these extensions and make use of them.

About typeclasses as an alternative

2020-07-31: u/zarazek remarked that you could also use typeclasses directly, like this:

class JsEnc a where
    toJs2 :: a -> JsValue
    fromJs2 :: JsValue -> Maybe a

instance JsEnc Double where
    toJs2 s = VNum s
    fromJs2 (VNum n) = Just n
    fromJs2 _        = Nothing

instance JsEnc Integer where
    toJs2 s = VNum (fromIntegral s)
    fromJs2 (VNum n) = Just (floor n)
    fromJs2 _        = Nothing

instance {-# OVERLAPPING #-} JsEnc String where
    toJs2 s = VString s
    fromJs2 (VString s) = Just s
    fromJs2 _           = Nothing

instance JsEnc a => JsEnc [a] where
    toJs2   xs          = VArray (fmap toJs2 xs)
    fromJs2 (VArray xs) = sequence (fmap fromJs2 xs)
    fromJs2 _           = Nothing

Note the String is a type alias for [Char]. This means you're going to need FlexibleInstances enabled and prefix it with {-# OVERLAPPING #-}. Without this the compiler is going to have issue with overlapping instances.

We're looking at something really similar here:

toJs  :: JsTypeMapTerm a -> TypeOf a -> JsValue
toJs2 :: JsEnc a         => a        -> JsValue

fromJs  :: JsTypeMapTerm a -> JsValue -> Maybe (TypeOf a)
fromJs2 :: JsEnc a         => JsValue -> Maybe a

You could've also used a GADT as a map.

data JsTypeMap2 :: * -> * where
    AsDouble2 :: JsTypeMap2 Double
    AsInteger2 :: JsTypeMap2 Integer
    AsList2 :: JsTypeMap2 a -> JsTypeMap2 [a]
    AsString2 :: JsTypeMap2 String

deriving instance Show (JsTypeMap2 a)

And we get a third way to convert values into JSON.

toJs  :: JsTypeMapTerm a -> TypeOf a -> JsValue
toJs2 :: JsEnc a         => a        -> JsValue
toJs3 :: JsTypeMap2 a    -> a        -> JsValue

If you'd like to make it very similar to typeclasses, you could use the following constructor that requires you to pass in the implementation:

data JsTypeMap3 :: * -> * where
    GenMap :: (JsValue -> Maybe a)
           -> (a -> JsValue)
           -> JsTypeMap3 a

toJs4 :: JsTypeMap3 a -> a -> JsValue
toJs4 (GenMap fromJ toJ) = toJ

fromJs4 :: JsTypeMap3 a -> JsValue -> Maybe a
fromJs4 (GenMap fromJ toJ) = fromJ

The typeclasses implicitly find the conversion so when the conversion is unique against a Haskell type, you likely will find it sufficient. Otherwise you're better off using a GADT or type families like presented in this article.

Now you have few ways to do this same thing. Thank you to u/zarazek for this.

Similar posts