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

Safe HaskellNone
LanguageHaskell2010

QIO.QioSyn

Contents

Description

This module defines the Syntax of the Quantum IO Monad, which is an embedded language for writing quantum computations.

Synopsis

Documentation

type RR = Double Source #

For Real numbers, we simply use the built in Double type

type CC = Complex RR Source #

For Complex numbers, we use the built in Complex numbers, over our Real number type (i.e. Double)

amp :: CC -> RR Source #

The amplitude of a complex number is the magnitude squared.

newtype Qbit Source #

The type of Qubits in QIO are simply integer references.

Constructors

Qbit Int 

Instances

Enum Qbit Source # 

Methods

succ :: Qbit -> Qbit #

pred :: Qbit -> Qbit #

toEnum :: Int -> Qbit #

fromEnum :: Qbit -> Int #

enumFrom :: Qbit -> [Qbit] #

enumFromThen :: Qbit -> Qbit -> [Qbit] #

enumFromTo :: Qbit -> Qbit -> [Qbit] #

enumFromThenTo :: Qbit -> Qbit -> Qbit -> [Qbit] #

Eq Qbit Source # 

Methods

(==) :: Qbit -> Qbit -> Bool #

(/=) :: Qbit -> Qbit -> Bool #

Num Qbit Source # 

Methods

(+) :: Qbit -> Qbit -> Qbit #

(-) :: Qbit -> Qbit -> Qbit #

(*) :: Qbit -> Qbit -> Qbit #

negate :: Qbit -> Qbit #

abs :: Qbit -> Qbit #

signum :: Qbit -> Qbit #

fromInteger :: Integer -> Qbit #

Ord Qbit Source # 

Methods

compare :: Qbit -> Qbit -> Ordering #

(<) :: Qbit -> Qbit -> Bool #

(<=) :: Qbit -> Qbit -> Bool #

(>) :: Qbit -> Qbit -> Bool #

(>=) :: Qbit -> Qbit -> Bool #

max :: Qbit -> Qbit -> Qbit #

min :: Qbit -> Qbit -> Qbit #

Show Qbit Source #

We can display a qubit reference

Methods

showsPrec :: Int -> Qbit -> ShowS #

show :: Qbit -> String #

showList :: [Qbit] -> ShowS #

Heap HeapMap Source #

A HeapMap is an instance of the Heap type class, where the Heap functions can make use of the underlying Map functions.

Qdata Bool Qbit Source #

The lowest-level instance of Qdata is the relation between Booleans and Qubits.

Methods

mkQ :: Bool -> QIO Qbit Source #

measQ :: Qbit -> QIO Bool Source #

letU :: Bool -> (Qbit -> U) -> U Source #

condQ :: Qbit -> (Bool -> U) -> U Source #

type Rotation = (Bool, Bool) -> CC Source #

A rotation is in essence a two-by-two complex valued matrix

data U Source #

The underlying data type of a U unitary operation

Constructors

UReturn 
Rot Qbit Rotation U 
Swap Qbit Qbit U 
Cond Qbit (Bool -> U) U 
Ulet Bool (Qbit -> U) U 

Instances

Show U Source #

We can display a representation of a unitary

Methods

showsPrec :: Int -> U -> ShowS #

show :: U -> String #

showList :: [U] -> ShowS #

Monoid U Source #

The type U forms a Monoid

Methods

mempty :: U #

mappend :: U -> U -> U #

mconcat :: [U] -> U #

data QIO a Source #

The underlying data type of a QIO Computation

Constructors

QReturn a 
MkQbit Bool (Qbit -> QIO a) 
ApplyU U (QIO a) 
Meas Qbit (Bool -> QIO a) 

Instances

Monad QIO Source #

The QIO type forms a Monad

Methods

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

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

return :: a -> QIO a #

fail :: String -> QIO a #

Functor QIO Source # 

Methods

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

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

Applicative QIO Source # 

Methods

pure :: a -> QIO a #

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

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

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

rot :: Qbit -> Rotation -> U Source #

Apply the given rotation to the given qubit

swap :: Qbit -> Qbit -> U Source #

Swap the state of the two given qubits

cond :: Qbit -> (Bool -> U) -> U Source #

Apply the conditional unitary, depending on the value of the given qubit

ulet :: Bool -> (Qbit -> U) -> U Source #

Introduce an Ancilla qubit in the given state, for use in the sub-unitary

urev :: U -> U Source #

Returns the inverse (or reverse) of the given unitary operation

unot :: Qbit -> U Source #

Apply a not rotation to the given qubit

uhad :: Qbit -> U Source #

Apply a hadamard rotation to the given qubit

uphase :: Qbit -> RR -> U Source #

Apply a phase rotation (of the given angle) to the given qubit

mkQbit :: Bool -> QIO Qbit Source #

Initialise a qubit in the given state (adding it to the overall quantum state)

applyU :: U -> QIO () Source #

Apply the given unitary operation to the current quantum state

measQbit :: Qbit -> QIO Bool Source #

Measure the given qubit, and return the measurement outcome (note that this operation may affect the overall quantum state, as a measurement is destructive)

rid :: Rotation Source #

The identity rotation

rnot :: Rotation Source #

The not rotation

rhad :: Rotation Source #

The hadamard rotation

rphase :: RR -> Rotation Source #

The phase rotation

rrev :: Rotation -> Rotation Source #

Returns the inverse (or reverse) of the given rotation

show' :: U -> Int -> Int -> String Source #

A helper function for the show instance of U

spaces :: Int -> String Source #

A helper function that returns a string of 4x spaces.

Orphan instances

Eq Rotation Source #

Rotations can be compared for equality. They are equal if the define the same matrix.

Show Rotation Source #

We can display the matrix representation of a rotation