| Copyright | (c) Alberto Ruiz 2014 | 
|---|---|
| License | BSD3 | 
| Maintainer | Alberto Ruiz | 
| Stability | provisional | 
| Safe Haskell | None | 
| Language | Haskell98 | 
Numeric.LinearAlgebra.Devel
Contents
Description
The library can be easily extended using the tools in this module.
- createVector :: Storable a => Int -> IO (Vector a)
 - createMatrix :: Storable a => MatrixOrder -> Int -> Int -> IO (Matrix a)
 - class TransArray c where
 - data MatrixOrder
 - orderOf :: Matrix t -> MatrixOrder
 - cmat :: Element t => Matrix t -> Matrix t
 - fmat :: Element t => Matrix t -> Matrix t
 - matrixFromVector :: Storable t => MatrixOrder -> Int -> Int -> Vector t -> Matrix t
 - unsafeFromForeignPtr :: Storable a => ForeignPtr a -> Int -> Int -> Vector a
 - unsafeToForeignPtr :: Storable a => Vector a -> (ForeignPtr a, Int, Int)
 - check :: String -> IO CInt -> IO ()
 - (//) :: x -> (x -> y) -> y
 - (#|) :: IO CInt -> String -> IO ()
 - at' :: Storable a => Vector a -> Int -> a
 - atM' :: Storable t => Matrix t -> Int -> Int -> t
 - fi :: Int -> CInt
 - ti :: CInt -> Int
 - data STVector s t
 - newVector :: Storable t => t -> Int -> ST s (STVector s t)
 - thawVector :: Storable t => Vector t -> ST s (STVector s t)
 - freezeVector :: Storable t => STVector s t -> ST s (Vector t)
 - runSTVector :: Storable t => (forall s. ST s (STVector s t)) -> Vector t
 - readVector :: Storable t => STVector s t -> Int -> ST s t
 - writeVector :: Storable t => STVector s t -> Int -> t -> ST s ()
 - modifyVector :: Storable t => STVector s t -> Int -> (t -> t) -> ST s ()
 - liftSTVector :: Storable t => (Vector t -> a) -> STVector s t -> ST s a
 - data STMatrix s t
 - newMatrix :: Storable t => t -> Int -> Int -> ST s (STMatrix s t)
 - thawMatrix :: Element t => Matrix t -> ST s (STMatrix s t)
 - freezeMatrix :: Element t => STMatrix s t -> ST s (Matrix t)
 - runSTMatrix :: Storable t => (forall s. ST s (STMatrix s t)) -> Matrix t
 - readMatrix :: Storable t => STMatrix s t -> Int -> Int -> ST s t
 - writeMatrix :: Storable t => STMatrix s t -> Int -> Int -> t -> ST s ()
 - modifyMatrix :: Storable t => STMatrix s t -> Int -> Int -> (t -> t) -> ST s ()
 - liftSTMatrix :: Element t => (Matrix t -> a) -> STMatrix s t -> ST s a
 - mutable :: Element t => (forall s. (Int, Int) -> STMatrix s t -> ST s u) -> Matrix t -> (Matrix t, u)
 - extractMatrix :: Element a => STMatrix s1 a -> RowRange -> ColRange -> ST s2 (Matrix a)
 - setMatrix :: Element t => STMatrix s t -> Int -> Int -> Matrix t -> ST s ()
 - rowOper :: (Num t, Element t) => RowOper t -> STMatrix s t -> ST s ()
 - data RowOper t
 - data RowRange
 - data ColRange
 - gemmm :: Element t => t -> Slice s t -> t -> Slice s t -> Slice s t -> ST s ()
 - data Slice s t = Slice (STMatrix s t) Int Int Int Int
 - newUndefinedVector :: Storable t => Int -> ST s (STVector s t)
 - unsafeReadVector :: Storable t => STVector s t -> Int -> ST s t
 - unsafeWriteVector :: Storable t => STVector s t -> Int -> t -> ST s ()
 - unsafeThawVector :: Storable t => Vector t -> ST s (STVector s t)
 - unsafeFreezeVector :: Storable t => STVector s t -> ST s (Vector t)
 - newUndefinedMatrix :: Storable t => MatrixOrder -> Int -> Int -> ST s (STMatrix s t)
 - unsafeReadMatrix :: Storable t => STMatrix s t -> Int -> Int -> ST s t
 - unsafeWriteMatrix :: Storable t => STMatrix s t -> Int -> Int -> t -> ST s ()
 - unsafeThawMatrix :: Storable t => Matrix t -> ST s (STMatrix s t)
 - unsafeFreezeMatrix :: Storable t => STMatrix s t -> ST s (Matrix t)
 - mapVectorWithIndex :: (Storable a, Storable b) => (Int -> a -> b) -> Vector a -> Vector b
 - zipVector :: (Storable a, Storable b, Storable (a, b)) => Vector a -> Vector b -> Vector (a, b)
 - zipVectorWith :: (Storable a, Storable b, Storable c) => (a -> b -> c) -> Vector a -> Vector b -> Vector c
 - unzipVector :: (Storable a, Storable b, Storable (a, b)) => Vector (a, b) -> (Vector a, Vector b)
 - unzipVectorWith :: (Storable (a, b), Storable c, Storable d) => ((a, b) -> (c, d)) -> Vector (a, b) -> (Vector c, Vector d)
 - mapVectorM :: (Storable a, Storable b, Monad m) => (a -> m b) -> Vector a -> m (Vector b)
 - mapVectorM_ :: (Storable a, Monad m) => (a -> m ()) -> Vector a -> m ()
 - mapVectorWithIndexM :: (Storable a, Storable b, Monad m) => (Int -> a -> m b) -> Vector a -> m (Vector b)
 - mapVectorWithIndexM_ :: (Storable a, Monad m) => (Int -> a -> m ()) -> Vector a -> m ()
 - foldLoop :: (Int -> t -> t) -> t -> Int -> t
 - foldVector :: Storable a => (a -> b -> b) -> b -> Vector a -> b
 - foldVectorG :: Storable t1 => (Int -> (Int -> t1) -> t2 -> t2) -> t2 -> Vector t1 -> t2
 - foldVectorWithIndex :: Storable a => (Int -> a -> b -> b) -> b -> Vector a -> b
 - mapMatrixWithIndex :: (Element a, Storable b) => ((Int, Int) -> a -> b) -> Matrix a -> Matrix b
 - mapMatrixWithIndexM :: (Element a, Storable b, Monad m) => ((Int, Int) -> a -> m b) -> Matrix a -> m (Matrix b)
 - mapMatrixWithIndexM_ :: (Element a, Num a, Monad m) => ((Int, Int) -> a -> m ()) -> Matrix a -> m ()
 - 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
 - liftMatrix2Auto :: (Element t, Element a, Element b) => (Vector a -> Vector b -> Vector t) -> Matrix a -> Matrix b -> Matrix t
 - data CSR = CSR {}
 - fromCSR :: CSR -> GMatrix
 - mkCSR :: AssocMatrix -> CSR
 - data GMatrix
 - toByteString :: Storable t => Vector t -> ByteString
 - fromByteString :: Storable t => ByteString -> Vector t
 - showInternal :: Storable t => Matrix t -> IO ()
 - reorderVector :: Element a => Vector CInt -> Vector CInt -> Vector a -> Vector a
 
FFI tools
See examples/devel in the repository.
createMatrix :: Storable a => MatrixOrder -> Int -> Int -> IO (Matrix a) Source #
class TransArray c where 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
| Storable t => TransArray (Vector t) Source # | |
| Storable t => TransArray (Matrix t) Source # | |
orderOf :: Matrix t -> MatrixOrder Source #
matrixFromVector :: Storable t => MatrixOrder -> Int -> Int -> Vector t -> Matrix t Source #
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.
ST
In-place manipulation inside the ST monad.
 See examples/inplace.hs in the repository.
Mutable Vectors
Mutable Matrices
mutable :: Element t => (forall s. (Int, Int) -> STMatrix s t -> ST s u) -> Matrix t -> (Matrix t, u) Source #
Unsafe functions
newUndefinedMatrix :: Storable t => MatrixOrder -> Int -> Int -> ST s (STMatrix s t) Source #
Special maps and zips
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
foldVector :: Storable a => (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
Constructors
| CSR | |
mkCSR :: AssocMatrix -> CSR 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)]>>>mSparseR {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])>>>mDense {gmDense = (2><2) [ 1.0, 2.0 , 3.0, 4.0 ], nRows = 2, nCols = 2}
Misc
toByteString :: Storable t => Vector t -> ByteString Source #
fromByteString :: Storable t => ByteString -> Vector t Source #
Arguments
| :: Element a | |
| => Vector CInt | 
  | 
| -> Vector CInt | 
  | 
| -> Vector a | 
  | 
| -> Vector a | 
  | 
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.