blas-0.5: Bindings to the BLAS librarySource codeContentsIndex
Data.Matrix.Banded.Internal
Stabilityexperimental
MaintainerPatrick Perry <patperry@stanford.edu>
Contents
Banded matrix data types
Converting to and from foreign pointers
To and from the underlying storage matrix
Bandwith properties
Creating new matrices
Pure
Impure
Getting rows and columns
Vector views
Casting matrices
Unsafe operations
Description
Synopsis
data BMatrix t mn e = BM {
fptrOf :: !!(ForeignPtr e)
offsetOf :: !!Int
size1 :: !!Int
size2 :: !!Int
lowBW :: !!Int
upBW :: !!Int
ldaOf :: !!Int
isHerm :: !!Bool
}
type Banded = BMatrix Imm
type IOBanded = BMatrix Mut
module BLAS.Matrix.Base
module BLAS.Tensor
toForeignPtr :: BMatrix t (m, n) e -> (ForeignPtr e, Int, (Int, Int), (Int, Int), Int, Bool)
fromForeignPtr :: ForeignPtr e -> Int -> (Int, Int) -> (Int, Int) -> Int -> Bool -> BMatrix t (m, n) e
toRawMatrix :: Elem e => BMatrix t (m, n) e -> ((Int, Int), (Int, Int), DMatrix t (m', n') e, Bool)
fromRawMatrix :: Elem e => (Int, Int) -> (Int, Int) -> DMatrix t (m, n) e -> Bool -> Maybe (BMatrix t (m', n') e)
bandwidth :: BMatrix t (m, n) e -> (Int, Int)
numLower :: BMatrix t (m, n) e -> Int
numUpper :: BMatrix t (m, n) e -> Int
banded :: BLAS1 e => (Int, Int) -> (Int, Int) -> [((Int, Int), e)] -> Banded (m, n) e
listsBanded :: BLAS1 e => (Int, Int) -> (Int, Int) -> [[e]] -> Banded (m, n) e
newBanded_ :: Elem e => (Int, Int) -> (Int, Int) -> IO (BMatrix t (m, n) e)
newBanded :: BLAS1 e => (Int, Int) -> (Int, Int) -> [((Int, Int), e)] -> IO (BMatrix t (m, n) e)
newListsBanded :: BLAS1 e => (Int, Int) -> (Int, Int) -> [[e]] -> IO (BMatrix t (m, n) e)
row :: BLAS1 e => Banded (m, n) e -> Int -> Vector n e
col :: BLAS1 e => Banded (m, n) e -> Int -> Vector m e
rows :: BLAS1 e => Banded (m, n) e -> [Vector n e]
cols :: BLAS1 e => Banded (m, n) e -> [Vector m e]
getRow :: BLAS1 e => BMatrix t (m, n) e -> Int -> IO (DVector r n e)
getCol :: BLAS1 e => BMatrix t (m, n) e -> Int -> IO (DVector r m e)
toLists :: BLAS1 e => Banded (m, n) e -> ((Int, Int), (Int, Int), [[e]])
diag :: Elem e => BMatrix t (m, n) e -> Int -> DVector t k e
rowView :: Elem e => BMatrix t (m, n) e -> Int -> (Int, DVector t k e, Int)
colView :: Elem e => BMatrix t (m, n) e -> Int -> (Int, DVector t k e, Int)
coerceBanded :: BMatrix t mn e -> BMatrix t kl e
unsafeBanded :: BLAS1 e => (Int, Int) -> (Int, Int) -> [((Int, Int), e)] -> Banded (m, n) e
unsafeNewBanded :: BLAS1 e => (Int, Int) -> (Int, Int) -> [((Int, Int), e)] -> IO (BMatrix t (m, n) e)
unsafeFreeze :: BMatrix t mn e -> Banded mn e
unsafeThaw :: BMatrix t mn e -> IOBanded mn e
unsafeWithElemPtr :: Elem e => BMatrix t (m, n) e -> (Int, Int) -> (Ptr e -> IO a) -> IO a
unsafeWithBasePtr :: Elem e => BMatrix t (m, n) e -> (Ptr e -> IO a) -> IO a
unsafeDiag :: Elem e => BMatrix t (m, n) e -> Int -> DVector t k e
unsafeGetRow :: BLAS1 e => BMatrix t (m, n) e -> Int -> IO (DVector r n e)
unsafeGetCol :: BLAS1 e => BMatrix t (m, n) e -> Int -> IO (DVector r m e)
unsafeRow :: BLAS1 e => Banded (m, n) e -> Int -> Vector n e
unsafeCol :: BLAS1 e => Banded (m, n) e -> Int -> Vector m e
unsafeRowView :: Elem e => BMatrix t (m, n) e -> Int -> (Int, DVector t k e, Int)
unsafeColView :: Elem e => BMatrix t (m, n) e -> Int -> (Int, DVector t k e, Int)
Banded matrix data types
data BMatrix t mn e Source
Constructors
BM
fptrOf :: !!(ForeignPtr e)
offsetOf :: !!Int
size1 :: !!Int
size2 :: !!Int
lowBW :: !!Int
upBW :: !!Int
ldaOf :: !!Int
isHerm :: !!Bool
show/hide Instances
Matrix (BMatrix t)
BLAS2 e => RMatrix (BMatrix s) e
BLAS2 e => IMatrix (BMatrix Imm) e
BLAS1 e => Scalable (BMatrix Imm ((,) m n)) e
BLAS1 e => ITensor (BMatrix Imm ((,) m n)) ((,) Int Int) e
BLAS1 e => RTensor (BMatrix t ((,) m n)) ((,) Int Int) e IO
BLAS1 e => MTensor (BMatrix Mut ((,) m n)) ((,) Int Int) e IO
(BLAS1 e, Eq e) => Eq (BMatrix Imm ((,) m n) e)
BLAS1 e => Show (BMatrix Imm ((,) m n) e)
(BLAS1 e, AEq e) => AEq (BMatrix Imm ((,) m n) e)
type Banded = BMatrix ImmSource
type IOBanded = BMatrix MutSource
module BLAS.Matrix.Base
module BLAS.Tensor
Converting to and from foreign pointers
toForeignPtr :: BMatrix t (m, n) e -> (ForeignPtr e, Int, (Int, Int), (Int, Int), Int, Bool)Source
fromForeignPtr :: ForeignPtr e -> Int -> (Int, Int) -> (Int, Int) -> Int -> Bool -> BMatrix t (m, n) eSource
To and from the underlying storage matrix
toRawMatrix :: Elem e => BMatrix t (m, n) e -> ((Int, Int), (Int, Int), DMatrix t (m', n') e, Bool)Source
fromRawMatrix :: Elem e => (Int, Int) -> (Int, Int) -> DMatrix t (m, n) e -> Bool -> Maybe (BMatrix t (m', n') e)Source
Bandwith properties
bandwidth :: BMatrix t (m, n) e -> (Int, Int)Source
numLower :: BMatrix t (m, n) e -> IntSource
numUpper :: BMatrix t (m, n) e -> IntSource
Creating new matrices
Pure
banded :: BLAS1 e => (Int, Int) -> (Int, Int) -> [((Int, Int), e)] -> Banded (m, n) eSource
listsBanded :: BLAS1 e => (Int, Int) -> (Int, Int) -> [[e]] -> Banded (m, n) eSource
Impure
newBanded_ :: Elem e => (Int, Int) -> (Int, Int) -> IO (BMatrix t (m, n) e)Source
newBanded :: BLAS1 e => (Int, Int) -> (Int, Int) -> [((Int, Int), e)] -> IO (BMatrix t (m, n) e)Source
newListsBanded :: BLAS1 e => (Int, Int) -> (Int, Int) -> [[e]] -> IO (BMatrix t (m, n) e)Source
Getting rows and columns
row :: BLAS1 e => Banded (m, n) e -> Int -> Vector n eSource
col :: BLAS1 e => Banded (m, n) e -> Int -> Vector m eSource
rows :: BLAS1 e => Banded (m, n) e -> [Vector n e]Source
cols :: BLAS1 e => Banded (m, n) e -> [Vector m e]Source
getRow :: BLAS1 e => BMatrix t (m, n) e -> Int -> IO (DVector r n e)Source
getCol :: BLAS1 e => BMatrix t (m, n) e -> Int -> IO (DVector r m e)Source
toLists :: BLAS1 e => Banded (m, n) e -> ((Int, Int), (Int, Int), [[e]])Source
Vector views
diag :: Elem e => BMatrix t (m, n) e -> Int -> DVector t k eSource
rowView :: Elem e => BMatrix t (m, n) e -> Int -> (Int, DVector t k e, Int)Source
colView :: Elem e => BMatrix t (m, n) e -> Int -> (Int, DVector t k e, Int)Source
Casting matrices
coerceBanded :: BMatrix t mn e -> BMatrix t kl eSource
Coerce the phantom shape type from one type to another.
Unsafe operations
unsafeBanded :: BLAS1 e => (Int, Int) -> (Int, Int) -> [((Int, Int), e)] -> Banded (m, n) eSource
unsafeNewBanded :: BLAS1 e => (Int, Int) -> (Int, Int) -> [((Int, Int), e)] -> IO (BMatrix t (m, n) e)Source
unsafeFreeze :: BMatrix t mn e -> Banded mn eSource
unsafeThaw :: BMatrix t mn e -> IOBanded mn eSource
unsafeWithElemPtr :: Elem e => BMatrix t (m, n) e -> (Int, Int) -> (Ptr e -> IO a) -> IO aSource
unsafeWithBasePtr :: Elem e => BMatrix t (m, n) e -> (Ptr e -> IO a) -> IO aSource
unsafeDiag :: Elem e => BMatrix t (m, n) e -> Int -> DVector t k eSource
unsafeGetRow :: BLAS1 e => BMatrix t (m, n) e -> Int -> IO (DVector r n e)Source
unsafeGetCol :: BLAS1 e => BMatrix t (m, n) e -> Int -> IO (DVector r m e)Source
unsafeRow :: BLAS1 e => Banded (m, n) e -> Int -> Vector n eSource
unsafeCol :: BLAS1 e => Banded (m, n) e -> Int -> Vector m eSource
unsafeRowView :: Elem e => BMatrix t (m, n) e -> Int -> (Int, DVector t k e, Int)Source
unsafeColView :: Elem e => BMatrix t (m, n) e -> Int -> (Int, DVector t k e, Int)Source
Produced by Haddock version 2.3.0