[Haskell-cafe] A new type of newtype --- Type-level instance diversification and resolution (tl; dr)

Albert Y. C. Lai trebla at vex.net
Fri May 26 01:26:19 UTC 2017


When you store elements in a binary search tree, wouldn't you love to 
custom-order the comparison order? Wouldn't you love to do so without 
newtype-wrapping the element type? In fact you may actually opine that 
your element type should not admit a standard order in the first place 
(e.g., complex numbers), and whichever order used for the sake of binary 
search trees should stay just that and not become a general-purpose default.

Perhaps more pressing to most people is when you store elements in a 
HashSet and you want to customize the hash function, again without 
either newtype-wrapping or fighting over defaults.

Here is how to do that.

Have a parameterized Ord class like this:

{-# LANGUAGE MultiParamTypeClasses, PolyKinds, KindSignatures #-}

class MyOrd (resolver :: k) a where
     mycmp :: p resolver -> a -> a -> Ordering

instance MyOrd () Int where
     mycmp _ x y = compare x y

data Rev

instance MyOrd Rev Int where
     mycmp _ x y = compare y x

It is also possible to get rid of the proxy parameter and use 
TypeApplication instead.

dmwit from IRC suggests that MyOrd could be tied back to standard Ord by:

instance MyOrd () a => Ord a

which helps with backward compatibility. So basically use () to resolve 
to the standard instances (wherever a community-wide standard makes 
sense) and have existing standard classes tied to the new parameterized 
classes by resolver ~ ().

Now use the parameterized Ord class for binary search trees:

{-# LANGUAGE ScopedTypeVariables #-}
import Data.Proxy(Proxy(Proxy))
import Data.List(foldl')

data BST (resolver :: k) a = Nil | Bin !(BST resolver a) a !(BST resolver a)

empty :: BST r a
empty = Nil

insert :: forall r a. MyOrd r a => a -> BST r a -> BST r a
insert a Nil = Bin Nil a Nil
insert a t@(Bin left key right) = case mycmp (Proxy :: Proxy r) a key of
   EQ -> t
   LT -> Bin (insert a left) key right
   GT -> Bin left key (insert a right)

fromList :: MyOrd r a => [a] -> BST r a
fromList xs = foldl' (flip insert) Nil xs

toAscList :: BST r a -> [a]
toAscList t = run t []
   where
     run Nil = id
     run (Bin left key right) = run left . (key :) . run right

Now we have it.

toAscList (fromList [3,1,4,15,9,2,6,5,38] :: BST () Int)
evaluates to
[1,2,3,4,5,6,9,15,38]

toAscList (fromList [3,1,4,15,9,2,6,5,38] :: BST Rev Int)
evaluates to
[38,15,9,6,5,4,3,2,1]

and both terms have the same type [Int]. The second term does not have 
to have type [Down Int].

Other applications include: Custom-making equivalence relations without 
calling them Eq; alternative interfaces to groupBy, sortBy, maximumBy, 
etc.; SML-style functorial programming; and liberating Complex from Ord.

I thank jadrian from IRC for proposing "named instance":

> so instead of "instance Num n => Monoid (Sum n) where" we'd write e.g. 
> "instance Sum of Num n => Monoid n where"   and use it as "Sum.mempty"

which stimulated me to think "oh we can emulate that by multiple 
parameter type class..."


More information about the Haskell-Cafe mailing list