newsynth-0.3.0.4: Exact and approximate synthesis of quantum circuits

Safe HaskellNone
LanguageHaskell98

Quantum.Synthesis.Ring

Contents

Description

This module provides type classes for rings. It also provides several specific instances of rings, such as the ring ℤ₂ of integers modulo 2, the ring ℚ of rational numbers, the ring ℤ[½] of dyadic fractions, the ring ℤ[i] of Gaussian integers, the ring ℤ[√2] of quadratic integers with radix 2, and the ring ℤ[ω] of cyclotomic integers of degree 8.

Synopsis

Rings

class Num a => Ring a Source #

A type class to denote rings. We make Ring a synonym of Haskell's Num type class, so that we can use the usual notation +, -, * for the ring operations. This is not a perfect fit, because Haskell's Num class also contains two non-ring operations abs and signum. By convention, for rings where these notions don't make sense (or are inconvenient to define), we set abs x = x and signum x = 1.

Instances

Num a => Ring a Source # 

Rings with particular elements

We define several classes of rings with special elements.

Rings with ½

class Ring a => HalfRing a where Source #

A type class for rings that contain ½.

Minimal complete definition: half. The default definition of fromDyadic uses the expression a*half^n. However, this can give potentially bad round-off errors for fixed-precision types where the expression half^n can underflow. For such rings, one should provide a custom definition, for example by using a/2^n instead.

Minimal complete definition

half

Methods

half :: a Source #

The value ½.

fromDyadic :: Dyadic -> a Source #

The unique ring homomorphism from ℤ[½] to any HalfRing. This exists because ℤ[½] is the free HalfRing.

Rings with √2

class Ring a => RootTwoRing a where Source #

A type class for rings that contain √2.

Minimal complete definition: roottwo. The default definition of fromZRootTwo uses the expression x+roottwo*y. However, this can give potentially bad round-off errors for fixed-precision types, where the expression roottwo*y can be vastly inaccurate if y is large. For such rings, one should provide a custom definition.

Minimal complete definition

roottwo

Methods

roottwo :: a Source #

The square root of 2.

fromZRootTwo :: RootTwoRing a => ZRootTwo -> a Source #

The unique ring homomorphism from ℤ[√2] to any ring containing √2. This exists because ℤ[√2] is the free such ring.

Rings with 1/√2

class (HalfRing a, RootTwoRing a) => RootHalfRing a where Source #

A type class for rings that contain 1/√2.

Minimal complete definition: roothalf. The default definition of fromDRootTwo uses the expression x+roottwo*y. However, this can give potentially bad round-off errors for fixed-precision types, where the expression roottwo*y can be vastly inaccurate if y is large. For such rings, one should provide a custom definition.

Minimal complete definition

roothalf

Methods

roothalf :: a Source #

The square root of ½.

fromDRootTwo :: RootHalfRing a => DRootTwo -> a Source #

The unique ring homomorphism from D[√2] to any ring containing 1/√2. This exists because D[√2] = ℤ[1/√2] is the free such ring.

Rings with i

class Ring a => ComplexRing a where Source #

A type class for rings that contain a square root of -1.

Minimal complete definition

i

Methods

i :: a Source #

The complex unit.

Instances

(Ring a, RealFloat a) => ComplexRing (Complex a) Source # 

Methods

i :: Complex a Source #

Ring a => ComplexRing (Omega a) Source # 

Methods

i :: Omega a Source #

Ring a => ComplexRing (Cplx a) Source # 

Methods

i :: Cplx a Source #

(Eq a, ComplexRing a) => ComplexRing (RootTwo a) Source # 

Methods

i :: RootTwo a Source #

(ComplexRing a, Nat n) => ComplexRing (Matrix n n a) Source # 

Methods

i :: Matrix n n a Source #

Rings with ω

class Ring a => OmegaRing a where Source #

A type class for rings that contain a square root of i, or equivalently, a fourth root of −1.

Minimal complete definition

omega

Methods

omega :: a Source #

The square root of i.

Rings with particular automorphisms

Rings with complex conjugation

class Adjoint a where Source #

A type class for rings with complex conjugation, i.e., an automorphism mapping i to −i.

When instances of this type class are vectors or matrices, the conjugation also exchanges the roles of rows and columns (in other words, it is the adjoint).

For rings that are not complex, the conjugation can be defined to be the identity function.

Minimal complete definition

adj

Methods

adj :: a -> a Source #

Compute the adjoint (complex conjugate transpose).

Instances

Adjoint Double Source # 

Methods

adj :: Double -> Double Source #

Adjoint Float Source # 

Methods

adj :: Float -> Float Source #

Adjoint Int Source # 

Methods

adj :: Int -> Int Source #

Adjoint Integer Source # 

Methods

adj :: Integer -> Integer Source #

Adjoint Rational Source # 
Adjoint Rationals Source # 
Adjoint Dyadic Source # 

Methods

adj :: Dyadic -> Dyadic Source #

Adjoint Z2 Source # 

Methods

adj :: Z2 -> Z2 Source #

(Adjoint a, Ring a) => Adjoint (Complex a) Source # 

Methods

adj :: Complex a -> Complex a Source #

(Adjoint a, Ring a) => Adjoint (Omega a) Source # 

Methods

adj :: Omega a -> Omega a Source #

(Adjoint a, Ring a) => Adjoint (Cplx a) Source # 

Methods

adj :: Cplx a -> Cplx a Source #

Adjoint a => Adjoint (RootTwo a) Source # 

Methods

adj :: RootTwo a -> RootTwo a Source #

(Nat n, Adjoint a) => Adjoint (Matrix n n a) Source # 

Methods

adj :: Matrix n n a -> Matrix n n a Source #

Rings with √2-conjugation

class Adjoint2 a where Source #

A type class for rings with a √2-conjugation, i.e., an automorphism mapping √2 to −√2.

When instances of this type class are vectors or matrices, the √2-conjugation does not exchange the roles of rows and columns.

For rings that have no √2, the conjugation can be defined to be the identity function.

Minimal complete definition

adj2

Methods

adj2 :: a -> a Source #

Compute the adjoint, mapping a + b√2 to ab√2.

Instances

Adjoint2 Int Source # 

Methods

adj2 :: Int -> Int Source #

Adjoint2 Integer Source # 

Methods

adj2 :: Integer -> Integer Source #

Adjoint2 Rational Source # 
Adjoint2 Rationals Source # 
Adjoint2 Dyadic Source # 

Methods

adj2 :: Dyadic -> Dyadic Source #

Adjoint2 Z2 Source # 

Methods

adj2 :: Z2 -> Z2 Source #

(Adjoint2 a, Ring a) => Adjoint2 (Omega a) Source # 

Methods

adj2 :: Omega a -> Omega a Source #

(Adjoint2 a, Ring a) => Adjoint2 (Cplx a) Source # 

Methods

adj2 :: Cplx a -> Cplx a Source #

(Adjoint2 a, Num a) => Adjoint2 (RootTwo a) Source # 

Methods

adj2 :: RootTwo a -> RootTwo a Source #

(Nat n, Adjoint2 a) => Adjoint2 (Matrix n n a) Source # 

Methods

adj2 :: Matrix n n a -> Matrix n n a Source #

Normed rings

class Ring r => NormedRing r where Source #

A (number-theoretic) norm on a ring R is a function N : R → ℤ such that N(rs) = N(r)N(s), for all r, sR. The norm also satisfies N(r) = 0 iff r = 0, and N(r) = ±1 iff r is a unit of the ring.

Minimal complete definition

norm

Methods

norm :: r -> Integer Source #

Floor and ceiling

class Ring r => Floor r where Source #

The floor and ceiling functions provided by the standard Haskell libraries are predicated on many unnecessary assumptions. This type class provides an alternative.

Minimal complete definition: floor_of or ceiling_of.

Methods

floor_of :: r -> Integer Source #

Compute the floor of x, i.e., the greatest integer n such that nx.

ceiling_of :: r -> Integer Source #

Compute the ceiling of x, i.e., the least integer n such that xn.

Particular rings

The ring ℤ₂ of integers modulo 2

data Z2 Source #

The ring ℤ₂ of integers modulo 2.

Constructors

Even 
Odd 

Instances

Eq Z2 Source # 

Methods

(==) :: Z2 -> Z2 -> Bool #

(/=) :: Z2 -> Z2 -> Bool #

Num Z2 Source # 

Methods

(+) :: Z2 -> Z2 -> Z2 #

(-) :: Z2 -> Z2 -> Z2 #

(*) :: Z2 -> Z2 -> Z2 #

negate :: Z2 -> Z2 #

abs :: Z2 -> Z2 #

signum :: Z2 -> Z2 #

fromInteger :: Integer -> Z2 #

Show Z2 Source # 

Methods

showsPrec :: Int -> Z2 -> ShowS #

show :: Z2 -> String #

showList :: [Z2] -> ShowS #

Adjoint2 Z2 Source # 

Methods

adj2 :: Z2 -> Z2 Source #

Adjoint Z2 Source # 

Methods

adj :: Z2 -> Z2 Source #

Residue Integer Z2 Source # 

Methods

residue :: Integer -> Z2 Source #

OmegaRing (Omega Z2) Source # 

Methods

omega :: Omega Z2 Source #

ShowLaTeX (Omega Z2) Source # 

The ring D of dyadic fractions

data Dyadic Source #

A dyadic fraction is a rational number whose denominator is a power of 2. We denote the dyadic fractions by D = ℤ[½].

We internally represent a dyadic fraction a/2n as a pair (a,n). Note that this representation is not unique. When it is necessary to choose a canonical representative, we choose the least possible n≥0.

Constructors

Dyadic !Integer !Integer 

Instances

Eq Dyadic Source # 

Methods

(==) :: Dyadic -> Dyadic -> Bool #

(/=) :: Dyadic -> Dyadic -> Bool #

Num Dyadic Source # 
Ord Dyadic Source # 
Real Dyadic Source # 
Show DOmega Source # 
Show DRComplex Source # 
Show Dyadic Source # 
ToQOmega Dyadic Source # 
DenomExp DOmega Source # 
DenomExp DRootTwo Source # 
Adjoint2 Dyadic Source # 

Methods

adj2 :: Dyadic -> Dyadic Source #

Adjoint Dyadic Source # 

Methods

adj :: Dyadic -> Dyadic Source #

HalfRing Dyadic Source # 
ShowLaTeX DOmega Source # 
ShowLaTeX Dyadic Source # 
WholePart DOmega ZOmega Source # 
WholePart DRootTwo ZRootTwo Source # 
WholePart Dyadic Integer Source # 
ToDyadic Rational Dyadic Source # 
ToDyadic Rationals Dyadic Source # 
ToDyadic Dyadic Dyadic Source # 
Nat m => Show (Matrix m n DOmega) # 

Methods

showsPrec :: Int -> Matrix m n DOmega -> ShowS #

show :: Matrix m n DOmega -> String #

showList :: [Matrix m n DOmega] -> ShowS #

Nat m => Show (Matrix m n DRComplex) # 
Nat m => Show (Matrix m n DRootTwo) # 
Nat n => ShowLaTeX (Matrix n m DRComplex) Source # 
Nat n => ShowLaTeX (Matrix n m DOmega) Source # 

decompose_dyadic :: Dyadic -> (Integer, Integer) Source #

Given a dyadic fraction r, return (a,n) such that r = a/2n, where n≥0 is chosen as small as possible.

integer_of_dyadic :: Dyadic -> Integer -> Integer Source #

Given a dyadic fraction r and an integer k≥0, such that a = r2k is an integer, return a. If a is not an integer, the behavior is undefined.

The ring ℚ of rational numbers

newtype Rationals Source #

We define our own variant of the rational numbers, which is an identical copy of the type Rational from the standard Haskell library, except that it has a more sensible Show instance.

Constructors

ToRationals 

Instances

Eq Rationals Source # 
Fractional Rationals Source # 
Num Rationals Source # 
Ord Rationals Source # 
Real Rationals Source # 
RealFrac Rationals Source # 
Show Rationals Source # 
ToQOmega Rationals Source # 
Floor QRootTwo Source # 
Floor Rationals Source # 
Adjoint2 Rationals Source # 
Adjoint Rationals Source # 
HalfRing Rationals Source # 
ToDyadic Rationals Dyadic Source # 

showsPrec_rational :: (Show a, Integral a) => Int -> Ratio a -> ShowS Source #

An auxiliary function for printing rational numbers, using correct precedences, and omitting denominators of 1.

fromRationals :: Fractional a => Rationals -> a Source #

Conversion from Rationals to any Fractional type.

The ring R[√2]

data RootTwo a Source #

The ring R[√2], where R is any ring. The value RootTwo a b represents a + b √2.

Constructors

RootTwo !a !a 

Instances

Show DRComplex Source # 
Parity ZRootTwo Source # 

Methods

parity :: ZRootTwo -> Z2 Source #

DenomExp DRootTwo Source # 
Floor QRootTwo Source # 
EuclideanDomain ZRootTwo Source # 
WholePart DRootTwo ZRootTwo Source # 
Eq a => Eq (RootTwo a) Source # 

Methods

(==) :: RootTwo a -> RootTwo a -> Bool #

(/=) :: RootTwo a -> RootTwo a -> Bool #

(Eq a, Fractional a) => Fractional (RootTwo a) Source # 

Methods

(/) :: RootTwo a -> RootTwo a -> RootTwo a #

recip :: RootTwo a -> RootTwo a #

fromRational :: Rational -> RootTwo a #

(Eq a, Num a) => Num (RootTwo a) Source # 

Methods

(+) :: RootTwo a -> RootTwo a -> RootTwo a #

(-) :: RootTwo a -> RootTwo a -> RootTwo a #

(*) :: RootTwo a -> RootTwo a -> RootTwo a #

negate :: RootTwo a -> RootTwo a #

abs :: RootTwo a -> RootTwo a #

signum :: RootTwo a -> RootTwo a #

fromInteger :: Integer -> RootTwo a #

(Eq a, Ring a) => Ord (RootTwo a) Source # 

Methods

compare :: RootTwo a -> RootTwo a -> Ordering #

(<) :: RootTwo a -> RootTwo a -> Bool #

(<=) :: RootTwo a -> RootTwo a -> Bool #

(>) :: RootTwo a -> RootTwo a -> Bool #

(>=) :: RootTwo a -> RootTwo a -> Bool #

max :: RootTwo a -> RootTwo a -> RootTwo a #

min :: RootTwo a -> RootTwo a -> RootTwo a #

(Show a, Eq a, Ring a) => Show (RootTwo a) Source # 

Methods

showsPrec :: Int -> RootTwo a -> ShowS #

show :: RootTwo a -> String #

showList :: [RootTwo a] -> ShowS #

ToQOmega a => ToQOmega (RootTwo a) Source # 

Methods

toQOmega :: RootTwo a -> QOmega Source #

(Eq a, NormedRing a) => NormedRing (RootTwo a) Source # 

Methods

norm :: RootTwo a -> Integer Source #

(Adjoint2 a, Num a) => Adjoint2 (RootTwo a) Source # 

Methods

adj2 :: RootTwo a -> RootTwo a Source #

Adjoint a => Adjoint (RootTwo a) Source # 

Methods

adj :: RootTwo a -> RootTwo a Source #

(Eq a, ComplexRing a) => ComplexRing (RootTwo a) Source # 

Methods

i :: RootTwo a Source #

(Eq a, HalfRing a) => RootHalfRing (RootTwo a) Source # 
(Eq a, Ring a) => RootTwoRing (RootTwo a) Source # 
(Eq a, HalfRing a) => HalfRing (RootTwo a) Source # 
(ShowLaTeX a, Eq a, Ring a) => ShowLaTeX (RootTwo a) Source # 
HalfRing a => RealPart (Omega a) (RootTwo a) Source # 

Methods

real :: Omega a -> RootTwo a Source #

ToDyadic a b => ToDyadic (RootTwo a) (RootTwo b) Source # 
Residue a b => Residue (RootTwo a) (RootTwo b) Source # 

Methods

residue :: RootTwo a -> RootTwo b Source #

Nat m => Show (Matrix m n DRComplex) # 
Nat m => Show (Matrix m n DRootTwo) # 
Nat n => ShowLaTeX (Matrix n m DRComplex) Source # 

The ring ℤ[√2]

type ZRootTwo = RootTwo Integer Source #

The ring ℤ[√2].

zroottwo_root :: ZRootTwo -> Maybe ZRootTwo Source #

Return a square root of an element of ℤ[√2], if such a square root exists, or else Nothing.

The ring D[√2]

type DRootTwo = RootTwo Dyadic Source #

The ring D[√2] = ℤ[1/√2].

The field ℚ[√2]

type QRootTwo = RootTwo Rationals Source #

The field ℚ[√2].

fromQRootTwo :: (RootTwoRing a, Fractional a) => QRootTwo -> a Source #

The unique ring homomorphism from ℚ[√2] to any ring containing the rational numbers and √2. This exists because ℚ[√2] is the free such ring.

The ring R[i]

data Cplx a Source #

The ring R[i], where R is any ring. The reason we do not use the Complex a type from the standard Haskell libraries is that it assumes too much, for example, it assumes a is a member of the RealFloat class. Also, this allows us to define a more sensible Show instance.

Constructors

Cplx !a !a 

Instances

Show DRComplex Source # 
EuclideanDomain ZComplex Source # 
Eq a => Eq (Cplx a) Source # 

Methods

(==) :: Cplx a -> Cplx a -> Bool #

(/=) :: Cplx a -> Cplx a -> Bool #

Fractional a => Fractional (Cplx a) Source # 

Methods

(/) :: Cplx a -> Cplx a -> Cplx a #

recip :: Cplx a -> Cplx a #

fromRational :: Rational -> Cplx a #

Num a => Num (Cplx a) Source # 

Methods

(+) :: Cplx a -> Cplx a -> Cplx a #

(-) :: Cplx a -> Cplx a -> Cplx a #

(*) :: Cplx a -> Cplx a -> Cplx a #

negate :: Cplx a -> Cplx a #

abs :: Cplx a -> Cplx a #

signum :: Cplx a -> Cplx a #

fromInteger :: Integer -> Cplx a #

(Eq a, Show a, Num a) => Show (Cplx a) Source # 

Methods

showsPrec :: Int -> Cplx a -> ShowS #

show :: Cplx a -> String #

showList :: [Cplx a] -> ShowS #

ToQOmega a => ToQOmega (Cplx a) Source # 

Methods

toQOmega :: Cplx a -> QOmega Source #

DenomExp a => DenomExp (Cplx a) Source # 
NormedRing a => NormedRing (Cplx a) Source # 

Methods

norm :: Cplx a -> Integer Source #

(Adjoint2 a, Ring a) => Adjoint2 (Cplx a) Source # 

Methods

adj2 :: Cplx a -> Cplx a Source #

(Adjoint a, Ring a) => Adjoint (Cplx a) Source # 

Methods

adj :: Cplx a -> Cplx a Source #

Ring a => ComplexRing (Cplx a) Source # 

Methods

i :: Cplx a Source #

RootHalfRing a => RootHalfRing (Cplx a) Source # 
RootTwoRing a => RootTwoRing (Cplx a) Source # 
HalfRing a => HalfRing (Cplx a) Source # 
(ShowLaTeX a, Ring a, Eq a) => ShowLaTeX (Cplx a) Source # 
RealPart (Cplx a) a Source # 

Methods

real :: Cplx a -> a Source #

WholePart a b => WholePart (Cplx a) (Cplx b) Source # 

Methods

from_whole :: Cplx b -> Cplx a Source #

to_whole :: Cplx a -> Cplx b Source #

ToDyadic a b => ToDyadic (Cplx a) (Cplx b) Source # 

Methods

maybe_dyadic :: Cplx a -> Maybe (Cplx b) Source #

Residue a b => Residue (Cplx a) (Cplx b) Source # 

Methods

residue :: Cplx a -> Cplx b Source #

Nat m => Show (Matrix m n DRComplex) # 
Nat n => ShowLaTeX (Matrix n m DRComplex) Source # 

The ring ℤ[i] of Gaussian integers

type ZComplex = Cplx Integer Source #

The ring ℤ[i] of Gaussian integers.

fromZComplex :: ComplexRing a => ZComplex -> a Source #

The unique ring homomorphism from ℤ[i] to any ring containing i. This exists because ℤ[i] is the free such ring.

The ring D[i]

type DComplex = Cplx Dyadic Source #

The ring D[i] = ℤ[½, i] of Gaussian dyadic fractions.

fromDComplex :: (ComplexRing a, HalfRing a) => DComplex -> a Source #

The unique ring homomorphism from D[i] to any ring containing ½ and i. This exists because D[i] is the free such ring.

The ring ℚ[i] of Gaussian rationals

type QComplex = Cplx Rationals Source #

The ring ℚ[i] of Gaussian rationals.

fromQComplex :: (ComplexRing a, Fractional a) => QComplex -> a Source #

The unique ring homomorphism from ℚ[i] to any ring containing the rational numbers and i. This exists because ℚ[i] is the free such ring.

The ring D[√2, i]

type DRComplex = Cplx DRootTwo Source #

The ring D[√2, i] = ℤ[1/√2, i].

fromDRComplex :: (RootHalfRing a, ComplexRing a) => DRComplex -> a Source #

The unique ring homomorphism from D[√2, i] to any ring containing 1/√2 and i. This exists because D[√2, i] = ℤ[1/√2, i] is the free such ring.

The ring ℚ[√2, i]

type QRComplex = Cplx QRootTwo Source #

The field ℚ[√2, i].

fromQRComplex :: (RootTwoRing a, ComplexRing a, Fractional a) => QRComplex -> a Source #

The unique ring homomorphism from ℚ[√2, i] to any ring containing the rational numbers, √2, and i. This exists because ℚ[√2, i] is the free such ring.

The ring ℂ of complex numbers

We provide two versions of the complex numbers using floating point arithmetic.

type CDouble = Cplx Double Source #

Double precision complex floating point numbers.

type CFloat = Cplx Float Source #

Single precision complex floating point numbers.

The ring R[ω]

data Omega a Source #

The ring R[ω], where R is any ring, and ω = eiπ/4 is an 8th root of unity. The value Omega a b c d represents aω3+bω2+cω+d.

Constructors

Omega !a !a !a !a 

Instances

Show DOmega Source # 
DenomExp DOmega Source # 
OmegaRing ZOmega Source # 

Methods

omega :: ZOmega Source #

EuclideanDomain ZOmega Source # 
ShowLaTeX DOmega Source # 
ShowLaTeX ZOmega Source # 
WholePart DOmega ZOmega Source # 
Eq a => Eq (Omega a) Source # 

Methods

(==) :: Omega a -> Omega a -> Bool #

(/=) :: Omega a -> Omega a -> Bool #

Fractional a => Fractional (Omega a) Source # 

Methods

(/) :: Omega a -> Omega a -> Omega a #

recip :: Omega a -> Omega a #

fromRational :: Rational -> Omega a #

Num a => Num (Omega a) Source # 

Methods

(+) :: Omega a -> Omega a -> Omega a #

(-) :: Omega a -> Omega a -> Omega a #

(*) :: Omega a -> Omega a -> Omega a #

negate :: Omega a -> Omega a #

abs :: Omega a -> Omega a #

signum :: Omega a -> Omega a #

fromInteger :: Integer -> Omega a #

(Show a, Ring a) => Show (Omega a) Source # 

Methods

showsPrec :: Int -> Omega a -> ShowS #

show :: Omega a -> String #

showList :: [Omega a] -> ShowS #

ToQOmega a => ToQOmega (Omega a) Source # 

Methods

toQOmega :: Omega a -> QOmega Source #

NormedRing a => NormedRing (Omega a) Source # 

Methods

norm :: Omega a -> Integer Source #

(Adjoint2 a, Ring a) => Adjoint2 (Omega a) Source # 

Methods

adj2 :: Omega a -> Omega a Source #

(Adjoint a, Ring a) => Adjoint (Omega a) Source # 

Methods

adj :: Omega a -> Omega a Source #

OmegaRing (Omega Z2) Source # 

Methods

omega :: Omega Z2 Source #

Ring a => ComplexRing (Omega a) Source # 

Methods

i :: Omega a Source #

HalfRing a => RootHalfRing (Omega a) Source # 
Ring a => RootTwoRing (Omega a) Source # 
HalfRing a => HalfRing (Omega a) Source # 
ShowLaTeX (Omega Z2) Source # 
HalfRing a => RealPart (Omega a) (RootTwo a) Source # 

Methods

real :: Omega a -> RootTwo a Source #

ToDyadic a b => ToDyadic (Omega a) (Omega b) Source # 

Methods

maybe_dyadic :: Omega a -> Maybe (Omega b) Source #

Residue a b => Residue (Omega a) (Omega b) Source # 

Methods

residue :: Omega a -> Omega b Source #

Nat m => Show (Matrix m n DOmega) # 

Methods

showsPrec :: Int -> Matrix m n DOmega -> ShowS #

show :: Matrix m n DOmega -> String #

showList :: [Matrix m n DOmega] -> ShowS #

Nat n => ShowLaTeX (Matrix n m DOmega) Source # 

omega_real :: Omega a -> a Source #

An inverse to the embedding RR[ω]: return the "real rational" part. In other words, map aω3+bω2+cω+d to d.

The ring ℤ[ω]

type ZOmega = Omega Integer Source #

The ring ℤ[ω] of cyclotomic integers of degree 8. Such rings were first studied by Kummer around 1840, and used in his proof of special cases of Fermat's Last Theorem. See also:

fromZOmega :: OmegaRing a => ZOmega -> a Source #

The unique ring homomorphism from ℤ[ω] to any ring containing ω. This exists because ℤ[ω] is the free such ring.

zroottwo_of_zomega :: ZOmega -> ZRootTwo Source #

Inverse of the embedding ℤ[√2] → ℤ[ω]. Note that ℤ[√2] = ℤ[ω] ∩ ℝ. This function takes an element of ℤ[ω] that is real, and converts it to an element of ℤ[√2]. It throws an error if the input is not real.

The ring D[ω]

type DOmega = Omega Dyadic Source #

The ring D[ω]. Here D=ℤ[½] is the ring of dyadic fractions. In fact, D[ω] is isomorphic to the ring D[√2, i], but they have different Show instances.

fromDOmega :: (RootHalfRing a, ComplexRing a) => DOmega -> a Source #

The unique ring homomorphism from D[ω] to any ring containing 1/√2 and i. This exists because D[ω] is the free such ring.

The field ℚ[ω]

type QOmega = Omega Rationals Source #

The field ℚ[ω] of cyclotomic rationals of degree 8.

fromQOmega :: (RootHalfRing a, ComplexRing a, Fractional a) => QOmega -> a Source #

The unique ring homomorphism from ℚ[ω] to any ring containing the rational numbers, √2, and i. This exists because ℚ[ω] is the free such ring.

Conversion to dyadic

class ToDyadic a b | a -> b where Source #

A type class relating "rational" types to their dyadic counterparts.

Minimal complete definition

maybe_dyadic

Methods

maybe_dyadic :: a -> Maybe b Source #

Convert a "rational" value to a "dyadic" value, if the denominator is a power of 2. Otherwise, return Nothing.

to_dyadic :: ToDyadic a b => a -> b Source #

Convert a "rational" value to a "dyadic" value, if the denominator is a power of 2. Otherwise, throw an error.

Real part

class RealPart a b | a -> b where Source #

A type class for rings that have a "real" component. A typical instance is a = DRComplex with b = DRootTwo.

Minimal complete definition

real

Methods

real :: a -> b Source #

Take the real part.

Instances

RealPart (Cplx a) a Source # 

Methods

real :: Cplx a -> a Source #

HalfRing a => RealPart (Omega a) (RootTwo a) Source # 

Methods

real :: Omega a -> RootTwo a Source #

Rings of integers

class WholePart a b | a -> b where Source #

A type class for rings that have a distinguished subring "of integers". A typical instance is a = DRootTwo, which has b = ZRootTwo as its ring of integers.

Minimal complete definition

from_whole, to_whole

Methods

from_whole :: b -> a Source #

The embedding of the ring of integers into the larger ring.

to_whole :: a -> b Source #

The inverse of from_whole. Throws an error if the given element is not actually an integer in the ring.

Instances

WholePart () () Source # 

Methods

from_whole :: () -> () Source #

to_whole :: () -> () Source #

WholePart DOmega ZOmega Source # 
WholePart DRootTwo ZRootTwo Source # 
WholePart Dyadic Integer Source # 
WholePart a b => WholePart [a] [b] Source # 

Methods

from_whole :: [b] -> [a] Source #

to_whole :: [a] -> [b] Source #

WholePart a b => WholePart (Cplx a) (Cplx b) Source # 

Methods

from_whole :: Cplx b -> Cplx a Source #

to_whole :: Cplx a -> Cplx b Source #

(WholePart a a', WholePart b b') => WholePart (a, b) (a', b') Source # 

Methods

from_whole :: (a', b') -> (a, b) Source #

to_whole :: (a, b) -> (a', b') Source #

WholePart a b => WholePart (Vector n a) (Vector n b) Source # 

Methods

from_whole :: Vector n b -> Vector n a Source #

to_whole :: Vector n a -> Vector n b Source #

WholePart a b => WholePart (Matrix m n a) (Matrix m n b) Source # 

Methods

from_whole :: Matrix m n b -> Matrix m n a Source #

to_whole :: Matrix m n a -> Matrix m n b Source #

Common denominators

class DenomExp a where Source #

A type class for things from which a common power of 1/√2 (a least denominator exponent) can be factored out. Typical instances are DRootTwo, DRComplex, as well as tuples, lists, vectors, and matrices thereof.

Minimal complete definition

denomexp, denomexp_factor

Methods

denomexp :: a -> Integer Source #

Calculate the least denominator exponent k of a. Returns the smallest k≥0 such that a = b/√2k for some integral b.

denomexp_factor :: a -> Integer -> a Source #

Factor out a kth power of 1/√2 from a. In other words, calculate a√2k.

denomexp_decompose :: (WholePart a b, DenomExp a) => a -> (b, Integer) Source #

Calculate and factor out the least denominator exponent k of a. Return (b,k), where a = b/(√2)k and k≥0.

showsPrec_DenomExp :: (WholePart a b, Show b, DenomExp a) => Int -> a -> ShowS Source #

Generic show-like method that factors out a common denominator exponent.

Conversion to ℚ[ω]

QOmega is the largest one of our "exact" arithmetic types. We define a toQOmega family of functions for converting just about anything to QOmega.

class ToQOmega a where Source #

A type class for things that can be exactly converted to ℚ[ω].

Minimal complete definition

toQOmega

Methods

toQOmega :: a -> QOmega Source #

Conversion to QOmega.

Parity

class Parity a where Source #

A type class for things that have parity.

Minimal complete definition

parity

Methods

parity :: a -> Z2 Source #

Return the parity of something.

Instances

Integral a => Parity a Source # 

Methods

parity :: a -> Z2 Source #

Parity ZRootTwo Source # 

Methods

parity :: ZRootTwo -> Z2 Source #

Auxiliary functions

lobit :: Integer -> Integer Source #

Return the position of the rightmost "1" bit of an Integer, or -1 if none. Do this in time O(n log n), where n is the size of the integer (in digits).

log2 :: Integer -> Maybe Integer Source #

If n is of the form 2k, return k. Otherwise, return Nothing.

hibit :: Integer -> Int Source #

Return 1 + the position of the leftmost "1" bit of a non-negative Integer. Do this in time O(n log n), where n is the size of the integer (in digits).

intsqrt :: Integral n => n -> n Source #

For n ≥ 0, return the floor of the square root of n. This is done using integer arithmetic, so there are no rounding errors.