factory-0.3.0.0: Rational arithmetic in an irrational world.

Safe HaskellNone
LanguageHaskell2010

Factory.Data.Polynomial

Contents

Description

Synopsis

Types

Type-synonyms

Data-types

data Polynomial coefficient exponent Source #

  • The type of an arbitrary univariate polynomial; actually it's more general, since it permits negative powers (https://en.wikipedia.org/wiki/Laurent_polynomials). It can't describe multivariate polynomials, which would require a list of exponents. Rather than requiring the exponent to implement the type-class Integral, this is implemented at the function-level, as required.
  • The structure permits gaps between exponents, in which coefficients are inferred to be zero, thus enabling efficient representation of sparse polynomials.
  • CAVEAT: the MonomialList is required to; be ordered by descending exponent (ie. reverse https://en.wikipedia.org/wiki/Monomial_order); have had zero coefficients removed; and to have had like terms merged; so the raw data-constructor isn't exported.

Instances

(Eq exponent, Eq coefficient) => Eq (Polynomial coefficient exponent) Source # 

Methods

(==) :: Polynomial coefficient exponent -> Polynomial coefficient exponent -> Bool #

(/=) :: Polynomial coefficient exponent -> Polynomial coefficient exponent -> Bool #

(Show exponent, Show coefficient) => Show (Polynomial coefficient exponent) Source # 

Methods

showsPrec :: Int -> Polynomial coefficient exponent -> ShowS #

show :: Polynomial coefficient exponent -> String #

showList :: [Polynomial coefficient exponent] -> ShowS #

(Eq c, Num c, Num e, Ord e) => Ring (Polynomial c e) Source #

Makes Polynomial a Ring, over the field composed from all possible coefficients; https://en.wikipedia.org/wiki/Polynomial_ring.

(Eq c, Fractional c, Num e, Ord e) => QuotientRing (Polynomial c e) Source #

Defines the ability to divide polynomials.

Methods

quotRem' :: Polynomial c e -> Polynomial c e -> (Polynomial c e, Polynomial c e) Source #

Constants

zero :: Polynomial c e Source #

Constructs a polynomial with zero terms.

one :: (Eq c, Num c, Num e) => Polynomial c e Source #

Constructs a constant monomial, independent of the indeterminate.

Functions

evaluate Source #

Arguments

:: (Num n, Integral e, Show e) 
=> n

The indeterminate.

-> Polynomial n e 
-> n

The Result.

  • Evaluate the polynomial at a specific indeterminate.
  • CAVEAT: requires positive exponents; but it wouldn't really be a polynomial otherwise.
  • If the polynomial is very sparse, this may be inefficient, since it memoizes the complete sequence of powers up to the polynomial's degree.

getLeadingTerm :: Polynomial c e -> Monomial c e Source #

Return the highest-degree monomial.

lift :: (MonomialList c1 e1 -> MonomialList c2 e2) -> Polynomial c1 e1 -> Polynomial c2 e2 Source #

  • Transforms the data behind the constructor.
  • CAVEAT: similar to fmap, but Polynomial isn't an instance of Functor since we may want to operate on both type-parameters.
  • CAVEAT: the caller is required to re-normalise the resulting polynomial depending on the nature of the transformation of the data.

mod' Source #

Arguments

:: Integral c 
=> Polynomial c e 
-> c

Modulus.

-> Polynomial c e 

Reduces all the coefficients using modular arithmetic.

normalise :: (Eq c, Num c, Ord e) => Polynomial c e -> Polynomial c e Source #

Sorts into descending order of exponents, groups like exponents, and calls pruneCoefficients.

raiseModulo Source #

Arguments

:: (Integral c, Integral power, Num e, Ord e, Show power) 
=> Polynomial c e

The base.

-> power

The exponent to which the base should be raised.

-> c

The modulus.

-> Polynomial c e

The result.

  • Raise a polynomial to the specified positive integral power, but using modulo-arithmetic.
  • Whilst one could naively implement this as (x Data.Ring.=^ n) mod m, this will result in arithmetic operatons on unnecessarily big integers.

realCoefficientsToFrac :: (Real r, Fractional f) => Polynomial r e -> Polynomial f e Source #

Convert the type of the coefficients.

terms :: Polynomial c e -> Int Source #

Returns the number of non-zero terms in the polynomial.

Constructors

mkConstant :: (Eq c, Num c, Num e) => c -> Polynomial c e Source #

Constructs an arbitrary zeroeth-degree polynomial, ie. independent of the indeterminate.

mkLinear Source #

Arguments

:: (Eq c, Num c, Num e) 
=> c

Gradient.

-> c

Constant.

-> Polynomial c e 

Constructs an arbitrary first-degree polynomial.

mkPolynomial :: (Eq c, Num c, Ord e) => MonomialList c e -> Polynomial c e Source #

Smart constructor. Constructs an arbitrary polynomial.

Operators

(*=) :: (Eq c, Num c, Num e) => Polynomial c e -> Monomial c e -> Polynomial c e infixl 7 Source #

Predicates

areCongruentModulo Source #

Arguments

:: (Integral c, Num e, Ord e) 
=> Polynomial c e

LHS.

-> Polynomial c e

RHS.

-> c

Modulus.

-> Bool 

inAscendingOrder :: Ord e => Polynomial c e -> Bool Source #

True if the exponents of successive terms are in ascending order.

inDescendingOrder :: Ord e => Polynomial c e -> Bool Source #

True if the exponents of successive terms are in descending order.

isMonomial :: Polynomial c e -> Bool Source #

True if there's exactly one term.

isNormalised :: (Eq c, Num c, Ord e) => Polynomial c e -> Bool Source #

True if no term has a coefficient of zero and the exponents of successive terms are in descending order.

isPolynomial :: Integral e => Polynomial c e -> Bool Source #

True if all exponents are positive integers as required.

isZero :: Polynomial c e -> Bool Source #

True if there are zero terms.