computational-algebra-0.5.0.0: Well-kinded computational algebra library, currently supporting Groebner basis.

Safe HaskellNone
LanguageHaskell2010

Algebra.Field.AlgebraicReal

Contents

Description

Algebraic Real Numbers for exact computation

Since 0.4.0.0

Synopsis

Documentation

data Algebraic Source #

Algebraic real numbers, which can be expressed as a root of a rational polynomial.

Instances

Eq Algebraic Source # 
Fractional Algebraic Source # 
Num Algebraic Source # 
Ord Algebraic Source # 
Show Algebraic Source # 
InvolutiveMultiplication Algebraic Source # 
TriviallyInvolutive Algebraic Source # 
Commutative Algebraic Source # 
UnitNormalForm Algebraic Source # 
ZeroProductSemiring Algebraic Source # 
Ring Algebraic Source # 
Rig Algebraic Source # 
DecidableZero Algebraic Source # 

Methods

isZero :: Algebraic -> Bool #

DecidableUnits Algebraic Source # 
DecidableAssociates Algebraic Source # 
Division Algebraic Source # 
Unital Algebraic Source # 

Methods

one :: Algebraic #

pow :: Algebraic -> Natural -> Algebraic #

productWith :: Foldable f => (a -> Algebraic) -> f a -> Algebraic #

Group Algebraic Source # 
Multiplicative Algebraic Source # 
Semiring Algebraic Source # 
Monoidal Algebraic Source # 

Methods

zero :: Algebraic #

sinnum :: Natural -> Algebraic -> Algebraic #

sumWith :: Foldable f => (a -> Algebraic) -> f a -> Algebraic #

Additive Algebraic Source # 
Abelian Algebraic Source # 
LeftModule Integer Algebraic Source # 

Methods

(.*) :: Integer -> Algebraic -> Algebraic #

LeftModule Natural Algebraic Source # 

Methods

(.*) :: Natural -> Algebraic -> Algebraic #

RightModule Integer Algebraic Source # 

Methods

(*.) :: Algebraic -> Integer -> Algebraic #

RightModule Natural Algebraic Source # 

Methods

(*.) :: Algebraic -> Natural -> Algebraic #

LeftModule (Fraction Integer) Algebraic Source # 
LeftModule (Scalar (Fraction Integer)) Algebraic Source # 
RightModule (Fraction Integer) Algebraic Source # 
RightModule (Scalar (Fraction Integer)) Algebraic Source # 

algebraic :: Unipol Rational -> Interval Rational -> Maybe Algebraic Source #

Smart constructor. algebraic f i represents the unique root of rational polynomial f in the interval i. If no root is found, or more than one root belongs to the given interval, returns Nothing.

Operations

nthRoot :: Int -> Algebraic -> Maybe Algebraic Source #

nthRoot n r tries to computes n-th root of the given algebraic real r. It returns Nothing if it's undefined.

See also nthRoot'.

nthRoot' :: Int -> Algebraic -> Algebraic Source #

Unsafe version of nthRoot.

improve :: Algebraic -> Algebraic Source #

improve r returns the same algebraic number, but with more tighter bounds.

approximate :: Rational -> Algebraic -> Rational Source #

approximate eps r returns rational number r' close to r, with abs (r - r') < eps.

approxFractional :: Fractional r => Rational -> Algebraic -> r Source #

Same as approximate, but returns Fractional value instead.

Equation solver

realRoots :: Unipol Rational -> [Algebraic] Source #

realRoots f finds all real roots of the rational polynomial f.

complexRoots :: Unipol Rational -> [Complex Algebraic] Source #

realRoots f finds all complex roots of the rational polynomial f.

CAUTION: This function currently comes with really naive implementation. Easy to explode.

Interval arithmetic

data Interval r Source #

Constructors

Interval 

Fields

Instances

Eq r => Eq (Interval r) Source # 

Methods

(==) :: Interval r -> Interval r -> Bool #

(/=) :: Interval r -> Interval r -> Bool #

Ord r => Ord (Interval r) Source # 

Methods

compare :: Interval r -> Interval r -> Ordering #

(<) :: Interval r -> Interval r -> Bool #

(<=) :: Interval r -> Interval r -> Bool #

(>) :: Interval r -> Interval r -> Bool #

(>=) :: Interval r -> Interval r -> Bool #

max :: Interval r -> Interval r -> Interval r #

min :: Interval r -> Interval r -> Interval r #

Show r => Show (Interval r) Source # 

Methods

showsPrec :: Int -> Interval r -> ShowS #

show :: Interval r -> String #

showList :: [Interval r] -> ShowS #

(Ord r, Multiplicative r, Monoidal r) => Multiplicative (Interval r) Source # 

Methods

(*) :: Interval r -> Interval r -> Interval r #

pow1p :: Interval r -> Natural -> Interval r #

productWith1 :: Foldable1 f => (a -> Interval r) -> f a -> Interval r #

Group r => Additive (Interval r) Source # 

Methods

(+) :: Interval r -> Interval r -> Interval r #

sinnum1p :: Natural -> Interval r -> Interval r #

sumWith1 :: Foldable1 f => (a -> Interval r) -> f a -> Interval r #

representative :: (Additive r, Division r, Num r) => Interval r -> r Source #

Choose representative element of the given interval.

includes :: Ord a => Interval a -> Interval a -> Bool Source #

Test if the former interval includes the latter.

intersect :: (Monoidal a, Ord a) => Interval a -> Interval a -> Interval a Source #

Takes intersection of two intervals.

Internal utility functions

presultant :: (Euclidean k, CoeffRing k) => Unipol k -> Unipol k -> k Source #

Pseudo resultant. should we expose this?