{-# LANGUAGE CPP #-} {-| Module : Main Description : simple examples of using AERN-Real Copyright : (c) Michal Konecny License : BSD3 Maintainer : mik@konecny.aow.cz Stability : experimental Portability : portable Simple examples of using AERN-Real -} module Main where import qualified Data.Number.ER.Real as AERN import Data.Number.ER.Real (ConvergRealSeq(..), convertFuncRA2Seq) #ifdef USE_MPFR --type B = AERN.BAP -- use pure Haskell floats type B = AERN.BMAP -- use combination of double and pure Haskell floats --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 type R = ConvergRealSeq IRA one :: R one = 1 two :: R two = 2 piSeq :: R piSeq = ConvergRealSeq $ AERN.pi seqExp = convertFuncRA2Seq $ AERN.exp seqSine = convertFuncRA2Seq $ AERN.sin seqCosine = convertFuncRA2Seq $ AERN.cos main = do AERN.initialiseBaseArithmetic (0 :: RA) putStrLn "****************************" putStrLn "Testing interval arithmetic:" putStrLn "****************************" putStrLn "**** Fractions:" putStrLn $ "(default granularity, show internals) 1/3 =\n " ++ AERN.showApprox 30 True True (1/3 :: RA) putStrLn $ "(granularity 50, show internals) 1/3 =\n " ++ AERN.showApprox 30 True True ((AERN.setGranularity 50 1/3) :: RA) putStrLn $ "(granularity 100, show internals) 1/3 =\n " ++ AERN.showApprox 40 True True ((AERN.setGranularity 100 1/3) :: RA) putStrLn $ "(granularity 100, do not show internals) 1/3 =\n " ++ AERN.showApprox 40 True False ((AERN.setGranularity 100 1/3) :: RA) putStrLn $ "(granularity 100, default show) 1/3 =\n " ++ show ((AERN.setGranularity 100 1/3) :: RA) putStrLn "**** Exp:" putStrLn $ "(effort 5, granularity 50) exp 1 =\n " ++ (show $ AERN.exp 5 (AERN.setGranularity 50 (1::RA))) putStrLn $ "(effort 10, granularity 50) exp 1 =\n " ++ (show $ AERN.exp 10 (AERN.setGranularity 50 (1::RA))) putStrLn $ "(effort 10, granularity 100) exp 1 =\n " ++ (show $ AERN.exp 10 (AERN.setGranularity 100 (1::RA))) putStrLn $ "(effort 20, granularity 50) exp 1 =\n " ++ (show $ AERN.exp 20 (AERN.setGranularity 50 (1::RA))) putStrLn $ "(effort 20, granularity 100) exp 1 =\n " ++ (show $ AERN.exp 20 (AERN.setGranularity 100 (1::RA))) putStrLn "**** Pi:" putStrLn $ "(effort 10) pi =\n " ++ (show $ (AERN.pi 10 :: RA)) putStrLn $ "(effort 50) pi =\n " ++ (AERN.showApprox 20 True False $ (AERN.pi 50 :: RA)) putStrLn $ "(effort 100) pi =\n " ++ (AERN.showApprox 35 True False $ (AERN.pi 100 :: RA)) putStrLn $ "(effort 200) pi =\n " ++ (AERN.showApprox 65 True False $ (AERN.pi 200 :: RA)) putStrLn $ "(effort 400) pi =\n " ++ (AERN.showApprox 125 True False $ (AERN.pi 400 :: RA)) putStrLn "**** Sine:" putStrLn $ "(effort 10, granularity 50) sin 1 =\n " ++ (show $ AERN.sin 10 (AERN.setGranularity 50 (1::RA))) putStrLn $ "(effort 10, granularity 100) sin 1 =\n " ++ (show $ AERN.sin 10 (AERN.setGranularity 100 (1::RA))) putStrLn "**** Integration:" putStrLn $ "(effort 10, granularity 50) integrate exp 0 1 =\n " ++ (show $ AERN.integrateContAdapt_R AERN.exp 10 0 (AERN.setGranularity 50 (1::RA))) putStrLn $ "(effort 20, granularity 50) integrate exp 0 1 =\n " ++ (show $ AERN.integrateContAdapt_R AERN.exp 20 0 (AERN.setGranularity 50 (1::RA))) -- putStrLn $ -- "(effort 30, granularity 50) integrate exp 0 1 =\n " ++ -- (show $ AERN.integrateContAdapt_R AERN.exp 30 0 (AERN.setGranularity 50 (1::RA))) putStrLn "*****************************" putStrLn "Testing convergent sequences:" putStrLn "*****************************" -- putStrLn $ "1 =\n " ++ show one -- putStrLn $ "1 + 2 =\n " ++ (show $ one + two) putStrLn "**** Fractions:" putStrLn $ "(precision 20) 1/3 =\n " ++ (AERN.showConvergRealSeqAuto 20 $ one / 3) putStrLn $ "(precision 20) 100000000001/300000000000 =\n " ++ (AERN.showConvergRealSeqAuto 20 $ (one + 100000000000)/300000000000 ) putStrLn $ "100000000001/300000000000 =? 1/3:\n " ++ (show $ one/3 == 100000000001/300000000000) -- putStrLn $ "abs -1 = " ++ (show $ abs (- one)) -- putStrLn $ "neg 2 = " ++ (show $ negate two) -- putStrLn $ "1 + 2 = " ++ (show $ one + 2) putStrLn "**** Elementary:" putStrLn $ "(precision 30) exp 1 =\n " ++ (AERN.showConvergRealSeqAuto 30 $ seqExp one) putStrLn $ "(precision 500) pi =\n " ++ (AERN.showConvergRealSeqAuto 500 $ piSeq) putStrLn $ "(precision 30) cosine(1) =\n " ++ (AERN.showConvergRealSeqAuto 30 $ seqCosine one) putStrLn $ "(precision 30) sine(1) =\n " ++ (AERN.showConvergRealSeqAuto 30 $ seqSine one) putStrLn "**** Integration:" putStrLn $ -- very slow for precision > 4 "(precision 3) integrate exp 0 1 =\n " ++ (AERN.showConvergRealSeqAuto 3 $ AERN.integrateCont AERN.exp 0 one)