hmatrix-0.20.2: Numeric Linear Algebra
Copyright(c) Alberto Ruiz 2014
LicenseBSD3
MaintainerAlberto Ruiz
Stabilityprovisional
Safe HaskellSafe-Inferred
LanguageHaskell2010

Numeric.LinearAlgebra.Devel

Description

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

Synopsis

FFI tools

See examples/devel in the repository.

class TransArray c where Source #

Associated Types

type Trans c b Source #

type TransRaw c b Source #

Methods

apply :: c -> (b -> IO r) -> Trans c b -> IO r infixl 1 Source #

applyRaw :: c -> (b -> IO r) -> TransRaw c b -> IO r infixl 1 Source #

Instances

Instances details
Storable t => TransArray (Matrix t) Source # 
Instance details

Defined in Internal.Matrix

Associated Types

type Trans (Matrix t) b Source #

type TransRaw (Matrix t) b Source #

Methods

apply :: Matrix t -> (b -> IO r) -> Trans (Matrix t) b -> IO r Source #

applyRaw :: Matrix t -> (b -> IO r) -> TransRaw (Matrix t) b -> IO r Source #

Storable t => TransArray (Vector t) Source # 
Instance details

Defined in Internal.Devel

Associated Types

type Trans (Vector t) b Source #

type TransRaw (Vector t) b Source #

Methods

apply :: Vector t -> (b -> IO r) -> Trans (Vector t) b -> IO r Source #

applyRaw :: Vector t -> (b -> IO r) -> TransRaw (Vector t) b -> IO r Source #

data MatrixOrder Source #

Constructors

RowMajor 
ColumnMajor 

Instances

Instances details
Show MatrixOrder Source # 
Instance details

Defined in Internal.Matrix

Eq MatrixOrder Source # 
Instance details

Defined in Internal.Matrix

cmat :: Element t => Matrix t -> Matrix t Source #

fmat :: Element t => Matrix t -> Matrix t 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 ($))

(#|) :: IO CInt -> String -> IO () infixl 0 Source #

postfix error code check

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

access to Vector elements without range checking

atM' :: Storable t => Matrix t -> Int -> Int -> t Source #

fi :: Int -> CInt Source #

specialized fromIntegral

ti :: CInt -> Int Source #

specialized fromIntegral

ST

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

Mutable Vectors

data STVector s t Source #

newVector :: Storable t => t -> Int -> ST s (STVector s 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 s t -> ST s a Source #

Mutable Matrices

data STMatrix s t Source #

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

thawMatrix :: Element t => Matrix t -> ST s (STMatrix s 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 :: Element t => (Matrix t -> a) -> STMatrix s t -> ST s a Source #

mutable :: Element t => (forall s. (Int, Int) -> STMatrix s t -> ST s u) -> Matrix t -> (Matrix t, u) Source #

setMatrix :: Element t => STMatrix s t -> Int -> Int -> Matrix t -> ST s () Source #

rowOper :: (Num t, Element t) => RowOper t -> STMatrix s t -> ST s () Source #

gemmm :: Element t => t -> Slice s t -> t -> Slice s t -> Slice s t -> ST s () Source #

data Slice s t Source #

r0 c0 height width

Constructors

Slice (STMatrix s t) Int Int Int Int 

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 :: (Element a, Element 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

Instances details
Show CSR Source # 
Instance details

Defined in Internal.Sparse

Methods

showsPrec :: Int -> CSR -> ShowS #

show :: CSR -> String #

showList :: [CSR] -> ShowS #

mkCSR :: AssocMatrix -> CSR Source #

Produce a CSR sparse matrix from a association matrix.

impureCSR :: PrimMonad m => (forall x. (x -> (IndexOf Matrix, Double) -> m x) -> m x -> (x -> m CSR) -> r) -> r Source #

Produce a CSR sparse matrix by applying a generic folding function.

This allows one to build a CSR from an effectful streaming source when combined with libraries like pipes, io-streams, or streaming.

For example

impureCSR Pipes.Prelude.foldM :: PrimMonad m => Producer AssocEntry m () -> m CSR
impureCSR Streaming.Prelude.foldM :: PrimMonad m => Stream (Of AssocEntry) m r -> m (Of CSR r)

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

SparseC 

Fields

Diag 

Fields

Dense 

Fields

Instances

Instances details
Show GMatrix Source # 
Instance details

Defined in Internal.Sparse

Testable GMatrix Source # 
Instance details

Defined in Internal.CG

Methods

checkT :: GMatrix -> (Bool, IO ()) Source #

ioCheckT :: GMatrix -> IO (Bool, IO ()) Source #

Transposable GMatrix GMatrix Source # 
Instance details

Defined in Internal.Sparse

Misc

reorderVector Source #

Arguments

:: Element a 
=> Vector CInt

strides: array strides

-> Vector CInt

dims: array dimensions of new array v

-> Vector a

v: flattened input array

-> Vector a

v': flattened output array

Transpose an array with dimensions dims by making a copy using strides. For example, for an array with 3 indices, (reorderVector strides dims v) ! ((i * dims ! 1 + j) * dims ! 2 + k) == v ! (i * strides ! 0 + j * strides ! 1 + k * strides ! 2) This function is intended to be used internally by tensor libraries.