| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Numerical.HBLAS.MatrixTypes
- data Orientation
- data SOrientation :: Orientation -> * where
- sTranpose :: (x ~ TransposeF y, y ~ TransposeF x) => SOrientation x -> SOrientation y
- data Transpose
- type family TransposeF x :: Orientation
- data DenseMatrix :: Orientation -> * -> * where- DenseMatrix :: { - _OrientationMat :: SOrientation ornt
- _XdimDenMat :: !Int
- _YdimDenMat :: !Int
- _StrideDenMat :: !Int
- _bufferDenMat :: !(Vector elem)
 
 
- DenseMatrix :: { 
- data MutDenseMatrix :: * -> Orientation -> * -> * where- MutableDenseMatrix :: { - _OrientationMutMat :: SOrientation ornt
- _XdimDenMutMat :: !Int
- _YdimDenMutMat :: !Int
- _StrideDenMutMat :: !Int
- _bufferDenMutMat :: !(MVector s elem)
 
 
- MutableDenseMatrix :: { 
- type IODenseMatrix = MutDenseMatrix RealWorld
- unsafeFreezeDenseMatrix :: (Storable elem, PrimMonad m) => MutDenseMatrix (PrimState m) or elem -> m (DenseMatrix or elem)
- unsafeThawDenseMatrix :: (Storable elem, PrimMonad m) => DenseMatrix or elem -> m (MutDenseMatrix (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
- uncheckedMutDenseMatrixIndexM :: (PrimMonad m, Storable elem) => MutDenseMatrix (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 (MutDenseMatrix (PrimState m) x 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 Orientation Source
PSA, the matrix data types used in the hOpenBLAS 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 leve library to provide any generic operations.
Instances
data SOrientation :: Orientation -> * where Source
Constructors
| SRow :: SOrientation Row | |
| SColumn :: SOrientation Column | 
Instances
sTranpose :: (x ~ TransposeF y, y ~ TransposeF x) => SOrientation x -> SOrientation y Source
Constructors
| NoTranspose | |
| Transpose | |
| ConjTranspose | |
| ConjNoTranspose | 
type family TransposeF x :: Orientation Source
Instances
| type TransposeF Column = Row | |
| type TransposeF Row = Column | 
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 
 | |
Instances
| (Show el, Storable el) => Show (DenseMatrix Column el) | |
| (Show el, Storable el) => Show (DenseMatrix Row el) | 
data MutDenseMatrix :: * -> Orientation -> * -> * where Source
MDenseMatrix 
Constructors
| MutableDenseMatrix :: SOrientation ornt -> !Int -> !Int -> !Int -> !(MVector s elem) -> MutDenseMatrix s ornt elem | |
| Fields 
 | |
unsafeFreezeDenseMatrix :: (Storable elem, PrimMonad m) => MutDenseMatrix (PrimState m) or elem -> m (DenseMatrix or elem) Source
unsafeThawDenseMatrix :: (Storable elem, PrimMonad m) => DenseMatrix or elem -> m (MutDenseMatrix (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
uncheckedMutDenseMatrixIndexM :: (PrimMonad m, Storable elem) => MutDenseMatrix (PrimState m) or elem -> (Int, Int) -> m elem Source
mapDenseMatrix :: (Storable a, Storable b) => (a -> b) -> DenseMatrix or a -> DenseMatrix or b Source
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
generateMutableDenseMatrix :: (Storable a, PrimMonad m) => SOrientation x -> (Int, Int) -> ((Int, Int) -> a) -> m (MutDenseMatrix (PrimState m) x 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