-- |
-- Module:      Math.NumberTheory.Zeta.Hurwitz
-- Copyright:   (c) 2018 Alexandre Rodrigues Baldé
-- Licence:     MIT
-- Maintainer:  Alexandre Rodrigues Baldé <alexandrer_b@outlook.com>
--
-- Hurwitz zeta function.

{-# LANGUAGE ScopedTypeVariables #-}

module Math.NumberTheory.Zeta.Hurwitz
  ( zetaHurwitz
  ) where

import Math.NumberTheory.Recurrences (bernoulli, factorial)
import Math.NumberTheory.Zeta.Utils  (skipEvens, skipOdds)

-- | Values of Hurwitz zeta function evaluated at @ζ(s, a)@ for @s ∈ [0, 1 ..]@.
--
-- The algorithm used was based on the Euler-Maclaurin formula and was derived
-- from <http://fredrikj.net/thesis/thesis.pdf Fast and Rigorous Computation of Special Functions to High Precision>
-- by F. Johansson, chapter 4.8, formula 4.8.5.
-- The error for each value in this recurrence is given in formula 4.8.9 as an
--  indefinite integral, and in formula 4.8.12 as a closed form formula.
--
-- It is the __user's responsibility__ to provide an appropriate precision for
-- the type chosen.
--
-- For instance, when using @Double@s, it does not make sense
-- to provide a number @ε < 1e-53@ as the desired precision. For @Float@s,
-- providing an @ε < 1e-24@ also does not make sense.
-- Example of how to call the function:
--
-- >>> zetaHurwitz 1e-15 0.25 !! 5
-- 1024.3489745265808
zetaHurwitz :: forall a . (Floating a, Ord a) => a -> a -> [a]
zetaHurwitz :: a -> a -> [a]
zetaHurwitz a
eps a
a = (a -> a -> a -> a) -> [a] -> [a] -> [a] -> [a]
forall a b c d. (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
zipWith3 (\a
s a
i a
t -> a
s a -> a -> a
forall a. Num a => a -> a -> a
+ a
i a -> a -> a
forall a. Num a => a -> a -> a
+ a
t) [a]
ss [a]
is [a]
ts
  where
    -- When given @1e-14@ as the @eps@ argument, this'll be
    -- @div (33 * (length . takeWhile (>= 1) . iterate (/ 10) . recip) 1e-14) 10 == div (33 * 14) 10@
    -- @div (33 * 14) 10 == 46.
    -- meaning @N,M@ in formula 4.8.5 will be @46@.
    -- Multiplying by 33 and dividing by 10 is because asking for @14@ digits
    -- of decimal precision equals asking for @(log 10 / log 2) * 14 ~ 3.3 * 14 ~ 46@
    -- bits of precision.
    digitsOfPrecision :: Integer
    digitsOfPrecision :: Integer
digitsOfPrecision =
       let magnitude :: Integer
magnitude = Int -> Integer
forall a. Integral a => a -> Integer
toInteger (Int -> Integer) -> (a -> Int) -> a -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([a] -> Int) -> (a -> [a]) -> a -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Bool) -> [a] -> [a]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (a -> a -> Bool
forall a. Ord a => a -> a -> Bool
>= a
1) ([a] -> [a]) -> (a -> [a]) -> a -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> a) -> a -> [a]
forall a. (a -> a) -> a -> [a]
iterate (a -> a -> a
forall a. Fractional a => a -> a -> a
/ a
10) (a -> [a]) -> (a -> a) -> a -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> a
forall a. Fractional a => a -> a
recip (a -> Integer) -> a -> Integer
forall a b. (a -> b) -> a -> b
$ a
eps
       in  Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
div (Integer
magnitude Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
33) Integer
10

    -- @a + n@
    aPlusN :: a
    aPlusN :: a
aPlusN = a
a a -> a -> a
forall a. Num a => a -> a -> a
+ Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
digitsOfPrecision

    -- @[(a + n)^s | s <- [0, 1, 2 ..]]@
    powsOfAPlusN :: [a]
    powsOfAPlusN :: [a]
powsOfAPlusN = (a -> a) -> a -> [a]
forall a. (a -> a) -> a -> [a]
iterate (a
aPlusN a -> a -> a
forall a. Num a => a -> a -> a
*) a
1

    -- [                   [      1      ] |                   ]
    -- | \sum_{k=0}^\(n-1) | ----------- | | s <- [0, 1, 2 ..] |
    -- [                   [ (a + k) ^ s ] |                   ]
    -- @S@ value in 4.8.5 formula.
    ss :: [a]
    ss :: [a]
ss = let numbers :: [a]
numbers = (Integer -> a) -> [Integer] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map ((a
a a -> a -> a
forall a. Num a => a -> a -> a
+) (a -> a) -> (Integer -> a) -> Integer -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> a
forall a. Num a => Integer -> a
fromInteger) [Integer
0..Integer
digitsOfPrecisionInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
-Integer
1]
             denoms :: [[a]]
denoms  = Int -> a -> [a]
forall a. Int -> a -> [a]
replicate (Integer -> Int
forall a. Num a => Integer -> a
fromInteger Integer
digitsOfPrecision) a
1 [a] -> [[a]] -> [[a]]
forall a. a -> [a] -> [a]
:
                       ([a] -> [a]) -> [a] -> [[a]]
forall a. (a -> a) -> a -> [a]
iterate ((a -> a -> a) -> [a] -> [a] -> [a]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith a -> a -> a
forall a. Num a => a -> a -> a
(*) [a]
numbers) [a]
numbers
         in ([a] -> a) -> [[a]] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map ([a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([a] -> a) -> ([a] -> [a]) -> [a] -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> a) -> [a] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map a -> a
forall a. Fractional a => a -> a
recip) [[a]]
denoms

    -- [ (a + n) ^ (1 - s)            a + n         |                   ]
    -- | ----------------- = ---------------------- | s <- [0, 1, 2 ..] |
    -- [       s - 1          (a + n) ^ s * (s - 1) |                   ]
    -- @I@ value in 4.8.5 formula.
    is :: [a]
    is :: [a]
is = let denoms :: [a]
denoms = (a -> Integer -> a) -> [a] -> [Integer] -> [a]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith
                      (\a
powOfA Integer
int -> a
powOfA a -> a -> a
forall a. Num a => a -> a -> a
* Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
int)
                      [a]
powsOfAPlusN
                      [-Integer
1, Integer
0..]
         in (a -> a) -> [a] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map (a
aPlusN a -> a -> a
forall a. Fractional a => a -> a -> a
/) [a]
denoms

    -- [      1      |             ]
    -- [ ----------- | s <- [0 ..] ]
    -- [ (a + n) ^ s |             ]
    constants2 :: [a]
    constants2 :: [a]
constants2 = (a -> a) -> [a] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map a -> a
forall a. Fractional a => a -> a
recip [a]
powsOfAPlusN

    -- [ [(s)_(2*k - 1) | k <- [1 ..]], s <- [0 ..]], i.e. odd indices of
    -- infinite rising factorial sequences, each sequence starting at a
    -- positive integer.
    pochhammers :: [[Integer]]
    pochhammers :: [[Integer]]
pochhammers = let -- [ [(s)_k | k <- [1 ..]], s <- [1 ..]]
                      pochhs :: [[Integer]]
                      pochhs :: [[Integer]]
pochhs = ([Integer] -> [Integer]) -> [Integer] -> [[Integer]]
forall a. (a -> a) -> a -> [a]
iterate (\(Integer
x : [Integer]
xs) -> (Integer -> Integer) -> [Integer] -> [Integer]
forall a b. (a -> b) -> [a] -> [b]
map (Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`div` Integer
x) [Integer]
xs) ([Integer] -> [Integer]
forall a. [a] -> [a]
tail [Integer]
forall a. (Num a, Enum a) => [a]
factorial)
                  in -- When @s@ is @0@, the infinite sequence of rising
                     -- factorials starting at @s@ is @[0,0,0,0..]@.
                     Integer -> [Integer]
forall a. a -> [a]
repeat Integer
0 [Integer] -> [[Integer]] -> [[Integer]]
forall a. a -> [a] -> [a]
: ([Integer] -> [Integer]) -> [[Integer]] -> [[Integer]]
forall a b. (a -> b) -> [a] -> [b]
map [Integer] -> [Integer]
forall a. [a] -> [a]
skipOdds [[Integer]]
pochhs

    -- [            B_2k           |             ]
    -- | ------------------------- | k <- [1 ..] |
    -- [ (2k)! (a + n) ^ (2*k - 1) |             ]
    second :: [a]
    second :: [a]
second =
        Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
take (Integer -> Int
forall a. Num a => Integer -> a
fromInteger Integer
digitsOfPrecision) ([a] -> [a]) -> [a] -> [a]
forall a b. (a -> b) -> a -> b
$
        (Rational -> Integer -> a -> a)
-> [Rational] -> [Integer] -> [a] -> [a]
forall a b c d. (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
zipWith3
        (\Rational
bern Integer
evenFac a
denom -> Rational -> a
forall a. Fractional a => Rational -> a
fromRational Rational
bern a -> a -> a
forall a. Fractional a => a -> a -> a
/ (a
denom a -> a -> a
forall a. Num a => a -> a -> a
* Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
evenFac))
        ([Rational] -> [Rational]
forall a. [a] -> [a]
tail ([Rational] -> [Rational]) -> [Rational] -> [Rational]
forall a b. (a -> b) -> a -> b
$ [Rational] -> [Rational]
forall a. [a] -> [a]
skipOdds [Rational]
forall a. Integral a => [Ratio a]
bernoulli)
        ([Integer] -> [Integer]
forall a. [a] -> [a]
tail ([Integer] -> [Integer]) -> [Integer] -> [Integer]
forall a b. (a -> b) -> a -> b
$ [Integer] -> [Integer]
forall a. [a] -> [a]
skipOdds [Integer]
forall a. (Num a, Enum a) => [a]
factorial)
        -- Recall that @powsOfAPlusN = [(a + n) ^ s | s <- [0 ..]]@, so this
        -- is @[(a + n) ^ (2 * s - 1) | s <- [1 ..]]@
        ([a] -> [a]
forall a. [a] -> [a]
skipEvens [a]
powsOfAPlusN)

    fracs :: [a]
    fracs :: [a]
fracs = ([Integer] -> a) -> [[Integer]] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map
            ([a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([a] -> a) -> ([Integer] -> [a]) -> [Integer] -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Integer -> a) -> [a] -> [Integer] -> [a]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (\a
s Integer
p -> a
s a -> a -> a
forall a. Num a => a -> a -> a
* Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
p) [a]
second)
            [[Integer]]
pochhammers

    -- Infinite list of @T@ values in 4.8.5 formula, for every @s@ in
    -- @[0, 1, 2 ..]@.
    ts :: [a]
    ts :: [a]
ts = (a -> a -> a) -> [a] -> [a] -> [a]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith
         (\a
constant2 a
frac -> a
constant2 a -> a -> a
forall a. Num a => a -> a -> a
* (a
0.5 a -> a -> a
forall a. Num a => a -> a -> a
+ a
frac))
         [a]
constants2
         [a]
fracs