{-
	Copyright (C) 2011 Dr. Alistair Ward

	This program is free software: you can redistribute it and/or modify
	it under the terms of the GNU General Public License as published by
	the Free Software Foundation, either version 3 of the License, or
	(at your option) any later version.

	This program is distributed in the hope that it will be useful,
	but WITHOUT ANY WARRANTY; without even the implied warranty of
	MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
	GNU General Public License for more details.

	You should have received a copy of the GNU General Public License
	along with this program.  If not, see <https://www.gnu.org/licenses/>.
-}
{- |
 [@AUTHOR@]	Dr. Alistair Ward

 [@DESCRIPTION@]	Defines a specific base-@2^16@ /BBP/-formula; <https://mathworld.wolfram.com/PiFormulas.html>

-}

module Factory.Math.Implementations.Pi.BBP.Base65536(
-- * Constants
	series
) where

import qualified	Factory.Math.Implementations.Pi.BBP.Series	as Math.Implementations.Pi.BBP.Series

-- | Defines the parameters of this specific series.
series :: Math.Implementations.Pi.BBP.Series.Series
series :: Series
series	= MkSeries :: [Integer] -> (Int -> [Integer]) -> Rational -> Integer -> Series
Math.Implementations.Pi.BBP.Series.MkSeries {
	numerators :: [Integer]
Math.Implementations.Pi.BBP.Series.numerators		= ((Integer -> Integer) -> Integer -> Integer)
-> [Integer -> Integer] -> [Integer] -> [Integer]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (Integer -> Integer) -> Integer -> Integer
forall a b. (a -> b) -> a -> b
($) ([Integer -> Integer] -> [Integer -> Integer]
forall a. [a] -> [a]
cycle [Integer -> Integer
forall a. a -> a
id, Integer -> Integer
forall a. a -> a
id, Integer -> Integer
forall a. a -> a
id, Integer -> Integer
forall a. Num a => a -> a
negate]) ([Integer] -> [Integer]) -> [Integer] -> [Integer]
forall a b. (a -> b) -> a -> b
$ (Integer -> Integer) -> [Integer] -> [Integer]
forall a b. (a -> b) -> [a] -> [b]
map (Integer
2 Integer -> Integer -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^) [Integer
15 :: Integer, Integer
14, Integer
14, Integer
12, Integer
11, Integer
10, Integer
10, Integer
8, Integer
7, Integer
6, Integer
6, Integer
4, Integer
3, Integer
2, Integer
2, Integer
0],
	getDenominators :: Int -> [Integer]
Math.Implementations.Pi.BBP.Series.getDenominators	= \Int
i -> (Integer -> Integer) -> [Integer] -> [Integer]
forall a b. (a -> b) -> [a] -> [b]
map (Integer
32 Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+) [Integer
2, Integer
3, Integer
4, Integer
7, Integer
10, Integer
11, Integer
12, Integer
15, Integer
18, Integer
19, Integer
20, Integer
23, Integer
26, Integer
27, Integer
28, Integer
31],
	seriesScalingFactor :: Rational
Math.Implementations.Pi.BBP.Series.seriesScalingFactor	= Rational -> Rational
forall a. Fractional a => a -> a
recip (Rational -> Rational) -> Rational -> Rational
forall a b. (a -> b) -> a -> b
$ Rational
2 Rational -> Int -> Rational
forall a b. (Num a, Integral b) => a -> b -> a
^ (Int
13 :: Int),
	base :: Integer
Math.Implementations.Pi.BBP.Series.base			= Integer
2 Integer -> Int -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ (Int
16 :: Int)
}