hmatrix-0.1.0.0: Linear algebra and numerical computationsSource codeContentsIndex
Data.Packed.Internal.Matrix
Portabilityportable (uses FFI)
Stabilityprovisional
MaintainerAlberto Ruiz <aruiz@um.es>
Description
Internal matrix representation
Synopsis
data MatrixOrder
= RowMajor
| ColumnMajor
data Matrix t
= MC {
rows :: Int
cols :: Int
cdat :: Vector t
}
| MF {
rows :: Int
cols :: Int
fdat :: Vector t
}
trans :: Matrix t -> Matrix t
flatten :: Element t => Matrix t -> Vector t
type Mt t s = Int -> Int -> Ptr t -> s
toLists :: Element t => Matrix t -> [[t]]
fromRows :: Element t => [Vector t] -> Matrix t
toRows :: Element t => Matrix t -> [Vector t]
fromColumns :: Element t => [Vector t] -> Matrix t
toColumns :: Element t => Matrix t -> [Vector t]
(@@>) :: Storable t => Matrix t -> (Int, Int) -> t
reshape :: Element t => Int -> Vector t -> Matrix t
liftMatrix :: (Element a, Element b) => (Vector a -> Vector b) -> Matrix a -> Matrix b
liftMatrix2 :: (Element t, Element a, Element b) => (Vector a -> Vector b -> Vector t) -> Matrix a -> Matrix b -> Matrix t
compat :: Matrix a -> Matrix b -> Bool
class (Storable a, Floating a) => Element a where
constantD :: a -> Int -> Vector a
transdata :: Int -> Vector a -> Int -> Vector a
multiplyD :: Matrix a -> Matrix a -> Matrix a
subMatrixD :: (Int, Int) -> (Int, Int) -> Matrix a -> Matrix a
diagD :: Vector a -> Matrix a
(>|<) :: Element a => Int -> Int -> [a] -> Matrix a
transdataR :: Int -> Vector Double -> Int -> Vector Double
transdataC :: Int -> Vector (Complex Double) -> Int -> Vector (Complex Double)
ctransR :: TMM
ctransC :: TCMCM
cmultiplyR :: Int -> Int -> Int -> Ptr Double -> Int -> Int -> Int -> Ptr Double -> Int -> Int -> Ptr Double -> IO Int
cmultiplyC :: Int -> Int -> Int -> Ptr (Complex Double) -> Int -> Int -> Int -> Ptr (Complex Double) -> Int -> Int -> Ptr (Complex Double) -> IO Int
multiply' :: Element a => MatrixOrder -> Matrix a -> Matrix a -> Matrix a
multiply :: Element a => Matrix a -> Matrix a -> Matrix a
subMatrixR :: (Int, Int) -> (Int, Int) -> Matrix Double -> Matrix Double
c_submatrixR :: Int -> Int -> Int -> Int -> TMM
subMatrixC :: (Int, Int) -> (Int, Int) -> Matrix (Complex Double) -> Matrix (Complex Double)
subMatrix :: Element a => (Int, Int) -> (Int, Int) -> Matrix a -> Matrix a
diagR :: Vector Double -> Matrix Double
c_diagR :: TVM
diagC :: Vector (Complex Double) -> Matrix (Complex Double)
c_diagC :: TCVCM
diag :: Element a => Vector a -> Matrix a
constantR :: Double -> Int -> Vector Double
cconstantR :: Ptr Double -> TV
constantC :: Complex Double -> Int -> Vector (Complex Double)
cconstantC :: Ptr (Complex Double) -> TCV
constant :: Element a => a -> Int -> Vector a
conj :: Vector (Complex Double) -> Vector (Complex Double)
toComplex :: (Vector Double, Vector Double) -> Vector (Complex Double)
fromComplex :: Vector (Complex Double) -> (Vector Double, Vector Double)
comp :: Vector Double -> Vector (Complex Double)
fromFile :: FilePath -> (Int, Int) -> IO (Matrix Double)
c_gslReadMatrix :: Ptr CChar -> TM
Documentation
data MatrixOrder Source
Constructors
RowMajor
ColumnMajor
show/hide Instances
data Matrix t Source
Matrix representation suitable for GSL and LAPACK computations.
Constructors
MC
rows :: Int
cols :: Int
cdat :: Vector t
MF
rows :: Int
cols :: Int
fdat :: Vector t
show/hide Instances
trans :: Matrix t -> Matrix tSource
Matrix transpose.
flatten :: Element t => Matrix t -> Vector tSource

Creates a vector by concatenation of rows

> flatten (ident 3)
9 |> [1.0,0.0,0.0,0.0,1.0,0.0,0.0,0.0,1.0]
type Mt t s = Int -> Int -> Ptr t -> sSource
toLists :: Element t => Matrix t -> [[t]]Source
the inverse of Data.Packed.Matrix.fromLists
fromRows :: Element t => [Vector t] -> Matrix tSource
creates a Matrix from a list of vectors
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 tSource
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
(@@>) :: Storable t => Matrix t -> (Int, Int) -> tSource
Reads a matrix position.
reshape :: Element t => Int -> Vector t -> Matrix tSource

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 ]
liftMatrix :: (Element a, Element b) => (Vector a -> Vector b) -> Matrix a -> Matrix bSource
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 tSource
application of a vector function on the flattened matrices elements
compat :: Matrix a -> Matrix b -> BoolSource
class (Storable a, Floating a) => Element a whereSource
Optimized matrix computations are provided for elements in the Element class.
Methods
constantD :: a -> Int -> Vector aSource
transdata :: Int -> Vector a -> Int -> Vector aSource
multiplyD :: Matrix a -> Matrix a -> Matrix aSource
subMatrixDSource
:: (Int, Int)(r0,c0) starting position
-> (Int, Int)(rt,ct) dimensions of submatrix
-> Matrix a
-> Matrix a
diagD :: Vector a -> Matrix aSource
show/hide Instances
(>|<) :: Element a => Int -> Int -> [a] -> Matrix aSource
transdataR :: Int -> Vector Double -> Int -> Vector DoubleSource
transdataC :: Int -> Vector (Complex Double) -> Int -> Vector (Complex Double)Source
ctransR :: TMMSource
ctransC :: TCMCMSource
cmultiplyR :: Int -> Int -> Int -> Ptr Double -> Int -> Int -> Int -> Ptr Double -> Int -> Int -> Ptr Double -> IO IntSource
cmultiplyC :: Int -> Int -> Int -> Ptr (Complex Double) -> Int -> Int -> Int -> Ptr (Complex Double) -> Int -> Int -> Ptr (Complex Double) -> IO IntSource
multiply' :: Element a => MatrixOrder -> Matrix a -> Matrix a -> Matrix aSource
multiply :: Element a => Matrix a -> Matrix a -> Matrix aSource
matrix product
subMatrixR :: (Int, Int) -> (Int, Int) -> Matrix Double -> Matrix DoubleSource
extraction of a submatrix from a real matrix
c_submatrixR :: Int -> Int -> Int -> Int -> TMMSource
subMatrixC :: (Int, Int) -> (Int, Int) -> Matrix (Complex Double) -> Matrix (Complex Double)Source
extraction of a submatrix from a complex matrix
subMatrixSource
:: Element a
=> (Int, Int)(r0,c0) starting position
-> (Int, Int)(rt,ct) dimensions of submatrix
-> Matrix ainput matrix
-> Matrix aresult
Extracts a submatrix from a matrix.
diagR :: Vector Double -> Matrix DoubleSource
diagonal matrix from a real vector
c_diagR :: TVMSource
diagC :: Vector (Complex Double) -> Matrix (Complex Double)Source
diagonal matrix from a real vector
c_diagC :: TCVCMSource
diag :: Element a => Vector a -> Matrix aSource
creates a square matrix with the given diagonal
constantR :: Double -> Int -> Vector DoubleSource
cconstantR :: Ptr Double -> TVSource
constantC :: Complex Double -> Int -> Vector (Complex Double)Source
cconstantC :: Ptr (Complex Double) -> TCVSource
constant :: Element a => a -> Int -> Vector aSource

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]
conj :: Vector (Complex Double) -> Vector (Complex Double)Source
obtains the complex conjugate of a complex vector
toComplex :: (Vector Double, Vector Double) -> Vector (Complex Double)Source
creates a complex vector from vectors with real and imaginary parts
fromComplex :: Vector (Complex Double) -> (Vector Double, Vector Double)Source
the inverse of toComplex
comp :: Vector Double -> Vector (Complex Double)Source
converts a real vector into a complex representation (with zero imaginary parts)
fromFile :: FilePath -> (Int, Int) -> IO (Matrix Double)Source
loads a matrix efficiently from formatted ASCII text file (the number of rows and columns must be known in advance).
c_gslReadMatrix :: Ptr CChar -> TMSource
Produced by Haddock version 2.4.2