semirings-0.5.1: two monoids as one, in holy haskimony

Copyright(c) 2019 Andrew Lelechenko
LicenseBSD3
MaintainerAndrew Lelechenko <andrew.lelechenko@gmail.com>
Safe HaskellNone
LanguageHaskell98

Data.Euclidean

Description

 
Synopsis

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.

Minimal complete definition

quotRem, degree

Methods

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
Euclidean Double Source # 
Instance details

Defined in Data.Euclidean

Euclidean Float Source # 
Instance details

Defined in Data.Euclidean

Euclidean Int Source # 
Instance details

Defined in Data.Euclidean

Methods

quotRem :: Int -> Int -> (Int, Int) Source #

quot :: Int -> Int -> Int Source #

rem :: Int -> Int -> Int Source #

degree :: Int -> Natural Source #

Euclidean Integer Source # 
Instance details

Defined in Data.Euclidean

Euclidean Natural Source # 
Instance details

Defined in Data.Euclidean

Euclidean Word Source # 
Instance details

Defined in Data.Euclidean

Euclidean () Source # 
Instance details

Defined in Data.Euclidean

Methods

quotRem :: () -> () -> ((), ()) Source #

quot :: () -> () -> () Source #

rem :: () -> () -> () Source #

degree :: () -> Natural Source #

Euclidean CFloat Source # 
Instance details

Defined in Data.Euclidean

Euclidean CDouble Source # 
Instance details

Defined in Data.Euclidean

Integral a => Euclidean (Ratio a) Source # 
Instance details

Defined in Data.Euclidean

Methods

quotRem :: Ratio a -> Ratio a -> (Ratio a, Ratio a) Source #

quot :: Ratio a -> Ratio a -> Ratio a Source #

rem :: Ratio a -> Ratio a -> Ratio a Source #

degree :: Ratio a -> Natural Source #

Field a => Euclidean (Complex a) Source # 
Instance details

Defined in Data.Euclidean

Fractional a => Euclidean (WrappedFractional a) Source # 
Instance details

Defined in Data.Euclidean

Integral a => Euclidean (WrappedIntegral a) Source # 
Instance details

Defined in Data.Euclidean

class (Euclidean a, Ring a) => Field a Source #

A Field represents a field, a ring with a multiplicative inverse for any non-zero element.

Instances
Field Double Source # 
Instance details

Defined in Data.Euclidean

Field Float Source # 
Instance details

Defined in Data.Euclidean

Field () Source # 
Instance details

Defined in Data.Euclidean

Field CFloat Source # 
Instance details

Defined in Data.Euclidean

Field CDouble Source # 
Instance details

Defined in Data.Euclidean

Integral a => Field (Ratio a) Source # 
Instance details

Defined in Data.Euclidean

Field a => Field (Complex a) Source # 
Instance details

Defined in Data.Euclidean

Fractional a => Field (WrappedFractional a) Source # 
Instance details

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  = ...

Minimal complete definition

Nothing

Methods

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)

divide :: (Eq a, Euclidean a) => 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)

gcd :: a -> a -> a Source #

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)

gcd :: (Eq a, Euclidean a) => a -> a -> a Source #

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)

lcm :: a -> a -> a Source #

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)

lcm :: Eq a => a -> a -> a Source #

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)

coprime :: Eq a => 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
GcdDomain Double Source # 
Instance details

Defined in Data.Euclidean

GcdDomain Float Source # 
Instance details

Defined in Data.Euclidean

GcdDomain Int Source # 
Instance details

Defined in Data.Euclidean

Methods

divide :: Int -> Int -> Maybe Int Source #

gcd :: Int -> Int -> Int Source #

lcm :: Int -> Int -> Int Source #

coprime :: Int -> Int -> Bool Source #

GcdDomain Integer Source # 
Instance details

Defined in Data.Euclidean

GcdDomain Natural Source # 
Instance details

Defined in Data.Euclidean

GcdDomain Word Source # 
Instance details

Defined in Data.Euclidean

GcdDomain () Source # 
Instance details

Defined in Data.Euclidean

Methods

divide :: () -> () -> Maybe () Source #

gcd :: () -> () -> () Source #

lcm :: () -> () -> () Source #

coprime :: () -> () -> Bool Source #

GcdDomain CFloat Source # 
Instance details

Defined in Data.Euclidean

GcdDomain CDouble Source # 
Instance details

Defined in Data.Euclidean

Integral a => GcdDomain (Ratio a) Source # 
Instance details

Defined in Data.Euclidean

Methods

divide :: Ratio a -> Ratio a -> Maybe (Ratio a) Source #

gcd :: Ratio a -> Ratio a -> Ratio a Source #

lcm :: Ratio a -> Ratio a -> Ratio a Source #

coprime :: Ratio a -> Ratio a -> Bool Source #

Field a => GcdDomain (Complex a) Source # 
Instance details

Defined in Data.Euclidean

Fractional a => GcdDomain (WrappedFractional a) Source # 
Instance details

Defined in Data.Euclidean

Integral a => GcdDomain (WrappedIntegral a) Source # 
Instance details

Defined in Data.Euclidean

newtype WrappedIntegral a Source #

Wrapper around Integral with GcdDomain and Euclidean instances.

Constructors

WrapIntegral 

Fields

Instances
Enum a => Enum (WrappedIntegral a) Source # 
Instance details

Defined in Data.Euclidean

Eq a => Eq (WrappedIntegral a) Source # 
Instance details

Defined in Data.Euclidean

Integral a => Integral (WrappedIntegral a) Source # 
Instance details

Defined in Data.Euclidean

Num a => Num (WrappedIntegral a) Source # 
Instance details

Defined in Data.Euclidean

Ord a => Ord (WrappedIntegral a) Source # 
Instance details

Defined in Data.Euclidean

Real a => Real (WrappedIntegral a) Source # 
Instance details

Defined in Data.Euclidean

Show a => Show (WrappedIntegral a) Source # 
Instance details

Defined in Data.Euclidean

Bits a => Bits (WrappedIntegral a) Source # 
Instance details

Defined in Data.Euclidean

Num a => Ring (WrappedIntegral a) Source # 
Instance details

Defined in Data.Euclidean

Num a => Semiring (WrappedIntegral a) Source # 
Instance details

Defined in Data.Euclidean

Integral a => Euclidean (WrappedIntegral a) Source # 
Instance details

Defined in Data.Euclidean

Integral a => GcdDomain (WrappedIntegral a) Source # 
Instance details

Defined in Data.Euclidean

newtype WrappedFractional a Source #

Wrapper around Fractional with trivial GcdDomain and Euclidean instances.

Constructors

WrapFractional 

Fields

Instances
Eq a => Eq (WrappedFractional a) Source # 
Instance details

Defined in Data.Euclidean

Fractional a => Fractional (WrappedFractional a) Source # 
Instance details

Defined in Data.Euclidean

Num a => Num (WrappedFractional a) Source # 
Instance details

Defined in Data.Euclidean

Ord a => Ord (WrappedFractional a) Source # 
Instance details

Defined in Data.Euclidean

Show a => Show (WrappedFractional a) Source # 
Instance details

Defined in Data.Euclidean

Num a => Ring (WrappedFractional a) Source # 
Instance details

Defined in Data.Euclidean

Num a => Semiring (WrappedFractional a) Source # 
Instance details

Defined in Data.Euclidean

Fractional a => Field (WrappedFractional a) Source # 
Instance details

Defined in Data.Euclidean

Fractional a => Euclidean (WrappedFractional a) Source # 
Instance details

Defined in Data.Euclidean

Fractional a => GcdDomain (WrappedFractional a) Source # 
Instance details

Defined in Data.Euclidean