The problem is that you are using &#39;suc&#39; as if it is a constructor: ((suc m) `eq` (suc n) =  m `eq` n)<br>You&#39;ll have to change it to something else, and it will probably require adding an unpacking function to your class and it will probably be messy.<br>
I&#39;d suggest you make use of the Eq typeclass and defined the Eq instances separately:<br><br>class (Eq n) =&gt; Peano2 n where<br> one :: n<br> plus :: n -&gt; n -&gt; n<br> suc :: n -&gt; n<br> suc a = a `plus` one<br>
<br>- Job<br><br><div class="gmail_quote">On Thu, Sep 17, 2009 at 2:36 PM, pat browne <span dir="ltr">&lt;<a href="mailto:Patrick.Browne@comp.dit.ie" target="_blank">Patrick.Browne@comp.dit.ie</a>&gt;</span> wrote:<br>
<blockquote class="gmail_quote" style="border-left: 1px solid rgb(204, 204, 204); margin: 0pt 0pt 0pt 0.8ex; padding-left: 1ex;">Hi,<br>
Below are two attempts to define Peano arithmetic in Haskell.<br>
The first attempt, Peano1, consists of just a signature in the class<br>
with the axioms in the instance. In the second attempt, Peano2, I am<br>
trying to move the axioms into the class. The reason is, I want to put<br>
as much specification as possible into the class. Then I would like to<br>
include properties in the class such as commutativity something like:<br>
infixl 5 `com`<br>
com :: Int -&gt; Int -&gt; Int<br>
x `com` y  = (x + y)<br>
commutative com a b = (a `com` b) == (b `com` a)<br>
<br>
I seem to be able to include just one default equation the Peano2 attempt.<br>
Any ideas?<br>
I have looked at<br>
<a href="http://www.haskell.org/haskellwiki/Peano_numbers" target="_blank">http://www.haskell.org/haskellwiki/Peano_numbers</a><br>
<br>
Regards,<br>
Pat<br>
<br>
-- Attempt 1<br>
-- In this attempt the axioms are in the instance and things seem OK<br>
module Peano1 where<br>
infixl 6 `eq`<br>
infixl 5 `plus`<br>
<br>
class Peano1 n where<br>
 suc :: n -&gt; n<br>
 eq :: n -&gt; n -&gt; Bool<br>
 plus :: n -&gt; n -&gt; n<br>
<br>
data Nat = One | Suc Nat deriving Show<br>
<br>
<br>
instance  Peano1 Nat where<br>
 suc = Suc<br>
 One `eq` One = True<br>
 (Suc m) `eq` (Suc n) =  m `eq` n<br>
 _`eq`_  = False<br>
 m `plus` One = Suc m<br>
 m `plus` (Suc n) = Suc (m `plus` n)<br>
-- Evaluation *Peano1&gt; Suc(One) `plus` ( Suc (One))<br>
<br>
<br>
<br>
<br>
<br>
-- Attempt 2<br>
-- In this attempt the axioms are in the class and things are not OK.<br>
module Peano2 where<br>
infixl 6 `eq`<br>
infixl 5 `plus`<br>
<br>
class Peano2 n where<br>
  one :: n<br>
  eq :: n -&gt; n -&gt; Bool<br>
  plus :: n -&gt; n -&gt; n<br>
  suc :: n -&gt; n<br>
  suc a = a `plus` one<br>
<br>
{-<br>
 I cannot add the remaining default axioms<br>
  one `eq` one = True<br>
  (suc m) `eq` (suc n) =  m `eq` n<br>
  (suc a) `eq` (suc b) =  a `eq` b<br>
  _`eq`_  = False<br>
-}<br>
<br>
_______________________________________________<br>
Haskell-Cafe mailing list<br>
<a href="mailto:Haskell-Cafe@haskell.org" target="_blank">Haskell-Cafe@haskell.org</a><br>
<a href="http://www.haskell.org/mailman/listinfo/haskell-cafe" target="_blank">http://www.haskell.org/mailman/listinfo/haskell-cafe</a><br>
</blockquote></div><br>