| Copyright | (c) Justus Sagemüller 2015 | 
|---|---|
| License | GPL v3 | 
| Maintainer | (@) sagemueller $ geo.uni-koeln.de | 
| Stability | experimental | 
| Portability | portable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Data.Manifold.Atlas
Description
- class Semimanifold m => Atlas m where- type ChartIndex m :: *
 
- type AffineManifold m = (Atlas m, Manifold m, AffineSpace m, Needle m ~ Diff m, HasTrie (ChartIndex m))
- type EuclidSpace x = (AffineManifold x, InnerSpace (Diff x), DualVector (Diff x) ~ Diff x, Floating (Scalar (Diff x)))
- euclideanMetric :: EuclidSpace x => proxy x -> Metric x
Documentation
class Semimanifold m => Atlas m where Source #
Minimal complete definition
Associated Types
type ChartIndex m :: * Source #
Methods
chartReferencePoint :: ChartIndex m -> m Source #
interiorChartReferencePoint :: Functor p => p m -> ChartIndex m -> Interior m Source #
lookupAtlas :: m -> ChartIndex m Source #
Instances
| Atlas S⁰ Source # | |
| Atlas S¹ Source # | |
| Atlas ℝ Source # | |
| Atlas S² Source # | |
| Num s => Atlas (V0 s) Source # | |
| Num s => Atlas (V1 s) Source # | |
| Num s => Atlas (V2 s) Source # | |
| Num s => Atlas (V3 s) Source # | |
| Num s => Atlas (V4 s) Source # | |
| Atlas (ZeroDim s) Source # | |
| (Atlas x, Atlas y) => Atlas (x, y) Source # | |
| (LinearSpace (a n), (~) * (Needle (a n)) (a n), (~) * (Interior (a n)) (a n)) => Atlas (Point a n) Source # | |
| (LinearSpace v, (~) * (Scalar v) s, TensorSpace w, (~) * (Scalar w) s) => Atlas (LinearMap s v w) Source # | |
| (TensorSpace v, (~) * (Scalar v) s, TensorSpace w, (~) * (Scalar w) s) => Atlas (Tensor s v w) Source # | |
type AffineManifold m = (Atlas m, Manifold m, AffineSpace m, Needle m ~ Diff m, HasTrie (ChartIndex m)) Source #
The AffineSpace class plus manifold constraints.
type EuclidSpace x = (AffineManifold x, InnerSpace (Diff x), DualVector (Diff x) ~ Diff x, Floating (Scalar (Diff x))) Source #
An euclidean space is a real affine space whose tangent space is a Hilbert space.
euclideanMetric :: EuclidSpace x => proxy x -> Metric x Source #