hmatrix-0.15.2.1: Linear algebra and numerical computation

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

Numeric.Container

Contents

Description

Basic numeric operations on Vector and Matrix, including conversion routines.

The Container class is used to define optimized generic functions which work on Vector and Matrix with real or complex elements.

Some of these functions are also available in the instances of the standard numeric Haskell classes provided by Numeric.LinearAlgebra.

Synopsis

Basic functions

constant :: Element a => a -> Int -> Vector a Source

creates a vector with a given number of equal components:

> constant 2 7
7 |> [2.0,2.0,2.0,2.0,2.0,2.0,2.0]

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

Creates a real vector containing a range of values:

> linspace 5 (-3,7)
5 |> [-3.0,-0.5,2.0,4.5,7.0]

Logarithmic spacing can be defined as follows:

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

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

Creates a square matrix with a given diagonal.

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

creates the identity matrix of given dimension

ctrans :: (Container Vector e, Element e) => Matrix e -> Matrix e Source

conjugate transpose

Generic operations

class (Complexable c, Fractional e, Element e) => Container c e where Source

Basic element-by-element functions for numeric containers

Methods

scalar :: e -> c e Source

create a structure with a single element

conj :: c e -> c e Source

complex conjugate

scale :: e -> c e -> c e Source

scaleRecip :: e -> c e -> c e Source

scale the element by element reciprocal of the object:

scaleRecip 2 (fromList [5,i]) == 2 |> [0.4 :+ 0.0,0.0 :+ (-2.0)]

addConstant :: e -> c e -> c e Source

add :: c e -> c e -> c e Source

sub :: c e -> c e -> c e Source

mul :: c e -> c e -> c e Source

element by element multiplication

divide :: c e -> c e -> c e Source

element by element division

equal :: c e -> c e -> Bool Source

arctan2 :: c e -> c e -> c e Source

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

cannot implement instance Functor because of Element class constraint

konst :: e -> IndexOf c -> c e Source

constant structure of given size

build :: IndexOf c -> ArgOf c e -> c e Source

create a structure using a function

Hilbert matrix of order N:

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

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

indexing function

minIndex :: c e -> IndexOf c Source

index of min element

maxIndex :: c e -> IndexOf c Source

index of max element

minElement :: c e -> e Source

value of min element

maxElement :: c e -> e Source

value of max element

sumElements :: c e -> e Source

the sum of elements (faster than using fold)

prodElements :: c e -> e Source

the product of elements (faster than using fold)

step :: RealElement 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 
=> 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 :: (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)]

assoc Source

Arguments

:: IndexOf c

size

-> e

default value

-> [(IndexOf c, e)]

association list

-> c e

result

Create a structure from an association list

> assoc 5 0 [(2,7),(1,3)] :: Vector Double
 5 |> [0.0,3.0,7.0,0.0,0.0]

accum Source

Arguments

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

Matrix product

class Element e => Product e where Source

Matrix product and related functions

Methods

multiply :: Matrix e -> Matrix e -> Matrix e Source

matrix product

dot :: Vector e -> Vector e -> e Source

dot (inner) product

absSum :: Vector e -> RealOf e Source

sum of absolute value of elements (differs in complex case from norm1)

norm1 :: Vector e -> RealOf e Source

sum of absolute value of elements

norm2 :: Vector e -> RealOf e Source

euclidean norm

normInf :: Vector e -> RealOf e Source

element of maximum magnitude

optimiseMult :: Product t => [Matrix t] -> Matrix t Source

Provide optimal association order for a chain of matrix multiplications and apply the multiplications.

The algorithm is the well-known O(n^3) dynamic programming algorithm that builds a pyramid of optimal associations.

m1, m2, m3, m4 :: Matrix Double
m1 = (10><15) [1..]
m2 = (15><20) [1..]
m3 = (20><5) [1..]
m4 = (5><10) [1..]
>>> optimiseMult [m1,m2,m3,m4]

will perform ((m1 multiply (m2 multiply m3)) multiply m4)

The naive left-to-right multiplication would take 4500 scalar multiplications whereas the optimised version performs 2750 scalar multiplications. The complexity in this case is 32 (= 4^3/2) * (2 comparisons, 3 scalar multiplications, 3 scalar additions, 5 lookups, 2 updates) + a constant (= three table allocations)

mXm :: Product t => Matrix t -> Matrix t -> Matrix t Source

mXv :: Product t => Matrix t -> Vector t -> Vector t Source

vXm :: Product t => Vector t -> Matrix t -> Vector t Source

(<.>) :: Product t => Vector t -> Vector t -> t infixl 7 Source

Dot product: u <.> v = dot u v

class Mul a b c | a b -> c where Source

Methods

(<>) :: Product t => a t -> b t -> c t infixl 7 Source

Matrix-matrix, matrix-vector, and vector-matrix products.

class LSDiv b c | b -> c, c -> b where Source

Methods

(<\>) :: Field t => Matrix t -> b t -> c t infixl 7 Source

least squares solution of a linear system, similar to the \ operator of Matlab/Octave (based on linearSolveSVD)

outer :: Product t => Vector t -> Vector t -> Matrix t Source

Outer product of two vectors.

> fromList [1,2,3] `outer` fromList [5,2,3]
(3><3)
 [  5.0, 2.0, 3.0
 , 10.0, 4.0, 6.0
 , 15.0, 6.0, 9.0 ]

kronecker :: Product t => Matrix t -> Matrix t -> Matrix t Source

Kronecker product of two matrices.

m1=(2><3)
 [ 1.0,  2.0, 0.0
 , 0.0, -1.0, 3.0 ]
m2=(4><3)
 [  1.0,  2.0,  3.0
 ,  4.0,  5.0,  6.0
 ,  7.0,  8.0,  9.0
 , 10.0, 11.0, 12.0 ]
> kronecker m1 m2
(8><9)
 [  1.0,  2.0,  3.0,   2.0,   4.0,   6.0,  0.0,  0.0,  0.0
 ,  4.0,  5.0,  6.0,   8.0,  10.0,  12.0,  0.0,  0.0,  0.0
 ,  7.0,  8.0,  9.0,  14.0,  16.0,  18.0,  0.0,  0.0,  0.0
 , 10.0, 11.0, 12.0,  20.0,  22.0,  24.0,  0.0,  0.0,  0.0
 ,  0.0,  0.0,  0.0,  -1.0,  -2.0,  -3.0,  3.0,  6.0,  9.0
 ,  0.0,  0.0,  0.0,  -4.0,  -5.0,  -6.0, 12.0, 15.0, 18.0
 ,  0.0,  0.0,  0.0,  -7.0,  -8.0,  -9.0, 21.0, 24.0, 27.0
 ,  0.0,  0.0,  0.0, -10.0, -11.0, -12.0, 30.0, 33.0, 36.0 ]

Random numbers

data RandDist Source

Constructors

Uniform

uniform distribution in [0,1)

Gaussian

normal distribution with mean zero and standard deviation one

Instances

randomVector Source

Arguments

:: Int

seed

-> RandDist

distribution

-> Int

vector size

-> Vector Double 

Obtains a vector of pseudorandom elements from the the mt19937 generator in GSL, with a given seed. Use randomIO to get a random seed.

gaussianSample Source

Arguments

:: Seed 
-> Int

number of rows

-> Vector Double

mean vector

-> Matrix Double

covariance matrix

-> Matrix Double

result

Obtains a matrix whose rows are pseudorandom samples from a multivariate Gaussian distribution.

uniformSample Source

Arguments

:: Seed 
-> Int

number of rows

-> [(Double, Double)]

ranges for each column

-> Matrix Double

result

Obtains a matrix whose rows are pseudorandom samples from a multivariate uniform distribution.

meanCov :: Matrix Double -> (Vector Double, Matrix Double) Source

Compute mean vector and covariance matrix of the rows of a matrix.

Element 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

class Complexable c Source

Structures that may contain complex numbers

Minimal complete definition

toComplex', fromComplex', comp', single', double'

class (Element t, Element (Complex t), RealFloat t) => RealElement t Source

Supported real types

type family RealOf x Source

Instances

type family SingleOf x Source

Instances

type family DoubleOf x Source

Instances

type family IndexOf c Source

Instances

type IndexOf Vector = Int 
type IndexOf Matrix = (Int, Int) 

Input / Output

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

Show a matrix with a given number of decimal places.

@disp = putStr . dispf 3

> disp (1/3 + ident 4) 4x4 1.333 0.333 0.333 0.333 0.333 1.333 0.333 0.333 0.333 0.333 1.333 0.333 0.333 0.333 0.333 1.333 @

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

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

@disp = putStr . disps 2

> disp $ 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.

vecdisp :: Element t => (Matrix t -> String) -> Vector t -> String Source

Show a vector using a function for showing matrices.

@disp = putStr . vecdisp (dispf 2)

> disp (linspace 10 (0,1)) 10 |> 0.00 0.11 0.22 0.33 0.44 0.56 0.67 0.78 0.89 1.00 @

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.

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")

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

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

saveMatrix Source

Arguments

:: FilePath 
-> String

format (%f, %g, %e)

-> Matrix Double 
-> IO () 

Saves a matrix as 2D ASCII table.

fromFile :: FilePath -> (Int, Int) -> IO (Matrix Double) Source

Loads a matrix from an ASCII file (the number of rows and columns must be known in advance).

fileDimensions :: FilePath -> IO (Int, Int) Source

obtains the number of rows and columns in an ASCII data file (provisionally using unix's wc).

readMatrix :: String -> Matrix Double Source

reads a matrix from a string containing a table of numbers.

fscanfVector :: FilePath -> Int -> IO (Vector Double) Source

Loads a vector from an ASCII file (the number of elements must be known in advance).

fprintfVector :: FilePath -> String -> Vector Double -> IO () Source

Saves the elements of a vector, with a given format (%f, %e, %g), to an ASCII file.

freadVector :: FilePath -> Int -> IO (Vector Double) Source

Loads a vector from a binary file (the number of elements must be known in advance).

fwriteVector :: FilePath -> Vector Double -> IO () Source

Saves the elements of a vector to a binary file.

Experimental

build' :: Build f => BoundsOf f -> f -> ContainerOf f Source

konst' :: (Konst s, Element e) => e -> s -> ContainerOf' s e Source