manifolds-0.2.3.0: Coordinate-free hypersurfaces

Safe HaskellNone
LanguageHaskell2010

Data.LinearMap.HerMetric

Contents

Synopsis

Metric operator types

newtype HerMetric v Source

HerMetric is a portmanteau of Hermitian and metric (in the sense as used in e.g. general relativity – though those particular ones aren't positive definite and thus not really metrics).

Mathematically, there are two directly equivalent ways to describe such a metric: as a bilinear mapping of two vectors to a scalar, or as a linear mapping from a vector space to its dual space. We choose the latter, though you can always as well think of metrics as “quadratic dual vectors”.

Yet other possible interpretations of this type include density matrix (as in quantum mechanics), standard range of statistical fluctuations, and volume element.

Constructors

HerMetric 

Fields

metricMatrix :: Maybe (Linear (Scalar v) v (DualSpace v))
 

Instances

ImpliesMetric HerMetric Source 
(HasMetric v, (~) * v (Scalar v), (~) * v (DualSpace v), Floating v) => Floating (HerMetric v) Source 
(HasMetric v, (~) * v (Scalar v), (~) * v (DualSpace v), Fractional v) => Fractional (HerMetric v) Source 
(HasMetric v, (~) * v (DualSpace v), Num (Scalar v)) => Num (HerMetric v) Source 
(HasMetric v, (~) * (Scalar v) Double, Show (DualSpace v)) => Show (HerMetric v) Source 
HasMetric v => VectorSpace (HerMetric v) Source 
HasMetric v => AdditiveGroup (HerMetric v) Source

Deprecated (this doesn't preserve positive-definiteness)

(HasMetric v, (~) * (Scalar v) ) => HasEigenSystem (HerMetric v) Source 
(HasMetric v, (~) * (Scalar v) ) => HasEigenSystem (HerMetric v, HerMetric v) Source 
type MetricRequirement HerMetric x = (~) * x (Needle x) Source 
type Scalar (HerMetric v) = Scalar v Source 
type EigenVector (HerMetric v) = DualSpace v Source 
type EigenVector (HerMetric v, HerMetric v) = DualSpace v Source 

newtype HerMetric' v Source

A metric on the dual space; equivalent to a linear mapping from the dual space to the original vector space.

Prime-versions of the functions in this module target those dual-space metrics, so we can avoid some explicit handling of double-dual spaces.

Constructors

HerMetric' 

Fields

metricMatrix' :: Maybe (Linear (Scalar v) (DualSpace v) v)
 

Evaluating metrics

metricSq :: HasMetric v => HerMetric v -> v -> Scalar v Source

Evaluate a vector through a metric. For the canonical metric on a Hilbert space, this will be simply magnitudeSq.

metric :: (HasMetric v, Floating (Scalar v)) => HerMetric v -> v -> Scalar v Source

Evaluate a vector's “magnitude” through a metric. This assumes an actual mathematical metric, i.e. positive definite – otherwise the internally used square root may get negative arguments (though it can still produce results if the scalars are complex; however, complex spaces aren't supported yet).

metrics :: (HasMetric v, Floating (Scalar v)) => HerMetric v -> [v] -> Scalar v Source

Square-sum over the metrics for each dual-space vector.

metrics m vs ≡ sqrt . sum $ metricSq m <$> vs

Defining metrics

projector :: HasMetric v => DualSpace v -> HerMetric v Source

A metric on v that simply yields the squared overlap of a vector with the given dual-space reference.

It will perhaps be the most common way of defining HerMetric values to start with such dual-space vectors and superimpose the projectors using the VectorSpace instance; e.g. projector (1,0) ^+^ projector (0,2) yields a hermitian operator describing the ellipsoid span of the vectors e₀ and 2⋅e₁. Metrics generated this way are positive definite if no negative coefficients have been introduced with the *^ scaling operator or with ^-^.

Note: projector a ^+^ projector b ^+^ ... is more efficiently written as projectors [a, b, ...]

projectors :: HasMetric v => [DualSpace v] -> HerMetric v Source

Efficient shortcut for the sumV of multiple projectors.

Metrics induce inner products

spanHilbertSubspace Source

Arguments

:: (HasMetric v, Scalar v ~ s, IsFreeSpace w, Scalar w ~ s) 
=> HerMetric v

Metric to induce the inner product on the Hilbert space.

-> [v]

n linearly independent vectors, to span the subspace w.

-> Option (Embedding (Linear s) w v)

An embedding of the n-dimensional free subspace w (if the given vectors actually span such a space) into the main space v. Regardless of the structure of v (which doesn't need to have an inner product at all!), w will be an InnerSpace with the scalar product defined by the given metric.

spanSubHilbertSpace :: forall s v w. (HasMetric v, InnerSpace v, Scalar v ~ s, IsFreeSpace w, Scalar w ~ s) => [v] -> Option (Embedding (Linear s) w v) Source

Same as spanHilbertSubspace, but with the standard euclideanMetric (i.e., the basis vectors will be orthonormal in the usual sense, in both w and v).

class (FiniteDimensional v, KnownNat (FreeDimension v)) => IsFreeSpace v Source

Class of spaces that directly represent a free vector space, i.e. that are simply n-fold products of the base field. This class basically contains 'ℝ', 'ℝ²', 'ℝ³' etc., in future also the complex and probably integral versions.

Instances

IsFreeSpace Source 
(SmoothScalar s, IsFreeSpace v, (~) * (Scalar v) s, FiniteDimensional s, (~) * s (Scalar s)) => IsFreeSpace (v, s) Source 

One-dimensional axes and product spaces

factoriseMetric :: forall v w. (HasMetric v, HasMetric w, Scalar v ~ , Scalar w ~ ) => HerMetric (v, w) -> (HerMetric v, HerMetric w) Source

Project a metric on each of the factors of a product space. This works by projecting the eigenvectors into both subspaces.

factoriseMetric' :: forall v w. (HasMetric v, HasMetric w, Scalar v ~ , Scalar w ~ ) => HerMetric' (v, w) -> (HerMetric' v, HerMetric' w) Source

productMetric :: forall v w. (HasMetric v, HasMetric w, Scalar v ~ , Scalar w ~ ) => HerMetric v -> HerMetric w -> HerMetric (v, w) Source

productMetric' :: forall v w. (HasMetric v, HasMetric w, Scalar v ~ , Scalar w ~ ) => HerMetric' v -> HerMetric' w -> HerMetric' (v, w) Source

metricAsLength :: HerMetric -> Source

Unsafe version of tryMetricAsLength, only works reliable if the metric is strictly positive definite.

Utility for metrics

transformMetric :: forall s v w. (HasMetric v, HasMetric w, Scalar v ~ s, Scalar w ~ s) => Linear s w v -> HerMetric v -> HerMetric w Source

transformMetric' :: forall s v w. (HasMetric v, HasMetric w, Scalar v ~ s, Scalar w ~ s) => Linear s v w -> HerMetric' v -> HerMetric' w Source

dualCoCoProduct :: (HasMetric v, HasMetric w, Scalar v ~ s, Scalar w ~ s) => Linear s w v -> Linear s w v -> HerMetric w Source

This does something vaguely like \s t -> (s⋅t)², but without actually requiring an inner product on the covectors. Used for calculating the superaffine term of multiplications in Differentiable categories.

dualiseMetric :: HasMetric v => HerMetric (DualSpace v) -> HerMetric' v Source

This doesn't really do anything at all, since HerMetric v is essentially a synonym for HerMetric (DualSpace v).

recipMetric :: HasMetric v => HerMetric' v -> HerMetric v Source

The inverse mapping of a metric tensor. Since a metric maps from a space to its dual, the inverse maps from the dual into the (double-dual) space – i.e., it is a metric on the dual space. Deprecated: the singular case isn't properly handled.

Eigenvectors

eigenSpan :: (HasMetric v, Scalar v ~ ) => HerMetric' v -> [v] Source

The eigenbasis of a metric, with each eigenvector scaled to the square root of the eigenvalue. If the metric is not positive definite (i.e. if it has zero eigenvalues), then the eigenSpan will contain zero vectors.

This constitutes, in a sense, a decomposition of a metric into a set of projector' vectors. If those are sumVed again (use projectors's for this), then the original metric is obtained. (This holds even for non-Hilbert/Banach spaces, although the concept of eigenbasis and “scaled length” doesn't really make sense there.)

eigenCoSpan :: (HasMetric v, Scalar v ~ ) => HerMetric' v -> [DualSpace v] Source

The reciprocal-space counterparts of the nonzero-EV eigenvectors, as can be obtained from eigenSpan. The systems of vectors/dual vectors behave as orthonormal groups WRT each other, i.e. for each f in eigenCoSpan m there will be exactly one v in eigenSpan m such that f.^v ≡ 1; the other f.^v pairings are zero.

Furthermore, metric m f ≡ 1 for each f in the co-span, which might be seen as the actual defining characteristic of these span/co-span systems.

class HasEigenSystem m where Source

Associated Types

type EigenVector m :: * Source

Methods

eigenSystem :: m -> ([Stiefel1 (EigenVector m)], [(EigenVector m, DualSpace (EigenVector m))]) Source

Generalised combination of eigenSpan and eigenCoSpan; this will give a maximum spanning set of vector-covector pairs (f,v) such that f.^v ≡ 1 and metric m f ≡ 1, whereas all f and v' from different tuples are orthogonal. It also yields the kernel of singular metric, spanned by a set of stiefel-manifold points, i.e. vectors of unspecified length that correspond to the eigenvalue 0.

You may also consider this as a factorisation of a linear operator 𝐴 : 𝑉 → 𝑉' into mappings 𝑅 : 𝑉 → ℝⁿ and 𝐿 : ℝⁿ → 𝑉' (or, equivalently because ℝⁿ is a Hilbert space, 𝑅' : ℝⁿ → V' and 𝐿' : V → ℝⁿ, which gives you an SVD-style inverse).

Scaling operations

metriNormalise :: (HasMetric v, Floating (Scalar v)) => HerMetric v -> v -> v Source

Divide a vector by its own norm, according to metric, i.e. normalise it or “project to the metric's boundary”.

metriScale :: (HasMetric v, Floating (Scalar v)) => HerMetric v -> v -> v Source

“Anti-normalise” a vector: multiply with its own norm, according to metric.

adjoint :: (HasMetric v, HasMetric w, s ~ Scalar v, s ~ Scalar w) => Linear s v w -> Linear s (DualSpace w) (DualSpace v) Source

Transpose a linear operator. Contrary to popular belief, this does not just inverse the direction of mapping between the spaces, but also switch to their duals.

applyLinMapMetric' :: forall v w. (HasMetric v, HasMetric w, Scalar v ~ , Scalar w ~ ) => HerMetric' (Linear v w) -> v -> HerMetric' w Source

The dual-space class

class (FiniteDimensional v, FiniteDimensional (DualSpace v), VectorSpace (DualSpace v), HasBasis (DualSpace v), MetricScalar (Scalar v), Scalar v ~ Scalar (DualSpace v)) => HasMetric' v where Source

While the main purpose of this class is to express HerMetric, it's actually all about dual spaces.

Minimal complete definition

(<.>^), functional, doubleDual, doubleDual'

Associated Types

type DualSpace v :: * Source

DualSpace v is isomorphic to the space of linear functionals on v, i.e. v :-* Scalar v. Typically (for all Hilbert- / InnerSpaces) this is in turn isomorphic to v itself, which will be rather more efficient (hence the distinction between a vector space and its dual is often neglected or reduced to “column vs row vectors”). Mathematically though, it makes sense to keep the concepts apart, even if ultimately DualSpace v ~ v (which needs not always be the case, though!).

Methods

(<.>^) :: DualSpace v -> v -> Scalar v infixr 7 Source

Apply a dual space vector (aka linear functional) to a vector.

functional :: (v -> Scalar v) -> DualSpace v Source

Interpret a functional as a dual-space vector. Like linear, this assumes (completely unchecked) that the supplied function is linear.

doubleDual :: HasMetric' (DualSpace v) => v -> DualSpace (DualSpace v) Source

While isomorphism between a space and its dual isn't generally canonical, the double-dual space should be canonically isomorphic in pretty much all relevant cases. Indeed, it is recommended that they are the very same type; this condition is enforced by the HasMetric constraint (which is recommended over using HasMetric' itself in signatures).

doubleDual' :: HasMetric' (DualSpace v) => DualSpace (DualSpace v) -> v Source

basisInDual :: Tagged v (Basis v -> Basis (DualSpace v)) Source

Instances

HasMetric' Double Source 
MetricScalar k => HasMetric' (ZeroDim k) Source 
(HasMetric v, HasMetric w, (~) * (Scalar v) (Scalar w)) => HasMetric' (v, w) Source 
(HasMetric v, HasMetric w, (~) * s (Scalar v), (~) * s (Scalar w)) => HasMetric' (Linear s v w) Source 

(^<.>) :: HasMetric v => v -> DualSpace v -> Scalar v infixr 7 Source

Simple flipped version of <.>^.

Fundamental requirements

type MetricScalar s = (SmoothScalar s, Ord s) Source

Constraint that a space's scalars need to fulfill so it can be used for HerMetric.

class (HasBasis v, HasTrie (Basis v), SmoothScalar (Scalar v)) => FiniteDimensional v where Source

Many linear algebra operations are best implemented via packed, dense Matrixes. For one thing, that makes common general vector operations quite efficient, in particular on high-dimensional spaces. More importantly, hmatrix offers linear facilities such as inverse and eigenbasis transformations, which aren't available in the vector-space library yet. But the classes from that library are strongly preferrable to plain matrices and arrays, conceptually.

The FiniteDimensional class is used to convert between both representations. It would be nice not to have the requirement of finite dimension on HerMetric, but it's probably not feasible to get rid of it in forseeable time.

Instead of the run-time dimension information, we would rather have a compile-time type Dimension v :: Nat, but type-level naturals are not mature enough yet. This will almost certainly change in the future.

Minimal complete definition

dimension, basisIndex, indexBasis

Methods

dimension :: Tagged v Int Source

basisIndex :: Tagged v (Basis v -> Int) Source

indexBasis :: Tagged v (Int -> Basis v) Source

Index must be in [0 .. dimension-1], otherwise this is undefined.

completeBasis :: Tagged v [Basis v] Source

completeBasisValues :: [v] Source

asPackedVector :: v -> Vector (Scalar v) Source

asPackedMatrix :: (FiniteDimensional w, Scalar w ~ Scalar v) => (v :-* w) -> Matrix (Scalar v) Source

fromPackedVector :: Vector (Scalar v) -> v Source

fromPackedMatrix :: (FiniteDimensional w, Scalar w ~ Scalar v) => Matrix (Scalar v) -> v :-* w Source

Misc

newtype Stiefel1 v Source

The n-th Stiefel manifold is the space of all possible configurations of n orthonormal vectors. In the case n = 1, simply the subspace of normalised vectors, i.e. equivalent to the UnitSphere. Even so, it strictly speaking requires the containing space to be at least metric (if not Hilbert); we would however like to be able to use this concept also in spaces with no inner product, therefore we define this space not as normalised vectors, but rather as all vectors modulo scaling by positive factors.

Constructors

Stiefel1 

Fields

getStiefel1N :: DualSpace v
 

covariance :: forall v w. (HasMetric v, HasMetric w, Scalar v ~ , Scalar w ~ ) => HerMetric' (v, w) -> Option (Linear v w) Source

outerProducts :: (HasMetric v, FiniteDimensional w, Scalar v ~ s, Scalar w ~ s) => [(w, DualSpace v)] -> Linear s v w Source