{-| Module : Main Description : simple examples of using AERN-RnToRm Copyright : (c) Michal Konecny License : BSD3 Maintainer : mik@konecny.aow.cz Stability : experimental Portability : portable Simple examples of using AERN-RnToRm. -} module Main where import qualified Data.Number.ER.RnToRm as AERNFunc import qualified Data.Number.ER.Real.DomainBox as DBox import qualified Data.Number.ER.Real as AERN import Data.Number.ER.Misc type B = AERN.BM -- use machine double as a basis type RA = AERN.RA B type IRA = AERN.IRA B type FAPWP = AERNFunc.FAPWP B -- function f(x) = x for x in [0,1]: x :: FAPWP x = AERNFunc.setMaxDegree 2 $ AERNFunc.proj (DBox.fromAscList [(0,(0) AERN.\/ 1)]) 0 -- function f(x1) = x1 for x1 in [0,1]: x1 :: FAPWP x1 = AERNFunc.setMaxDegree 2 $ AERNFunc.proj (DBox.fromAscList [(1,(0) AERN.\/ 1)]) 1 -- domains combined automatically: fn1 :: FAPWP fn1 = 2*x + x1 -- ensure the piecewise representation has 4 segments: fn1depth2 :: FAPWP fn1depth2 = AERNFunc.bisectUnbisectDepth 2 fn1 -- apply sine pointwise to the function enclosure: fn2 :: FAPWP fn2 = -- AERN.sin 10 fn1depth2 AERN.sin 15 fn1depth2 -- evaluate the function at point x = 0.1, x1 = 0.1: fn2at0101 :: IRA [fn2at0101] = AERNFunc.eval (DBox.fromList [(0,0.1), (1,0.1)]) fn2 -- partially evaluate fn2 at x1 = 1: fn3 :: FAPWP fn3 = AERNFunc.partialEval (DBox.fromList [(1,1)]) fn2 -- integrate fn3 by x with value 1 at origin x = 1: fn4 :: FAPWP fn4 = AERNFunc.integrate ix fn2 var span origin value where ix = 2 -- effort index var = 0 span = DBox.noinfo -- integrate over the whole domain origin = 1 value = 1 -- integrate fn2 by x1 with value (1 - x) at origin x1 = 0: fn5 :: FAPWP fn5 = AERNFunc.integrate ix fn2 var span origin value where ix = 2 -- effort index var = 1 span = DBox.noinfo -- integrate over the whole domain origin = 0 value = 1 - x main = do AERN.initialiseBaseArithmetic (0 :: RA) putStrLn "****************************************" putStrLn "Testing polynomial enclosure arithmetic:" putStrLn "****************************************" putStrLn "**** Projections:" putStrLn $ "x =\n " ++ show x putStrLn $ "\nx1 =\n " ++ show x1 putStrLn "\n**** Merging domains:" putStrLn $ "2*x + x1 =\n " ++ showHead 12 fn1 putStrLn "\n**** Bisection depth 2:" putStrLn $ "2*x + x1 =\n " ++ showHead 17 fn1depth2 putStrLn "\n**** Elementary functions:" putStrLn $ "sin(2*x + x1) =\n " ++ showHead 17 fn2 putStrLn "\n**** Evaluation:" putStrLn $ "sin(2*x + x1)[x = 0.1, x1 = 0.1] = sin(0.3) = \n " ++ show fn2at0101 putStrLn "\n**** Partial evaluation:" putStrLn $ "sin(2*x + x1)[x1 = 1] = sin(5*x + 1) = \n " ++ showHead 15 fn3 putStrLn "\n**** Integration of 1-dim function:" putStrLn $ "f(x) = (Int sin(2*x + 1) dx) [f(1) = 1] =\n " ++ showHead 15 fn4 putStrLn "\n**** Integration of 2-dim function:" putStrLn $ "f(x,x1) = (Int sin(2*x + x1) dx1) [f(x,1) = 1 - x] =\n " ++ showHead 17 fn5 showHead n = showFirstLastLines n 0