quipper-algorithms-0.9.0.0: A set of algorithms implemented in Quipper.

Safe HaskellNone
LanguageHaskell98

Quipper.Algorithms.QLS.QLS

Contents

Description

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

Synopsis

Documentation

type OracleARunTime Source #

Arguments

 = 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 #

Arguments

 = Double

Magnitude resolution.

-> Double

Phase resolution.

-> ([Qubit], [Qubit], [Qubit])

(x=index,m+magnitude,p+phase).

-> Circ ([Qubit], [Qubit], [Qubit]) 

The type of oracle_b and oracle_r input arguments during runtime.

data Oracle 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.

Constructors

RT_param 

Fields

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 eiYt gate. The timestep t is a parameter.

expYt_at :: Timestep -> Qubit -> Circ () Source #

Apply an eiYt 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.

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.

w :: (Qubit, Qubit) -> Circ () Source #

Auxiliary function: the W-gate.

test_w :: IO () Source #

Testing function for w.

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.