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

Safe HaskellNone
LanguageHaskell2010

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 HeapMap Source #

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 -> Pure Source #

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

Instances

Monoid Unitary Source #

The Unitary type forms a Monoid

unitaryRot :: Rotation -> Bool Source #

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) -> Unitary Source #

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 -> Unitary Source #

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

uSwap :: Qbit -> Qbit -> Unitary Source #

A swap operation can be defined as a Unitary

uCond :: Qbit -> (Bool -> Unitary) -> Unitary Source #

A conditional operation can be defined as a Unitary

uLet :: Bool -> (Qbit -> Unitary) -> Unitary Source #

A let operation can be defined as a Unitary

runU :: U -> Unitary Source #

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

pa :: Pure -> RR Source #

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

split :: Pure -> Qbit -> Split Source #

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 where Source #

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

Minimal complete definition

merge

Methods

merge :: RR -> m a -> m a -> m a Source #

Instances

PMonad IO Source #

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

Methods

merge :: RR -> IO a -> IO a -> IO a Source #

PMonad Prob Source #

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

Methods

merge :: RR -> Prob a -> Prob a -> Prob a Source #

data Prob a Source #

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

Constructors

Prob 

Fields

Instances

Monad Prob Source #

Prob forms a Monad

Methods

(>>=) :: Prob a -> (a -> Prob b) -> Prob b #

(>>) :: Prob a -> Prob b -> Prob b #

return :: a -> Prob a #

fail :: String -> Prob a #

Functor Prob Source # 

Methods

fmap :: (a -> b) -> Prob a -> Prob b #

(<$) :: a -> Prob b -> Prob a #

Applicative Prob Source # 

Methods

pure :: a -> Prob a #

(<*>) :: Prob (a -> b) -> Prob a -> Prob b #

(*>) :: Prob a -> Prob b -> Prob b #

(<*) :: Prob a -> Prob b -> Prob a #

PMonad Prob Source #

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

Methods

merge :: RR -> Prob a -> Prob a -> Prob a Source #

Show a => Show (Prob a) Source #

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

Methods

showsPrec :: Int -> Prob a -> ShowS #

show :: Prob a -> String #

showList :: [Prob a] -> ShowS #

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 a Source #

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

run :: QIO a -> IO a Source #

Running a QIO computation evaluates it in the IO PMonad

sim :: QIO a -> Prob a Source #

Simulating a QIO computation evaluates it in the Prob PMonad