QIO-1.2: The Quantum IO Monad is a library for defining quantum computations in Haskell

Safe HaskellSafe-Infered

QIO.Qio

Description

This module defines the functions that can be used to simulate the running of QIO computations.

Synopsis

Documentation

type Pure = VecEqL CC HeapMapSource

A Pure state can be thought of as a vector of classical basis states, stored as Heaps, along with complex amplitudes.

updateP :: Pure -> Qbit -> Bool -> PureSource

The state of a qubit can be updated in a Pure state, by mapping the update operation over each Heap.

newtype Unitary Source

A Unitary can be thought of as an operation on a HeapMap that may produce a Pure state.

Constructors

U 

Fields

unU :: Int -> HeapMap -> Pure
 

Instances

Monoid Unitary

The Unitary type forms a Monoid

unitaryRot :: Rotation -> BoolSource

A function that checks if a given Rotation is in face unitary. Note that this is currently a dummy stub function, and states that any rotation is unitary. (This is only o.k. at the moment as all the rotations defined in the QIO library are unitary, but won't catch un-unitary user-defined Rotations)

uMatrix :: Qbit -> (CC, CC, CC, CC) -> UnitarySource

Given the four complex numbers that make up a 2-by-2 matrix, we can create a Unitary that applies the rotation to the given qubit.

uRot :: Qbit -> Rotation -> UnitarySource

A rotation can be converted into a Unitary, using the uMatrix function

uSwap :: Qbit -> Qbit -> UnitarySource

A swap operation can be defined as a Unitary

uCond :: Qbit -> (Bool -> Unitary) -> UnitarySource

A conditional operation can be defined as a Unitary

uLet :: Bool -> (Qbit -> Unitary) -> UnitarySource

A let operation can be defined as a Unitary

runU :: U -> UnitarySource

Any member of the U type can be "run" by converting it into a Unitary.

data StateQ Source

A quantum state is a defined as the next free qubit reference, along with the Pure state that represents the overall quantum state

Constructors

StateQ 

Fields

free :: Int
 
pure :: Pure
 

pa :: Pure -> RRSource

Given a Pure state, return a sum of all the amplitudes.

data Split Source

A Split, is defined as a probability, along with the two Pure states.

Constructors

Split 

Fields

p :: RR
 
ifTrue :: Pure
 
ifFalse :: Pure
 

split :: Pure -> Qbit -> SplitSource

Given a Pure state, we can create a Split, by essentially splitting the state into the part where the qubit is True, and the part where the qubit is False. This is how measurements are implemented in QIO.

class Monad m => PMonad m whereSource

We can extend a Monad into a PMonad if it defines a way of probabilistically merging two computations, based on a given probability.

Methods

merge :: RR -> m a -> m a -> m aSource

Instances

PMonad IO

IO forms a PMonad, using the random number generator to pick one of the "merged" computations probabilistically.

PMonad Prob

Prob is also a PMonad, where the result of both computations are combined into a probability distribution.

data Prob a Source

The type Prob is defined as a wrapper around Vectors with Real probabilities.

Constructors

Prob 

Fields

unProb :: Vec RR a
 

Instances

Monad Prob

Prob forms a Monad

PMonad Prob

Prob is also a PMonad, where the result of both computations are combined into a probability distribution.

Show a => Show (Prob a)

We can show a probability distribution by filtering out elements with a zero probability.

evalWith :: PMonad m => QIO a -> State StateQ (m a)Source

Given a PMonad, a QIO Computation can be converted into a Stateful computation over a quantum state (of type StateQ).

eval :: PMonad m => QIO a -> m aSource

A QIO computation is evaluated by converting it into a stateful computation and then evaluating that over the initial state.

run :: QIO a -> IO aSource

Running a QIO computation evaluates it in the IO PMonad

sim :: QIO a -> Prob aSource

Simulating a QIO computation evaluates it in the Prob PMonad