yap-0.2: yet another prelude - a simplistic refactoring with algebraic classes

Portabilityportable
Stabilityprovisional
Maintainerross@soi.city.ac.uk
Safe HaskellSafe-Infered

Data.YAP.Algebra

Contents

Description

Classes corresponding to common structures from abstract algebra.

Synopsis

Classes

class AbelianGroup a whereSource

An Abelian group has an commutative associative binary operation with an identity and inverses.

Minimal complete definition: zero, (+) and ((-) or negate).

Methods

zero :: aSource

The identity of (+).

(+), (-) :: a -> a -> aSource

A commutative associative operation with identity zero.

negate :: a -> aSource

Inverse for (+) (unary negation).

class AbelianGroup a => Ring a whereSource

A ring: addition forms an Abelian group, and multiplication defines a monoid and distributes over addition. Multiplication is not guaranteed to be commutative.

Minimal complete definition: (*) and fromInteger.

Methods

(*) :: a -> a -> aSource

An associative operation with identity fromInteger 1, distributing over (+) and zero.

fromInteger :: Integer -> aSource

Conversion from Integer, the initial ring: fromInteger is the unique function preserving zero, (+), (-) and (*), and for which fromInteger 1 is the identity of (*).

An integer literal represents the application of the function fromInteger to the appropriate value of type Integer, so such literals have type (Ring a) => a.

Instances

Ring Double 
Ring Float 
Ring Int 
Ring Integer 
EuclideanDomain a => Ring (Ratio a) 
Ring a => Ring (Complex a) 
Ring a => Ring (Matrix a) 
Ring a => Ring (Polynomial a) 
(Ring a, Ring b) => Ring (a, b)

Direct product

class (Eq a, Ring a) => EuclideanDomain a whereSource

A integral domain (a non-trivial commutative Ring with no zero divisors) on which the Euclid's algorithm for gcd works.

Minimal complete definition: (divMod or (div and mod)) and unit.

Methods

div, mod :: a -> a -> aSource

Division with remainder: for any d /= 0,

  • n == div n d * d + mod n d
  • mod (n + a*d) d == mod n d
  • mod n d is smaller than d in some well-founded order.

For integral types, mod n d is a non-negative integer smaller than the absolute value of d.

divMod :: a -> a -> (a, a)Source

divMod n d == (div n d, mod n d)

associate, unit :: a -> aSource

For each x there is a decomposition x == associate x * unit x such that unit x has a multiplicative inverse and

For integral types, associate x is a non-negative integer and unit x is -1 or 1.

Instances

EuclideanDomain Int 
EuclideanDomain Integer 
Integral a => EuclideanDomain (Complex a)

Gaussian integers: if b is non-zero, the norm (squared magnitude) of mod a b is at most half that of b. Standard associates lie in the positive quadrant.

(Eq a, Field a) => EuclideanDomain (Polynomial a)

If b is non-zero, mod a b has a smaller degree than b. If a is non-zero, associate a has a leading coefficient of 1.

class Ring a => Field a whereSource

A commutative Ring in which all non-zero elements have multiplicative inverses.

Minimal complete definition: recip or (/).

Methods

(/) :: a -> a -> aSource

recip :: a -> aSource

Multiplicative inverse.

Instances

Field Double 
Field Float 
EuclideanDomain a => Field (Ratio a) 
RealFloat a => Field (Complex a)

RealFloat is used to do scaling to reduce the incidence of overflow.

Utility functions

subtract :: AbelianGroup a => a -> a -> aSource

The same as flip (-).

Because - is treated specially in the Haskell grammar, (- e) is not a section, but an application of prefix negation. However, (subtract exp) is equivalent to the disallowed section.

gcd :: EuclideanDomain a => a -> a -> aSource

gcd x y is a common factor of x and y such that

  • associate (gcd x y) == gcd x y, and
  • any common factor of x and y is a factor of gcd x y.

lcm :: EuclideanDomain a => a -> a -> aSource

lcm x y is a common multiple of x and y such that

  • associate (lcm x y) == lcm x y, and
  • any common multiple of x and y is a multiple of lcm x y.