Copyright | (c) 2019 Andrew Lelechenko |
---|---|
License | BSD3 |
Maintainer | Andrew Lelechenko <andrew.lelechenko@gmail.com> |
Safe Haskell | Safe-Inferred |
Language | Haskell98 |
Synopsis
- class GcdDomain a => Euclidean a where
- class (Euclidean a, Ring a) => Field a
- class Semiring a => GcdDomain a where
- newtype WrappedIntegral a = WrapIntegral {
- unwrapIntegral :: a
- newtype WrappedFractional a = WrapFractional {
- unwrapFractional :: a
- gcdExt :: (Eq a, Euclidean a, Ring a) => a -> a -> (a, a)
Documentation
class GcdDomain a => Euclidean a where Source #
Informally speaking, Euclidean
is a superclass of Integral
,
lacking toInteger
, which allows to define division with remainder
for a wider range of types, e. g., complex integers
and polynomials with rational coefficients.
Euclidean
represents a
Euclidean domain
endowed by a given Euclidean function degree
.
No particular rounding behaviour is expected of quotRem
. E. g.,
it is not guaranteed to truncate towards zero or towards negative
infinity (cf. divMod
), and remainders are not guaranteed to be non-negative.
For a faithful representation of residue classes one can use
mod package instead.
quotRem :: a -> a -> (a, a) Source #
Division with remainder.
\x y -> y == 0 || let (q, r) = x `quotRem` y in x == q * y + r
quot :: a -> a -> a infixl 7 Source #
Division. Must match its default definition:
\x y -> quot x y == fst (quotRem x y)
rem :: a -> a -> a infixl 7 Source #
Remainder. Must match its default definition:
\x y -> rem x y == snd (quotRem x y)
degree :: a -> Natural Source #
Euclidean (aka degree, valuation, gauge, norm) function on a
. Usually
.fromIntegral
.
abs
degree
is rarely used by itself. Its purpose
is to provide an evidence of soundness of quotRem
by testing the following property:
\x y -> y == 0 || let (q, r) = x `quotRem` y in (r == 0 || degree r < degree y)
Instances
class (Euclidean a, Ring a) => Field a Source #
Instances
Field CDouble Source # | |
Defined in Data.Euclidean | |
Field CFloat Source # | |
Defined in Data.Euclidean | |
Field Mod2 Source # | |
Defined in Data.Euclidean | |
Field () Source # | |
Defined in Data.Euclidean | |
Field Double Source # | |
Defined in Data.Euclidean | |
Field Float Source # | |
Defined in Data.Euclidean | |
Field a => Field (Complex a) Source # | |
Defined in Data.Euclidean | |
Integral a => Field (Ratio a) Source # | |
Defined in Data.Euclidean | |
Fractional a => Field (WrappedFractional a) Source # | |
Defined in Data.Euclidean |
class Semiring a => GcdDomain a where Source #
GcdDomain
represents a
GCD domain.
This is a domain, where GCD can be defined,
but which does not necessarily allow a well-behaved
division with remainder (as in Euclidean
domains).
For example, there is no way to define rem
over
polynomials with integer coefficients such that
remainder is always "smaller" than divisor. However,
gcd
is still definable, just not by means of
Euclidean algorithm.
All methods of GcdDomain
have default implementations
in terms of Euclidean
. So most of the time
it is enough to write:
instance GcdDomain Foo instance Euclidean Foo where quotRem = ... degree = ...
Nothing
divide :: a -> a -> Maybe a infixl 7 Source #
Division without remainder.
\x y -> (x * y) `divide` y == Just x
\x y -> maybe True (\z -> x == z * y) (x `divide` y)
Greatest common divisor. Must satisfy
\x y -> isJust (x `divide` gcd x y) && isJust (y `divide` gcd x y)
\x y z -> isJust (gcd (x * z) (y * z) `divide` z)
Lowest common multiple. Must satisfy
\x y -> isJust (lcm x y `divide` x) && isJust (lcm x y `divide` y)
\x y z -> isNothing (z `divide` x) || isNothing (z `divide` y) || isJust (z `divide` lcm x y)
coprime :: a -> a -> Bool Source #
Test whether two arguments are coprime. Must match its default definition:
\x y -> coprime x y == isJust (1 `divide` gcd x y)
Instances
newtype WrappedIntegral a Source #
Instances
newtype WrappedFractional a Source #
Wrapper around Fractional
with trivial GcdDomain
and Euclidean
instances.