Copyright | (c) 2016 Andrew Lelechenko |
---|---|
License | MIT |
Maintainer | Andrew Lelechenko <andrew.lelechenko@gmail.com> |
Safe Haskell | Safe |
Language | Haskell2010 |
Bilinear recurrent sequences and Bernoulli numbers, roughly covering Ch. 5-6 of Concrete Mathematics by R. L. Graham, D. E. Knuth and O. Patashnik.
Note on memory leaks and memoization. Top-level definitions in this module are polymorphic, so the results of computations are not retained in memory. Make them monomorphic to take advantages of memoization. Compare
>>>
:set +s
>>>
binomial !! 1000 !! 1000 :: Integer
1 (0.01 secs, 1,385,512 bytes)>>>
binomial !! 1000 !! 1000 :: Integer
1 (0.01 secs, 1,381,616 bytes)
against
>>>
let binomial' = binomial :: [[Integer]]
>>>
binomial' !! 1000 !! 1000 :: Integer
1 (0.01 secs, 1,381,696 bytes)>>>
binomial' !! 1000 !! 1000 :: Integer
1 (0.01 secs, 391,152 bytes)
Synopsis
- binomial :: Integral a => [[a]]
- stirling1 :: (Num a, Enum a) => [[a]]
- stirling2 :: (Num a, Enum a) => [[a]]
- lah :: Integral a => [[a]]
- eulerian1 :: (Num a, Enum a) => [[a]]
- eulerian2 :: (Num a, Enum a) => [[a]]
- bernoulli :: Integral a => [Ratio a]
- euler :: forall a. Integral a => [a]
- eulerPolyAt1 :: forall a. Integral a => [Ratio a]
- faulhaberPoly :: Integral a => Int -> [Ratio a]
Documentation
binomial :: Integral a => [[a]] Source #
Infinite zero-based table of binomial coefficients (also known as Pascal triangle):
binomial !! n !! k == n! / k! / (n - k)!
.
>>>
take 5 (map (take 5) binomial)
[[1],[1,1],[1,2,1],[1,3,3,1],[1,4,6,4,1]]
Complexity: binomial !! n !! k
is O(n) bits long, its computation
takes O(k n) time and forces thunks binomial !! n !! i
for 0 <= i <= k
.
Use the symmetry of Pascal triangle binomial !! n !! k == binomial !! n !! (n - k)
to speed up computations.
One could also consider binomial
to compute stand-alone values.
stirling1 :: (Num a, Enum a) => [[a]] Source #
Infinite zero-based table of Stirling numbers of the first kind.
>>>
take 5 (map (take 5) stirling1)
[[1],[0,1],[0,1,1],[0,2,3,1],[0,6,11,6,1]]
Complexity: stirling1 !! n !! k
is O(n ln n) bits long, its computation
takes O(k n^2 ln n) time and forces thunks stirling1 !! i !! j
for 0 <= i <= n
and max(0, k - n + i) <= j <= k
.
One could also consider unsignedStirling1st
to compute stand-alone values.
stirling2 :: (Num a, Enum a) => [[a]] Source #
Infinite zero-based table of Stirling numbers of the second kind.
>>>
take 5 (map (take 5) stirling2)
[[1],[0,1],[0,1,1],[0,1,3,1],[0,1,7,6,1]]
Complexity: stirling2 !! n !! k
is O(n ln n) bits long, its computation
takes O(k n^2 ln n) time and forces thunks stirling2 !! i !! j
for 0 <= i <= n
and max(0, k - n + i) <= j <= k
.
One could also consider stirling2nd
to compute stand-alone values.
lah :: Integral a => [[a]] Source #
Infinite one-based table of Lah numbers.
lah !! n !! k
equals to lah(n + 1, k + 1).
>>>
take 5 (map (take 5) lah)
[[1],[2,1],[6,6,1],[24,36,12,1],[120,240,120,20,1]]
Complexity: lah !! n !! k
is O(n ln n) bits long, its computation
takes O(k n ln n) time and forces thunks lah !! n !! i
for 0 <= i <= k
.
eulerian1 :: (Num a, Enum a) => [[a]] Source #
Infinite zero-based table of Eulerian numbers of the first kind.
>>>
take 5 (map (take 5) eulerian1)
[[],[1],[1,1],[1,4,1],[1,11,11,1]]
Complexity: eulerian1 !! n !! k
is O(n ln n) bits long, its computation
takes O(k n^2 ln n) time and forces thunks eulerian1 !! i !! j
for 0 <= i <= n
and max(0, k - n + i) <= j <= k
.
eulerian2 :: (Num a, Enum a) => [[a]] Source #
Infinite zero-based table of Eulerian numbers of the second kind.
>>>
take 5 (map (take 5) eulerian2)
[[],[1],[1,2],[1,8,6],[1,22,58,24]]
Complexity: eulerian2 !! n !! k
is O(n ln n) bits long, its computation
takes O(k n^2 ln n) time and forces thunks eulerian2 !! i !! j
for 0 <= i <= n
and max(0, k - n + i) <= j <= k
.
bernoulli :: Integral a => [Ratio a] Source #
Infinite zero-based sequence of Bernoulli numbers,
computed via connection
with stirling2
.
>>>
take 5 bernoulli
[1 % 1,(-1) % 2,1 % 6,0 % 1,(-1) % 30]
Complexity: bernoulli !! n
is O(n ln n) bits long, its computation
takes O(n^3 ln n) time and forces thunks stirling2 !! i !! j
for 0 <= i <= n
and 0 <= j <= i
.
One could also consider bernoulli
to compute stand-alone values.
euler :: forall a. Integral a => [a] Source #
The same sequence as euler'
, but with type [a]
instead of [Ratio a]
as the denominators in euler'
are always 1
.
>>>
take 10 euler :: [Integer]
[1,0,-1,0,5,0,-61,0,1385,0]
eulerPolyAt1 :: forall a. Integral a => [Ratio a] Source #
Infinite zero-based list of the n
-th order Euler polynomials evaluated at 1
.
The algorithm used was derived from Algorithms for Bernoulli numbers and Euler numbers
by Kwang-Wu Chen, third formula of the Corollary in page 7.
Element-by-element division of sequences A1986631
and A006519 in OEIS.
>>>
take 10 eulerPolyAt1 :: [Rational]
[1 % 1,1 % 2,0 % 1,(-1) % 4,0 % 1,1 % 2,0 % 1,(-17) % 8,0 % 1,31 % 2]