hmatrix-0.16.0.3: Numeric Linear Algebra

Copyright(c) Alberto Ruiz 2014
LicenseBSD3
MaintainerAlberto Ruiz
Stabilityprovisional
Safe HaskellNone
LanguageHaskell98

Numeric.LinearAlgebra.Data

Contents

Description

Basic data processing.

Synopsis

Vector

1D arrays are storable vectors from the vector package.

vector :: [] -> Vector Source

create a real vector

>>> vector [1..5]
fromList [1.0,2.0,3.0,4.0,5.0]

(|>) :: Storable a => Int -> [a] -> Vector a infixl 9 Source

Create a vector from a list of elements and explicit dimension. The input list is explicitly truncated if it is too long, so it may safely be used, for instance, with infinite lists.

>>> 5 |> [1..]
fromList [1.0,2.0,3.0,4.0,5.0]

Matrix

matrix Source

Arguments

:: Int

columns

-> []

elements

-> Matrix  

create a real matrix

>>> matrix 5 [1..15]
(3><5)
 [  1.0,  2.0,  3.0,  4.0,  5.0
 ,  6.0,  7.0,  8.0,  9.0, 10.0
 , 11.0, 12.0, 13.0, 14.0, 15.0 ]

(><) :: Storable a => Int -> Int -> [a] -> Matrix a Source

create a general matrix

>>> (2><3) [2, 4, 7+2*𝑖,   -3, 11, 0]
(2><3)
 [       2.0 :+ 0.0,  4.0 :+ 0.0, 7.0 :+ 2.0
 , (-3.0) :+ (-0.0), 11.0 :+ 0.0, 0.0 :+ 0.0 ]

The input list is explicitly truncated, so that it can safely be used with lists that are too long (like infinite lists).

>>> (2><3)[1..]
(2><3)
 [ 1.0, 2.0, 3.0
 , 4.0, 5.0, 6.0 ]

This is the format produced by the instances of Show (Matrix a), which can also be used for input.

tr :: Transposable m mt => m -> mt Source

(conjugate) transpose

Indexing

size :: Container c t => c t -> IndexOf c Source

>>> size $ fromList[1..10::Double]
10
>>> size $ (2><5)[1..10::Double]
(2,5)

class Indexable c t | c -> t, t -> c where Source

>>> vect [1..10] ! 3
4.0
>>> mat 5 [1..15] ! 1
fromList [6.0,7.0,8.0,9.0,10.0]
>>> mat 5 [1..15] ! 1 ! 3
9.0

Methods

(!) :: c -> Int -> t infixl 9 Source

Construction

scalar :: Container c e => e -> c e Source

create a structure with a single element

>>> let v = fromList [1..3::Double]
>>> v / scalar (norm2 v)
fromList [0.2672612419124244,0.5345224838248488,0.8017837257372732]

class Konst e d c | d -> c, c -> d where Source

Methods

konst :: e -> d -> c e Source

>>> konst 7 3 :: Vector Float
fromList [7.0,7.0,7.0]
>>> konst i (3::Int,4::Int)
(3><4)
 [ 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0
 , 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0
 , 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0 ]

class Build d f c e | d -> c, c -> d, f -> e, f -> d, f -> c, c e -> f, d e -> f where Source

Methods

build :: d -> f -> c e Source

>>> build 5 (**2) :: Vector Double
fromList [0.0,1.0,4.0,9.0,16.0]

Hilbert matrix of order N:

>>> let hilb n = build (n,n) (\i j -> 1/(i+j+1)) :: Matrix Double
>>> putStr . dispf 2 $ hilb 3
3x3
1.00  0.50  0.33
0.50  0.33  0.25
0.33  0.25  0.20

Instances

Container Vector e => Build Int (e -> e) Vector e 
Container Matrix e => Build (Int, Int) (e -> e -> e) Matrix e 

assoc Source

Arguments

:: Container c e 
=> IndexOf c

size

-> e

default value

-> [(IndexOf c, e)]

association list

-> c e

result

Create a structure from an association list

>>> assoc 5 0 [(3,7),(1,4)] :: Vector Double
fromList [0.0,4.0,0.0,7.0,0.0]
>>> assoc (2,3) 0 [((0,2),7),((1,0),2*i-3)] :: Matrix (Complex Double)
(2><3)
 [    0.0 :+ 0.0, 0.0 :+ 0.0, 7.0 :+ 0.0
 , (-3.0) :+ 2.0, 0.0 :+ 0.0, 0.0 :+ 0.0 ]

accum Source

Arguments

:: Container c e 
=> c e

initial structure

-> (e -> e -> e)

update function

-> [(IndexOf c, e)]

association list

-> c e

result

Modify a structure using an update function

>>> accum (ident 5) (+) [((1,1),5),((0,3),3)] :: Matrix Double
(5><5)
 [ 1.0, 0.0, 0.0, 3.0, 0.0
 , 0.0, 6.0, 0.0, 0.0, 0.0
 , 0.0, 0.0, 1.0, 0.0, 0.0
 , 0.0, 0.0, 0.0, 1.0, 0.0
 , 0.0, 0.0, 0.0, 0.0, 1.0 ]

computation of histogram:

>>> accum (konst 0 7) (+) (map (flip (,) 1) [4,5,4,1,5,2,5]) :: Vector Double
fromList [0.0,1.0,1.0,0.0,2.0,3.0,0.0]

linspace :: Container Vector e => Int -> (e, e) -> Vector e Source

Creates a real vector containing a range of values:

>>> linspace 5 (-3,7::Double)
fromList [-3.0,-0.5,2.0,4.5,7.0]@
>>> linspace 5 (8,2+i) :: Vector (Complex Double)
fromList [8.0 :+ 0.0,6.5 :+ 0.25,5.0 :+ 0.5,3.5 :+ 0.75,2.0 :+ 1.0]

Logarithmic spacing can be defined as follows:

logspace n (a,b) = 10 ** linspace n (a,b)

Diagonal

ident :: (Num a, Element a) => Int -> Matrix a Source

creates the identity matrix of given dimension

diag :: (Num a, Element a) => Vector a -> Matrix a Source

Creates a square matrix with a given diagonal.

diagl :: [Double] -> Matrix Double Source

create a real diagonal matrix from a list

>>> diagl [1,2,3]
(3><3)
 [ 1.0, 0.0, 0.0
 , 0.0, 2.0, 0.0
 , 0.0, 0.0, 3.0 ]

diagRect :: Storable t => t -> Vector t -> Int -> Int -> Matrix t Source

creates a rectangular diagonal matrix:

>>> diagRect 7 (fromList [10,20,30]) 4 5 :: Matrix Double
(4><5)
 [ 10.0,  7.0,  7.0, 7.0, 7.0
 ,  7.0, 20.0,  7.0, 7.0, 7.0
 ,  7.0,  7.0, 30.0, 7.0, 7.0
 ,  7.0,  7.0,  7.0, 7.0, 7.0 ]

takeDiag :: Element t => Matrix t -> Vector t Source

extracts the diagonal from a rectangular matrix

Data manipulation

fromList :: Storable a => [a] -> Vector a

O(n) Convert a list to a vector

toList :: Storable a => Vector a -> [a] Source

extracts the Vector elements to a list

>>> toList (linspace 5 (1,10))
[1.0,3.25,5.5,7.75,10.0]

subVector Source

Arguments

:: Storable t 
=> Int

index of the starting element

-> Int

number of elements to extract

-> Vector t

source

-> Vector t

result

takes a number of consecutive elements from a Vector

>>> subVector 2 3 (fromList [1..10])
fromList [3.0,4.0,5.0]

takesV :: Storable t => [Int] -> Vector t -> [Vector t] Source

Extract consecutive subvectors of the given sizes.

>>> takesV [3,4] (linspace 10 (1,10::Double))
[fromList [1.0,2.0,3.0],fromList [4.0,5.0,6.0,7.0]]

vjoin :: Storable t => [Vector t] -> Vector t Source

concatenate a list of vectors

>>> vjoin [fromList [1..5::Double], konst 1 3]
fromList [1.0,2.0,3.0,4.0,5.0,1.0,1.0,1.0]

flatten :: Element t => Matrix t -> Vector t Source

Creates a vector by concatenation of rows. If the matrix is ColumnMajor, this operation requires a transpose.

>>> flatten (ident 3)
fromList [1.0,0.0,0.0,0.0,1.0,0.0,0.0,0.0,1.0]

reshape :: Storable t => Int -> Vector t -> Matrix t Source

Creates a matrix from a vector by grouping the elements in rows with the desired number of columns. (GNU-Octave groups by columns. To do it you can define reshapeF r = trans . reshape r where r is the desired number of rows.)

>>> reshape 4 (fromList [1..12])
(3><4)
 [ 1.0,  2.0,  3.0,  4.0
 , 5.0,  6.0,  7.0,  8.0
 , 9.0, 10.0, 11.0, 12.0 ]

asRow :: Storable a => Vector a -> Matrix a Source

creates a 1-row matrix from a vector

>>> asRow (fromList [1..5])
 (1><5)
  [ 1.0, 2.0, 3.0, 4.0, 5.0 ]

asColumn :: Storable a => Vector a -> Matrix a Source

creates a 1-column matrix from a vector

>>> asColumn (fromList [1..5])
(5><1)
 [ 1.0
 , 2.0
 , 3.0
 , 4.0
 , 5.0 ]

row :: [Double] -> Matrix Double Source

create a single row real matrix from a list

col :: [Double] -> Matrix Double Source

create a single column real matrix from a list

fromRows :: Element t => [Vector t] -> Matrix t Source

Create a matrix from a list of vectors. All vectors must have the same dimension, or dimension 1, which is are automatically expanded.

toRows :: Element t => Matrix t -> [Vector t] Source

extracts the rows of a matrix as a list of vectors

fromColumns :: Element t => [Vector t] -> Matrix t Source

Creates a matrix from a list of vectors, as columns

toColumns :: Element t => Matrix t -> [Vector t] Source

Creates a list of vectors from the columns of a matrix

fromLists :: Element t => [[t]] -> Matrix t Source

Creates a Matrix from a list of lists (considered as rows).

>>> fromLists [[1,2],[3,4],[5,6]]
(3><2)
 [ 1.0, 2.0
 , 3.0, 4.0
 , 5.0, 6.0 ]

toLists :: Element t => Matrix t -> [[t]] Source

the inverse of fromLists

takeRows :: Element t => Int -> Matrix t -> Matrix t Source

Creates a matrix with the first n rows of another matrix

dropRows :: Element t => Int -> Matrix t -> Matrix t Source

Creates a copy of a matrix without the first n rows

takeColumns :: Element t => Int -> Matrix t -> Matrix t Source

Creates a matrix with the first n columns of another matrix

dropColumns :: Element t => Int -> Matrix t -> Matrix t Source

Creates a copy of a matrix without the first n columns

subMatrix Source

Arguments

:: Element a 
=> (Int, Int)

(r0,c0) starting position

-> (Int, Int)

(rt,ct) dimensions of submatrix

-> Matrix a

input matrix

-> Matrix a

result

Extracts a submatrix from a matrix.

(?) :: Element t => Matrix t -> [Int] -> Matrix t infixl 9 Source

extract rows

>>> (20><4) [1..] ? [2,1,1]
(3><4)
 [ 9.0, 10.0, 11.0, 12.0
 , 5.0,  6.0,  7.0,  8.0
 , 5.0,  6.0,  7.0,  8.0 ]

¿ :: Element t => Matrix t -> [Int] -> Matrix t infixl 9 Source

extract columns

(unicode 0x00bf, inverted question mark, Alt-Gr ?)

>>> (3><4) [1..] ¿ [3,0]
(3><2)
 [  4.0, 1.0
 ,  8.0, 5.0
 , 12.0, 9.0 ]

fliprl :: Element t => Matrix t -> Matrix t Source

Reverse columns

flipud :: Element t => Matrix t -> Matrix t Source

Reverse rows

Block matrix

fromBlocks :: Element t => [[Matrix t]] -> Matrix t Source

Create a matrix from blocks given as a list of lists of matrices.

Single row-column components are automatically expanded to match the corresponding common row and column:

disp = putStr . dispf 2
>>> disp $ fromBlocks [[ident 5, 7, row[10,20]], [3, diagl[1,2,3], 0]]
8x10
1  0  0  0  0  7  7  7  10  20
0  1  0  0  0  7  7  7  10  20
0  0  1  0  0  7  7  7  10  20
0  0  0  1  0  7  7  7  10  20
0  0  0  0  1  7  7  7  10  20
3  3  3  3  3  1  0  0   0   0
3  3  3  3  3  0  2  0   0   0
3  3  3  3  3  0  0  3   0   0

(¦) :: Matrix Double -> Matrix Double -> Matrix Double infixl 3 Source

horizontal concatenation of real matrices

(unicode 0x00a6, broken bar)

>>> ident 3 ¦ konst 7 (3,4)
(3><7)
 [ 1.0, 0.0, 0.0, 7.0, 7.0, 7.0, 7.0
 , 0.0, 1.0, 0.0, 7.0, 7.0, 7.0, 7.0
 , 0.0, 0.0, 1.0, 7.0, 7.0, 7.0, 7.0 ]

—— :: Matrix Double -> Matrix Double -> Matrix Double infixl 2 Source

vertical concatenation of real matrices

(unicode 0x2014, em dash)

diagBlock :: (Element t, Num t) => [Matrix t] -> Matrix t Source

create a block diagonal matrix

>>> disp 2 $ diagBlock [konst 1 (2,2), konst 2 (3,5), col [5,7]]
7x8
1  1  0  0  0  0  0  0
1  1  0  0  0  0  0  0
0  0  2  2  2  2  2  0
0  0  2  2  2  2  2  0
0  0  2  2  2  2  2  0
0  0  0  0  0  0  0  5
0  0  0  0  0  0  0  7
>>> diagBlock [(0><4)[], konst 2 (2,3)]  :: Matrix Double
(2><7)
 [ 0.0, 0.0, 0.0, 0.0, 2.0, 2.0, 2.0
 , 0.0, 0.0, 0.0, 0.0, 2.0, 2.0, 2.0 ]

repmat :: Element t => Matrix t -> Int -> Int -> Matrix t Source

creates matrix by repetition of a matrix a given number of rows and columns

>>> repmat (ident 2) 2 3
(4><6)
 [ 1.0, 0.0, 1.0, 0.0, 1.0, 0.0
 , 0.0, 1.0, 0.0, 1.0, 0.0, 1.0
 , 1.0, 0.0, 1.0, 0.0, 1.0, 0.0
 , 0.0, 1.0, 0.0, 1.0, 0.0, 1.0 ]

toBlocks :: Element t => [Int] -> [Int] -> Matrix t -> [[Matrix t]] Source

Partition a matrix into blocks with the given numbers of rows and columns. The remaining rows and columns are discarded.

toBlocksEvery :: Element t => Int -> Int -> Matrix t -> [[Matrix t]] Source

Fully partition a matrix into blocks of the same size. If the dimensions are not a multiple of the given size the last blocks will be smaller.

Mapping functions

conj :: Container c e => c e -> c e Source

complex conjugate

cmap :: (Element b, Container c e) => (e -> b) -> c e -> c b Source

like fmap (cannot implement instance Functor because of Element class constraint)

step :: (RealElement e, Container c e) => c e -> c e Source

A more efficient implementation of cmap (\x -> if x>0 then 1 else 0)

>>> step $ linspace 5 (-1,1::Double)
5 |> [0.0,0.0,0.0,1.0,1.0]

cond Source

Arguments

:: (RealElement e, Container c e) 
=> c e

a

-> c e

b

-> c e

l

-> c e

e

-> c e

g

-> c e

result

Element by element version of case compare a b of {LT -> l; EQ -> e; GT -> g}.

Arguments with any dimension = 1 are automatically expanded:

>>> cond ((1><4)[1..]) ((3><1)[1..]) 0 100 ((3><4)[1..]) :: Matrix Double
(3><4)
[ 100.0,   2.0,   3.0,  4.0
,   0.0, 100.0,   7.0,  8.0
,   0.0,   0.0, 100.0, 12.0 ]

Find elements

find :: Container c e => (e -> Bool) -> c e -> [IndexOf c] Source

Find index of elements which satisfy a predicate

>>> find (>0) (ident 3 :: Matrix Double)
[(0,0),(1,1),(2,2)]

maxIndex :: Container c e => c e -> IndexOf c Source

index of maximum element

minIndex :: Container c e => c e -> IndexOf c Source

index of minimum element

maxElement :: Container c e => c e -> e Source

value of maximum element

minElement :: Container c e => c e -> e Source

value of minimum element

atIndex :: Container c e => c e -> IndexOf c -> e Source

indexing function

Sparse

IO

disp :: Int -> Matrix Double -> IO () Source

print a real matrix with given number of digits after the decimal point

>>> disp 5 $ ident 2 / 3
2x2
0.33333  0.00000
0.00000  0.33333

loadMatrix :: FilePath -> IO (Matrix Double) Source

load a matrix from an ASCII file formatted as a 2D table.

saveMatrix Source

Arguments

:: FilePath 
-> String

"printf" format (e.g. "%.2f", "%g", etc.)

-> Matrix Double 
-> IO () 

save a matrix as a 2D ASCII table

latexFormat Source

Arguments

:: String

type of braces: "matrix", "bmatrix", "pmatrix", etc.

-> String

Formatted matrix, with elements separated by spaces and newlines

-> String 

Tool to display matrices with latex syntax.

>>> latexFormat "bmatrix" (dispf 2 $ ident 2)
"\\begin{bmatrix}\n1  &  0\n\\\\\n0  &  1\n\\end{bmatrix}"

dispf :: Int -> Matrix Double -> String Source

Show a matrix with a given number of decimal places.

>>> dispf 2 (1/3 + ident 3)
"3x3\n1.33  0.33  0.33\n0.33  1.33  0.33\n0.33  0.33  1.33\n"
>>> putStr . dispf 2 $ (3><4)[1,1.5..]
3x4
1.00  1.50  2.00  2.50
3.00  3.50  4.00  4.50
5.00  5.50  6.00  6.50
>>> putStr . unlines . tail . lines . dispf 2 . asRow $ linspace 10 (0,1)
0.00  0.11  0.22  0.33  0.44  0.56  0.67  0.78  0.89  1.00

disps :: Int -> Matrix Double -> String Source

Show a matrix with "autoscaling" and a given number of decimal places.

>>> putStr . disps 2 $ 120 * (3><4) [1..]
3x4  E3
 0.12  0.24  0.36  0.48
 0.60  0.72  0.84  0.96
 1.08  1.20  1.32  1.44

dispcf :: Int -> Matrix (Complex Double) -> String Source

Pretty print a complex matrix with at most n decimal digits.

format :: Element t => String -> (t -> String) -> Matrix t -> String Source

Creates a string from a matrix given a separator and a function to show each entry. Using this function the user can easily define any desired display function:

import Text.Printf(printf)
disp = putStr . format "  " (printf "%.2f")

Conversion

class Convert t where Source

Methods

real :: Container c t => c (RealOf t) -> c t Source

complex :: Container c t => c t -> c (ComplexOf t) Source

single :: Container c t => c t -> c (SingleOf t) Source

double :: Container c t => c t -> c (DoubleOf t) Source

toComplex :: (Container c t, RealElement t) => (c t, c t) -> c (Complex t) Source

fromComplex :: (Container c t, RealElement t) => c (Complex t) -> (c t, c t) Source

Misc

arctan2 :: Container c e => c e -> c e -> c e Source

separable :: Element t => (Vector t -> Vector t) -> Matrix t -> Matrix t Source

matrix computation implemented as separated vector operations by rows and columns.

data Matrix t Source

Matrix representation suitable for BLAS/LAPACK computations.

The elements are stored in a continuous memory array.

data GMatrix Source

General matrix with specialized internal representations for dense, sparse, diagonal, banded, and constant elements.

>>> let m = mkSparse [((0,999),1.0),((1,1999),2.0)]
>>> m
SparseR {gmCSR = CSR {csrVals = fromList [1.0,2.0],
                      csrCols = fromList [1000,2000],
                      csrRows = fromList [1,2,3],
                      csrNRows = 2,
                      csrNCols = 2000},
                      nRows = 2,
                      nCols = 2000}
>>> let m = mkDense (mat 2 [1..4])
>>> m
Dense {gmDense = (2><2)
 [ 1.0, 2.0
 , 3.0, 4.0 ], nRows = 2, nCols = 2}