fpnla-0.1.1: A library for NLA operations

Safe HaskellSafe-Inferred

FPNLA.Operations.Parameters

Contents

Synopsis

Elements

class (Eq e, Floating e) => Elt e whereSource

This class represents the elements that can be used in the BLAS operations. The elements in BLAS are real or complex numbers, so we provide default instances for the Haskell Double, Float and Complex types.

Methods

getConjugate :: e -> eSource

Returns the conjugate of a number. For real numbers it's the identity function and for complex numbers it's the common conjugate function.

Instances

Strategies and contexts

type family StratCtx s :: *Source

This type family is used to represent the context of an operation. A particular implementation is a combination of an algorithm and a parallelism technique, and we call it a strategy. A particular strategy may need particular information to execute. For example, an operation that computes the matrix-matrix multiplication by splitting the matrices in blocks must require the size of the blocks. With this context we allows to pass any additional information that the operation needs to execute as parameters, but maintaining a common signature. The s type parameter is the strategy so, there must exist a Haskell data type to represent a particular strategy.

Result type

In BLAS it's common that operations in higher levels use operations in the lower levels, so, an operation in level three that by its signature manipulates matrices only, internally uses level two operations that manipulates vectors. In order to avoid the show . read problem, the type of the vector (or any other internal data type) must appear in the signature of an operation. To solve the problem we use phantom types to pass the internally used types to the Haskell type system.

data ResM s v m e Source

The ResM data type is used as result of level three BLAS operations and returns a matrix m of elements e and contains the strategy s and vector v as phantom types.

Instances

Show (m e) => Show (ResM s v m e) 

data ResV s v e Source

The ResV data type is used as result of level two BLAS operations and returns a vector v of elements e and contains the strategy s as phantom types.

Instances

Show (v e) => Show (ResV s v e) 

data ResS s e Source

The ResS data type is used as result of level one BLAS operations and returns an scalar e and contains the strategy s as phantom types.

Instances

Show e => Show (ResS s e) 

blasResultM :: MatrixVector m v e => m e -> ResM s v m eSource

Wrap a matrix into a ResM.

blasResultV :: Vector v e => v e -> ResV s v eSource

Wrap a vector into a ResV.

blasResultS :: e -> ResS s eSource

Wrap a scalar into a ResS.

getResultDataM :: MatrixVector m v e => ResM s v m e -> m eSource

Unwrap a matrix from a ResM.

getResultDataV :: Vector v e => ResV s v e -> v eSource

Unwrap a vector from a ResV.

getResultDataS :: ResS s e -> eSource

Unwrap a scalar from a ResS.

Miscellaneous

data TransType m Source

Indicates if a matrix must be considered as normal, transposed or transposed conjugated. This is part of the common flags in the BLAS operation signatures and it's useful to work with a transposed matrix without really computing the transposed matrix.

Constructors

Trans m 
NoTrans m 
ConjTrans m 

Instances

Eq m => Eq (TransType m) 
Show m => Show (TransType m) 

data UnitType m Source

Indicates if a matrix must be considered as unitary or not. An unitary matrix is a matrix that contains ones in the diagonal. This is part of the common flags in the BLAS operation signatures.

Constructors

Unit m 
NoUnit m 

Instances

Eq m => Eq (UnitType m) 
Show m => Show (UnitType m) 

data TriangType m Source

Indicates that a matrix is symmetric and with which triangular part of the matrix the operation is going to work (Upper or Lower). The operation only will see the indicated part of the matrix and should not try to access the other part. This is part of the common flags in the BLAS operation signatures.

Constructors

Lower m 
Upper m 

Instances

Eq m => Eq (TriangType m) 
Show m => Show (TriangType m) 

unTransT :: TransType a -> (b -> TransType b, a)Source

Given a data type flagged by a TransType, returns a pair containing the TransType constructor and the data type.

unUnitT :: UnitType a -> (b -> UnitType b, a)Source

Given a data type flagged by a UnitType, returns a pair containing the UnitType constructor and the data type.

unTriangT :: TriangType a -> (b -> TriangType b, a)Source

Given a data type flagged by a TriangType, returns a pair containing the TriangType constructor and the data type.

elemTrans_m :: (Elt e, Matrix m e) => Int -> Int -> TransType (m e) -> eSource

Given an i,j position and a TransType flagged matrix, returns the element in that position without computing the transpose.

dimTrans_m :: Matrix m e => TransType (m e) -> (Int, Int)Source

Given a TransType flagged matrix, returns the dimension of the matrix without computing the transpose.

elemSymm :: (Elt e, Matrix m e) => Int -> Int -> TriangType (m e) -> eSource

Given an i,j position and a TransType flagged matrix, returns the element in that position only accessing the part indicated by the TransType.

dimTriang :: Matrix m e => TriangType (m e) -> (Int, Int)Source

Given a TransType flagged matrix, returns the dimension of the matrix.

elemUnit_m :: (Elt e, Matrix m e) => Int -> Int -> UnitType (m e) -> eSource

Given an i,j position and a UnitType flagged matrix, returns the element in that position. If the matrix is flagged as Unit and i == j (the element is in the diagonal) returns one.

dimUnit_m :: Matrix m e => UnitType (m e) -> (Int, Int)Source

Given a UnitType flagged matrix, returns the dimension of the matrix.

elemTransUnit_m :: (Elt e, Matrix m e) => Int -> Int -> TransType (UnitType (m e)) -> eSource

Given an i,j position and a TransType-UnitType flagged matrix, returns the element in that position without computing the transpose.

dimTransUnit_m :: Matrix m e => TransType (UnitType (m e)) -> (Int, Int)Source

Given a TransType-UnitType flagged matrix, returns the dimension of the matrix.

transTrans_m :: (Elt e, Matrix m e) => TransType (m e) -> m eSource

Given a TransType flagged matrix, computes and returns its transpose.