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

Copyright(c) Justus Sagemüller 2013
LicenseGPL v3
Maintainer(@) sagemueller $ geo.uni-koeln.de
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Data.Manifold

Contents

Description

This is something of a first attempt at formalising manifolds and continuous mappings thereon. They work (check out http://hackage.haskell.org/package/dynamic-plot-0.1.0.0 for a use case), but aren't very efficient. The interface might well change considerably in the future.

Synopsis

Documentation

data domain :--> codomain where Source

Continuous mapping.

Constructors

Continuous :: (Manifold d, Manifold c, v ~ TangentSpace d, u ~ TangentSpace c, δ ~ Metric v, ε ~ Metric u) => (Chart d -> v -> (Chart c, u, ε -> Option δ)) -> d :--> c 

Fields

runContinuous :: Chart d -> v -> (Chart c, u, ε -> Option δ)
 

const__ :: (Manifold c, Manifold d) => c -> d :--> c Source

flatContinuous :: (FlatManifold v, FlatManifold w, δ ~ Metric v, ε ~ Metric w) => (v -> (w, ε -> Option δ)) -> v :--> w Source

runFlatContinuous :: (FlatManifold v, FlatManifold w, δ ~ Metric v, ε ~ Metric w) => (v :--> w) -> v -> (w, ε -> Option δ) Source

data Chart :: * -> * where Source

A chart is a homeomorphism from a connected, open subset QM of an n-manifold M to either the open unit disk DⁿV ≃ ℝ, or the half-disk Hⁿ = {xDⁿ: x₀≥0}. In e.g. the former case, chartInMap is thus defined ∀ vV : |v| < 1, while 'chartOutMap p' will yield Just x with xDⁿ provided p is in Q, and Nothing otherwise. Obviously, fromJust . chartOutMap . chartInMap should be equivalent to id on Dⁿ, and chartInMap . fromJust . chartOutMap to id on Q.

Constructors

IdChart :: FlatManifold v => Chart v 
Chart :: (Manifold m, v ~ TangentSpace m, FlatManifold v) => (v :--> m) -> (m -> Maybe (m :--> v)) -> ChartKind -> Chart m 

Fields

chartInMap :: v :--> m
 
chartOutMap :: m -> Maybe (m :--> v)
 
chartKind :: ChartKind
 

data ChartKind Source

Constructors

LandlockedChart

A MDⁿ chart, for ordinary manifolds

RimChart

A MHⁿ chart, for manifolds with a rim

type Atlas m = [Chart m] Source

class (MetricSpace (TangentSpace m), Metric (TangentSpace m) ~ ) => Manifold m where Source

Associated Types

type TangentSpace m :: * Source

Methods

localAtlas :: m -> Atlas m Source

Instances

Manifold Double 
Manifold () 
(FlatManifold v₁, FlatManifold v₂, (~) * (Scalar v₁) (Scalar v₂), MetricSpace (Scalar v₁), (~) * (Metric (Scalar v₁)) , VectorSpace (v₁, v₂), (~) * (Scalar (v₁, v₂)) (Scalar v₁)) => Manifold (v₁, v₂) 

continuousFlatFunction :: (FlatManifold d, FlatManifold c, ε ~ Metric c, δ ~ Metric d) => (d -> (c, ε -> Option δ)) -> d :--> c Source

cntnFuncsCombine :: forall d v c c' c'' ε ε' ε''. (FlatManifold c, FlatManifold c', FlatManifold c'', ε ~ Metric c, ε' ~ Metric c', ε'' ~ Metric c'', ε ~ ε', ε ~ ε'') => (c' -> c'' -> (c, ε -> (ε', ε''))) -> (d :--> c') -> (d :--> c'') -> d :--> c Source

cntnFnValsFunc :: (FlatManifold c, FlatManifold c', Manifold d, ε ~ Metric c, ε ~ Metric c') => (c' -> (c, ε -> Option ε)) -> CntnFuncValue d c' -> CntnFuncValue d c Source

cntnFnValsCombine :: forall d c c' c'' ε ε' ε''. (FlatManifold c, FlatManifold c', FlatManifold c'', Manifold d, ε ~ Metric c, ε' ~ Metric c', ε'' ~ Metric c'', ε ~ ε', ε ~ ε'') => (c' -> c'' -> (c, ε -> (ε', (ε', ε''), ε''))) -> CntnFuncValue d c' -> CntnFuncValue d c'' -> CntnFuncValue d c Source

(.:) :: (c -> d) -> (a -> b -> c) -> a -> b -> d Source

just :: a -> Option a Source

class (RealFloat (Metric v), InnerSpace v) => MetricSpace v where Source

Minimal complete definition

metricToScalar

Associated Types

type Metric v :: * Source

Methods

metric :: v -> Metric v Source

metricSq :: v -> Metric v Source

(|*^) :: Metric v -> v -> v Source

metricToScalar :: v -> Metric v -> Scalar v Source

Instances

MetricSpace () 
MetricSpace  
(RealFloat r, MetricSpace r, (~) * (Scalar (Complex r)) (Metric r)) => MetricSpace (Complex r) 
(MetricSpace v, MetricSpace (Scalar v), MetricSpace w, (~) * (Scalar v) (Scalar w), (~) * (Metric v) (Metric (Scalar v)), (~) * (Metric w) (Metric v), (~) * (Metric (Scalar w)) (Metric v), RealFloat (Metric v)) => MetricSpace (v, w) 

Index / ASCII names

Linear manifolds

data ZeroDim k Source

A single point. Can be considered a zero-dimensional vector space, WRT any scalar.

Constructors

Origin 

Instances

type ℝ² = (, ) Source

type ℝ³ = (ℝ², ) Source

Hyperspheres

data S⁰ Source

The zero-dimensional sphere is actually just two points. Implementation might therefore change to ℝ⁰ + ℝ⁰: the disjoint sum of two single-point spaces.

newtype Source

The unit circle.

Constructors

 

Fields

φParamS¹ :: Double

Must be in range [-π, π[.

data Source

The ordinary unit sphere.

Constructors

 

Fields

ϑParamS² :: !Double

Range [0, π[.

φParamS² :: !Double

Range [-π, π[.

Projective spaces

data ℝP² Source

The two-dimensional real projective space, implemented as a unit disk with opposing points on the rim glued together.

Constructors

ℝP² 

Fields

rParamℝP² :: !Double

Range [0, 1].

φParamℝP² :: !Double

Range [-π, π[.

Intervals/disks/cones

newtype Source

The “one-dimensional disk” – really just the line segment between the two points -1 and 1 of 'S⁰', i.e. this is simply a closed interval.

Constructors

 

Fields

xParamD¹ :: Double

Range [-1, 1].

data Source

The standard, closed unit disk. Homeomorphic to the cone over 'S¹', but not in the the obvious, “flat” way. (And not at all, despite the identical ADT definition, to the projective space 'ℝP²'!)

Constructors

 

Fields

rParamD² :: !Double

Range [0, 1].

φParamD² :: !Double

Range [-π, π[.

Instances

type ℝay = Cℝay ℝ⁰ Source

Better known as ℝ⁺ (which is not a legal Haskell name), the ray of positive numbers (including zero, i.e. closed on one end).

data CD¹ x Source

A (closed) cone over a space x is the product of x with the closed interval 'D¹' of “heights”, except on its “tip”: here, x is smashed to a single point.

This construct becomes (homeomorphic-to-) an actual geometric cone (and to 'D²') in the special case x = 'S¹'.

Constructors

CD¹ 

Fields

hParamCD¹ :: !Double

Range [0, 1]

pParamCD¹ :: !x

Irrelevant at h = 0.

Instances

(PseudoAffine m, VectorSpace (Needle m), (~) * (Scalar (Needle m)) ) => PseudoAffine (CD¹ m) 
(PseudoAffine m, VectorSpace (Needle m), (~) * (Scalar (Needle m)) ) => Semimanifold (CD¹ m) 
type Needle (CD¹ m) = (Needle m, ) 

data Cℝay x Source

An open cone is homeomorphic to a closed cone without the “lid”, i.e. without the “last copy” of x, at the far end of the height interval. Since that means the height does not include its supremum, it is actually more natural to express it as the entire real ray, hence the name.

Constructors

Cℝay 

Fields

hParamCℝay :: !Double

Range [0, ∞[

pParamCℝay :: !x

Irrelevant at h = 0.

Instances

Utility (deprecated)

type Endomorphism a = a -> a Source

(^) :: Num a => a -> Int -> a Source

type EqFloating f = (Eq f, Ord f, Floating f) Source