numeric-prelude-0.4.2: An experimental alternative hierarchy of numeric type classes

Safe HaskellNone
LanguageHaskell98

NumericPrelude.Numeric

Synopsis

Documentation

(+), (-) :: C a => a -> a -> a Source

add and subtract elements

(+), (-) :: C a => a -> a -> a Source

add and subtract elements

negate :: C a => a -> a Source

inverse with respect to +

zero :: C a => a Source

zero element of the vector space

subtract :: C a => a -> a -> a Source

subtract is (-) with swapped operand order. This is the operand order which will be needed in most cases of partial application.

sum :: C a => [a] -> a Source

Sum up all elements of a list. An empty list yields zero.

This function is inappropriate for number types like Peano. Maybe we should make sum a method of Additive. This would also make lengthLeft and lengthRight superfluous.

sum1 :: C a => [a] -> a Source

Sum up all elements of a non-empty list. This avoids including a zero which is useful for types where no universal zero is available.

isZero :: C a => a -> Bool Source

(*) :: C a => a -> a -> a Source

one :: C a => a Source

(^) :: C a => a -> Integer -> a Source

The exponent has fixed type Integer in order to avoid an arbitrarily limitted range of exponents, but to reduce the need for the compiler to guess the type (default type). In practice the exponent is most oftenly fixed, and is most oftenly 2. Fixed exponents can be optimized away and thus the expensive computation of Integers doesn't matter. The previous solution used a C constrained type and the exponent was converted to Integer before computation. So the current solution is not less efficient.

A variant of ^ with more flexibility is provided by ringPower.

ringPower :: (C a, C b) => b -> a -> a Source

A prefix function of '(Algebra.Ring.^)' with a parameter order that fits the needs of partial application and function composition. It has generalised exponent.

See: Argument order of expNat on http://www.haskell.org/pipermail/haskell-cafe/2006-September/018022.html

sqr :: C a => a -> a Source

product :: C a => [a] -> a Source

product1 :: C a => [a] -> a Source

div, mod :: C a => a -> a -> a Source

div, mod :: C a => a -> a -> a Source

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

divides :: (C a, C a) => a -> a -> Bool Source

even :: (C a, C a) => a -> Bool Source

odd :: (C a, C a) => a -> Bool Source

(/) :: C a => a -> a -> a Source

recip :: C a => a -> a Source

(^-) :: C a => a -> Integer -> a Source

fieldPower :: (C a, C b) => b -> a -> a Source

A prefix function of '(Algebra.Field.^-)'. It has a generalised exponent.

fromRational :: C a => Rational -> a Source

Needed to work around shortcomings in GHC.

(^/) :: C a => a -> Rational -> a Source

sqrt :: C a => a -> a Source

pi :: C a => a Source

exp, log :: C a => a -> a Source

exp, log :: C a => a -> a Source

logBase, (**) :: C a => a -> a -> a Source

logBase, (**) :: C a => a -> a -> a Source

(^?) :: C a => a -> a -> a infixr 8 Source

sin, tan, cos :: C a => a -> a Source

sin, tan, cos :: C a => a -> a Source

sin, tan, cos :: C a => a -> a Source

asin, atan, acos :: C a => a -> a Source

asin, atan, acos :: C a => a -> a Source

asin, atan, acos :: C a => a -> a Source

sinh, tanh, cosh :: C a => a -> a Source

sinh, tanh, cosh :: C a => a -> a Source

sinh, tanh, cosh :: C a => a -> a Source

asinh, atanh, acosh :: C a => a -> a Source

asinh, atanh, acosh :: C a => a -> a Source

asinh, atanh, acosh :: C a => a -> a Source

abs :: C a => a -> a Source

signum :: C a => a -> a Source

quot, rem :: C a => a -> a -> a Source

quot, rem :: C a => a -> a -> a Source

quotRem :: C a => a -> a -> (a, a) Source

splitFraction :: (C a, C b) => a -> (b, a) Source

fraction :: C a => a -> a Source

truncate :: (C a, C b) => a -> b Source

round :: (C a, C b) => a -> b Source

ceiling, floor :: (C a, C b) => a -> b Source

ceiling, floor :: (C a, C b) => a -> b Source

approxRational :: (C a, C a) => a -> a -> Rational Source

TODO: Should be moved to a continued fraction module.

atan2 :: C a => a -> a -> a Source

toRational :: C a => a -> Rational Source

Lossless conversion from any representation of a rational to Rational

toInteger :: C a => a -> Integer Source

fromIntegral :: (C a, C b) => a -> b Source

isUnit :: C a => a -> Bool Source

extendedGCD :: C a => a -> a -> (a, (a, a)) Source

Compute the greatest common divisor and solve a respective Diophantine equation.

  (g,(a,b)) = extendedGCD x y ==>
       g==a*x+b*y   &&  g == gcd x y

TODO: This method is not appropriate for the PID class, because there are rings like the one of the multivariate polynomials, where for all x and y greatest common divisors of x and y exist, but they cannot be represented as a linear combination of x and y. TODO: The definition of extendedGCD does not return the canonical associate.

gcd :: C a => a -> a -> a Source

The Greatest Common Divisor is defined by:

  gcd x y == gcd y x
  divides z x && divides z y ==> divides z (gcd x y)   (specification)
  divides (gcd x y) x

lcm :: C a => a -> a -> a Source

Least common multiple

euclid :: (C a, C a) => (a -> a -> a) -> a -> a -> a Source

extendedEuclid :: (C a, C a) => (a -> a -> (a, a)) -> a -> a -> (a, (a, a)) Source

(%) :: C a => a -> a -> T a infixl 7 Source

numerator :: T a -> a Source

denominator :: T a -> a Source

data Int :: *

A fixed-precision integer type with at least the range [-2^29 .. 2^29-1]. The exact range for a given implementation can be determined by using minBound and maxBound from the Bounded class.

data Float :: *

Single-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE single-precision type.

data Double :: *

Double-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE double-precision type.

(*>) :: C a v => a -> v -> v Source

scale a vector by a scalar