hmatrix-vector-sized-0.1.3.0: Conversions between hmatrix and vector-sized types
Copyright(c) Justin Le 2018
LicenseBSD3
Maintainerjustin@jle.im
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

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

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).

grVec :: (KnownNat n, Vector v ) => R n -> Vector v n Source #

rVec, but generalized to work for all types of sized vectors.

Usually O(n), but if using this with storable vectors, should have the same characteristics as rVec due to rewrite rules.

Since: 0.1.3.0

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).

gcVec :: (KnownNat n, Vector v ) => C n -> Vector v n Source #

cVec, but generalized to work for all types of sized vectors.

Usually O(n), but if using this with storable vectors, should have the same characteristics as cVec due to rewrite rules.

Since: 0.1.3.0

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

glVec :: (KnownNat m, KnownNat n, Vector v ) => L m n -> Vector v (m * n) Source #

lVec, but generalized to work for all types of sized vectors.

Usually O(m*n), but if using this with storable vectors, should have the same characteristics as lVec due to rewrite rules.

Since: 0.1.3.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

gmVec :: (KnownNat m, KnownNat n, Vector v ) => M m n -> Vector v (m * n) Source #

mVec, but generalized to work for all types of sized vectors.

Usually O(m*n), but if using this with storable vectors, should have the same characteristics as mVec due to rewrite rules.

Since: 0.1.3.0

vecM :: forall m n. KnownNat n => Vector (m * n) -> M m n Source #

Shape a vector-sized storable vector of elements into an hmatrix complex matrix.

O(1)

Since: 0.1.1.0

gvecM :: (KnownNat n, Vector v ) => Vector v (m * n) -> M m n Source #

vecM, but generalized to work for all types of sized vectors.

Usually O(m*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