{-| Module : Data.Number.ER.RnToRm.UnitDom.ChebyshevBase.Polynom.Tests.Compose Description : (testing) properties of enclosure composition Copyright : (c) 2007-2008 Michal Konecny License : BSD3 Maintainer : mik@konecny.aow.cz Stability : experimental Portability : portable Quickcheck properties of polynomial enclosure composition. -} module Data.Number.ER.RnToRm.UnitDom.ChebyshevBase.Polynom.Tests.Compose where import Data.Number.ER.RnToRm.UnitDom.ChebyshevBase.Polynom.Compose import Data.Number.ER.RnToRm.UnitDom.ChebyshevBase.Polynom.Enclosure import Data.Number.ER.RnToRm.UnitDom.ChebyshevBase.Polynom.Ring import Data.Number.ER.RnToRm.UnitDom.ChebyshevBase.Polynom.Basic import Data.Number.ER.RnToRm.UnitDom.ChebyshevBase.Polynom.Tests.Generate import Data.Number.ER.Real.Approx.Interval import qualified Data.Number.ER.Real.DomainBox as DBox import Data.Number.ER.BasicTypes import Data.Number.ER.Misc import Test.QuickCheck prop_enclCompose_ThinEncl_consistent reportFileName (Deg20Size20 maxDegree maxSize, varSelector, (PSize30 (n1,p1)), (PSize30 (n2,p2))) = compose_encl_consistent reportFileName maxDegree maxSize varSelector n1 p1 n2 p2Encl where p2Encl = enclThin p2 prop_enclCompose_ThickEncl_consistent reportFileName (Deg20Size20 maxDegree maxSize, varSelector, (PSize30 (n1,p1)), (PSize30 (n21,p21), PSize30 (n22, p22))) = compose_encl_consistent reportFileName maxDegree maxSize varSelector n1 p1 (n21, n22) p2Encl where p2Encl = makeThickEncl maxDegree maxSize p21 p22 prop_enclCompose_ParalEncl_consistent reportFileName (Deg20Size20 maxDegree maxSize, varSelector, (PSize30 (n1, p1)), (SmallRatio w2Num w2Denom, PSize30 (n2, p2))) = compose_encl_consistent reportFileName maxDegree maxSize varSelector n1 p1 ((w2Num, w2Denom), n2) p2Encl where p2Encl = makeParalEncl p2 w2Num w2Denom compose_encl_consistent reportFileName maxDegree maxSize varSelector p1Id p1 p2Id p2Encl@(p2LowNeg, p2High) = -- unsafePrint -- ( -- "compose_encl_consistent: " -- ++ "\n p1 = " ++ show p1 -- ++ "\n substVar = " ++ show substVar -- ++ "\n p2Low = " ++ show (chplNeg p2LowNeg) -- ++ "\n p2High = " ++ show p2High -- ++ "\n composition = " ++ show resEncl -- ++ "\n**********************" -- ) $ enclAtKeyPointsConsistent reportFileName ((maxDegree, maxSize), varSelector, p1Id, p2Id) composeAtPointInner allVars resEncl where resEncl = enclCompose maxDegree maxSize p1 substVar p2Encl substVar = p1Vars !! (varSelector `mod` (length p1Vars)) p1Vars = chplGetVars p1 allVars = chplGetVars $ p1 +^ p2LowNeg +^ p2High p1Encl = (chplNeg p1, p1) composeAtPointInner point = -- unsafePrintReturn -- ( -- "\n point = " ++ show point -- ++ "\n substVar = " ++ show substVar -- ++ " substVal = " ++ show substVal -- ++ "\n result = " -- ) $ enclRAEvalInner p1Encl pointWithSubst where pointWithSubst = DBox.insert substVar substVal $ DBox.map (\b -> ERInterval b b) point substVal = enclEvalInner p2Encl point