Rational and % operator remix

Hi, Thanks again for the help last night. The second function cf2 is an attempt to reverse the process of the first function, i.e., given a rational number it returns a list of integers, possibly infinite, but you shouldn't get into trouble if you use 98%67 as input (output should be [1,2,6,5]). The interpreter is complaining about the '=' following the 'in' keyword. Is there a better way to state this? Michael import Data.Ratio cf :: [Int] -> Rational cf (x:[]) = toRational x cf (x:xs) = toRational x + 1 / cf xs cf2 :: Rational -> [Int] cf2 a = let ai = toRational (floor ((numerator a) / (denominator a))) in if a = ai then [a] else ai : cf2 ((toRational 1) / (subtract ai a))

I think you probably mean ==, the comparison operator (function), not = (assignment in let-forms or where-forms) -Ross On Mar 29, 2009, at 1:40 PM, michael rice wrote:
Hi,
Thanks again for the help last night.
The second function cf2 is an attempt to reverse the process of the first function, i.e., given a rational number it returns a list of integers, possibly infinite, but you shouldn't get into trouble if you use 98%67 as input (output should be [1,2,6,5]). The interpreter is complaining about the '=' following the 'in' keyword. Is there a better way to state this?
Michael
import Data.Ratio cf :: [Int] -> Rational cf (x:[]) = toRational x cf (x:xs) = toRational x + 1 / cf xs
cf2 :: Rational -> [Int] cf2 a = let ai = toRational (floor ((numerator a) / (denominator a))) in if a = ai then [a] else ai : cf2 ((toRational 1) / (subtract ai a))
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

You can use floor in a Rational directly, no need to take it apart and divide.
There is no need to write (toRational 1), just write 1.
Don't write (subtract ai a), write (ai - i).
You also have a type error; the ai should no be a Rational, so you
need to move to toRational call to the comparison.
-- Lennart
2009/3/29 michael rice
Hi,
Thanks again for the help last night.
The second function cf2 is an attempt to reverse the process of the first function, i.e., given a rational number it returns a list of integers, possibly infinite, but you shouldn't get into trouble if you use 98%67 as input (output should be [1,2,6,5]). The interpreter is complaining about the '=' following the 'in' keyword. Is there a better way to state this?
Michael
import Data.Ratio cf :: [Int] -> Rational cf (x:[]) = toRational x cf (x:xs) = toRational x + 1 / cf xs
cf2 :: Rational -> [Int] cf2 a = let ai = toRational (floor ((numerator a) / (denominator a))) in if a = ai then [a] else ai : cf2 ((toRational 1) / (subtract ai a))
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Am Sonntag 29 März 2009 19:40:19 schrieb michael rice:
Hi,
Thanks again for the help last night.
The second function cf2 is an attempt to reverse the process of the first function, i.e., given a rational number it returns a list of integers, possibly infinite,
Not for rational numbers.
but you shouldn't get into trouble if you use 98%67 as input (output should be [1,2,6,5]). The interpreter is complaining about the '=' following the 'in' keyword.
That should be '=='.
Is there a better way to state this?
Michael
import Data.Ratio cf :: [Int] -> Rational cf (x:[]) = toRational x cf (x:xs) = toRational x + 1 / cf xs
cf2 :: Rational -> [Int] cf2 a = let ai = toRational (floor ((numerator a) / (denominator a))) in if a = ai then [a] else ai : cf2 ((toRational 1) / (subtract ai a))
import Data.List (unfoldr) cf3 :: Rational -> [Integer] -- Int may overflow cf3 0 = [0] cf3 x = a0:unfoldr f r where a0 = floor x r = x - fromInteger a0 f 0 = Nothing f y = Just (properFraction $ recip y)
participants (4)
-
Daniel Fischer
-
Lennart Augustsson
-
michael rice
-
Ross Mellgren