numeric-prelude-0.4.3.3: An experimental alternative hierarchy of numeric type classes
Safe HaskellSafe-Inferred
LanguageHaskell98

Algebra.Ring

Synopsis

Class

class C a => C a Source #

Ring encapsulates the mathematical structure of a (not necessarily commutative) ring, with the laws

  a * (b * c) === (a * b) * c
      one * a === a
      a * one === a
  a * (b + c) === a * b + a * c

Typical examples include integers, polynomials, matrices, and quaternions.

Minimal definition: *, (one or fromInteger)

Minimal complete definition

(*), (one | fromInteger)

Instances

Instances details
C Double Source # 
Instance details

Defined in Algebra.Ring

C Float Source # 
Instance details

Defined in Algebra.Ring

C Int Source # 
Instance details

Defined in Algebra.Ring

C Int8 Source # 
Instance details

Defined in Algebra.Ring

C Int16 Source # 
Instance details

Defined in Algebra.Ring

C Int32 Source # 
Instance details

Defined in Algebra.Ring

C Int64 Source # 
Instance details

Defined in Algebra.Ring

C Integer Source # 
Instance details

Defined in Algebra.Ring

C Word Source # 
Instance details

Defined in Algebra.Ring

C Word8 Source # 
Instance details

Defined in Algebra.Ring

C Word16 Source # 
Instance details

Defined in Algebra.Ring

C Word32 Source # 
Instance details

Defined in Algebra.Ring

C Word64 Source # 
Instance details

Defined in Algebra.Ring

C T Source # 
Instance details

Defined in Number.Peano

Methods

(*) :: T -> T -> T Source #

one :: T Source #

fromInteger :: Integer -> T Source #

(^) :: T -> Integer -> T Source #

C T Source # 
Instance details

Defined in Number.GaloisField2p32m5

Methods

(*) :: T -> T -> T Source #

one :: T Source #

fromInteger :: Integer -> T Source #

(^) :: T -> Integer -> T Source #

C T Source # 
Instance details

Defined in Number.FixedPoint.Check

Methods

(*) :: T -> T -> T Source #

one :: T Source #

fromInteger :: Integer -> T Source #

(^) :: T -> Integer -> T Source #

C T Source # 
Instance details

Defined in Number.Positional.Check

Methods

(*) :: T -> T -> T Source #

one :: T Source #

fromInteger :: Integer -> T Source #

(^) :: T -> Integer -> T Source #

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

Defined in Algebra.Ring

Methods

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

one :: Ratio a Source #

fromInteger :: Integer -> Ratio a Source #

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

RealFloat a => C (Complex a) Source # 
Instance details

Defined in Algebra.Ring

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

Defined in Number.NonNegative

Methods

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

one :: T a Source #

fromInteger :: Integer -> T a Source #

(^) :: T a -> Integer -> T a Source #

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

Defined in Number.Ratio

Methods

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

one :: T a Source #

fromInteger :: Integer -> T a Source #

(^) :: T a -> Integer -> T a Source #

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

Defined in MathObj.Wrapper.Haskell98

Methods

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

one :: T a Source #

fromInteger :: Integer -> T a Source #

(^) :: T a -> Integer -> T a Source #

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

Defined in Number.ResidueClass.Maybe

Methods

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

one :: T a Source #

fromInteger :: Integer -> T a Source #

(^) :: T a -> Integer -> T a Source #

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

Defined in Number.ResidueClass.Func

Methods

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

one :: T a Source #

fromInteger :: Integer -> T a Source #

(^) :: T a -> Integer -> T a Source #

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

Defined in Number.ResidueClass.Check

Methods

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

one :: T a Source #

fromInteger :: Integer -> T a Source #

(^) :: T a -> Integer -> T a Source #

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

Defined in Number.PartiallyTranscendental

Methods

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

one :: T a Source #

fromInteger :: Integer -> T a Source #

(^) :: T a -> Integer -> T a Source #

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

Defined in Number.NonNegativeChunky

Methods

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

one :: T a Source #

fromInteger :: Integer -> T a Source #

(^) :: T a -> Integer -> T a Source #

C a => C (T a) Source #
QC.choose (1,10) /\ \expon (QC.Positive x) xs -> let xt = x:xs in  equalTrunc 15 (PS.pow (const x) (1 % expon) (PST.coeffs (PST.fromCoeffs xt ^ expon)) ++ repeat zero) (xt ++ repeat zero)
Instance details

Defined in MathObj.PowerSeries

Methods

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

one :: T a Source #

fromInteger :: Integer -> T a Source #

(^) :: T a -> Integer -> T a Source #

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

Defined in MathObj.PowerSeries2

Methods

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

one :: T a Source #

fromInteger :: Integer -> T a Source #

(^) :: T a -> Integer -> T a Source #

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

Defined in MathObj.Polynomial

Methods

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

one :: T a Source #

fromInteger :: Integer -> T a Source #

(^) :: T a -> Integer -> T a Source #

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

Defined in MathObj.PowerSum

Methods

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

one :: T a Source #

fromInteger :: Integer -> T a Source #

(^) :: T a -> Integer -> T a Source #

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

Defined in MathObj.RootSet

Methods

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

one :: T a Source #

fromInteger :: Integer -> T a Source #

(^) :: T a -> Integer -> T a Source #

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

Defined in MathObj.PartialFraction

Methods

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

one :: T a Source #

fromInteger :: Integer -> T a Source #

(^) :: T a -> Integer -> T a Source #

C a => C (T a) Source #
genIntMatrix /\ \a -> Laws.leftIdentity  (*) (Matrix.one (Matrix.numRows a)) a
genIntMatrix /\ \a -> Laws.rightIdentity (*) (Matrix.one (Matrix.numColumns a)) a
genIntMatrix /\ \a -> genFactorMatrix a /\ \b -> Laws.homomorphism Matrix.transpose (*) (flip (*)) a b
genIntMatrix /\ \a -> genFactorMatrix a /\ \b -> genFactorMatrix b /\ \c -> Laws.associative (*) a b c
genIntMatrix /\ \b -> genSameMatrix b /\ \c -> genFactorMatrix b /\ \a -> Laws.leftDistributive (*) (+) a b c
genIntMatrix /\ \a -> genFactorMatrix a /\ \b -> genSameMatrix b /\ \c -> Laws.rightDistributive (*) (+) a b c
QC.choose (0,10) /\ \k -> genDimension /\ \n -> genMatrixFor n n /\ \a -> a^k == nest (fromInteger k) ((a::Matrix.T Integer)*) (Matrix.one n)
Instance details

Defined in MathObj.Matrix

Methods

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

one :: T a Source #

fromInteger :: Integer -> T a Source #

(^) :: T a -> Integer -> T a Source #

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

Defined in Number.Complex

Methods

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

one :: T a Source #

fromInteger :: Integer -> T a Source #

(^) :: T a -> Integer -> T a Source #

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

Defined in Number.Quaternion

Methods

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

one :: T a Source #

fromInteger :: Integer -> T a Source #

(^) :: T a -> Integer -> T a Source #

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

Defined in MathObj.LaurentPolynomial

Methods

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

one :: T a Source #

fromInteger :: Integer -> T a Source #

(^) :: T a -> Integer -> T a Source #

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

Defined in MathObj.Wrapper.NumericPrelude

Methods

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

one :: T a Source #

fromInteger :: Integer -> T a Source #

(^) :: T a -> Integer -> T a Source #

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

Defined in MathObj.Algebra

Methods

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

one :: T a b Source #

fromInteger :: Integer -> T a b Source #

(^) :: T a b -> Integer -> T a b Source #

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

Defined in Number.OccasionallyScalarExpression

Methods

(*) :: T a v -> T a v -> T a v Source #

one :: T a v Source #

fromInteger :: Integer -> T a v Source #

(^) :: T a v -> Integer -> T a v Source #

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

Defined in Number.DimensionTerm

Methods

(*) :: T u a -> T u a -> T u a Source #

one :: T u a Source #

fromInteger :: Integer -> T u a Source #

(^) :: T u a -> Integer -> T u a Source #

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

Defined in Number.Physical

Methods

(*) :: T i a -> T i a -> T i a Source #

one :: T i a Source #

fromInteger :: Integer -> T i a Source #

(^) :: T i a -> Integer -> T i a Source #

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

Defined in Number.SI

Methods

(*) :: T a v -> T a v -> T a v Source #

one :: T a v Source #

fromInteger :: Integer -> T a v Source #

(^) :: T a v -> Integer -> T a v Source #

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

one :: C a => a Source #

(^) :: C a => a -> Integer -> a infixr 8 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.

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

Complex functions

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

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

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

Properties

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

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

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

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

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

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

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

Commutativity need not be satisfied by all instances of C.