Safe Haskell | None |
---|---|
Language | Haskell98 |
This module provides functions for the representation and exact synthesis of multi-qubit Clifford+T operators.
The multi-qubit Clifford+T exact synthesis algorithm is described in the paper:
- Brett Giles, Peter Selinger. Exact synthesis of multiqubit Clifford+T circuits. Physical Review A 87, 032332 (7 pages), 2013. Available from http://arxiv.org/abs/1212.0506.
It generalizes the single-qubit exact synthesis algorithm of Kliuchnikov, Maslov, and Mosca.
- class Residue a b | a -> b where
- type Index = Int
- data TwoLevel
- invert_twolevel :: TwoLevel -> TwoLevel
- invert_twolevels :: [TwoLevel] -> [TwoLevel]
- twolevel_matrix :: (Ring a, Nat n) => (a, a) -> (a, a) -> Index -> Index -> Matrix n n a
- onelevel_matrix :: (Ring a, Nat n) => a -> Index -> Matrix n n a
- matrix_of_twolevel :: (OmegaRing a, RootHalfRing a, Nat n) => TwoLevel -> Matrix n n a
- matrix_of_twolevels :: (OmegaRing a, RootHalfRing a, Nat n) => [TwoLevel] -> Matrix n n a
- list_insert :: Index -> a -> [a] -> [a]
- transform_at :: (a -> a) -> Index -> [a] -> [a]
- transform_at2 :: ((a, a) -> (a, a)) -> Index -> Index -> [a] -> [a]
- list_pairs :: [a] -> ([(a, a)], Maybe a)
- log_omega :: ZOmega -> Maybe Int
- omega_power :: OmegaRing a => Int -> a -> a
- reduce_ZOmega :: ZOmega -> ZOmega
- opX_zomega :: (ZOmega, ZOmega) -> (ZOmega, ZOmega)
- opH_zomega :: (ZOmega, ZOmega) -> (ZOmega, ZOmega)
- apply_twolevel_zomega :: TwoLevel -> [ZOmega] -> [ZOmega]
- apply_twolevels_zomega :: [TwoLevel] -> [ZOmega] -> [ZOmega]
- data ResidueType
- residue_type :: Omega Z2 -> ResidueType
- residue_shift :: Omega Z2 -> Int
- residue_type_shift :: Omega Z2 -> (ResidueType, Int)
- residue_offset :: Omega Z2 -> Omega Z2 -> Int
- reducible :: Omega Z2 -> Bool
- row_step :: ((Index, Omega Z2, ZOmega), (Index, Omega Z2, ZOmega)) -> [TwoLevel]
- reduce_column :: Nat n => Matrix n One DOmega -> Index -> [TwoLevel]
- synthesis_nqubit :: Nat n => Matrix n n DOmega -> [TwoLevel]
- data TwoLevelAlt
- twolevels_of_twolevelalts :: [TwoLevelAlt] -> [TwoLevel]
- invert_twolevels_alt :: [TwoLevelAlt] -> [TwoLevel]
- row_step_alt :: ((Index, Omega Z2, ZOmega), (Index, Omega Z2, ZOmega)) -> [TwoLevelAlt]
- reduce_column_alt :: Nat n => Matrix n One DOmega -> Index -> [TwoLevelAlt]
- synthesis_nqubit_alt :: Nat n => Matrix n n DOmega -> [TwoLevelAlt]
Residues
class Residue a b | a -> b where Source #
A type class for things that have residues. In a typical instance, a is a ring whose elements are expressed with coefficients in ℤ, and b is a corresponding ring whose elements are expressed with coefficients in ℤ2.
Residue Integer Z2 Source # | |
Residue () () Source # | |
Residue a b => Residue [a] [b] Source # | |
Residue a b => Residue (Omega a) (Omega b) Source # | |
Residue a b => Residue (Cplx a) (Cplx b) Source # | |
Residue a b => Residue (RootTwo a) (RootTwo b) Source # | |
(Residue a a', Residue b b') => Residue (a, b) (a', b') Source # | |
Residue a b => Residue (Vector n a) (Vector n b) Source # | |
Residue a b => Residue (Matrix m n a) (Matrix m n b) Source # | |
One- and two-level operators
Symbolic representation
Symbolic representation of one- and two-level operators. Note
that the power k in the TL_T
and TL_omega
constructors can be
positive or negative, and should be regarded modulo 8.
Note: when we use a list of TwoLevel
operators to express a
sequence of operators, the operators are meant to be applied
right-to-left, i.e., as in the mathematical notation for matrix
multiplication. This is the opposite of the quantum circuit
notation.
Constructors for two-level matrices
twolevel_matrix :: (Ring a, Nat n) => (a, a) -> (a, a) -> Index -> Index -> Matrix n n a Source #
Construct a two-level matrix with the given entries.
onelevel_matrix :: (Ring a, Nat n) => a -> Index -> Matrix n n a Source #
Construct a one-level matrix with the given entry.
matrix_of_twolevel :: (OmegaRing a, RootHalfRing a, Nat n) => TwoLevel -> Matrix n n a Source #
Convert a symbolic one- or two-level operator into a matrix.
matrix_of_twolevels :: (OmegaRing a, RootHalfRing a, Nat n) => [TwoLevel] -> Matrix n n a Source #
Convert a list of symbolic one- or two-level operators into a matrix. Note that the operators are to be applied right-to-left, exactly as in mathematical notation.
Auxiliary list functions
list_insert :: Index -> a -> [a] -> [a] Source #
Replace the ith element of a list by x.
transform_at :: (a -> a) -> Index -> [a] -> [a] Source #
Apply a unary operator to element i of a list.
transform_at2 :: ((a, a) -> (a, a)) -> Index -> Index -> [a] -> [a] Source #
Apply a binary operator to elements i and j of a list.
list_pairs :: [a] -> ([(a, a)], Maybe a) Source #
Split a list into pairs. Return a list of pairs, and a final element if the length of the list was odd.
Functions on ℤ[ω]
log_omega :: ZOmega -> Maybe Int Source #
Given an element of the form ωm, return m ∈ {0,…,7}, or
Nothing
if not of that form.
omega_power :: OmegaRing a => Int -> a -> a Source #
Multiply a scalar by ωn.
reduce_ZOmega :: ZOmega -> ZOmega Source #
Divide an element of ZOmega
by √2, or throw an error if it is
not divisible.
opX_zomega :: (ZOmega, ZOmega) -> (ZOmega, ZOmega) Source #
Apply the X operator to a 2-dimensional vector over ZOmega
.
Functions on residues
data ResidueType Source #
The residue type of t ∈ ℤ[ω] is the residue of t†t. It is 0000, 0001, or 1010.
residue_type :: Omega Z2 -> ResidueType Source #
Return the residue's ResidueType
.
residue_shift :: Omega Z2 -> Int Source #
Return the residue's shift.
The shift is defined so that:
- 0001, 1110, 0011 have shift 0,
- 0010, 1101, 0110 have shift 1,
- 0100, 1011, 1100 have shift 2, and
- 1000, 0111, 1001 have shift 3.
Residues of type RT_0000
have shift 0.
residue_type_shift :: Omega Z2 -> (ResidueType, Int) Source #
Return the residue's ResidueType
and the shift.
residue_offset :: Omega Z2 -> Omega Z2 -> Int Source #
Given two irreducible residues a and b of the same type, find an index m such that a + ωmb = 0000. If no such index exists, find an index m such that a + ωmb = 1111.
reducible :: Omega Z2 -> Bool Source #
Check whether a residue is reducible. A residue r is called reducible if it is of the form r = √2 ⋅ r', i.e., r ∈ {0000, 0101, 1010, 1111}.
Exact synthesis
row_step :: ((Index, Omega Z2, ZOmega), (Index, Omega Z2, ZOmega)) -> [TwoLevel] Source #
Perform a single row operation as in Lemma 4, applied to rows i and j. The entries at rows i and j are x and y, respectively, with respective residues a and b. A precondition is that x and y are of the same residue type. Returns a list of two-level operations that decreases the denominator exponent.
reduce_column :: Nat n => Matrix n One DOmega -> Index -> [TwoLevel] Source #
Row reduction: Given a unit column vector v, generate a sequence of two-level operators that reduces the ith standard basis vector ei to v. Any rows that are already 0 in both vectors are guaranteed not to be touched.
synthesis_nqubit :: Nat n => Matrix n n DOmega -> [TwoLevel] Source #
Input an exact n×n unitary operator with coefficients in D[ω], and output an equivalent sequence of two-level operators. This is the algorithm from the Giles-Selinger paper. It has superexponential complexity.
Note: the list of TwoLevel
operators 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.
Alternative algorithm
Section 6 of the Giles-Selinger paper mentions an alternate version of the decomposition algorithm. It requires no ancillas, provided that the determinant of the operator permits this.
data TwoLevelAlt Source #
Symbolic representation of one- and two-level operators, with an alternate set of generators.
Note: when we use a list of TwoLevel
operators to express a
sequence of operators, the operators are meant to be applied
right-to-left, i.e., as in the mathematical notation for matrix
multiplication. This is the opposite of the quantum circuit
notation.
twolevels_of_twolevelalts :: [TwoLevelAlt] -> [TwoLevel] Source #
Convert from the alternate generators to the original generators.
invert_twolevels_alt :: [TwoLevelAlt] -> [TwoLevel] Source #
Invert a list of TwoLevelAlt
operators, and convert the output
to a list of TwoLevel
operators.
row_step_alt :: ((Index, Omega Z2, ZOmega), (Index, Omega Z2, ZOmega)) -> [TwoLevelAlt] Source #
Perform a single row operation as in Lemma 4, applied to rows i and j, using the generators of Section 6. The entries at rows i and j are x and y, respectively, with respective residues a and b. A precondition is that x and y are of the same residue type. Returns a list of two-level operations that decreases the denominator exponent.
reduce_column_alt :: Nat n => Matrix n One DOmega -> Index -> [TwoLevelAlt] Source #
Row reduction: Given a unit column vector v, generate a sequence of two-level operators that reduces the ith standard basis vector ei to v. Any rows that are already 0 in both vectors are guaranteed not to be touched, except possibly row i+1 may be multiplied by a scalar.
synthesis_nqubit_alt :: Nat n => Matrix n n DOmega -> [TwoLevelAlt] Source #
Input an exact n×n unitary operator with coefficients in D[ω], and output an equivalent sequence of two-level operators (in the alternative generators, where all but at most one of the generators has determinant 1). This is the algorithm from the Giles-Selinger paper, Section 6. It has superexponential complexity.
Note: the list of TwoLevelAlt
operators 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.