Safe Haskell | None |
---|
This module contains the Quipper implementation of the Quantum Linear Systems Algorithm.
The algorithm estimates the radar cross section for a FEM scattering problem by using amplitude estimation to calculate probability amplitudes.
The notations are based on the paper
- B. D. Clader, B. C. Jacobs, C. R. Sprouse. Quantum algorithm to calculate electromagnetic scattering cross sections. http://arxiv.org/abs/1301.2340.
Synopsis
- type OracleARunTime = Double -> Int -> Bool -> ([Qubit], [Qubit], [Qubit]) -> Circ ([Qubit], [Qubit], [Qubit])
- type OracleBRRunTime = Double -> Double -> ([Qubit], [Qubit], [Qubit]) -> Circ ([Qubit], [Qubit], [Qubit])
- data Oracle = Oracle {}
- dummy_oracle :: Oracle
- data RunTimeParam = RT_param {
- k :: Double
- theta :: Double
- phi :: Double
- e0 :: Double
- lambda :: Double
- xlength :: Double
- ylength :: Double
- scatteringnodes :: [(Int, Int)]
- nx :: Int
- ny :: Int
- lx :: Double
- ly :: Double
- kappa :: Double
- epsilon :: Double
- t0 :: Double
- r :: Double
- b_max :: Double
- r_max :: Double
- d :: Int
- nb :: Int
- p2 :: Double
- n0 :: Int
- n1 :: Int
- n2 :: Int
- n4 :: Int
- magnitudeArgflag :: Bool
- phaseArgflag :: Bool
- dummy_RT_param :: RunTimeParam
- large_RT_param :: RunTimeParam
- small_RT_param :: RunTimeParam
- expYt :: Timestep -> Qubit -> Circ Qubit
- expYt_at :: Timestep -> Qubit -> Circ ()
- dynamic_lift_double :: Double -> [Bit] -> Circ Double
- qft_for_show :: [Qubit] -> Circ [Qubit]
- qlsa_FEM_main :: RunTimeParam -> Oracle -> Circ Double
- qlsa_AmpEst_phi_b :: RunTimeParam -> Oracle -> Circ Double
- test_qlsa_AmpEst_phi_b :: Bool -> IO ()
- qlsa_AmpEst_phi_bx :: RunTimeParam -> Oracle -> Circ Double
- qlsa_AmpEst_phi_bxr :: RunTimeParam -> Oracle -> Bool -> Circ Double
- qlsa_StatePrep :: RunTimeParam -> ([Qubit], Qubit) -> OracleBRRunTime -> Double -> Circ ()
- test_qlsa_StatePrep :: Bool -> IO ()
- qlsa_Solve_x :: RunTimeParam -> ([Qubit], Qubit) -> Oracle -> Circ ()
- integer_inverse :: ([Qubit], [Qubit]) -> Circ ()
- qlsa_Solve_xr :: RunTimeParam -> ([Qubit], [Qubit], Qubit, Qubit, Qubit, Qubit) -> Oracle -> Circ ()
- qlsa_HamiltonianSimulation :: RunTimeParam -> ([Qubit], [Qubit]) -> OracleARunTime -> Circ ()
- test_qlsa_HamiltonianSimulation :: Bool -> IO ()
- qlsa_HsimKernel :: RunTimeParam -> ([Qubit], [Qubit]) -> Int -> Double -> OracleARunTime -> Circ ()
- test_qlsa_HsimKernel :: Bool -> IO ()
- qlsa_ApplyHmag :: RunTimeParam -> ([Qubit], [Qubit], [Qubit]) -> Double -> Circ ()
- test_qlsa_ApplyHmag :: Bool -> IO ()
- w :: (Qubit, Qubit) -> Circ ()
- test_w :: IO ()
- qlsa_ControlledPhase :: [Qubit] -> Double -> Bool -> Circ ()
- qlsa_ControlledRotation :: ([Qubit], Qubit) -> Double -> Bool -> Circ ()
- make_factor_rep :: Double -> Int -> QDouble -> Circ [Qubit]
- inline_oracle_r :: RunTimeParam -> Double -> Double -> ([Qubit], [Qubit], [Qubit]) -> Circ ([Qubit], [Qubit], [Qubit])
- inline_oracle_b :: RunTimeParam -> Double -> Double -> ([Qubit], [Qubit], [Qubit]) -> Circ ([Qubit], [Qubit], [Qubit])
- inline_oracle_A :: RunTimeParam -> Double -> Int -> Bool -> ([Qubit], [Qubit], [Qubit]) -> Circ ([Qubit], [Qubit], [Qubit])
- inline_oracle :: Oracle
Documentation
type OracleARunTime Source #
= Double | Value resolution. |
-> Int | Band. |
-> Bool | Argflag. |
-> ([Qubit], [Qubit], [Qubit]) | (x=index,y+node,z+value). |
-> Circ ([Qubit], [Qubit], [Qubit]) |
The type of oracle_A
input arguments during runtime.
type OracleBRRunTime Source #
A type to encapsulate all three oracles.
dummy_oracle :: Oracle Source #
A set of oracles using only blackboxes.
data RunTimeParam Source #
A type to hold the runtime parameters.
RT_param | |
|
Instances
Show RunTimeParam # | |
Defined in Quipper.Algorithms.QLS.QLS showsPrec :: Int -> RunTimeParam -> ShowS # show :: RunTimeParam -> String # showList :: [RunTimeParam] -> ShowS # |
dummy_RT_param :: RunTimeParam Source #
A convenient set of runtime parameters for testing.
large_RT_param :: RunTimeParam Source #
A set of larger values, for testing scalability.
small_RT_param :: RunTimeParam Source #
A set of smaller values, for manageable yet meaningful output.
expYt :: Timestep -> Qubit -> Circ Qubit Source #
Apply an e−iYt gate. The timestep t is a parameter.
expYt_at :: Timestep -> Qubit -> Circ () Source #
Apply an e−iYt gate. The timestep t is a parameter.
dynamic_lift_double :: Double -> [Bit] -> Circ Double Source #
Read a list of bits and make it into a Double
, by multiplying
its integer value by the provided factor.
qft_for_show :: [Qubit] -> Circ [Qubit] Source #
A black box gate to stand in as a replacement for QFT.
qlsa_FEM_main :: RunTimeParam -> Oracle -> Circ Double Source #
Main function: for estimating the radar cross section for a FEM scattering problem. The problem can be reduced to the calculation of four angles: φb, φbx, φr1 and φr0.
Amplitude Estimation Functions
qlsa_AmpEst_phi_b :: RunTimeParam -> Oracle -> Circ Double Source #
Estimates φb, related to the probability of success for the preparation of the known state b, using amplitude amplification.
test_qlsa_AmpEst_phi_b :: Bool -> IO () Source #
Testing function for qlsa_AmpEst_phi_b
.
qlsa_AmpEst_phi_bx :: RunTimeParam -> Oracle -> Circ Double Source #
Estimates φbx, related to the probability of success in computing solution value x.
qlsa_AmpEst_phi_bxr :: RunTimeParam -> Oracle -> Bool -> Circ Double Source #
Estimates φr0 and φr1 (depending on the boolean parameter), related to the overlap of the solution with the arbitrary state r.
State Preparation.
qlsa_StatePrep :: RunTimeParam -> ([Qubit], Qubit) -> OracleBRRunTime -> Double -> Circ () Source #
Prepares a quantum state x, as specified by an oracle function, entangled with a single qubit flag q marking the desired state.
test_qlsa_StatePrep :: Bool -> IO () Source #
Testing function for qlsa_StatePrep
.
Linear System Solver Functions
qlsa_Solve_x :: RunTimeParam -> ([Qubit], Qubit) -> Oracle -> Circ () Source #
Implements the QLSA procedure to generate the solution state |x〉.
integer_inverse :: ([Qubit], [Qubit]) -> Circ () Source #
Implementation of the integer division. The two registers are supposed to be of the same size and represent little-headian unsigned integers, i.e., the head of the list holds the least significant bit.
qlsa_Solve_xr :: RunTimeParam -> ([Qubit], [Qubit], Qubit, Qubit, Qubit, Qubit) -> Oracle -> Circ () Source #
Implements the complete QLSA procedure to find the solution state |x〉 and then implements the swap protocol required for estimation of 〈x|r〉.
Hamiltonian Simulation Functions.
qlsa_HamiltonianSimulation :: RunTimeParam -> ([Qubit], [Qubit]) -> OracleARunTime -> Circ () Source #
Uses a quantum register |t〉 to control the implementation of the Suzuki method for simulating a Hamiltonian specified by an oracle function.
test_qlsa_HamiltonianSimulation :: Bool -> IO () Source #
Testing function for qlsa_HamiltonianSimulation
.
qlsa_HsimKernel :: RunTimeParam -> ([Qubit], [Qubit]) -> Int -> Double -> OracleARunTime -> Circ () Source #
Uses an oracle function and timestep control register (t) to apply 1-sparse Hamiltonian to the input state |t, x〉.
test_qlsa_HsimKernel :: Bool -> IO () Source #
Testing function for qlsa_HsimKernel
.
qlsa_ApplyHmag :: RunTimeParam -> ([Qubit], [Qubit], [Qubit]) -> Double -> Circ () Source #
Applies the magnitude component of coupling elements in a 1-sparse Hamiltonian.
test_qlsa_ApplyHmag :: Bool -> IO () Source #
Testing function for qlsa_ApplyHmag
.
Controlled Logic Operations
qlsa_ControlledPhase :: [Qubit] -> Double -> Bool -> Circ () Source #
Applies a phase shift of φ/2 to the signed input register |φ〉.
qlsa_ControlledRotation :: ([Qubit], Qubit) -> Double -> Bool -> Circ () Source #
Applies a rotation of φ/2 to the signed input register |φ〉.
Oracles
make_factor_rep :: Double -> Int -> QDouble -> Circ [Qubit] Source #
Map a QDouble
into an integer, understood as being scaled by
the given factor. Take the factor and the size of the output
register as parameter.
inline_oracle_r :: RunTimeParam -> Double -> Double -> ([Qubit], [Qubit], [Qubit]) -> Circ ([Qubit], [Qubit], [Qubit]) Source #
Implements the oracle for the arbitrary state |r〉, using the
Template Haskell implementation of calcRweights
.
inline_oracle_b :: RunTimeParam -> Double -> Double -> ([Qubit], [Qubit], [Qubit]) -> Circ ([Qubit], [Qubit], [Qubit]) Source #
Implements the oracle for the known state |b〉, using the
Template Haskell implementation of getKnownWeights
.
inline_oracle_A :: RunTimeParam -> Double -> Int -> Bool -> ([Qubit], [Qubit], [Qubit]) -> Circ ([Qubit], [Qubit], [Qubit]) Source #
Implementation of the oracle calculating the matrix A
corresponding to the discretization of the scattering problem,
using the Template Haskell implementation of
getNodeValuesMoreOutputs
.
inline_oracle :: Oracle Source #
Encapsulate the inline oracles in Template Haskell into an object
of type Oracle
.