Safe Haskell | None |
---|
This library provides functions for simulating certain classes of circuits, for testing and debugging purposes.
We can efficiently simulate classical (boolean) circuits and Clifford (stabilizer) circuits. We also provide functions for simulating arbitrary quantum circuits; however, the latter is (necessarily) very inefficient.
Synopsis
- run_classical_generic :: (QCData qa, QCData qb, QCurry qfun qa qb, Curry fun (BType qa) (BType qb)) => qfun -> fun
- run_clifford_generic :: (QCData qa, QCDataPlus qb, QCurry qfun qa qb, Curry qfun' (BType qa) (IO (BType qb))) => qfun -> qfun'
- run_generic :: (Floating r, Random r, Ord r, RandomGen g, QCData qa, QCDataPlus qb, QCurry qfun qa qb, Curry qfun' (QCType Bool Bool qa) (QCType Qubit Bool (QCType Bit Bit qb))) => g -> r -> qfun -> qfun'
- run_generic_io :: (Floating r, Random r, Ord r, QCData qa, QCDataPlus qb, QCurry qfun qa qb, Curry qfun' (QCType Bool Bool qa) (IO (QCType Qubit Bool (QCType Bit Bit qb)))) => r -> qfun -> qfun'
- sim_amps :: (RandomGen g, Floating r, Random r, Ord r, QData qa, QData qb, qb ~ QCType Qubit Bool qb, Ord (BType qb)) => g -> (qa -> Circ qb) -> Map (BType qa) (Cplx r) -> Map (BType qb) (Cplx r)
- type QuantumTrace r = ProbabilityDistribution r [Bool]
- run_generic_trace :: (Floating r, Random r, Ord r, RandomGen g, QCData qa, QCDataPlus qb, QCurry qfun qa qb, Curry qfun' (QCType Bool Bool qa) [QuantumTrace r]) => g -> r -> qfun -> qfun'
- run_generic_trace_io :: (Floating r, Random r, Ord r, QCData qa, QCDataPlus qb, QCurry qfun qa qb, Curry qfun' (QCType Bool Bool qa) (IO [QuantumTrace r])) => r -> qfun -> qfun'
- data Vector n a = Vector [(a, n)]
- type ProbabilityDistribution r a = Vector r a
- sim_generic :: (Floating r, Ord r, QCData qa, QCDataPlus qb, QCurry qfun qa qb, Curry qfun' (QCType Bool Bool qa) (ProbabilityDistribution r (QCType Qubit Bool (QCType Bit Bit qb)))) => r -> qfun -> qfun'
Classical simulation
run_classical_generic :: (QCData qa, QCData qb, QCurry qfun qa qb, Curry fun (BType qa) (BType qb)) => qfun -> fun Source #
Boolean simulation of a circuit, for testing and debugging purposes. Input a classical circuit, and output the corresponding boolean function. This will fail with an error if the circuit contains a gate not acting within the computational basis, or if some assertion is not met.
Unlike run_classical_unary
, this can be applied to a
circuit-generating function in curried form with n arguments, for
any n ≥ 0. The resulting boolean function then will also have n arguments.
The type of this heavily overloaded function is difficult to read. In more readable form, it has all of the following types:
run_classical_generic :: (QCData qa) => Circ qa -> BType qa run_classical_generic :: (QCData qa, QCData qb) => (qa -> Circ qb) -> BType qa -> BType qb run_classical_generic :: (QCData qa, QCData qb, QCData qc) => (qa -> qb -> Circ qc) -> BType qa -> BType qb -> BType qc
and so forth.
Stabilizer simulation
run_clifford_generic :: (QCData qa, QCDataPlus qb, QCurry qfun qa qb, Curry qfun' (BType qa) (IO (BType qb))) => qfun -> qfun' Source #
Efficiently simulate a Quipper circuit that consists entirely of Clifford group operators, using the stabilizer formalism.
Inputs a quantum circuit, and outputs a corresponding probabilistic
boolean function. The inputs to the quantum circuit are initialized
according to the given boolean arguments. The outputs of the
quantum circuit are measured, and the boolean measurement outcomes
are returned. Because the measurement outcomes are probabilistic,
this function takes place in the IO
monad.
The type of this heavily overloaded function is difficult to read. In more readable form, it has all of the following types (for example):
run_clifford_generic :: (QCData qa) => Circ qa -> IO (BType qa) run_clifford_generic :: (QCData qa, QCData qb) => (qa -> Circ qb) -> BType qa -> IO (BType qb) run_clifford_generic :: (QCData qa, QCData qb, QCData qc) => (qa -> qb -> Circ qc) -> BType qa -> BType qb -> IO (BType qc)
and so forth.
Quantum simulation
run_generic :: (Floating r, Random r, Ord r, RandomGen g, QCData qa, QCDataPlus qb, QCurry qfun qa qb, Curry qfun' (QCType Bool Bool qa) (QCType Qubit Bool (QCType Bit Bit qb))) => g -> r -> qfun -> qfun' Source #
Quantum simulation of a circuit, for testing and debugging purposes. Input a source of randomness, a real number, and a quantum circuit. Output a corresponding probabilistic boolean function.
The inputs to the quantum circuit are initialized according to the given boolean arguments. The outputs of the quantum circuit are measured, and the boolean measurement outcomes are returned.
The real number argument is a dummy and is never evaluated; its only purpose is to specify the type of real numbers that will be used during the simulation.
The type of this heavily overloaded function is difficult to read. In more readable form, it has all of the following types (for example):
run_generic :: (Floating r, Random r, Ord r, RandomGen g, QCData qa) => g -> r -> Circ qa -> BType qa run_generic :: (Floating r, Random r, Ord r, RandomGen g, QCData qa, QCData qb) => g -> r -> (qa -> Circ qb) -> BType qa -> BType qb run_generic :: (Floating r, Random r, Ord r, RandomGen g, QCData qa, QCData qb, QCData qc) => g -> r -> (qa -> qb -> Circ qc) -> BType qa -> BType qb -> BType qc
and so forth.
run_generic_io :: (Floating r, Random r, Ord r, QCData qa, QCDataPlus qb, QCurry qfun qa qb, Curry qfun' (QCType Bool Bool qa) (IO (QCType Qubit Bool (QCType Bit Bit qb)))) => r -> qfun -> qfun' Source #
Like run_generic
, but run in the IO
monad instead of passing
an explicit source of randomness.
sim_amps :: (RandomGen g, Floating r, Random r, Ord r, QData qa, QData qb, qb ~ QCType Qubit Bool qb, Ord (BType qb)) => g -> (qa -> Circ qb) -> Map (BType qa) (Cplx r) -> Map (BType qb) (Cplx r) Source #
Input a source of randomness, a quantum circuit, and an initial state (represented as a map from basis vectors to amplitudes). Simulate the circuit and return the final state. If the circuit includes measurements, the simulation will be probabilistic.
The type of this heavily overloaded function is difficult to read. It has, for example, the following types:
sim_amps :: StdGen -> (Qubit -> Circ Qubit) -> Map Bool (Cplx Double) -> Map Bool (Cplx Double) sim_amps :: StdGen -> ((Qubit,Qubit) -> Circ Qubit) -> Map (Bool,Bool) (Cplx Double) -> Map Bool (Cplx Double)
and so forth. Note that instead of Double
, another real number
type, such as FixedPrec
e, can be used.
Special purpose functions
Simulation with trace
type QuantumTrace r = ProbabilityDistribution r [Bool] Source #
A QuantumTrace is essentially a probability distribution for the current state of the qubits that have been traced. We can represent this using a Vector. The list of Booleans is in the same order as the list of Qubits that was being traced.
run_generic_trace :: (Floating r, Random r, Ord r, RandomGen g, QCData qa, QCDataPlus qb, QCurry qfun qa qb, Curry qfun' (QCType Bool Bool qa) [QuantumTrace r]) => g -> r -> qfun -> qfun' Source #
Like run_generic
, but also output a trace of the states of the
given list of qubits at each step during the evaluation.
run_generic_trace_io :: (Floating r, Random r, Ord r, QCData qa, QCDataPlus qb, QCurry qfun qa qb, Curry qfun' (QCType Bool Bool qa) (IO [QuantumTrace r])) => r -> qfun -> qfun' Source #
Like run_generic_trace
, but run in the IO
monad instead of
passing an explicit source of randomness.
Probability distributions
The type of vectors with scalars in n over the basis a. A vector is simply a list of pairs.
Vector [(a, n)] |
Instances
(Floating r, Eq r) => PMonad r (Vector r) # |
|
Num n => Monad (Vector n) # | Any numeric indexed vector forms a |
Num n => Functor (Vector n) # | |
Num n => Applicative (Vector n) # | |
(Show a, Eq a, Num n, Eq n, Show n) => Show (Vector n a) # | We can show certain vectors, ignoring any 0 probabilities, and combining equal terms. |
type ProbabilityDistribution r a = Vector r a Source #
A probability distribution gives each element a probability.
sim_generic :: (Floating r, Ord r, QCData qa, QCDataPlus qb, QCurry qfun qa qb, Curry qfun' (QCType Bool Bool qa) (ProbabilityDistribution r (QCType Qubit Bool (QCType Bit Bit qb)))) => r -> qfun -> qfun' Source #
A generic function to simulate Quipper circuits, returning a probability distribution of the possible results.
The type of this heavily overloaded function is difficult to read. In more readable form, it has all of the following types (for example):
sim_generic :: (Floating r, Ord r, QCData qa) => r -> Circ qa -> ProbabilityDistribution r (BType qa) sim_generic :: (Floating r, Ord r, QCData qa, QCData qb) => r -> (qa -> Circ qb) -> BType qa -> ProbabilityDistribution r (BType qb) sim_generic :: (Floating r, Ord r, QCData qa, QCData qb, QCData qc) => r -> (qa -> qb -> Circ qc) -> BType qa -> BType qb -> ProbabilityDistribution r (BType qc)
and so forth.