1

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?

gilgamec
  • 357
  • 1
  • 6

2 Answers2

2

I think the problem is that GHC doesn't know that (1+d) is not 0 for any d.

To determine overlap, you only look to the right of =>. These overlap:

SumVectorSized 0
SumVectorSized d'

How can I get across that the instances don't overlap?

Add {-# OVERLAPPING #-} to the second instance.

Or is there another way to do this kind of induction?

This is one of many tricks to palliate the lack of dependent types in Haskell. A reasonable solution is to turn to a dependently typed language like Idris or Agda, where induction can actually be formulated as a plain function.

A less radical alternative is to go through a Peano-like singleton type:

data NatS (n :: Nat) where
  ZS :: NatS 0
  SS :: (n' ~ (n-1), n ~ (1 + n')) => NatS n' -> NatS n

The technique you described requires a new type class for every operation you want to perform, requiring duplication of that unsightly trick with overlapping instances. You only need one of those classes to convert a KnownNat constraint into a NatS singleton value, and then everything else is a plain function:

sumVS :: NatS n -> V.Vector n Int -> Int
sumVS ZS _ = 0
sumVS (SS n) v = V.head v + sumVS (V.tail v)
Li-yao Xia
  • 31,896
  • 2
  • 33
  • 56
1

You can implement matching on KnownNats like so

matchKnownNat :: forall n r. KnownNat n => Proxy# n -> (n ~ 0 => r) -> (forall m. (KnownNat m, n ~ (1 + m)) => Proxy# m -> r) -> r
matchKnownNat n z s = case natVal' n of
    0 | Refl <- (unsafeCoerce Refl :: n :~: 0) -> z
    n | SomeNat (m :: Proxy m) <- someNatVal (n - 1), Refl <- (unsafeCoerce Refl :: n :~: 1 + m) -> s (proxy# @_ @m)

sumVS can be implemented in terms of this match.

sumVS :: forall n. KnownNat n => V.Vector n Int -> Int
sumVS = matchKnownNat (proxy# @_ @n) (\_ -> 0) (\_ vec -> V.head vec + sumVS (V.tail vec))

Note that it's is redundant to require KnownNat n and V.Vector n Int. All sized vectors already know their own size:

sumVS' :: forall n. V.Vector n Int -> Int
sumVS' v = V.knownLength v (sumVS v)
HTNW
  • 27,182
  • 1
  • 32
  • 60
  • I imagine you might as well offer `n ~ (1 + m), n ~ (m + 1)` using `unsafeCoerce Refl :: '(n, n) :~: '(1 + m, m + 1)`. Just a tiny bit less inconvenient. – dfeuer Feb 21 '20 at 03:22
  • @dfeuer Sure, but it's not needed here. Also, it would be better to state that property as its own `addComm :: forall n m. n + m :~: m + n` before using that in `matchKnownNat`. Band-aiding ad hoc axioms wherever it seems "convenient" is not a good plan. Every bit of complexity added to an `unsafedCoerce`'d axiom is a potential error. – HTNW Feb 21 '20 at 04:50
  • But one thing you surely want to do is index `r` so you can use this as a general induction principle.... – dfeuer Feb 21 '20 at 05:09
  • @dfeuer `r` can already depend on `n`. `annoying :: forall n r. KnownNat n => r 0 -> (forall m. KnownNat m => Proxy# m -> r (1 + m)) -> r n` (as I think you want) is no more powerful than this version and is much less convenient, because you have to a) think about which occurrences of `n` in `r` you want to replace, b) have to duplicate hypotheses and all that if you want to rewrite in them, and c) write out a whole new data type practically for every use. This just lets GHC manage the rewriting. `annoying z s = matchKnownNat (proxy# @_ @n) z s` (reverse direction left as exercise :P) – HTNW Feb 21 '20 at 05:17
  • So the `unsafeCoerce` here is basically being used to specify a type axiom which is being brought into scope by the pattern match? – gilgamec Feb 24 '20 at 08:53
  • @gilgamec Correct. – HTNW Feb 24 '20 at 18:04