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

{-# LANGUAGE ScopedTypeVariables #-}

module Math.NumberTheory.Zeta.Dirichlet
  ( betas
  , betasEven
  , betasOdd
  ) where

import Data.ExactPi
import Data.List                      (zipWith4)
import Data.Ratio                     ((%))

import Math.NumberTheory.Recurrences  (euler, factorial)
import Math.NumberTheory.Zeta.Hurwitz (zetaHurwitz)
import Math.NumberTheory.Zeta.Utils   (intertwine, skipOdds)

-- | Infinite sequence of exact values of Dirichlet beta-function at odd arguments, starting with @β(1)@.
--
-- >>> import Data.ExactPi
-- >>> approximateValue (betasOdd !! 25) :: Double
-- 0.9999999999999987
-- >>> import Data.Number.Fixed
-- >>> approximateValue (betasOdd !! 25) :: Fixed Prec50
-- 0.99999999999999999999999960726927497384196726751694
betasOdd :: [ExactPi]
betasOdd :: [ExactPi]
betasOdd = (Integer -> Rational -> ExactPi)
-> [Integer] -> [Rational] -> [ExactPi]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Integer -> Rational -> ExactPi
Exact [Integer
1, Integer
3 ..] ([Rational] -> [ExactPi]) -> [Rational] -> [ExactPi]
forall a b. (a -> b) -> a -> b
$ (Rational -> Integer -> Integer -> Integer -> Rational)
-> [Rational] -> [Integer] -> [Integer] -> [Integer] -> [Rational]
forall a b c d e.
(a -> b -> c -> d -> e) -> [a] -> [b] -> [c] -> [d] -> [e]
zipWith4
                                     (\Rational
sgn Integer
denom Integer
eul Integer
twos -> Rational
sgn Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* (Integer
eul Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% (Integer
twos Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
denom)))
                                     ([Rational] -> [Rational]
forall a. [a] -> [a]
cycle [Rational
1, -Rational
1])
                                     ([Integer] -> [Integer]
forall a. [a] -> [a]
skipOdds [Integer]
forall a. (Num a, Enum a) => [a]
factorial)
                                     ([Integer] -> [Integer]
forall a. [a] -> [a]
skipOdds [Integer]
forall a. Integral a => [a]
euler)
                                     ((Integer -> Integer) -> Integer -> [Integer]
forall a. (a -> a) -> a -> [a]
iterate (Integer
4 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
*) Integer
4)

-- | Infinite sequence of approximate values of the Dirichlet @β@ function at
-- positive even integer arguments, starting with @β(0)@.
betasEven :: forall a. (Floating a, Ord a) => a -> [a]
betasEven :: a -> [a]
betasEven a
eps = (a
1 a -> a -> a
forall a. Fractional a => a -> a -> a
/ a
2) a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
hurwitz
  where
    hurwitz :: [a]
    hurwitz :: [a]
hurwitz =
        (a -> a -> a -> a) -> [a] -> [a] -> [a] -> [a]
forall a b c d. (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
zipWith3 (\a
quarter a
threeQuarters a
four ->
            (a
quarter a -> a -> a
forall a. Num a => a -> a -> a
- a
threeQuarters) a -> a -> a
forall a. Fractional a => a -> a -> a
/ a
four)
        ([a] -> [a]
forall a. [a] -> [a]
tail ([a] -> [a]) -> ([a] -> [a]) -> [a] -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> [a]
forall a. [a] -> [a]
skipOdds ([a] -> [a]) -> [a] -> [a]
forall a b. (a -> b) -> a -> b
$ a -> a -> [a]
forall a. (Floating a, Ord a) => a -> a -> [a]
zetaHurwitz a
eps a
0.25)
        ([a] -> [a]
forall a. [a] -> [a]
tail ([a] -> [a]) -> ([a] -> [a]) -> [a] -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> [a]
forall a. [a] -> [a]
skipOdds ([a] -> [a]) -> [a] -> [a]
forall a b. (a -> b) -> a -> b
$ a -> a -> [a]
forall a. (Floating a, Ord a) => a -> a -> [a]
zetaHurwitz a
eps a
0.75)
        ((a -> a) -> a -> [a]
forall a. (a -> a) -> a -> [a]
iterate (a
16 a -> a -> a
forall a. Num a => a -> a -> a
*) a
16)

-- | Infinite sequence of approximate (up to given precision)
-- values of Dirichlet beta-function at integer arguments, starting with @β(0)@.
--
-- >>> take 5 (betas 1e-14) :: [Double]
-- [0.5,0.7853981633974483,0.9159655941772189,0.9689461462593694,0.9889445517411051]
betas :: (Floating a, Ord a) => a -> [a]
betas :: a -> [a]
betas a
eps = a
e a -> [a] -> [a]
forall a. a -> [a] -> [a]
: a
o a -> [a] -> [a]
forall a. a -> [a] -> [a]
: (a -> a -> a) -> [a] -> [a]
forall a. (a -> a -> a) -> [a] -> [a]
scanl1 a -> a -> a
forall a. (Ord a, Fractional a) => a -> a -> a
f ([a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
intertwine [a]
es [a]
os)
  where
    a
e : [a]
es = a -> [a]
forall a. (Floating a, Ord a) => a -> [a]
betasEven a
eps
    a
o : [a]
os = (ExactPi -> a) -> [ExactPi] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map ((a -> a -> Bool) -> [Rational] -> a
forall a. Fractional a => (a -> a -> Bool) -> [Rational] -> a
getRationalLimit (\a
a a
b -> a -> a
forall a. Num a => a -> a
abs (a
a a -> a -> a
forall a. Num a => a -> a -> a
- a
b) a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
eps) ([Rational] -> a) -> (ExactPi -> [Rational]) -> ExactPi -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ExactPi -> [Rational]
rationalApproximations) [ExactPi]
betasOdd

    -- Cap-and-floor to improve numerical stability:
    -- 1 > beta(n + 1) - 1 > (beta(n) - 1) / 2
    -- A similar method is used in @Math.NumberTheory.Zeta.Riemann.zetas@.
    f :: a -> a -> a
f a
x a
y = a
1 a -> a -> a
forall a. Ord a => a -> a -> a
`min` (a
y a -> a -> a
forall a. Ord a => a -> a -> a
`max` (a
1 a -> a -> a
forall a. Num a => a -> a -> a
+ (a
x a -> a -> a
forall a. Num a => a -> a -> a
- a
1) a -> a -> a
forall a. Fractional a => a -> a -> a
/ a
2))