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

NumericPrelude.Numeric

Synopsis

Documentation

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

add and subtract elements

negate :: C a => a -> aSource

inverse with respect to +

zero :: C a => aSource

zero element of the vector space

subtract :: C a => a -> a -> aSource

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] -> aSource

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] -> aSource

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 -> BoolSource

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

one :: C a => aSource

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

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 Algebra.ToInteger.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 Algebra.Core.ringPower.

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

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 -> aSource

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

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

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

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

divides :: (C a, C a) => a -> a -> BoolSource

even, odd :: (C a, C a) => a -> BoolSource

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

recip :: C a => a -> aSource

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

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

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

fromRational :: C a => Rational -> aSource

Needed to work around shortcomings in GHC.

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

sqrt :: C a => a -> aSource

pi :: C a => aSource

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

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

(^?) :: C a => a -> a -> aSource

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

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

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

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

abs :: C a => a -> aSource

signum :: C a => a -> aSource

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

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

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

fraction :: C a => a -> aSource

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

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

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

approxRational :: (C a, C a) => a -> a -> RationalSource

TODO: Should be moved to a continued fraction module.

atan2 :: C a => a -> a -> aSource

toRational :: C a => a -> RationalSource

Lossless conversion from any representation of a rational to Rational

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

isUnit :: C a => a -> BoolSource

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 -> aSource

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 -> aSource

Least common multiple

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

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

(%) :: C a => a -> a -> T aSource

numerator :: T a -> aSource

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 Prelude.minBound and Prelude.maxBound from the Prelude.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 -> vSource

scale a vector by a scalar