| Safe Haskell | None | 
|---|---|
| Language | Haskell98 | 
Quipper.Algorithms.GSE.GSE
Description
This module provides the main circuit for the GSE algorithm. This circuit consists of a state preparation, followed by a large number of Hamiltonian simulation terms for small time steps, followed by an inverse Quantum Fourier Transform and a final measurement.
Synopsis
- exp_pq :: ((Int, Int) -> Double) -> Double -> [Qubit] -> Qubit -> Circ ()
 - exp_pqrs :: ((Int, Int, Int, Int) -> Double) -> Double -> [Qubit] -> Qubit -> Circ ()
 - exp_pqrs_orthodox :: ((Int, Int, Int, Int) -> Double) -> Double -> [Qubit] -> Qubit -> Circ ()
 - unitary_hat_at :: GSEData -> Int -> Double -> Double -> Bool -> Int -> [Qubit] -> Qubit -> Circ ()
 - gse :: Int -> Int -> Int -> GSEData -> Double -> Double -> (Int -> Int) -> Bool -> Circ [Bit]
 
Basic time step
These functions provide one- and two-electron operators for an individual Trotter time step θ. Each operator consists of a large number of individual Hamiltonian terms.
exp_pq :: ((Int, Int) -> Double) -> Double -> [Qubit] -> Qubit -> Circ () Source #
Apply the one-electron operator e-iθH, where H = hpq ap†aq if p = q and H = hpq (ap†aq + aq†ap) otherwise, to every pair of qubits p≥q in a register |ψ〉. The inputs are Hamiltonian data h, the angle θ, the register |ψ〉, and a control qubit.
exp_pqrs :: ((Int, Int, Int, Int) -> Double) -> Double -> [Qubit] -> Qubit -> Circ () Source #
Apply the two-electron operator e-iθH, where H = hpqrs ap†aq†aras if (p,q) = (s,r) and H = ap†aq†aras + as†ar†aqap otherwise, to every quadruple (p, q, r, s) of qubits in a register |ψ〉. To ensure that terms are enumerated exactly once, we only consider indices where (p, q) ≥ (s, r) in the lexicographic order (i.e., p>s or (p=s and q≥r). The inputs are Hamiltonian data h, the angle θ, the register |ψ〉, and a control qubit.
exp_pqrs_orthodox :: ((Int, Int, Int, Int) -> Double) -> Double -> [Qubit] -> Qubit -> Circ () Source #
Like exp_pqrs, but use the "orthodox" circuit template for
 the Coulomb operator.
Iteration
The following function iterates the basic Trotter timestep Nk times, and also normalizes the maximum energy Emax.
Arguments
| :: GSEData | The integral data hpq and hpqrs.  | 
| -> Int | The Trotter iteration count Nk.  | 
| -> Double | The Hamiltonian scaling parameter τ.  | 
| -> Double | The maximum energy Emax.  | 
| -> Bool | Use the "orthodox" Coulomb operator?  | 
| -> Int | The control qubit index k.  | 
| -> [Qubit] | The state |ψ〉.  | 
| -> Qubit | The control qubit bk.  | 
| -> Circ () | 
Apply the operator Ûk ≈ eiEmaxτ2ke-iHτ2k to |ψ〉.
Main circuit
The main circuit for the GSE Algorithm. This consists of the initial state preparation, the Trotterized phase estimation circuit, the Quantum Fourier Transform, and the final measurement.
Arguments
| :: Int | The number of precision qubits b.  | 
| -> Int | The number of basis functions M.  | 
| -> Int | The number of occupied orbitals N.  | 
| -> GSEData | The integral data hpq and hpqrs.  | 
| -> Double | The Hamiltonian scaling parameter τ.  | 
| -> Double | The maximum energy Emax.  | 
| -> (Int -> Int) | The function k ↦ Nk.  | 
| -> Bool | Use the "orthodox" Coulomb operator?  | 
| -> Circ [Bit] | 
The main circuit for the GSE Algorithm.