blas-hs-0.1.0.2: Low-level Haskell bindings to Blas.

Stabilityexperimental
Safe HaskellNone

Blas.Generic.Safe

Description

Generic interface to Blas using safe foreign calls. Refer to the GHC documentation for more information regarding appropriate use of safe and unsafe foreign calls.

The functions here are named in a similar fashion to the original Blas interface, with the type-dependent letter(s) removed. Some functions have been merged with others to allow the interface to work on both real and complex numbers. If you can't a particular function, try looking for its corresponding complex equivalent (e.g. symv is a special case of hemv applied to real numbers).

It'd be really nice if these functions were actually documented. Alas, for the time being, you'll have to refer to the various Blas docs scattered across the Internet. Note that the interface is based off of CBlas, not Fortran Blas, which is slightly different.

Synopsis

Documentation

class (Floating a, Storable a) => Numeric a whereSource

Blas operations that are applicable to real and complex numbers.

Instances are defined for the 4 types supported by Blas: the single- and double-precision floating point types and their complex versions.

Associated Types

type RealType a :: *Source

The corresponding real type of a.

In other words, RealType (Complex a) is an alias for a. For everything else, RealType a is simply a.

Methods

dotu :: Int -> Ptr a -> Int -> Ptr a -> Int -> IO aSource

dotc :: Int -> Ptr a -> Int -> Ptr a -> Int -> IO aSource

nrm2 :: Int -> Ptr a -> Int -> IO (RealType a)Source

asum :: Int -> Ptr a -> Int -> IO (RealType a)Source

iamax :: Int -> Ptr a -> Int -> IO IntSource

swap :: Int -> Ptr a -> Int -> Ptr a -> Int -> IO ()Source

copy :: Int -> Ptr a -> Int -> Ptr a -> Int -> IO ()Source

axpy :: Int -> a -> Ptr a -> Int -> Ptr a -> Int -> IO ()Source

scal :: Int -> a -> Ptr a -> Int -> IO ()Source

gemv :: Order -> Transpose -> Int -> Int -> a -> Ptr a -> Int -> Ptr a -> Int -> a -> Ptr a -> Int -> IO ()Source

gbmv :: Order -> Transpose -> Int -> Int -> Int -> Int -> a -> Ptr a -> Int -> Ptr a -> Int -> a -> Ptr a -> Int -> IO ()Source

trmv :: Order -> Uplo -> Transpose -> Diag -> Int -> Ptr a -> Int -> Ptr a -> Int -> IO ()Source

tbmv :: Order -> Uplo -> Transpose -> Diag -> Int -> Int -> Ptr a -> Int -> Ptr a -> Int -> IO ()Source

tpmv :: Order -> Uplo -> Transpose -> Diag -> Int -> Ptr a -> Ptr a -> Int -> IO ()Source

trsv :: Order -> Uplo -> Transpose -> Diag -> Int -> Ptr a -> Int -> Ptr a -> Int -> IO ()Source

tbsv :: Order -> Uplo -> Transpose -> Diag -> Int -> Int -> Ptr a -> Int -> Ptr a -> Int -> IO ()Source

tpsv :: Order -> Uplo -> Transpose -> Diag -> Int -> Ptr a -> Ptr a -> Int -> IO ()Source

hemv :: Order -> Uplo -> Int -> a -> Ptr a -> Int -> Ptr a -> Int -> a -> Ptr a -> Int -> IO ()Source

hbmv :: Order -> Uplo -> Int -> Int -> a -> Ptr a -> Int -> Ptr a -> Int -> a -> Ptr a -> Int -> IO ()Source

hpmv :: Order -> Uplo -> Int -> a -> Ptr a -> Ptr a -> Int -> a -> Ptr a -> Int -> IO ()Source

geru :: Order -> Int -> Int -> a -> Ptr a -> Int -> Ptr a -> Int -> Ptr a -> Int -> IO ()Source

gerc :: Order -> Int -> Int -> a -> Ptr a -> Int -> Ptr a -> Int -> Ptr a -> Int -> IO ()Source

her :: Order -> Uplo -> Int -> RealType a -> Ptr a -> Int -> Ptr a -> Int -> IO ()Source

hpr :: Order -> Uplo -> Int -> RealType a -> Ptr a -> Int -> Ptr a -> IO ()Source

her2 :: Order -> Uplo -> Int -> a -> Ptr a -> Int -> Ptr a -> Int -> Ptr a -> Int -> IO ()Source

hpr2 :: Order -> Uplo -> Int -> a -> Ptr a -> Int -> Ptr a -> Int -> Ptr a -> IO ()Source

gemmSource

Arguments

:: Order

Layout of all matrices.

-> Transpose

(transa) Operation applied to a.

-> Transpose

(transb) Operation applied to b.

-> Int

(m) Number of rows of op(a) and c.

-> Int

(n) Number of columns of op(b) and c.

-> Int

(k) Number of columns of op(a) and number of of rows of op(b).

-> a

(alpha) Scaling factor of the product.

-> Ptr a

(a) Pointer to a matrix.

-> Int

(lda) Stride of the major dimension of a.

-> Ptr a

(b) Pointer to a matrix.

-> Int

(ldb) Stride of the major dimension of b.

-> a

(beta) Scaling factor of the original c.

-> Ptr a

(c) Pointer to a mutable matrix.

-> Int

(ldc) Stride of the major dimension of c.

-> IO () 

Calculate a general matrix-matrix product:

 c := alpha * opa(a) * opb(b) + beta * c

where opa and opb are operations specified by transa and transb respectively.

symm :: Order -> Side -> Uplo -> Int -> Int -> a -> Ptr a -> Int -> Ptr a -> Int -> a -> Ptr a -> Int -> IO ()Source

syrk :: Order -> Uplo -> Transpose -> Int -> Int -> a -> Ptr a -> Int -> a -> Ptr a -> Int -> IO ()Source

syr2k :: Order -> Uplo -> Transpose -> Int -> Int -> a -> Ptr a -> Int -> Ptr a -> Int -> a -> Ptr a -> Int -> IO ()Source

hemm :: Order -> Side -> Uplo -> Int -> Int -> a -> Ptr a -> Int -> Ptr a -> Int -> a -> Ptr a -> Int -> IO ()Source

herk :: Order -> Uplo -> Transpose -> Int -> Int -> RealType a -> Ptr a -> Int -> RealType a -> Ptr a -> Int -> IO ()Source

her2k :: Order -> Uplo -> Transpose -> Int -> Int -> a -> Ptr a -> Int -> Ptr a -> Int -> RealType a -> Ptr a -> Int -> IO ()Source

trmm :: Order -> Side -> Uplo -> Transpose -> Diag -> Int -> Int -> a -> Ptr a -> Int -> Ptr a -> Int -> IO ()Source

trsm :: Order -> Side -> Uplo -> Transpose -> Diag -> Int -> Int -> a -> Ptr a -> Int -> Ptr a -> Int -> IO ()Source

class Numeric a => RealNumeric a whereSource

Blas operations that are only applicable to real numbers.

Note: although complex versions of rot and rotg exist in many implementations, they are not part of the official Blas standard and therefore not included here. If you really need them, submit a ticket so we can try to come up with a solution.

Methods

rotg :: Ptr a -> Ptr a -> Ptr a -> Ptr a -> IO ()Source

rotmg :: Ptr a -> Ptr a -> Ptr a -> a -> Ptr a -> IO ()Source

rot :: Int -> Ptr a -> Int -> Ptr a -> Int -> a -> a -> IO ()Source

rotm :: Int -> Ptr a -> Int -> Ptr a -> Int -> Ptr a -> IO ()Source