I'm trying to figure out how to do type-level induction on KnownNats. A toy example, summing up sized vectors from vector-sized:
{-# LANGUAGE FlexibleInstances, UndecidableInstances #-}
{-# LANGUAGE TypeFamilies, TypeApplications, TypeOperators #-}
{-# LANGUAGE RankNTypes, DataKinds #-}
module Main where
import GHC.TypeNats
import qualified Data.Vector.Sized as V
class KnownNat d => SumVectorSized d where
sumVS :: V.Vector d Int -> Int
instance SumVectorSized 0 where
sumVS _ = 0
instance (SumVectorSized d, KnownNat d', d' ~ (1+d)) => SumVectorSized d' where
sumVS vec = V.head vec + sumVS (V.tail vec)
main = do
let Just vec = V.fromList @4 [1..4]
print $ sumVS vec
When compiled, this gives an error:
• Overlapping instances for SumVectorSized 0
arising from a use of ‘sumVS’
Matching instances:
instance SumVectorSized 0 -- Defined at src/Main.hs:14:10
instance (SumVectorSized d, KnownNat d', d' ~ (1 + d)) =>
SumVectorSized d'
-- Defined at src/Main.hs:17:10
I think the problem is that GHC doesn't know that (1+d) is not 0 for any d. How can I get across that the instances don't overlap? Or is there another way to do this kind of induction?