{-# LANGUAGE CPP #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE DeriveDataTypeable #-} module Main where import qualified Data.Number.ER.Real as AERN import qualified Data.Number.ER.RnToRm as AERNFunc import Data.Number.ER.BasicTypes import Data.Number.ER.Misc import Data.Number.ER.RnToRm.TestingDefs import Data.Maybe import qualified Data.List as List import qualified Data.Map as Map #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 main = do AERN.initialiseBaseArithmetic (0 :: RA) putStrLn $ "ix = " ++ show ix ++ "; deg = " ++ show deg ++ "; gran = " ++ show gran -- putStrLn $ "sin(sin(sin(x))) = " ++ show sin3 -- putStrLn $ "integ(sin(sin(sin(x)))dx = " ++ show integrSin3 putStrLn $ "integ_0^1(sin(sin(sin(x)))dx] = " ++ show result putStrLn $ " precision = " ++ show (AERN.getPrecision result) where result = head $ AERNFunc.eval (AERNFunc.unary 1) integrSin3 integrSin3 = AERNFunc.integrateUnary 0 sin3 (0 AERN.\/ 1) 0 [0] ix = 100 deg = 50 size = 1000 gran = 5000 depth = 0 sin3 = AERN.sin ix $ AERN.sin ix $ AERN.sin ix $ AERNFunc.bisectUnbisectDepth depth $ AERNFunc.bisectUnbisectDepth depth $ AERNFunc.setMaxSize size $ AERNFunc.setMaxDegree deg fapwUPX0