[Haskell-cafe] About "Fun with type functions" example

Arnaud Bailly arnaud.oqube at gmail.com
Thu Nov 18 14:17:45 EST 2010


Hello,
I am trying to understand and use the Nat n type defined in the
aforementioned article. Unfortunately, the given code does not compile
properly:

Here is the code:

module Naturals where

data Zero
data Succ a

class Nat n where
  toInt :: n -> Int

instance Nat Zero where
  toInt _  = 0

instance (Nat n) => Nat (Succ n) where
  toInt   _ = 1 + toInt (undefined :: n)

type One = Succ Zero
type Two = Succ One

And here is the error:

D:\projets\sequencer>ghc Naturals.hs

Naturals.hs:16:18:
    Ambiguous type variable `n' in the constraint:
      `Nat n' arising from a use of `toInt' at Naturals.hs:16:18-39
    Probable fix: add a type signature that fixes these type variable(s)

I use 6.12.3 on Windows XP.

I am most probably missing an option but does not know which one.

Thanks in advance for any advice,
Arnaud


More information about the Haskell-Cafe mailing list