Numeric Classes
The Haskell 98 numeric classes were designed to classify the operations
supported by the Haskell 98 types, Integer
, Int
, Float
, Double
,
Complex
and Ratio
. However they are not suitable for other mathematical
objects.
If the Haskell 98 classes were retained for backwards compatibility, but with a more refined class hierarchy, the change would impact mostly on those defining instances (and these are the people inconvenienced by the current system). Clients of the classes would notice only some more general types.
References
- other Issues with Standard Classes
- Standard Haskell Classes of Haskell 98
- Standard Prelude of Haskell 98
- Basic Algebra Proposal
- Numeric prelude project
Some standard algebraic structures
This is a partial list of common structures from abstract algebra. Structures further down and/or to the right are special cases of those further up and/or to the left:
Monoid | Commutative monoid | |
---|---|---|
Group | Abelian group | |
Ring | Commutative ring | |
Domain | Integral domain | |
Unique factorization domain | ||
Principal ideal domain | ||
Euclidean domain | ||
Division ring | Field |
See also Semiring, which also lies between commutative monoid and ring.
The Num class
Issues:
-
Eq
andShow
don't make sense for functions under lifting. -
(*)
doesn't make sense for vectors. -
abs
andsignum
don't make sense forComplex Integer
(Gaussian integers), vectors, matrices, etc. In general,abs
andsignum
make it hard to liftNum
through type constructors.
Proposals:
- A group-like class with
zero
,(+)
andnegate
/(-)
. - (Could be further split with a monoid sub-class.)
- A ring-like subclass adding
(*)
andone
/fromInteger
, with the existingNum
class as a further subclass. - (Could be further split with a semiring subclass, e.g. for natural numbers.)
Note that the Float
and Double
instances will not satisfy the usual axioms for these structures.
Proposed new classes:
class AbelianGroup a where -- could also factor out Monoid
zero :: a
(+), (-) :: a -> a -> a
negate :: a -> a
-- Minimal complete definition:
-- zero, (+) and (negate or (-))
negate x = zero - x
x - y = x + negate y
class AbelianGroup a => Ring a where
(*) :: a -> a -> a
one :: a
fromInteger :: Integer -> a
-- Minimal complete definition:
-- (*) and (one or fromInteger)
one = fromInteger 1
fromInteger n
| n < 0 = negate (fi (negate n))
| otherwise = fi n
where fi 0 = zero
fi 1 = one
fi n
| even n = fin + fin
| otherwise = fin + fin + one
where fin = fi (n `div` 2)
Haskell 98 compatibility class:
class (Eq a, Show a, Ring a) => Num a where
abs, signum :: a -> a
The Fractional class
Issues:
-
(/)
,recip
andfromRational
can be lifted to functions, but many of the pre-requisites can't be defined for these.
Proposals:
-
Add a division ring-like superclass adding these operations to the ring-like class. (A division ring has the same operations as a field, but does not assume commutative multiplication, allowing structures such as quaternions.)
-
Add default
fromRational x = fromInteger (numerator x) / fromInteger (denominator x)
This is independent of all the other proposals.
Proposed new classes:
class Ring a => DivisionRing a where
(/) :: a -> a -> a
recip :: a -> a
fromRational :: Rational -> a
-- Minimal complete definition:
-- recip or (/)
recip x = one / x
x / y = x * recip y
fromRational x = fromInteger (numerator x) /
fromInteger (denominator x)
class DivisionRing a => Field a
Haskell 98 compatibility class:
class (Num a, Field a) => Fractional a
The Real class
Issues:
- The class assumes a mapping to
Rational
, but this cannot be defined for structures intermediate between the rationals and reals even though the operations of subclasses make sense for them, e.g. surds, computable reals.
Proposal:
- Retain the class for backward compatibility only.
The Integral class
Issues:
- Division with remainder also makes sense for polynomials and Gaussian
integers, but not
Enum
,toInteger
,Ord
,Num(abs, signum)
ortoRational
. Provided any non-zero remainder is "smaller" than the divisor, in some well-founded sense, Euclid's algorithm terminates. - Defining
Ratio
also requires a canonical factorization of any element as x as y*
u where u is an invertible element (or unit). Any such y is called an associate of x. For integral types (but not others), this is similar tosignum
andabs
, but the general idea makes sense for any integral domain. - In algebra, each field is trivially a Euclidean domain, with the remainder always zero. However this would break backwards compatibility, as well as the programming languages convention of distinguishing integer division.
Proposal:
-
Add a Euclidean domain class, with canonical factorization satisfying
stdAssociate x * stdUnit x = x stdUnit (x*y) = stdUnit x * stdUnit y stdUnit x * (one `div` stdUnit x) = x x*y = one => stdUnit x = x
and either
divMod
orquotRem
. -
(Could be further split by placing canonical factorization in an integral domain class, but division would not be available for default definitions, and would also need to supply the reciprocal of
stdUnit x
.)
Proposed new class:
class Ring a => EuclideanDomain a where
stdAssociate :: a -> a
stdUnit :: a -> a
normalize :: a -> (a, a)
div, mod :: a -> a -> a
divMod :: a -> a -> (a,a)
-- Minimal complete definition:
-- (stdUnit or normalize) and (divMod or (div and mod))
stdAssociate x = x `div` stdUnit x
stdUnit x = snd (normalize x)
normalize x = (stdAssociate x, stdUnit x)
n `divMod` d = (n `div` d, n `mod` d)
n `div` d = q where (q,r) = divMod n d
n `mod` d = r where (q,r) = divMod n d
Haskell 98 compatibility class:
class (Real a, Enum a, EuclideanDomain a) => Integral a where
quot, rem :: a -> a -> a
quotRem :: a -> a -> (a,a)
toInteger :: a -> Integer
-- Minimal complete definition:
-- toInteger
n `quot` d = q where (q,r) = quotRem n d
n `rem` d = r where (q,r) = quotRem n d
quotRem n d = if signum r == - signum d then (q+one, r-d) else qr
where qr@(q,r) = divMod n d
The RealFloat class
Issues:
- The class groups together the trigonometric operation
atan2
with operations on the components of floating-point numbers.
Proposals
- add new subclasses for groups, rings, division rings and Euclidean domains, as above.
- as 1, plus additional subclasses that do not assume negation (monoid, semiring, etc). This would make most sense if we had natural numbers.