exp-pairs-0.2.1.0: Linear programming over exponent pairs

Copyright(c) Andrew Lelechenko 2014-2020
LicenseGPL-3
Maintainerandrew.lelechenko@gmail.com
Safe HaskellSafe
LanguageHaskell2010

Math.ExpPairs.Pair

Contents

Description

Initial exponent pairs.

Provides a set of initial exponent pairs, consisting of two points (0, 1), (1/2, 1/2) and a triangle with vertices in (1/6, 2/3), (2/13, 35/52) and (13/84, 55/84). The triangle is represented as a list of nodes of a net, covering the triangle.

Below A and B stands for van der Corput's processes. See Math.ExpPairs.Process for explanations.

Synopsis

Documentation

data Triangle Source #

Vertices of the triangle of initial exponent pairs.

Constructors

Corput16

Usual van der Corput exponent pair (1/6, 2/3) = AB(0, 1).

HuxW87b1

An exponent pair (2/13, 35/52) from Huxley M. N. `Exponential sums and the Riemann zeta function' // Proceedings of the International Number Theory Conference held at Universite Laval in 1987, Walter de Gruyter, 1989, P. 417-423.

Bourgain17

An exponent pair (13/84, 55/84) from Bourgain J. `Decoupling, exponential sums and the Riemann zeta function` // J. Amer. Math. Soc., 2017, 30, P. 205-224.

Instances
Bounded Triangle Source # 
Instance details

Defined in Math.ExpPairs.Pair

Enum Triangle Source # 
Instance details

Defined in Math.ExpPairs.Pair

Eq Triangle Source # 
Instance details

Defined in Math.ExpPairs.Pair

Ord Triangle Source # 
Instance details

Defined in Math.ExpPairs.Pair

Show Triangle Source # 
Instance details

Defined in Math.ExpPairs.Pair

Generic Triangle Source # 
Instance details

Defined in Math.ExpPairs.Pair

Associated Types

type Rep Triangle :: Type -> Type #

Methods

from :: Triangle -> Rep Triangle x #

to :: Rep Triangle x -> Triangle #

Pretty Triangle Source # 
Instance details

Defined in Math.ExpPairs.Pair

Methods

pretty :: Triangle -> Doc ann #

prettyList :: [Triangle] -> Doc ann #

type Rep Triangle Source # 
Instance details

Defined in Math.ExpPairs.Pair

type Rep Triangle = D1 (MetaData "Triangle" "Math.ExpPairs.Pair" "exp-pairs-0.2.1.0-J4IGbuSTVwXCgBqjoU0P5n" False) (C1 (MetaCons "Corput16" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "HuxW87b1" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Bourgain17" PrefixI False) (U1 :: Type -> Type)))

data InitPair' t Source #

Type to hold an initial exponent pair.

Constructors

Corput01

Usual van der Corput exponent pair (0, 1).

Corput12

Usual van der Corput exponent pair (1/2, 1/2) = B(0, 1).

Mix !t !t

Point from the interior of Triangle. Exactly Mix a b = a * Corput16 + b * HuxW87b1 + (1-a-b) * Bourgain17

Instances
Eq t => Eq (InitPair' t) Source # 
Instance details

Defined in Math.ExpPairs.Pair

Methods

(==) :: InitPair' t -> InitPair' t -> Bool #

(/=) :: InitPair' t -> InitPair' t -> Bool #

Ord t => Ord (InitPair' t) Source # 
Instance details

Defined in Math.ExpPairs.Pair

Show t => Show (InitPair' t) Source # 
Instance details

Defined in Math.ExpPairs.Pair

Generic (InitPair' t) Source # 
Instance details

Defined in Math.ExpPairs.Pair

Associated Types

type Rep (InitPair' t) :: Type -> Type #

Methods

from :: InitPair' t -> Rep (InitPair' t) x #

to :: Rep (InitPair' t) x -> InitPair' t #

(Pretty t, Num t, Eq t) => Pretty (InitPair' t) Source # 
Instance details

Defined in Math.ExpPairs.Pair

Methods

pretty :: InitPair' t -> Doc ann #

prettyList :: [InitPair' t] -> Doc ann #

type Rep (InitPair' t) Source # 
Instance details

Defined in Math.ExpPairs.Pair

type Rep (InitPair' t) = D1 (MetaData "InitPair'" "Math.ExpPairs.Pair" "exp-pairs-0.2.1.0-J4IGbuSTVwXCgBqjoU0P5n" False) (C1 (MetaCons "Corput01" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Corput12" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Mix" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 t) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 t))))

type InitPair = InitPair' Rational Source #

Exponent pair built from rational fractions of Corput16, HuxW87b1 and Hux05

initPairs :: [InitPair] Source #

The set of initial exponent pairs. It consists of Corput01, Corput12 and 496 = sum [1..31] Mix-points, which forms a uniform net over Triangle.

initPairToValue :: InitPair -> (Rational, Rational) Source #

Convert initial exponent pair from its symbolic representation as InitPair to pair of rationals.

initPairToProjValue :: InitPair -> (Integer, Integer, Integer) Source #

Same as initPairToValue, but immediately convert from Q^2 to PN^3.

Orphan instances

(Integral a, Show a) => Pretty (Ratio a) Source # 
Instance details

Methods

pretty :: Ratio a -> Doc ann #

prettyList :: [Ratio a] -> Doc ann #