Is it possible to do type-level arithmetic without UndeciableInstances?

{-# LANGUAGE TypeFamilies #-} module PeanoArith
data Z = Z data S n = S n
So, this type family works just fine:
type family Plus a b type instance Plus Z b = b type instance Plus (S a) b = S (Plus a b)
As does this one:
type family Minus a b type instance Minus a Z = Z type instance Minus Z (S b) = Z type instance Minus (S a) (S b) = Minus a b
But this one doesn't work without UndecidableInstances:
type family Times a b type instance Times Z b = Z type instance Times (S a) b = Plus b (Times a b)
I tried several different implementations for Times but I was unable to come up with one that passed the type family termination checker. Is there a way to do so? Some examples of attempts:
-- (a+1)*(b+1) = ab + a + b + 1 type family Times1 a b type instance Times1 Z Z = Z type instance Times1 (S n) Z = Z type instance Times1 Z (S n) = Z type instance Times1 (S a) (S b) = S (Plus (Times1 a b) (Plus a b))
-- inline Plus type family Times2_H a b acc type Times2 a b = Times2_H a b Z type instance Times2_H a b (S acc) = S (Times2_H a b acc) type instance Times2_H Z b Z = Z type instance Times2_H (S a) b Z = Times2_H a b b
Do you have any other ideas? Is (a*b) too big for the termination checker to ever accept? -- ryan

On Fri, Jun 05, 2009 at 01:58:33PM -0700, Ryan Ingram wrote:
I tried several different implementations for Times but I was unable to come up with one that passed the type family termination checker. Is there a way to do so?
Here is a solution. I don't understand exactly why this works while various simpler things don't. {-# LANGUAGE TypeFamilies, TypeOperators, KindSignatures #-} data Z = Z data S n = S n newtype Id a = Id a newtype (a :. b) c = O (a (b c)) type family Expand x type instance Expand Z = Z type instance Expand (S a) = S (Expand a) type instance Expand (Id a) = Expand a type instance Expand ((a :. b) c) = Expand (a (b c)) type family (f :: * -> *) :^ n :: * -> * type instance f :^ Z = Id type instance f :^ (S a) = f :. (f :^ a) type Plus a = S :^ a type Times a b = Expand ((Plus a :^ b) Z) {- *Main> undefined :: Times (S (S Z)) (S (S (S Z))) <interactive>:1:0: No instance for (Show (S (S (S (S (S (S Z))))))) arising from a use of `print' at <interactive>:1:0-41 Possible fix: add an instance declaration for (Show (S (S (S (S (S (S Z))))))) In a stmt of a 'do' expression: print it -} Regards, Reid

This is a bit beyond my normal level of expertise, but if I understand it correctly the type checker is normally limited to type functions that are "primitive recursive" (http://en.wikipedia.org/wiki/Primitive_recursive_function). This means that they are guaranteed to terminate, but on the other hand the resulting language is not Turing complete. Setting UndecidableInstances lifts the Primitive Recursive restriction, making the type checker Turing Complete, but also creating the potential for endless loops. So yes, you can do type arithmetic without UndecidableInstances, provided you limit yourself to the Primitive Recursive axioms. The Wikipedia page lists them, and turning them into Haskell type classes shouldn't be more than a few milli-Olegs. Paul.
participants (3)
-
Paul Johnson
-
Reid Barton
-
Ryan Ingram