| Copyright | (c) Justin Le 2018 | 
|---|---|
| License | BSD3 | 
| Maintainer | justin@jle.im | 
| Stability | experimental | 
| Portability | non-portable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Numeric.LinearAlgebra.Static.Vector
Description
Conversions between statically sized types in Numeric.LinearAlgebra.Static from hmatrix and vector-sized.
This module is intentionally minimal, exporting only functions that
 cannot be written without "unsafe" operations.  With these, however, you
 can easily write other useful combinators by using type-safe operations
 like fmap, map, liftA2, convert,
 etc.
Synopsis
- rVec :: KnownNat n => R n -> Vector n ℝ
- grVec :: (KnownNat n, Vector v ℝ) => R n -> Vector v n ℝ
- vecR :: Vector n ℝ -> R n
- gvecR :: Vector v ℝ => Vector v n ℝ -> R n
- cVec :: KnownNat n => C n -> Vector n ℂ
- gcVec :: (KnownNat n, Vector v ℂ) => C n -> Vector v n ℂ
- vecC :: Vector n ℂ -> C n
- gvecC :: Vector v ℂ => Vector v n ℂ -> C n
- lRows :: (KnownNat m, KnownNat n) => L m n -> Vector m (R n)
- rowsL :: forall m n. KnownNat n => Vector m (R n) -> L m n
- lCols :: forall m n. (KnownNat m, KnownNat n) => L m n -> Vector n (R m)
- colsL :: forall m n. KnownNat m => Vector n (R m) -> L m n
- lVec :: forall m n. (KnownNat m, KnownNat n) => L m n -> Vector (m * n) ℝ
- glVec :: (KnownNat m, KnownNat n, Vector v ℝ) => L m n -> Vector v (m * n) ℝ
- vecL :: forall m n. KnownNat n => Vector (m * n) ℝ -> L m n
- gvecL :: (KnownNat n, Vector v ℝ) => Vector v (m * n) ℝ -> L m n
- mRows :: forall m n. (KnownNat m, KnownNat n) => M m n -> Vector m (C n)
- rowsM :: forall m n. KnownNat n => Vector m (C n) -> M m n
- mCols :: forall m n. (KnownNat m, KnownNat n) => M m n -> Vector n (C m)
- colsM :: forall m n. KnownNat m => Vector n (C m) -> M m n
- mVec :: forall m n. (KnownNat m, KnownNat n) => M m n -> Vector (m * n) ℂ
- gmVec :: (KnownNat m, KnownNat n, Vector v ℂ) => M m n -> Vector v (m * n) ℂ
- vecM :: forall m n. KnownNat n => Vector (m * n) ℂ -> M m n
- gvecM :: (KnownNat n, Vector v ℂ) => Vector v (m * n) ℂ -> M m n
Vector
Real
rVec :: KnownNat n => R n -> Vector n ℝ Source #
Convert an hmatrix vector (parameterized by its lenth) to
 a vector-sized storable vector of Doubles.
This is normally O(1), but will be O(n) if the R was contructed
 with konst or any other replicated-value constructor (like literals
 and fromInteger/fromRational).
vecR :: Vector n ℝ -> R n Source #
Convert a vector-sized storable vector to an hmatrix vector (parameterized by its lenth).
O(1)
gvecR :: Vector v ℝ => Vector v n ℝ -> R n Source #
vecR, but generalized to work for all types of sized vectors.
Usually O(n), but if using this with storable vectors, should be O(1) due to rewrite rules (but don't rely on this).
Since: 0.1.3.0
Complex
cVec :: KnownNat n => C n -> Vector n ℂ Source #
Convert an hmatrix complex vector (parameterized by its lenth) to a vector-sized storable vector of 'Complex Double's, preserving the length in the type.
This is normally O(1), but will be O(n) if the C was contructed
 with konst or any other replicated-value constructor (like literals
 and fromInteger/fromRational).
vecC :: Vector n ℂ -> C n Source #
Convert a vector-sized storable vector to an hmatrix complex vector (parameterized by its lenth), preserving the length in the type.
O(1)
gvecC :: Vector v ℂ => Vector v n ℂ -> C n Source #
vecC, but generalized to work for all types of sized vectors.
Usually O(n), but if using this with storable vectors, should be O(1) due to rewrite rules (but don't rely on this).
Since: 0.1.3.0
Matrix
Real
lRows :: (KnownNat m, KnownNat n) => L m n -> Vector m (R n) Source #
Split an hmatrix matrix (parameterized by its dimensions) to a vector-sized boxed vector of its rows (as hmatrix vectors).
This is normally O(m*n), but can sometimes be O(m) depending on the
 representation of the L being used.
rowsL :: forall m n. KnownNat n => Vector m (R n) -> L m n Source #
Join together a vector-sized boxed vector of hmatrix vectors to an hmatrix matrix as its rows.
O(m*n)
lCols :: forall m n. (KnownNat m, KnownNat n) => L m n -> Vector n (R m) Source #
Split an hmatrix matrix (parameterized by its dimensions) to a vector-sized boxed vector of its columns (as hmatrix vectors).
This is normally O(m*n), but can sometimes be O(n) depending on the
 representation of the L being used.
colsL :: forall m n. KnownNat m => Vector n (R m) -> L m n Source #
Join together a vector-sized boxed vector of hmatrix vectors to an hmatrix matrix as its columns.
O(m*n)
lVec :: forall m n. (KnownNat m, KnownNat n) => L m n -> Vector (m * n) ℝ Source #
Flatten an hmatrix matrix into a vector-sized storable vector of its items.
This is normally O(m*n), but can sometimes be O(1) depending on the
 representation of the L being used.
Since: 0.1.1.0
vecL :: forall m n. KnownNat n => Vector (m * n) ℝ -> L m n Source #
Shape a vector-sized storable vector of elements into an hmatrix matrix.
O(1)
Since: 0.1.1.0
gvecL :: (KnownNat n, Vector v ℝ) => Vector v (m * n) ℝ -> L m n Source #
vecL, but generalized to work for all types of sized vectors.
Usually O(n), but if using this with storable vectors, should be O(1) due to rewrite rules (but don't rely on this).
Since: 0.1.3.0
Complex
mRows :: forall m n. (KnownNat m, KnownNat n) => M m n -> Vector m (C n) Source #
Split an hmatrix complex matrix (parameterized by its dimensions) to a vector-sized boxed vector of its rows (as hmatrix complex vectors).
This is normally O(m*n), but can sometimes be O(m) depending on the
 representation of the C being used.
rowsM :: forall m n. KnownNat n => Vector m (C n) -> M m n Source #
Join together a vector-sized boxed vector of hmatrix complex vectors to an hmatrix complex matrix as its rows.
O(m*n)
mCols :: forall m n. (KnownNat m, KnownNat n) => M m n -> Vector n (C m) Source #
Split an hmatrix complex matrix (parameterized by its dimensions) to a vector-sized boxed vector of its columns (as hmatrix complex vectors).
This is normally O(m*n), but can sometimes be O(n) depending on the
 representation of the C being used.
colsM :: forall m n. KnownNat m => Vector n (C m) -> M m n Source #
Join together a vector-sized boxed vector of hmatrix complex vectors to an hmatrix complex matrix as its columns.
O(m*n)
mVec :: forall m n. (KnownNat m, KnownNat n) => M m n -> Vector (m * n) ℂ Source #
Flatten an hmatrix complex matrix into a vector-sized storable vector of its items.
This is normally O(m*n), but can sometimes be O(1) depending on the
 representation of the M being used.
Since: 0.1.1.0