hmatrix-0.15.2.1: Linear algebra and numerical computation

Copyright(c) Alberto Ruiz 2007-10
LicenseGPL
MaintainerAlberto Ruiz <aruiz@um.es>
Stabilityprovisional
Safe HaskellNone
LanguageHaskell98

Data.Packed.Matrix

Description

A Matrix representation suitable for numerical computations using LAPACK and GSL.

This module provides basic functions for manipulation of structure.

Synopsis

Documentation

data Matrix t Source

Matrix representation suitable for GSL and LAPACK computations.

The elements are stored in a continuous memory array.

class Storable a => Element a Source

Supported matrix elements.

This class provides optimized internal operations for selected element types. It provides unoptimised defaults for any Storable type, so you can create instances simply as: instance Element Foo.

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

An easy way to create a matrix:

> (2><3)[1..6]
(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.

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

Example:

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

trans :: Matrix t -> Matrix t Source

Matrix transpose.

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 ]

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)
 9 |> [1.0,0.0,0.0,0.0,1.0,0.0,0.0,0.0,1.0]

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

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

creates a Matrix of the specified size using the supplied function to to map the row/column position to the value at that row/column position.

> buildMatrix 3 4 (\(r,c) -> fromIntegral r * fromIntegral c)
(3><4)
 [ 0.0, 0.0, 0.0, 0.0, 0.0
 , 0.0, 1.0, 2.0, 3.0, 4.0
 , 0.0, 2.0, 4.0, 6.0, 8.0]

Hilbert matrix of order N:

hilb n = buildMatrix n n (\(i,j)->1/(fromIntegral i + fromIntegral j +1))

(@@>) :: Storable t => Matrix t -> (Int, Int) -> t infixl 9 Source

Reads a matrix position.

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

creates a 1-row matrix from a vector

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

creates a 1-column matrix from a vector

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

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

Creates 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:

@> let disp = putStr . dispf 2 > let vector xs = fromList xs :: Vector Double > let diagl = diag . vector > let rowm = asRow . vector

> disp $ fromBlocks [[ident 5, 7, rowm[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@

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

create a block diagonal matrix

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.

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 :: Matrix Double
(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 ]

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

Reverse rows

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

Reverse 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.

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

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

rearranges the rows of a matrix according to the order given in a list of integers.

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

mapMatrix :: (Storable a, Storable b) => (a -> b) -> Matrix a -> Matrix b Source

mapMatrixWithIndex :: (Element a, Storable b) => ((Int, Int) -> a -> b) -> Matrix a -> Matrix b Source

ghci> mapMatrixWithIndex (\(i,j) v -> 100*v + 10*i + j) (ident 3:: Matrix Double)
(3><3)
 [ 100.0,   1.0,   2.0
 ,  10.0, 111.0,  12.0
 ,  20.0,  21.0, 122.0 ]

mapMatrixWithIndexM :: (Element a, Storable b, Monad m) => ((Int, Int) -> a -> m b) -> Matrix a -> m (Matrix b) Source

ghci> mapMatrixWithIndexM (\(i,j) v -> Just $ 100*v + 10*i + j) (ident 3:: Matrix Double)
Just (3><3)
 [ 100.0,   1.0,   2.0
 ,  10.0, 111.0,  12.0
 ,  20.0,  21.0, 122.0 ]

mapMatrixWithIndexM_ :: (Element a, Num a, Monad m) => ((Int, Int) -> a -> m ()) -> Matrix a -> m () Source

ghci> mapMatrixWithIndexM_ (\(i,j) v -> printf "m[%.0f,%.0f] = %.f\n" i j v :: IO()) ((2><3)[1 :: Double ..])
m[0,0] = 1
m[0,1] = 2
m[0,2] = 3
m[1,0] = 4
m[1,1] = 5
m[1,2] = 6

liftMatrix :: (Storable a, Storable b) => (Vector a -> Vector b) -> Matrix a -> Matrix b Source

application of a vector function on the flattened matrix elements

liftMatrix2 :: (Element t, Element a, Element b) => (Vector a -> Vector b -> Vector t) -> Matrix a -> Matrix b -> Matrix t Source

application of a vector function on the flattened matrices elements

liftMatrix2Auto :: (Element t, Element a, Element b) => (Vector a -> Vector b -> Vector t) -> Matrix a -> Matrix b -> Matrix t Source

A version of liftMatrix2 which automatically adapt matrices with a single row or column to match the dimensions of the other matrix.