{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Data.Qubit (
QIndex
, QState(..)
, Amplitude
, Wavefunction
, Operator
, qubit
, pureQubit
, qubits
, groundState
, pureState
, qubitsOperator
, wavefunctionOrder
, wavefunctionIndices
, wavefunctionAmplitudes
, rawWavefunction
, operatorOrder
, operatorIndices
, operatorAmplitudes
, rawOperator
, (^*^)
, (^*)
, (*^)
, (^^*)
, (*^^)
, probabilities
, project
, measure
, wavefunctionProbability
) where
import Control.Arrow (first, second)
import Control.Monad (ap, mapM, replicateM)
import Control.Monad.Random.Class (fromList)
import Control.Monad.Random.Lazy (Rand, RandomGen)
import Data.Complex (Complex(..), conjugate, magnitude)
import Data.Function (on)
import Data.Int.Util (ilog2, isqrt)
import Data.List (elemIndex, groupBy, intersect, intercalate, sortBy)
import Data.Maybe (catMaybes)
import Numeric.LinearAlgebra.Array ((.*))
import Numeric.LinearAlgebra.Array.Util (Idx(iName), asScalar, coords, dims, mapArray, order, outers, renameExplicit, reorder, setType)
import Numeric.LinearAlgebra.Tensor (Tensor, Variant(..), contrav, listTensor, switch)
import qualified Data.Vector.Storable as V (map, toList)
data QState =
QState0
| QState1
deriving (Bounded, Enum, Eq, Ord)
instance Read QState where
readsPrec = (fmap (first toEnum) .) . readsPrec
instance Show QState where
show = show . fromEnum
type QIndex = Int
names :: Tensor a -> [String]
names = fmap iName . dims
variantPrefix :: Variant -> Char
variantPrefix Contra = 'm'
variantPrefix Co = 'n'
prefixVariant :: String -> Variant
prefixVariant ('m' : _) = Contra
prefixVariant ('n' : _) = Co
prefixVariant _ = error "Unexpected index."
prefixDimension :: String -> Int
prefixDimension ('m' : _) = 2
prefixDimension ('n' : _) = -2
prefixDimension _ = error "Unexpected index."
indexLabels :: Variant
-> [QIndex]
-> [(String, String)]
indexLabels variant indices =
let
n = length indices
o =
case variant of
Contra -> 0
Co -> n
in
zipWith (\k v -> (show k, variantPrefix variant : show v)) [(1+o)..] $ reverse indices
wavefunctionLabels :: Int
-> [(String, String)]
wavefunctionLabels n = indexLabels Contra [0..(n-1)]
operatorLabels :: [QIndex]
-> [(String, String)]
operatorLabels indices = indexLabels Contra indices ++ indexLabels Co indices
type Amplitude = Complex Double
showAmplitude :: Amplitude -> String
showAmplitude (a :+ b)
| b == 0 = show a
| a == 0 = show b ++ "i"
| b < 0 = "(" ++ show a ++ show b ++ "i)"
| otherwise = "(" ++ show a ++ "+" ++ show b ++ "i)"
type ShowState = Int
-> ([QState], Amplitude)
-> String
showTensor :: (a -> Tensor Amplitude)
-> ShowState
-> a
-> String
showTensor toTensor format x =
let
x' = canonicalOrder $ toTensor x
n = order x'
in
(++ (show $ tensorIndices x'))
. (++ " @ ")
. intercalate " + "
. fmap (format n)
. filter ((/= 0) . snd)
$ tensorAmplitudes x'
tensorIndices :: Tensor Amplitude
-> [QIndex]
tensorIndices =
fmap (read . tail)
. filter ((== variantPrefix Contra) . head)
. names
canonicalOrder :: Tensor Amplitude -> Tensor Amplitude
canonicalOrder x =
if False
then let
n = order x
f (v : i) (v' : i') = (v, - read i :: Int) `compare` (v', - read i')
f _ _ = undefined
ns = names x
ns' = sortBy f ns
Just permutation = (mapM . flip elemIndex) ns ns'
permute y = map (y !!) permutation
x' =
renameExplicit (zip (show <$> ([1..] :: [Int])) ns')
. listTensor (prefixDimension <$> ns')
. fmap snd
. sortBy (compare `on` fst)
. fmap (first permute)
. zip (replicateM n [(minBound::QState)..maxBound])
. V.toList
$ coords x
in
foldl (flip $ ap setType prefixVariant) (contrav x') ns'
else let
f (v : i) (v' : i') = (v, - read i :: Int) `compare` (v', - read i')
f _ _ = undefined
in
reorder (sortBy f $ names x) x
tensorAmplitudes :: Tensor Amplitude
-> [([QState], Amplitude)]
tensorAmplitudes x =
let
n = order x
in
zip (replicateM n [minBound..maxBound])
. V.toList
$ coords x
newtype Wavefunction = Wavefunction {rawWavefunction' :: Tensor Amplitude}
deriving (Eq, Floating, Fractional, Num)
instance Show Wavefunction where
show =
showTensor rawWavefunction'
$ \_ (k, v) ->
showAmplitude v ++ "|" ++ concatMap show k ++ ">"
rawWavefunction :: Wavefunction -> Tensor Amplitude
rawWavefunction = canonicalOrder . rawWavefunction'
wavefunctionOrder :: Wavefunction -> Int
wavefunctionOrder = order . rawWavefunction'
wavefunctionIndices :: Wavefunction
-> [QIndex]
wavefunctionIndices = tensorIndices . rawWavefunction'
wavefunctionAmplitudes :: Wavefunction
-> [([QState], Amplitude)]
wavefunctionAmplitudes = tensorAmplitudes . rawWavefunction'
qubit :: QIndex
-> (Amplitude, Amplitude)
-> Wavefunction
qubit index (a0, a1) =
Wavefunction
. renameExplicit [("1", variantPrefix Contra : show index)]
$ listTensor [2] [a0, a1]
pureQubit :: QIndex
-> QState
-> Wavefunction
pureQubit index QState0 = qubit index (1, 0)
pureQubit index QState1 = qubit index (0, 1)
qubits :: [Amplitude]
-> Wavefunction
qubits amplitudes =
let
n = ilog2 $ length amplitudes
in
Wavefunction
. renameExplicit (wavefunctionLabels n)
$ listTensor (replicate n 2) amplitudes
groundState :: Int
-> Wavefunction
groundState = pureState . flip replicate QState0
pureState :: [QState]
-> Wavefunction
pureState =
Wavefunction
. outers
. (rawWavefunction' <$>)
. (uncurry pureQubit <$>)
. zip [0..]
. reverse
newtype Operator = Operator {rawOperator' :: Tensor (Complex Double)}
deriving (Eq, Floating, Fractional, Num)
instance Show Operator where
show =
showTensor rawOperator'
$ \n (k, v) ->
let
(kr, kc) = splitAt (n `div` 2) $ concatMap show k
in
showAmplitude v ++ "|" ++ kr ++ "><" ++ kc ++ "|"
rawOperator :: Operator -> Tensor Amplitude
rawOperator = canonicalOrder . rawOperator'
operatorOrder :: Operator -> Int
operatorOrder = isqrt . order . rawOperator'
operatorIndices :: Operator
-> [QIndex]
operatorIndices = tensorIndices . rawOperator'
operatorAmplitudes :: Operator
-> [(([QState], [QState]), Amplitude)]
operatorAmplitudes (Operator x) =
let
x' = tensorAmplitudes x
n = length . fst $ head x'
in
first (splitAt $ n `div` 2) <$> x'
qubitsOperator :: [QIndex]
-> [Amplitude]
-> Operator
qubitsOperator indices =
let
n = length indices
in
Operator
. renameExplicit (operatorLabels $ reverse indices)
. listTensor (replicate n 2 ++ replicate n (-2))
mult :: Tensor Amplitude -> Tensor Amplitude -> Tensor Amplitude
mult x y =
let
lft = filter ((== variantPrefix Co ) . head) $ names x
rght = filter ((== variantPrefix Contra) . head) $ names y
cmmn = fmap tail lft `intersect` fmap tail rght
x' = renameExplicit [(i, '@' : tail i) | i <- filter ((`elem` cmmn) . tail) lft ] x
y' = renameExplicit [(i, '@' : tail i) | i <- filter ((`elem` cmmn) . tail) rght] y
in
x' * y'
(^*^) :: Operator -> Operator -> Operator
Operator x ^*^ Operator y = Operator $ x `mult` y
infixr 7 ^*^
(^*) :: Operator -> Wavefunction -> Wavefunction
Operator x ^* Wavefunction y = Wavefunction $ x `mult` y
infixr 6 ^*
(*^) :: Wavefunction -> Operator -> Wavefunction
(*^) = flip (^*)
infixl 6 *^
(^^*) :: Foldable t => t Operator -> Wavefunction -> Wavefunction
(^^*) = flip . foldl $ flip (^*)
infixr 6 ^^*
(*^^) :: Foldable t => Wavefunction -> t Operator -> Wavefunction
(*^^) = flip (^^*)
infixl 6 *^^
probabilities :: [QIndex]
-> Wavefunction
-> [([(QIndex, QState)], Double)]
probabilities indices x =
let
indices' = wavefunctionIndices x
positions = catMaybes $ (`elemIndex` indices') <$> indices
in
filter ((/= 0) . snd)
. fmap (\kvs -> (fst $ head kvs, sum $ snd <$> kvs))
. groupBy ((==) `on` fst)
$ sortBy (compare `on` fst)
[
(
fmap snd . filter ((`elem` positions) . fst) . zip [0..] $ zip indices' states
, magnitude amplitude ^ (2::Int)
)
|
(states, amplitude) <- wavefunctionAmplitudes x
]
project :: [(QIndex, QState)]
-> Wavefunction
-> Wavefunction
project states x =
let
y = canonicalOrder $ rawWavefunction' x
p =
canonicalOrder
. outers
$ fmap rawWavefunction'
[
case i `lookup` states of
Nothing -> qubit i (1, 1)
Just s -> pureQubit i s
|
i <- [0..(order y - 1)]
]
z = p .* y
in
Wavefunction $ z / sqrt (mapArray (V.map conjugate) z * switch z)
measure :: RandomGen g
=> [QIndex]
-> Wavefunction
-> Rand g ([(QIndex, QState)], Wavefunction)
measure indices x =
do
let
candidates = probabilities indices x
collapse <- fromList $ second toRational <$> candidates
return (collapse, project collapse x)
wavefunctionProbability :: Wavefunction
-> Amplitude
wavefunctionProbability (Wavefunction x) = asScalar $ mapArray (V.map conjugate) x * switch x