manifolds-0.4.4.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.

Instances

Functor (PointsWeb a) Source # 

Methods

fmap :: (a -> b) -> PointsWeb a a -> PointsWeb a b #

(<$) :: a -> PointsWeb a b -> PointsWeb a a #

Foldable (PointsWeb a) Source # 

Methods

fold :: Monoid m => PointsWeb a m -> m #

foldMap :: Monoid m => (a -> m) -> PointsWeb a a -> m #

foldr :: (a -> b -> b) -> b -> PointsWeb a a -> b #

foldr' :: (a -> b -> b) -> b -> PointsWeb a a -> b #

foldl :: (b -> a -> b) -> b -> PointsWeb a a -> b #

foldl' :: (b -> a -> b) -> b -> PointsWeb a a -> b #

foldr1 :: (a -> a -> a) -> PointsWeb a a -> a #

foldl1 :: (a -> a -> a) -> PointsWeb a a -> a #

toList :: PointsWeb a a -> [a] #

null :: PointsWeb a a -> Bool #

length :: PointsWeb a a -> Int #

elem :: Eq a => a -> PointsWeb a a -> Bool #

maximum :: Ord a => PointsWeb a a -> a #

minimum :: Ord a => PointsWeb a a -> a #

sum :: Num a => PointsWeb a a -> a #

product :: Num a => PointsWeb a a -> a #

Traversable (PointsWeb a) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> PointsWeb a a -> f (PointsWeb a b) #

sequenceA :: Applicative f => PointsWeb a (f a) -> f (PointsWeb a a) #

mapM :: Monad m => (a -> m b) -> PointsWeb a a -> m (PointsWeb a b) #

sequence :: Monad m => PointsWeb a (m a) -> m (PointsWeb a a) #

Foldable (PointsWeb x) (->) (->) Source # 

Methods

ffoldl :: (ObjectPair (->) a b, ObjectPair (->) a (PointsWeb x b)) => ((a, b) -> a) -> (a, PointsWeb x b) -> a #

foldMap :: (Object (->) a, Object (->) (PointsWeb x a), Monoid m, Object (->) m, Object (->) m) => (a -> m) -> PointsWeb x a -> m #

Generic (PointsWeb a b) Source # 

Associated Types

type Rep (PointsWeb a b) :: * -> * #

Methods

from :: PointsWeb a b -> Rep (PointsWeb a b) x #

to :: Rep (PointsWeb a b) x -> PointsWeb a b #

(NFData x, NFData (Metric x), NFData (Needle' x), NFData y) => NFData (PointsWeb x y) Source # 

Methods

rnf :: PointsWeb x y -> () #

type Rep (PointsWeb a b) Source # 
type Rep (PointsWeb a b) = D1 (MetaData "PointsWeb" "Data.Manifold.Web.Internal" "manifolds-0.4.4.0-4U7mLxDASVE34WPYCdNRgy" True) (C1 (MetaCons "PointsWeb" PrefixI True) (S1 (MetaSel (Just Symbol "webNodeRsc") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Shaded a (Neighbourhood a b)))))

Construction

fromWebNodes :: forall x y. (WithField Manifold x, SimpleSpace (Needle x)) => MetricChoice x -> [(x, y)] -> PointsWeb x y 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 :: forall x y. (WithField Manifold x, SimpleSpace (Needle x)) => PointsWeb x y -> x -> Maybe (x, y) Source #

fmap from the co-Kleisli category of WebLocally.

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

localModels_CGrid :: forall x y ㄇ. (ModellableRelation x y, LocalModel ㄇ) => PointsWeb x (Shade' y) -> [(x, ㄇ x y)] Source #

Calculate a quadratic fit with uncertainty margin centered around the connection between any two adjacent nodes. In case of a regular grid (which we by no means require here!) this corresponds to the vector quantities of an Arakawa type C/D grid (cf. A. Arakawa, V.R. Lamb (1977): Computational design of the basic dynamical processes of the UCLA general circulation model)

Differential equations

Fixed resolution

iterateFilterDEqn_static :: (ModellableRelation x y, MonadPlus m, LocalModel ㄇ) => InformationMergeStrategy [] m (x, Shade' y) iy -> Embedding (->) (Shade' y) iy -> DifferentialEqn ㄇ x y -> PointsWeb x (Shade' y) -> Cofree m (PointsWeb x (Shade' y)) Source #

iterateFilterDEqn_static_selective :: (ModellableRelation x y, MonadPlus m, badness ~ , LocalModel ㄇ) => InformationMergeStrategy [] m (x, Shade' y) iy -> Embedding (->) (Shade' y) iy -> (x -> iy -> badness) -> DifferentialEqn ㄇ x y -> PointsWeb x (Shade' y) -> Cofree m (PointsWeb x (Shade' y)) Source #

Automatic resolution

filterDEqnSolutions_adaptive Source #

Arguments

:: (ModellableRelation x y, AffineManifold y, badness ~ , Monad m, LocalModel ㄇ) 
=> 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

:: (ModellableRelation x y, AffineManifold y, LocalModel ㄇ, 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 function for local results.

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

Configuration

newtype InformationMergeStrategy n m y' y Source #

Constructors

InformationMergeStrategy 

Fields

Misc

data ConvexSet x Source #

Constructors

EmptyConvex 
ConvexSet 

Fields

Instances

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

Under intersection.

Methods

(<>) :: ConvexSet x -> ConvexSet x -> ConvexSet x #

sconcat :: NonEmpty (ConvexSet x) -> ConvexSet x #

stimes :: Integral b => b -> ConvexSet x -> ConvexSet x #

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

rescanPDELocally :: forall x y ㄇ. (ModellableRelation x y, LocalModel ㄇ) => DifferentialEqn ㄇ x y -> WebLocally x (Shade' y) -> Maybe (Shade' y) Source #

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

knitShortcuts :: forall x y. (WithField Manifold x, SimpleSpace (Needle x)) => MetricChoice x -> PointsWeb x y -> PointsWeb x y Source #

Consider at each node not just the connections to already known neighbours, but also the connections to their neighbours. If these next-neighbours turn out to be actually situated closer, link to them directly.