quantum-arrow-0.0.4: An embedding of quantum computation as a Haskell arrowSource codeContentsIndex
Control.Arrow.Quantum
Synopsis
data Quantum m b c
type Amp = Complex Double
entangle :: Monad m => Quantum m [(a, Amp)] a
qLift :: (Eq a, MonadRandom m) => (a -> m b) -> Quantum m a b
qLift_ :: MonadRandom m => m b -> Quantum m () b
observeWith :: MonadRandom m => (a -> a -> Bool) -> Quantum m a a
observe :: (Eq a, MonadRandom m) => Quantum m a a
runQuantum :: Monad m => Quantum m a b -> [(a, Amp)] -> m [(b, Amp)]
execQuantum :: (Eq b, MonadRandom m) => Quantum m a b -> a -> m b
Documentation
data Quantum m b c Source

The Quantum arrow represents a quantum computation with observation. You can give a quantum computation a superposition of values, and it will operate over them, returning you a superposition back. If ever you observe (using the qLift or qLift_ functions), the system collapses to an eigenstate of what you observed.

 x <- entangle -< [(1, 1 :+ 0), (2, 1 :+ 0)]
 -- x is in state |1> + |2>; i.e. 1 or 2 with equal probability
 let y = x + 1
 -- y is in state |2> + |3>
 qLift print -< y    -- will print either 2 or 3; let's say it printed 2
 -- state collapses here, y in state |2>
 qLift print -< x    -- prints 1 (assuming 2 was printed earlier)

So the variables become entangled with each other in order to maintain consistency of the computation.

show/hide Instances
type Amp = Complex DoubleSource
Representation of a probability amplitude
entangle :: Monad m => Quantum m [(a, Amp)] aSource

entangle takes as input a list of values and probability amplitudes and gives as output a superposition of the inputs. For example:

 x <- entangle -< [(1, 1 :+ 0), (2, 0 :+ 1)]
 -- x is now |1> + i|2>
 qLift print -< x    -- prints 1 or 2 with equal probability
qLift :: (Eq a, MonadRandom m) => (a -> m b) -> Quantum m a bSource
qLift f -< x first collapses x to an eigenstate (using observe) then executes f x in the underlying monad. All conditionals up to this point are collapsed to an eigenstate (True or False) so a current branch of the computation is selected.
qLift_ :: MonadRandom m => m b -> Quantum m () bSource

qLift_ is just qIO which doesn't take an input. eg.

 qLift_ $ print "hello world" -< ()

All conditionals up to this point are collapsed to an eigenstate (True or False) so a current branch of the computation is selected.

observeWith :: MonadRandom m => (a -> a -> Bool) -> Quantum m a aSource

observeWith f takes an equivalence relation f, breaks the state space into eigenstates of that relation, and collapses to one. For example:

 x <- entangle -< map (\s -> (s,1 :+ 0)) [1..20]
 observeWith (\x y -> x `mod` 2 == y `mod` 2)

Will collapse x to be either even or odd, but make no finer decisions than that.

observe :: (Eq a, MonadRandom m) => Quantum m a aSource
observe is just observeWith on equality.
runQuantum :: Monad m => Quantum m a b -> [(a, Amp)] -> m [(b, Amp)]Source
runQuantum takes an input state vector, runs it through the given Quantum arrow, and returns a state vector of outputs.
execQuantum :: (Eq b, MonadRandom m) => Quantum m a b -> a -> m bSource
execQuantum q x passes the state |x> through q, collapses q's output to an eigenstate, and returns it.
Produced by Haddock version 2.3.0