[Haskell-cafe] strictness and the simple continued fraction

William Lee Irwin III wli at holomorphy.com
Sat Oct 9 15:33:53 EDT 2004


So, I discovered that simple continued fractions are supposed to be
spiffy lazy lists and thought I'd bang out some continued fraction code.
But then I discovered ContFrac.hs and couldn't really better it. Of
course, I went about trying to actually do things relying on their
laziness, and discovered they weren't as lazy as I hoped they'd be.
Simple uses of approximations at the ghci command line such as:

instance Ord ContFrac where 
        (ContFrac (x:xs)) `compare` (ContFrac (y:ys)) = 
                case x `compare` y of
                        LT -> LT
                        GT -> GT
                        EQ -> (ContFrac ys) `compare` (ContFrac xs)
        (ContFrac []) `compare` cf =
                case cf of
                        ContFrac (x:_) -> 0 `compare` x
                        ContFrac [] -> EQ
        cf `compare` (ContFrac []) =
                case cf of
                        ContFrac (x:_) -> x `compare` 0
                        ContFrac [] -> EQ

x = expCF (1/2)
	where
		expCF x	| x < 0 = recip . expCF $ negate x
			| x == 0 = 1
			| x == 1 = let ContFrac es = ecf
						in ContFrac (take 100 es)
			| otherwise = case x of
				ContFrac [y] -> (expCF 1)^y
				ContFrac (y:ys) -> if y /= 0
					then ((expCF 1)^y)
						*(expCF (ContFrac (0:ys)))
					else (1+x+x^2/2+x^3/6+x^4/24+x^5/120)
				ContFrac [] -> expCF 0

where the instance was added to ContFrac.hs seems to fail to terminate,
where manually reducing things a bit appears to restore termination.
So, what hit me?


-- wli


More information about the Haskell-Cafe mailing list