| Copyright | (c) Erich Gut |
|---|---|
| License | BSD3 |
| Maintainer | zerich.gut@gmail.com |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
OAlg.Structure.Number.Definition
Description
definition of numbers as ordered Semiring with infinitely many elements.
Synopsis
- class (Semiring r, Commutative r, Ord r) => Number r where
- zFloor :: Number r => r -> Z
- toDigits :: (Number r, KnownNat b, 2 <= b) => r -> Digits b r
- data Digits (b :: Nat) r where
- toDigitsFinite :: (Number r, KnownNat b, 2 <= b) => N -> r -> Digits b r
- fromDigits :: (Number r, Acyclic r, KnownNat b) => N -> Digits b r -> r
- dgsBase :: KnownNat b => Digits b r -> N
- dgsProxy :: Digits b r -> Proxy b
- dgsFrcTake :: N -> Digits b r -> Digits b r
- class Number a => Integral a where
- primes :: [N]
- class (Distributive a, Abelian a, Invertible a) => Acyclic a where
- type Fractional r = (Number r, Abelian r, Acyclic r)
- class (Entity a, Number r) => Measurable a r where
- dist :: a -> a -> r
Number
class (Semiring r, Commutative r, Ord r) => Number r where Source #
ordered commutative semi ring where + and * respect the given ordering.
Definitions
- A number
xis called positive if0 < xand negative ifx < 0. - A number structure is called positive if it contains no negative elements.
Properties
1is positive.- For all
x < yandzholds:x+z < y+z - For all
0 < x,0 < yholds:0 < x.*y - For all
xholds:x ==.signumx*absx - For all
xholds:.floorx+fractionx == x
Note
Minimal complete definition
Methods
the additive inverse of 1 - if it exists - and will be
denoted by -1 (see the note above).
sign of a number.
Property For all x holds: if 0 < x then signum x == 1 and if x == 0
then signum x == 0 and if x < 0 then signum x == -1 (for -1 see ).minusOne
Note The default implementation is:
signum x = case rZero compare x of
GT -> rOne
EQ -> rZero
LT -> e where Just e = minusOne
absolute value of a number.
Definition The absolute value of a x is defined by
abs x = (which serves as the default implementation).signum x * x
Properties For all x holds:
0 <= abs x.- if
0 <= xthenabs x == x.
fractional part of a number.
Property For all x holds: 0 <= fraction x < 1.
zFloorFraction :: r -> (Z, r) Source #
digital represenation of numbers
toDigits :: (Number r, KnownNat b, 2 <= b) => r -> Digits b r Source #
the digital representation of x in the base b.
Let thenDigits s xs ys = toDigits r
sis the.signumxxsis the digital representation of.abs(floorx)ysis the - possibly infinite - digital representation ofin the baseabs(fractionx)b.
Examples
>>>toDigits (1/3) :: Digits 10 QDigits 1 [] [3,3,3..]
>>>toDigits (-4/3) :: Digits 3 QDigits (-1) [1] [1]
Note To get the first n digits of the fractional part ys for the digital
representation of x use .toDigitsFinite n x
data Digits (b :: Nat) r where Source #
digital representation of numbers for the given base b.
Note
Constructors
| Digits | |
Instances
| Show r => Show (Digits b r) Source # | |
| Eq r => Eq (Digits b r) Source # | |
| Ord r => Ord (Digits b r) Source # | |
Defined in OAlg.Structure.Number.Definition | |
| Validable r => Validable (Digits b r) Source # | |
| (KnownNat b, Entity r) => Entity (Digits b r) Source # | |
Defined in OAlg.Structure.Number.Definition | |
toDigitsFinite :: (Number r, KnownNat b, 2 <= b) => N -> r -> Digits b r Source #
toDigitsFinite n is like toDigits but the fractional part is limited to the
length of n and is given by .dgsFrcTake n . toDigits
fromDigits :: (Number r, Acyclic r, KnownNat b) => N -> Digits b r -> r Source #
fromDigits n dgs@( is given by
Digits s xs ys)s
where * (xm * b^m + .. + xi * b^i + .. + x0 * b^0 + y1 * r^1 + .. + yj * r^j + .. + yn * r^nb = , dgsBase dgsxs = [xm..xi..x0], ys = [y1,y2..yj..yn..]
and r = .invert b
Property Let 1 and < bdgs = where Digits s xs yss is either 1 or -1
and 0 for all <= xi < bi and 0 for all <= yj < bj
then for all n holds: .toDigits b n (fromDigits b n dgs) == dgs
Note
dgsBase :: KnownNat b => Digits b r -> N Source #
the base of a digit, i.e. the corresponding natural number of the type literal b.
dgsFrcTake :: N -> Digits b r -> Digits b r Source #
limits the fractional part dgsFrc to the length of n.
Integral
class Number a => Integral a where Source #
Minimal complete definition
Acyclic
class (Distributive a, Abelian a, Invertible a) => Acyclic a where Source #
distributive structure with entities scaleable by Q.
Property For every 0 and point < np holds: is
invertible.ntimes n (one p)
Note
Minimal complete definition
Nothing
Methods
Fractional
type Fractional r = (Number r, Abelian r, Acyclic r) Source #
continuous numbers, i.e acyclic and negateable numbers. They induce a sub
-vectorial structures of the real numbers.Q
Note We will distinguish here instances of and the mathematical
entities of real numbers! Fractional
Measurable
class (Entity a, Number r) => Measurable a r where Source #
measurable entities.
Methods
distance of two points.
Properties Let a r be Measurable, then holds:
- For all
xandyinaholds:0 <= dist x y - For all
xandyinaholds:dist x y == 0if and only ifx == y. - For all
xandyinaholds:dist x y == dist y x. - For all
x,yandzinaholds:dist x z<=dist x y+dist y z