I'm trying to create a polyvariadic function in Haskell, I used this answer to create a basic function. Here is the function's code :
class SumRes r where
sumOf :: Integer -> r
instance SumRes Integer where
sumOf = id
instance (Integral a, SumRes r) => SumRes (a -> r) where
sumOf x = sumOf . (x +) . toInteger
But the problem is : when the function is called without any arguments, it does not work.
Couldn't match expected type 'Integer' with actual type 'Integer -> r0'
Probable cause: 'sumOf' is applied to too few arguments
For example, I would like to be able to write sumOf :: Integer
and have this function return 0
.
How should I do this ?
The simplest version only works for Integer
results.
This works off what you already wrote, taking advantage of the fact that 0
is the identity for addition.
class SumRes r where
sumOf' :: Integer -> r
instance SumRes Integer where
sumOf' = toInteger
instance (Integral b, SumRes r) => SumRes (b -> r) where
sumOf' a b = sumOf' $! a + toInteger b
sumOf :: SumRes r => r
sumOf = sumOf' 0
The two instances, Integer
and b -> r
, inherently don't overlap.
To get more general result types, you need a somewhat different approach, because the two instances described above mush together if Integer
is replaced by a type variable. You can do this with MultiParamTypeClasses
and TypeFamilies
.
{-# LANGUAGE ScopedTypeVariables, AllowAmbiguousTypes, DataKinds,
KindSignatures, TypeApplications, MultiParamTypeClasses,
TypeFamilies, FlexibleInstances #-}
module SumRes2 where
data Nat = Z | S Nat
class SumRes (c :: Nat) r where
sumOf' :: Integer -> r
type family CountArgs a :: Nat where
CountArgs (_ -> r) = 'S (CountArgs r)
CountArgs _ = 'Z
instance Num r => SumRes 'Z r where
sumOf' = fromInteger
instance (Integral b, SumRes n r) => SumRes ('S n) (b -> r) where
sumOf' a b = sumOf' @n (a + toInteger b)
sumOf :: forall r n. (SumRes n r, CountArgs r ~ n) => r
sumOf = sumOf' @n 0
The only limitation is that if you have an Integral
instance for a function type, you can't use sumOf
to produce it. That shouldn't really be a problem though. I've used TypeApplications
and AllowAmbiguousTypes
for brevity, but you can certainly use proxy passing or Tagged
instead.