
Hi. Please, tell me where I'm wrong and how to improve my approach. I'm trying to simplify algebraic expressions this way: import Data.Ratio data Func = Const (Ratio Int) | Pow (Ratio Int) | Add Func Func | Mul Func Func instance Show Func where show (Const n) = "(" ++ show n ++ ")" show (Pow n) | n == 0 = "1" | n == 1 = "x" | otherwise = "(x**(" ++ show n ++ "))" show (Add t1 t2) ="(" ++ (show t1) ++ "+" ++ (show t2) ++ ")" show (Mul t1 t2) ="(" ++ (show t1) ++ "*" ++ (show t2) ++ ")" deriv (Const _) = Const 0 deriv (Pow 1) = Const 1 deriv (Pow n) = Const n `Mul` Pow (n-1) deriv (Add a b) = deriv a `Add` deriv b deriv (Mul a b) = Add (deriv a `Mul` b) (a `Mul` deriv b) p0 = Const 1 p1 = p0 `Add` (Mul (Pow 1) (Const 2)) p2 = p1 `Add` (Mul (Pow 2) (Const 3)) s rdc (Const x) = Const x s rdc (Pow 0) = Const 1 s rdc (Pow x) = Pow x s rdc (Add (Const a) (Const b)) = Const (a+b) s rdc (Mul (Const 0) _) = Const 0 s rdc (Mul _ (Const 0)) = Const 0 s rdc (Mul (Const a) (Const b)) = Const (a*b) s rdc (Mul (Pow n) (Pow m)) = Pow (n+m) s rdc (Add x (Const 0)) = rdc x s rdc (Add (Const 0) x) = rdc x s rdc (Mul (Const m) (Mul (Const n) x)) = rdc $ Mul (Const (n*m)) (rdc x) s rdc (Mul x (Const 1)) = rdc x s rdc (Mul x (Const a)) = rdc $ Mul (Const a) (rdc x) s rdc (Mul (Const 1) x) = rdc x s rdc (Mul x (Add a b)) = Mul (rdc x) (rdc a) `Add` Mul (rdc x) (rdc b) s rdc (Mul (Add a b) x) = Mul (rdc a) (rdc x) `Add` Mul (rdc b) (rdc x) s rdc (Mul a b) = rdc a `Mul` rdc b s rdc (Add a b) = rdc a `Add` rdc b fix f = f (fix f) The result I got is : *Main> fix s $ deriv p2 (((2 % 1)+(0 % 1))+(((6 % 1)*x)+(0 % 1))) instead of the anticipated expression ((2 % 1)+((6 % 1)*x)). And worst of all, I must apply (fix s) repeatedly to achieve correct answer: *Main> fix s $ fix s $ deriv p2 ((2 % 1)+((6 % 1)*x)). I'll be very much appriciated for any help and useful links.