Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides a representation of the single-qubit Clifford+T operators, Matsumoto-Amano normal forms, and functions for the exact synthesis of single-qubit Clifford+T operators.
Matsumoto-Amano normal forms and the Matsumoto-Amano exact synthesis algorithm are described in the paper:
- Ken Matsumoto, Kazuyuki Amano. Representation of Quantum Circuits with Clifford and π/8 Gates. http://arxiv.org/abs/0806.3834.
Synopsis
- data Gate
- class ToGates a where
- class FromGates a where
- from_gates :: [Gate] -> a
- invert_gates :: [Gate] -> [Gate]
- convert :: (ToGates a, FromGates b) => a -> b
- u2_X :: Ring a => U2 a
- u2_Y :: ComplexRing a => U2 a
- u2_Z :: Ring a => U2 a
- u2_H :: RootHalfRing a => U2 a
- u2_S :: ComplexRing a => U2 a
- u2_T :: OmegaRing a => U2 a
- u2_E :: (OmegaRing a, RootHalfRing a) => U2 a
- u2_W :: OmegaRing a => U2 a
- u2_of_gate :: (RootHalfRing a, ComplexRing a, OmegaRing a) => Gate -> U2 a
- so3_X :: Ring a => SO3 a
- so3_Y :: Ring a => SO3 a
- so3_Z :: Ring a => SO3 a
- so3_H :: Ring a => SO3 a
- so3_S :: Ring a => SO3 a
- so3_E :: Ring a => SO3 a
- so3_T :: RootHalfRing a => SO3 a
- so3_of_gate :: RootHalfRing a => Gate -> SO3 a
- so3_of_u2 :: (Adjoint a, ComplexRing a, RealPart a b, HalfRing b) => U2 a -> SO3 b
- so3_of_clifford :: (ToClifford a, Ring b) => a -> SO3 b
- clifford_of_so3 :: (Ring a, Eq a, Adjoint a) => SO3 a -> Clifford
- data NormalForm = NormalForm Syllables Clifford
- data Syllables
- normalform_append :: NormalForm -> Gate -> NormalForm
- nf_id :: NormalForm
- nf_mult :: ToGates b => NormalForm -> b -> NormalForm
- nf_inv :: ToGates a => a -> NormalForm
- normalize :: ToGates a => a -> NormalForm
- synthesis_bloch :: SO3 DRootTwo -> [Gate]
- synthesis_u2 :: U2 DOmega -> [Gate]
- normalform_pack :: NormalForm -> Integer
- normalform_unpack :: Integer -> NormalForm
- clifford_pack :: Clifford -> Integer
- clifford_unpack :: Integer -> Clifford
Clifford+T interchange format
It is convenient to have a simple but exact "interchange format" for operators in the single-qubit Clifford+T group. Different operator representations can be converted to and from this format.
Our format is simply a list of gates from X, Y, Z, H, S, T, and E = HS3ω3, with the obvious interpretation as a matrix product. We also include the global phase gate W = ω = eiπ/4. The W gate is ignored when converting to or from representations that cannot represent global phase (such as the Bloch sphere representation).
An enumeration type to represent symbolic basic gates (X, Y, Z, H, S, T, W, E).
Note: when we use a list of Gate
s 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.
class ToGates a where Source #
A type class for all things that can be exactly converted to a list of gates. These are the exact representations of the single-qubit Clifford+T group.
Instances
ToGates Char Source # | |
ToGates Integer Source # | |
ToGates Axis Source # | |
ToGates Clifford Source # | |
ToGates TwoLevel Source # | |
ToGates Syllables Source # | |
ToGates NormalForm Source # | |
Defined in Quantum.Synthesis.CliffordT to_gates :: NormalForm -> [Gate] Source # | |
ToGates Gate Source # | |
ToGates a => ToGates [a] Source # | |
Defined in Quantum.Synthesis.CliffordT | |
ToQOmega a => ToGates (SO3 a) Source # | |
ToQOmega a => ToGates (U2 a) Source # | |
class FromGates a where Source #
A type class for all things that a list of gates can be converted to. For example, a list of gates can be converted to an element of U(2) or an element of SO(3), using various (exact or approximate) representations of the matrix entries.
from_gates :: [Gate] -> a Source #
Convert a list of gates to any suitable type.
Instances
FromGates Integer Source # | |
Defined in Quantum.Synthesis.CliffordT from_gates :: [Gate] -> Integer Source # | |
FromGates String Source # | |
Defined in Quantum.Synthesis.CliffordT from_gates :: [Gate] -> String Source # | |
FromGates NormalForm Source # | |
Defined in Quantum.Synthesis.CliffordT from_gates :: [Gate] -> NormalForm Source # | |
FromGates [Gate] Source # | |
Defined in Quantum.Synthesis.CliffordT from_gates :: [Gate] -> [Gate] Source # | |
RootHalfRing a => FromGates (SO3 a) Source # | |
Defined in Quantum.Synthesis.CliffordT from_gates :: [Gate] -> SO3 a Source # | |
(RootHalfRing a, ComplexRing a, OmegaRing a) => FromGates (U2 a) Source # | |
Defined in Quantum.Synthesis.CliffordT from_gates :: [Gate] -> U2 a Source # |
invert_gates :: [Gate] -> [Gate] Source #
Invert a gate list.
Matrices in U(2) and SO(3)
Matrices in U(2)
u2_Y :: ComplexRing a => U2 a Source #
The Pauli Y operator.
u2_H :: RootHalfRing a => U2 a Source #
The Hadamard operator.
u2_S :: ComplexRing a => U2 a Source #
The S operator.
u2_of_gate :: (RootHalfRing a, ComplexRing a, OmegaRing a) => Gate -> U2 a Source #
Convert a symbolic gate to the corresponding operator.
Matrices in SO(3)
This is the Bloch sphere representation of single qubit operators.
so3_T :: RootHalfRing a => SO3 a Source #
The T operator.
so3_of_gate :: RootHalfRing a => Gate -> SO3 a Source #
Convert a symbolic gate to the corresponding Bloch sphere operator.
Conversions
so3_of_u2 :: (Adjoint a, ComplexRing a, RealPart a b, HalfRing b) => U2 a -> SO3 b Source #
Conversion from U(2) to SO(3).
so3_of_clifford :: (ToClifford a, Ring b) => a -> SO3 b Source #
Convert a Clifford operator to a matrix in SO(3).
clifford_of_so3 :: (Ring a, Eq a, Adjoint a) => SO3 a -> Clifford Source #
Convert a matrix in SO(3) to a Clifford gate. Throw an error if the matrix isn't Clifford.
Matsumoto-Amano normal forms
A Matsumoto-Amano normal form is a sequence of Clifford+T operators that is of the form
- (ε | T) (HT | SHT)* C.
Here, ε is the empty sequence, C is any Clifford operator, and
the meanings of "|"
and "*"
are as for regular
expressions. Every single-qubit Clifford+T operator has a unique
Matsumoto-Amano normal form.
Representation of normal forms
data NormalForm Source #
A representation of normal forms, optimized for right multiplication.
Instances
Eq NormalForm Source # | |
Defined in Quantum.Synthesis.CliffordT (==) :: NormalForm -> NormalForm -> Bool # (/=) :: NormalForm -> NormalForm -> Bool # | |
Show NormalForm Source # | |
Defined in Quantum.Synthesis.CliffordT showsPrec :: Int -> NormalForm -> ShowS # show :: NormalForm -> String # showList :: [NormalForm] -> ShowS # | |
FromGates NormalForm Source # | |
Defined in Quantum.Synthesis.CliffordT from_gates :: [Gate] -> NormalForm Source # | |
ToGates NormalForm Source # | |
Defined in Quantum.Synthesis.CliffordT to_gates :: NormalForm -> [Gate] Source # |
Syllables is a circuit of the form (ε|T) (HT|SHT)*.
S_I | The empty sequence ε. |
S_T | The sequence T. |
SApp_HT Syllables | A sequence of the form …HT. |
SApp_SHT Syllables | A sequence of the form …SHT. |
normalform_append :: NormalForm -> Gate -> NormalForm Source #
Right-multiply the given normal form by a gate.
Group operations on normal forms
nf_id :: NormalForm Source #
The identity as a normal form.
nf_mult :: ToGates b => NormalForm -> b -> NormalForm Source #
Multiply two normal forms. The right factor can be any
ToGates
.
Conversion to normal form
normalize :: ToGates a => a -> NormalForm Source #
Convert any ToGates
list to a NormalForm
, thereby normalizing it.
Exact synthesis
Synthesis from SO(3)
synthesis_bloch :: SO3 DRootTwo -> [Gate] Source #
Input an exact matrix in SO(3), and output the corresponding Clifford+T normal form. It is an error if the given matrix is not an element of SO(3), i.e., orthogonal with determinant 1.
This implementation uses the Matsumoto-Amano algorithm.
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.
Synthesis from U(2)
synthesis_u2 :: U2 DOmega -> [Gate] Source #
Input an exact matrix in U(2), and output the corresponding Clifford+T normal form. The behavior is undefined if the given matrix is not an element of U(2), i.e., unitary with determinant 1.
We use a variant of the Kliuchnikov-Maslov-Mosca algorithm, as implemented in Quantum.Synthesis.MultiQubitSynthesis.
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.
Compact representation of normal forms
It is sometimes useful to store Clifford+T operators in a file; for this purpose, we provide a very succinct encoding of Clifford+T operators as bit strings, which are in turns represented as integers.
Our bitwise encoding is as follows. The first regular expression represents the set of Matsumoto-Amano normal forms (with a particular presentation of the rightmost Clifford operator). The second regular expression, which has the same form, defines the corresponding bit string encoding.
- (ε|T) (HT|SHT)* (ε|H|SH) (ε|X) (ε|S²) (ε|S) (ε|ω⁴) (ε|ω²) (ε|ω)
- (10|11) (0|1)* (00|01|10) (0|1) (0|1) (0|1) (0|1) (0|1) (0|1)
As a special case, the leading bits 10 are omitted in case the encoded operator is a Clifford operator. This ensures that the encoding of a Clifford operator is an integer from 0 to 191.
This format has the property that the encoded Clifford+T operator can, in principle, be read off directly from the hexadecimal representation of the bit string, with the following decoding:
Leftmost one or two hexadecimal digits:
0 = n/a 4 = HT 8 = HTHT c = THTHT 1 = see below 5 = SHT 9 = HTSHT d = THTSHT 2 = ε 6 = THT a = SHTHT e = TSHTHT 3 = T 7 = TSHT b = SHTSHT f = TSHTSHT 10 = HTHTHT 14 = SHTHTHT 18 = THTHTHT 1c = TSHTHTHT 11 = HTHTSHT 15 = SHTHTSHT 19 = THTHTSHT 1d = TSHTHTSHT 12 = HTSHTHT 16 = SHTSHTHT 1a = THTSHTHT 1e = TSHTSHTHT 13 = HTSHTSHT 17 = SHTSHTSHT 1b = THTSHTSHT 1f = TSHTSHTSHT
Central hexadecimal digit:
0 = HTHTHTHT 4 = HTSHTHTHT 8 = SHTHTHTHT c = SHTSHTHTHT 1 = HTHTHTSHT 5 = HTSHTHTSHT 9 = SHTHTHTSHT d = SHTSHTHTSHT 2 = HTHTSHTHT 6 = HTSHTSHTHT a = SHTHTSHTHT e = SHTSHTSHTHT 3 = HTHTSHTSHT 7 = HTSHTSHTSHT b = SHTHTSHTSHT f = SHTSHTSHTSHT
Second-to-rightmost hexadecimal digit:
0 = ε 4 = H 8 = SH c = n/a 1 = SS 5 = HSS 9 = SHSS d = n/a 2 = X 6 = HX a = SHX e = n/a 3 = XSS 7 = HXSS b = SHXSS f = n/a
Rightmost hexadecimal digit:
0 = ε 4 = ω⁴ 8 = S c = Sω⁴ 1 = ω 5 = ω⁵ 9 = Sω d = Sω⁵ 2 = ω² 6 = ω⁶ a = Sω² e = Sω⁶ 3 = ω³ 7 = ω⁷ b = Sω³ f = Sω⁷
For example, the hexadecimal integer
6bf723e31
encodes the Clifford+T operator
THT SHTHTSHTSHT SHTSHTSHTSHT HTSHTSHTSHT HTHTSHTHT HTHTSHTSHT SHTSHTSHTHT XSS ω.
normalform_pack :: NormalForm -> Integer Source #
Compactly encode a NormalForm
as an Integer
.
normalform_unpack :: Integer -> NormalForm Source #
Decode a NormalForm
from its Integer
encoding. This is the
inverse of normalform_pack
.
clifford_pack :: Clifford -> Integer Source #
Encode a Clifford operator as an integer in the range 0−191.
clifford_unpack :: Integer -> Clifford Source #
Decode a Clifford operator from its integer encoding. This is the
inverse of clifford_pack