Safe Haskell | None |
---|---|
Language | Haskell2010 |
Qubits and operations on them, using the indexing conventions of <https://arxiv.org/abs/1711.02086/>.
- type QIndex = Int
- data QState
- type Amplitude = Complex Double
- data Wavefunction
- data Operator
- qubit :: QIndex -> (Amplitude, Amplitude) -> Wavefunction
- pureQubit :: QIndex -> QState -> Wavefunction
- qubits :: [Amplitude] -> Wavefunction
- groundState :: Int -> Wavefunction
- pureState :: [QState] -> Wavefunction
- qubitsOperator :: [QIndex] -> [Amplitude] -> Operator
- wavefunctionOrder :: Wavefunction -> Int
- wavefunctionIndices :: Wavefunction -> [QIndex]
- wavefunctionAmplitudes :: Wavefunction -> [([QState], Amplitude)]
- rawWavefunction :: Wavefunction -> Tensor Amplitude
- operatorOrder :: Operator -> Int
- operatorIndices :: Operator -> [QIndex]
- operatorAmplitudes :: Operator -> [(([QState], [QState]), Amplitude)]
- rawOperator :: Operator -> Tensor Amplitude
- (^*^) :: Operator -> Operator -> Operator
- (^*) :: Operator -> Wavefunction -> Wavefunction
- (*^) :: Wavefunction -> Operator -> Wavefunction
- (^^*) :: Foldable t => t Operator -> Wavefunction -> Wavefunction
- (*^^) :: Foldable t => Wavefunction -> t Operator -> Wavefunction
- probabilities :: [QIndex] -> Wavefunction -> [([(QIndex, QState)], Double)]
- project :: [(QIndex, QState)] -> Wavefunction -> Wavefunction
- measure :: RandomGen g => [QIndex] -> Wavefunction -> Rand g ([(QIndex, QState)], Wavefunction)
- wavefunctionProbability :: Wavefunction -> Amplitude
Types
States of a quibit.
data Wavefunction Source #
A wavefunction for qubits.
An operator on wavefunctions.
Construction
:: 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.
:: QIndex | Which qubit. |
-> QState | The state of the qubit. |
-> Wavefunction | The wavefunction. |
Construct a qubit with a pure state.
:: [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.
:: Int | Number of qubits. |
-> Wavefunction | The ground state wavefunction. |
Construct the ground state where each qubit is in state 0.
:: [QState] | The state of each qubit, ordered from higher index to lower index. |
-> Wavefunction | The wavefunction. |
Constructa a pure state.
:: [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.
:: Wavefunction | The wavefunction. |
-> [QIndex] | List of qubit indices. |
Qubit indices in a wavefunction.
wavefunctionAmplitudes Source #
:: Wavefunction | The wavefunction. |
-> [([QState], Amplitude)] | List of qubit states and their amplitudes, where indices of states are ordered according to |
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.
Qubit indices in an operator.
:: Operator | The wavefunction. |
-> [(([QState], [QState]), Amplitude)] | List of qubit state transitions and their amplitudes, in row-major order with the states ordered according to |
Amplitudes of state transitions in a qubit operator.
Operations
(^*) :: 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.
:: [QIndex] | Which qubits. |
-> Wavefunction | The wavefunciton. |
-> [([(QIndex, QState)], Double)] | The probabilities for the combinations of qubit states. |
Probabilities of a selection of qubits.
:: [(QIndex, QState)] | The qubits for the state. |
-> Wavefunction | The wavefunction. |
-> Wavefunction | The projected wavefunction. |
Project a wavefunction onto a particular state.
:: 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.