yap-0.3.0: yet another prelude - a simplistic refactoring with algebraic classes
Copyright(c) Ross Paterson 2011
LicenseBSD-style (see the file LICENSE)
Maintainer[email protected]
Stabilityprovisional
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Data.YAP.Algebra

Description

Classes corresponding to common structures from abstract algebra, defined as superclasses of the Haskell 2010 numeric classes, yielding the following class hierarchy (grey classes are unchanged):

Synopsis

Addition

class AdditiveMonoid a where Source #

A commutative associative binary operation with an identity.

Rationale:

  • This is the common superclass of AbelianGroup and Semiring. General monoids are also useful, but it is a common expectation that an operation denoted by + is commutative.
  • zero is required because this class is insufficient for integer literals.
  • Ideally, 0 could be defined as equivalent to zero, with other integer literals handled by fromNatural.

Minimal complete definition

(+), zero

Methods

(+) :: a -> a -> a infixl 6 Source #

An associative operation.

zero :: a Source #

The identity of (+).

atimes :: ToInteger b => b -> a -> a Source #

Sum of n copies of x. n should be non-negative.

Instances

Instances details
AdditiveMonoid Integer Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

AdditiveMonoid Natural Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

AdditiveMonoid Double Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

AdditiveMonoid Float Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

AdditiveMonoid Int Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Methods

(+) :: Int -> Int -> Int Source #

zero :: Int Source #

atimes :: ToInteger b => b -> Int -> Int Source #

AdditiveMonoid Word Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Methods

(+) :: Word -> Word -> Word Source #

zero :: Word Source #

atimes :: ToInteger b => b -> Word -> Word Source #

AdditiveMonoid a => AdditiveMonoid (Complex a) Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Methods

(+) :: Complex a -> Complex a -> Complex a Source #

zero :: Complex a Source #

atimes :: ToInteger b => b -> Complex a -> Complex a Source #

(Eq a, StandardAssociate a, Euclidean a) => AdditiveMonoid (Ratio a) Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Methods

(+) :: Ratio a -> Ratio a -> Ratio a Source #

zero :: Ratio a Source #

atimes :: ToInteger b => b -> Ratio a -> Ratio a Source #

AdditiveMonoid a => AdditiveMonoid (Product a) Source # 
Instance details

Defined in Data.YAP.MonoidAdaptors

Methods

(+) :: Product a -> Product a -> Product a Source #

zero :: Product a Source #

atimes :: ToInteger b => b -> Product a -> Product a Source #

AdditiveMonoid a => AdditiveMonoid (Sum a) Source # 
Instance details

Defined in Data.YAP.MonoidAdaptors

Methods

(+) :: Sum a -> Sum a -> Sum a Source #

zero :: Sum a Source #

atimes :: ToInteger b => b -> Sum a -> Sum a Source #

(AdditiveMonoid a, AdditiveMonoid b) => AdditiveMonoid (a, b) Source #

Direct product

Instance details

Defined in Data.YAP.Algebra.Internal

Methods

(+) :: (a, b) -> (a, b) -> (a, b) Source #

zero :: (a, b) Source #

atimes :: ToInteger b0 => b0 -> (a, b) -> (a, b) Source #

atimesIdempotent :: (ToInteger b, AdditiveMonoid a) => b -> a -> a Source #

Faster implementation of atimes when addition is idempotent.

timesCancelling :: (ToInteger a, AdditiveMonoid b) => a -> b -> b Source #

Faster implementation of atimes or gtimes when x+x = zero.

Subtraction

class AdditiveMonoid a => AbelianGroup a where Source #

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

Rationale:

  • The abs and signum operations lack sensible definitions for many useful instances, such as complex numbers, polynomials, matrices, etc.
  • Types that have subtraction but not multiplication include vectors and dimensioned quantities.

Minimal complete definition

(-) | negate

Methods

(-) :: a -> a -> a infixl 6 Source #

Subtraction operator.

negate :: a -> a Source #

Inverse for (+) (unary negation).

gtimes :: (AbelianGroup b, ToInteger b) => b -> a -> a Source #

Sum of n copies of x.

Instances

Instances details
AbelianGroup Integer Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

AbelianGroup Double Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

AbelianGroup Float Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

AbelianGroup Int Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Methods

(-) :: Int -> Int -> Int Source #

negate :: Int -> Int Source #

gtimes :: (AbelianGroup b, ToInteger b) => b -> Int -> Int Source #

AbelianGroup Word Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Methods

(-) :: Word -> Word -> Word Source #

negate :: Word -> Word Source #

gtimes :: (AbelianGroup b, ToInteger b) => b -> Word -> Word Source #

AbelianGroup a => AbelianGroup (Complex a) Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Methods

(-) :: Complex a -> Complex a -> Complex a Source #

negate :: Complex a -> Complex a Source #

gtimes :: (AbelianGroup b, ToInteger b) => b -> Complex a -> Complex a Source #

(Eq a, StandardAssociate a, Euclidean a, Ring a) => AbelianGroup (Ratio a) Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Methods

(-) :: Ratio a -> Ratio a -> Ratio a Source #

negate :: Ratio a -> Ratio a Source #

gtimes :: (AbelianGroup b, ToInteger b) => b -> Ratio a -> Ratio a Source #

AbelianGroup a => AbelianGroup (Product a) Source # 
Instance details

Defined in Data.YAP.MonoidAdaptors

Methods

(-) :: Product a -> Product a -> Product a Source #

negate :: Product a -> Product a Source #

gtimes :: (AbelianGroup b, ToInteger b) => b -> Product a -> Product a Source #

AbelianGroup a => AbelianGroup (Sum a) Source # 
Instance details

Defined in Data.YAP.MonoidAdaptors

Methods

(-) :: Sum a -> Sum a -> Sum a Source #

negate :: Sum a -> Sum a Source #

gtimes :: (AbelianGroup b, ToInteger b) => b -> Sum a -> Sum a Source #

(AbelianGroup a, AbelianGroup b) => AbelianGroup (a, b) Source #

Direct product

Instance details

Defined in Data.YAP.Algebra.Internal

Methods

(-) :: (a, b) -> (a, b) -> (a, b) Source #

negate :: (a, b) -> (a, b) Source #

gtimes :: (AbelianGroup b0, ToInteger b0) => b0 -> (a, b) -> (a, b) Source #

subtract :: AbelianGroup a => a -> a -> a Source #

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.

gtimesIdempotent :: (ToInteger b, AbelianGroup a) => b -> a -> a Source #

Faster implementation of gtimes when addition is idempotent.

Multiplication

class AdditiveMonoid a => Semiring a where Source #

A semiring: addition defines a commutative monoid, and multiplication defines a monoid and distributes over addition and zero. Multiplication is not guaranteed to be commutative.

Rationale:

  • Natural is the key example of a type with multiplication but not subtraction, but there are many more.
  • one is required because this class is insufficient for integer literals.
  • In an ideal world, an integer literal i would be treated as equivalent to fromNatural i and have type (Semiring a) => a. (The lexical syntax already permits only non-negative numbers.)
  • rescale is available here with a trivial default definition so that some operations on complex numbers, whose direct definitions would often overflow on Float or Double components, can be defined for other types as well.

Minimal complete definition

(*), (one | fromNatural)

Methods

(*) :: a -> a -> a infixl 7 Source #

An associative operation that distributes over (+).

one :: a Source #

The identity of (*).

fromNatural :: Natural -> a Source #

Conversion from Natural, the initial semiring: fromNatural is the unique function preserving zero, one, (+) and (*).

rescale :: a -> a -> (a, a, a -> a) Source #

rescale x y = (x', y', s) where s is a linear function such that s x' = x and s y' = y, chosen so that multiplications by x' and y' are less likely to overflow. In the default definition, s is id.

Instances

Instances details
Semiring Integer Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Semiring Natural Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Semiring Double Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Semiring Float Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Semiring Int Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Semiring Word Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Ring a => Semiring (Complex a) Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

(Eq a, StandardAssociate a, Euclidean a) => Semiring (Ratio a) Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Methods

(*) :: Ratio a -> Ratio a -> Ratio a Source #

one :: Ratio a Source #

fromNatural :: Natural -> Ratio a Source #

rescale :: Ratio a -> Ratio a -> (Ratio a, Ratio a, Ratio a -> Ratio a) Source #

Semiring a => Semiring (Product a) Source # 
Instance details

Defined in Data.YAP.MonoidAdaptors

Semiring a => Semiring (Sum a) Source # 
Instance details

Defined in Data.YAP.MonoidAdaptors

Methods

(*) :: Sum a -> Sum a -> Sum a Source #

one :: Sum a Source #

fromNatural :: Natural -> Sum a Source #

rescale :: Sum a -> Sum a -> (Sum a, Sum a, Sum a -> Sum a) Source #

(Semiring a, Semiring b) => Semiring (a, b) Source #

Direct product

Instance details

Defined in Data.YAP.Algebra.Internal

Methods

(*) :: (a, b) -> (a, b) -> (a, b) Source #

one :: (a, b) Source #

fromNatural :: Natural -> (a, b) Source #

rescale :: (a, b) -> (a, b) -> ((a, b), (a, b), (a, b) -> (a, b)) Source #

class (AbelianGroup a, Semiring a) => Ring a where Source #

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

Rationale:

  • This is sufficient to define fromInteger, but often a much more efficient definition is available.

Minimal complete definition

Nothing

Methods

fromInteger :: Integer -> a Source #

Conversion from Integer, the initial ring: fromInteger is the unique function preserving zero, one, (+), (-) and (*).

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. (Ideally, they would represent an application of fromNatural, and have type (Semiring a) => a.)

Instances

Instances details
Ring Integer Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Ring Double Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Ring Float Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Ring Int Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Ring Word Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Ring a => Ring (Complex a) Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

(Eq a, StandardAssociate a, Euclidean a, Ring a) => Ring (Ratio a) Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Ring a => Ring (Product a) Source # 
Instance details

Defined in Data.YAP.MonoidAdaptors

Ring a => Ring (Sum a) Source # 
Instance details

Defined in Data.YAP.MonoidAdaptors

Methods

fromInteger :: Integer -> Sum a Source #

(Ring a, Ring b) => Ring (a, b) Source #

Direct product

Instance details

Defined in Data.YAP.Algebra.Internal

Methods

fromInteger :: Integer -> (a, b) Source #

class Semiring a => StandardAssociate a where Source #

A cancellative commutative semiring with a designated canonical factoring of each value as the product of a unit (invertible value) and an associate.

Rationale:

  • This normalization is required so that the results of operations such as gcd and lcm can be uniquely defined. In the original Prelude, abs and signum were used for this, but they lack coherent definitions on many useful instances.
  • This class is usually used together with Euclidean, and generally has matching instances. Merging the two classes would be a possibility. That would allow a default definition of stdAssociate.

Minimal complete definition

stdUnit, stdRecip

Methods

stdAssociate :: a -> a Source #

A representative associate:

For integral types, stdAssociate x is a non-negative integer.

stdUnit :: a -> a Source #

stdUnit x has a multiplicative inverse and satisfies

For integral types, stdUnit x is 1 or -1.

stdRecip :: a -> a Source #

multiplicative inverse of stdUnit x

Instances

Instances details
StandardAssociate Integer Source #

Units have absolute value 1. Standard associates are non-negative.

Instance details

Defined in Data.YAP.Algebra.Internal

StandardAssociate Natural Source #

The only unit is 1. stdAssociate is the identity.

Instance details

Defined in Data.YAP.Algebra.Internal

StandardAssociate Int Source #

Units have absolute value 1. Standard associates are non-negative.

Instance details

Defined in Data.YAP.Algebra.Internal

StandardAssociate Word Source #

The only unit is 1. stdAssociate is the identity.

Instance details

Defined in Data.YAP.Algebra.Internal

(Ring a, ToInteger a) => StandardAssociate (Complex a) Source #

Gaussian integers: units have magnitude 1; standard associates are natural numbers or in the positive quadrant.

Instance details

Defined in Data.YAP.Algebra.Internal

Division with remainder

class Semiring a => Euclidean a where Source #

A Euclidean semiring: a commutative semiring with Euclidean division, yielding a quotient and a remainder that is smaller than the divisor in a well-founded ordering. This is sufficient to implement Euclid's algorithm for the greatest common divisor.

Rationale:

  • This class, together with StandardAssociate, is sufficient to define gcd, and thus to define arithmetic operations on Ratio a.
  • The uniformity condition is required to make modular arithmetic work. Non-integer examples include Complex Integer (Gaussian integers) and polynomials.
  • The usual definition of a Euclidean domain assumes a ring, but division with remainder can be defined in the absence of negation, e.g. for Natural.

Minimal complete definition

(divMod | div, mod), euclideanNorm

Methods

div :: a -> a -> a infixl 7 Source #

Division with remainder: for any d that is not zero,

mod :: a -> a -> a infixl 7 Source #

Remainder of division: for any d that is not zero,

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)

euclideanNorm :: a -> Natural Source #

A measure of the size of a non-zero value. This may be undefined on zero. If the argument is non-zero, the value is positive.

Instances

Instances details
Euclidean Integer Source #

mod is non-negative

Instance details

Defined in Data.YAP.Algebra.Internal

Euclidean Natural Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Euclidean Int Source #

mod is non-negative

Instance details

Defined in Data.YAP.Algebra.Internal

Methods

div :: Int -> Int -> Int Source #

mod :: Int -> Int -> Int Source #

divMod :: Int -> Int -> (Int, Int) Source #

euclideanNorm :: Int -> Natural Source #

Euclidean Word Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

(Ring a, ToInteger a) => Euclidean (Complex a) Source #

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

Instance details

Defined in Data.YAP.Algebra.Internal

gcd :: (Eq a, StandardAssociate a, Euclidean a) => a -> a -> a Source #

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

lcm :: (Eq a, StandardAssociate a, Euclidean a) => a -> a -> a Source #

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

bezout :: (Eq a, AbelianGroup a, StandardAssociate a, Euclidean a) => a -> a -> (a, a) Source #

bezout x y = (a, b) such that a*x + b*y = gcd x y (Bézout's identity).

In particular, if x and y are coprime (i.e. gcd x y == one),

  • b is the multiplicative inverse of y modulo x.
  • a is the multiplicative inverse of x modulo y.
  • j*a*x + i*b*y is equivalent to i modulo x and to j modulo y (Chinese Remainder Theorem).

extendedEuclid :: (Eq a, AbelianGroup a, StandardAssociate a, Euclidean a) => a -> a -> [(a, a, a, a)] Source #

The list of quadruples \((q_i, r_i, s_i, t_i)\) generated by the extended Euclidean algorithm, which is a maximal list satisfying:

  • \(r_{i-1} = q_i r_i + r_{i+1}\) with \(r_{i+1}\) smaller than \(r_i\), where \(r_0 = a\) and \(r_1 = b\), and
  • \(r_i = s_i a + t_i b\).

The last \(r_i\) in the list is a greatest common divisor of \(a\) and \(b\), so that the second equation above becomes Bézout's identity.

Exact division

class Semiring a => DivisionSemiring a where Source #

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

Rationale:

  • Quaternions have multiplicative inverses, but do not form a field, because multiplication is not commutative.
  • Some semirings, such as the tropical semiring and its dual, support division but not subtraction.

Methods

recip :: a -> a Source #

Multiplicative inverse of any value but zero.

Instances

Instances details
DivisionSemiring Double Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Methods

recip :: Double -> Double Source #

DivisionSemiring Float Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Methods

recip :: Float -> Float Source #

Field a => DivisionSemiring (Complex a) Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Methods

recip :: Complex a -> Complex a Source #

(Eq a, StandardAssociate a, Euclidean a) => DivisionSemiring (Ratio a) Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Methods

recip :: Ratio a -> Ratio a Source #

class DivisionSemiring a => Semifield a where Source #

A commutative Semiring in which all non-zero elements have multiplicative inverses, so that division is uniquely defined.

Rationale:

  • Some semirings, such as the tropical semiring and its dual, support division but not subtraction.

Minimal complete definition

Nothing

Methods

(/) :: a -> a -> a infixl 7 Source #

Division operator.

Instances

Instances details
Semifield Double Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Methods

(/) :: Double -> Double -> Double Source #

Semifield Float Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Methods

(/) :: Float -> Float -> Float Source #

Field a => Semifield (Complex a) Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Methods

(/) :: Complex a -> Complex a -> Complex a Source #

(Eq a, StandardAssociate a, Euclidean a) => Semifield (Ratio a) Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Methods

(/) :: Ratio a -> Ratio a -> Ratio a Source #

class (Ring a, DivisionSemiring a) => DivisionRing a Source #

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

Rationale:

  • Quaternions have multiplicative inverses, but multiplication is not commutative, so they do not have a well-defined division operation, and do not form a field.

Instances

Instances details
DivisionRing Double Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

DivisionRing Float Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Field a => DivisionRing (Complex a) Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

(Eq a, StandardAssociate a, Euclidean a, Ring a) => DivisionRing (Ratio a) Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

class (DivisionRing a, Semifield a) => Field a Source #

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

Rationale:

  • fromRational needs to be in an independent class, because Rational cannot be embedded in finite fields.
  • While fields trivially support Euclidean division and standard associates, they are kept apart for backward compatibility.

Instances

Instances details
Field Double Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Field Float Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Field a => Field (Complex a) Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

(Eq a, StandardAssociate a, Euclidean a, Ring a) => Field (Ratio a) Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Embeddings

These classes define one-to-one embeddings. In contrast, the functions fromNatural and fromInteger (in Semiring and Ring respectively) are not required to be one-to-one.

class Ring a => FromRational a where Source #

Rings extending Rational. Such a ring should have characteristic 0, i.e. no sum 1 + ... + 1 should equal zero.

Rationale:

  • For fromRational to be injective, its domain must be infinite, which naturally excludes finite fields. Indeed Rational is initial in the category of infinite fields. (It's true that Float and Double aren't infinite, but they aren't even additive monoids.)
  • Conversely, many rings that are not fields support embedding of rationals, e.g. polynomials and matrices.

Methods

fromRational :: Rational -> a Source #

Conversion from a Rational (that is, Ratio Integer) preserving zero, one, (+), (-) and (*). Under the assumption that the ring has characteristic 0, this implies that fromRational is injective.

For an infinite field, fromRational is the unique function preserving zero, one, (+), (-), (*) and (/).

A floating literal stands for an application of fromRational to a value of type Rational, so such literals have type (FromRational a) => a.

Instances

Instances details
FromRational Double Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

FromRational Float Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

FromRational a => FromRational (Complex a) Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Integral a => FromRational (Ratio a) Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

(FromRational a, FromRational b) => FromRational (a, b) Source #

Direct product

Instance details

Defined in Data.YAP.Algebra.Internal

Methods

fromRational :: Rational -> (a, b) Source #

class (Ord a, Semiring a) => ToRational a where Source #

Types that can be faithfully embedded in Rational.

Rationale:

  • This is essentially equivalent to the old Real class, but with the Num superclass reduced to Semiring (so it does not assume negative values).

Methods

toRational :: a -> Rational Source #

The rational equivalent of its argument with full precision

Instances

Instances details
ToRational Integer Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

ToRational Natural Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

ToRational Double Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

ToRational Float Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

ToRational Int Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

ToRational Word Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

(ToInteger a, Integral a) => ToRational (Ratio a) Source #

The original version of Integral is required here by the old instance Ord (Ratio a). Ideally this would be replaced with Ord a.

Instance details

Defined in Data.YAP.Algebra.Internal

ToRational a => ToRational (Product a) Source # 
Instance details

Defined in Data.YAP.MonoidAdaptors

ToRational a => ToRational (Sum a) Source # 
Instance details

Defined in Data.YAP.MonoidAdaptors

Methods

toRational :: Sum a -> Rational Source #

class (StandardAssociate a, Euclidean a, ToRational a) => ToInteger a where Source #

Types representing a contiguous set of integers, including 0, 1 and 2.

Rationale:

  • This is similar to the old Integral class, but does not require subtraction, which does not work for Natural.

Methods

toInteger :: a -> Integer Source #

Conversion to Integer, satisfying

fromInteger (toInteger x) = x

Instances

Instances details
ToInteger Integer Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

ToInteger Natural Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

ToInteger Int Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

ToInteger Word Source # 
Instance details

Defined in Data.YAP.Algebra.Internal

Differentiation and integration

class Semiring a => Differentiable a where Source #

A differential semiring

Methods

derivative :: a -> a Source #

A monoid homomorphism that satisfies

class Differentiable a => Integrable a where Source #

A differential semiring with anti-differentiation

Methods

integral :: a -> a Source #

A monoid homomorphism that is a pre-inverse of derivative, i.e.

Mapping

class AdditiveFunctor (f :: Type -> Type) where Source #

A functor on additive monoids

Methods

mapAdditive :: (AdditiveMonoid a, AdditiveMonoid b) => (a -> b) -> f a -> f b Source #

Map with a function that preserves zero and (+).