haquil-0.2.1.5: A Haskell implementation of the Quil instruction set for quantum computing.

Safe HaskellNone
LanguageHaskell2010

Data.Qubit

Contents

Description

Qubits and operations on them, using the indexing conventions of <https://arxiv.org/abs/1711.02086/>.

Synopsis

Types

type QIndex = Int Source #

Index for qubits in a wavefunction.

type Amplitude = Complex Double Source #

Amplitude of a state in a wavefunction.

data Wavefunction Source #

A wavefunction for qubits.

Instances

Eq Wavefunction Source # 
Floating Wavefunction Source # 
Fractional Wavefunction Source # 
Num Wavefunction Source # 
Show Wavefunction Source # 

Construction

qubit Source #

Arguments

:: QIndex

The index of the qubit in the wavefunction.

-> (Amplitude, Amplitude)

The amplitude of the 0 and 1 states, respectively.

-> Wavefunction

The wavefunction for the qubit.

Construct a qubit from the amplitudes of its states.

The squares of the norms of the amplitudes must sum to one.

pureQubit Source #

Arguments

:: QIndex

Which qubit.

-> QState

The state of the qubit.

-> Wavefunction

The wavefunction.

Construct a qubit with a pure state.

qubits Source #

Arguments

:: [Amplitude]

The amplitudes.

-> Wavefunction

The wavefunction.

Construct a wavefunction for the amplitudes of its qubit states.

Amplitudes ordered so that the 0 state appears before the 1 state and the lower qubit indices cycle faster than then higher qubit indices. For example, a two-qubit state has its amplitudes ordered |00>, |01>, |10>, |11>. This ordering can be generated as follows, where qubits are orderd from higher indices to lower ones:

>>> sequence $ replicate 3 [minBound..maxBound] :: [[QState]]
[[0,0,0],[0,0,1],[0,1,0],[0,1,1],[1,0,0],[1,0,1],[1,1,0],[1,1,1]]

The squares of the norms of the amplitudes must sum to one.

groundState Source #

Arguments

:: Int

Number of qubits.

-> Wavefunction

The ground state wavefunction.

Construct the ground state where each qubit is in state 0.

pureState Source #

Arguments

:: [QState]

The state of each qubit, ordered from higher index to lower index.

-> Wavefunction

The wavefunction.

Constructa a pure state.

qubitsOperator Source #

Arguments

:: [QIndex]

The qubit indices for which the operator applies, in descending order according to <https://arxiv.org/pdf/1711.02086/>.

-> [Amplitude]

The amplitudes of the operator matrix, in row-major order with the states ordered from higher indices to lower ones.

-> Operator

The wavefunction operator.

Construct an operator on qubit wavefunctions.

Amplitudes in row-major order where amplitudes are ordered so that the 0 state appears before the 1 state and the lower qubit indices cycle faster than then higher qubit indices. For example, a three-qubit operator has its amplitudes ordered <00|00>, <00|01>, <00|10>, <00|11>, <01|00>, <01|01>, <01|10>, <01|11>, <10|00>, <10|01>, <10|10>, <10|11>, <11|00>, <11|01>, <11|10>, <11|11>, where states in the bras and kets are correspond to the order of the first argument to qubitsOperator. This ordering can be generated as follows:

>>> fmap (splitAt 2) . sequence $ replicate (2 * 2) [minBound..maxBound] :: [([QState], [QState])]
[([0,0],[0,0]),([0,0],[0,1]),([0,0],[1,0]),([0,0],[1,1]),([0,1],[0,0]),([0,1],[0,1]),([0,1],[1,0]),([0,1],[1,1]),([1,0],[0,0]),([1,0],[0,1]),([1,0],[1,0]),([1,0],[1,1]),([1,1],[0,0]),([1,1],[0,1]),([1,1],[1,0]),([1,1],[1,1])]

The operator must be unitary.

Properties

wavefunctionOrder :: Wavefunction -> Int Source #

Number of qubits in a wavefunction.

wavefunctionIndices Source #

Arguments

:: Wavefunction

The wavefunction.

-> [QIndex]

List of qubit indices.

Qubit indices in a wavefunction.

wavefunctionAmplitudes Source #

Arguments

:: Wavefunction

The wavefunction.

-> [([QState], Amplitude)]

List of qubit states and their amplitudes, where indices of states are ordered according to wavefunctionIndices.

Amplitudes of states in a qubit wavefunction.

rawWavefunction :: Wavefunction -> Tensor Amplitude Source #

The Tensor encoding the wavefunction.

operatorOrder :: Operator -> Int Source #

Number of qubits for an operator.

operatorIndices Source #

Arguments

:: Operator

The operator.

-> [QIndex]

List of qubit indices.

Qubit indices in an operator.

operatorAmplitudes Source #

Arguments

:: Operator

The wavefunction.

-> [(([QState], [QState]), Amplitude)]

List of qubit state transitions and their amplitudes, in row-major order with the states ordered according to operatorIndices.

Amplitudes of state transitions in a qubit operator.

rawOperator :: Operator -> Tensor Amplitude Source #

The Tensor encoding the operator.

Operations

(^*^) :: Operator -> Operator -> Operator infixr 7 Source #

Apply two operators in sequence.

(^*) :: Operator -> Wavefunction -> Wavefunction infixr 6 Source #

Apply an operator to a wavefunction.

(*^) :: Wavefunction -> Operator -> Wavefunction infixl 6 Source #

Apply an operator to a wavefunction.

(^^*) :: Foldable t => t Operator -> Wavefunction -> Wavefunction infixr 6 Source #

Apply a sequence of operators to a wavefunction.

(*^^) :: Foldable t => Wavefunction -> t Operator -> Wavefunction infixl 6 Source #

Apply a sequence of operators to a wavefunction.

probabilities Source #

Arguments

:: [QIndex]

Which qubits.

-> Wavefunction

The wavefunciton.

-> [([(QIndex, QState)], Double)]

The probabilities for the combinations of qubit states.

Probabilities of a selection of qubits.

project Source #

Arguments

:: [(QIndex, QState)]

The qubits for the state.

-> Wavefunction

The wavefunction.

-> Wavefunction

The projected wavefunction.

Project a wavefunction onto a particular state.

measure Source #

Arguments

:: RandomGen g 
=> [QIndex]

Which qubits to measure.

-> Wavefunction

The wavefunction.

-> Rand g ([(QIndex, QState)], Wavefunction)

Action for the resulting measurement and wavefunction.

Measure qubits in a wavefunction.

wavefunctionProbability :: Wavefunction -> Amplitude Source #

The total probability for the wave function, which should be 1.