<div class="gmail_quote"><br><br>Why?<div><br></div><div>real numbers, complex nuimbers, n-dimensional spaces have well defined + and * operations (vectorial product in the latter case).</div><div><br></div><div>even algebraic expressions like:</div>
<div>
<br></div><div>data Expr = Var String | Number Integer | Sin Expr | Cos Expr</div><div><br></div><div><br></div><div>can be instances of Num and express certain simplification rules in the definition.</div><div><br></div>

<div>instance Num Expr where</div><div>  ...</div><div> (Sin x) * (Cos x) = (Sin (2 * x))/2</div><div> ...</div><div><br></div><div><br></div><div>I started to develop a extensible symbolic math manipulation around the idea of using symbolic expressions as instances of Num and other basic classes. But I leaved it out due to lack of time.</div>

<div><br></div><div>By the way I attach it just in case anyone want to get some idea from it:</div><div><br></div><div><br></div><div><div>module DynAlgebra where</div><div><br></div><div>data Dyn= forall a.(Num a, Eq a, Show a, Ord a, Read a, Simplify a)=&gt; Dyn a</div>

<div><br></div><div>instance Show Dyn where</div><div>   show (Dyn a)= show a</div><div><br></div><div>instance Eq Dyn where</div><div>    (Dyn a) == (Dyn b)= solve a== solve b</div><div><br></div><div>class Simplify a where</div>

<div>  simplify :: a -&gt; a</div><div>  solve    :: a -&gt; Polonomial Expr1</div><div><br></div><div>data Polonomial e  =  e  :/ e  | e :+ e  | e :* e    deriving Show</div><div><br></div><div>data Expr1= Var String | I Integer   | Pi | E   deriving Show</div>

<div><br></div><div>-- Integer :/ Integer for exact rational arithmetic</div><div><br></div><div>data Expr= Polinomial Expr  | Formula Dyn deriving (Show, Eq)</div><div><br></div><div><br></div><div>instance Num (Polonomial Expr1) where</div>

<div> fromInteger = I</div><div> (+) (I a) (I b)= I (a+b)</div><div> (+) e1 e2  = e1 :+ e2</div><div><br></div><div> (*) (I a) (I b)= I (a*b)</div><div> (*) e1 e2 = (:*) e1 e2</div><div> </div><div> abs (I x) | x&gt;=0 = I x </div>

<div>           | otherwise = I (-x)</div><div> signum (I x) | x &gt;= 0 = 1 </div><div>              | otherwise= -1</div><div><br></div><div>instance Ord Polonomial  where</div><div> compare  (I a) (I b)= compare a b</div>

<div> compare  ( x :+ z)  y | x &lt; y &amp;&amp; z &gt;0 = LT</div><div>                       | x &gt; y &amp;&amp; z &gt;0 = GT</div><div><br></div><div> compare   y ( x :+ z) | y &gt; x &amp;&amp; z &gt;0 = LT</div><div>

                       | y &gt; x &amp;&amp; z &gt;0 = GT</div><div><br></div><div>instance Eq Polonomial  where</div><div>   (I a) == (I b) = a == b</div><div><br></div><div>   </div><div>   (I a :+ I b)== ( I c :+ I d)= a + b== c + d</div>

<div>   (I a :* I b)== ( I c :* I d)= a * b== c * d</div><div class="im"><div><br></div><div>   (a :+ b)== (c :+ d)= a==c &amp;&amp; b == d</div></div><div>   (a :* b)== (c :* d)= a== c &amp;&amp; b == d</div><div>   (a :/ b)== (c :/ d)= a * d == b * c</div>

<div>   </div><div>   exp1 == exp2 = simplify exp1== simplify exp2</div><div><br></div><div>            </div><div>             </div><div>instance Simplify  (Polonomial Expr1) where</div><div>  solve  x = simplify x     </div>

<div><br></div><div>  simplify ( (I x) :/ (I y))=  case quotRem x y   of</div><div>                      (q,0) -&gt; I q</div><div>                      (q,r) -&gt; let m= mcd y r in (I(x `div` m)) :/  (I(y `div` m)) </div>

<div> </div><div>  simplify ((I a) :+ (I b))= I (a + b)</div><div>  simplify ((I a) :* (I b))= I (a * b)</div><div>  </div><div>  </div><div>  simplify ((a :* b) :+ (c :* d)) | a == c = simplify $  a * (b :+d)</div><div>
  simplify (exp1 :+ exp2) = simplify exp1 :+ simplify exp2</div>
<div>  simplify (exp1 :* exp2) = simplify exp1 :* simplify exp2</div><div><br></div><div>  simplify expr= expr</div><div><br></div><div>mcd x y= case mod x y of</div><div>           0 -&gt; y</div><div>           t -&gt; mcd y t</div>

<div>  </div><div>  </div><div>subst:: Polonomial  -&gt; [(String, Polonomial )] -&gt; Polonomial </div><div>subst exp l= subs1 exp where</div><div> subs1 (Var v)= case lookup v l of</div><div>                 Nothing -&gt; Var v</div>

<div>                 Just e  -&gt; e</div><div> subs1 (e1 :+ e2) = ((subs1 e1) :+ (subs1 e2))</div><div> subs1 (e1 :* e2) = ((subs1 e1) :* (subs1 e2))</div><div> subs1 (e1 :/ e2) = ((subs1 e1) :/ (subs1 e2))</div><div><br>

</div><div> subst e= e</div><div><br></div><div>f x= x :* x</div><div><br></div><div><br></div><div><br></div><div>main= print  $ solve  $ 2 :+1</div><div><br></div><div><br></div><div class="gmail_quote">2009/10/5 Miguel Mitrofanov <span dir="ltr">&lt;<a href="mailto:miguelimo38@yandex.ru" target="_blank">miguelimo38@yandex.ru</a>&gt;</span><div>
<div></div><div class="h5"><br>
<blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><div><br>
<br>
Sönke Hahn wrote:<br>
<br>
<blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">
I used to implement<br>
<br>
    fromInteger n = (r, r) where r = fromInteger n<br>
<br>
, but thinking about it, <br>
    fromInteger n = (fromInteger n, 0)<br>
<br>
seems very reasonable, too. <br>
</blockquote>
<br></div>
Stop pretending something is a number when it&#39;s not.<div><div></div><div><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>
</div></div></blockquote></div></div></div><br></div>
</div><br>