manifolds-0.5.1.0: Coordinate-free hypersurfaces

Copyright(c) Justus Sagemüller 2015
LicenseGPL v3
Maintainer(@) jsag $ hvl.no
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Data.Manifold.PseudoAffine

Contents

Description

This is the second prototype of a manifold class. It appears to give considerable advantages over Manifold, so that class will probably soon be replaced with the one we define here (though PseudoAffine does not follow the standard notion of a manifold very closely, it should work quite equivalently for pretty much all Haskell types that qualify as manifolds).

Manifolds are interesting as objects of various categories, from continuous to diffeomorphic. At the moment, we mainly focus on region-wise differentiable functions, which are a promising compromise between flexibility of definition and provability of analytic properties. In particular, they are well-suited for visualisation purposes.

The classes in this module are mostly aimed at manifolds without boundary. Manifolds with boundary (which we call MWBound, never manifold!) are more or less treated as a disjoint sum of the interior and the boundary. To understand how this module works, best first forget about boundaries – in this case, Interior x ~ x, fromInterior and toInterior are trivial, and .+~|, |-~. and betweenBounds are irrelevant. The manifold structure of the boundary itself is not considered at all here.

Synopsis

Manifold class

class (PseudoAffine m, LSpace (Needle m)) => Manifold m where Source #

See Semimanifold and PseudoAffine for the methods.

Minimal complete definition

Nothing

Methods

inInterior :: m -> Interior m Source #

inInterior :: m ~ Interior m => m -> Interior m Source #

class AdditiveGroup (Needle x) => Semimanifold x where #

Minimal complete definition

((.+~^) | fromInterior), toInterior, translateP

Associated Types

type Needle x :: Type #

The space of “natural” ways starting from some reference point and going to some particular target point. Hence, the name: like a compass needle, but also with an actual length. For affine spaces, Needle is simply the space of line segments (aka vectors) between two points, i.e. the same as Diff. The AffineManifold constraint makes that requirement explicit.

This space should be isomorphic to the tangent space (and is in fact used somewhat synonymously).

type Interior x :: Type #

Manifolds with boundary are a bit tricky. We support such manifolds, but carry out most calculations only in “the fleshy part” – the interior, which is an “infinite space”, so you can arbitrarily scale paths.

The default implementation is Interior x = x, which corresponds to a manifold that has no boundary to begin with.

Methods

(.+~^) :: Interior x -> Needle x -> x infixl 6 #

Generalised translation operation. Note that the result will always also be in the interior; scaling up the needle can only get you ever closer to a boundary.

fromInterior :: Interior x -> x #

id sans boundary.

toInterior :: x -> Maybe (Interior x) #

translateP :: Tagged x (Interior x -> Needle x -> Interior x) #

The signature of .+~^ should really be Interior x -> Needle x -> Interior x, only, this is not possible because it only consists of non-injective type families. The solution is this tagged signature, which is of course rather unwieldy. That's why .+~^ has the stronger, but easier usable signature. Without boundary, these functions should be equivalent, i.e. translateP = Tagged (.+~^).

(.-~^) :: Interior x -> Needle x -> x infixl 6 #

Shorthand for \p v -> p .+~^ negateV v, which should obey the asymptotic law

p .-~^ v .+~^ v ≅ p

Meaning: if v is scaled down with sufficiently small factors η, then the difference (p.-~^v.+~^v) .-~. p should scale down even faster: as O (η²). For large vectors, it will however behave differently, except in flat spaces (where all this should be equivalent to the AffineSpace instance).

semimanifoldWitness :: SemimanifoldWitness x #

Instances
Semimanifold Double 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle Double :: Type #

type Interior Double :: Type #

Semimanifold Float 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle Float :: Type #

type Interior Float :: Type #

Semimanifold Rational 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle Rational :: Type #

type Interior Rational :: Type #

Semimanifold S⁰ 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle S⁰ :: Type #

type Interior S⁰ :: Type #

Semimanifold ℝP⁰ 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle ℝP⁰ :: Type #

type Interior ℝP⁰ :: Type #

Semimanifold  
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle :: Type #

type Interior :: Type #

Semimanifold ℝP¹ 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle ℝP¹ :: Type #

type Interior ℝP¹ :: Type #

Semimanifold Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

Associated Types

type Needle :: Type #

type Interior :: Type #

Semimanifold ℝP² Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

Associated Types

type Needle ℝP² :: Type #

type Interior ℝP² :: Type #

Semimanifold  
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle :: Type #

type Interior :: Type #

AdditiveGroup (DualVector (Needle (VRep m))) => Semimanifold (GenericNeedle' m) 
Instance details

Defined in Math.LinearMap.Category.Class

Associated Types

type Needle (GenericNeedle' m) :: Type #

type Interior (GenericNeedle' m) :: Type #

Methods

(.+~^) :: Interior (GenericNeedle' m) -> Needle (GenericNeedle' m) -> GenericNeedle' m #

fromInterior :: Interior (GenericNeedle' m) -> GenericNeedle' m #

toInterior :: GenericNeedle' m -> Maybe (Interior (GenericNeedle' m)) #

translateP :: Tagged (GenericNeedle' m) (Interior (GenericNeedle' m) -> Needle (GenericNeedle' m) -> Interior (GenericNeedle' m)) #

(.-~^) :: Interior (GenericNeedle' m) -> Needle (GenericNeedle' m) -> GenericNeedle' m #

semimanifoldWitness :: SemimanifoldWitness (GenericNeedle' m) #

Semimanifold (ZeroDim k) 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle (ZeroDim k) :: Type #

type Interior (ZeroDim k) :: Type #

AdditiveGroup (Needle (VRep x)) => Semimanifold (GenericNeedle x) 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle (GenericNeedle x) :: Type #

type Interior (GenericNeedle x) :: Type #

Semimanifold (VRep x) => Semimanifold (GenericInterior x) 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle (GenericInterior x) :: Type #

type Interior (GenericInterior x) :: Type #

ConeSemimfd m => Semimanifold (CD¹ m) Source # 
Instance details

Defined in Data.Manifold.Cone

Associated Types

type Needle (CD¹ m) :: Type #

type Interior (CD¹ m) :: Type #

ConeSemimfd m => Semimanifold (Cℝay m) Source # 
Instance details

Defined in Data.Manifold.Cone

Associated Types

type Needle (Cℝay m) :: Type #

type Interior (Cℝay m) :: Type #

(LinearSpace v, FiniteFreeSpace v, FiniteFreeSpace (DualVector v), StiefelScalar (Scalar v)) => Semimanifold (Stiefel1 v) Source # 
Instance details

Defined in Data.Manifold.Types

Associated Types

type Needle (Stiefel1 v) :: Type #

type Interior (Stiefel1 v) :: Type #

AffineManifold x => Semimanifold (Shade' x) Source # 
Instance details

Defined in Data.Manifold.Shade

Associated Types

type Needle (Shade' x) :: Type #

type Interior (Shade' x) :: Type #

PseudoAffine x => Semimanifold (Shade x) Source # 
Instance details

Defined in Data.Manifold.Shade

Associated Types

type Needle (Shade x) :: Type #

type Interior (Shade x) :: Type #

(Semimanifold a, Semimanifold b) => Semimanifold (a, b) 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle (a, b) :: Type #

type Interior (a, b) :: Type #

Methods

(.+~^) :: Interior (a, b) -> Needle (a, b) -> (a, b) #

fromInterior :: Interior (a, b) -> (a, b) #

toInterior :: (a, b) -> Maybe (Interior (a, b)) #

translateP :: Tagged (a, b) (Interior (a, b) -> Needle (a, b) -> Interior (a, b)) #

(.-~^) :: Interior (a, b) -> Needle (a, b) -> (a, b) #

semimanifoldWitness :: SemimanifoldWitness (a, b) #

(LinearSpace (a n), Needle (a n) ~ a n, Interior (a n) ~ a n) => Semimanifold (Point a n) Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

Associated Types

type Needle (Point a n) :: Type #

type Interior (Point a n) :: Type #

Methods

(.+~^) :: Interior (Point a n) -> Needle (Point a n) -> Point a n #

fromInterior :: Interior (Point a n) -> Point a n #

toInterior :: Point a n -> Maybe (Interior (Point a n)) #

translateP :: Tagged (Point a n) (Interior (Point a n) -> Needle (Point a n) -> Interior (Point a n)) #

(.-~^) :: Interior (Point a n) -> Needle (Point a n) -> Point a n #

semimanifoldWitness :: SemimanifoldWitness (Point a n) #

(Generic1 f, TensorSpace y, TensorSpace (f y), Scalar (f y) ~ Scalar y, Monoidal f (LinearFunction (Scalar y)) (LinearFunction (Scalar y))) => Semimanifold (LinearApplicativeSpace f y) 
Instance details

Defined in Math.LinearMap.Category.Instances

Associated Types

type Needle (LinearApplicativeSpace f y) :: Type #

type Interior (LinearApplicativeSpace f y) :: Type #

Methods

(.+~^) :: Interior (LinearApplicativeSpace f y) -> Needle (LinearApplicativeSpace f y) -> LinearApplicativeSpace f y #

fromInterior :: Interior (LinearApplicativeSpace f y) -> LinearApplicativeSpace f y #

toInterior :: LinearApplicativeSpace f y -> Maybe (Interior (LinearApplicativeSpace f y)) #

translateP :: Tagged (LinearApplicativeSpace f y) (Interior (LinearApplicativeSpace f y) -> Needle (LinearApplicativeSpace f y) -> Interior (LinearApplicativeSpace f y)) #

(.-~^) :: Interior (LinearApplicativeSpace f y) -> Needle (LinearApplicativeSpace f y) -> LinearApplicativeSpace f y #

semimanifoldWitness :: SemimanifoldWitness (LinearApplicativeSpace f y) #

(TensorSpace v, Scalar v ~ s) => Semimanifold (SymmetricTensor s v) 
Instance details

Defined in Math.LinearMap.Category.Instances

Associated Types

type Needle (SymmetricTensor s v) :: Type #

type Interior (SymmetricTensor s v) :: Type #

(ParallelTransporting ((->) :: Type -> Type -> Type) m (Interior f), Semimanifold f, ParallelTransporting (LinearFunction s) (Needle m) (Needle f), s ~ Scalar (Needle m)) => Semimanifold (FibreBundle m f) Source # 
Instance details

Defined in Data.Manifold.FibreBundle

Associated Types

type Needle (FibreBundle m f) :: Type #

type Interior (FibreBundle m f) :: Type #

Semimanifold x => Semimanifold (WithAny x y) Source # 
Instance details

Defined in Data.Manifold.Shade

Associated Types

type Needle (WithAny x y) :: Type #

type Interior (WithAny x y) :: Type #

Semimanifold a => Semimanifold (Rec0 a s) 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle (Rec0 a s) :: Type #

type Interior (Rec0 a s) :: Type #

Methods

(.+~^) :: Interior (Rec0 a s) -> Needle (Rec0 a s) -> Rec0 a s #

fromInterior :: Interior (Rec0 a s) -> Rec0 a s #

toInterior :: Rec0 a s -> Maybe (Interior (Rec0 a s)) #

translateP :: Tagged (Rec0 a s) (Interior (Rec0 a s) -> Needle (Rec0 a s) -> Interior (Rec0 a s)) #

(.-~^) :: Interior (Rec0 a s) -> Needle (Rec0 a s) -> Rec0 a s #

semimanifoldWitness :: SemimanifoldWitness (Rec0 a s) #

(Semimanifold a, Semimanifold b, Semimanifold c) => Semimanifold (a, b, c) 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle (a, b, c) :: Type #

type Interior (a, b, c) :: Type #

Methods

(.+~^) :: Interior (a, b, c) -> Needle (a, b, c) -> (a, b, c) #

fromInterior :: Interior (a, b, c) -> (a, b, c) #

toInterior :: (a, b, c) -> Maybe (Interior (a, b, c)) #

translateP :: Tagged (a, b, c) (Interior (a, b, c) -> Needle (a, b, c) -> Interior (a, b, c)) #

(.-~^) :: Interior (a, b, c) -> Needle (a, b, c) -> (a, b, c) #

semimanifoldWitness :: SemimanifoldWitness (a, b, c) #

(AdditiveGroup (DualVector (f p)), AdditiveGroup (DualVector (g p))) => Semimanifold (GenericTupleDual f g p) 
Instance details

Defined in Math.LinearMap.Category.Class

Associated Types

type Needle (GenericTupleDual f g p) :: Type #

type Interior (GenericTupleDual f g p) :: Type #

Methods

(.+~^) :: Interior (GenericTupleDual f g p) -> Needle (GenericTupleDual f g p) -> GenericTupleDual f g p #

fromInterior :: Interior (GenericTupleDual f g p) -> GenericTupleDual f g p #

toInterior :: GenericTupleDual f g p -> Maybe (Interior (GenericTupleDual f g p)) #

translateP :: Tagged (GenericTupleDual f g p) (Interior (GenericTupleDual f g p) -> Needle (GenericTupleDual f g p) -> Interior (GenericTupleDual f g p)) #

(.-~^) :: Interior (GenericTupleDual f g p) -> Needle (GenericTupleDual f g p) -> GenericTupleDual f g p #

semimanifoldWitness :: SemimanifoldWitness (GenericTupleDual f g p) #

(LinearSpace v, TensorSpace w, Scalar v ~ s, Scalar w ~ s) => Semimanifold (LinearMap s v w) 
Instance details

Defined in Math.LinearMap.Category.Class

Associated Types

type Needle (LinearMap s v w) :: Type #

type Interior (LinearMap s v w) :: Type #

(TensorSpace v, TensorSpace w, Scalar v ~ s, Scalar w ~ s) => Semimanifold (Tensor s v w) 
Instance details

Defined in Math.LinearMap.Category.Class

Associated Types

type Needle (Tensor s v w) :: Type #

type Interior (Tensor s v w) :: Type #

Methods

(.+~^) :: Interior (Tensor s v w) -> Needle (Tensor s v w) -> Tensor s v w #

fromInterior :: Interior (Tensor s v w) -> Tensor s v w #

toInterior :: Tensor s v w -> Maybe (Interior (Tensor s v w)) #

translateP :: Tagged (Tensor s v w) (Interior (Tensor s v w) -> Needle (Tensor s v w) -> Interior (Tensor s v w)) #

(.-~^) :: Interior (Tensor s v w) -> Needle (Tensor s v w) -> Tensor s v w #

semimanifoldWitness :: SemimanifoldWitness (Tensor s v w) #

VectorSpace w => Semimanifold (LinearFunction s v w) 
Instance details

Defined in Math.LinearMap.Asserted

Associated Types

type Needle (LinearFunction s v w) :: Type #

type Interior (LinearFunction s v w) :: Type #

(Semimanifold (f p), Semimanifold (g p)) => Semimanifold (NeedleProductSpace f g p) 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle (NeedleProductSpace f g p) :: Type #

type Interior (NeedleProductSpace f g p) :: Type #

(Semimanifold (f p), Semimanifold (g p)) => Semimanifold (InteriorProductSpace f g p) 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle (InteriorProductSpace f g p) :: Type #

type Interior (InteriorProductSpace f g p) :: Type #

(Atlas x, HasTrie (ChartIndex x), LinearSpace (Needle x), Scalar (Needle x) ~ s, Manifold y, Scalar (Needle y) ~ s) => Semimanifold (Affine s x y) Source # 
Instance details

Defined in Data.Function.Affine

Associated Types

type Needle (Affine s x y) :: Type #

type Interior (Affine s x y) :: Type #

Methods

(.+~^) :: Interior (Affine s x y) -> Needle (Affine s x y) -> Affine s x y #

fromInterior :: Interior (Affine s x y) -> Affine s x y #

toInterior :: Affine s x y -> Maybe (Interior (Affine s x y)) #

translateP :: Tagged (Affine s x y) (Interior (Affine s x y) -> Needle (Affine s x y) -> Interior (Affine s x y)) #

(.-~^) :: Interior (Affine s x y) -> Needle (Affine s x y) -> Affine s x y #

semimanifoldWitness :: SemimanifoldWitness (Affine s x y) #

(Semimanifold (f p), Semimanifold (g p)) => Semimanifold ((f :*: g) p) 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle ((f :*: g) p) :: Type #

type Interior ((f :*: g) p) :: Type #

Methods

(.+~^) :: Interior ((f :*: g) p) -> Needle ((f :*: g) p) -> (f :*: g) p #

fromInterior :: Interior ((f :*: g) p) -> (f :*: g) p #

toInterior :: (f :*: g) p -> Maybe (Interior ((f :*: g) p)) #

translateP :: Tagged ((f :*: g) p) (Interior ((f :*: g) p) -> Needle ((f :*: g) p) -> Interior ((f :*: g) p)) #

(.-~^) :: Interior ((f :*: g) p) -> Needle ((f :*: g) p) -> (f :*: g) p #

semimanifoldWitness :: SemimanifoldWitness ((f :*: g) p) #

Semimanifold (f p) => Semimanifold (M1 i c f p) 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Associated Types

type Needle (M1 i c f p) :: Type #

type Interior (M1 i c f p) :: Type #

Methods

(.+~^) :: Interior (M1 i c f p) -> Needle (M1 i c f p) -> M1 i c f p #

fromInterior :: Interior (M1 i c f p) -> M1 i c f p #

toInterior :: M1 i c f p -> Maybe (Interior (M1 i c f p)) #

translateP :: Tagged (M1 i c f p) (Interior (M1 i c f p) -> Needle (M1 i c f p) -> Interior (M1 i c f p)) #

(.-~^) :: Interior (M1 i c f p) -> Needle (M1 i c f p) -> M1 i c f p #

semimanifoldWitness :: SemimanifoldWitness (M1 i c f p) #

type Needle' x = DualVector (Needle x) Source #

A co-needle can be understood as a “paper stack”, with which you can measure the length that a needle reaches in a given direction by counting the number of holes punched through them.

class Semimanifold x => PseudoAffine x where #

This is the class underlying manifolds. (Manifold only precludes boundaries and adds an extra constraint that would be circular if it was in a single class. You can always just use Manifold as a constraint in your signatures, but you must define only PseudoAffine for manifold types – the Manifold instance follows universally from this, if 'Interior x ~ x.)

The interface is (boundaries aside) almost identical to the better-known AffineSpace class, but we don't require associativity of .+~^ with ^+^ – except in an asymptotic sense for small vectors.

That innocent-looking change makes the class applicable to vastly more general types: while an affine space is basically nothing but a vector space without particularly designated origin, a pseudo-affine space can have nontrivial topology on the global scale, and yet be used in practically the same way as an affine space. At least the usual spheres and tori make good instances, perhaps the class is in fact equivalent to manifolds in their usual maths definition (with an atlas of charts: a family of overlapping regions of the topological space, each homeomorphic to the Needle vector space or some simply-connected subset thereof).

Minimal complete definition

(.-~.) | (.-~!)

Methods

(.-~.) :: x -> x -> Maybe (Needle x) infix 6 #

The path reaching from one point to another. Should only yield Nothing if

  • The points are on disjoint segments of a non–path-connected space.
  • Either of the points is on the boundary. Use |-~. to deal with this.

On manifolds, the identity

p .+~^ (q.-~.p) ≡ q

should hold, at least save for floating-point precision limits etc..

.-~. and .+~^ only really work in manifolds without boundary. If you consider the path between two points, one of which lies on the boundary, it can't really be possible to scale this path any longer – it would have to reach “out of the manifold”. To adress this problem, these functions basically consider only the interior of the space.

(.-~!) :: x -> x -> Needle x infix 6 #

Unsafe version of .-~.. If the two points lie in disjoint regions, the behaviour is undefined.

pseudoAffineWitness :: PseudoAffineWitness x #

Instances
PseudoAffine Double 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

PseudoAffine Float 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

PseudoAffine Rational 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

PseudoAffine S⁰ 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

PseudoAffine ℝP⁰ 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

PseudoAffine  
Instance details

Defined in Math.Manifold.Core.PseudoAffine

PseudoAffine ℝP¹ 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

PseudoAffine Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

PseudoAffine ℝP² Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

PseudoAffine  
Instance details

Defined in Math.Manifold.Core.PseudoAffine

AdditiveGroup (DualVector (Needle (VRep m))) => PseudoAffine (GenericNeedle' m) 
Instance details

Defined in Math.LinearMap.Category.Class

Methods

(.-~.) :: GenericNeedle' m -> GenericNeedle' m -> Maybe (Needle (GenericNeedle' m)) #

(.-~!) :: GenericNeedle' m -> GenericNeedle' m -> Needle (GenericNeedle' m) #

pseudoAffineWitness :: PseudoAffineWitness (GenericNeedle' m) #

PseudoAffine (ZeroDim k) 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

AdditiveGroup (Needle (VRep x)) => PseudoAffine (GenericNeedle x) 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

PseudoAffine (VRep x) => PseudoAffine (GenericInterior x) 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

(LinearSpace v, FiniteFreeSpace v, FiniteFreeSpace (DualVector v), StiefelScalar (Scalar v)) => PseudoAffine (Stiefel1 v) Source # 
Instance details

Defined in Data.Manifold.Types

(PseudoAffine a, PseudoAffine b) => PseudoAffine (a, b) 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Methods

(.-~.) :: (a, b) -> (a, b) -> Maybe (Needle (a, b)) #

(.-~!) :: (a, b) -> (a, b) -> Needle (a, b) #

pseudoAffineWitness :: PseudoAffineWitness (a, b) #

(LinearSpace (a n), Needle (a n) ~ a n, Interior (a n) ~ a n) => PseudoAffine (Point a n) Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

Methods

(.-~.) :: Point a n -> Point a n -> Maybe (Needle (Point a n)) #

(.-~!) :: Point a n -> Point a n -> Needle (Point a n) #

pseudoAffineWitness :: PseudoAffineWitness (Point a n) #

(Generic1 f, TensorSpace y, TensorSpace (f y), Scalar (f y) ~ Scalar y, Monoidal f (LinearFunction (Scalar y)) (LinearFunction (Scalar y))) => PseudoAffine (LinearApplicativeSpace f y) 
Instance details

Defined in Math.LinearMap.Category.Instances

Methods

(.-~.) :: LinearApplicativeSpace f y -> LinearApplicativeSpace f y -> Maybe (Needle (LinearApplicativeSpace f y)) #

(.-~!) :: LinearApplicativeSpace f y -> LinearApplicativeSpace f y -> Needle (LinearApplicativeSpace f y) #

pseudoAffineWitness :: PseudoAffineWitness (LinearApplicativeSpace f y) #

(TensorSpace v, Scalar v ~ s) => PseudoAffine (SymmetricTensor s v) 
Instance details

Defined in Math.LinearMap.Category.Instances

(ParallelTransporting ((->) :: Type -> Type -> Type) m f, ParallelTransporting ((->) :: Type -> Type -> Type) m (Interior f), PseudoAffine f, ParallelTransporting (LinearFunction s) (Needle m) (Needle f), s ~ Scalar (Needle m)) => PseudoAffine (FibreBundle m f) Source # 
Instance details

Defined in Data.Manifold.FibreBundle

PseudoAffine x => PseudoAffine (WithAny x y) Source # 
Instance details

Defined in Data.Manifold.Shade

PseudoAffine a => PseudoAffine (Rec0 a s) 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Methods

(.-~.) :: Rec0 a s -> Rec0 a s -> Maybe (Needle (Rec0 a s)) #

(.-~!) :: Rec0 a s -> Rec0 a s -> Needle (Rec0 a s) #

pseudoAffineWitness :: PseudoAffineWitness (Rec0 a s) #

(PseudoAffine a, PseudoAffine b, PseudoAffine c) => PseudoAffine (a, b, c) 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Methods

(.-~.) :: (a, b, c) -> (a, b, c) -> Maybe (Needle (a, b, c)) #

(.-~!) :: (a, b, c) -> (a, b, c) -> Needle (a, b, c) #

pseudoAffineWitness :: PseudoAffineWitness (a, b, c) #

(AdditiveGroup (DualVector (f p)), AdditiveGroup (DualVector (g p))) => PseudoAffine (GenericTupleDual f g p) 
Instance details

Defined in Math.LinearMap.Category.Class

Methods

(.-~.) :: GenericTupleDual f g p -> GenericTupleDual f g p -> Maybe (Needle (GenericTupleDual f g p)) #

(.-~!) :: GenericTupleDual f g p -> GenericTupleDual f g p -> Needle (GenericTupleDual f g p) #

pseudoAffineWitness :: PseudoAffineWitness (GenericTupleDual f g p) #

(LinearSpace v, TensorSpace w, Scalar v ~ s, Scalar w ~ s) => PseudoAffine (LinearMap s v w) 
Instance details

Defined in Math.LinearMap.Category.Class

Methods

(.-~.) :: LinearMap s v w -> LinearMap s v w -> Maybe (Needle (LinearMap s v w)) #

(.-~!) :: LinearMap s v w -> LinearMap s v w -> Needle (LinearMap s v w) #

pseudoAffineWitness :: PseudoAffineWitness (LinearMap s v w) #

(TensorSpace v, TensorSpace w, Scalar v ~ s, Scalar w ~ s) => PseudoAffine (Tensor s v w) 
Instance details

Defined in Math.LinearMap.Category.Class

Methods

(.-~.) :: Tensor s v w -> Tensor s v w -> Maybe (Needle (Tensor s v w)) #

(.-~!) :: Tensor s v w -> Tensor s v w -> Needle (Tensor s v w) #

pseudoAffineWitness :: PseudoAffineWitness (Tensor s v w) #

VectorSpace w => PseudoAffine (LinearFunction s v w) 
Instance details

Defined in Math.LinearMap.Asserted

(PseudoAffine (f p), PseudoAffine (g p)) => PseudoAffine (NeedleProductSpace f g p) 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

(PseudoAffine (f p), PseudoAffine (g p)) => PseudoAffine (InteriorProductSpace f g p) 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

(Atlas x, HasTrie (ChartIndex x), LinearSpace (Needle x), Scalar (Needle x) ~ s, Manifold y, Scalar (Needle y) ~ s) => PseudoAffine (Affine s x y) Source # 
Instance details

Defined in Data.Function.Affine

Methods

(.-~.) :: Affine s x y -> Affine s x y -> Maybe (Needle (Affine s x y)) #

(.-~!) :: Affine s x y -> Affine s x y -> Needle (Affine s x y) #

pseudoAffineWitness :: PseudoAffineWitness (Affine s x y) #

(PseudoAffine (f p), PseudoAffine (g p)) => PseudoAffine ((f :*: g) p) 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Methods

(.-~.) :: (f :*: g) p -> (f :*: g) p -> Maybe (Needle ((f :*: g) p)) #

(.-~!) :: (f :*: g) p -> (f :*: g) p -> Needle ((f :*: g) p) #

pseudoAffineWitness :: PseudoAffineWitness ((f :*: g) p) #

PseudoAffine (f p) => PseudoAffine (M1 i c f p) 
Instance details

Defined in Math.Manifold.Core.PseudoAffine

Methods

(.-~.) :: M1 i c f p -> M1 i c f p -> Maybe (Needle (M1 i c f p)) #

(.-~!) :: M1 i c f p -> M1 i c f p -> Needle (M1 i c f p) #

pseudoAffineWitness :: PseudoAffineWitness (M1 i c f p) #

Type definitions

Needles

newtype Local x Source #

A point on a manifold, as seen from a nearby reference point.

Constructors

Local 

Fields

Instances
Show (Needle x) => Show (Local x) Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

Methods

showsPrec :: Int -> Local x -> ShowS #

show :: Local x -> String #

showList :: [Local x] -> ShowS #

(⊙+^) :: forall x proxy. Semimanifold x => Interior x -> Needle x -> proxy x -> Interior x infix 6 Source #

Proxy-version of translateP.

(!+~^) :: forall x. (Semimanifold x, HasCallStack) => x -> Needle x -> x infixl 6 Source #

Boundary-unsafe version of .+~^.

Metrics

type Metric x = Norm (Needle x) Source #

The word “metric” is used in the sense as in general relativity. Actually this is just the type of scalar products on the tangent space. The actual metric is the function x -> x -> Scalar (Needle x) defined by

\p q -> m |$| (p.-~!q)

type RieMetric x = x -> Metric x Source #

A Riemannian metric assigns each point on a manifold a scalar product on the tangent space. Note that this association is not continuous, because the charts/tangent spaces in the bundle are a priori disjoint. However, for a proper Riemannian metric, all arising expressions of scalar products from needles between points on the manifold ought to be differentiable.

type RieMetric' x = x -> Metric' x Source #

Constraints

data SemimanifoldWitness x where #

This is the reified form of the property that the interior of a semimanifold is a manifold. These constraints would ideally be expressed directly as superclass constraints, but that would require the UndecidableSuperclasses extension, which is not reliable yet.

Also, if all those equality constraints are in scope, GHC tends to infer needlessly complicated types like Interior (Interior (Needle (Interior x))), which is the same as just Needle x.

data BoundarylessWitness m where #

Constructors

BoundarylessWitness :: forall m. (Semimanifold m, Interior m ~ m) => BoundarylessWitness m 

type WithField s c x = (c x, s ~ Scalar (Needle x), s ~ Scalar (Needle' x)) Source #

Require some constraint on a manifold, and also fix the type of the manifold's underlying field. For example, WithField ℝ HilbertManifold v constrains v to be a real (i.e., Double-) Hilbert space. Note that for this to compile, you will in general need the -XLiberalTypeSynonyms extension (except if the constraint is an actual type class (like Manifold): only those can always be partially applied, for type constraints this is by default not allowed).

type LocallyScalable s x = (PseudoAffine x, LSpace (Needle x), s ~ Scalar (Needle x), s ~ Scalar (Needle' x), Num' s) Source #

Local functions

type LocalAffine x y = (Needle y, LocalLinear x y) Source #

Misc

alerpB :: (AffineSpace x, VectorSpace (Diff x), Scalar (Diff x) ~ ) => x -> x -> -> x #

Like alerp, but actually restricted to the interval between the points.

palerp :: (PseudoAffine x, VectorSpace (Needle x)) => x -> x -> Maybe (Scalar (Needle x) -> x) #

Interpolate between points, approximately linearly. For points that aren't close neighbours (i.e. lie in an almost flat region), the pathway is basically undefined – save for its end points.

A proper, really well-defined (on global scales) interpolation only makes sense on a Riemannian manifold, as Geodesic.

palerpB :: (PseudoAffine x, VectorSpace (Needle x), Scalar (Needle x) ~ ) => x -> x -> Maybe ( -> x) #

Like palerp, but actually restricted to the interval between the points, with a signature like geodesicBetween rather than alerp.

class (Semimanifold x, Semimanifold ξ, LSpace (Needle x), LSpace (Needle ξ), Scalar (Needle x) ~ Scalar (Needle ξ)) => LocallyCoercible x ξ where Source #

Instances of this class must be diffeomorphic manifolds, and even have canonically isomorphic tangent spaces, so that fromPackedVector . asPackedVector :: Needle x -> Needle ξ defines a meaningful “representational identity“ between these spaces.

Methods

locallyTrivialDiffeomorphism :: x -> ξ Source #

Must be compatible with the isomorphism on the tangent spaces, i.e. locallyTrivialDiffeomorphism (p .+~^ v) ≡ locallyTrivialDiffeomorphism p .+~^ coerceNeedle v

coerceNeedle :: Functor p => p (x, ξ) -> Needle x -+> Needle ξ Source #

coerceNeedle' :: Functor p => p (x, ξ) -> Needle' x -+> Needle' ξ Source #

coerceNorm :: Functor p => p (x, ξ) -> Metric x -> Metric ξ Source #

coerceVariance :: Functor p => p (x, ξ) -> Metric' x -> Metric' ξ Source #

oppositeLocalCoercion :: CanonicalDiffeomorphism ξ x Source #

oppositeLocalCoercion :: LocallyCoercible ξ x => CanonicalDiffeomorphism ξ x Source #

interiorLocalCoercion :: Functor p (->) (->) => p (x, ξ) -> CanonicalDiffeomorphism (Interior x) (Interior ξ) Source #

interiorLocalCoercion :: LocallyCoercible (Interior x) (Interior ξ) => p (x, ξ) -> CanonicalDiffeomorphism (Interior x) (Interior ξ) Source #

Instances
LocallyCoercible Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

LocallyCoercible (V1 ) Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

LocallyCoercible (V1 ) Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

NumPrime s => LocallyCoercible (V1 s) (V1 s) Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

NumPrime s => LocallyCoercible (V2 s) (V2 s) Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

NumPrime s => LocallyCoercible (V3 s) (V3 s) Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

NumPrime s => LocallyCoercible (V4 s) (V4 s) Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

NumPrime s => LocallyCoercible (V0 s) (ZeroDim s) Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

NumPrime s => LocallyCoercible (V0 s) (V0 s) Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

NumPrime s => LocallyCoercible (ZeroDim s) (V0 s) Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

NumPrime s => LocallyCoercible (ZeroDim s) (ZeroDim s) Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

LocallyCoercible (V2 ) (, ) Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

LocallyCoercible (V3 ) ((, ), ) Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

LocallyCoercible (V3 ) (, (, )) Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

LocallyCoercible (V4 ) ((, ), (, )) Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

LocallyCoercible ((, ), (, )) (V4 ) Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

LocallyCoercible ((, ), ) (V3 ) Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

LocallyCoercible (, (, )) (V3 ) Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

LocallyCoercible (, ) (V2 ) Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

(Semimanifold a, Semimanifold b, Semimanifold c, LSpace (Needle a), LSpace (Needle b), LSpace (Needle c), Scalar (Needle a) ~ Scalar (Needle b), Scalar (Needle b) ~ Scalar (Needle c), Scalar (Needle' a) ~ Scalar (Needle a), Scalar (Needle' b) ~ Scalar (Needle b), Scalar (Needle' c) ~ Scalar (Needle c)) => LocallyCoercible ((a, b), c) (a, (b, c)) Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

Methods

locallyTrivialDiffeomorphism :: ((a, b), c) -> (a, (b, c)) Source #

coerceNeedle :: Functor p => p (((a, b), c), (a, (b, c))) -> Needle ((a, b), c) -+> Needle (a, (b, c)) Source #

coerceNeedle' :: Functor p => p (((a, b), c), (a, (b, c))) -> Needle' ((a, b), c) -+> Needle' (a, (b, c)) Source #

coerceNorm :: Functor p => p (((a, b), c), (a, (b, c))) -> Metric ((a, b), c) -> Metric (a, (b, c)) Source #

coerceVariance :: Functor p => p (((a, b), c), (a, (b, c))) -> Metric' ((a, b), c) -> Metric' (a, (b, c)) Source #

oppositeLocalCoercion :: CanonicalDiffeomorphism (a, (b, c)) ((a, b), c) Source #

interiorLocalCoercion :: Functor p (->) (->) => p (((a, b), c), (a, (b, c))) -> CanonicalDiffeomorphism (Interior ((a, b), c)) (Interior (a, (b, c))) Source #

LocallyCoercible ((, ), ) ((, ), ) Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

Methods

locallyTrivialDiffeomorphism :: ((, ), ) -> ((, ), ) Source #

coerceNeedle :: Functor p => p (((, ), ), ((, ), )) -> Needle ((, ), ) -+> Needle ((, ), ) Source #

coerceNeedle' :: Functor p => p (((, ), ), ((, ), )) -> Needle' ((, ), ) -+> Needle' ((, ), ) Source #

coerceNorm :: Functor p => p (((, ), ), ((, ), )) -> Metric ((, ), ) -> Metric ((, ), ) Source #

coerceVariance :: Functor p => p (((, ), ), ((, ), )) -> Metric' ((, ), ) -> Metric' ((, ), ) Source #

oppositeLocalCoercion :: CanonicalDiffeomorphism ((, ), ) ((, ), ) Source #

interiorLocalCoercion :: Functor p (->) (->) => p (((, ), ), ((, ), )) -> CanonicalDiffeomorphism (Interior ((, ), )) (Interior ((, ), )) Source #

(Semimanifold a, Semimanifold b, Semimanifold c, LSpace (Needle a), LSpace (Needle b), LSpace (Needle c), Scalar (Needle a) ~ Scalar (Needle b), Scalar (Needle b) ~ Scalar (Needle c), Scalar (Needle' a) ~ Scalar (Needle a), Scalar (Needle' b) ~ Scalar (Needle b), Scalar (Needle' c) ~ Scalar (Needle c)) => LocallyCoercible (a, (b, c)) ((a, b), c) Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

Methods

locallyTrivialDiffeomorphism :: (a, (b, c)) -> ((a, b), c) Source #

coerceNeedle :: Functor p => p ((a, (b, c)), ((a, b), c)) -> Needle (a, (b, c)) -+> Needle ((a, b), c) Source #

coerceNeedle' :: Functor p => p ((a, (b, c)), ((a, b), c)) -> Needle' (a, (b, c)) -+> Needle' ((a, b), c) Source #

coerceNorm :: Functor p => p ((a, (b, c)), ((a, b), c)) -> Metric (a, (b, c)) -> Metric ((a, b), c) Source #

coerceVariance :: Functor p => p ((a, (b, c)), ((a, b), c)) -> Metric' (a, (b, c)) -> Metric' ((a, b), c) Source #

oppositeLocalCoercion :: CanonicalDiffeomorphism ((a, b), c) (a, (b, c)) Source #

interiorLocalCoercion :: Functor p (->) (->) => p ((a, (b, c)), ((a, b), c)) -> CanonicalDiffeomorphism (Interior (a, (b, c))) (Interior ((a, b), c)) Source #

LocallyCoercible (, (, )) (, (, )) Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

Methods

locallyTrivialDiffeomorphism :: (, (, )) -> (, (, )) Source #

coerceNeedle :: Functor p => p ((, (, )), (, (, ))) -> Needle (, (, )) -+> Needle (, (, )) Source #

coerceNeedle' :: Functor p => p ((, (, )), (, (, ))) -> Needle' (, (, )) -+> Needle' (, (, )) Source #

coerceNorm :: Functor p => p ((, (, )), (, (, ))) -> Metric (, (, )) -> Metric (, (, )) Source #

coerceVariance :: Functor p => p ((, (, )), (, (, ))) -> Metric' (, (, )) -> Metric' (, (, )) Source #

oppositeLocalCoercion :: CanonicalDiffeomorphism (, (, )) (, (, )) Source #

interiorLocalCoercion :: Functor p (->) (->) => p ((, (, )), (, (, ))) -> CanonicalDiffeomorphism (Interior (, (, ))) (Interior (, (, ))) Source #

LocallyCoercible (, ) (, ) Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

coerceMetric :: forall x ξ. (LocallyCoercible x ξ, LSpace (Needle ξ)) => RieMetric ξ -> RieMetric x Source #

coerceMetric' :: forall x ξ. (LocallyCoercible x ξ, LSpace (Needle ξ)) => RieMetric' ξ -> RieMetric' x Source #

class PseudoAffine m => Connected m where Source #

A connected manifold is one where any point can be reached by translation from any other point.

Minimal complete definition

Nothing

Methods

(.−.) :: m -> m -> Needle m infix 6 Source #

Safe version of '(.-~.)'.

Instances
Connected ℝP⁰ Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

Connected Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

Methods

(.−.) :: -> -> Needle Source #

Connected ℝP¹ Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

Connected Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

Methods

(.−.) :: -> -> Needle Source #

Connected ℝP² Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

Connected Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

Methods

(.−.) :: -> -> Needle Source #

Connected ℝ⁰ Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

Connected ℝ⁴ Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

Connected ℝ³ Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

Connected ℝ² Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

Connected ℝ¹ Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

(Connected x, Connected y) => Connected (x, y) Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

Methods

(.−.) :: (x, y) -> (x, y) -> Needle (x, y) Source #

(Connected x, Connected y, PseudoAffine (FibreBundle x y)) => Connected (FibreBundle x y) Source # 
Instance details

Defined in Data.Manifold.PseudoAffine

Methods

(.−.) :: FibreBundle x y -> FibreBundle x y -> Needle (FibreBundle x y) Source #

Orphan instances

Semimanifold Source # 
Instance details

Associated Types

type Needle :: Type #

type Interior :: Type #

Semimanifold ℝP² Source # 
Instance details

Associated Types

type Needle ℝP² :: Type #

type Interior ℝP² :: Type #

PseudoAffine Source # 
Instance details

PseudoAffine ℝP² Source # 
Instance details

(LinearSpace (a n), Needle (a n) ~ a n, Interior (a n) ~ a n) => Semimanifold (Point a n) Source # 
Instance details

Associated Types

type Needle (Point a n) :: Type #

type Interior (Point a n) :: Type #

Methods

(.+~^) :: Interior (Point a n) -> Needle (Point a n) -> Point a n #

fromInterior :: Interior (Point a n) -> Point a n #

toInterior :: Point a n -> Maybe (Interior (Point a n)) #

translateP :: Tagged (Point a n) (Interior (Point a n) -> Needle (Point a n) -> Interior (Point a n)) #

(.-~^) :: Interior (Point a n) -> Needle (Point a n) -> Point a n #

semimanifoldWitness :: SemimanifoldWitness (Point a n) #

(LinearSpace (a n), Needle (a n) ~ a n, Interior (a n) ~ a n) => PseudoAffine (Point a n) Source # 
Instance details

Methods

(.-~.) :: Point a n -> Point a n -> Maybe (Needle (Point a n)) #

(.-~!) :: Point a n -> Point a n -> Needle (Point a n) #

pseudoAffineWitness :: PseudoAffineWitness (Point a n) #