newsynth-0.1.0.0: Exact and approximate synthesis of quantum circuits

Safe HaskellNone

Quantum.Synthesis.Newsynth

Contents

Description

This module implements an efficient single-qubit Clifford+T approximation algorithm. The algorithm is described here:

Synopsis

Miscellaneous functions

ensure :: Bool -> Maybe ()Source

A useful operation for the Maybe monad, used to ensure that some condition holds (i.e., return Nothing if the condition is false). To be used like this:

 do
   x <- something
   y <- something_else
   ensure (x > y)
   ...

maybe_head :: [a] -> Maybe aSource

Return the head of a list, if non-empty, or else Nothing.

power :: (a -> a -> a) -> a -> a -> Integer -> aSource

Exponentiation via repeated squaring, parameterized by a multiplication function and a unit. Given an associative multiplication function * with unit e, the function power (*) e a n efficiently computes an = a * (a * (… * (a * e)…)).

floorlog :: (Fractional b, Ord b) => b -> b -> (Integer, b)Source

Given positive numbers b and x, return (n, r) such that

  • x = r bn and
  • 1 ≤ r < b.

In other words, let n = ⌊logb x⌋ and r = x bn. This can be more efficient than floor (logBase b x) depending on the type; moreover, it also works for exact types such as Rational and QRootTwo.

Randomized algorithms

keeptrying :: RandomGen g => (g -> Maybe a) -> g -> aSource

A combinator for turning a probabilistic function that succeeds with some small probability into a probabilistic function that always succeeds, by trying again and again.

keeptrying_count :: RandomGen g => (g -> Maybe a) -> g -> (a, Integer)Source

Like keeptrying, but also returns a count of the number of attempts.

try_for :: RandomGen g => Integer -> (g -> Maybe a) -> g -> Maybe aSource

A combinator for turning a probabilistic function that succeeds with some small probability into a probabilistic function that succeeds with a higher probability, by repeating it n times.

Square roots in ℤ[√2]

zroottwo_root :: ZRootTwo -> Maybe ZRootTwoSource

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

Roots of −1 in ℤp

root_minus_one_step :: RandomGen g => Integer -> g -> Maybe IntegerSource

Input an integer p, and maybe output a root of −1 modulo p. This succeeds with probability at least 1/2 if p is a positive prime ≡ 1 (mod 4); otherwise, the success probability is unspecified (and may be 0).

root_minus_one :: RandomGen g => Integer -> g -> IntegerSource

Input a positive prime p ≡ 1 (mod 4), and output a root of −1.

Solving a Diophantine equation

dioph_step :: RandomGen g => ZRootTwo -> g -> Maybe ZOmegaSource

Input ξ ∈ ℤ[√2], and maybe output some t ∈ ℤ[ω] such that tt = ξ. If ξ ≥ 0, ξ ≥ 0 and p = ξξ is a prime ≡ 1 (mod 4) in ℤ, then this succeeds with probability at least 1/2. Otherwise, the success probability is unspecified and may be 0.

dioph :: RandomGen g => ZRootTwo -> g -> ZOmegaSource

Input ξ ∈ ℤ[√2] such that ξ ≥ 0, ξ ≥ 0, and p = ξξ is a prime ≡ 1 (mod 4) in ℤ. Output t ∈ ℤ[ω] such that tt = ξ. If the hypotheses are not satisfied, this will likely loop forever.

Approximations in ℤ[√2]

gridpoints :: (RootTwoRing r, Fractional r, Floor r, Ord r) => (r, r) -> (r, r) -> [ZRootTwo]Source

Input two intervals [x₀, x₁] ⊆ ℝ and [y₀, y₁] ⊆ ℝ. Output a list of all points z = a + √2b ∈ ℤ[√2] such that z ∈ [x₀, x₁] and z ∈ [y₀, y₁]. The list will be produced lazily, and will be sorted in order of increasing z.

It is a theorem that there will be at least one solution if ΔxΔy ≥ (1 + √2)², and at most one solution if ΔxΔy < 1, where Δx = x₁ − x₀ ≥ 0 and Δy = y₁ − y₀ ≥ 0. Asymptotically, the expected number of solutions is ΔxΔy/√8.

This function is formulated so that the intervals can be specified exactly (using a type such as QRootTwo), or approximately (using a type such as Double or FixedPrec e).

gridpoint_random :: (RootTwoRing r, Fractional r, Floor r, Ord r, RandomGen g) => (r, r) -> (r, r) -> g -> Maybe ZRootTwoSource

Input two intervals [x₀, x₁] ⊆ ℝ and [y₀, y₁] ⊆ ℝ and a source of randomness. Output a random element z = a + √2b ∈ ℤ[√2] such that z ∈ [x₀, x₁] and z ∈ [y₀, y₁].

Note: the randomness will not be uniform. To ensure that the set of solutions is non-empty, we must have ΔxΔy ≥ (1 + √2)², where Δx = x₁ − x₀ ≥ 0 and Δy = y₁ − y₀ ≥ 0. If there are no solutions at all, the function will return Nothing.

This function is formulated so that the intervals can be specified exactly (using a type such as QRootTwo), or approximately (using a type such as Double or FixedPrec e).

gridpoint_random_parity :: (RootTwoRing r, Fractional r, Floor r, Ord r, RandomGen g) => Integer -> (r, r) -> (r, r) -> g -> Maybe ZRootTwoSource

Input an integer e, two intervals [x₀, x₁] ⊆ ℝ and [y₀, y₁] ⊆ ℝ, and a source of randomness. Output random z = a + √2b ∈ ℤ[√2] such that a + √2b ∈ [x₀, x₁], a - √2b ∈ [y₀, y₁], and a-e is even.

Note: the randomness will not be uniform. To ensure that the set of solutions is non-empty, we must have ΔxΔy ≥ 2(√2 + 1)², where Δx = x₁ − x₀ ≥ 0 and Δy = y₁ − y₀ ≥ 0. If there are no solutions at all, the function will return Nothing.

This function is formulated so that the intervals can be specified exactly (using a type such as QRootTwo), or approximately (using a type such as Double or FixedPrec e).

Approximate synthesis

The main algorithm

newsynth_step :: forall r g. (RealFrac r, Floating r, RootHalfRing r, Floor r, Adjoint r, RandomGen g) => r -> r -> g -> Maybe (U2 DOmega, Maybe Double)Source

The internal implementation of the approximate synthesis algorithm. The parameters are:

  • an angle θ, to implement a Rz(θ) = eiθZ/2 gate;
  • a precision p ≥ 0 in bits, such that ε = 2-p;
  • a source of randomness g.

With some probability, output a unitary operator in the Clifford+T group that approximates Rz(θ) to within ε in the operator norm. This operator can then be converted to a list of gates with to_gates. Also output log0.1 of the actual error, or Nothing if the error is 0.

This implementation does not use seeding.

As a special case, if the Rz(θ) is a Clifford operator (to within the given ε), always return this operator directly.

Note: the parameter θ must be of a real number type that has enough precision to perform intermediate calculations; this typically requires precision O(ε2). A more user-friendly function that does this automatically is newsynth.

User-friendly functions

newsynth :: RandomGen g => Double -> SymReal -> g -> U2 DOmegaSource

A user-friendly interface to the approximate synthesis algorithm. The parameters are:

  • an angle θ, to implement a Rz(θ) = eiθZ/2 gate;
  • a precision b ≥ 0 in bits, such that ε = 2-b;
  • a source of randomness g.

Output a unitary operator in the Clifford+T group that approximates Rz(θ) to within ε in the operator norm. This operator can then be converted to a list of gates with to_gates.

This implementation does not use seeding.

Note: the argument theta is given as a symbolic real number. It will automatically be expanded to as many digits as are necessary for the internal calculation. In this way, the caller can specify, e.g., an angle of pi/128 :: SymReal, without having to worry about how many digits of π to specify.

newsynth_stats :: RandomGen g => Double -> SymReal -> g -> (U2 DOmega, Maybe Double, Integer)Source

A version of newsynth that also returns some statistics: log0.1 of the actual approximation error (or Nothing if the error is 0), and the number of candidates tried.

newsynth_gates :: RandomGen g => Double -> SymReal -> g -> [Gate]Source

A version of newsynth that returns a list of gates instead of a matrix. The inputs are the same as for newsynth.

Note: the list of gates will be returned in right-to-left order, i.e., as in the mathematical notation for matrix multiplication. This is the opposite of the quantum circuit notation.