Floating phi, round and even Fibonnaci numbers

I'm rather new to Haskell and need, in typical newbie style, a bit of help understanding the type system. The Nth even Fibonacci number, EF(n) can be defined by the recursive relation EF(0) = 2, EF(n) = [EF(n-1) * (phi**3)], where phi is the golden ratio and [] is the nearest integer function. An infinite lazy list of this sequence would be nice to have for my Project Euler, er, project. Defining phi thusly,
phi :: (Floating t) => t phi = (1+sqrt(5))/2
With phi in place, if I understood types properly (and if I understand iterate correctly as I think), the lazy list should be a relatively quick matter.
even_fibs :: (Num t) => [t] even_fibs = iterate (\x -> round(x * (phi**3))) 2
Dynamically typed even_fibs :: (Floating t, Integral t, RealFrac t) => [t], assuming I pass -fno-monomorphism-restriction to ghci. That's not at all the type I assumed even_fibs would take, as can be seen from above. So, I went on a bit of sojourn. Having seen the sights of the Haskell Report section 6.4, the marvels of the references cited in the wiki's article on the monomorphism restriction and the Gentle Introduction's chapter 10 I must say I'm rather more terribly confused than when I started out, possibly. Can someone explain where my type statements have gone wrong?

On 7/10/07, Brian L. Troutwine
I'm rather new to Haskell and need, in typical newbie style, a bit of help understanding the type system.
The Nth even Fibonacci number, EF(n) can be defined by the recursive relation EF(0) = 2, EF(n) = [EF(n-1) * (phi**3)], where phi is the golden ratio and [] is the nearest integer function. An infinite lazy list of this sequence would be nice to have for my Project Euler, er, project. Defining phi thusly,
phi :: (Floating t) => t phi = (1+sqrt(5))/2
With phi in place, if I understood types properly (and if I understand iterate correctly as I think), the lazy list should be a relatively quick matter.
even_fibs :: (Num t) => [t] even_fibs = iterate (\x -> round(x * (phi**3))) 2
Dynamically typed even_fibs :: (Floating t, Integral t, RealFrac t) => [t], assuming I pass -fno-monomorphism-restriction to ghci. That's not at all the type I assumed even_fibs would take, as can be seen from above. So, I went on a bit of sojourn. Having seen the sights of the Haskell Report section 6.4, the marvels of the references cited in the wiki's article on the monomorphism restriction and the Gentle Introduction's chapter 10 I must say I'm rather more terribly confused than when I started out, possibly.
That was your first mistake :-) (As a beginner, anyway.) Look at the type of round: Prelude> :t round round :: forall a b. (RealFrac a, Integral b) => a -> b So the argument x in the lambda-expression being passed to iterate must have a type that's an instance of RealFrac. It must also have a type that's an instance of Integral, since the result of multiplying it with phi gets passed into the next iteration. Finally, it has to have a type that's an instance of Floating, since phi is declared as a Floating. You can probably see the problem. Cheers, Tim -- Tim Chevalier* catamorphism.org *Often in error, never in doubt "There's no money in poetry, but there's no poetry in money, either." --Robert Graves

Brian L. Troutwine wrote:
phi :: (Floating t) => t phi = (1+sqrt(5))/2
even_fibs :: (Num t) => [t] even_fibs = iterate (\x -> round(x * (phi**3))) 2
*Main> :t iterate iterate :: forall a. (a -> a) -> a -> [a] *Main> :t round round :: forall a b. (RealFrac a, Integral b) => a -> b So the 'x' in your anonymous lambda must be (a->a) and the type 'a' must be an integral. You need to convert this Integral 'x' into something that can be used in the math (x * (phi**3)) which is where you need to insert fromIntegral:
even_fibs :: (Integral t) => [t] even_fibs = iterate (\x -> round(fromIntegral x * (phi**3))) 2
Which of course can be tested against
even_fibs_2 = filter even fibs where fibs = 1 : 1 : zipWith (+) (fibs) (tail fibs)
And the phi version fails at
head $ dropWhile (uncurry (==)) $ zip even_fibs even_fibs_2
Which is (37889062373143904,37889062373143906)

But that also depended on phi defaulting to Double in even_fibs. To be clearer:
even_fibs :: (Integral t) => [t] even_fibs = iterate (\x -> round(fromIntegral x * (dp**3))) 2 where dp :: Double dp = phi
The above is equivalent to the previous. The below uses less precision:
even_fibs' :: (Integral t) => [t] even_fibs' = iterate (\x -> round(fromIntegral x * (dp**3))) 2 where dp :: Float dp = phi
So it fails earlier:
head $ dropWhile (uncurry (==)) $ zip even_fibs' even_fibs_2 (14930353,14930352)

And using dynamic precision : http://haskell.org/haskellwiki/Applications_and_libraries/Mathematics#Dynami... The ERA package (darcs get http://darcs.augustsson.net/Darcs/CReal/) one can do better...
import CReal
even_fibs'' :: (Integral t) => [t] even_fibs'' = iterate (\x -> round(fromIntegral x * (dp**3))) 2 where dp :: CReal dp = phi
even_fibs_2 = filter even fibs where fibs = 1 : 1 : zipWith (+) (fibs) (tail fibs)
z n = take n $ zipWith (\a b -> (a==b,a)) even_fibs'' even_fibs_2
t z = not $ null $ filter fst $ z
main = let y = z 1000 in putStr . unlines . map show $ y
This works quite well.... (True,2) (True,8) (True,34) (True,144) (True,610) (True,2584) (True,10946) (True,46368) ...snip... (True,3987795824799770715342824788687062628452272409956636682999616408) (True,16892574194241670428824570378554538679120491007541580961500624834) (True,71558092601766452430641106302905217344934236440122960529002115744) ...

Brian, I am also a Haskell newbie, and unfortunately can not answer your type question, but wish to make a 'side comment'. The use of a floating point phi to calculate Fibonacci numbers makes me a bit nervous. In 'Structure and Interpretation of Computer Programs' 2n Edition Exercise 1.19 there is an algorithm for calculating the n'th Fibonacci number in order of log n steps. Take a look at: http://mitpress.mit.edu/sicp/full-text/sicp/book/node18.html I would use the type Integer, with this algorithm, for arbitrary precision Fibonacci numbers. My concern is that your lazy list will start to deviate at some point from Fibonacci numbers because of the floating point calculations. Comments welcome, and I look forward to seeing the experts answer your type question. Best Regards, Robert On Wednesday 11 July 2007 05:11, Brian L. Troutwine wrote:
I'm rather new to Haskell and need, in typical newbie style, a bit of help understanding the type system.
The Nth even Fibonacci number, EF(n) can be defined by the recursive relation EF(0) = 2, EF(n) = [EF(n-1) * (phi**3)], where phi is the golden ratio and [] is the nearest integer function. An infinite lazy list of this sequence would be nice to have for my Project Euler, er, project. Defining phi thusly,
phi :: (Floating t) => t phi = (1+sqrt(5))/2
With phi in place, if I understood types properly (and if I understand iterate correctly as I think), the lazy list should be a relatively quick matter.
even_fibs :: (Num t) => [t] even_fibs = iterate (\x -> round(x * (phi**3))) 2
Dynamically typed even_fibs :: (Floating t, Integral t, RealFrac t) => [t], assuming I pass -fno-monomorphism-restriction to ghci. That's not at all the type I assumed even_fibs would take, as can be seen from above. So, I went on a bit of sojourn. Having seen the sights of the Haskell Report section 6.4, the marvels of the references cited in the wiki's article on the monomorphism restriction and the Gentle Introduction's chapter 10 I must say I'm rather more terribly confused than when I started out, possibly.
Can someone explain where my type statements have gone wrong? _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hello Robert, Thanks for the comments. The lazy list with Double phi embedded does indeed begin to deviate, at the 81st Fibonacci number, if I'm not mistaken. Another fellow in this thread calculated the deviation points for Double, Float and CReal. By way of further explanation, I'm writing up various approaches and solutions to the problems posed at Project Euler, discussing the various defects to each approach, comparing the runtimes of solutions and, hopefully, deriving interesting tidbits of math along the way. The project was begun to improve my Haskell ability by exercising it in as many ways on a single idea as possible. I'd not thought of the algorithm you pointed out in SICP and will now happily include it. Thanks. Brian On Wednesday 11 July 2007 07:00:05 you wrote:
Brian,
I am also a Haskell newbie, and unfortunately can not answer your type question, but wish to make a 'side comment'. The use of a floating point phi to calculate Fibonacci numbers makes me a bit nervous. In 'Structure and Interpretation of Computer Programs' 2n Edition Exercise 1.19 there is an algorithm for calculating the n'th Fibonacci number in order of log n steps. Take a look at:
http://mitpress.mit.edu/sicp/full-text/sicp/book/node18.html
I would use the type Integer, with this algorithm, for arbitrary precision Fibonacci numbers. My concern is that your lazy list will start to deviate at some point from Fibonacci numbers because of the floating point calculations. Comments welcome, and I look forward to seeing the experts answer your type question.
Best Regards, Robert
On Wednesday 11 July 2007 05:11, Brian L. Troutwine wrote:
I'm rather new to Haskell and need, in typical newbie style, a bit of help understanding the type system.
The Nth even Fibonacci number, EF(n) can be defined by the recursive relation EF(0) = 2, EF(n) = [EF(n-1) * (phi**3)], where phi is the golden ratio and [] is the nearest integer function. An infinite lazy list of this sequence would be nice to have for my Project Euler, er, project. Defining phi thusly,
phi :: (Floating t) => t phi = (1+sqrt(5))/2
With phi in place, if I understood types properly (and if I understand iterate correctly as I think), the lazy list should be a relatively quick matter.
even_fibs :: (Num t) => [t] even_fibs = iterate (\x -> round(x * (phi**3))) 2
Dynamically typed even_fibs :: (Floating t, Integral t, RealFrac t) => [t], assuming I pass -fno-monomorphism-restriction to ghci. That's not at all the type I assumed even_fibs would take, as can be seen from above. So, I went on a bit of sojourn. Having seen the sights of the Haskell Report section 6.4, the marvels of the references cited in the wiki's article on the monomorphism restriction and the Gentle Introduction's chapter 10 I must say I'm rather more terribly confused than when I started out, possibly.
Can someone explain where my type statements have gone wrong? _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Brian, You are welcome. Are you talking about http://projecteuler.net/ ? I have been experimenting with various ways of learning Haskell, tackling an interesting set of mathematical problems sounds good. Best Regards, Robert On Thursday 12 July 2007 00:06, Brian L. Troutwine wrote:
Hello Robert,
Thanks for the comments. The lazy list with Double phi embedded does indeed begin to deviate, at the 81st Fibonacci number, if I'm not mistaken. Another fellow in this thread calculated the deviation points for Double, Float and CReal.
By way of further explanation, I'm writing up various approaches and solutions to the problems posed at Project Euler, discussing the various defects to each approach, comparing the runtimes of solutions and, hopefully, deriving interesting tidbits of math along the way. The project was begun to improve my Haskell ability by exercising it in as many ways on a single idea as possible. I'd not thought of the algorithm you pointed out in SICP and will now happily include it. Thanks.
Brian

You are welcome. Are you talking about http://projecteuler.net/ ? I have been experimenting with various ways of learning Haskell, tackling an interesting set of mathematical problems sounds good.
I am. It's turned out to be quite a fun approach and the one that seems to be the most effective, at least for me. On Thursday 12 July 2007 07:50:42 you wrote:
Brian,
You are welcome. Are you talking about http://projecteuler.net/ ? I have been experimenting with various ways of learning Haskell, tackling an interesting set of mathematical problems sounds good.
Best Regards, Robert
On Thursday 12 July 2007 00:06, Brian L. Troutwine wrote:
Hello Robert,
Thanks for the comments. The lazy list with Double phi embedded does indeed begin to deviate, at the 81st Fibonacci number, if I'm not mistaken. Another fellow in this thread calculated the deviation points for Double, Float and CReal.
By way of further explanation, I'm writing up various approaches and solutions to the problems posed at Project Euler, discussing the various defects to each approach, comparing the runtimes of solutions and, hopefully, deriving interesting tidbits of math along the way. The project was begun to improve my Haskell ability by exercising it in as many ways on a single idea as possible. I'd not thought of the algorithm you pointed out in SICP and will now happily include it. Thanks.
Brian
participants (4)
-
Brian L. Troutwine
-
haskell@list.mightyreason.com
-
Robert Daniel Emerson
-
Tim Chevalier