hblas-0.3.2.1: Human friendly BLAS and Lapack bindings for Haskell.

Safe HaskellNone
LanguageHaskell2010

Numerical.HBLAS.MatrixTypes

Description

PSA, the matrix data types used in the hBLAS binding should not be regarded as being general purpose matrices.

They are designed to exactly express only the matrices which are valid inputs for BLAS. When applicable, such matrices should be easily mapped to and from other matrix libraries. That said, the BLAS and LAPACK matrix formats capture a rich and very expressive subset of Dense Matrix formats.

The primary and hence default format is Dense Row and Column Major Matrices, but support will be added for other formats that BLAS and LAPACK provide operations for.

A guiding rule of thumb for this package is that there are no generic abstractions provided, merely machinery to ensure all uses of BLAS and LAPACK operations can be used in their full generality in a human friendly type safe fashion. It is the role of a higher level library to provide any generic operations.

One such higher level lib you can interface with easily is Numerical. There is a work in progress binding to help this in the numerical-hblas package (which may not be public yet at the time of this writing)

Synopsis

Documentation

type Row = Row Source

data MatUpLo Source

For Symmetric, Hermetian or Triangular matrices, which part is modeled.

Constructors

MatUpper 
MatLower 

data MatDiag Source

Many triangular matrix routines expect to know if the matrix is all 1 (unit ) on the diagonal or not. Likewise, Many Factorizations routines can be assumed to return unit triangular matrices

Constructors

MatUnit 
MatNonUnit 

data EquationSide Source

For certain Square matrix product, do you want to Compute A*B or B*A only used as an argument

Constructors

LeftSide 
RightSide 

type family TransposeF x :: Orientation Source

Instances

data Variant Source

Constructors

Direct 
Implicit 

data SVariant :: Variant -> * where Source

Variant and SVariant are a bit odd looking, They crop up when needing to talk about eg the row vectors of a packed triangular row major matrix wrt both their logical size and manifest sizes this notion only makes sense in the 1dim case. If you don't understand this parameter, just use SDirect and Direct as they will generally be the correct choice for most users.

Constructors

SImplicit :: !Int -> !Int -> SVariant Implicit 

Fields

_frontPadding :: !Int
 
_endPadding :: !Int
 
SDirect :: SVariant Direct 

data DenseVector :: Variant -> * -> * where Source

Constructors

DenseVector :: !(SVariant varnt) -> !Int -> !Int -> !(Vector elem) -> DenseVector varnt elem 

data MDenseVector :: * -> Variant -> * -> * where Source

Constructors

MutableDenseVector :: !(SVariant varnt) -> !Int -> !Int -> !(MVector s elem) -> MDenseVector s varnt elem 

data DenseMatrix :: Orientation -> * -> * where Source

DenseMatrix is for dense row or column major matrices

Constructors

DenseMatrix :: SOrientation ornt -> !Int -> !Int -> !Int -> !(Vector elem) -> DenseMatrix ornt elem 

Fields

_OrientationMat :: SOrientation ornt
 
_XdimDenMat :: !Int
 
_YdimDenMat :: !Int
 
_StrideDenMat :: !Int
 
_bufferDenMat :: !(Vector elem)
 

Instances

(Show el, Storable el) => Show (DenseMatrix Column el) 
(Show el, Storable el) => Show (DenseMatrix Row el) 

mutableVectorToList :: (PrimMonad m, Storable a) => MVector (PrimState m) a -> m [a] Source

this should never be used in real code, ever ever, but its handy for testing but seriously never use this in real code, it doesn't do what you think because in the case of a matrix slice, the underlying buffer will have additional elements aside from the ones you expect! never use this in real code please. :)

data MDenseMatrix :: * -> Orientation -> * -> * where Source

Constructors

MutableDenseMatrix :: SOrientation ornt -> !Int -> !Int -> !Int -> !(MVector s elem) -> MDenseMatrix s ornt elem 

unsafeFreezeDenseMatrix :: (Storable elem, PrimMonad m) => MDenseMatrix (PrimState m) or elem -> m (DenseMatrix or elem) Source

unsafeThawDenseMatrix :: (Storable elem, PrimMonad m) => DenseMatrix or elem -> m (MDenseMatrix (PrimState m) or elem) Source

getDenseMatrixArray :: DenseMatrix or elem -> Vector elem Source

uncheckedDenseMatrixIndex :: Storable elem => DenseMatrix or elem -> (Int, Int) -> elem Source

uncheckedDenseMatrixIndexM :: (Monad m, Storable elem) => DenseMatrix or elem -> (Int, Int) -> m elem Source

uncheckedMutableDenseMatrixIndexM :: (PrimMonad m, Storable elem) => MDenseMatrix (PrimState m) or elem -> (Int, Int) -> m elem Source

swap :: (a, b) -> (b, a) Source

mapDenseMatrix :: (Storable a, Storable b) => (a -> b) -> DenseMatrix or a -> DenseMatrix or b Source

`map f matrix`

imapDenseMatrix :: (Storable a, Storable b) => ((Int, Int) -> a -> b) -> DenseMatrix or a -> DenseMatrix or b Source

uncheckedDenseMatrixNextTuple :: DenseMatrix or elem -> (Int, Int) -> Maybe (Int, Int) Source

In Matrix format memory order enumeration of the index tuples, for good locality 2dim map

generateDenseMatrix :: Storable a => SOrientation x -> (Int, Int) -> ((Int, Int) -> a) -> DenseMatrix x a Source

generateDenseMatrix Row (k,k) (i,j)-> if i == j then 1.0 else 0.0 would generate a KxK identity matrix

generateMutableDenseMatrix :: (Storable a, PrimMonad m) => SOrientation x -> (Int, Int) -> ((Int, Int) -> a) -> m (MDenseMatrix (PrimState m) x a) Source

mutable version of generateDenseMatrix

generateMutableDenseVector :: (Storable a, PrimMonad m) => Int -> (Int -> a) -> m (MDenseVector (PrimState m) Direct a) Source

uncheckedDenseMatrixSlice :: Storable elem => DenseMatrix or elem -> (Int, Int) -> (Int, Int) -> DenseMatrix or elem Source

transposeDenseMatrix :: (inor ~ TransposeF outor, outor ~ TransposeF inor) => DenseMatrix inor elem -> DenseMatrix outor elem Source

tranposeMatrix does a shallow transpose that swaps the format and the x y params, but changes nothing in the memory layout. Most applications where transpose is used in a computation need a deep, copying, tranpose operation