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

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

Data.Matrix.MatrixMarket

Contents

Description

Attoparsec parser and serializer for the NIST MatrixMarket format. The parser logic originally appeared in `accelerate-examples` and it is reused here (courtesy of T.McDonell and the accelerate developers) with some amendments.

In this version:

  • ) Numbers are represented with Scientific notation instead of floating point
  • ) Parsing rules are a bit relaxed to accommodate various whitespace corner cases

Synopsis

Load

readMatrix :: FilePath -> IO (Matrix Scientific) Source #

Load a matrix (sparse, i.e. in Coordinate format) from file

readArray :: FilePath -> IO (Array Scientific) Source #

Load a dense matrix (i.e. a matrix or vector in Array format) from file

Save

writeMatrix :: Show b => FilePath -> Matrix b -> IO () Source #

Serialize a sparse matrix in Coordinate format

writeArray :: Show a => FilePath -> Array a -> IO () Source #

Serialize a dense matrix in Array format

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 # 

Methods

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

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

Show a => Show (Matrix a) Source # 

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 # 

Methods

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

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

Show a => Show (Array a) Source # 

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

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 #

helpers

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