Safe Haskell | Safe |
---|---|
Language | Haskell98 |
This module provides functions for defining general-purpose transformations on low-level circuits. The uses of this include:
- gate transformations, where a whole circuit is transformed by replacing each kind of gate with another gate or circuit;
- error correcting codes, where a whole circuit is transformed replacing each qubit by some fixed number of qubits, and each gate by a circuit; and
- simulations, where a whole circuit is mapped to a semantic function by specifying a semantic function for each gate.
The interface is designed to allow the programmer to specify new transformers easily. To define a specific transformation, the programmer has to specify only four pieces of information:
- A type a=⟦Qubit⟧, to serve as a semantic domain for qubits.
- A type b=⟦Bit⟧, to serve as a semantic domain for bits.
- A monad m. This is to allow translations to have side effects if desired; one can use the identity monad otherwise.
- For every gate G, a corresponding semantic function ⟦G⟧. The type of this function depends on what kind of gate G is. For example:
If G :: Qubit -> Circ Qubit, then ⟦G⟧ :: a -> m a. If G :: (Qubit, Bit) -> Circ (Bit, Bit), then ⟦G⟧ :: (a, b) -> m (b, b).
The programmer provides this information by defining a function of
type Transformer
m a b. See #Transformers below. Once a
particular transformer has been defined, it can then be applied to
entire circuits. For example, for a circuit with 1 inputs and 2
outputs:
If C :: Qubit -> (Bit, Qubit), then ⟦C⟧ :: a -> m (b, a).
Synopsis
- data B_Endpoint a b
- = Endpoint_Qubit a
- | Endpoint_Bit b
- type Bindings a b = Map Wire (B_Endpoint a b)
- wires_of_bindings :: Bindings a b -> [Wire]
- bindings_empty :: Bindings a b
- bind :: Wire -> B_Endpoint a b -> Bindings a b -> Bindings a b
- bind_qubit_wire :: Wire -> a -> Bindings a b -> Bindings a b
- bind_bit_wire :: Wire -> b -> Bindings a b -> Bindings a b
- unbind :: Bindings a b -> Wire -> B_Endpoint a b
- unbind_qubit_wire :: Bindings a b -> Wire -> a
- unbind_bit_wire :: Bindings a b -> Wire -> b
- bind_delete :: Wire -> Bindings a b -> Bindings a b
- bind_list :: [Wire] -> [B_Endpoint a b] -> Bindings a b -> Bindings a b
- bind_qubit_wire_list :: [Wire] -> [a] -> Bindings a b -> Bindings a b
- bind_bit_wire_list :: [Wire] -> [b] -> Bindings a b -> Bindings a b
- unbind_list :: Bindings a b -> [Wire] -> [B_Endpoint a b]
- unbind_qubit_wire_list :: Bindings a b -> [Wire] -> [a]
- unbind_bit_wire_list :: Bindings a b -> [Wire] -> [b]
- type Ctrls a b = [Signed (B_Endpoint a b)]
- bind_controls :: Controls -> Ctrls a b -> Bindings a b -> Bindings a b
- unbind_controls :: Bindings a b -> Controls -> Ctrls a b
- data T_Gate m a b x
- = T_QGate String Int Int InverseFlag NoControlFlag (([a] -> [a] -> Ctrls a b -> m ([a], [a], Ctrls a b)) -> x)
- | T_QRot String Int Int InverseFlag Timestep NoControlFlag (([a] -> [a] -> Ctrls a b -> m ([a], [a], Ctrls a b)) -> x)
- | T_GPhase Double NoControlFlag (([B_Endpoint a b] -> Ctrls a b -> m (Ctrls a b)) -> x)
- | T_CNot NoControlFlag ((b -> Ctrls a b -> m (b, Ctrls a b)) -> x)
- | T_CGate String NoControlFlag (([b] -> m (b, [b])) -> x)
- | T_CGateInv String NoControlFlag ((b -> [b] -> m [b]) -> x)
- | T_CSwap NoControlFlag ((b -> b -> Ctrls a b -> m (b, b, Ctrls a b)) -> x)
- | T_QPrep NoControlFlag ((b -> m a) -> x)
- | T_QUnprep NoControlFlag ((a -> m b) -> x)
- | T_QInit Bool NoControlFlag (m a -> x)
- | T_CInit Bool NoControlFlag (m b -> x)
- | T_QTerm Bool NoControlFlag ((a -> m ()) -> x)
- | T_CTerm Bool NoControlFlag ((b -> m ()) -> x)
- | T_QMeas ((a -> m b) -> x)
- | T_QDiscard ((a -> m ()) -> x)
- | T_CDiscard ((b -> m ()) -> x)
- | T_DTerm Bool ((b -> m ()) -> x)
- | T_Subroutine BoxId InverseFlag NoControlFlag ControllableFlag [Wire] Arity [Wire] Arity RepeatFlag ((Namespace -> [B_Endpoint a b] -> Ctrls a b -> m ([B_Endpoint a b], Ctrls a b)) -> x)
- | T_Comment String InverseFlag (([(B_Endpoint a b, String)] -> m ()) -> x)
- type Transformer m a b = forall x. T_Gate m a b x -> x
- type BT m a b = Bindings a b -> m (Bindings a b)
- bind_gate :: Monad m => Namespace -> Gate -> T_Gate m a b (BT m a b)
- transform_circuit :: Monad m => Transformer m a b -> Circuit -> Bindings a b -> m (Bindings a b)
- transform_bcircuit_rec :: Monad m => Transformer m a b -> BCircuit -> Bindings a b -> m (Bindings a b)
- transform_bcircuit_id :: Transformer Id a b -> BCircuit -> Bindings a b -> Bindings a b
- data DynamicTransformer m a b = DT {
- transformer :: Transformer m a b
- define_subroutine :: BoxId -> TypedSubroutine -> m ()
- lifting_function :: b -> m Bool
- transform_dbcircuit :: Monad m => DynamicTransformer m a b -> DBCircuit x -> Bindings a b -> m (x, Bindings a b)
An example transformer
The following is a short but complete example of how to write and use a simple transformer. As usual, we start by importing Quipper:
import Quipper
We will write a transformer called sample_transformer
, which maps
every swap gate to a sequence of three controlled-not gates, and
leaves all other gates unchanged. For convenience, Quipper
pre-defines an identity_transformer
, which can be used as
a catch-all clause to take care of all the gates that don't need to
be rewritten.
mytransformer :: Transformer Circ Qubit Bit mytransformer (T_QGate "swap" 2 0 _ ncf f) = f $ \[q0, q1] [] ctrls -> do without_controls_if ncf $ do with_controls ctrls $ do qnot_at q0 `controlled` q1 qnot_at q1 `controlled` q0 qnot_at q0 `controlled` q1 return ([q0, q1], [], ctrls) mytransformer g = identity_transformer g
Note how Quipper syntax has been used to define the replacement
circuit, consisting of three controlled-not gates. Also, since the
original swap gate may have been controlled, we have added the
additional controls with a with_controls
operator.
To try this out, we define some random circuit using swap gates:
mycirc a b c d = do swap_at a b hadamard_at b swap_at b c `controlled` [a, d] hadamard_at c swap_at c d
To apply the transformer to this circuit, we use the generic
operator transform_generic
:
mycirc2 = transform_generic mytransformer mycirc
Finally, we use a main
function to display the original circuit
and then the transformed one:
main = do print_simple Preview mycirc print_simple Preview mycirc2
Bindings
We introduce the notion of a binding as a low-level way to describe functions of varying arities. A binding assigns a value to a wire in a circuit (much like a "valuation" in logic or semantics assigns values to variables).
To iterate through a circuit, one will typically specify initial
bindings for the input wires. This encodes the input of the function
⟦C⟧ mentioned in the introduction. The bindings are updated as
one passes through each gate. When the iteration is finished, the
final bindings assign a value to each output wire of the
circuit. This encodes the output of the function ⟦C⟧. Therefore,
the interpretation of a circuit is representable as a function from
bindings (of input wires) to bindings (of output wires), i.e., it
has the type ⟦C⟧ :: Bindings
a b -> Bindings
a b.
data B_Endpoint a b Source #
An endpoint is either a qubit or a bit. In a transformer,
we have ⟦B_Endpoint Qubit Bit⟧ = ⟦Qubit⟧ + ⟦Bit⟧. The type B_Endpoint
a b is the same as Either
a b, but we use more suggestive
field names.
Instances
type Bindings a b = Map Wire (B_Endpoint a b) Source #
A binding is a map from a set of wires to the disjoint union of a and b.
wires_of_bindings :: Bindings a b -> [Wire] Source #
Return the list of bound wires from a binding.
bindings_empty :: Bindings a b Source #
The empty binding.
bind :: Wire -> B_Endpoint a b -> Bindings a b -> Bindings a b Source #
Bind a wire to a value, and add it to the given bindings.
bind_qubit_wire :: Wire -> a -> Bindings a b -> Bindings a b Source #
Bind a qubit wire to a value, and add it to the given bindings.
bind_bit_wire :: Wire -> b -> Bindings a b -> Bindings a b Source #
Bind a bit wire to a value, and add it to the given bindings.
unbind :: Bindings a b -> Wire -> B_Endpoint a b Source #
Retrieve the value of a wire from the given bindings.
unbind_qubit_wire :: Bindings a b -> Wire -> a Source #
Retrieve the value of a qubit wire from the given bindings. Throws an error if the wire was bound to a classical bit.
unbind_bit_wire :: Bindings a b -> Wire -> b Source #
Retrieve the value of a bit wire from the given bindings. Throws an error if the wire was bound to a qubit.
bind_list :: [Wire] -> [B_Endpoint a b] -> Bindings a b -> Bindings a b Source #
Like bind
, except bind a list of wires to a list of values. The
lists must be of the same length.
bind_qubit_wire_list :: [Wire] -> [a] -> Bindings a b -> Bindings a b Source #
Like bind_qubit_wire
, except bind a list of qubit wires to a list of
values. The lists must be of the same length.
bind_bit_wire_list :: [Wire] -> [b] -> Bindings a b -> Bindings a b Source #
Like bind_bit_wire
, except bind a list of bit wires to a list of
values. The lists must be of the same length.
unbind_list :: Bindings a b -> [Wire] -> [B_Endpoint a b] Source #
Like unbind
, except retrieve a list of values.
unbind_qubit_wire_list :: Bindings a b -> [Wire] -> [a] Source #
Like unbind_qubit_wire
, except retrieve a list of values.
unbind_bit_wire_list :: Bindings a b -> [Wire] -> [b] Source #
Like unbind_bit_wire
, except retrieve a list of values.
type Ctrls a b = [Signed (B_Endpoint a b)] Source #
A list of signed values of type ⟦B_Endpoint⟧. This type is an abbreviation defined for convenience.
bind_controls :: Controls -> Ctrls a b -> Bindings a b -> Bindings a b Source #
Given a list of signed wires (controls), and a list of signed values, make a bindings from the wires to the values. Ignore the signs.
unbind_controls :: Bindings a b -> Controls -> Ctrls a b Source #
Like unbind
, but retrieve binding for all wires in a list of
controls.
Transformers
The types T_Gate
and Transformer
are at the heart of the
circuit transformer functionality. Their purpose is to give a
concise syntax in which to express semantic functions for gates. As
mentioned in the introduction, the programmer needs to specify two
type a and b, a monad m, and a semantic function for each
gate. With the T_Gate' and Transformer
types, the definition
takes the following form:
my_transformer :: Transformer m a b my_transformer (T_Gate1 <parameters> f) = f $ <semantic function for gate 1> my_transformer (T_Gate2 <parameters> f) = f $ <semantic function for gate 2> my_transformer (T_Gate3 <parameters> f) = f $ <semantic function for gate 3> ...
The type T_Gate
is very higher-order, involving a function f
that consumes the semantic function for each gate. The reason for
this higher-orderness is that the semantic functions for different
gates may have different types.
This higher-orderness makes the T_Gate
mechanism hard to read,
but easy to use. Effectively we only have to write lengthy and
messy code once and for all, rather than once for each transformer.
In particular, all the required low-level bindings and unbindings
can be handled by general-purpose code, and do not need to clutter
each transformer.
The type T_Gate
is used to define case distinctions over gates
in the definition of transformers. For each kind of gate X, it
contains a constructor of the form (T_X f)
. Here, X identifies
the gate, and f is a higher-order function to pass the
translation of X to.
type Transformer m a b = forall x. T_Gate m a b x -> x Source #
A circuit transformer is specified by defining a function of type
Transformer
m a b. This involves specifying a monad m,
semantic domains a=⟦Qubit⟧ and b=⟦Bit⟧, and a semantic function
for each gate, like this:
my_transformer :: Transformer m a b my_transformer (T_Gate1 <parameters> f) = f $ <semantic function for gate 1> my_transformer (T_Gate2 <parameters> f) = f $ <semantic function for gate 2> my_transformer (T_Gate3 <parameters> f) = f $ <semantic function for gate 3> ...
type BT m a b = Bindings a b -> m (Bindings a b) Source #
A "binding transformer" is a function from bindings to
bindings. The semantics of any gate or circuit is ultimately a
binding transformer, for some types a, b and some monad m. We
introduce an abbreviation for this type primarily as a convenience
for the definition of bind_gate
, but also because this type can
be completely hidden from user code.
bind_gate :: Monad m => Namespace -> Gate -> T_Gate m a b (BT m a b) Source #
Turn a Gate
into a T_Gate
. This is the function that actually
handles the explicit bindings/unbindings required for the inputs
and outputs of each gate. Effectively it gives a way, for each
gate, of turning a semantic function into a binding transformer.
Additionally, this function is passed a Namespace, so that the
semantic function for T_Subroutine can use it.
Applying transformers to circuits
transform_circuit :: Monad m => Transformer m a b -> Circuit -> Bindings a b -> m (Bindings a b) Source #
Apply a Transformer
⟦-⟧ to a Circuit
C, and output the
semantic function ⟦C⟧ :: bindings -> bindings.
transform_bcircuit_rec :: Monad m => Transformer m a b -> BCircuit -> Bindings a b -> m (Bindings a b) Source #
Like transform_circuit
, but for boxed circuits.
The handling of subroutines will depend on the transformer. For "gate transformation" types of applications, one typically would like to leave the boxed structure intact. For "simulation" types of applications, one would generally recurse through the boxed structure.
The difference is specified in the definition of the transformer within the semantic function of the Subroutine gate, whether to create another boxed gate or open the box.
transform_bcircuit_id :: Transformer Id a b -> BCircuit -> Bindings a b -> Bindings a b Source #
Same as transform_bcircuit_rec
, but specialized to when m is
the identity operation.
data DynamicTransformer m a b Source #
To transform Dynamic Boxed circuits, we require a Transformer to define the behavior on static gates, but we also require functions for what to do when a subroutine is defined, and for when a dynamic_lift operation occurs. This is all wrapped in the DynamicTransformer data type.
DT | |
|
transform_dbcircuit :: Monad m => DynamicTransformer m a b -> DBCircuit x -> Bindings a b -> m (x, Bindings a b) Source #
Like transform_bcircuit_rec
, but for dynamic-boxed circuits.
"Write" operations can be thought of as gates, and so they are passed to
the given transformer. The handling of "Read" operations is taken care of
by the "lifting_function" of the DynamicTransformer. "Subroutine" operations
call the define_subroutine
function of the DynamicTransformer.