{-# OPTIONS_GHC -Wall #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE CPP #-}
module Physics.Learn.QuantumMat
(
C
, xp
, xm
, yp
, ym
, zp
, zm
, np
, nm
, dim
, scaleV
, inner
, norm
, normalize
, probVector
, gramSchmidt
, conjV
, fromList
, toList
, sx
, sy
, sz
, scaleM
, (<>)
, (#>)
, (<#)
, conjugateTranspose
, fromLists
, toLists
, size
, matrixFunction
, couter
, dm
, trace
, normalizeDM
, oneQubitMixed
, timeEvMat
, timeEv
, timeEvMatSpec
, Kronecker(..)
, possibleOutcomes
, outcomesProjectors
, outcomesProbabilities
, Vector
, Matrix
)
where
import Numeric.LinearAlgebra
( C
, Vector
, Matrix
, Herm
, iC
, (><)
, ident
, scale
, norm_2
, inv
, (<\>)
, sym
, eigenvaluesSH
, eigSH
, cmap
, takeDiag
, conj
, dot
, tr
)
import qualified Numeric.LinearAlgebra as H
import Data.Complex
( Complex(..)
, magnitude
, realPart
)
#if MIN_VERSION_base(4,11,0)
import Prelude hiding ((<>))
#endif
xp :: Vector C
xp :: Vector C
xp = Vector C -> Vector C
normalize forall a b. (a -> b) -> a -> b
$ [C] -> Vector C
fromList [C
1, C
1]
xm :: Vector C
xm :: Vector C
xm = Vector C -> Vector C
normalize forall a b. (a -> b) -> a -> b
$ [C] -> Vector C
fromList [C
1, -C
1]
yp :: Vector C
yp :: Vector C
yp = Vector C -> Vector C
normalize forall a b. (a -> b) -> a -> b
$ [C] -> Vector C
fromList [C
1, C
iC]
ym :: Vector C
ym :: Vector C
ym = Vector C -> Vector C
normalize forall a b. (a -> b) -> a -> b
$ [C] -> Vector C
fromList [C
1, -C
iC]
zp :: Vector C
zp :: Vector C
zp = Vector C -> Vector C
normalize forall a b. (a -> b) -> a -> b
$ [C] -> Vector C
fromList [C
1, C
0]
zm :: Vector C
zm :: Vector C
zm = Vector C -> Vector C
normalize forall a b. (a -> b) -> a -> b
$ [C] -> Vector C
fromList [C
0, C
1]
np :: Double -> Double -> Vector C
np :: Double -> Double -> Vector C
np Double
theta Double
phi = [C] -> Vector C
fromList [ forall a. Floating a => a -> a
cos (Double
thetaforall a. Fractional a => a -> a -> a
/Double
2) forall a. a -> a -> Complex a
:+ Double
0
, forall a. Floating a => a -> a
exp(Double
0 forall a. a -> a -> Complex a
:+ Double
phi) forall a. Num a => a -> a -> a
* (forall a. Floating a => a -> a
sin (Double
thetaforall a. Fractional a => a -> a -> a
/Double
2) forall a. a -> a -> Complex a
:+ Double
0) ]
nm :: Double -> Double -> Vector C
nm :: Double -> Double -> Vector C
nm Double
theta Double
phi = [C] -> Vector C
fromList [ forall a. Floating a => a -> a
sin (Double
thetaforall a. Fractional a => a -> a -> a
/Double
2) forall a. a -> a -> Complex a
:+ Double
0
, -forall a. Floating a => a -> a
exp(Double
0 forall a. a -> a -> Complex a
:+ Double
phi) forall a. Num a => a -> a -> a
* (forall a. Floating a => a -> a
cos (Double
thetaforall a. Fractional a => a -> a -> a
/Double
2) forall a. a -> a -> Complex a
:+ Double
0) ]
dim :: Vector C -> Int
dim :: Vector C -> Int
dim = forall (c :: * -> *) t. Container c t => c t -> IndexOf c
H.size
scaleV :: C -> Vector C -> Vector C
scaleV :: C -> Vector C -> Vector C
scaleV = forall t (c :: * -> *). Linear t c => t -> c t -> c t
scale
inner :: Vector C -> Vector C -> C
inner :: Vector C -> Vector C -> C
inner = forall t. Numeric t => Vector t -> Vector t -> t
dot
norm :: Vector C -> Double
norm :: Vector C -> Double
norm = forall a. Normed a => a -> Double
norm_2
normalize :: Vector C -> Vector C
normalize :: Vector C -> Vector C
normalize Vector C
v = forall t (c :: * -> *). Linear t c => t -> c t -> c t
scale (Double
1 forall a. Fractional a => a -> a -> a
/ forall a. Normed a => a -> Double
norm_2 Vector C
v forall a. a -> a -> Complex a
:+ Double
0) Vector C
v
probVector :: Vector C
-> Vector Double
probVector :: Vector C -> Vector Double
probVector = forall b (c :: * -> *) e.
(Element b, Container c e) =>
(e -> b) -> c e -> c b
cmap (\C
c -> forall a. RealFloat a => Complex a -> a
magnitude C
cforall a. Floating a => a -> a -> a
**Double
2)
conjV :: Vector C -> Vector C
conjV :: Vector C -> Vector C
conjV = forall (c :: * -> *) e. Container c e => c e -> c e
conj
fromList :: [C] -> Vector C
fromList :: [C] -> Vector C
fromList = forall a. Storable a => [a] -> Vector a
H.fromList
toList :: Vector C -> [C]
toList :: Vector C -> [C]
toList = forall a. Storable a => Vector a -> [a]
H.toList
sx :: Matrix C
sx :: Matrix C
sx = (Int
2forall a. Storable a => Int -> Int -> [a] -> Matrix a
><Int
2) [ C
0, C
1
, C
1, C
0 ]
sy :: Matrix C
sy :: Matrix C
sy = (Int
2forall a. Storable a => Int -> Int -> [a] -> Matrix a
><Int
2) [ C
0, -C
iC
, C
iC, C
0 ]
sz :: Matrix C
sz :: Matrix C
sz = (Int
2forall a. Storable a => Int -> Int -> [a] -> Matrix a
><Int
2) [ C
1, C
0
, C
0, -C
1 ]
scaleM :: C -> Matrix C -> Matrix C
scaleM :: C -> Matrix C -> Matrix C
scaleM = forall t (c :: * -> *). Linear t c => t -> c t -> c t
scale
(<>) :: Matrix C -> Matrix C -> Matrix C
<> :: Matrix C -> Matrix C -> Matrix C
(<>) = forall t. Numeric t => Matrix t -> Matrix t -> Matrix t
(H.<>)
(#>) :: Matrix C -> Vector C -> Vector C
#> :: Matrix C -> Vector C -> Vector C
(#>) = forall t. Numeric t => Matrix t -> Vector t -> Vector t
(H.#>)
(<#) :: Vector C -> Matrix C -> Vector C
<# :: Vector C -> Matrix C -> Vector C
(<#) = forall t. Numeric t => Vector t -> Matrix t -> Vector t
(H.<#)
conjugateTranspose :: Matrix C -> Matrix C
conjugateTranspose :: Matrix C -> Matrix C
conjugateTranspose = forall m mt. Transposable m mt => m -> mt
tr
fromLists :: [[C]] -> Matrix C
fromLists :: [[C]] -> Matrix C
fromLists = forall t. Element t => [[t]] -> Matrix t
H.fromLists
toLists :: Matrix C -> [[C]]
toLists :: Matrix C -> [[C]]
toLists = forall t. Element t => Matrix t -> [[t]]
H.toLists
size :: Matrix C -> (Int,Int)
size :: Matrix C -> (Int, Int)
size = forall (c :: * -> *) t. Container c t => c t -> IndexOf c
H.size
matrixFunction :: (C -> C) -> Matrix C -> Matrix C
matrixFunction :: (C -> C) -> Matrix C -> Matrix C
matrixFunction C -> C
f Matrix C
m
= let (Vector C
valv,Matrix C
vecm) = forall t. Field t => Matrix t -> (Vector C, Matrix C)
H.eig Matrix C
m
fvalv :: Vector C
fvalv = [C] -> Vector C
fromList [C -> C
f C
val | C
val <- Vector C -> [C]
toList Vector C
valv]
in Matrix C
vecm Matrix C -> Matrix C -> Matrix C
<> forall a. (Num a, Element a) => Vector a -> Matrix a
H.diag Vector C
fvalv Matrix C -> Matrix C -> Matrix C
<> forall m mt. Transposable m mt => m -> mt
tr Matrix C
vecm
couter :: Vector C -> Vector C -> Matrix C
couter :: Vector C -> Vector C -> Matrix C
couter Vector C
v Vector C
w = Vector C
v forall t. Product t => Vector t -> Vector t -> Matrix t
`H.outer` forall (c :: * -> *) e. Container c e => c e -> c e
conj Vector C
w
dm :: Vector C -> Matrix C
dm :: Vector C -> Matrix C
dm Vector C
cvec = Vector C
cvec Vector C -> Vector C -> Matrix C
`couter` Vector C
cvec
trace :: Matrix C -> C
trace :: Matrix C -> C
trace = forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector C -> [C]
toList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. Element t => Matrix t -> Vector t
takeDiag
normalizeDM :: Matrix C -> Matrix C
normalizeDM :: Matrix C -> Matrix C
normalizeDM Matrix C
rho = forall t (c :: * -> *). Linear t c => t -> c t -> c t
scale (C
1 forall a. Fractional a => a -> a -> a
/ Matrix C -> C
trace Matrix C
rho) Matrix C
rho
oneQubitMixed :: Matrix C
oneQubitMixed :: Matrix C
oneQubitMixed = Matrix C -> Matrix C
normalizeDM forall a b. (a -> b) -> a -> b
$ forall a. (Num a, Element a) => Int -> Matrix a
ident Int
2
timeEvMat :: Double -> Matrix C -> Matrix C
timeEvMat :: Double -> Matrix C -> Matrix C
timeEvMat Double
dt Matrix C
h
= let ah :: Matrix C
ah = forall t (c :: * -> *). Linear t c => t -> c t -> c t
scale (Double
0 forall a. a -> a -> Complex a
:+ Double
dt forall a. Fractional a => a -> a -> a
/ Double
2) Matrix C
h
(Int
l,Int
m) = Matrix C -> (Int, Int)
size Matrix C
h
n :: Int
n = if Int
l forall a. Eq a => a -> a -> Bool
== Int
m then Int
m else forall a. HasCallStack => [Char] -> a
error [Char]
"timeEv needs square Hamiltonian"
identity :: Matrix C
identity = forall a. (Num a, Element a) => Int -> Matrix a
ident Int
n
in forall t. Field t => Matrix t -> Matrix t
inv (Matrix C
identity forall a. Num a => a -> a -> a
+ Matrix C
ah) Matrix C -> Matrix C -> Matrix C
<> (Matrix C
identity forall a. Num a => a -> a -> a
- Matrix C
ah)
timeEv :: Double -> Matrix C -> Vector C -> Vector C
timeEv :: Double -> Matrix C -> Vector C -> Vector C
timeEv Double
dt Matrix C
h Vector C
v
= let ah :: Matrix C
ah = forall t (c :: * -> *). Linear t c => t -> c t -> c t
scale (Double
0 forall a. a -> a -> Complex a
:+ Double
dt forall a. Fractional a => a -> a -> a
/ Double
2) Matrix C
h
(Int
l,Int
m) = Matrix C -> (Int, Int)
size Matrix C
h
n :: Int
n = if Int
l forall a. Eq a => a -> a -> Bool
== Int
m then Int
m else forall a. HasCallStack => [Char] -> a
error [Char]
"timeEv needs square Hamiltonian"
identity :: Matrix C
identity = forall a. (Num a, Element a) => Int -> Matrix a
ident Int
n
in (Matrix C
identity forall a. Num a => a -> a -> a
+ Matrix C
ah) forall (c :: * -> *) t.
(LSDiv c, Field t) =>
Matrix t -> c t -> c t
<\> ((Matrix C
identity forall a. Num a => a -> a -> a
- Matrix C
ah) Matrix C -> Vector C -> Vector C
#> Vector C
v)
timeEvMatSpec :: Matrix C -> Double -> Matrix C
timeEvMatSpec :: Matrix C -> Double -> Matrix C
timeEvMatSpec Matrix C
m Double
t = (C -> C) -> Matrix C -> Matrix C
matrixFunction (\C
h -> forall a. Floating a => a -> a
exp(-C
iC forall a. Num a => a -> a -> a
* C
h forall a. Num a => a -> a -> a
* (Double
t forall a. a -> a -> Complex a
:+ Double
0))) Matrix C
m
class Kronecker a where
kron :: a -> a -> a
instance H.Product t => Kronecker (Vector t) where
kron :: Vector t -> Vector t -> Vector t
kron Vector t
v1 Vector t
v2 = forall a. Storable a => [a] -> Vector a
H.fromList [t
c1 forall a. Num a => a -> a -> a
* t
c2 | t
c1 <- forall a. Storable a => Vector a -> [a]
H.toList Vector t
v1, t
c2 <- forall a. Storable a => Vector a -> [a]
H.toList Vector t
v2]
instance H.Product t => Kronecker (Matrix t) where
kron :: Matrix t -> Matrix t -> Matrix t
kron = forall t. Product t => Matrix t -> Matrix t -> Matrix t
H.kronecker
possibleOutcomes :: Matrix C -> [Double]
possibleOutcomes :: Matrix C -> [Double]
possibleOutcomes Matrix C
observable
= forall a. Storable a => Vector a -> [a]
H.toList forall a b. (a -> b) -> a -> b
$ forall t. Field t => Herm t -> Vector Double
eigenvaluesSH (forall t. Field t => Matrix t -> Herm t
sym Matrix C
observable)
valsVecs :: Herm C -> [(Double,Vector C)]
valsVecs :: Herm C -> [(Double, Vector C)]
valsVecs Herm C
h = let (Vector Double
valv,Matrix C
m) = forall t. Field t => Herm t -> (Vector Double, Matrix t)
eigSH Herm C
h
vals :: [Double]
vals = forall a. Storable a => Vector a -> [a]
H.toList Vector Double
valv
vecs :: [Vector C]
vecs = forall a b. (a -> b) -> [a] -> [b]
map (Vector C -> Vector C
conjV forall b c a. (b -> c) -> (a -> b) -> a -> c
. [C] -> Vector C
fromList) forall a b. (a -> b) -> a -> b
$ Matrix C -> [[C]]
toLists (Matrix C -> Matrix C
conjugateTranspose Matrix C
m)
in forall a b. [a] -> [b] -> [(a, b)]
zip [Double]
vals [Vector C]
vecs
valsPs :: Herm C -> [(Double,Matrix C)]
valsPs :: Herm C -> [(Double, Matrix C)]
valsPs Herm C
h = [(Double
val,Vector C -> Vector C -> Matrix C
couter Vector C
vec Vector C
vec) | (Double
val,Vector C
vec) <- Herm C -> [(Double, Vector C)]
valsVecs Herm C
h]
combineFst :: (Eq a, Num b) => [(a,b)] -> [(a,b)]
combineFst :: forall a b. (Eq a, Num b) => [(a, b)] -> [(a, b)]
combineFst [] = []
combineFst [(a, b)
p] = [(a, b)
p]
combineFst ((a
x1,b
m1):(a
x2,b
m2):[(a, b)]
ps)
= if a
x1 forall a. Eq a => a -> a -> Bool
== a
x2
then forall a b. (Eq a, Num b) => [(a, b)] -> [(a, b)]
combineFst ((a
x1,b
m1forall a. Num a => a -> a -> a
+b
m2)forall a. a -> [a] -> [a]
:[(a, b)]
ps)
else (a
x1,b
m1)forall a. a -> [a] -> [a]
:forall a b. (Eq a, Num b) => [(a, b)] -> [(a, b)]
combineFst ((a
x2,b
m2)forall a. a -> [a] -> [a]
:[(a, b)]
ps)
outcomesProjectors :: Matrix C -> [(Double,Matrix C)]
outcomesProjectors :: Matrix C -> [(Double, Matrix C)]
outcomesProjectors Matrix C
m = forall a b. (Eq a, Num b) => [(a, b)] -> [(a, b)]
combineFst (Herm C -> [(Double, Matrix C)]
valsPs (forall t. Field t => Matrix t -> Herm t
sym Matrix C
m))
outcomesProbabilities :: Matrix C -> Vector C -> [(Double,Double)]
outcomesProbabilities :: Matrix C -> Vector C -> [(Double, Double)]
outcomesProbabilities Matrix C
m Vector C
v
= [(Double
a,forall a. Complex a -> a
realPart (Vector C -> Vector C -> C
inner Vector C
v (Matrix C
p Matrix C -> Vector C -> Vector C
#> Vector C
v))) | (Double
a,Matrix C
p) <- Matrix C -> [(Double, Matrix C)]
outcomesProjectors Matrix C
m]
gramSchmidt :: [Vector C] -> [Vector C]
gramSchmidt :: [Vector C] -> [Vector C]
gramSchmidt [] = []
gramSchmidt (Vector C
v:[Vector C]
vs) = let nvs :: [Vector C]
nvs = [Vector C] -> [Vector C]
gramSchmidt [Vector C]
vs
nv :: Vector C
nv = Vector C -> Vector C
normalize (Vector C
v forall a. Num a => a -> a -> a
- forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [forall t (c :: * -> *). Linear t c => t -> c t -> c t
scale (Vector C -> Vector C -> C
inner Vector C
w Vector C
v) Vector C
w | Vector C
w <- [Vector C]
nvs])
in Vector C
nvforall a. a -> [a] -> [a]
:[Vector C]
nvs