hmatrix-0.16.0.3: Numeric Linear Algebra

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

Numeric.LinearAlgebra.Devel

Contents

Description

The library can be easily extended using the tools in this module.

Synopsis

FFI helpers

Sample usage, to upload a perspective matrix to a shader.

 glUniformMatrix4fv 0 1 (fromIntegral gl_TRUE) `appMatrix` perspective 0.01 100 (pi/2) (4/3)

app :: (a -> b) -> a -> b infixl 1 Source

Only useful since it is left associated with a precedence of 1, unlike $, which is right associative. e.g.

someFunction
    `appMatrixLen` m
    `appVectorLen` v
    `app` other
    `app` arguments
    `app` go here

One could also write:

(someFunction 
    `appMatrixLen` m
    `appVectorLen` v) 
    other 
    arguments 
    (go here)

appVector :: Storable a => (Ptr a -> b) -> Vector a -> b infixl 1 Source

appVectorLen :: Storable a => (CInt -> Ptr a -> b) -> Vector a -> b Source

appMatrix :: Element a => (Ptr a -> b) -> Matrix a -> b infixl 1 Source

appMatrixLen :: Element a => (CInt -> CInt -> Ptr a -> b) -> Matrix a -> b Source

appMatrixRaw :: Storable a => (Ptr a -> b) -> Matrix a -> b infixl 1 Source

appMatrixRawLen :: Element a => (CInt -> CInt -> Ptr a -> b) -> Matrix a -> b Source

unsafeMatrixToVector :: Matrix a -> Vector a Source

This will disregard the order of the matrix, and simply return it as-is. If the order of the matrix is RowMajor, this function is identical to flatten.

FFI tools

Illustrative usage examples can be found in the examples/devel folder included in the package.

vec :: Storable t => Vector t -> (((CInt -> Ptr t -> t1) -> t1) -> IO b) -> IO b Source

mat :: Storable t => Matrix t -> (((CInt -> CInt -> Ptr t -> t1) -> t1) -> IO b) -> IO b Source

app1 :: f -> Adapt1 f t1 Source

app2 :: f -> Adapt2 f t1 r1 t2 Source

app3 :: f -> Adapt3 f t1 r1 t2 r2 t3 Source

app4 :: f -> Adapt4 f t1 r1 t2 r2 t3 r3 t4 Source

app5 :: f -> Adapt5 f t1 r1 t2 r2 t3 r3 t4 r4 t5 Source

app6 :: f -> Adapt6 f t1 r1 t2 r2 t3 r3 t4 r4 t5 r5 t6 Source

app7 :: f -> Adapt7 f t1 r1 t2 r2 t3 r3 t4 r4 t5 r5 t6 r6 t7 Source

app8 :: f -> Adapt8 f t1 r1 t2 r2 t3 r3 t4 r4 t5 r5 t6 r6 t7 r7 t8 Source

app9 :: f -> Adapt9 f t1 r1 t2 r2 t3 r3 t4 r4 t5 r5 t6 r6 t7 r7 t8 r8 t9 Source

app10 :: f -> Adapt10 f t1 r1 t2 r2 t3 r3 t4 r4 t5 r5 t6 r6 t7 r7 t8 r8 t9 r9 t10 Source

unsafeFromForeignPtr

Arguments

:: Storable a 
=> ForeignPtr a

pointer

-> Int

offset

-> Int

length

-> Vector a 

O(1) Create a vector from a ForeignPtr with an offset and a length.

The data may not be modified through the ForeignPtr afterwards.

If your offset is 0 it is more efficient to use unsafeFromForeignPtr0.

unsafeToForeignPtr :: Storable a => Vector a -> (ForeignPtr a, Int, Int)

O(1) Yield the underlying ForeignPtr together with the offset to the data and its length. The data may not be modified through the ForeignPtr.

check :: String -> IO CInt -> IO () Source

check the error code

(//) :: x -> (x -> y) -> y infixl 0 Source

postfix function application (flip ($))

at' :: Storable a => Vector a -> Int -> a Source

access to Vector elements without range checking

atM' :: Storable a => Matrix a -> Int -> Int -> a Source

fi :: Int -> CInt Source

specialized fromIntegral

ST

In-place manipulation inside the ST monad. See examples/inplace.hs in the distribution.

Mutable Vectors

data STVector s t Source

newVector :: Storable t => t -> Int -> ST s (STVector s t) Source

freezeVector :: Storable t => STVector s1 t -> ST s2 (Vector t) Source

runSTVector :: Storable t => (forall s. ST s (STVector s t)) -> Vector t Source

readVector :: Storable t => STVector s t -> Int -> ST s t Source

writeVector :: Storable t => STVector s t -> Int -> t -> ST s () Source

modifyVector :: Storable t => STVector s t -> Int -> (t -> t) -> ST s () Source

liftSTVector :: Storable t => (Vector t -> a) -> STVector s1 t -> ST s2 a Source

Mutable Matrices

data STMatrix s t Source

newMatrix :: Storable t => t -> Int -> Int -> ST s (STMatrix s t) Source

freezeMatrix :: Storable t => STMatrix s1 t -> ST s2 (Matrix t) Source

runSTMatrix :: Storable t => (forall s. ST s (STMatrix s t)) -> Matrix t Source

readMatrix :: Storable t => STMatrix s t -> Int -> Int -> ST s t Source

writeMatrix :: Storable t => STMatrix s t -> Int -> Int -> t -> ST s () Source

modifyMatrix :: Storable t => STMatrix s t -> Int -> Int -> (t -> t) -> ST s () Source

liftSTMatrix :: Storable t => (Matrix t -> a) -> STMatrix s1 t -> ST s2 a Source

Unsafe functions

unsafeWriteVector :: Storable t => STVector s t -> Int -> t -> ST s () Source

unsafeReadMatrix :: Storable t => STMatrix s t -> Int -> Int -> ST s t Source

unsafeWriteMatrix :: Storable t => STMatrix s t -> Int -> Int -> t -> ST s () Source

Special maps and zips

mapVectorWithIndex :: (Storable a, Storable b) => (Int -> a -> b) -> Vector a -> Vector b Source

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

zip for Vectors

zipVectorWith :: (Storable a, Storable b, Storable c) => (a -> b -> c) -> Vector a -> Vector b -> Vector c Source

zipWith for Vectors

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

unzip for Vectors

unzipVectorWith :: (Storable (a, b), Storable c, Storable d) => ((a, b) -> (c, d)) -> Vector (a, b) -> (Vector c, Vector d) Source

unzipWith for Vectors

mapVectorM :: (Storable a, Storable b, Monad m) => (a -> m b) -> Vector a -> m (Vector b) Source

monadic map over Vectors the monad m must be strict

mapVectorM_ :: (Storable a, Monad m) => (a -> m ()) -> Vector a -> m () Source

monadic map over Vectors

mapVectorWithIndexM :: (Storable a, Storable b, Monad m) => (Int -> a -> m b) -> Vector a -> m (Vector b) Source

monadic map over Vectors with the zero-indexed index passed to the mapping function the monad m must be strict

mapVectorWithIndexM_ :: (Storable a, Monad m) => (Int -> a -> m ()) -> Vector a -> m () Source

monadic map over Vectors with the zero-indexed index passed to the mapping function

foldLoop :: (Int -> t -> t) -> t -> Int -> t Source

foldVector :: Storable a => (a -> b -> b) -> b -> Vector a -> b Source

foldVectorG :: Storable t1 => (Int -> (Int -> t1) -> t -> t) -> t -> Vector t1 -> t Source

foldVectorWithIndex :: Storable a => (Int -> a -> b -> b) -> b -> Vector a -> b Source

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

>>> mapMatrixWithIndex (\\(i,j) v -> 100*v + 10*fromIntegral i + fromIntegral 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

>>> mapMatrixWithIndexM (\(i,j) v -> Just $ 100*v + 10*fromIntegral i + fromIntegral 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

>>> mapMatrixWithIndexM_ (\(i,j) v -> printf "m[%d,%d] = %.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.

Sparse representation

data CSR Source

Constructors

CSR 

Instances

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}

Constructors

SparseR 

Fields

gmCSR :: CSR
 
nRows :: Int
 
nCols :: Int
 
SparseC 

Fields

gmCSC :: CSC
 
nRows :: Int
 
nCols :: Int
 
Diag 

Fields

diagVals :: Vector Double
 
nRows :: Int
 
nCols :: Int
 
Dense 

Fields

gmDense :: Matrix Double
 
nRows :: Int
 
nCols :: Int
 

Misc