Friday 10 April 2015

Num literals in Haskell

This post is a Literate Haskell file. You can save it as a .lhs file, and execute it.

In this post, I will screw around a bit with one particular fact of Haskell's syntax. So, let's first enable a language extension I will need (and explain) later, as well as knock out any relevant imports.

> {-# LANGUAGE ScopedTypeVariables #-}
>
> import Data.Function (on)

Now; when you enter a literal number, what would you expect it's type to be?

> literal = 0

It sort of looks like an integer, but it could actually also be a float with, coincidentally, nothing past the decimal point. So Haskell does the most reasonable thing possible -- 'literal :: Num a => a'. It doesn't decide what type of number it is yet. This opens up a couple of cool things.

> data Complex a = a :+ a
> type Complex' = Complex Double
>
> instance (Eq a, Floating a) => Num (Complex a) where
>   (r1 :+ i1) + (r2 :+ i2) = (r1 + r2)              :+ (i1 + i2)
>   (r1 :+ i1) * (r2 :+ i2) = (r1 * r2 - i1 * i2)    :+ (r1 * i2 + i1 * r2)
>   abs (r :+ i)            = (sqrt $ r * r + i * i) :+ 0
>   signum (0 :+ 0)         = 0 :+ 0
>   signum c@(r :+ i)       = let (mr :+ _) = abs c in (r / mr) :+ (i / mr)
>   negate (r :+ i)         = negate r :+ negate i
>   fromInteger             = (:+ 0) . fromInteger

This datatype of course corresponds to complex numbers, as defined in mathematics. Now, we can make literals be complex numbers without any futher work!

> literal2 = 5
>
> op1 :: Complex'
> op1 = literal2 + (2.3 :+ (-5.8))

'literal2 :: Complex''. That's pretty straightforward. Now let's have a bit of fun with this.

> data Lolteger = Zero | One | Two | Three | Four | Five
>               | Six | Seven | Eight | Nine
>               deriving (Bounded, Enum, Eq, Ord, Read, Show)

We can define a Num instance for this, pretty easily. For over/underflow on operations I'll just take the result modulo 10 (so Lolteger would form the ring Z_10, integers modulo 10). As we'll have a lot of converting to and from Enum, let's define helpers for this.

> apply1 :: (Int -> Int) -> Lolteger -> Lolteger
> apply1 f = toEnum . (`mod` limit) . f . fromEnum
>   where limit = 1 + fromEnum (maxBound :: Lolteger)
>
> apply2 :: (Int -> Int -> Int) -> Lolteger -> Lolteger -> Lolteger
> apply2 f a b = toEnum . (`mod` limit) $ f (fromEnum a) (fromEnum b)
>   where limit = 1 + fromEnum (maxBound :: Lolteger)

> instance Num Lolteger where
>   (+)         = apply2 (+)
>   (*)         = apply2 (*)
>   abs         = apply1 abs
>   signum      = apply1 signum
>   negate      = apply1 negate
>   fromInteger = toEnum . (`mod` limit) . fromInteger
>     where limit = 1 + fromEnum (maxBound :: Lolteger)

This is probably obvious now, but amuses me to no end:

> four :: Lolteger
> four = 4

=> Four

> addition = One + Five

=> Six

> youCanEvenMixIt = 3 `times` Two
>   where times = (*)

=> Six

In fact, anything that is Bounded and an Enum can be made to behave like a Num like this. So, let's make use of a common Haskell design pattern: The newtype with an instance.

> newtype NumWrapper a = NW { getNW :: a } deriving (Read, Show)

Now, we define an almost identical Num instance for this (the only difference is that a bit more wrapping and unwrapping is involved for the helpers).

> infixr 8 .:
> (.:) = (.) . (.)
>
> apply1' :: forall a. (Bounded a, Enum a) =>
>            (Int -> Int) -> NumWrapper a -> NumWrapper a
> apply1' f = NW . toEnum . (`mod` limit) . f . fromEnum . getNW
>   where limit = 1 + fromEnum (maxBound :: a)
>
> apply2' :: forall a. (Bounded a, Enum a) =>
>            (Int -> Int -> Int) -> NumWrapper a -> NumWrapper a -> NumWrapper a
> apply2' f = NW . toEnum . (`mod` limit) .: f `on` fromEnum . getNW
>   where limit = 1 + fromEnum (maxBound :: a)

There's two things here that might be hard to understand: The foralls in the type declarations, and (.:). So let's do them in order.

1) forall. Recall the beginning of this post, I enabled ScopedTypeVariables. That is part of a family of extensions that allow you to write foralls, and each of them does something slightly different. STV, which I used here, is the most simple of them. Notice that in the helper definition limit, I use a type signature on maxBound. Usually, maxBound :: a would mean that this maxBound can work for any 'a'. In fact, Haskell implicitly adds foralls to all type signatures per default. What I wanted to achieve, however, is that this 'a' is the same as in the type signature of the function - after all I'm looking for the maxBound of the Enum we're using! So now only the function is "for all 'a's", and the maxBound is for the specific 'a' we're dealing with. And that, in short, is what ScopedTypeVariables does.
2) (.:). This is actually pretty simple. 'f . g' composes two functions with one argument each. For 'f .: g', 'g' has two arguments, and 'f' one. How and why that works took me a while to figure out, but it's actually pretty simple (hint: Start with 'fmap . fmap', then apply the fact that for functions, 'fmap = (.)').

> instance (Bounded a, Enum a) => Num (NumWrapper a) where
>   (+)         = apply2' (+)
>   (*)         = apply2' (*)
>   abs         = apply1' abs
>   signum      = apply1' signum
>   negate      = apply1' negate
>   fromInteger = NW . toEnum . (`mod` limit) . fromInteger
>     where limit = 1 + fromEnum (maxBound :: a)

Anyways, here we define the pretty-much-identical Num instance for NumWrapper. Now any Bounded Enum can be treated as a Num.

> magic :: Bool
> magic = getNW literal

'literal' was defined at the very beginning of the file, as 'literal = 0'. After this, 'literal :: NumWrapper Bool'. Then, we remove the NumWrapper, and get False. In fact, amusingly enough, for all that work, we've created an alias for 'toEnum' for literals called 'getNW'.

This is all pretty trivial, I think, but working through it even once still can be of use, so there.

-- N