[Haskell-cafe] Using parallels for fibonacci
Mario Lang
mlang at delysid.org
Wed May 11 15:34:51 UTC 2016
Michael Litchard <michael at schmong.org> writes:
> I am trying to efficiently use multicores for my fizzbuzz
> <https://github.com/mlitchard/swiftfizz> project. My fizzbuzz uses a
> Fibonacci generator as input, and this is where it can get computationally
> heavy. I believe I have picked the best algorithm for my project (please
> correct this if wrong),
I'd like to point you to this rather interesting task and code example I
happened to stumble across recently:
https://www.youtube.com/watch?v=32f6JrQPV8c (18:30-21:40)
https://github.com/sean-parent/scratch/blob/master/scratch/main.cpp
Sean is basically saying that doing fibonacci via recursion is wrong.
Fibonacci is actually a linear recurrance, and can be calculated with a
power algorithm.
The Haskell Wiki has a section about this approach:
https://wiki.haskell.org/The_Fibonacci_sequence#Using_2x2_matrices
The code below gives fib of 100000000 in a few seconds on my PC.
No need to go paralell.
And if you need the complete series, [fib n | n <- [1..1000000]] still
just takes a second here.
```Haskell
module PowerFib where
import Data.List (transpose)
newtype Matrix a = Matrix [[a]] deriving (Eq, Show)
instance Num a => Num (Matrix a) where
Matrix as + Matrix bs = Matrix (zipWith (zipWith (+)) as bs)
Matrix as - Matrix bs = Matrix (zipWith (zipWith (-)) as bs)
Matrix as * Matrix bs = Matrix [[sum $ zipWith (*) a b | b <- transpose bs] | a <- as]
negate (Matrix as) = Matrix (map (map negate) as)
fromInteger x = Matrix (iterate (0:) (fromInteger x : repeat 0))
abs m = m
signum _ = 1
apply (Matrix as) b = [sum (zipWith (*) a b) | a <- as]
fib n = head (apply (Matrix [[0,1], [1,1]] ^ n) [0,1])
```
--
CYa,
⡍⠁⠗⠊⠕
More information about the Haskell-Cafe
mailing list