Safe Haskell | None |
---|
This module provides an implementation of the main binary welded tree algorithm and oracle, using a more-or-less imperative programming style. We abstract the oracle into a data type, so that different oracles can be plugged into the main algorithm.
Synopsis
- data Oracle = Oracle {}
- qrwbwt :: Oracle -> Int -> Timestep -> Circ [Bit]
- timestep :: (Qureg, Qureg, Qubit, Timestep, Int) -> Circ ()
- oracle :: (Qureg, Qureg, Qubit, Boolreg, Boolreg, Boolreg, Int) -> Circ ()
- parseNodeRoot :: (Qureg, Qubit, Qubit, Int) -> Circ ()
- parseNodeEven :: (Qureg, Qubit, Int) -> Circ ()
- testIsParent :: (Qureg, Qubit, Qubit, Qubit, Boolreg, Int, Int, Qubit) -> Circ ()
- testIsChild :: (Qubit, Qubit, Qubit, Boolreg, Int) -> Circ ()
- setParent :: (Qureg, Qureg, Qubit, Int) -> Circ ()
- setChild :: (Qureg, Qureg, Qubit, Qubit, Boolreg, Boolreg, Int) -> Circ ()
- setChildInTree :: (Qureg, Qureg, Qubit, Qubit, Int) -> Circ ()
- setWeld :: (Qureg, Qureg, Qubit, Qubit, Boolreg, Boolreg, Int) -> Circ ()
- doWeld1 :: (Qureg, Qureg, Qubit, Boolreg, Int) -> Circ ()
- doWeld0 :: (Qureg, Qureg, Qubit, Boolreg, Int) -> Circ ()
- cAddNum :: (Qubit, Qureg, Qureg, Boolreg, Int) -> Circ ()
- cAddNumClear :: (Qubit, Qureg, Qureg, Boolreg, Int) -> Circ ()
- cSubNum :: (Qubit, Qureg, Qureg, Boolreg, Int) -> Circ ()
- cSubNumClear :: (Qubit, Qureg, Qureg, Boolreg, Int) -> Circ ()
- oracle_orthodox :: Boollist -> Boollist -> Oracle
- main_circuit :: Format -> GateBase -> Oracle -> Int -> Timestep -> IO ()
- main_oracle :: Format -> GateBase -> Oracle -> Int -> IO ()
Oracle abstraction
A data structure to hold an oracle. The binary welded tree algorithm is parametric on an oracle. An oracle encodes a graph, and provides the following information: the tree depth n (in the above example: 3), the label length m (in bits; 5 in the above example), the number of edge colors k, the entrance label ENTRANCE, and for each color 0 ≤ c < k, a reversible circuit ORACLEc(a,b,r). On basis vectors, this circuit encodes the edge information in the following sense:
ORACLEc(a, b, r) = (a, b ⊕ vc(a), r ⊕ fc(a)),
where fc(a) is 1 if the node a is connected to an edge of color c, and 0 otherwise; and vc(a) is the node label connected to node a along an edge of color c (if any), and arbitrary otherwise.
Not all available node labels need to be used (for example, 0 and 16 are unused in the graph in the above illustration).
Top-level algorithm
qrwbwt :: Oracle -> Int -> Timestep -> Circ [Bit] Source #
The main loop of the binary welded tree algorithm.
qrwbwt oracle s dt
: Do a quantum random walk on the binary welded
tree given by the oracle oracle, for s times steps of length
dt. Returns a bit list corresponding to the computed exit node
label.
timestep :: (Qureg, Qureg, Qubit, Timestep, Int) -> Circ () Source #
timestep (a, b, r, dt, m)
: Perform a single time step dt of
the quantum walk. This is done by iterating through each of the
available edge colors, and performing a diffusion step for each
color. Here, a is an m-qubit registers holding (a superposition
of) the current node label. b is an m-qubit ancilla register,
and r is an ancilla qubit. Both b and r are expected to be
initialized to |0〉 by the caller, and will be returned in state
|0〉.
Oracle implementation
The functions in this section implement a particular oracle for a binary welded tree. The oracle is parametric on:
- the tree depth n;
- two "welding vectors" f and g, specifying how the leaves of the two binary trees are connected to each other. Specifically, f and g encode the permutations of leaves given by a ↦ a ⊕ f and a ↦ a + g, respectively, where "⊕" denotes bitwise exclusive or, and "+" denotes binary addition.
Oracle subroutines
oracle :: (Qureg, Qureg, Qubit, Boolreg, Boolreg, Boolreg, Int) -> Circ () Source #
The top-level oracle circuit. The arguments are of the form (a, b, r, color, f, g, n), where a, b are quantum registers of length n+2, color is a boolean register of length 2, and f and g are boolean registers of length n.
parseNodeRoot :: (Qureg, Qubit, Qubit, Int) -> Circ () Source #
Input a node label a of length at least n+1. Negate both root and even if a is a root node.
parseNodeEven :: (Qureg, Qubit, Int) -> Circ () Source #
Input a node label a of length at least n+1. Negate even if the node a occurs at an even height in the tree.
testIsParent :: (Qureg, Qubit, Qubit, Qubit, Boolreg, Int, Int, Qubit) -> Circ () Source #
Input a node label a of length at least 1, and flags root and even describing whether a is a root and at an even level, respectively. Negate isparent if a has a parent of color color in the tree.
The qubit ismatch is an ancilla, and really is either 0 or
1. They are jointly used to control uncomputation, so that the
following sequence will compute and then uncompute testIsParent
:
ismatch <- qinit 0 testIsParent (a, root, even, isparent, color, n, 1, ismatch) testIsParent (a, root, even, isparent, color, n, 0, ismatch) qterm 0 ismatch
testIsChild :: (Qubit, Qubit, Qubit, Boolreg, Int) -> Circ () Source #
Consider a node a, and negate ischild if a has a child node of color color. Also set direction to indicate whether it is a "left" or "right" child. Here, color is a boolean register of length 2, representing a color. This function is self-inverse.
setParent :: (Qureg, Qureg, Qubit, Int) -> Circ () Source #
Input a node label a of length at least n+2, and a flag isparent that has been initialized accordingly. Also input a register b of length at least n+2, initialized to |0〉. If isparent is set, set b to the node label of the parent of a. This is self-inverse.
setChild :: (Qureg, Qureg, Qubit, Qubit, Boolreg, Boolreg, Int) -> Circ () Source #
Similar to setParent
, but set b to the node label of the
indicated child of a. Here a and b are quantum registers of
length at least n+2, and f and g are boolean registers of
length n.
setChildInTree :: (Qureg, Qureg, Qubit, Qubit, Int) -> Circ () Source #
A special case of setChild
, where the child is inside the same
binary tree (i.e., not via the welding).
setWeld :: (Qureg, Qureg, Qubit, Qubit, Boolreg, Boolreg, Int) -> Circ () Source #
A special case of setChild
, where the child is in the opposite
binary tree, i.e., we follow one of the welding edges.
doWeld1 :: (Qureg, Qureg, Qubit, Boolreg, Int) -> Circ () Source #
Input a node label a, and a register b initialized to |0〉. If weldctrl is set, set b to the node connected to a by the welding function f. This is self-inverse. Here, a and b are quantum registers of length at least n+2, and f is a boolean register of length n.
doWeld0 :: (Qureg, Qureg, Qubit, Boolreg, Int) -> Circ () Source #
Input a node label a, and a register b initialized to |0〉. If weldctrl is set, set b to the node connected to a by the welding function g. This is self-inverse. Here, a and b are quantum registers of length at least n+2, and g is a boolean register of length n.
cAddNum :: (Qubit, Qureg, Qureg, Boolreg, Int) -> Circ () Source #
This function implements integer addition. Input a quantum register input and a boolean register num, representing integers, and a quantum register out initialized to |0〉. If control is set, set out to input + num, otherwise do nothing. Here input and out are quantum registers of length at least n, num is a boolean register of length n.
cAddNumClear :: (Qubit, Qureg, Qureg, Boolreg, Int) -> Circ () Source #
A helper function for clearing the scratch space used by cAddNum
.
cSubNum :: (Qubit, Qureg, Qureg, Boolreg, Int) -> Circ () Source #
Like cAddNum
, except subtract instead of adding.
cSubNumClear :: (Qubit, Qureg, Qureg, Boolreg, Int) -> Circ () Source #
A helper function for clearing the scratch space used by cSubNum
.
The oracle data structure
oracle_orthodox :: Boollist -> Boollist -> Oracle Source #
This function inputs two welding functions f and g, and returns the oracle defined by the preceding functions.
We call this the "orthodox" oracle, because the implementation follows its specification very closely. For example, it uses a very "imperative" programming style. For alternative implementations of this and other oracles, see the modules Quipper.Algorithms.BWT.Alternative and Quipper.Algorithms.BWT.Template.