numeric-prelude-0.4.4: An experimental alternative hierarchy of numeric type classes
Safe HaskellNone
LanguageHaskell98

Algebra.RealRing

Synopsis

Documentation

>>> import qualified Algebra.RealRing as RealRing
>>> import Data.Tuple.HT (mapFst)
>>> import NumericPrelude.Numeric as NP
>>> import NumericPrelude.Base
>>> import Prelude ()
>>> 
>>> infix 4 =~=
>>> 
>>> (=~=) :: (Eq b) => (a -> b) -> (a -> b) -> a -> Bool
>>> (f =~= g) x = f x == g x

class (C a, Ord a) => C a where Source #

Minimal complete definition: splitFraction or floor

There are probably more laws, but some laws are

splitFraction x === (fromInteger (floor x), fraction x)
fromInteger (floor x) + fraction x === x
floor x       <= x       x <  floor x + 1
ceiling x - 1 <  x       x <= ceiling x
0 <= fraction x          fraction x < 1
              - ceiling x === floor (-x)
               truncate x === signum x * floor (abs x)
   ceiling (toRational x) === ceiling x :: Integer
  truncate (toRational x) === truncate x :: Integer
     floor (toRational x) === floor x :: Integer

The new function fraction doesn't return the integer part of the number. This also removes a type ambiguity if the integer part is not needed.

Many people will associate rounding with fractional numbers, and thus they are surprised about the superclass being Ring not Field. The reason is that all of these methods can be defined exclusively with functions from Ord and Ring. The implementations of genericFloor and other functions demonstrate that. They implement power-of-two-algorithms like the one for finding the number of digits of an Integer in FixedPoint-fractions module. They are even reasonably efficient.

I am still uncertain whether it was a good idea to add instances for Integer and friends, since calling floor or fraction on an integer may well indicate a bug. The rounding functions are just the identity function and fraction is constant zero. However, I decided to associate our class with Ring rather than Field, after I found myself using repeated subtraction and testing rather than just calling fraction, just in order to get the constraint (Ring a, Ord a) that was more general than (RealField a).

For the results of the rounding functions we have chosen the constraint Ring instead of ToInteger, since this is more flexible to use, but it still signals to the user that only integral numbers can be returned. This is so, because the plain Ring class only provides zero, one and operations that allow to reach all natural numbers but not more.

As an aside, let me note the similarities between splitFraction x and divMod x 1 (if that were defined). In particular, it might make sense to unify the rounding modes somehow.

The new methods fraction and splitFraction differ from properFraction semantics. They always round to floor. This means that the fraction is always non-negative and is always smaller than 1. This is more useful in practice and can be generalised to more than real numbers. Since every T denominator type supports divMod, every T can provide fraction and splitFraction, e.g. fractions of polynomials. However the Ring constraint for the 'integral' part of splitFraction is too weak in order to generate polynomials. After all, I am uncertain whether this would be useful or not.

Can there be a separate class for fraction, splitFraction, floor and ceiling since they do not need reals and their ordering?

We might also add a round method, that rounds 0.5 always up or always down. This is much more efficient in inner loops and is acceptable or even preferable for many applications.

Minimal complete definition

splitFraction | floor

Methods

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

\x -> (x::Rational) == (uncurry (+) $ mapFst fromInteger $ splitFraction x)
\x -> uncurry (==) $ mapFst (((x::Double)-) . fromInteger) $ splitFraction x
\x -> uncurry (==) $ mapFst (((x::Rational)-) . fromInteger) $ splitFraction x
\x -> splitFraction x == (floor (x::Double) :: Integer, fraction x)
\x -> splitFraction x == (floor (x::Rational) :: Integer, fraction x)

fraction :: a -> a Source #

\x -> let y = fraction (x::Double) in 0<=y && y<1
\x -> let y = fraction (x::Rational) in 0<=y && y<1

ceiling :: C b => a -> b Source #

\x -> ceiling (-x) == negate (floor (x::Double) :: Integer)
\x -> ceiling (-x) == negate (floor (x::Rational) :: Integer)

floor :: C b => a -> b Source #

\x -> ceiling (-x) == negate (floor (x::Double) :: Integer)
\x -> ceiling (-x) == negate (floor (x::Rational) :: Integer)

truncate :: C b => a -> b Source #

round :: C b => a -> b Source #

Instances

Instances details
C Double Source # 
Instance details

Defined in Algebra.RealRing

Methods

splitFraction :: C b => Double -> (b, Double) Source #

fraction :: Double -> Double Source #

ceiling :: C b => Double -> b Source #

floor :: C b => Double -> b Source #

truncate :: C b => Double -> b Source #

round :: C b => Double -> b Source #

C Float Source # 
Instance details

Defined in Algebra.RealRing

Methods

splitFraction :: C b => Float -> (b, Float) Source #

fraction :: Float -> Float Source #

ceiling :: C b => Float -> b Source #

floor :: C b => Float -> b Source #

truncate :: C b => Float -> b Source #

round :: C b => Float -> b Source #

C Int Source # 
Instance details

Defined in Algebra.RealRing

Methods

splitFraction :: C b => Int -> (b, Int) Source #

fraction :: Int -> Int Source #

ceiling :: C b => Int -> b Source #

floor :: C b => Int -> b Source #

truncate :: C b => Int -> b Source #

round :: C b => Int -> b Source #

C Int8 Source # 
Instance details

Defined in Algebra.RealRing

Methods

splitFraction :: C b => Int8 -> (b, Int8) Source #

fraction :: Int8 -> Int8 Source #

ceiling :: C b => Int8 -> b Source #

floor :: C b => Int8 -> b Source #

truncate :: C b => Int8 -> b Source #

round :: C b => Int8 -> b Source #

C Int16 Source # 
Instance details

Defined in Algebra.RealRing

Methods

splitFraction :: C b => Int16 -> (b, Int16) Source #

fraction :: Int16 -> Int16 Source #

ceiling :: C b => Int16 -> b Source #

floor :: C b => Int16 -> b Source #

truncate :: C b => Int16 -> b Source #

round :: C b => Int16 -> b Source #

C Int32 Source # 
Instance details

Defined in Algebra.RealRing

Methods

splitFraction :: C b => Int32 -> (b, Int32) Source #

fraction :: Int32 -> Int32 Source #

ceiling :: C b => Int32 -> b Source #

floor :: C b => Int32 -> b Source #

truncate :: C b => Int32 -> b Source #

round :: C b => Int32 -> b Source #

C Int64 Source # 
Instance details

Defined in Algebra.RealRing

Methods

splitFraction :: C b => Int64 -> (b, Int64) Source #

fraction :: Int64 -> Int64 Source #

ceiling :: C b => Int64 -> b Source #

floor :: C b => Int64 -> b Source #

truncate :: C b => Int64 -> b Source #

round :: C b => Int64 -> b Source #

C Integer Source # 
Instance details

Defined in Algebra.RealRing

Methods

splitFraction :: C b => Integer -> (b, Integer) Source #

fraction :: Integer -> Integer Source #

ceiling :: C b => Integer -> b Source #

floor :: C b => Integer -> b Source #

truncate :: C b => Integer -> b Source #

round :: C b => Integer -> b Source #

C Word8 Source # 
Instance details

Defined in Algebra.RealRing

Methods

splitFraction :: C b => Word8 -> (b, Word8) Source #

fraction :: Word8 -> Word8 Source #

ceiling :: C b => Word8 -> b Source #

floor :: C b => Word8 -> b Source #

truncate :: C b => Word8 -> b Source #

round :: C b => Word8 -> b Source #

C Word16 Source # 
Instance details

Defined in Algebra.RealRing

Methods

splitFraction :: C b => Word16 -> (b, Word16) Source #

fraction :: Word16 -> Word16 Source #

ceiling :: C b => Word16 -> b Source #

floor :: C b => Word16 -> b Source #

truncate :: C b => Word16 -> b Source #

round :: C b => Word16 -> b Source #

C Word32 Source # 
Instance details

Defined in Algebra.RealRing

Methods

splitFraction :: C b => Word32 -> (b, Word32) Source #

fraction :: Word32 -> Word32 Source #

ceiling :: C b => Word32 -> b Source #

floor :: C b => Word32 -> b Source #

truncate :: C b => Word32 -> b Source #

round :: C b => Word32 -> b Source #

C Word64 Source # 
Instance details

Defined in Algebra.RealRing

Methods

splitFraction :: C b => Word64 -> (b, Word64) Source #

fraction :: Word64 -> Word64 Source #

ceiling :: C b => Word64 -> b Source #

floor :: C b => Word64 -> b Source #

truncate :: C b => Word64 -> b Source #

round :: C b => Word64 -> b Source #

C T Source # 
Instance details

Defined in Number.FixedPoint.Check

Methods

splitFraction :: C b => T -> (b, T) Source #

fraction :: T -> T Source #

ceiling :: C b => T -> b Source #

floor :: C b => T -> b Source #

truncate :: C b => T -> b Source #

round :: C b => T -> b Source #

C T Source # 
Instance details

Defined in Number.Positional.Check

Methods

splitFraction :: C b => T -> (b, T) Source #

fraction :: T -> T Source #

ceiling :: C b => T -> b Source #

floor :: C b => T -> b Source #

truncate :: C b => T -> b Source #

round :: C b => T -> b Source #

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

Defined in Number.NonNegative

Methods

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

fraction :: T a -> T a Source #

ceiling :: C b => T a -> b Source #

floor :: C b => T a -> b Source #

truncate :: C b => T a -> b Source #

round :: C b => T a -> b Source #

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

Defined in Algebra.RealRing

Methods

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

fraction :: T a -> T a Source #

ceiling :: C b => T a -> b Source #

floor :: C b => T a -> b Source #

truncate :: C b => T a -> b Source #

round :: C b => T a -> b Source #

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

Defined in MathObj.Wrapper.Haskell98

Methods

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

fraction :: T a -> T a Source #

ceiling :: C b => T a -> b Source #

floor :: C b => T a -> b Source #

truncate :: C b => T a -> b Source #

round :: C b => T a -> b Source #

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

Defined in MathObj.Wrapper.NumericPrelude

Methods

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

fraction :: T a -> T a Source #

ceiling :: C b => T a -> b Source #

floor :: C b => T a -> b Source #

truncate :: C b => T a -> b Source #

round :: C b => T a -> b Source #

roundSimple :: (C a, C b) => a -> b Source #

This function rounds to the closest integer. For fraction x == 0.5 it rounds away from zero. This function is not the result of an ingenious mathematical insight, but is simply a kind of rounding that is the fastest on IEEE floating point architectures.

fastSplitFraction :: (RealFrac a, C a, C b) => (a -> Int) -> (Int -> a) -> a -> (b, a) Source #

fixSplitFraction :: (C a, C b, Ord a) => (b, a) -> (b, a) Source #

fixFraction :: (C a, Ord a) => a -> a Source #

splitFractionInt :: (C a, Ord a) => (a -> Int) -> (Int -> a) -> a -> (Int, a) Source #

floorInt :: (C a, Ord a) => (a -> Int) -> (Int -> a) -> a -> Int Source #

ceilingInt :: (C a, Ord a) => (a -> Int) -> (Int -> a) -> a -> Int Source #

roundInt :: (C a, Ord a) => (a -> Int) -> (Int -> a) -> a -> Int Source #

roundSimpleInt :: (C a, C a, Ord a) => (a -> Int) -> (Int -> a) -> a -> Int Source #

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

TODO: Should be moved to a continued fraction module.

generic implementation of round functions

powersOfTwo :: C a => [a] Source #

pairsOfPowersOfTwo :: (C a, C b) => [(a, b)] Source #

genericFloor :: (Ord a, C a, C b) => a -> b Source #

The generic rounding functions need a number of operations proportional to the number of binary digits of the integer portion. If operations like multiplication with two and comparison need time proportional to the number of binary digits, then the overall rounding requires quadratic time.

RealRing.genericFloor =~= (NP.floor :: Double -> Integer)
RealRing.genericFloor =~= (NP.floor :: Rational -> Integer)

genericCeiling :: (Ord a, C a, C b) => a -> b Source #

RealRing.genericCeiling =~= (NP.ceiling :: Double -> Integer)
RealRing.genericCeiling =~= (NP.ceiling :: Rational -> Integer)

genericTruncate :: (Ord a, C a, C b) => a -> b Source #

RealRing.genericTruncate =~= (NP.truncate :: Double -> Integer)
RealRing.genericTruncate =~= (NP.truncate :: Rational -> Integer)

genericRound :: (Ord a, C a, C b) => a -> b Source #

RealRing.genericRound =~= (NP.round :: Double -> Integer)
RealRing.genericRound =~= (NP.round :: Rational -> Integer)

genericFraction :: (Ord a, C a) => a -> a Source #

RealRing.genericFraction =~= (NP.fraction :: Double -> Double)
RealRing.genericFraction =~= (NP.fraction :: Rational -> Rational)

genericSplitFraction :: (Ord a, C a, C b) => a -> (b, a) Source #

RealRing.genericSplitFraction =~= (NP.splitFraction :: Double -> (Integer,Double))
RealRing.genericSplitFraction =~= (NP.splitFraction :: Rational -> (Integer,Rational))

genericPosFloor :: (Ord a, C a, C b) => a -> b Source #

genericPosCeiling :: (Ord a, C a, C b) => a -> b Source #

genericHalfPosFloorDigits :: (Ord a, C a, C b) => a -> ((a, b), [Bool]) Source #

genericPosRound :: (Ord a, C a, C b) => a -> b Source #

genericPosFraction :: (Ord a, C a) => a -> a Source #

genericPosSplitFraction :: (Ord a, C a, C b) => a -> (b, a) Source #

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

Needs linear time with respect to the number of digits.

This and other functions using OrderDecision like floor where argument and result are the same may be moved to a new module.

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