I started this post not long after its predecessor, but ended up forgetting about it.In the previous post about polyvariadic functions, we gave some examples of how to define them in haskell using typeclass trickery. The final definitions were, however, very repetitive, as we had to define a typeclass for each of the functions. Our handy list of our ghc-specific language extensions.{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
In the previous post, while I did mention type families, I did not use them anywhere. Functional dependencies are an alternative, but the general concensus is to move away from these due to inference problems.Like functions are to terms, type families are to types. Type families enable you to write type level functions. We’re going to use this to implement some way of determining what the result type is of a function.type family PolyRes r where
PolyRes (a -> r) = PolyRes r
PolyRes r = r
This definition essentially recursively searches for the result type by proceeding into the right-hand side of function types. So a type signature like Int -> Int -> Int -> [Int]
, which we would like append
to have in append 1 2 3
, would map to [Int]
. We can use this type family to define generic variants of the various typeclasses from the previous post. In this particular instance, we will attempt to write a polyvariadic variant of the fold function using this Poly
typeclass.The typical type signature of a fold function, using foldr
as an example, follows (a -> b -> b) -> b -> [a] -> b
, where a
is the argument type and b
is the result type. We can use this as inspiration to determine what the type signature will be of our generic polyvariant fold. We already know PolyRes r
will represent our result type, so the expression becomes (a -> PolyRes r -> PolyRes r) -> PolyRes r -> [a] -> r
. Note that the last instance of r
isn’t prefixed by PolyRes, this is because we will be outputting the polyvariant function, not its result. Finally, we can also remove the argument list [a]
as our arguments will be coming in incrementally at each instance resolution step at function type, a -> r
. So our final type signature is (a -> PolyRes r -> PolyRes r) -> PolyRes r -> r
.class Poly a r where
poly :: (a -> PolyRes r -> PolyRes r) -> PolyRes r -> r
This definition, however, would require that the user would have to define an annoying amount of superfluous instances. To see why, remember how a fold is usually defined.foldr f z [] = z
foldr f z (x : xs) = f x (foldr f xs)
As we’re working with typeclasses, we will have to implement the first or base case of foldr
as an instance for each of the types we want to use as a result type of our function. This amounts to the following boilerplate.instance Poly a Bool where
poly f r = r
instance Poly a Int where
poly f r = r
Using the default instance language extension, we can define the base case of the fold straight into the typeclass itself. So our typeclass definition now becomes:class Poly a r where
poly :: (a -> PolyRes r -> PolyRes r) -> PolyRes r -> r
default poly :: (r ~ PolyRes r) =>
(a -> PolyRes r -> PolyRes r) ->
PolyRes r -> r
poly f r = r
instance Poly a Bool
instance Poly a Integer
instance Poly a [r]
The above definition of poly
in our typeclass kind of encompasses what we would expect the base case of a fold
function to look like. The combining step, we will implement using our instance for function terms, where we assert that we have an argument of type a
compatible with the function given to poly
, a -> PolyRes r -> PolyRes r
.instance Poly a r => Poly a (a -> r) where
poly :: (a -> PolyRes r -> PolyRes r) -> PolyRes r -> a -> r
poly f r a = poly f (f a r)
This instance for function types can be interpreted as: each time poly is treated as a function, we have an argument of type a
that we can use to do a single application of the fold. After which we proceed with a recursive call to poly
.Now we can straightforwardly define polyvariadic variants of common list functions. Note that the type signatures are required as otherwise, the type checker has problems inferring the correct types. Unfortunately, the PolyRes r ~ whatever
type equality constraints don’t provide ghc with enough type information to be able to use the below functions ‘as is’. They have to be type annotated on usage, so in the form of cons' True False True :: [Bool]
, etc.and' :: (Poly Bool r, PolyRes r ~ Bool) => r
and' = poly (&&) True
or' :: (Poly Bool r, PolyRes r ~ Bool) => r
or' = poly (||) False
cons' :: (Poly a r, PolyRes r ~ [a]) => r
cons' = poly (:) []
fold' :: (Poly a r, PolyRes r ~ s) => (a -> s -> s) -> s -> r
fold' = poly
As an excercise, try implementing a variation of Poly
that gathers the given arguments in a list and then applies a function [a] -> PolyRes r
. This variant could be used to convert any function on lists to its corresponding polyvariadic counterpart.