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

Safe HaskellSafe
LanguageHaskell98

Algebra.IntegralDomain

Contents

Synopsis

Class

class C a => C a Source #

IntegralDomain corresponds to a commutative ring, where a mod b picks a canonical element of the equivalence class of a in the ideal generated by b. div and mod satisfy the laws

                        a * b === b * a
(a `div` b) * b + (a `mod` b) === a
              (a+k*b) `mod` b === a `mod` b
                    0 `mod` b === 0

Typical examples of IntegralDomain include integers and polynomials over a field. Note that for a field, there is a canonical instance defined by the above rules; e.g.,

instance IntegralDomain.C Rational where
    divMod a b =
       if isZero b
         then (undefined,a)
         else (a\/b,0)

It shall be noted, that div, mod, divMod have a parameter order which is unfortunate for partial application. But it is adapted to mathematical conventions, where the operators are used in infix notation.

Minimal definition: divMod or (div and mod)

Minimal complete definition

divMod | div, mod

Instances
C Int Source # 
Instance details

Defined in Algebra.IntegralDomain

Methods

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

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

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

C Int8 Source # 
Instance details

Defined in Algebra.IntegralDomain

Methods

div :: Int8 -> Int8 -> Int8 Source #

mod :: Int8 -> Int8 -> Int8 Source #

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

C Int16 Source # 
Instance details

Defined in Algebra.IntegralDomain

C Int32 Source # 
Instance details

Defined in Algebra.IntegralDomain

C Int64 Source # 
Instance details

Defined in Algebra.IntegralDomain

C Integer Source # 
Instance details

Defined in Algebra.IntegralDomain

C Word Source # 
Instance details

Defined in Algebra.IntegralDomain

Methods

div :: Word -> Word -> Word Source #

mod :: Word -> Word -> Word Source #

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

C Word8 Source # 
Instance details

Defined in Algebra.IntegralDomain

C Word16 Source # 
Instance details

Defined in Algebra.IntegralDomain

C Word32 Source # 
Instance details

Defined in Algebra.IntegralDomain

C Word64 Source # 
Instance details

Defined in Algebra.IntegralDomain

C T Source # 
Instance details

Defined in Number.Peano

Methods

div :: T -> T -> T Source #

mod :: T -> T -> T Source #

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

(Ord a, C a) => C (T a) Source # 
Instance details

Defined in Number.NonNegative

Methods

div :: T a -> T a -> T a Source #

mod :: T a -> T a -> T a Source #

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

Integral a => C (T a) Source # 
Instance details

Defined in MathObj.Wrapper.Haskell98

Methods

div :: T a -> T a -> T a Source #

mod :: T a -> T a -> T a Source #

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

(Ord a, C a, C a) => C (T a) Source #

divMod is implemented in terms of divModStrict. If it is needed we could also provide a function that accesses the divisor first in a lazy way and then uses a strict divisor for subsequent rounds of the subtraction loop. This way we can handle the cases "dividend smaller than divisor" and "dividend greater than divisor" in a lazy and efficient way. However changing the way of operation within one number is also not nice.

Instance details

Defined in Number.NonNegativeChunky

Methods

div :: T a -> T a -> T a Source #

mod :: T a -> T a -> T a Source #

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

(C a, C a) => C (T a) Source # 
Instance details

Defined in MathObj.PowerSeries

Methods

div :: T a -> T a -> T a Source #

mod :: T a -> T a -> T a Source #

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

(C a, C a) => C (T a) Source #

The C instance is intensionally built from the C structure of the polynomial coefficients. If we would use Integral.C a superclass, then the Euclidean algorithm could not determine the greatest common divisor of e.g. [1,1] and [2].

Instance details

Defined in MathObj.Polynomial

Methods

div :: T a -> T a -> T a Source #

mod :: T a -> T a -> T a Source #

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

C a => C (T a) Source # 
Instance details

Defined in Number.Complex

Methods

div :: T a -> T a -> T a Source #

mod :: T a -> T a -> T a Source #

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

C a => C (T a) Source # 
Instance details

Defined in MathObj.Wrapper.NumericPrelude

Methods

div :: T a -> T a -> T a Source #

mod :: T a -> T a -> T a Source #

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

div, mod :: C a => a -> a -> a infixl 7 `div`, `mod` Source #

div, mod :: C a => a -> a -> a infixl 7 `mod`, `div` Source #

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

Derived functions

divModZero :: (C a, C a) => a -> a -> (a, a) Source #

Allows division by zero. If the divisor is zero, then the dividend is returned as remainder.

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

sameResidueClass :: (C a, C a) => a -> a -> a -> Bool Source #

divChecked :: (C a, C a) => a -> a -> a Source #

Returns the result of the division, if divisible. Otherwise undefined.

safeDiv :: (C a, C a) => a -> a -> a Source #

Deprecated: use divChecked instead

Returns the result of the division, if divisible. Otherwise undefined.

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

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

divUp :: C a => a -> a -> a Source #

divUp n m is similar to div but it rounds up the quotient, such that divUp n m * m = roundUp n m.

roundDown :: C a => a -> a -> a Source #

roundDown n m rounds n down to the next multiple of m. That is, roundDown n m is the greatest multiple of m that is at most n. The parameter order is consistent with div and friends, but maybe not useful for partial application.

roundUp :: C a => a -> a -> a Source #

roundUp n m rounds n up to the next multiple of m. That is, roundUp n m is the greatest multiple of m that is at most n.

Algorithms

decomposeVarPositional :: (C a, C a) => [a] -> a -> [a] Source #

decomposeVarPositional [b0,b1,b2,...] x decomposes x into a positional representation with mixed bases x0 + b0*(x1 + b1*(x2 + b2*x3)) E.g. decomposeVarPositional (repeat 10) 123 == [3,2,1]

decomposeVarPositionalInf :: C a => [a] -> a -> [a] Source #

Properties

propInverse :: (Eq a, C a, C a) => a -> a -> Property Source #

propMultipleDiv :: (Eq a, C a, C a) => a -> a -> Property Source #

propMultipleMod :: (Eq a, C a, C a) => a -> a -> Property Source #

propProjectAddition :: (Eq a, C a, C a) => a -> a -> a -> Property Source #

propProjectMultiplication :: (Eq a, C a, C a) => a -> a -> a -> Property Source #

propUniqueRepresentative :: (Eq a, C a, C a) => a -> a -> a -> Property Source #

propSameResidueClass :: (Eq a, C a, C a) => a -> a -> a -> Property Source #