Copyright | (c) 2011 Daniel Fischer |
---|---|
License | MIT |
Maintainer | Daniel Fischer <daniel.is.fischer@googlemail.com> |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Efficient calculation of linear recurrent sequences, including Fibonacci and Lucas sequences.
Documentation
factorial :: (Num a, Enum a) => Infinite a Source #
Infinite zero-based table of factorials.
>>>
take 5 factorial
[1,1,2,6,24]
The time-and-space behaviour of factorial
is similar to described in
Math.NumberTheory.Recurrences.Bilinear.
factorialFactors :: Word -> [(Prime Word, Word)] Source #
Prime factors of a factorial.
factorialFactors n == factorise (factorial !! n)
>>>
factorialFactors 10
[(Prime 2,8),(Prime 3,4),(Prime 5,2),(Prime 7,1)]
fibonacci :: Num a => Int -> a Source #
calculates the fibonacci
kk
-th Fibonacci number in
O(log (abs k)
) steps. The index may be negative. This
is efficient for calculating single Fibonacci numbers (with
large index), but for computing many Fibonacci numbers in
close proximity, it is better to use the simple addition
formula starting from an appropriate pair of successive
Fibonacci numbers.
fibonacciPair :: Num a => Int -> (a, a) Source #
returns the pair fibonacciPair
k(F(k), F(k+1))
of the k
-th
Fibonacci number and its successor, thus it can be used to calculate
the Fibonacci numbers from some index on without needing to compute
the previous. The pair is efficiently calculated
in O(log (abs k)
) steps. The index may be negative.
lucasPair :: Num a => Int -> (a, a) Source #
computes the pair lucasPair
k(L(k), L(k+1))
of the k
-th
Lucas number and its successor. Very similar to
.fibonacciPair
generalLucas :: Num a => a -> a -> Int -> (a, a, a, a) Source #
calculates the quadruple generalLucas
p q k(U(k), U(k+1), V(k), V(k+1))
where U(i)
is the Lucas sequence of the first kind and V(i)
the Lucas
sequence of the second kind for the parameters p
and q
, where p^2-4q /= 0
.
Both sequences satisfy the recurrence relation A(j+2) = p*A(j+1) - q*A(j)
,
the starting values are U(0) = 0, U(1) = 1
and V(0) = 2, V(1) = p
.
The Fibonacci numbers form the Lucas sequence of the first kind for the
parameters p = 1, q = -1
and the Lucas numbers form the Lucas sequence of
the second kind for these parameters.
Here, the index must be non-negative, since the terms of the sequence for
negative indices are in general not integers.