manifolds-0.1.0.2: 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

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) 

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

data ZeroDim k Source

Constructors

Origin 

newtype Source

Constructors

 

Fields

φParamS¹ :: Double
 

type Endomorphism a = a -> a Source

type ℝ² = (, ) Source

type ℝ³ = (ℝ², ) Source

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