matrix-market-attoparsec-0.1.1.2: Parsing and serialization functions for the NIST Matrix Market format

Copyright(c) Marco Zocca 2017-2020
LicenseBSD2 (see the file LICENSE)
Maintainerzocca marco gmail
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Data.Matrix.MatrixMarket

Contents

Description

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 :

  1. https://math.nist.gov/MatrixMarket/
Synopsis

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

data Matrix a Source #

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

Instances
Eq a => Eq (Matrix a) Source # 
Instance details

Defined in Data.Matrix.MatrixMarket.Internal

Methods

(==) :: Matrix a -> Matrix a -> Bool #

(/=) :: Matrix a -> Matrix a -> Bool #

Show a => Show (Matrix a) Source # 
Instance details

Defined in Data.Matrix.MatrixMarket.Internal

Methods

showsPrec :: Int -> Matrix a -> ShowS #

show :: Matrix a -> String #

showList :: [Matrix a] -> ShowS #

data Array a Source #

Array, i.e. a DENSE matrix (also used to represent vectors as n-by-1 matrices)

Constructors

RArray (Int, Int) Structure [a] 
CArray (Int, Int) Structure [Complex a] 
Instances
Eq a => Eq (Array a) Source # 
Instance details

Defined in Data.Matrix.MatrixMarket.Internal

Methods

(==) :: Array a -> Array a -> Bool #

(/=) :: Array a -> Array a -> Bool #

Show a => Show (Array a) Source # 
Instance details

Defined in Data.Matrix.MatrixMarket.Internal

Methods

showsPrec :: Int -> Array a -> ShowS #

show :: Array a -> String #

showList :: [Array a] -> ShowS #

data Format Source #

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.

Constructors

Coordinate 
Array 
Instances
Eq Format Source # 
Instance details

Defined in Data.Matrix.MatrixMarket.Internal

Methods

(==) :: Format -> Format -> Bool #

(/=) :: Format -> Format -> Bool #

Show Format Source # 
Instance details

Defined in Data.Matrix.MatrixMarket.Internal

data Structure Source #

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.

Constructors

General 
Symmetric 
Hermitian 
Skew 

Helpers

Matrix-related

nnz :: Matrix t -> Int Source #

Number of matrix nonzeros

dim :: Matrix t -> (Int, Int) Source #

Matrix size : number of rows, number of columns

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

dimArr :: Array t -> (Int, Int) Source #

Array size : number of rows, number of columns

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