manifolds-0.1.0.2: Working with manifolds in a direct, embedding-free way.

Safe HaskellNone
LanguageHaskell2010

Data.LinearMap.HerMetric

Contents

Synopsis

Metric operator types

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

Instances

(HasMetric v, (~) * v (Scalar v), (~) * v (DualSpace v), Floating v) => Floating (HerMetric v) 
(HasMetric v, (~) * v (Scalar v), (~) * v (DualSpace v), Fractional v) => Fractional (HerMetric v) 
(HasMetric v, (~) * v (DualSpace v), Num (Scalar v)) => Num (HerMetric v) 
HasMetric v => VectorSpace (HerMetric v) 
HasMetric v => AdditiveGroup (HerMetric v) 
type Scalar (HerMetric v) = Scalar v 

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

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 by projectors

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

Utility

adjoint :: (HasMetric v, HasMetric w, Scalar w ~ Scalar v) => (v :-* w) -> 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.

class (HasBasis v, VectorSpace (Scalar v), HasTrie (Basis v), VectorSpace (DualSpace v), HasBasis (DualSpace v), Scalar v ~ Scalar (DualSpace v), Basis v ~ Basis (DualSpace v)) => HasMetric v where Source

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

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; the tuple instance actually assumes this to be able to offer an efficient implementation (namely, id) of the isomorphisms.

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

Instances

HasMetric Double 
VectorSpace k => HasMetric (ZeroDim k) 
(HasMetric v, HasMetric w, (~) * (Scalar v) (Scalar w), HasMetric (DualSpace v), (~) * (DualSpace (DualSpace v)) v, HasMetric (DualSpace w), (~) * (DualSpace (DualSpace w)) w) => HasMetric (v, w) 

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

Simple flipped version of <.>^.

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