Safe Haskell | None |
---|
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.
- data Zero
- data Succ a
- type One = Succ Zero
- type Two = Succ One
- type Three = Succ Two
- type Four = Succ Three
- type Five = Succ Four
- type Six = Succ Five
- type Seven = Succ Six
- type Eight = Succ Seven
- type Nine = Succ Eight
- type Ten = Succ Nine
- type Ten_and a = Succ (Succ (Succ (Succ (Succ (Succ (Succ (Succ (Succ (Succ a)))))))))
- data NNat where
- fromNNat :: NNat n -> Integer
- class Nat n where
- type family Plus n m
- type family Times n m
- data Vector where
- vector_singleton :: a -> Vector One a
- vector_length :: Nat n => Vector n a -> Integer
- list_of_vector :: Vector n a -> [a]
- vector_zipwith :: (a -> b -> c) -> Vector n a -> Vector n b -> Vector n c
- vector_map :: (a -> b) -> Vector n a -> Vector n b
- vector_enum :: (Num a, Nat n) => Vector n a
- vector_of_function :: (Num a, Nat n) => (a -> b) -> Vector n b
- vector :: Nat n => [a] -> Vector n a
- vector_index :: Integral i => Vector n a -> i -> a
- vector_repeat :: Nat n => a -> Vector n a
- vector_transpose :: Nat m => Vector n (Vector m a) -> Vector m (Vector n a)
- vector_foldl :: (a -> b -> a) -> a -> Vector n b -> a
- vector_foldr :: (a -> b -> b) -> b -> Vector n a -> b
- vector_tail :: Vector (Succ n) a -> Vector n a
- vector_head :: Vector (Succ n) a -> a
- vector_append :: Vector n a -> Vector m a -> Vector (n `Plus` m) a
- vector_sequence :: Monad m => Vector n (m a) -> m (Vector n a)
- data Matrix m n a = Matrix !(Vector n (Vector m a))
- unMatrix :: Matrix m n a -> Vector n (Vector m a)
- matrix_size :: (Nat m, Nat n) => Matrix m n a -> (Integer, Integer)
- (.+.) :: Num a => Matrix m n a -> Matrix m n a -> Matrix m n a
- (.-.) :: Num a => Matrix m n a -> Matrix m n a -> Matrix m n a
- matrix_map :: (a -> b) -> Matrix m n a -> Matrix m n b
- matrix_enum :: (Num a, Nat n, Nat m) => Matrix m n (a, a)
- matrix_of_function :: (Num a, Nat n, Nat m) => (a -> a -> b) -> Matrix m n b
- scalarmult :: Num a => a -> Matrix m n a -> Matrix m n a
- scalardiv :: Fractional a => Matrix m n a -> a -> Matrix m n a
- (.*.) :: (Num a, Nat m) => Matrix m n a -> Matrix n p a -> Matrix m p a
- null_matrix :: (Num a, Nat n, Nat m) => Matrix m n a
- matrix_transpose :: Nat m => Matrix m n a -> Matrix n m a
- adjoint :: (Nat m, Adjoint a) => Matrix m n a -> Matrix n m a
- matrix_index :: Integral i => Matrix m n a -> i -> i -> a
- matrix_entries :: Matrix m n a -> [a]
- matrix_sequence :: Monad m => Matrix n p (m a) -> m (Matrix n p a)
- tr :: Ring a => Matrix n n a -> a
- hs_sqnorm :: (Ring a, Adjoint a, Nat n) => Matrix n m a -> a
- stack_vertical :: Matrix m n a -> Matrix p n a -> Matrix (m `Plus` p) n a
- stack_horizontal :: Matrix m n a -> Matrix m p a -> Matrix m (n `Plus` p) a
- tensor_vertical :: (Num a, Nat n) => Vector p a -> Matrix m n a -> Matrix (p `Times` m) n a
- concat_vertical :: (Num a, Nat n) => Vector p (Matrix m n a) -> Matrix (p `Times` m) n a
- tensor_horizontal :: (Num a, Nat m) => Vector p a -> Matrix m n a -> Matrix m (p `Times` n) a
- concat_horizontal :: (Num a, Nat m) => Vector p (Matrix m n a) -> Matrix m (p `Times` n) a
- 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
- 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
- matrix_controlled :: (Eq a, Num a, Nat n) => Matrix n n a -> Matrix (n `Plus` n) (n `Plus` n) a
- type U2 a = Matrix Two Two a
- type SO3 a = Matrix Three Three a
- matrix_of_columns :: (Nat n, Nat m) => [[a]] -> Matrix n m a
- matrix_of_rows :: (Nat n, Nat m) => [[a]] -> Matrix n m a
- matrix :: (Nat n, Nat m) => [[a]] -> Matrix n m a
- columns_of_matrix :: Matrix n m a -> [[a]]
- rows_of_matrix :: Nat n => Matrix n m a -> [[a]]
- matrix2x2 :: (a, a) -> (a, a) -> Matrix Two Two a
- from_matrix2x2 :: Matrix Two Two a -> ((a, a), (a, a))
- matrix3x3 :: (a, a, a) -> (a, a, a) -> (a, a, a) -> Matrix Three Three a
- matrix4x4 :: (a, a, a, a) -> (a, a, a, a) -> (a, a, a, a) -> (a, a, a, a) -> Matrix Four Four a
- column3 :: (a, a, a) -> Matrix Three One a
- from_column3 :: Matrix Three One a -> (a, a, a)
- column_matrix :: Vector n a -> Matrix n One a
- cnot :: Num a => Matrix Four Four a
- swap :: Num a => Matrix Four Four a
- zrot :: (Eq r, Floating r, Adjoint r) => r -> Matrix Two Two (Cplx r)
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.
Type-level representation of zero.
Nat Zero | |
(Ring a, Eq a, Adjoint a) => ToClifford (SO3 a) | |
RootHalfRing a => FromGates (SO3 a) | |
(RootHalfRing a, ComplexRing a) => FromGates (U2 a) | |
ToQOmega a => ToGates (SO3 a) | |
ToQOmega a => ToGates (U2 a) |
Type-level representation of successor.
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
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.
A type class for the natural numbers. The members are exactly the type-level natural numbers.
Return a term-level natural number corresponding to this type-level natural number.
Return a term-level integer corresponding to this type-level natural number. The argument is just a dummy argument and is not evaluated.
Fixed-length vectors
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.
vector_singleton :: a -> Vector One aSource
Construct a vector of length 1.
vector_length :: Nat n => Vector n a -> IntegerSource
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 cSource
Zip two equal length lists.
vector_map :: (a -> b) -> Vector n a -> Vector n bSource
Map a function over a fixed-length list.
vector_enum :: (Num a, Nat n) => Vector n aSource
Create the vector (0, 1, …, n-1).
vector_of_function :: (Num a, Nat n) => (a -> b) -> Vector n bSource
Create the vector (f(0), f(1), …, f(n-1)).
vector :: Nat n => [a] -> Vector n aSource
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 -> aSource
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 aSource
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 -> aSource
Left strict fold over a fixed-length list.
vector_foldr :: (a -> b -> b) -> b -> Vector n a -> bSource
Right fold over a fixed-length list.
vector_tail :: Vector (Succ n) a -> Vector n aSource
Return the tail of a fixed-length list. Note that the type system ensures that this never fails.
vector_head :: Vector (Succ n) a -> aSource
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) aSource
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
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.
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 aSource
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 aSource
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 bSource
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 bSource
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 aSource
Multiplication of a scalar and an m×n-matrix.
scalardiv :: Fractional a => Matrix m n a -> a -> Matrix m n aSource
Division of an m×n-matrix by a scalar.
(.*.) :: (Num a, Nat m) => Matrix m n a -> Matrix n p a -> Matrix m p aSource
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 aSource
Return the 0 matrix of the given dimension.
matrix_transpose :: Nat m => Matrix m n a -> Matrix n m aSource
Take the transpose of an m×n-matrix.
adjoint :: (Nat m, Adjoint a) => Matrix m n a -> Matrix n m aSource
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 -> aSource
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.
hs_sqnorm :: (Ring a, Adjoint a, Nat n) => Matrix n m a -> aSource
Return the square of the Hilbert-Schmidt norm of an m×n-matrix, defined by ‖M‖² = tr M†M.
Operations on block matrices
stack_vertical :: Matrix m n a -> Matrix p n a -> Matrix (m `Plus` p) n aSource
Stack matrices vertically.
stack_horizontal :: Matrix m n a -> Matrix m p a -> Matrix m (n `Plus` p) aSource
Stack matrices horizontally.
tensor_vertical :: (Num a, Nat n) => Vector p a -> Matrix m n a -> Matrix (p `Times` m) n aSource
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 aSource
Vertically concatenate a vector of matrices.
tensor_horizontal :: (Num a, Nat m) => Vector p a -> Matrix m n a -> Matrix m (p `Times` n) aSource
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) aSource
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) aSource
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) aSource
Form a diagonal block matrix.
matrix_controlled :: (Eq a, Num a, Nat n) => Matrix n n a -> Matrix (n `Plus` n) (n `Plus` n) aSource
Form a controlled gate.
Constructors and destructors
matrix_of_columns :: (Nat n, Nat m) => [[a]] -> Matrix n m aSource
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 aSource
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.
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 aSource
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 aSource
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 aSource
A convenience constructor for 4×4-matrices. The arguments are by rows.
column3 :: (a, a, a) -> Matrix Three One aSource
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 aSource
A convenience constructor for turning a vector into a column matrix.