{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FlexibleInstances #-} module Test.MathObj.PowerSeries where import qualified MathObj.PowerSeries.Core as PS import qualified MathObj.PowerSeries.Example as PSE import Test.NumericPrelude.Utility (equalInfLists {- , testUnit -} ) -- import Test.QuickCheck (Property, quickCheck, (==>)) import qualified Test.HUnit as HUnit import NumericPrelude.Base as P import NumericPrelude.Numeric as NP identitiesExplODE, identitiesSeriesFunction, identitiesInverses :: [(String, Int, [Rational],[Rational])] identitiesExplODE = ("exp", 500, PSE.expExpl, PSE.expODE) : ("sin", 500, PSE.sinExpl, PSE.sinODE) : ("cos", 500, PSE.cosExpl, PSE.cosODE) : ("tan", 50, PSE.tanExpl, PSE.tanODE) : ("tan", 50, PSE.tanExpl, PSE.tanExplSieve) : ("tan", 50, PSE.tanODE, PSE.tanODESieve) : ("log", 500, PSE.logExpl, PSE.logODE) : ("asin", 50, PSE.asinODE, snd (PS.inv PSE.sinODE)) : ("atan", 500, PSE.atanExpl, PSE.atanODE) : ("sinh", 500, PSE.sinhExpl, PSE.sinhODE) : ("cosh", 500, PSE.coshExpl, PSE.coshODE) : ("atanh", 500, PSE.atanhExpl, PSE.atanhODE) : ("sqrt", 100, PSE.sqrtExpl, PSE.sqrtODE) : [] identitiesSeriesFunction = ("exp", 500, PSE.expExpl, PS.exp (\0 -> 1) [0,1]) : ("sin", 500, PSE.sinExpl, PS.sin (\0 -> (0,1)) [0,1]) : ("cos", 500, PSE.cosExpl, PS.cos (\0 -> (0,1)) [0,1]) : ("tan", 50, PSE.tanExpl, PS.tan (\0 -> (0,1)) [0,1]) : ("sqrt", 50, PSE.sqrtExpl, PS.sqrt (\1 -> 1) [1,1]) : ("power", 500, PSE.powExpl (-1/3), PS.pow (\1 -> 1) (-1/3) [1,1]) : ("power", 50, PSE.powExpl (-1/3), PS.exp (\0 -> 1) (PS.scale (-1/3) PSE.log)) : ("log", 500, PSE.logExpl, PS.log (\1 -> 0) [1,1]) : ("asin", 50, PSE.asin, PS.asin (\1 -> 1) (\0 -> 0) [0,1]) : -- ("acos", 50, PSE.acos, PS.acos (\1 -> 1) (\0 -> pi/2) [0,1]) : ("atan", 500, PSE.atan, PS.atan (\0 -> 0) [0,1]) : [] identitiesInverses = ("exp", 100, 1:1:repeat 0, PS.exp (\0 -> 1) PSE.log) : ("log", 100, 0:1:repeat 0, PS.log (\1 -> 0) PSE.exp) : ("tan", 50, 0:1:repeat 0, PS.tan (\0 -> (0,1)) PSE.atan) : ("atan", 50, 0:1:repeat 0, PS.atan (\0 -> 0) PSE.tan) : ("sin", 50, 0:1:repeat 0, PS.sin (\0 -> (0,1)) PSE.asin) : ("asin", 100, 0:1:repeat 0, PS.asin (\1 -> 1) (\0 -> 0) PSE.sin) : ("sqrt", 500, 1:1:repeat 0, PS.sqrt (\1 -> 1) (PS.mul [1,1] [1,1])) : [] testSeriesIdentity :: (String, Int, [Rational], [Rational]) -> HUnit.Test testSeriesIdentity (label, len, x, y) = HUnit.test (HUnit.assertBool label (equalInfLists len [x,y])) testSeriesIdentities :: String -> [(String, Int, [Rational], [Rational])] -> HUnit.Test testSeriesIdentities label ids = HUnit.TestLabel label $ HUnit.TestList $ map testSeriesIdentity ids checkSeriesIdentities :: [(String, Int, [Rational], [Rational])] -> [(String,Bool)] checkSeriesIdentities = map (\(label, len, x, y) -> (label, equalInfLists len [x,y])) powerMult :: Rational -> Rational -> Bool powerMult exp0 exp1 = PS.mul (PSE.pow exp0) (PSE.pow exp1) == PSE.pow (exp0+exp1) powerExplODE :: Rational -> Bool powerExplODE expon = PSE.powODE expon == PSE.powExpl expon tests :: HUnit.Test tests = HUnit.TestLabel "power series" $ HUnit.TestList [ testSeriesIdentities "explicit vs. ODE solution" identitiesExplODE, testSeriesIdentities "transcendent functions of series" identitiesSeriesFunction, testSeriesIdentities "inverses of some series" identitiesInverses {- HUnit.TestLabel "laws" $ HUnit.TestList $ map testUnit $ ("products of powers", quickCheck (powerMult)) : ("power explicit vs. ODE", quickCheck (powerExplODE)) : [] -} ]