1

I'm trying to implement a dynamically typed programming languages in Haskell which supports three data types, let's call them A, B and C and just for illustration purposes I will let A = Integer, B = [Integer] and C = (Integer, Integer) (but you can ignore the semantics of these types, that's not what I'm concerned about).

In order to use values of any type interchangeably in arithmetic expressions I have implemented an algebraic data type Value:

data Value = A A
           | B B
           | C C

And because I want to be able to add and multiply values I have implemented the typeclass OP:

class Op a where
  add :: a -> a -> a
  mul :: a -> a -> a

Now, I also want my types to implicitly convertible to each other (when two different types appear in an arithmetic expression), according to the following rules:

  • If both types are A, no conversion takes place
  • If one of the types is A, the other is converted to A
  • Otherwise, both types are converted to B

To make this possible I have implemented another typeclass, ImplicitlyConvertible:

class ImplicitlyConvertible a where
  toA :: a -> A
  toB :: a -> B

A complete example would then look like this:

{-# LANGUAGE FlexibleInstances, TypeSynonymInstances #-}

module Value where

type A = Integer

type B = [Integer]

type C = (Integer,Integer)

data Value = A A
           | B B
           | C C

class ImplicitlyConvertible a where
  toA :: a -> A
  toB :: a -> B

instance ImplicitlyConvertible A where
  toA = id
  toB = error "can't convert A to B"

instance ImplicitlyConvertible B where
  toA = sum
  toB = id

instance ImplicitlyConvertible C where
  toA   = sum
  toB c = [fst c, snd c]

instance ImplicitlyConvertible Value where
  toA v = case v of
    A a -> toA a
    B b -> toA b
    C c -> toA c
  toB v = case v of
    A a -> toB a
    B b -> toB b
    C c -> toB c

class Op a where
  add :: a -> a -> a
  mul :: a -> a -> a

instance Op A where
  add = (+)
  mul = (*)

instance Op B where
  add = zipWith (+)
  mul = zipWith (*)

valueOp :: (Value -> Value -> Value) -> (Value -> Value -> Value)
valueOp op (A v) v' = op (A v) (A $ toA v')
valueOp op v (A v') = op (A $ toA v) (A v')
valueOp op v v'     = op (B $ toB v) (B $ toB v')

instance Op Value where
  add = valueOp add
  mul = valueOp mul

I have three problems with this:

  • The fact that toB is not actually implemented for A seems unclean. Even though it should never be called I would like to avoid having to implement it at all.

  • instance ImplicitlyConvertible Value is just a bunch of boilerplate code that I would like to get rid of.

  • I'm not sure if my implementation of instance Op Value is sensible.

Am I maybe going about this the wrong way in the first place? How can I implement all of this more cleanly?

Peter
  • 2,919
  • 1
  • 16
  • 35

1 Answers1

1

It's actually easiest to work backwards through your questions, so I'll start at the end.

  • I'm not sure if my implementation of instance Op Value is sensible.

No, your implementation of instance Op Value isn't sensible. Have you tried evaluating it on example inputs? You may have noticed that it doesn't ever produce a result. The problem stems from what you're calling valueOp with. It looks like you're calling valueOp with the polymorphic function add (or mult), but you're really not. Since valueOp always takes as its first argument a function on Values, the definition of add in your Op Value instance will always call valueOp with the function add that is defined by the instance itself. This creates an infinite recursion.

How can you pass the polymorphic function add to valueOp instead? Consider a type like this:

valueOp :: (forall a. Op a => a -> a -> a) -> (Value -> Value -> Value)

(Note that you'll need to enable RankNTypes for this.) This type takes as input a binary function on a that works for any a that has an Op instance. So, for the first case, you can write:

valueOp op (A v) v' = A $ op v (toA v')

The inputs and output are still of type Value, but when we call op, we're doing so with values of type A, which is what we want. The other two cases follow naturally:

valueOp op v (A v') = A $ op (toA v) v'
valueOp op v v'     = B $ op (toB v) (toB v')

  • instance ImplicitlyConvertible Value is just a bunch of boilerplate code that I would like to get rid of.

Do you actually need the ImplicitlyConvertible instance for A, B, and C? If you never use them independently, then you could merge them into the Value instance, which would definitely reduce boilerplate. At that point, if you only have one instance (the Value instance), you could consider getting rid of the class structure altogether and simply defining the functions toA :: Value -> Value and toB :: Value -> Value.

If you need to keep all of these instances, then I don't really see a way around the boilerplate.


  • The fact that toB is not actually implemented for A seems unclean. Even though it should never be called I would like to avoid having to implement it at all.

This should raise a question to you about your overall strategy. In many ways, you've made things pleasingly generic, but it's not clear what that has bought you. After all, if your only use case for ImplicitlyConvertible is in valueOp, do you really need a new class for just one function? If not, perhaps you should fold the instances into the definition of valueOp itself? You may still have an error "can't convert A to B" in the definition, but you'll actually be able to prove that it's never called, unlike in your current code where anyone could come along and call toB on an A value.

valueOp :: (forall a. Op a => a -> a -> a) -> (Value -> Value -> Value)
valueOp op x y = case (x,y) of
  (A v, v') -> A $ op v (toA v')
  (v, A v') -> A $ op (toA v) v'
  (v, v')   -> B $ op (toB v) (toB v')
  where
    toA (A a) = a
    toA (B b) = sum b
    toA (C c) = sum c
    toB (A a) = error "can't convert A to B"
    toB (B b) = b
    toB (C c) = [fst c, snd c]

Alternatively, if this kind of conversion is necessary, you could define it only when it's explicitly possible:

class Convert x y where
  convert :: x -> y

instance Convert Value A where
  convert (A a) = convert a
  convert (B b) = convert b
  convert (C c) = convert c

instance Convert A A where
  convert = id

instance Convert B A where
  convert = sum

instance Convert C A where
  convert = sum

instance Convert B B where
  convert = id

instance Convert C B where
  convert c = [fst c, snd c]


valueOp :: (forall a. Op a => a -> a -> a) -> (Value -> Value -> Value)
valueOp op (A v) v' = A $ op v (convert v')
valueOp op v (A v') = A $ op (convert v) v'
valueOp op (B v) (B v') = B $ op v v'
valueOp op (B v) (C v') = B $ op v (convert v')
valueOp op (C v) (B v') = B $ op (convert v) v'
valueOp op (C v) (C v') = B $ op (convert v) (convert v')

This requires enumerating all possible options of B and C as inputs to valueOp, which is frustratingly verbose, but you can rest easily knowing that all your functions are total.

DDub
  • 3,884
  • 1
  • 5
  • 12
  • This is amazing! I have never seen the `forall a.` construct before, that's exactly what I couldn't figure out. – Peter Jan 01 '21 at 15:30