{-# LANGUAGE CPP #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE DeriveDataTypeable #-} module Main where import qualified Data.Number.ER.Real as AERN import Data.Number.ER.Real (ConvergRealSeq(..), convertFuncRA2Seq) import Data.Number.ER.BasicTypes import Data.Number.ER.Misc import Data.Maybe #ifdef USE_MPFR type B = AERN.BMPFR -- use MPFR floats #else type B = AERN.BAP -- use pure Haskell floats --type B = AERN.BMAP -- use combination of double and pure Haskell floats #endif type RA = AERN.RA B type IRA = AERN.IRA B decimalPrec = 100 --decimalPrec = 1000 binaryPrec = fromInteger $ toInteger $ snd $ AERN.integerBounds $ (fromInteger decimalPrec :: RA) * (AERN.log 100 10)/(AERN.log 100 2) main = do AERN.initialiseBaseArithmetic (0 :: RA) putStrLn $ show decimalPrec ++ " decimal digits of pi = \n" ++ (AERN.showConvergRealSeqAuto binaryPrec pi) where pi :: ConvergRealSeq RA pi = ConvergRealSeq AERN.pi