newsynth-0.4.0.0: Exact and approximate synthesis of quantum circuits

Safe HaskellNone
LanguageHaskell98

Quantum.Synthesis.Matrix

Contents

Description

This module provides fixed but arbitrary sized vectors and matrices. The dimensions of the vectors and matrices are determined by the type, for example,

Matrix Two Three Complex

for complex 2×3-matrices. The type system ensures that there are no run-time dimension errors.

Synopsis

Type-level natural numbers

Note: with Haskell 7.4.2 data-kinds, this could be replaced by a tighter definition; however, the following works just fine in Haskell 7.2.

data Zero Source #

Type-level representation of zero.

Instances

Nat Zero Source # 
RootHalfRing a => FromGates (SO3 a) Source # 

Methods

from_gates :: [Gate] -> SO3 a Source #

(RootHalfRing a, ComplexRing a, OmegaRing a) => FromGates (U2 a) Source # 

Methods

from_gates :: [Gate] -> U2 a Source #

ToQOmega a => ToGates (SO3 a) Source # 

Methods

to_gates :: SO3 a -> [Gate] Source #

ToQOmega a => ToGates (U2 a) Source # 

Methods

to_gates :: U2 a -> [Gate] Source #

type Times Zero m Source # 
type Times Zero m = Zero
type Plus Zero m Source # 
type Plus Zero m = m

data Succ a Source #

Type-level representation of successor.

Instances

Nat a => Nat (Succ a) Source # 

Methods

nnat :: NNat (Succ a) Source #

nat :: Succ a -> Integer Source #

RootHalfRing a => FromGates (SO3 a) Source # 

Methods

from_gates :: [Gate] -> SO3 a Source #

(RootHalfRing a, ComplexRing a, OmegaRing a) => FromGates (U2 a) Source # 

Methods

from_gates :: [Gate] -> U2 a Source #

ToQOmega a => ToGates (SO3 a) Source # 

Methods

to_gates :: SO3 a -> [Gate] Source #

ToQOmega a => ToGates (U2 a) Source # 

Methods

to_gates :: U2 a -> [Gate] Source #

type Times (Succ n) m Source # 
type Times (Succ n) m = Plus m (Times n m)
type Plus (Succ n) m Source # 
type Plus (Succ n) m = Succ (Plus n m)

type One = Succ Zero Source #

The natural number 1 as a type.

type Two = Succ One Source #

The natural number 2 as a type.

type Three = Succ Two Source #

The natural number 3 as a type.

type Four = Succ Three Source #

The natural number 4 as a type.

type Five = Succ Four Source #

The natural number 5 as a type.

type Six = Succ Five Source #

The natural number 6 as a type.

type Seven = Succ Six Source #

The natural number 7 as a type.

type Eight = Succ Seven Source #

The natural number 8 as a type.

type Nine = Succ Eight Source #

The natural number 9 as a type.

type Ten = Succ Nine Source #

The natural number 10 as a type.

type Ten_and a = Succ (Succ (Succ (Succ (Succ (Succ (Succ (Succ (Succ (Succ a))))))))) Source #

The 10th successor of a natural number type. For example, the natural number 18 as a type is

Ten_and Eight

data NNat :: * -> * where Source #

A data type for the natural numbers. Specifically, if n is a type-level natural number, then

NNat n

is a singleton type containing only the natural number n.

Constructors

Zero :: NNat Zero 
Succ :: Nat n => NNat n -> NNat (Succ n) 

Instances

Show (NNat n) Source # 

Methods

showsPrec :: Int -> NNat n -> ShowS #

show :: NNat n -> String #

showList :: [NNat n] -> ShowS #

fromNNat :: NNat n -> Integer Source #

Convert an NNat to an Integer.

class Nat n where Source #

A type class for the natural numbers. The members are exactly the type-level natural numbers.

Minimal complete definition

nnat, nat

Methods

nnat :: NNat n Source #

Return a term-level natural number corresponding to this type-level natural number.

nat :: n -> Integer Source #

Return a term-level integer corresponding to this type-level natural number. The argument is just a dummy argument and is not evaluated.

Instances

Nat Zero Source # 
Nat a => Nat (Succ a) Source # 

Methods

nnat :: NNat (Succ a) Source #

nat :: Succ a -> Integer Source #

type family Plus n m Source #

Addition of type-level natural numbers.

Instances

type Plus Zero m Source # 
type Plus Zero m = m
type Plus (Succ n) m Source # 
type Plus (Succ n) m = Succ (Plus n m)

type family Times n m Source #

Multiplication of type-level natural numbers.

Instances

type Times Zero m Source # 
type Times Zero m = Zero
type Times (Succ n) m Source # 
type Times (Succ n) m = Plus m (Times n m)

Fixed-length vectors

data Vector :: * -> * -> * where Source #

Vector n a is the type of lists of length n with elements from a. We call this a "vector" rather than a tuple or list for two reasons: the vectors are homogeneous (all elements have the same type), and they are strict: if any one component is undefined, the whole vector is undefined.

Constructors

Nil :: Vector Zero a 
Cons :: !a -> !(Vector n a) -> Vector (Succ n) a infixr 5 

Instances

Eq a => Eq (Vector n a) Source # 

Methods

(==) :: Vector n a -> Vector n a -> Bool #

(/=) :: Vector n a -> Vector n a -> Bool #

Show a => Show (Vector n a) Source # 

Methods

showsPrec :: Int -> Vector n a -> ShowS #

show :: Vector n a -> String #

showList :: [Vector n a] -> ShowS #

DenomExp a => DenomExp (Vector n a) Source # 
WholePart a b => WholePart (Vector n a) (Vector n b) Source # 

Methods

from_whole :: Vector n b -> Vector n a Source #

to_whole :: Vector n a -> Vector n b Source #

ToDyadic a b => ToDyadic (Vector n a) (Vector n b) Source # 

Methods

maybe_dyadic :: Vector n a -> Maybe (Vector n b) Source #

Residue a b => Residue (Vector n a) (Vector n b) Source # 

Methods

residue :: Vector n a -> Vector n b Source #

vector_singleton :: a -> Vector One a Source #

Construct a vector of length 1.

vector_length :: Nat n => Vector n a -> Integer Source #

Return the length of a vector. Since this information is contained in the type, the vector argument is never evaluated and can be a dummy (undefined) argument.

list_of_vector :: Vector n a -> [a] Source #

Convert a fixed-length list to an ordinary list.

vector_zipwith :: (a -> b -> c) -> Vector n a -> Vector n b -> Vector n c Source #

Zip two equal length lists.

vector_map :: (a -> b) -> Vector n a -> Vector n b Source #

Map a function over a fixed-length list.

vector_enum :: (Num a, Nat n) => Vector n a Source #

Create the vector (0, 1, …, n-1).

vector_of_function :: (Num a, Nat n) => (a -> b) -> Vector n b Source #

Create the vector (f(0), f(1), …, f(n-1)).

vector :: Nat n => [a] -> Vector n a Source #

Construct a vector from a list. Note: since the length of the vector is a type-level integer, it cannot be inferred from the length of the input list; instead, it must be specified explicitly in the type. It is an error to apply this function to a list of the wrong length.

vector_index :: Integral i => Vector n a -> i -> a Source #

Return the ith element of the vector. Counting starts from 0. Throws an error if the index is out of range.

vector_repeat :: Nat n => a -> Vector n a Source #

Return a fixed-length list consisting of a repetition of the given element. Unlike replicate, no count is needed, because this information is already contained in the type. However, the type must of course be inferable from the context.

vector_transpose :: Nat m => Vector n (Vector m a) -> Vector m (Vector n a) Source #

Turn a list of columns into a list of rows.

vector_foldl :: (a -> b -> a) -> a -> Vector n b -> a Source #

Left strict fold over a fixed-length list.

vector_foldr :: (a -> b -> b) -> b -> Vector n a -> b Source #

Right fold over a fixed-length list.

vector_tail :: Vector (Succ n) a -> Vector n a Source #

Return the tail of a fixed-length list. Note that the type system ensures that this never fails.

vector_head :: Vector (Succ n) a -> a Source #

Return the head of a fixed-length list. Note that the type system ensures that this never fails.

vector_append :: Vector n a -> Vector m a -> Vector (n `Plus` m) a Source #

Append two fixed-length lists.

vector_sequence :: Monad m => Vector n (m a) -> m (Vector n a) Source #

Version of sequence for fixed-length lists.

Matrices

data Matrix m n a Source #

An m×n-matrix is a list of n columns, each of which is a list of m scalars. The type of square matrices of any fixed dimension is an instance of the Ring class, and therefore the usual symbols, such as "+" and "*" can be used on them. However, the non-square matrices, the symbols ".+." and ".*." must be used.

Constructors

Matrix !(Vector n (Vector m a)) 

Instances

RootHalfRing a => FromGates (SO3 a) Source # 

Methods

from_gates :: [Gate] -> SO3 a Source #

(RootHalfRing a, ComplexRing a, OmegaRing a) => FromGates (U2 a) Source # 

Methods

from_gates :: [Gate] -> U2 a Source #

ToQOmega a => ToGates (SO3 a) Source # 

Methods

to_gates :: SO3 a -> [Gate] Source #

ToQOmega a => ToGates (U2 a) Source # 

Methods

to_gates :: U2 a -> [Gate] Source #

Eq a => Eq (Matrix m n a) Source # 

Methods

(==) :: Matrix m n a -> Matrix m n a -> Bool #

(/=) :: Matrix m n a -> Matrix m n a -> Bool #

(Num a, Nat n) => Num (Matrix n n a) Source # 

Methods

(+) :: Matrix n n a -> Matrix n n a -> Matrix n n a #

(-) :: Matrix n n a -> Matrix n n a -> Matrix n n a #

(*) :: Matrix n n a -> Matrix n n a -> Matrix n n a #

negate :: Matrix n n a -> Matrix n n a #

abs :: Matrix n n a -> Matrix n n a #

signum :: Matrix n n a -> Matrix n n a #

fromInteger :: Integer -> Matrix n n a #

Nat m => Show (Matrix m n DOmega) Source # 

Methods

showsPrec :: Int -> Matrix m n DOmega -> ShowS #

show :: Matrix m n DOmega -> String #

showList :: [Matrix m n DOmega] -> ShowS #

Nat m => Show (Matrix m n DRComplex) Source # 
Nat m => Show (Matrix m n DRootTwo) Source # 
(Nat m, Show a) => Show (Matrix m n a) Source # 

Methods

showsPrec :: Int -> Matrix m n a -> ShowS #

show :: Matrix m n a -> String #

showList :: [Matrix m n a] -> ShowS #

DenomExp a => DenomExp (Matrix m n a) Source # 

Methods

denomexp :: Matrix m n a -> Integer Source #

denomexp_factor :: Matrix m n a -> Integer -> Matrix m n a Source #

(Nat n, Adjoint2 a) => Adjoint2 (Matrix n n a) Source # 

Methods

adj2 :: Matrix n n a -> Matrix n n a Source #

(Nat n, Adjoint a) => Adjoint (Matrix n n a) Source # 

Methods

adj :: Matrix n n a -> Matrix n n a Source #

(ComplexRing a, Nat n) => ComplexRing (Matrix n n a) Source # 

Methods

i :: Matrix n n a Source #

(RootHalfRing a, Nat n) => RootHalfRing (Matrix n n a) Source # 
(RootTwoRing a, Nat n) => RootTwoRing (Matrix n n a) Source # 
(HalfRing a, Nat n) => HalfRing (Matrix n n a) Source # 

Methods

half :: Matrix n n a Source #

fromDyadic :: Dyadic -> Matrix n n a Source #

Nat n => ShowLaTeX (Matrix n m DRComplex) Source # 
Nat n => ShowLaTeX (Matrix n m DOmega) Source # 
(ShowLaTeX a, Nat n) => ShowLaTeX (Matrix n m a) Source # 

Methods

showlatex :: Matrix n m a -> String Source #

showlatex_p :: Int -> Matrix n m a -> ShowS Source #

WholePart a b => WholePart (Matrix m n a) (Matrix m n b) Source # 

Methods

from_whole :: Matrix m n b -> Matrix m n a Source #

to_whole :: Matrix m n a -> Matrix m n b Source #

ToDyadic a b => ToDyadic (Matrix m n a) (Matrix m n b) Source # 

Methods

maybe_dyadic :: Matrix m n a -> Maybe (Matrix m n b) Source #

Residue a b => Residue (Matrix m n a) (Matrix m n b) Source # 

Methods

residue :: Matrix m n a -> Matrix m n b Source #

unMatrix :: Matrix m n a -> Vector n (Vector m a) Source #

Decompose a matrix into a list of columns.

matrix_size :: (Nat m, Nat n) => Matrix m n a -> (Integer, Integer) Source #

Return the size (m, n) of a matrix, where m is the number of rows, and n is the number of columns. Since this information is contained in the type, the matrix argument is not evaluated and can be a dummy (undefined) argument.

Basic matrix operations

(.+.) :: Num a => Matrix m n a -> Matrix m n a -> Matrix m n a infixl 6 Source #

Addition of m×n-matrices. We use a special symbol because m×n-matrices do not form a ring; only n×n-matrices form a ring (in which case the normal symbol "+" also works).

(.-.) :: Num a => Matrix m n a -> Matrix m n a -> Matrix m n a infixl 6 Source #

Subtraction of m×n-matrices. We use a special symbol because m×n-matrices do not form a ring; only n×n-matrices form a ring (in which case the normal symbol "-" also works).

matrix_map :: (a -> b) -> Matrix m n a -> Matrix m n b Source #

Map some function over every element of a matrix.

matrix_enum :: (Num a, Nat n, Nat m) => Matrix m n (a, a) Source #

Create the matrix whose i,j-entry is (i,j). Here i and j are 0-based, i.e., the top left entry is (0,0).

matrix_of_function :: (Num a, Nat n, Nat m) => (a -> a -> b) -> Matrix m n b Source #

Create the matrix whose i,j-entry is f i j. Here i and j are 0-based, i.e., the top left entry is f 0 0.

scalarmult :: Num a => a -> Matrix m n a -> Matrix m n a infixl 7 Source #

Multiplication of a scalar and an m×n-matrix.

scalardiv :: Fractional a => Matrix m n a -> a -> Matrix m n a infixl 7 Source #

Division of an m×n-matrix by a scalar.

(.*.) :: (Num a, Nat m) => Matrix m n a -> Matrix n p a -> Matrix m p a infixl 7 Source #

Multiplication of m×n-matrices. We use a special symbol because m×n-matrices do not form a ring; only n×n-matrices form a ring (in which case the normal symbol "*" also works).

null_matrix :: (Num a, Nat n, Nat m) => Matrix m n a Source #

Return the 0 matrix of the given dimension.

matrix_transpose :: Nat m => Matrix m n a -> Matrix n m a Source #

Take the transpose of an m×n-matrix.

adjoint :: (Nat m, Adjoint a) => Matrix m n a -> Matrix n m a Source #

Take the adjoint of an m×n-matrix. Unlike adj, this can be applied to non-square matrices.

matrix_index :: Integral i => Matrix m n a -> i -> i -> a Source #

Return the element in the ith row and jth column of the matrix. Counting of rows and columns starts from 0. Throws an error if the index is out of range.

matrix_entries :: Matrix m n a -> [a] Source #

Return a list of all the entries of a matrix, in some fixed but unspecified order.

matrix_sequence :: Monad m => Matrix n p (m a) -> m (Matrix n p a) Source #

Version of sequence for matrices.

tr :: Ring a => Matrix n n a -> a Source #

Return the trace of a square matrix.

hs_sqnorm :: (Ring a, Adjoint a, Nat n) => Matrix n m a -> a Source #

Return the square of the Hilbert-Schmidt norm of an m×n-matrix, defined by ‖M‖² = tr MM.

Operations on block matrices

stack_vertical :: Matrix m n a -> Matrix p n a -> Matrix (m `Plus` p) n a Source #

Stack matrices vertically.

stack_horizontal :: Matrix m n a -> Matrix m p a -> Matrix m (n `Plus` p) a Source #

Stack matrices horizontally.

tensor_vertical :: (Num a, Nat n) => Vector p a -> Matrix m n a -> Matrix (p `Times` m) n a Source #

Repeat a matrix vertically, according to some vector of scalars.

concat_vertical :: (Num a, Nat n) => Vector p (Matrix m n a) -> Matrix (p `Times` m) n a Source #

Vertically concatenate a vector of matrices.

tensor_horizontal :: (Num a, Nat m) => Vector p a -> Matrix m n a -> Matrix m (p `Times` n) a Source #

Repeat a matrix horizontally, according to some vector of scalars.

concat_horizontal :: (Num a, Nat m) => Vector p (Matrix m n a) -> Matrix m (p `Times` n) a Source #

Horizontally concatenate a vector of matrices.

tensor :: (Num a, Nat n, Nat (p `Times` m)) => Matrix p q a -> Matrix m n a -> Matrix (p `Times` m) (q `Times` n) a Source #

Kronecker tensor of two matrices.

oplus :: (Num a, Nat m, Nat q, Nat n, Nat p) => Matrix p q a -> Matrix m n a -> Matrix (p `Plus` m) (q `Plus` n) a Source #

Form a diagonal block matrix.

matrix_controlled :: (Eq a, Num a, Nat n) => Matrix n n a -> Matrix (n `Plus` n) (n `Plus` n) a Source #

Form a controlled gate.

Constructors and destructors

type U2 a = Matrix Two Two a Source #

A convenient abbreviation for the type of 2×2-matrices.

type SO3 a = Matrix Three Three a Source #

A convenient abbreviation for the type of 3×3-matrices.

matrix_of_columns :: (Nat n, Nat m) => [[a]] -> Matrix n m a Source #

A convenience constructor for matrices: turn a list of columns into a matrix.

Note: since the dimensions of the matrix are type-level integers, they cannot be inferred from the dimensions of the input; instead, they must be specified explicitly in the type. It is an error to apply this function to a list of the wrong dimension.

matrix_of_rows :: (Nat n, Nat m) => [[a]] -> Matrix n m a Source #

A convenience constructor for matrices: turn a list of rows into a matrix.

Note: since the dimensions of the matrix are type-level integers, they cannot be inferred from the dimensions of the input; instead, they must be specified explicitly in the type. It is an error to apply this function to a list of the wrong dimension.

matrix :: (Nat n, Nat m) => [[a]] -> Matrix n m a Source #

A synonym for matrix_of_rows.

columns_of_matrix :: Matrix n m a -> [[a]] Source #

Turn a matrix into a list of columns.

rows_of_matrix :: Nat n => Matrix n m a -> [[a]] Source #

Turn a matrix into a list of rows.

matrix2x2 :: (a, a) -> (a, a) -> Matrix Two Two a Source #

A convenience constructor for 2×2-matrices. The arguments are by rows.

from_matrix2x2 :: Matrix Two Two a -> ((a, a), (a, a)) Source #

A convenience destructor for 2×2-matrices. The result is by rows.

matrix3x3 :: (a, a, a) -> (a, a, a) -> (a, a, a) -> Matrix Three Three a Source #

A convenience constructor for 3×3-matrices. The arguments are by rows.

matrix4x4 :: (a, a, a, a) -> (a, a, a, a) -> (a, a, a, a) -> (a, a, a, a) -> Matrix Four Four a Source #

A convenience constructor for 4×4-matrices. The arguments are by rows.

column3 :: (a, a, a) -> Matrix Three One a Source #

A convenience constructor for 3-dimensional column vectors.

from_column3 :: Matrix Three One a -> (a, a, a) Source #

A convenience destructor for 3-dimensional column vectors. This is the inverse of column3.

column_matrix :: Vector n a -> Matrix n One a Source #

A convenience constructor for turning a vector into a column matrix.

Particular matrices

cnot :: Num a => Matrix Four Four a Source #

Controlled-not gate.

swap :: Num a => Matrix Four Four a Source #

Swap gate.

zrot :: (Eq r, Floating r, Adjoint r) => r -> Matrix Two Two (Cplx r) Source #

A z-rotation gate, Rsub /z/ = eiθZ/2.