Copyright | (c) Marco Zocca 2017-2020 |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | zocca marco gmail |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
attoparsec
-based parser and serializer for the NIST MatrixMarket format [1]. The parser logic originally appeared in accelerate-examples
and it is reused here (courtesy of T.McDonell and the accelerate
developers) with some amendments.
References :
Synopsis
- readMatrix :: FilePath -> IO (Matrix Scientific)
- readMatrix' :: MonadThrow m => ByteString -> m (Matrix Scientific)
- readArray :: FilePath -> IO (Array Scientific)
- readArray' :: MonadThrow m => ByteString -> m (Array Scientific)
- writeMatrix :: Show b => FilePath -> Matrix b -> IO ()
- writeMatrix' :: (MonadThrow m, Show b) => Matrix b -> m ByteString
- writeArray :: Show a => FilePath -> Array a -> IO ()
- writeArray' :: Show a => Array a -> ByteString
- data Matrix a
- data Array a
- data Format
- = Coordinate
- | Array
- data Structure
- nnz :: Matrix t -> Int
- dim :: Matrix t -> (Int, Int)
- numDat :: Matrix t -> Int
- dimArr :: Array t -> (Int, Int)
- numDatArr :: Array a -> Int
- data ImportError = FileParseError String String
- data ExportError = FormatExportNotSupported String String
Load
Matrix
readMatrix :: FilePath -> IO (Matrix Scientific) Source #
Load a matrix (sparse, i.e. in Coordinate format) from file.
Uses readMatrix'
internally
readMatrix' :: MonadThrow m => ByteString -> m (Matrix Scientific) Source #
Deserialize a matrix (sparse, i.e. in Coordinate format) from a lazy ByteString
.
Throws a FileParseError
if the input cannot be parsed
Array
readArray :: FilePath -> IO (Array Scientific) Source #
Load a dense matrix (i.e. a matrix or vector in Array format) from file.
Uses readArray'
internally
readArray' :: MonadThrow m => ByteString -> m (Array Scientific) Source #
Deserialize a dense matrix (i.e. a matrix or vector in Array format) from a lazy ByteString
.
Throws a FileParseError
if the input cannot be parsed
Save
Matrix
writeMatrix :: Show b => FilePath -> Matrix b -> IO () Source #
Store a sparse matrix in Coordinate format to a file.
Uses writeMatrix'
internally
writeMatrix' :: (MonadThrow m, Show b) => Matrix b -> m ByteString Source #
Serialize a sparse matrix in Coordinate format into a ByteString
.
Throws a FormatExportNotSupported
if the user tries to serialize a PatternMatrix
value.
Array
writeArray :: Show a => FilePath -> Array a -> IO () Source #
Write a dense matrix from the Array format into a file.
Uses writeArray'
internally.
writeArray' :: Show a => Array a -> ByteString Source #
Serialize a dense matrix from the Array format into a ByteString
Types
Sparse matrix in coordinate form (row, column, entry) NB: indices are 1-based i.e. A(1,1) is the top-left entry of matrix A
RMatrix (Int, Int) Int Structure [(Int, Int, a)] | |
CMatrix (Int, Int) Int Structure [(Int, Int, Complex a)] | |
PatternMatrix (Int, Int) Int Structure [(Int32, Int32)] | |
IntMatrix (Int, Int) Int Structure [(Int32, Int32, Int)] |
Array, i.e. a DENSE matrix (also used to represent vectors as n-by-1 matrices)
Specifies either sparse or dense storage. In sparse ("coordinate") storage, elements are given in (i,j,x) triplets for matrices (or (i,x) for vectors). Indices are 1-based, so that A(1,1) is the first element of a matrix, and x(1) is the first element of a vector.
In dense ("array") storage, elements are given in column-major order.
In both cases, each element is given on a separate line.
Specifies any special structure in the matrix. For symmetric and hermitian matrices, only the lower-triangular part of the matrix is given. For skew matrices, only the entries below the diagonal are stored.
Helpers
Matrix-related
numDat :: Matrix t -> Int Source #
Length of data vector internal to the Matrix; this is _not_ necessarily the actual number of matrix entries because symmetric entries are not stored
Array-related
numDatArr :: Array a -> Int Source #
Length of data vector internal to the Array; this is _not_ necessarily the actual number of matrix entries because symmetric entries are not stored
Exceptions
data ImportError Source #
Exceptions related to loading/importing data
Instances
Eq ImportError Source # | |
Defined in Control.Exception.Common (==) :: ImportError -> ImportError -> Bool # (/=) :: ImportError -> ImportError -> Bool # | |
Show ImportError Source # | |
Defined in Control.Exception.Common showsPrec :: Int -> ImportError -> ShowS # show :: ImportError -> String # showList :: [ImportError] -> ShowS # | |
Exception ImportError Source # | |
Defined in Control.Exception.Common |
data ExportError Source #
Exceptions related to serializing/storing data
Instances
Eq ExportError Source # | |
Defined in Control.Exception.Common (==) :: ExportError -> ExportError -> Bool # (/=) :: ExportError -> ExportError -> Bool # | |
Show ExportError Source # | |
Defined in Control.Exception.Common showsPrec :: Int -> ExportError -> ShowS # show :: ExportError -> String # showList :: [ExportError] -> ShowS # | |
Exception ExportError Source # | |
Defined in Control.Exception.Common |