Safe Haskell | None |
---|---|
Language | Haskell2010 |
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)
- data Orientation
- type Row = Row
- type Column = Column
- data SOrientation :: Orientation -> * where
- sTranpose :: (x ~ TransposeF y, y ~ TransposeF x) => SOrientation x -> SOrientation y
- data Transpose
- data MatUpLo
- data MatDiag
- data EquationSide
- type family TransposeF (x :: Orientation) :: Orientation
- data Variant
- data SVariant :: Variant -> * where
- data DenseVector :: Variant -> * -> * where
- DenseVector :: {..} -> DenseVector varnt elem
- data MDenseVector :: * -> Variant -> * -> * where
- MutableDenseVector :: {..} -> MDenseVector s varnt elem
- data DenseMatrix :: Orientation -> * -> * where
- DenseMatrix :: {..} -> DenseMatrix ornt elem
- mutableVectorToList :: (PrimMonad m, Storable a) => MVector (PrimState m) a -> m [a]
- data MDenseMatrix :: * -> Orientation -> * -> * where
- MutableDenseMatrix :: {..} -> MDenseMatrix s ornt elem
- type IODenseMatrix = MDenseMatrix RealWorld
- unsafeFreezeDenseMatrix :: (Storable elem, PrimMonad m) => MDenseMatrix (PrimState m) or elem -> m (DenseMatrix or elem)
- unsafeThawDenseMatrix :: (Storable elem, PrimMonad m) => DenseMatrix or elem -> m (MDenseMatrix (PrimState m) or elem)
- getDenseMatrixRow :: DenseMatrix or elem -> Int
- getDenseMatrixColumn :: DenseMatrix or elem -> Int
- getDenseMatrixLeadingDimStride :: DenseMatrix or elem -> Int
- getDenseMatrixArray :: DenseMatrix or elem -> Vector elem
- getDenseMatrixOrientation :: DenseMatrix or elem -> SOrientation or
- uncheckedDenseMatrixIndex :: Storable elem => DenseMatrix or elem -> (Int, Int) -> elem
- uncheckedDenseMatrixIndexM :: (Monad m, Storable elem) => DenseMatrix or elem -> (Int, Int) -> m elem
- uncheckedMutableDenseMatrixIndexM :: (PrimMonad m, Storable elem) => MDenseMatrix (PrimState m) or elem -> (Int, Int) -> m elem
- swap :: (a, b) -> (b, a)
- mapDenseMatrix :: (Storable a, Storable b) => (a -> b) -> DenseMatrix or a -> DenseMatrix or b
- imapDenseMatrix :: (Storable a, Storable b) => ((Int, Int) -> a -> b) -> DenseMatrix or a -> DenseMatrix or b
- uncheckedDenseMatrixNextTuple :: DenseMatrix or elem -> (Int, Int) -> Maybe (Int, Int)
- generateDenseMatrix :: Storable a => SOrientation x -> (Int, Int) -> ((Int, Int) -> a) -> DenseMatrix x a
- generateMutableDenseMatrix :: (Storable a, PrimMonad m) => SOrientation x -> (Int, Int) -> ((Int, Int) -> a) -> m (MDenseMatrix (PrimState m) x a)
- generateMutableUpperTriangular :: forall a x m. (Num a, Storable a, PrimMonad m) => SOrientation x -> (Int, Int) -> ((Int, Int) -> a) -> m (MDenseMatrix (PrimState m) x a)
- generateMutableLowerTriangular :: forall a x m. (Num a, Storable a, PrimMonad m) => SOrientation x -> (Int, Int) -> ((Int, Int) -> a) -> m (MDenseMatrix (PrimState m) x a)
- generateMutableDenseVector :: (Storable a, PrimMonad m) => Int -> (Int -> a) -> m (MDenseVector (PrimState m) Direct a)
- generateMutableDenseVectorWithStride :: (Num a, Storable a, PrimMonad m) => Int -> Int -> (Int -> a) -> m (MDenseVector (PrimState m) Direct a)
- uncheckedDenseMatrixSlice :: Storable elem => DenseMatrix or elem -> (Int, Int) -> (Int, Int) -> DenseMatrix or elem
- transposeDenseMatrix :: (inor ~ TransposeF outor, outor ~ TransposeF inor) => DenseMatrix inor elem -> DenseMatrix outor elem
Documentation
data SOrientation :: Orientation -> * where Source #
SRow :: SOrientation Row | |
SColumn :: SOrientation Column |
Eq (SOrientation a) Source # | |
Ord (SOrientation a) Source # | |
Show (SOrientation a) Source # | |
sTranpose :: (x ~ TransposeF y, y ~ TransposeF x) => SOrientation x -> SOrientation y Source #
For Symmetric, Hermetian or Triangular matrices, which part is modeled.
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
data EquationSide Source #
For certain Square matrix product, do you want to Compute A*B or B*A only used as an argument
type family TransposeF (x :: Orientation) :: Orientation Source #
type TransposeF Column Source # | |
type TransposeF Row Source # | |
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.
SImplicit :: {..} -> SVariant Implicit | |
| |
SDirect :: SVariant Direct |
data DenseVector :: Variant -> * -> * where Source #
DenseVector :: {..} -> DenseVector varnt elem | |
|
data MDenseVector :: * -> Variant -> * -> * where Source #
MutableDenseVector :: {..} -> MDenseVector s varnt elem | |
|
data DenseMatrix :: Orientation -> * -> * where Source #
DenseMatrix
is for dense row or column major matrices
DenseMatrix :: {..} -> DenseMatrix ornt elem | |
|
mutableVectorToList :: (PrimMonad m, Storable a) => MVector (PrimState m) a -> m [a] Source #
toList routine for pure matrices TODO this should build on top of a traverse/mapM style routine like the mapper etc
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 #
MutableDenseMatrix :: {..} -> MDenseMatrix s ornt elem | |
|
type IODenseMatrix = MDenseMatrix RealWorld Source #
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 #
getDenseMatrixRow :: DenseMatrix or elem -> Int Source #
getDenseMatrixColumn :: DenseMatrix or elem -> Int Source #
getDenseMatrixLeadingDimStride :: DenseMatrix or elem -> Int Source #
getDenseMatrixArray :: DenseMatrix or elem -> Vector elem Source #
getDenseMatrixOrientation :: DenseMatrix or elem -> SOrientation or 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 #
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
generateMutableUpperTriangular :: forall a x m. (Num a, Storable a, PrimMonad m) => SOrientation x -> (Int, Int) -> ((Int, Int) -> a) -> m (MDenseMatrix (PrimState m) x a) Source #
generateMutableLowerTriangular :: forall a x m. (Num a, Storable a, PrimMonad m) => SOrientation x -> (Int, Int) -> ((Int, Int) -> a) -> m (MDenseMatrix (PrimState m) x a) Source #
generateMutableDenseVector :: (Storable a, PrimMonad m) => Int -> (Int -> a) -> m (MDenseVector (PrimState m) Direct a) Source #
generateMutableDenseVectorWithStride :: (Num a, Storable a, PrimMonad m) => Int -> 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