Copyright | (c) Erich Gut |
---|---|
License | BSD3 |
Maintainer | zerich.gut@gmail.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
basic number types.
Synopsis
- data N
- (>-) :: N -> N -> N
- class LengthN x where
- takeN :: N -> [a] -> [a]
- splitAtN :: N -> [x] -> ([x], [x])
- data Z
- data Integer
- data Int
- modInt :: Int -> Int -> Int
- divInt :: Int -> Int -> Int
- data Q
- (%) :: Z -> N -> Q
- numerator :: Q -> Z
- denominator :: Q -> N
- class Enum a where
- succ :: a -> a
- pred :: a -> a
- toEnum :: Int -> a
- fromEnum :: a -> Int
- enumFrom :: a -> [a]
- enumFromThen :: a -> a -> [a]
- enumFromTo :: a -> a -> [a]
- enumFromThenTo :: a -> a -> a -> [a]
- enum :: (Ord i, Enum i) => i -> i -> [i]
Natural Numbers
natural numbers 0, 1, 2..
.
Instances
(>-) :: N -> N -> N infixl 6 Source #
a >- b = a - b
if b <= a
, otherwise a
exception will be
thrown.Undefined
SubtrahendToBig
class LengthN x where Source #
types admitting a length.
Instances
LengthN N' Source # | |
LengthN W' Source # | |
LengthN (W n) Source # | |
LengthN (ProductSymbol x) Source # | |
Defined in OAlg.Entity.Product.ProductSymbol lengthN :: ProductSymbol x -> N Source # | |
LengthN (Permutation i) Source # | |
Defined in OAlg.Entity.Sequence.Permutation lengthN :: Permutation i -> N Source # | |
LengthN (PermutationForm i) Source # | |
Defined in OAlg.Entity.Sequence.Permutation lengthN :: PermutationForm i -> N Source # | |
LengthN (Set x) Source # | |
LengthN (Path q) Source # | |
LengthN [x] Source # | |
Defined in OAlg.Data.Number | |
LengthN (Dim x p) Source # | |
LengthN (Col i x) Source # | |
LengthN (Row j x) Source # | |
LengthN (Product N a) Source # | |
LengthN (ProductForm N a) Source # | |
Defined in OAlg.Entity.Product.Definition | |
LengthN (Graph i x) Source # | |
LengthN (PSequence i x) Source # | |
LengthN (SumForm N a) Source # | |
LengthN (Entries i j x) Source # | |
splitAtN :: N -> [x] -> ([x], [x]) Source #
splits a list in left and right part according to the given number.
Integers
integers ..-1, 0, 1, 2..
.
Instances
Arbitrary precision integers. In contrast with fixed-size integral types
such as Int
, the Integer
type represents the entire infinite range of
integers.
Integers are stored in a kind of sign-magnitude form, hence do not expect two's complement form when using bit operations.
If the value is small (fit into an Int
), IS
constructor is used.
Otherwise Integer
and IN
constructors are used to store a BigNat
representing respectively the positive or the negative value magnitude.
Invariant: Integer
and IN
are used iff value doesn't fit in IS
Instances
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
minBound
and maxBound
from the Bounded
class.
Instances
Rationals
rational numbers q = z
with %
n
and numerator
q == z
.denominator
q == n
Instances
denominator :: Q -> N Source #
denominator of a rational.
Example
>>>
denominator (3/2)
2
Enum
Class Enum
defines operations on sequentially ordered types.
The enumFrom
... methods are used in Haskell's translation of
arithmetic sequences.
Instances of Enum
may be derived for any enumeration type (types
whose constructors have no fields). The nullary constructors are
assumed to be numbered left-to-right by fromEnum
from 0
through n-1
.
See Chapter 10 of the Haskell Report for more details.
For any type that is an instance of class Bounded
as well as Enum
,
the following should hold:
- The calls
andsucc
maxBound
should result in a runtime error.pred
minBound
fromEnum
andtoEnum
should give a runtime error if the result value is not representable in the result type. For example,
is an error.toEnum
7 ::Bool
enumFrom
andenumFromThen
should be defined with an implicit bound, thus:
enumFrom x = enumFromTo x maxBound enumFromThen x y = enumFromThenTo x y bound where bound | fromEnum y >= fromEnum x = maxBound | otherwise = minBound
the successor of a value. For numeric types, succ
adds 1.
the predecessor of a value. For numeric types, pred
subtracts 1.
Convert from an Int
.
Convert to an Int
.
It is implementation-dependent what fromEnum
returns when
applied to a value that is too large to fit in an Int
.
Used in Haskell's translation of [n..]
with [n..] = enumFrom n
,
a possible implementation being enumFrom n = n : enumFrom (succ n)
.
For example:
enumFrom 4 :: [Integer] = [4,5,6,7,...]
enumFrom 6 :: [Int] = [6,7,8,9,...,maxBound :: Int]
enumFromThen :: a -> a -> [a] #
Used in Haskell's translation of [n,n'..]
with [n,n'..] = enumFromThen n n'
, a possible implementation being
enumFromThen n n' = n : n' : worker (f x) (f x n')
,
worker s v = v : worker s (s v)
, x = fromEnum n' - fromEnum n
and
f n y
| n > 0 = f (n - 1) (succ y)
| n < 0 = f (n + 1) (pred y)
| otherwise = y
For example:
enumFromThen 4 6 :: [Integer] = [4,6,8,10...]
enumFromThen 6 2 :: [Int] = [6,2,-2,-6,...,minBound :: Int]
enumFromTo :: a -> a -> [a] #
Used in Haskell's translation of [n..m]
with
[n..m] = enumFromTo n m
, a possible implementation being
enumFromTo n m
| n <= m = n : enumFromTo (succ n) m
| otherwise = []
.
For example:
enumFromTo 6 10 :: [Int] = [6,7,8,9,10]
enumFromTo 42 1 :: [Integer] = []
enumFromThenTo :: a -> a -> a -> [a] #
Used in Haskell's translation of [n,n'..m]
with
[n,n'..m] = enumFromThenTo n n' m
, a possible implementation
being enumFromThenTo n n' m = worker (f x) (c x) n m
,
x = fromEnum n' - fromEnum n
, c x = bool (>=) ((x 0)
f n y
| n > 0 = f (n - 1) (succ y)
| n < 0 = f (n + 1) (pred y)
| otherwise = y
and
worker s c v m
| c v m = v : worker s c (s v) m
| otherwise = []
For example:
enumFromThenTo 4 2 -6 :: [Integer] = [4,2,0,-2,-4,-6]
enumFromThenTo 6 8 2 :: [Int] = []