manifolds-0.5.0.1: Coordinate-free hypersurfaces

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

Data.Manifold.Web.Internal

Description

 

Synopsis

Documentation

data Neighbourhood x y Source #

Instances

Functor (Neighbourhood x) Source # 

Methods

fmap :: (a -> b) -> Neighbourhood x a -> Neighbourhood x b #

(<$) :: a -> Neighbourhood x b -> Neighbourhood x a #

Foldable (Neighbourhood x) Source # 

Methods

fold :: Monoid m => Neighbourhood x m -> m #

foldMap :: Monoid m => (a -> m) -> Neighbourhood x a -> m #

foldr :: (a -> b -> b) -> b -> Neighbourhood x a -> b #

foldr' :: (a -> b -> b) -> b -> Neighbourhood x a -> b #

foldl :: (b -> a -> b) -> b -> Neighbourhood x a -> b #

foldl' :: (b -> a -> b) -> b -> Neighbourhood x a -> b #

foldr1 :: (a -> a -> a) -> Neighbourhood x a -> a #

foldl1 :: (a -> a -> a) -> Neighbourhood x a -> a #

toList :: Neighbourhood x a -> [a] #

null :: Neighbourhood x a -> Bool #

length :: Neighbourhood x a -> Int #

elem :: Eq a => a -> Neighbourhood x a -> Bool #

maximum :: Ord a => Neighbourhood x a -> a #

minimum :: Ord a => Neighbourhood x a -> a #

sum :: Num a => Neighbourhood x a -> a #

product :: Num a => Neighbourhood x a -> a #

Traversable (Neighbourhood x) Source # 

Methods

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

sequenceA :: Applicative f => Neighbourhood x (f a) -> f (Neighbourhood x a) #

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

sequence :: Monad m => Neighbourhood x (m a) -> m (Neighbourhood x a) #

(WithField PseudoAffine x, SimpleSpace (Needle x), Show (Needle' x), Show y) => Show (Neighbourhood x y) Source # 
Generic (Neighbourhood x y) Source # 

Associated Types

type Rep (Neighbourhood x y) :: * -> * #

Methods

from :: Neighbourhood x y -> Rep (Neighbourhood x y) x #

to :: Rep (Neighbourhood x y) x -> Neighbourhood x y #

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

Methods

rnf :: Neighbourhood x y -> () #

type Rep (Neighbourhood x y) Source # 
type Rep (Neighbourhood x y) = D1 * (MetaData "Neighbourhood" "Data.Manifold.Web.Internal" "manifolds-0.5.0.1-BXWDyndrqVvASnHIWZyxjI" False) (C1 * (MetaCons "Neighbourhood" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_dataAtNode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * y)) (S1 * (MetaSel (Just Symbol "_neighbours") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Vector WebNodeIdOffset)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_localScalarProduct") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Metric x))) (S1 * (MetaSel (Just Symbol "_webBoundaryAtNode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe (Needle' x)))))))

dataAtNode :: forall x y y. Lens (Neighbourhood x y) (Neighbourhood x y) y y Source #

data WebLocally x y Source #

Instances

Functor (WebLocally x) Source # 

Methods

fmap :: (a -> b) -> WebLocally x a -> WebLocally x b #

(<$) :: a -> WebLocally x b -> WebLocally x a #

WithField Manifold x => Comonad (WebLocally x) Source #

fmap from the co-Kleisli category of WebLocally.

Methods

extract :: WebLocally x a -> a #

duplicate :: WebLocally x a -> WebLocally x (WebLocally x a) #

extend :: (WebLocally x a -> b) -> WebLocally x a -> WebLocally x b #

Generic (WebLocally x y) Source # 

Associated Types

type Rep (WebLocally x y) :: * -> * #

Methods

from :: WebLocally x y -> Rep (WebLocally x y) x #

to :: Rep (WebLocally x y) x -> WebLocally x y #

type Rep (WebLocally x y) Source # 
type Rep (WebLocally x y) = D1 * (MetaData "WebLocally" "Data.Manifold.Web.Internal" "manifolds-0.5.0.1-BXWDyndrqVvASnHIWZyxjI" False) (C1 * (MetaCons "LocalWebInfo" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "_thisNodeCoord") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * x)) ((:*:) * (S1 * (MetaSel (Just Symbol "_thisNodeData") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * y)) (S1 * (MetaSel (Just Symbol "_thisNodeId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * WebNodeId)))) ((:*:) * (S1 * (MetaSel (Just Symbol "_nodeNeighbours") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [(WebNodeId, (Needle x, WebLocally x y))])) ((:*:) * (S1 * (MetaSel (Just Symbol "_nodeLocalScalarProduct") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Metric x))) (S1 * (MetaSel (Just Symbol "_webBoundingPlane") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe (Needle' x))))))))

thisNodeData :: forall x y. Lens' (WebLocally x y) y Source #

thisNodeCoord :: forall x y. Lens' (WebLocally x y) x Source #

nodeNeighbours :: forall x y. Lens' (WebLocally x y) [(WebNodeId, (Needle x, WebLocally x y))] Source #

newtype PointsWeb :: * -> * -> * where 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.

Constructors

PointsWeb :: {..} -> PointsWeb x y 

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) ((->) LiftedRep LiftedRep) ((->) LiftedRep LiftedRep) Source # 
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.5.0.1-BXWDyndrqVvASnHIWZyxjI" True) (C1 * (MetaCons "PointsWeb" PrefixI True) (S1 * (MetaSel (Just Symbol "webNodeRsc") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Shaded a (Neighbourhood a b)))))

data WebChunk x y Source #

thisChunk :: forall x y. Lens' (WebChunk x y) (PointsWeb x y) Source #

thisNodeOnly :: forall x y. Lens' (NodeInWeb x y) (x, Neighbourhood x y) Source #

data PathStep x y Source #

Constructors

PathStep 

pathStepStart :: forall x y. Lens' (PathStep x y) (WebLocally x y) Source #

pathStepEnd :: forall x y. Lens' (PathStep x y) (WebLocally x y) Source #

type MetricChoice x = Shade x -> Metric x Source #

traverseInnermostChunks :: forall f x y z. Applicative f => (WebChunk x y -> f (PointsWeb x z)) -> PointsWeb x y -> f (PointsWeb x z) Source #

traverseNodesInEnvi :: forall f x y z. Applicative f => (NodeInWeb x y -> f (Neighbourhood x z)) -> PointsWeb x y -> f (PointsWeb x z) Source #

ixedFoci :: [a] -> [((Int, a), [a])] Source #

pumpHalfspace Source #

Arguments

:: (SimpleSpace v, Scalar v ~ ) 
=> Norm v 
-> v

A vector v for which we want dv.^v ≥ 0.

-> (DualVector v, [v])

A plane dv₀ and some vectors ws with dv₀.^w ≥ 0, which should also fulfill dv.^w ≥ 0.

-> Maybe (DualVector v)

The plane dv fulfilling these properties, if possible.

data LinkingBadness r Source #

Constructors

LinkingBadness 

Fields

  • gatherDirectionsBadness :: !r

    Prefer picking neighbours at right angles to the currently-explored-boundary. This is needed while we still have to link to points in different spatial directions.

  • closeSystemBadness :: !r

    Prefer points directly opposed to the current boundary. This is useful when the system of directions is already complete and we want a nicely symmetric “ball” of neighbours around each point.

Instances

linkingUndesirability Source #

Arguments

::

Absolute-square distance (euclidean norm squared)

->

Directional distance (distance from wall containing all already known neighbours)

-> LinkingBadness

“Badness” of this point as the next neighbour to link to. In gatherDirections mode this is large if the point is far away, but also if it is right normal to the wall. The reason we punish this is that adding two points directly opposed to each other would lead to an ill-defined wall orientation, i.e. wrong normals on the web boundary.

bestNeighbours :: forall i v. (SimpleSpace v, Scalar v ~ ) => Norm v -> [(i, v)] -> ([i], Maybe (DualVector v)) Source #

bestNeighbours' :: forall i v. (SimpleSpace v, Scalar v ~ ) => Norm v -> [(i, v)] -> ([(i, v)], Maybe (DualVector v)) Source #

gatherGoodNeighbours :: forall i v. (SimpleSpace v, Scalar v ~ ) => Norm v -> Variance v -> DualVector v -> [v] -> [(i, v)] -> [(i, v)] -> ([(i, v)], Maybe (DualVector v)) Source #

extractSmallestOn :: Ord b => (a -> Maybe b) -> [a] -> Maybe (a, [a]) Source #

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

traversePathInIWeb :: forall φ x y. (WithField Manifold x, Monad φ, HasCallStack) => [WebNodeId] -> (PathStep x y -> φ y) -> PointsWeb x (WebLocally x y) -> φ (PointsWeb x (WebLocally x y)) Source #

traversePathsTowards Source #

Arguments

:: (WithField Manifold x, Monad φ, Monad f, HasCallStack) 
=> WebNodeId

The node towards which the paths should converge.

-> (PathStep x y -> φ y)

The action which to traverse along each path.

-> (forall υ. WebLocally x y -> φ υ -> f υ)

Initialisation/evaluation for each path-traversal.

-> PointsWeb x y 
-> f (PointsWeb x y)