manifolds-0.4.1.0: Coordinate-free hypersurfaces

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

Data.Manifold.Web

Contents

Description

 

Synopsis

The web data type

data PointsWeb :: * -> * -> * Source

A PointsWeb is almost, but not quite a mesh. It is a stongly connected† directed graph, backed by a tree for fast nearest-neighbour lookup of points.

†In general, there can be disconnected components, but every connected component is strongly connected.

Construction

fromWebNodes :: forall x y. (WithField Manifold x, SimpleSpace (Needle x)) => MetricChoice x -> [(x, y)] -> PointsWeb x y Source

fromShadeTree_auto :: forall x. (WithField Manifold x, SimpleSpace (Needle x)) => ShadeTree x -> PointsWeb x () Source

fromShadeTree :: forall x. (WithField Manifold x, SimpleSpace (Needle x)) => (Shade x -> Metric x) -> ShadeTree x -> PointsWeb x () Source

fromShaded Source

Arguments

:: (WithField Manifold x, SimpleSpace (Needle x)) 
=> MetricChoice x

Local scalar-product generator. You can always use recipMetric . _shadeExpanse (but this may give distortions compared to an actual Riemannian metric).

-> (x `Shaded` y)

Source tree.

-> PointsWeb x y 

Lookup

nearestNeighbour :: (WithField Manifold x, SimpleSpace (Needle x)) => PointsWeb x y -> x -> Maybe (x, y) Source

indexWeb :: (WithField Manifold x, SimpleSpace (Needle x)) => PointsWeb x y -> WebNodeId -> Maybe (x, y) Source

webEdges :: forall x y. (WithField Manifold x, SimpleSpace (Needle x)) => PointsWeb x y -> [((x, y), (x, y))] Source

toGraph :: (WithField Manifold x, SimpleSpace (Needle x)) => PointsWeb x y -> (Graph, Vertex -> (x, y)) Source

Decomposition

sliceWeb_lin :: forall x y. (WithField Manifold x, SimpleSpace (Needle x), Geodesic x, Geodesic y) => PointsWeb x y -> Cutplane x -> [(x, y)] Source

Fetch a point between any two neighbouring web nodes on opposite sides of the plane, and linearly interpolate the values onto the cut plane.

sampleWeb_2Dcartesian_lin :: (x ~ , y ~ , Geodesic z) => PointsWeb (x, y) z -> ((x, x), Int) -> ((y, y), Int) -> [(y, [(x, Maybe z)])] Source

sampleEntireWeb_2Dcartesian_lin :: (x ~ , y ~ , Geodesic z) => PointsWeb (x, y) z -> Int -> Int -> [(y, [(x, Maybe z)])] Source

Local environments

localFocusWeb :: WithField Manifold x => PointsWeb x y -> PointsWeb x ((x, y), [(Needle x, y)]) Source

Uncertain functions

differentiateUncertainWebFunction :: forall x y. (WithField Manifold x, SimpleSpace (Needle x), WithField Manifold y, SimpleSpace (Needle y), Refinable y) => PointsWeb x (Shade' y) -> PointsWeb x (Shade' (LocalLinear x y)) Source

Differential equations

Fixed resolution

iterateFilterDEqn_static :: (WithField Manifold x, FlatSpace (Needle x), Refinable y, Geodesic y, FlatSpace (Needle y), WithField AffineManifold ð, Geodesic ð, SimpleSpace (Needle ð), MonadPlus m) => InformationMergeStrategy [] m (x, Shade' y) iy -> Embedding (->) (Shade' y) iy -> DifferentialEqn x ð y -> PointsWeb x (Shade' y) -> Cofree m (PointsWeb x (Shade' y)) Source

Automatic resolution

filterDEqnSolutions_adaptive Source

Arguments

:: (WithField Manifold x, SimpleSpace (Needle x), WithField AffineManifold y, Refinable y, Geodesic y, WithField AffineManifold ð, Geodesic ð, SimpleSpace (Needle ð), badness ~ , Monad m) 
=> MetricChoice x

Scalar product on the domain, for regularising the web.

-> InconsistencyStrategy m x (Shade' y) 
-> DifferentialEqn x ð y 
-> (x -> Shade' y -> badness) 
-> PointsWeb x (SolverNodeState x y) 
-> m (PointsWeb x (SolverNodeState x y)) 

iterateFilterDEqn_adaptive Source

Arguments

:: (WithField Manifold x, SimpleSpace (Needle x), WithField AffineManifold y, Refinable y, Geodesic y, Monad m, WithField AffineManifold ð, Geodesic ð, SimpleSpace (Needle ð)) 
=> MetricChoice x

Scalar product on the domain, for regularising the web.

-> InconsistencyStrategy m x (Shade' y) 
-> DifferentialEqn x ð y 
-> (x -> Shade' y -> )

Badness function for local results.

-> PointsWeb x (Shade' y) 
-> [PointsWeb x (Shade' y)] 

Configuration

newtype InformationMergeStrategy n m y' y Source

Constructors

InformationMergeStrategy 

Fields

mergeInformation :: y -> n y' -> m y
 

naïve :: (NonEmpty y -> y) -> InformationMergeStrategy [] Identity (x, y) y Source

inconsistencyAware :: (NonEmpty y -> m y) -> InformationMergeStrategy [] m (x, y) y Source

Misc

data ConvexSet x Source

Constructors

EmptyConvex 
ConvexSet 

Fields

convexSetHull :: Shade' x

If p is in all intersectors, it must also be in the hull.

convexSetIntersectors :: [Shade' x]
 

Instances

LtdErrorShow x => Show (ConvexSet x) Source 
Refinable x => Semigroup (ConvexSet x) Source

Under intersection.

ellipsoidSet :: Embedding (->) (Maybe (Shade' x)) (ConvexSet x) Source

coerceWebDomain :: forall a b y. (Manifold a, Manifold b, LocallyCoercible a b) => PointsWeb a y -> PointsWeb b y Source

rescanPDELocally :: forall x y ð. (WithField Manifold x, FlatSpace (Needle x), WithField Refinable y, Geodesic y, FlatSpace (Needle y)) => DifferentialEqn x ð y -> WebLocally x (Shade' y) -> (Maybe (Shade' y), Maybe (Shade' ð)) Source

webOnions :: forall x y. WithField Manifold x => PointsWeb x y -> PointsWeb x [[(x, y)]] Source