{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} {-| Module : Data.Number.ER.RnToRm.UnitDom.ChebyshevBase.Polynom Description : polynoms in the Chebyshev basis of the 1st kind Copyright : (c) 2007-2008 Michal Konecny License : BSD3 Maintainer : mik@konecny.aow.cz Stability : experimental Portability : portable Arithmetic of multivariate polynomials represented by their coefficients it the Chebyshev basis. The polynomials are never to be used outside the domain @[-1,1]^n@. All operations are rounded in such a way that the resulting polynomial is a /point-wise upper or lower bound/ of the exact result. -} module Data.Number.ER.RnToRm.UnitDom.ChebyshevBase.Polynom ( ERChebPoly(..), TermKey ) where import Data.Number.ER.RnToRm.UnitDom.ChebyshevBase.Polynom.Basic import Data.Number.ER.RnToRm.UnitDom.ChebyshevBase.Polynom.Field import Data.Number.ER.RnToRm.UnitDom.ChebyshevBase.Polynom.Eval import Data.Number.ER.RnToRm.UnitDom.ChebyshevBase.Polynom.Bounds import Data.Number.ER.RnToRm.UnitDom.ChebyshevBase.Polynom.Integration import Data.Number.ER.RnToRm.UnitDom.ChebyshevBase.Polynom.Elementary import qualified Data.Number.ER.RnToRm.UnitDom.Base as UFB import qualified Data.Number.ER.Real.Base as B import Data.Number.ER.Real.Approx.Interval import Data.Number.ER.Real.DomainBox (VariableID(..), DomainBox, DomainBoxMappable, DomainIntBox) {- code for testing purpose, to be deleted later -} import Data.Number.ER.Real.DefaultRepr import Data.Number.ER.Real.DomainBox.IntMap type P = ERChebPoly (Box Int) B x0 = chplVar 0 :: P x1 = chplVar 1 :: P x2 = chplVar 2 :: P x3 = chplVar 3 :: P x4 = chplVar 4 :: P p1 = x1 * x1 * x1 + x1 * (x2 + 2) * (x3 - 3) {- end of code for testing purposes -} instance (B.ERRealBase rb, RealFrac rb, DomainBox box varid Int, Ord box, DomainBoxMappable boxb boxbb varid rb [(rb,rb)], DomainBoxMappable boxra boxras varid (ERInterval rb) [ERInterval rb], DomainIntBox boxra varid (ERInterval rb)) => (UFB.ERUnitFnBase boxb boxra varid rb (ERInterval rb) (ERChebPoly box rb)) where check = chplCheck getGranularity = chplGetGranularity setMinGranularity = chplSetMinGranularity setGranularity = chplSetGranularity const = chplConst affine = chplAffine scale = chplScale scaleApprox (ERInterval ratioDown ratioUp) = chplScaleApprox (ratioDown, ratioUp) -- Arity = chplGetArity getDegree = chplGetDegree reduceDegree = chplReduceDegree volumeAboveZero = chplVolumeAboveZero integrate = chplIntegrate upperBound = chplUpperBoundAffine -- upperBound = chplUpperBoundQuadr nonneg = chplNonneg recip = chplRecip max = chplMax sqrt = chplSqrt exp = chplExp log = chplLog sin = chplSineCosine True cos = chplSineCosine False eval = chplEval evalApprox ufb x = chplEvalApprox (\ b -> ERInterval b b) ufb x partialEvalApprox substitutions ufb = chplPartialEvalApprox (UFB.raEndpoints ufb) substitutions ufb raEndpoints _ (ERInterval l h) = (l,h) raEndpoints _ ERIntervalAny = (- B.plusInfinity, B.plusInfinity) raFromEndpoints _ (l,h) = normaliseERInterval (ERInterval l h) compose = chplCompose