-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Coordinate-free hypersurfaces -- -- Manifolds, a generalisation of the notion of “smooth curves” or -- surfaces, are topological spaces locally homeomorphic to a vector -- space. This gives rise to what is actually the most natural / -- mathematically elegant way of dealing with them: calculations can be -- carried out locally, in connection with Riemannian products etc., in a -- vector space, the tangent space / tangent bundle. -- -- However, this does not trivially translate to non-local operations. -- Common ways to carry those out include using a single affine map to -- cover (almost) all of the manifold (in general not possible -- homeomorphically, which leads to both topological and geometrical -- problems), to embed the manifold into a larger-dimensional vector -- space (which tends to distract from the manifold's own properties and -- is often not friendly to computations) or approximating the manifold -- by some kind of finite simplicial mesh (which intrinsically introduces -- non-differentiability issues and leads to the question of what -- precision is required). -- -- This library tries to mitigate these problems by using Haskell's -- functional nature to keep the representation close to the mathematical -- ideal of local linearity with homeomorphic coordinate transforms, and, -- where it is necessary to recede to the less elegant alternatives, -- exploiting lazy evaluation etc. to optimise the compromises that have -- to be made. @package manifolds @version 0.5.1.0 -- | This is the second prototype of a manifold class. It appears to give -- considerable advantages over Manifold, so that class will -- probably soon be replaced with the one we define here (though -- PseudoAffine does not follow the standard notion of a manifold -- very closely, it should work quite equivalently for pretty much all -- Haskell types that qualify as manifolds). -- -- Manifolds are interesting as objects of various categories, from -- continuous to diffeomorphic. At the moment, we mainly focus on -- region-wise differentiable functions, which are a promising -- compromise between flexibility of definition and provability of -- analytic properties. In particular, they are well-suited for -- visualisation purposes. -- -- The classes in this module are mostly aimed at manifolds without -- boundary. Manifolds with boundary (which we call MWBound, -- never manifold!) are more or less treated as a disjoint sum of -- the interior and the boundary. To understand how this module works, -- best first forget about boundaries – in this case, Interior -- x ~ x, fromInterior and toInterior are trivial, and -- .+~|, |-~. and betweenBounds are -- irrelevant. The manifold structure of the boundary itself is not -- considered at all here. module Data.Manifold.PseudoAffine -- | See Semimanifold and PseudoAffine for the methods. class (PseudoAffine m, LSpace (Needle m)) => Manifold m inInterior :: Manifold m => m -> Interior m inInterior :: (Manifold m, m ~ Interior m) => m -> Interior m class AdditiveGroup Needle x => Semimanifold x where { -- | The space of “natural” ways starting from some reference point and -- going to some particular target point. Hence, the name: like a compass -- needle, but also with an actual length. For affine spaces, -- Needle is simply the space of line segments (aka vectors) -- between two points, i.e. the same as Diff. The -- AffineManifold constraint makes that requirement explicit. -- -- This space should be isomorphic to the tangent space (and is in fact -- used somewhat synonymously). type family Needle x :: Type; -- | Manifolds with boundary are a bit tricky. We support such manifolds, -- but carry out most calculations only in “the fleshy part” – the -- interior, which is an “infinite space”, so you can arbitrarily scale -- paths. -- -- The default implementation is Interior x = x, which -- corresponds to a manifold that has no boundary to begin with. type family Interior x :: Type; } -- | Generalised translation operation. Note that the result will always -- also be in the interior; scaling up the needle can only get you ever -- closer to a boundary. (.+~^) :: Semimanifold x => Interior x -> Needle x -> x -- | id sans boundary. fromInterior :: Semimanifold x => Interior x -> x toInterior :: Semimanifold x => x -> Maybe (Interior x) -- | The signature of .+~^ should really be Interior x -- -> Needle x -> Interior x, only, this is not -- possible because it only consists of non-injective type families. The -- solution is this tagged signature, which is of course rather unwieldy. -- That's why .+~^ has the stronger, but easier usable signature. -- Without boundary, these functions should be equivalent, i.e. -- translateP = Tagged (.+~^). translateP :: Semimanifold x => Tagged x (Interior x -> Needle x -> Interior x) -- | Shorthand for \p v -> p .+~^ negateV v, which -- should obey the asymptotic law -- --
--   p .-~^ v .+~^ v ≅ p
--   
-- -- Meaning: if v is scaled down with sufficiently small factors -- η, then the difference (p.-~^v.+~^v) .-~. p should -- scale down even faster: as O (η²). For large vectors, it -- will however behave differently, except in flat spaces (where all this -- should be equivalent to the AffineSpace instance). (.-~^) :: Semimanifold x => Interior x -> Needle x -> x semimanifoldWitness :: Semimanifold x => SemimanifoldWitness x infixl 6 .+~^ infixl 6 .-~^ -- | A co-needle can be understood as a “paper stack”, with which you can -- measure the length that a needle reaches in a given direction by -- counting the number of holes punched through them. type Needle' x = DualVector (Needle x) -- | This is the class underlying manifolds. (Manifold only -- precludes boundaries and adds an extra constraint that would be -- circular if it was in a single class. You can always just use -- Manifold as a constraint in your signatures, but you must -- define only PseudoAffine for manifold types – the -- Manifold instance follows universally from this, if -- 'Interior x ~ x.) -- -- The interface is (boundaries aside) almost identical to the -- better-known AffineSpace class, but we don't require -- associativity of .+~^ with ^+^ – except in an -- asymptotic sense for small vectors. -- -- That innocent-looking change makes the class applicable to vastly more -- general types: while an affine space is basically nothing but a vector -- space without particularly designated origin, a pseudo-affine space -- can have nontrivial topology on the global scale, and yet be used in -- practically the same way as an affine space. At least the usual -- spheres and tori make good instances, perhaps the class is in fact -- equivalent to manifolds in their usual maths definition (with an atlas -- of charts: a family of overlapping regions of the topological space, -- each homeomorphic to the Needle vector space or some -- simply-connected subset thereof). class Semimanifold x => PseudoAffine x -- | The path reaching from one point to another. Should only yield -- Nothing if -- -- -- -- On manifolds, the identity -- --
--   p .+~^ (q.-~.p) ≡ q
--   
-- -- should hold, at least save for floating-point precision limits etc.. -- -- .-~. and .+~^ only really work in manifolds without -- boundary. If you consider the path between two points, one of which -- lies on the boundary, it can't really be possible to scale this path -- any longer – it would have to reach “out of the manifold”. To adress -- this problem, these functions basically consider only the -- interior of the space. (.-~.) :: PseudoAffine x => x -> x -> Maybe (Needle x) -- | Unsafe version of .-~.. If the two points lie in disjoint -- regions, the behaviour is undefined. (.-~!) :: PseudoAffine x => x -> x -> Needle x pseudoAffineWitness :: PseudoAffine x => PseudoAffineWitness x infix 6 .-~. infix 6 .-~! -- | A point on a manifold, as seen from a nearby reference point. newtype Local x Local :: Needle x -> Local x [getLocalOffset] :: Local x -> Needle x -- | Proxy-version of translateP. (⊙+^) :: forall x proxy. Semimanifold x => Interior x -> Needle x -> proxy x -> Interior x infix 6 ⊙+^ -- | Boundary-unsafe version of .+~^. (!+~^) :: forall x. (Semimanifold x, HasCallStack) => x -> Needle x -> x infixl 6 !+~^ -- | The word “metric” is used in the sense as in general relativity. -- Actually this is just the type of scalar products on the tangent -- space. The actual metric is the function x -> x -> Scalar -- (Needle x) defined by -- --
--   \p q -> m |$| (p.-~!q)
--   
type Metric x = Norm (Needle x) type Metric' x = Variance (Needle x) -- | A Riemannian metric assigns each point on a manifold a scalar product -- on the tangent space. Note that this association is not -- continuous, because the charts/tangent spaces in the bundle are a -- priori disjoint. However, for a proper Riemannian metric, all arising -- expressions of scalar products from needles between points on the -- manifold ought to be differentiable. type RieMetric x = x -> Metric x type RieMetric' x = x -> Metric' x -- | This is the reified form of the property that the interior of a -- semimanifold is a manifold. These constraints would ideally be -- expressed directly as superclass constraints, but that would require -- the UndecidableSuperclasses extension, which is not reliable -- yet. -- -- Also, if all those equality constraints are in scope, GHC tends to -- infer needlessly complicated types like Interior -- (Interior (Needle (Interior x))), which is -- the same as just Needle x. data SemimanifoldWitness x [SemimanifoldWitness] :: forall x. (Semimanifold (Needle x), Needle (Interior x) ~ Needle x, Needle (Needle x) ~ Needle x, Interior (Needle x) ~ Needle x) => BoundarylessWitness (Interior x) -> SemimanifoldWitness x data PseudoAffineWitness x [PseudoAffineWitness] :: forall x. (PseudoAffine (Interior x), PseudoAffine (Needle x)) => SemimanifoldWitness x -> PseudoAffineWitness x data BoundarylessWitness m [BoundarylessWitness] :: forall m. (Semimanifold m, Interior m ~ m) => BoundarylessWitness m boundarylessWitness :: Manifold m => BoundarylessWitness m type DualNeedleWitness x = DualSpaceWitness (Needle x) -- | Require some constraint on a manifold, and also fix the type of the -- manifold's underlying field. For example, WithField ℝ -- HilbertManifold v constrains v to be a real -- (i.e., Double-) Hilbert space. Note that for this to compile, -- you will in general need the -XLiberalTypeSynonyms extension -- (except if the constraint is an actual type class (like -- Manifold): only those can always be partially applied, for -- type constraints this is by default not allowed). type WithField s c x = (c x, s ~ Scalar (Needle x), s ~ Scalar (Needle' x)) type LocallyScalable s x = (PseudoAffine x, LSpace (Needle x), s ~ Scalar (Needle x), s ~ Scalar (Needle' x), Num' s) type LocalLinear x y = LinearMap (Scalar (Needle x)) (Needle x) (Needle y) type LocalBilinear x y = LinearMap (Scalar (Needle x)) (SymmetricTensor (Scalar (Needle x)) (Needle x)) (Needle y) type LocalAffine x y = (Needle y, LocalLinear x y) -- | Like alerp, but actually restricted to the interval between the -- points. alerpB :: (AffineSpace x, VectorSpace (Diff x), Scalar (Diff x) ~ ℝ) => x -> x -> D¹ -> x -- | Interpolate between points, approximately linearly. For points that -- aren't close neighbours (i.e. lie in an almost flat region), the -- pathway is basically undefined – save for its end points. -- -- A proper, really well-defined (on global scales) interpolation only -- makes sense on a Riemannian manifold, as Geodesic. palerp :: (PseudoAffine x, VectorSpace (Needle x)) => x -> x -> Maybe (Scalar (Needle x) -> x) -- | Like palerp, but actually restricted to the interval between -- the points, with a signature like geodesicBetween rather than -- alerp. palerpB :: (PseudoAffine x, VectorSpace (Needle x), Scalar (Needle x) ~ ℝ) => x -> x -> Maybe (D¹ -> x) -- | Instances of this class must be diffeomorphic manifolds, and even have -- canonically isomorphic tangent spaces, so that -- fromPackedVector . asPackedVector :: -- Needle x -> Needle ξ defines a meaningful -- “representational identity“ between these spaces. class (Semimanifold x, Semimanifold ξ, LSpace (Needle x), LSpace (Needle ξ), Scalar (Needle x) ~ Scalar (Needle ξ)) => LocallyCoercible x ξ -- | Must be compatible with the isomorphism on the tangent spaces, i.e. -- locallyTrivialDiffeomorphism (p .+~^ v) ≡ -- locallyTrivialDiffeomorphism p .+~^ coerceNeedle v locallyTrivialDiffeomorphism :: LocallyCoercible x ξ => x -> ξ coerceNeedle :: (LocallyCoercible x ξ, Functor p) => p (x, ξ) -> Needle x -+> Needle ξ coerceNeedle' :: (LocallyCoercible x ξ, Functor p) => p (x, ξ) -> Needle' x -+> Needle' ξ coerceNorm :: (LocallyCoercible x ξ, Functor p) => p (x, ξ) -> Metric x -> Metric ξ coerceVariance :: (LocallyCoercible x ξ, Functor p) => p (x, ξ) -> Metric' x -> Metric' ξ oppositeLocalCoercion :: LocallyCoercible x ξ => CanonicalDiffeomorphism ξ x oppositeLocalCoercion :: (LocallyCoercible x ξ, LocallyCoercible ξ x) => CanonicalDiffeomorphism ξ x interiorLocalCoercion :: (LocallyCoercible x ξ, Functor p (->) (->)) => p (x, ξ) -> CanonicalDiffeomorphism (Interior x) (Interior ξ) interiorLocalCoercion :: (LocallyCoercible x ξ, LocallyCoercible (Interior x) (Interior ξ)) => p (x, ξ) -> CanonicalDiffeomorphism (Interior x) (Interior ξ) data CanonicalDiffeomorphism a b [CanonicalDiffeomorphism] :: LocallyCoercible a b => CanonicalDiffeomorphism a b class ImpliesMetric s where { type family MetricRequirement s x :: Constraint; type MetricRequirement s x = Semimanifold x; } inferMetric :: (ImpliesMetric s, MetricRequirement s x, LSpace (Needle x)) => s x -> Metric x inferMetric' :: (ImpliesMetric s, MetricRequirement s x, LSpace (Needle x)) => s x -> Metric' x coerceMetric :: forall x ξ. (LocallyCoercible x ξ, LSpace (Needle ξ)) => RieMetric ξ -> RieMetric x coerceMetric' :: forall x ξ. (LocallyCoercible x ξ, LSpace (Needle ξ)) => RieMetric' ξ -> RieMetric' x -- | A connected manifold is one where any point can be reached by -- translation from any other point. class (PseudoAffine m) => Connected m -- | Safe version of '(.-~.)'. (.−.) :: Connected m => m -> m -> Needle m infix 6 .−. instance GHC.Show.Show (Math.Manifold.Core.PseudoAffine.Needle x) => GHC.Show.Show (Data.Manifold.PseudoAffine.Local x) instance Data.Manifold.PseudoAffine.Connected Math.Manifold.Core.Types.Internal.ℝ⁰ instance Data.Manifold.PseudoAffine.Connected Math.Manifold.Core.Types.Internal.ℝ instance Data.Manifold.PseudoAffine.Connected Data.Manifold.Types.Primitive.ℝ¹ instance Data.Manifold.PseudoAffine.Connected Data.Manifold.Types.Primitive.ℝ² instance Data.Manifold.PseudoAffine.Connected Data.Manifold.Types.Primitive.ℝ³ instance Data.Manifold.PseudoAffine.Connected Data.Manifold.Types.Primitive.ℝ⁴ instance Data.Manifold.PseudoAffine.Connected Math.Manifold.Core.Types.Internal.S¹ instance Data.Manifold.PseudoAffine.Connected Math.Manifold.Core.Types.Internal.S² instance Data.Manifold.PseudoAffine.Connected Math.Manifold.Core.Types.Internal.ℝP⁰ instance Data.Manifold.PseudoAffine.Connected Math.Manifold.Core.Types.Internal.ℝP¹ instance Data.Manifold.PseudoAffine.Connected Math.Manifold.Core.Types.Internal.ℝP² instance (Data.Manifold.PseudoAffine.Connected x, Data.Manifold.PseudoAffine.Connected y) => Data.Manifold.PseudoAffine.Connected (x, y) instance (Data.Manifold.PseudoAffine.Connected x, Data.Manifold.PseudoAffine.Connected y, Math.Manifold.Core.PseudoAffine.PseudoAffine (Math.Manifold.Core.PseudoAffine.FibreBundle x y)) => Data.Manifold.PseudoAffine.Connected (Math.Manifold.Core.PseudoAffine.FibreBundle x y) instance Data.Manifold.PseudoAffine.ImpliesMetric Math.LinearMap.Category.Norm instance Data.Manifold.PseudoAffine.NumPrime s => Data.Manifold.PseudoAffine.LocallyCoercible (Math.Manifold.VectorSpace.ZeroDimensional.ZeroDim s) (Math.Manifold.VectorSpace.ZeroDimensional.ZeroDim s) instance Data.Manifold.PseudoAffine.NumPrime s => Data.Manifold.PseudoAffine.LocallyCoercible (Linear.V0.V0 s) (Linear.V0.V0 s) instance Data.Manifold.PseudoAffine.LocallyCoercible Math.Manifold.Core.Types.Internal.ℝ Math.Manifold.Core.Types.Internal.ℝ instance Data.Manifold.PseudoAffine.NumPrime s => Data.Manifold.PseudoAffine.LocallyCoercible (Linear.V1.V1 s) (Linear.V1.V1 s) instance Data.Manifold.PseudoAffine.LocallyCoercible (Math.Manifold.Core.Types.Internal.ℝ, Math.Manifold.Core.Types.Internal.ℝ) (Math.Manifold.Core.Types.Internal.ℝ, Math.Manifold.Core.Types.Internal.ℝ) instance Data.Manifold.PseudoAffine.NumPrime s => Data.Manifold.PseudoAffine.LocallyCoercible (Linear.V2.V2 s) (Linear.V2.V2 s) instance Data.Manifold.PseudoAffine.LocallyCoercible (Math.Manifold.Core.Types.Internal.ℝ, (Math.Manifold.Core.Types.Internal.ℝ, Math.Manifold.Core.Types.Internal.ℝ)) (Math.Manifold.Core.Types.Internal.ℝ, (Math.Manifold.Core.Types.Internal.ℝ, Math.Manifold.Core.Types.Internal.ℝ)) instance Data.Manifold.PseudoAffine.LocallyCoercible ((Math.Manifold.Core.Types.Internal.ℝ, Math.Manifold.Core.Types.Internal.ℝ), Math.Manifold.Core.Types.Internal.ℝ) ((Math.Manifold.Core.Types.Internal.ℝ, Math.Manifold.Core.Types.Internal.ℝ), Math.Manifold.Core.Types.Internal.ℝ) instance Data.Manifold.PseudoAffine.NumPrime s => Data.Manifold.PseudoAffine.LocallyCoercible (Linear.V3.V3 s) (Linear.V3.V3 s) instance Data.Manifold.PseudoAffine.NumPrime s => Data.Manifold.PseudoAffine.LocallyCoercible (Linear.V4.V4 s) (Linear.V4.V4 s) instance Data.Manifold.PseudoAffine.NumPrime s => Data.Manifold.PseudoAffine.LocallyCoercible (Math.Manifold.VectorSpace.ZeroDimensional.ZeroDim s) (Linear.V0.V0 s) instance Data.Manifold.PseudoAffine.NumPrime s => Data.Manifold.PseudoAffine.LocallyCoercible (Linear.V0.V0 s) (Math.Manifold.VectorSpace.ZeroDimensional.ZeroDim s) instance Data.Manifold.PseudoAffine.LocallyCoercible Math.Manifold.Core.Types.Internal.ℝ (Linear.V1.V1 Math.Manifold.Core.Types.Internal.ℝ) instance Data.Manifold.PseudoAffine.LocallyCoercible (Linear.V1.V1 Math.Manifold.Core.Types.Internal.ℝ) Math.Manifold.Core.Types.Internal.ℝ instance Data.Manifold.PseudoAffine.LocallyCoercible (Math.Manifold.Core.Types.Internal.ℝ, Math.Manifold.Core.Types.Internal.ℝ) (Linear.V2.V2 Math.Manifold.Core.Types.Internal.ℝ) instance Data.Manifold.PseudoAffine.LocallyCoercible (Linear.V2.V2 Math.Manifold.Core.Types.Internal.ℝ) (Math.Manifold.Core.Types.Internal.ℝ, Math.Manifold.Core.Types.Internal.ℝ) instance Data.Manifold.PseudoAffine.LocallyCoercible ((Math.Manifold.Core.Types.Internal.ℝ, Math.Manifold.Core.Types.Internal.ℝ), Math.Manifold.Core.Types.Internal.ℝ) (Linear.V3.V3 Math.Manifold.Core.Types.Internal.ℝ) instance Data.Manifold.PseudoAffine.LocallyCoercible (Math.Manifold.Core.Types.Internal.ℝ, (Math.Manifold.Core.Types.Internal.ℝ, Math.Manifold.Core.Types.Internal.ℝ)) (Linear.V3.V3 Math.Manifold.Core.Types.Internal.ℝ) instance Data.Manifold.PseudoAffine.LocallyCoercible (Linear.V3.V3 Math.Manifold.Core.Types.Internal.ℝ) ((Math.Manifold.Core.Types.Internal.ℝ, Math.Manifold.Core.Types.Internal.ℝ), Math.Manifold.Core.Types.Internal.ℝ) instance Data.Manifold.PseudoAffine.LocallyCoercible (Linear.V3.V3 Math.Manifold.Core.Types.Internal.ℝ) (Math.Manifold.Core.Types.Internal.ℝ, (Math.Manifold.Core.Types.Internal.ℝ, Math.Manifold.Core.Types.Internal.ℝ)) instance Data.Manifold.PseudoAffine.LocallyCoercible ((Math.Manifold.Core.Types.Internal.ℝ, Math.Manifold.Core.Types.Internal.ℝ), (Math.Manifold.Core.Types.Internal.ℝ, Math.Manifold.Core.Types.Internal.ℝ)) (Linear.V4.V4 Math.Manifold.Core.Types.Internal.ℝ) instance Data.Manifold.PseudoAffine.LocallyCoercible (Linear.V4.V4 Math.Manifold.Core.Types.Internal.ℝ) ((Math.Manifold.Core.Types.Internal.ℝ, Math.Manifold.Core.Types.Internal.ℝ), (Math.Manifold.Core.Types.Internal.ℝ, Math.Manifold.Core.Types.Internal.ℝ)) instance (Math.Manifold.Core.PseudoAffine.Semimanifold a, Math.Manifold.Core.PseudoAffine.Semimanifold b, Math.Manifold.Core.PseudoAffine.Semimanifold c, Math.LinearMap.Category.Class.LSpace (Math.Manifold.Core.PseudoAffine.Needle a), Math.LinearMap.Category.Class.LSpace (Math.Manifold.Core.PseudoAffine.Needle b), Math.LinearMap.Category.Class.LSpace (Math.Manifold.Core.PseudoAffine.Needle c), Data.VectorSpace.Scalar (Math.Manifold.Core.PseudoAffine.Needle a) Data.Type.Equality.~ Data.VectorSpace.Scalar (Math.Manifold.Core.PseudoAffine.Needle b), Data.VectorSpace.Scalar (Math.Manifold.Core.PseudoAffine.Needle b) Data.Type.Equality.~ Data.VectorSpace.Scalar (Math.Manifold.Core.PseudoAffine.Needle c), Data.VectorSpace.Scalar (Data.Manifold.PseudoAffine.Needle' a) Data.Type.Equality.~ Data.VectorSpace.Scalar (Math.Manifold.Core.PseudoAffine.Needle a), Data.VectorSpace.Scalar (Data.Manifold.PseudoAffine.Needle' b) Data.Type.Equality.~ Data.VectorSpace.Scalar (Math.Manifold.Core.PseudoAffine.Needle b), Data.VectorSpace.Scalar (Data.Manifold.PseudoAffine.Needle' c) Data.Type.Equality.~ Data.VectorSpace.Scalar (Math.Manifold.Core.PseudoAffine.Needle c)) => Data.Manifold.PseudoAffine.LocallyCoercible (a, (b, c)) ((a, b), c) instance (Math.Manifold.Core.PseudoAffine.Semimanifold a, Math.Manifold.Core.PseudoAffine.Semimanifold b, Math.Manifold.Core.PseudoAffine.Semimanifold c, Math.LinearMap.Category.Class.LSpace (Math.Manifold.Core.PseudoAffine.Needle a), Math.LinearMap.Category.Class.LSpace (Math.Manifold.Core.PseudoAffine.Needle b), Math.LinearMap.Category.Class.LSpace (Math.Manifold.Core.PseudoAffine.Needle c), Data.VectorSpace.Scalar (Math.Manifold.Core.PseudoAffine.Needle a) Data.Type.Equality.~ Data.VectorSpace.Scalar (Math.Manifold.Core.PseudoAffine.Needle b), Data.VectorSpace.Scalar (Math.Manifold.Core.PseudoAffine.Needle b) Data.Type.Equality.~ Data.VectorSpace.Scalar (Math.Manifold.Core.PseudoAffine.Needle c), Data.VectorSpace.Scalar (Data.Manifold.PseudoAffine.Needle' a) Data.Type.Equality.~ Data.VectorSpace.Scalar (Math.Manifold.Core.PseudoAffine.Needle a), Data.VectorSpace.Scalar (Data.Manifold.PseudoAffine.Needle' b) Data.Type.Equality.~ Data.VectorSpace.Scalar (Math.Manifold.Core.PseudoAffine.Needle b), Data.VectorSpace.Scalar (Data.Manifold.PseudoAffine.Needle' c) Data.Type.Equality.~ Data.VectorSpace.Scalar (Math.Manifold.Core.PseudoAffine.Needle c)) => Data.Manifold.PseudoAffine.LocallyCoercible ((a, b), c) (a, (b, c)) instance (Math.Manifold.Core.PseudoAffine.PseudoAffine m, Math.LinearMap.Category.Class.LSpace (Math.Manifold.Core.PseudoAffine.Needle m), Math.Manifold.Core.PseudoAffine.Interior m Data.Type.Equality.~ m) => Data.Manifold.PseudoAffine.Manifold m instance (Math.LinearMap.Category.Class.LinearSpace (a n), Math.Manifold.Core.PseudoAffine.Needle (a n) Data.Type.Equality.~ a n, Math.Manifold.Core.PseudoAffine.Interior (a n) Data.Type.Equality.~ a n) => Math.Manifold.Core.PseudoAffine.Semimanifold (Linear.Affine.Point a n) instance (Math.LinearMap.Category.Class.LinearSpace (a n), Math.Manifold.Core.PseudoAffine.Needle (a n) Data.Type.Equality.~ a n, Math.Manifold.Core.PseudoAffine.Interior (a n) Data.Type.Equality.~ a n) => Math.Manifold.Core.PseudoAffine.PseudoAffine (Linear.Affine.Point a n) instance Math.Manifold.Core.PseudoAffine.Semimanifold Math.Manifold.Core.Types.Internal.S² instance Math.Manifold.Core.PseudoAffine.PseudoAffine Math.Manifold.Core.Types.Internal.S² instance Math.Manifold.Core.PseudoAffine.Semimanifold Math.Manifold.Core.Types.Internal.ℝP² instance Math.Manifold.Core.PseudoAffine.PseudoAffine Math.Manifold.Core.Types.Internal.ℝP² module Data.Manifold.FibreBundle pattern TangentBundle :: m -> Needle m -> FibreBundle m (Needle m) -- | Provided for convenience. Flipped synonym of FibreBundle, -- restricted to manifolds without boundary (so the type of the whole can -- be inferred from its interior). pattern (:@.) :: f -> m -> FibreBundle m f infixr 5 :@. -- | A zero vector in the fibre bundle at the given position. Intended to -- be used with tangent-modifying lenses such as delta. tangentAt :: (AdditiveGroup (Needle m), m ~ Interior m) => m -> TangentBundle m data TransportOnNeedleWitness k m f [TransportOnNeedle] :: ParallelTransporting (LinearFunction (Scalar (Needle m))) (Needle m) (Needle f) => TransportOnNeedleWitness k m f data ForgetTransportProperties k m f [ForgetTransportProperties] :: ParallelTransporting (->) m f => ForgetTransportProperties k m f class (PseudoAffine m, m ~ Interior m, Category k, Object k f) => ParallelTransporting k m f transportOnNeedleWitness :: ParallelTransporting k m f => TransportOnNeedleWitness k m f transportOnNeedleWitness :: (ParallelTransporting k m f, ParallelTransporting (LinearFunction (Scalar (Needle m))) (Needle m) (Needle f)) => TransportOnNeedleWitness k m f forgetTransportProperties :: ParallelTransporting k m f => ForgetTransportProperties k m f forgetTransportProperties :: (ParallelTransporting k m f, ParallelTransporting (->) m f) => ForgetTransportProperties k m f parallelTransport :: ParallelTransporting k m f => m -> Needle m -> k f f translateAndInvblyParTransport :: ParallelTransporting k m f => m -> Needle m -> (m, (k f f, k f f)) -- | ex -> ey, ey -> ez, ez -> ex transformEmbeddedTangents :: forall x f v. (NaturallyEmbedded (FibreBundle x f) (FibreBundle v v), v ~ Interior v) => (v -> v) -> FibreBundle x f -> FibreBundle x f instance (Math.Manifold.Core.PseudoAffine.PseudoAffine m, m Data.Type.Equality.~ Math.Manifold.Core.PseudoAffine.Interior m, s Data.Type.Equality.~ Data.VectorSpace.Scalar (Math.Manifold.Core.PseudoAffine.Needle m), Math.LinearMap.Category.Class.Num' s) => Data.Manifold.FibreBundle.ParallelTransporting Control.Category.Discrete.Discrete m (Math.Manifold.VectorSpace.ZeroDimensional.ZeroDim s) instance (Math.Manifold.Core.PseudoAffine.PseudoAffine m, m Data.Type.Equality.~ Math.Manifold.Core.PseudoAffine.Interior m, s Data.Type.Equality.~ Data.VectorSpace.Scalar (Math.Manifold.Core.PseudoAffine.Needle m), Math.LinearMap.Category.Class.Num' s) => Data.Manifold.FibreBundle.ParallelTransporting (Math.LinearMap.Asserted.LinearFunction s) m (Math.Manifold.VectorSpace.ZeroDimensional.ZeroDim s) instance (Math.Manifold.Core.PseudoAffine.PseudoAffine m, m Data.Type.Equality.~ Math.Manifold.Core.PseudoAffine.Interior m, s Data.Type.Equality.~ Data.VectorSpace.Scalar (Math.Manifold.Core.PseudoAffine.Needle m), Math.LinearMap.Category.Class.Num' s) => Data.Manifold.FibreBundle.ParallelTransporting (->) m (Math.Manifold.VectorSpace.ZeroDimensional.ZeroDim s) instance (Control.Category.Constrained.Category k, Control.Category.Constrained.Object k Math.Manifold.Core.Types.Internal.ℝ) => Data.Manifold.FibreBundle.ParallelTransporting k Math.Manifold.Core.Types.Internal.ℝ Math.Manifold.Core.Types.Internal.ℝ instance (Control.Category.Constrained.Category k, Control.Category.Constrained.Object k Data.Manifold.Types.Primitive.ℝ²) => Data.Manifold.FibreBundle.ParallelTransporting k Data.Manifold.Types.Primitive.ℝ² Data.Manifold.Types.Primitive.ℝ² instance (Control.Category.Constrained.Category k, Control.Category.Constrained.Object k Data.Manifold.Types.Primitive.ℝ³) => Data.Manifold.FibreBundle.ParallelTransporting k Data.Manifold.Types.Primitive.ℝ³ Data.Manifold.Types.Primitive.ℝ³ instance (Control.Category.Constrained.Category k, Control.Category.Constrained.Object k Data.Manifold.Types.Primitive.ℝ⁴) => Data.Manifold.FibreBundle.ParallelTransporting k Data.Manifold.Types.Primitive.ℝ⁴ Data.Manifold.Types.Primitive.ℝ⁴ instance (Control.Category.Constrained.Category k, Control.Category.Constrained.Object k Math.Manifold.Core.Types.Internal.ℝ) => Data.Manifold.FibreBundle.ParallelTransporting k Math.Manifold.Core.Types.Internal.S¹ Math.Manifold.Core.Types.Internal.ℝ instance (Control.Arrow.Constrained.EnhancedCat k (Math.LinearMap.Category.Class.LinearMap Math.Manifold.Core.Types.Internal.ℝ), Control.Category.Constrained.Object k Data.Manifold.Types.Primitive.ℝ²) => Data.Manifold.FibreBundle.ParallelTransporting k Math.Manifold.Core.Types.Internal.S² Data.Manifold.Types.Primitive.ℝ² instance (Data.Manifold.FibreBundle.ParallelTransporting k a fa, Data.Manifold.FibreBundle.ParallelTransporting k b fb, Math.Manifold.Core.PseudoAffine.PseudoAffine fa, Math.Manifold.Core.PseudoAffine.PseudoAffine fb, Data.VectorSpace.Scalar (Math.Manifold.Core.PseudoAffine.Needle a) Data.Type.Equality.~ s, Data.VectorSpace.Scalar (Math.Manifold.Core.PseudoAffine.Needle b) Data.Type.Equality.~ s, Data.VectorSpace.Scalar (Math.Manifold.Core.PseudoAffine.Needle fa) Data.Type.Equality.~ s, Data.VectorSpace.Scalar (Math.Manifold.Core.PseudoAffine.Needle fb) Data.Type.Equality.~ s, Math.LinearMap.Category.Class.Num' s, Control.Arrow.Constrained.Morphism k, Control.Category.Constrained.ObjectPair k fa fb) => Data.Manifold.FibreBundle.ParallelTransporting k (a, b) (fa, fb) instance (Data.Manifold.FibreBundle.ParallelTransporting k a f, Data.Manifold.FibreBundle.ParallelTransporting k a g, Data.Manifold.FibreBundle.ParallelTransporting (Math.LinearMap.Asserted.LinearFunction s) (Math.Manifold.Core.PseudoAffine.Needle a) (Math.Manifold.Core.PseudoAffine.Needle f, Math.Manifold.Core.PseudoAffine.Needle g), Math.Manifold.Core.PseudoAffine.PseudoAffine f, Math.Manifold.Core.PseudoAffine.PseudoAffine g, Control.Arrow.Constrained.Morphism k, Control.Category.Constrained.ObjectPair k f g) => Data.Manifold.FibreBundle.ParallelTransporting k a (f, g) instance (Data.Manifold.FibreBundle.ParallelTransporting (Math.LinearMap.Asserted.LinearFunction (Data.VectorSpace.Scalar f)) m f, Data.AdditiveGroup.AdditiveGroup m, Data.VectorSpace.VectorSpace f) => Data.AdditiveGroup.AdditiveGroup (Math.Manifold.Core.PseudoAffine.FibreBundle m f) instance (Data.Manifold.FibreBundle.ParallelTransporting (->) m (Math.Manifold.Core.PseudoAffine.Interior f), Math.Manifold.Core.PseudoAffine.Semimanifold f, Data.Manifold.FibreBundle.ParallelTransporting (Math.LinearMap.Asserted.LinearFunction s) (Math.Manifold.Core.PseudoAffine.Needle m) (Math.Manifold.Core.PseudoAffine.Needle f), s Data.Type.Equality.~ Data.VectorSpace.Scalar (Math.Manifold.Core.PseudoAffine.Needle m)) => Math.Manifold.Core.PseudoAffine.Semimanifold (Math.Manifold.Core.PseudoAffine.FibreBundle m f) instance (Data.Manifold.FibreBundle.ParallelTransporting (->) m f, Data.Manifold.FibreBundle.ParallelTransporting (->) m (Math.Manifold.Core.PseudoAffine.Interior f), Math.Manifold.Core.PseudoAffine.PseudoAffine f, Data.Manifold.FibreBundle.ParallelTransporting (Math.LinearMap.Asserted.LinearFunction s) (Math.Manifold.Core.PseudoAffine.Needle m) (Math.Manifold.Core.PseudoAffine.Needle f), s Data.Type.Equality.~ Data.VectorSpace.Scalar (Math.Manifold.Core.PseudoAffine.Needle m)) => Math.Manifold.Core.PseudoAffine.PseudoAffine (Math.Manifold.Core.PseudoAffine.FibreBundle m f) instance (Data.AdditiveGroup.AdditiveGroup f, x Data.Type.Equality.~ Math.Manifold.Core.PseudoAffine.Interior x) => Data.Manifold.Types.Primitive.NaturallyEmbedded x (Math.Manifold.Core.PseudoAffine.FibreBundle x f) instance (Data.Manifold.Types.Primitive.NaturallyEmbedded m v, Data.VectorSpace.VectorSpace f) => Data.Manifold.Types.Primitive.NaturallyEmbedded (Math.Manifold.Core.PseudoAffine.FibreBundle m Math.Manifold.Core.Types.Internal.ℝ⁰) (Math.Manifold.Core.PseudoAffine.FibreBundle v f) instance (Data.AdditiveGroup.AdditiveGroup y, Data.AdditiveGroup.AdditiveGroup g) => Data.Manifold.Types.Primitive.NaturallyEmbedded (Math.Manifold.Core.PseudoAffine.FibreBundle x f) (Math.Manifold.Core.PseudoAffine.FibreBundle (x, y) (f, g)) instance Data.Manifold.Types.Primitive.NaturallyEmbedded v w => Data.Manifold.Types.Primitive.NaturallyEmbedded (Math.Manifold.Core.PseudoAffine.FibreBundle Math.Manifold.Core.Types.Internal.ℝ v) (Math.Manifold.Core.PseudoAffine.FibreBundle Math.Manifold.Core.Types.Internal.ℝ w) instance Data.Manifold.Types.Primitive.NaturallyEmbedded v w => Data.Manifold.Types.Primitive.NaturallyEmbedded (Math.Manifold.Core.PseudoAffine.FibreBundle Data.Manifold.Types.Primitive.ℝ² v) (Math.Manifold.Core.PseudoAffine.FibreBundle Data.Manifold.Types.Primitive.ℝ² w) instance Data.Manifold.Types.Primitive.NaturallyEmbedded v w => Data.Manifold.Types.Primitive.NaturallyEmbedded (Math.Manifold.Core.PseudoAffine.FibreBundle Data.Manifold.Types.Primitive.ℝ³ v) (Math.Manifold.Core.PseudoAffine.FibreBundle Data.Manifold.Types.Primitive.ℝ³ w) instance Data.Manifold.Types.Primitive.NaturallyEmbedded v w => Data.Manifold.Types.Primitive.NaturallyEmbedded (Math.Manifold.Core.PseudoAffine.FibreBundle Data.Manifold.Types.Primitive.ℝ⁴ v) (Math.Manifold.Core.PseudoAffine.FibreBundle Data.Manifold.Types.Primitive.ℝ⁴ w) instance Data.Manifold.Types.Primitive.NaturallyEmbedded (Math.Manifold.Core.PseudoAffine.FibreBundle Math.Manifold.Core.Types.Internal.S¹ Math.Manifold.Core.Types.Internal.ℝ) (Math.Manifold.Core.PseudoAffine.FibreBundle Data.Manifold.Types.Primitive.ℝ² Data.Manifold.Types.Primitive.ℝ²) instance Data.Manifold.Types.Primitive.NaturallyEmbedded (Math.Manifold.Core.PseudoAffine.FibreBundle Math.Manifold.Core.Types.Internal.S² Data.Manifold.Types.Primitive.ℝ²) (Math.Manifold.Core.PseudoAffine.FibreBundle Data.Manifold.Types.Primitive.ℝ³ Data.Manifold.Types.Primitive.ℝ³) instance Math.Rotations.Class.Rotatable (Math.Manifold.Core.PseudoAffine.FibreBundle Math.Manifold.Core.Types.Internal.S² Data.Manifold.Types.Primitive.ℝ²) module Data.Manifold.Atlas class Semimanifold m => Atlas m where { type family ChartIndex m :: *; } chartReferencePoint :: Atlas m => ChartIndex m -> m interiorChartReferencePoint :: (Atlas m, Functor p) => p m -> ChartIndex m -> Interior m lookupAtlas :: Atlas m => m -> ChartIndex m -- | The AffineSpace class plus manifold constraints. type AffineManifold m = (Atlas m, Manifold m, AffineSpace m, Needle m ~ Diff m, HasTrie (ChartIndex m)) -- | An euclidean space is a real affine space whose tangent space is a -- Hilbert space. type EuclidSpace x = (AffineManifold x, InnerSpace (Diff x), DualVector (Diff x) ~ Diff x, Floating (Scalar (Diff x))) euclideanMetric :: EuclidSpace x => proxy x -> Metric x instance Data.Manifold.Atlas.Atlas (Math.Manifold.VectorSpace.ZeroDimensional.ZeroDim s) instance Data.Manifold.Atlas.Atlas Math.Manifold.Core.Types.Internal.ℝ instance GHC.Num.Num s => Data.Manifold.Atlas.Atlas (Linear.V0.V0 s) instance GHC.Num.Num s => Data.Manifold.Atlas.Atlas (Linear.V1.V1 s) instance GHC.Num.Num s => Data.Manifold.Atlas.Atlas (Linear.V2.V2 s) instance GHC.Num.Num s => Data.Manifold.Atlas.Atlas (Linear.V3.V3 s) instance GHC.Num.Num s => Data.Manifold.Atlas.Atlas (Linear.V4.V4 s) instance (Math.LinearMap.Category.Class.LinearSpace v, Data.VectorSpace.Scalar v Data.Type.Equality.~ s, Math.LinearMap.Category.Class.TensorSpace w, Data.VectorSpace.Scalar w Data.Type.Equality.~ s) => Data.Manifold.Atlas.Atlas (Math.LinearMap.Category.Class.LinearMap s v w) instance (Math.LinearMap.Category.Class.TensorSpace v, Data.VectorSpace.Scalar v Data.Type.Equality.~ s, Math.LinearMap.Category.Class.TensorSpace w, Data.VectorSpace.Scalar w Data.Type.Equality.~ s) => Data.Manifold.Atlas.Atlas (Math.LinearMap.Category.Class.Tensor s v w) instance (Data.Manifold.Atlas.Atlas x, Data.Manifold.Atlas.Atlas y) => Data.Manifold.Atlas.Atlas (x, y) instance Data.Manifold.Atlas.Atlas Math.Manifold.Core.Types.Internal.S⁰ instance Data.Manifold.Atlas.Atlas Math.Manifold.Core.Types.Internal.S¹ instance Data.Manifold.Atlas.Atlas Math.Manifold.Core.Types.Internal.S² instance (Math.LinearMap.Category.Class.LinearSpace (a n), Math.Manifold.Core.PseudoAffine.Needle (a n) Data.Type.Equality.~ a n, Math.Manifold.Core.PseudoAffine.Interior (a n) Data.Type.Equality.~ a n) => Data.Manifold.Atlas.Atlas (Linear.Affine.Point a n) module Data.Function.Affine data Affine s d c [Affine] :: (ChartIndex d :->: (c, LinearMap s (Needle d) (Needle c))) -> Affine s d c evalAffine :: forall s x y. (Manifold x, Atlas x, HasTrie (ChartIndex x), Manifold y, s ~ Scalar (Needle x), s ~ Scalar (Needle y)) => Affine s x y -> x -> (y, LinearMap s (Needle x) (Needle y)) fromOffsetSlope :: forall s x y. (LinearSpace x, Atlas x, HasTrie (ChartIndex x), Manifold y, s ~ Scalar x, s ~ Scalar (Needle y)) => y -> LinearMap s x (Needle y) -> Affine s x y lensEmbedding :: forall k s x c. (Num' s, LinearSpace x, LinearSpace c, Object k x, Object k c, Scalar x ~ s, Scalar c ~ s, EnhancedCat k (LinearMap s)) => Lens' x c -> Embedding k c x correspondingDirections :: forall s x c t. (WithField s AffineManifold c, WithField s AffineManifold x, SemiInner (Needle c), SemiInner (Needle x), RealFrac' s, Traversable t) => (Interior c, Interior x) -> t (Needle c, Needle x) -> Maybe (Embedding (Affine s) c x) instance Control.Category.Constrained.Category (Data.Function.Affine.Affine s) instance Math.LinearMap.Category.Class.Num' s => Control.Category.Constrained.Cartesian (Data.Function.Affine.Affine s) instance Math.LinearMap.Category.Class.Num' s => Control.Arrow.Constrained.Morphism (Data.Function.Affine.Affine s) instance Math.LinearMap.Category.Class.Num' s => Control.Arrow.Constrained.PreArrow (Data.Function.Affine.Affine s) instance Math.LinearMap.Category.Class.Num' s => Control.Arrow.Constrained.WellPointed (Data.Function.Affine.Affine s) instance Control.Arrow.Constrained.EnhancedCat (->) (Data.Function.Affine.Affine s) instance Control.Arrow.Constrained.EnhancedCat (Data.Function.Affine.Affine s) (Math.LinearMap.Category.Class.LinearMap s) instance (Data.Manifold.Atlas.Atlas x, Data.MemoTrie.HasTrie (Data.Manifold.Atlas.ChartIndex x), Math.LinearMap.Category.Class.LinearSpace (Math.Manifold.Core.PseudoAffine.Needle x), Data.VectorSpace.Scalar (Math.Manifold.Core.PseudoAffine.Needle x) Data.Type.Equality.~ s, Data.Manifold.PseudoAffine.Manifold y, Data.VectorSpace.Scalar (Math.Manifold.Core.PseudoAffine.Needle y) Data.Type.Equality.~ s) => Math.Manifold.Core.PseudoAffine.Semimanifold (Data.Function.Affine.Affine s x y) instance (Data.Manifold.Atlas.Atlas x, Data.MemoTrie.HasTrie (Data.Manifold.Atlas.ChartIndex x), Math.LinearMap.Category.Class.LinearSpace (Math.Manifold.Core.PseudoAffine.Needle x), Data.VectorSpace.Scalar (Math.Manifold.Core.PseudoAffine.Needle x) Data.Type.Equality.~ s, Data.Manifold.PseudoAffine.Manifold y, Data.VectorSpace.Scalar (Math.Manifold.Core.PseudoAffine.Needle y) Data.Type.Equality.~ s) => Math.Manifold.Core.PseudoAffine.PseudoAffine (Data.Function.Affine.Affine s x y) instance (Data.Manifold.Atlas.Atlas x, Data.MemoTrie.HasTrie (Data.Manifold.Atlas.ChartIndex x), Math.LinearMap.Category.Class.LinearSpace (Math.Manifold.Core.PseudoAffine.Needle x), Data.VectorSpace.Scalar (Math.Manifold.Core.PseudoAffine.Needle x) Data.Type.Equality.~ s, Data.Manifold.PseudoAffine.Manifold y, Data.VectorSpace.Scalar (Math.Manifold.Core.PseudoAffine.Needle y) Data.Type.Equality.~ s) => Data.AffineSpace.AffineSpace (Data.Function.Affine.Affine s x y) instance (Data.Manifold.Atlas.Atlas x, Data.MemoTrie.HasTrie (Data.Manifold.Atlas.ChartIndex x), Math.LinearMap.Category.Class.LinearSpace (Math.Manifold.Core.PseudoAffine.Needle x), Data.VectorSpace.Scalar (Math.Manifold.Core.PseudoAffine.Needle x) Data.Type.Equality.~ s, Math.LinearMap.Category.Class.LinearSpace y, Data.VectorSpace.Scalar y Data.Type.Equality.~ s, Math.LinearMap.Category.Class.Num' s) => Data.AdditiveGroup.AdditiveGroup (Data.Function.Affine.Affine s x y) instance (Data.Manifold.Atlas.Atlas x, Data.MemoTrie.HasTrie (Data.Manifold.Atlas.ChartIndex x), Math.LinearMap.Category.Class.LinearSpace (Math.Manifold.Core.PseudoAffine.Needle x), Data.VectorSpace.Scalar (Math.Manifold.Core.PseudoAffine.Needle x) Data.Type.Equality.~ s, Math.LinearMap.Category.Class.LinearSpace y, Data.VectorSpace.Scalar y Data.Type.Equality.~ s, Math.LinearMap.Category.Class.Num' s) => Data.VectorSpace.VectorSpace (Data.Function.Affine.Affine s x y) instance Control.Arrow.Constrained.EnhancedCat (Data.Embedding.Embedding (Data.Function.Affine.Affine s)) (Data.Embedding.Embedding (Math.LinearMap.Category.Class.LinearMap s)) module Data.Function.Differentiable -- | The category of differentiable functions between manifolds over scalar -- s. -- -- As you might guess, these offer automatic differentiation of -- sorts (basically, simple forward AD), but that's in itself is not -- really the killer feature here. More interestingly, we actually have -- the (à la Curry-Howard) proof built in: the function f -- has at x₀ derivative f'ₓ₀, if, for¹ ε>0, there -- exists δ such that |f x − (f x₀ + -- xf'ₓ₀)| < ε for all |xx₀| -- < δ. -- -- Observe that, though this looks quite similar to the standard -- definition of differentiability, it is not equivalent thereto – in -- fact it does not prove any analytic properties at all. To make it -- equivalent, we need a lower bound on δ: simply δ gives -- us continuity, and for continuous differentiability, δ must -- grow at least like √ε for small ε. Neither of these -- conditions are enforced by the type system, but we do require them for -- any allowed values because these proofs are obviously tremendously -- useful – for instance, you can have a root-finding algorithm and -- actually be sure you get all solutions correctly, not just -- some that are (hopefully) the closest to some reference point -- you'd need to laborously define! -- -- Unfortunately however, this also prevents doing any serious algebra -- with the category, because even something as simple as division -- necessary introduces singularities where the derivatives must diverge. -- Not to speak of many e.g. trigonometric functions that are undefined -- on whole regions. The PWDiffable and RWDiffable -- categories have explicit handling for those issues built in; you may -- simply use these categories even when you know the result will be -- smooth in your relevant domain (or must be, for e.g. physics reasons). -- -- ¹(The implementation does not deal with ε and δ as -- difference-bounding reals, but rather as metric tensors which define a -- boundary by prohibiting the overlap from exceeding one. This makes the -- category actually work on general manifolds.) data Differentiable s d c -- | Category of functions that, where defined, have an open region in -- which they are continuously differentiable. Hence -- RegionWiseDiff'able. Basically these are the partial version of -- PWDiffable. -- -- Though the possibility of undefined regions is of course not too nice -- (we don't need Java to demonstrate this with its everywhere-looming -- null values...), this category will propably be the -- “workhorse” for most serious calculus applications, because it -- contains all the usual trig etc. functions and of course everything -- algebraic you can do in the reals. -- -- The easiest way to define ordinary functions in this category is hence -- with its AgentValues, which have instances of the standard -- classes Num through Floating. For instance, the -- following defines the binary entropy as a differentiable -- function on the interval ]0,1[: (it will actually know -- where it's defined and where not. And I don't mean you need to -- exhaustively isNaN-check all results...) -- --
--   hb :: RWDiffable ℝ ℝ ℝ
--   hb = alg (\p -> - p * logBase 2 p - (1-p) * logBase 2 (1-p) )
--   
data RWDiffable s d c -- | Require the LHS to be defined before considering the RHS as result. -- This works analogously to the standard Applicative method -- --
--   (*>) :: Maybe a -> Maybe b -> Maybe b
--   Just _ *> a = a
--   _      *> a = Nothing
--   
--   
(?->) :: (RealDimension n, LocallyScalable n a, LocallyScalable n b, LocallyScalable n c, Manifold b, Manifold c, SimpleSpace (Needle b), SimpleSpace (Needle c)) => RWDfblFuncValue n c a -> RWDfblFuncValue n c b -> RWDfblFuncValue n c b infixr 4 ?-> -- | Return the RHS, if it is less than the LHS. (Really the purpose is -- just to compare the values, but returning one of them allows chaining -- of comparison operators like in Python.) Note that less-than -- comparison is equivalent to less-or-equal comparison, because -- there is no such thing as equality. (?>) :: (RealDimension n, LocallyScalable n a, Manifold a, SimpleSpace (Needle a)) => RWDfblFuncValue n a n -> RWDfblFuncValue n a n -> RWDfblFuncValue n a n infixl 5 ?> -- | Return the RHS, if it is greater than the LHS. (?<) :: (RealDimension n, LocallyScalable n a, Manifold a, SimpleSpace (Needle a)) => RWDfblFuncValue n a n -> RWDfblFuncValue n a n -> RWDfblFuncValue n a n infixl 5 ?< -- | Try the LHS, if it is undefined use the RHS. This works analogously to -- the standard Alternative method -- --
--   (<|>) :: Maybe a -> Maybe a -> Maybe a
--   Just x <|> _ = Just x
--   _      <|> a = a
--   
--   
-- -- Basically a weaker and agent-ised version of backupRegions. (?|:) :: (RealDimension n, LocallyScalable n a, LocallyScalable n b, Manifold a, Manifold b, SimpleSpace (Needle a), SimpleSpace (Needle b)) => RWDfblFuncValue n a b -> RWDfblFuncValue n a b -> RWDfblFuncValue n a b infixl 3 ?|: -- | Replace the regions in which the first function is undefined with -- values from the second function. backupRegions :: (RealDimension n, LocallyScalable n a, LocallyScalable n b) => RWDiffable n a b -> RWDiffable n a b -> RWDiffable n a b -- | A pathwise connected subset of a manifold m, whose tangent -- space has scalar s. data Region s m -- | Represent a Region by a smooth function which is positive -- within the region, and crosses zero at the boundary. smoothIndicator :: LocallyScalable ℝ q => Region ℝ q -> Differentiable ℝ q ℝ discretisePathIn :: (WithField ℝ Manifold y, SimpleSpace (Needle y)) => Int -> ℝInterval -> (RieMetric ℝ, RieMetric y) -> Differentiable ℝ ℝ y -> [(ℝ, y)] discretisePathSegs :: (WithField ℝ Manifold y, SimpleSpace (Needle y)) => Int -> (RieMetric ℝ, RieMetric y) -> RWDiffable ℝ ℝ y -> ([[(ℝ, y)]], [[(ℝ, y)]]) continuityRanges :: WithField ℝ Manifold y => Int -> RieMetric ℝ -> RWDiffable ℝ ℝ y -> ([ℝInterval], [ℝInterval]) regionOfContinuityAround :: RWDiffable ℝ q x -> q -> Region ℝ q analyseLocalBehaviour :: RWDiffable ℝ ℝ ℝ -> ℝ -> Maybe ((ℝ, ℝ), ℝ -> Maybe ℝ) intervalImages :: Int -> (RieMetric ℝ, RieMetric ℝ) -> RWDiffable ℝ ℝ ℝ -> ([(ℝInterval, ℝInterval)], [(ℝInterval, ℝInterval)]) instance Data.Function.Differentiable.RealDimension s => Control.Category.Constrained.HasAgent (Data.Function.Differentiable.Data.RWDiffable s) instance Data.Function.Differentiable.RealDimension s => Control.Arrow.Constrained.CartesianAgent (Data.Function.Differentiable.Data.RWDiffable s) instance Data.Function.Differentiable.RealDimension s => Control.Arrow.Constrained.PointAgent (Data.Function.Differentiable.RWDfblFuncValue s) (Data.Function.Differentiable.Data.RWDiffable s) a x instance (Data.Manifold.PseudoAffine.WithField s Data.Manifold.PseudoAffine.Manifold a, Math.VectorSpace.Docile.SimpleSpace (Math.Manifold.Core.PseudoAffine.Needle a), Data.Manifold.Atlas.Atlas v, Data.MemoTrie.HasTrie (Data.Manifold.Atlas.ChartIndex v), Math.VectorSpace.Docile.SimpleSpace v, Data.VectorSpace.Scalar v Data.Type.Equality.~ s, Data.Function.Differentiable.RealDimension s) => Data.AdditiveGroup.AdditiveGroup (Data.Function.Differentiable.RWDfblFuncValue s a v) instance (Data.Function.Differentiable.RealDimension n, Data.Manifold.PseudoAffine.WithField n Data.Manifold.PseudoAffine.Manifold a, Data.Manifold.PseudoAffine.LocallyScalable n a, Math.VectorSpace.Docile.SimpleSpace (Math.Manifold.Core.PseudoAffine.Needle a)) => GHC.Num.Num (Data.Function.Differentiable.RWDfblFuncValue n a n) instance (Data.Function.Differentiable.RealDimension n, Data.Manifold.PseudoAffine.WithField n Data.Manifold.PseudoAffine.Manifold a, Data.Manifold.PseudoAffine.LocallyScalable n a, Math.VectorSpace.Docile.SimpleSpace (Math.Manifold.Core.PseudoAffine.Needle a)) => GHC.Real.Fractional (Data.Function.Differentiable.RWDfblFuncValue n a n) instance (Data.Function.Differentiable.RealDimension n, Data.Manifold.PseudoAffine.WithField n Data.Manifold.PseudoAffine.Manifold a, Data.Manifold.PseudoAffine.LocallyScalable n a, Math.VectorSpace.Docile.SimpleSpace (Math.Manifold.Core.PseudoAffine.Needle a)) => GHC.Float.Floating (Data.Function.Differentiable.RWDfblFuncValue n a n) instance Math.VectorSpace.Docile.RealFrac' s => Control.Arrow.Constrained.CartesianAgent (Data.Function.Differentiable.Data.Differentiable s) instance Math.VectorSpace.Docile.RealFrac' s => Control.Arrow.Constrained.PointAgent (Data.Function.Differentiable.DfblFuncValue s) (Data.Function.Differentiable.Data.Differentiable s) a x instance (Math.LinearMap.Category.Class.LinearSpace v, Data.VectorSpace.Scalar v Data.Type.Equality.~ s, Data.Manifold.PseudoAffine.LocallyScalable s a, Math.VectorSpace.Docile.RealFloat' s) => Data.AdditiveGroup.AdditiveGroup (Data.Function.Differentiable.DfblFuncValue s a v) instance (Data.Function.Differentiable.RealDimension n, Data.Manifold.PseudoAffine.LocallyScalable n a) => GHC.Num.Num (Data.Function.Differentiable.DfblFuncValue n a n) instance Data.Function.Differentiable.RealDimension s => Control.Arrow.Constrained.EnhancedCat (->) (Data.Function.Differentiable.Data.Differentiable s) instance Data.Function.Differentiable.RealDimension s => Control.Category.Constrained.Category (Data.Function.Differentiable.Data.RWDiffable s) instance Data.Function.Differentiable.RealDimension s => Control.Arrow.Constrained.EnhancedCat (Data.Function.Differentiable.Data.RWDiffable s) (Data.Function.Differentiable.Data.Differentiable s) instance Data.Function.Differentiable.RealDimension s => Control.Category.Constrained.Cartesian (Data.Function.Differentiable.Data.RWDiffable s) instance Data.Function.Differentiable.RealDimension s => Control.Arrow.Constrained.Morphism (Data.Function.Differentiable.Data.RWDiffable s) instance Data.Function.Differentiable.RealDimension s => Control.Arrow.Constrained.PreArrow (Data.Function.Differentiable.Data.RWDiffable s) instance Data.Function.Differentiable.RealDimension s => Control.Arrow.Constrained.WellPointed (Data.Function.Differentiable.Data.RWDiffable s) instance Math.VectorSpace.Docile.RealFrac' s => Control.Category.Constrained.Category (Data.Function.Differentiable.Data.Differentiable s) instance Math.VectorSpace.Docile.RealFrac' s => Control.Category.Constrained.Cartesian (Data.Function.Differentiable.Data.Differentiable s) instance Math.VectorSpace.Docile.RealFrac' s => Control.Arrow.Constrained.Morphism (Data.Function.Differentiable.Data.Differentiable s) instance Math.VectorSpace.Docile.RealFrac' s => Control.Arrow.Constrained.PreArrow (Data.Function.Differentiable.Data.Differentiable s) instance Math.VectorSpace.Docile.RealFrac' s => Control.Arrow.Constrained.WellPointed (Data.Function.Differentiable.Data.Differentiable s) instance Math.VectorSpace.Docile.RealFrac' s => Control.Category.Constrained.HasAgent (Data.Function.Differentiable.Data.Differentiable s) -- | Stiefel manifolds are a generalisation of the concept of the -- UnitSphere in real vector spaces. The n-th Stiefel -- manifold is the space of all possible configurations of n -- orthonormal vectors. In the case n = 1, simply a single -- normalised vector, i.e. a vector on the unit sphere. -- -- Alternatively, the stiefel manifolds can be defined as quotient spaces -- under scalings, and we prefer that definition since it doesn't require -- a notion of unit length (which is only defined in inner-product -- spaces). module Data.Manifold.Types.Stiefel newtype Stiefel1 v Stiefel1 :: DualVector v -> Stiefel1 v [getStiefel1N] :: Stiefel1 v -> DualVector v instance GHC.Show.Show (Math.LinearMap.Category.Class.DualVector v) => GHC.Show.Show (Data.Manifold.Types.Stiefel.Stiefel1 v) -- | Several commonly-used manifolds, represented in some simple way as -- Haskell data types. All these are in the PseudoAffine class. module Data.Manifold.Types type Real0 = ℝ⁰ type Real1 = ℝ type RealPlus = ℝay type Real2 = ℝ² type Real3 = ℝ³ type Sphere0 = S⁰ type Sphere1 = S¹ type Sphere2 = S² type Projective0 = ℝP⁰ type Projective1 = ℝP¹ type Projective2 = ℝP² type Disk1 = D¹ type Disk2 = D² type Cone = CD¹ type OpenCone = Cℝay -- | A fibre bundle combines points in the base space b -- with points in the fibre f. The type FibreBundle b -- f is thus isomorphic to the tuple space (b,f), but it -- can have a different topology, the prime example being -- TangentBundle, where nearby points may have -- differently-oriented tangent spaces. data FibreBundle b f FibreBundle :: !b -> !f -> FibreBundle b f [baseSpace] :: FibreBundle b f -> !b [fibreSpace] :: FibreBundle b f -> !f -- | Points on a manifold, combined with vectors in the respective tangent -- space. type TangentBundle m = FibreBundle m Needle m data ZeroDim s Origin :: ZeroDim s type ℝ = Double type ℝ⁰ = ZeroDim ℝ type ℝ¹ = V1 ℝ type ℝ² = V2 ℝ type ℝ³ = V3 ℝ type ℝ⁴ = V4 ℝ newtype Stiefel1 v Stiefel1 :: DualVector v -> Stiefel1 v [getStiefel1N] :: Stiefel1 v -> DualVector v stiefel1Project :: LinearSpace v => DualVector v -> Stiefel1 v stiefel1Embed :: (HilbertSpace v, RealFloat (Scalar v)) => Stiefel1 v -> v class (PseudoAffine v, InnerSpace v, NaturallyEmbedded (UnitSphere v) (DualVector v)) => HasUnitSphere v where { type family UnitSphere v :: *; } stiefel :: HasUnitSphere v => UnitSphere v -> Stiefel1 v unstiefel :: HasUnitSphere v => Stiefel1 v -> UnitSphere v -- | The zero-dimensional sphere is actually just two points. -- Implementation might therefore change to ℝ⁰ + ℝ⁰: the -- disjoint sum of two single-point spaces. data S⁰ PositiveHalfSphere :: S⁰ NegativeHalfSphere :: S⁰ -- | The unit circle. newtype S¹ S¹Polar :: Double -> S¹ -- | Must be in range [-π, π[. [φParamS¹] :: S¹ -> Double pattern S¹ :: () => () => Double -> S¹ -- | The ordinary unit sphere. data S² S²Polar :: !Double -> !Double -> S² -- | Range [0, π[. [ϑParamS²] :: S² -> !Double -- | Range [-π, π[. [φParamS²] :: S² -> !Double pattern S² :: () => () => Double -> Double -> S² data ℝP⁰ ℝPZero :: ℝP⁰ newtype ℝP¹ HemisphereℝP¹Polar :: Double -> ℝP¹ -- | Range [-π/2,π/2[. [φParamℝP¹] :: ℝP¹ -> Double pattern ℝP¹ :: () => () => Double -> ℝP¹ -- | The two-dimensional real projective space, implemented as a disk with -- opposing points on the rim glued together. Image this disk as the -- northern hemisphere of a unit sphere; ℝP² is the space of all -- straight lines passing through the origin of ℝ³, and each of -- these lines is represented by the point at which it passes through the -- hemisphere. data ℝP² HemisphereℝP²Polar :: !Double -> !Double -> ℝP² -- | Range [0, π/2]. [ϑParamℝP²] :: ℝP² -> !Double -- | Range [-π, π[. [φParamℝP²] :: ℝP² -> !Double pattern ℝP² :: () => () => Double -> Double -> ℝP² -- | The “one-dimensional disk” – really just the line segment between the -- two points -1 and 1 of S⁰, i.e. this is simply a closed -- interval. newtype D¹ D¹ :: Double -> D¹ -- | Range [-1, 1]. [xParamD¹] :: D¹ -> Double -- | The standard, closed unit disk. Homeomorphic to the cone over -- , but not in the the obvious, “flat” way. (In is not -- homeomorphic, despite the almost identical ADT definition, to the -- projective space ℝP²!) data D² D²Polar :: !Double -> !Double -> D² -- | Range [0, 1]. [rParamD²] :: D² -> !Double -- | Range [-π, π[. [φParamD²] :: D² -> !Double pattern D² :: () => () => Double -> Double -> D² -- | Better known as ℝ⁺ (which is not a legal Haskell name), the ray of -- positive numbers (including zero, i.e. closed on one end). type ℝay = Cℝay ℝ⁰ -- | A (closed) cone over a space x is the product of x -- with the closed interval of “heights”, except on its “tip”: -- here, x is smashed to a single point. -- -- This construct becomes (homeomorphic-to-) an actual geometric cone -- (and to ) in the special case x = . data CD¹ x CD¹ :: !Double -> !x -> CD¹ x -- | Range [0, 1] [hParamCD¹] :: CD¹ x -> !Double -- | Irrelevant at h = 0. [pParamCD¹] :: CD¹ x -> !x -- | An open cone is homeomorphic to a closed cone without the “lid”, i.e. -- without the “last copy” of x, at the far end of the height -- interval. Since that means the height does not include its supremum, -- it is actually more natural to express it as the entire real ray, -- hence the name. data Cℝay x Cℝay :: !Double -> !x -> Cℝay x -- | Range [0, ∞[ [hParamCℝay] :: Cℝay x -> !Double -- | Irrelevant at h = 0. [pParamCℝay] :: Cℝay x -> !x data Line x Line :: x -> Stiefel1 (Needle' x) -> Line x [lineHandle] :: Line x -> x [lineDirection] :: Line x -> Stiefel1 (Needle' x) lineAsPlaneIntersection :: forall x. (WithField ℝ Manifold x, FiniteDimensional (Needle' x)) => Line x -> [Cutplane x] -- | Oriented hyperplanes, naïvely generalised to PseudoAffine -- manifolds: Cutplane p w represents the set of all -- points q such that (q.-~.p) ^<.> w ≡ 0. -- -- In vector spaces this is indeed a hyperplane; for general manifolds it -- should behave locally as a plane, globally as an -- (n−1)-dimensional submanifold. data Cutplane x Cutplane :: x -> Stiefel1 (Needle x) -> Cutplane x [sawHandle] :: Cutplane x -> x [cutNormal] :: Cutplane x -> Stiefel1 (Needle x) normalPlane :: x -> Needle' x -> Cutplane x fathomCutDistance :: forall x. (WithField ℝ PseudoAffine x, LinearSpace (Needle x)) => Cutplane x -> Metric' x -> x -> Maybe ℝ sideOfCut :: (WithField ℝ PseudoAffine x, LinearSpace (Needle x)) => Cutplane x -> x -> Maybe S⁰ cutPosBetween :: WithField ℝ Manifold x => Cutplane x -> (x, x) -> Maybe D¹ -- | The tensor product between one space's dual space and another space is -- the space spanned by vector–dual-vector pairs, in bra-ket -- notation written as -- --
--   m = ∑ |w⟩⟨v|
--   
-- -- Any linear mapping can be written as such a (possibly infinite) sum. -- The TensorProduct data structure only stores the linear -- independent parts though; for simple finite-dimensional spaces this -- means e.g. LinearMap ℝ ℝ³ ℝ³ effectively boils down to -- an ordinary matrix type, namely an array of column-vectors -- |w⟩. -- -- (The ⟨v| dual-vectors are then simply assumed to come from -- the canonical basis.) -- -- For bigger spaces, the tensor product may be implemented in a more -- efficient sparse structure; this can be defined in the -- TensorSpace instance. data LinearMap s v w type LocalLinear x y = LinearMap (Scalar (Needle x)) (Needle x) (Needle y) type StiefelScalar s = (RealFloat s, Unbox s) instance (GHC.Classes.Eq (Data.VectorSpace.Scalar v), Data.Vector.Unboxed.Base.Unbox (Data.VectorSpace.Scalar v)) => GHC.Classes.Eq (Data.Manifold.Types.Stiefel1Needle v) instance (GHC.Show.Show x, GHC.Show.Show (Data.Manifold.PseudoAffine.Needle' x)) => GHC.Show.Show (Data.Manifold.Types.Cutplane x) instance Data.VectorSpace.Free.FiniteFreeSpace v => Data.MemoTrie.HasTrie (Data.Manifold.Types.Stiefel1Basis v) instance (Math.LinearMap.Category.Class.LSpace v, Data.VectorSpace.Free.FiniteFreeSpace v, GHC.Classes.Eq (Data.VectorSpace.Scalar v), Data.Vector.Unboxed.Base.Unbox (Data.VectorSpace.Scalar v)) => Math.LinearMap.Category.Class.TensorSpace (Data.Manifold.Types.Stiefel1Needle v) instance (Data.VectorSpace.Free.FiniteFreeSpace v, Data.Vector.Unboxed.Base.Unbox (Data.VectorSpace.Scalar v)) => Data.Basis.HasBasis (Data.Manifold.Types.Stiefel1Needle v) instance (Data.VectorSpace.Free.FiniteFreeSpace v, Data.Vector.Unboxed.Base.Unbox (Data.VectorSpace.Scalar v)) => Data.AdditiveGroup.AdditiveGroup (Data.Manifold.Types.Stiefel1Needle v) instance (Data.VectorSpace.Free.FiniteFreeSpace v, Data.Vector.Unboxed.Base.Unbox (Data.VectorSpace.Scalar v)) => Data.VectorSpace.VectorSpace (Data.Manifold.Types.Stiefel1Needle v) instance (Data.VectorSpace.Free.FiniteFreeSpace v, Data.Vector.Unboxed.Base.Unbox (Data.VectorSpace.Scalar v)) => Data.VectorSpace.Free.FiniteFreeSpace (Data.Manifold.Types.Stiefel1Needle v) instance (Data.VectorSpace.Free.FiniteFreeSpace v, Data.Vector.Unboxed.Base.Unbox (Data.VectorSpace.Scalar v)) => Data.AffineSpace.AffineSpace (Data.Manifold.Types.Stiefel1Needle v) instance (Data.VectorSpace.Free.FiniteFreeSpace v, Data.Vector.Unboxed.Base.Unbox (Data.VectorSpace.Scalar v)) => Math.Manifold.Core.PseudoAffine.Semimanifold (Data.Manifold.Types.Stiefel1Needle v) instance (Data.VectorSpace.Free.FiniteFreeSpace v, Data.Vector.Unboxed.Base.Unbox (Data.VectorSpace.Scalar v)) => Math.Manifold.Core.PseudoAffine.PseudoAffine (Data.Manifold.Types.Stiefel1Needle v) instance (Math.LinearMap.Category.Class.LSpace v, Data.VectorSpace.Free.FiniteFreeSpace v, GHC.Classes.Eq (Data.VectorSpace.Scalar v), Data.Vector.Unboxed.Base.Unbox (Data.VectorSpace.Scalar v)) => Math.LinearMap.Category.Class.LinearSpace (Data.Manifold.Types.Stiefel1Needle v) instance (Math.LinearMap.Category.Class.LinearSpace v, Data.VectorSpace.Free.FiniteFreeSpace v, Data.VectorSpace.Free.FiniteFreeSpace (Math.LinearMap.Category.Class.DualVector v), Data.Manifold.Types.StiefelScalar (Data.VectorSpace.Scalar v)) => Math.Manifold.Core.PseudoAffine.Semimanifold (Data.Manifold.Types.Stiefel.Stiefel1 v) instance (Math.LinearMap.Category.Class.LinearSpace v, Data.VectorSpace.Free.FiniteFreeSpace v, Data.VectorSpace.Free.FiniteFreeSpace (Math.LinearMap.Category.Class.DualVector v), Data.Manifold.Types.StiefelScalar (Data.VectorSpace.Scalar v)) => Math.Manifold.Core.PseudoAffine.PseudoAffine (Data.Manifold.Types.Stiefel.Stiefel1 v) -- | Riemannian manifolds are manifolds equipped with a Metric at -- each point. That means, these manifolds aren't merely topological -- objects anymore, but have a geometry as well. This gives, in -- particular, a notion of distance and shortest paths (geodesics) along -- which you can interpolate. -- -- Keep in mind that the types in this library are generally defined in -- an abstract-mathematical spirit, which may not always match the -- intuition if you think about manifolds as embedded in ℝ³. (For -- instance, the torus inherits its geometry from the decomposition as -- × , not from the “doughnut” embedding; the -- cone over is simply treated as the unit disk, etc..) module Data.Manifold.Riemannian data GeodesicWitness x [GeodesicWitness] :: Geodesic (Interior x) => SemimanifoldWitness x -> GeodesicWitness x class Semimanifold x => Geodesic x geodesicBetween :: Geodesic x => x -> x -> Maybe (D¹ -> x) geodesicWitness :: Geodesic x => GeodesicWitness x geodesicWitness :: (Geodesic x, Geodesic (Interior x)) => GeodesicWitness x middleBetween :: Geodesic x => x -> x -> Maybe x interpolate :: (Geodesic x, IntervalLike i) => x -> x -> Maybe (i -> x) -- | One-dimensional manifolds, whose closure is homeomorpic to the unit -- interval. class WithField ℝ PseudoAffine i => IntervalLike i toClosedInterval :: IntervalLike i => i -> D¹ class Geodesic m => Riemannian m rieMetric :: Riemannian m => RieMetric m pointsBarycenter :: Geodesic m => NonEmpty m -> Maybe m type FlatSpace x = (AffineManifold x, Geodesic x, SimpleSpace x) instance Data.Manifold.Riemannian.Riemannian Math.Manifold.Core.Types.Internal.ℝ instance Data.Manifold.Riemannian.IntervalLike Math.Manifold.Core.Types.Internal.D¹ instance Data.Manifold.Riemannian.IntervalLike Math.Manifold.Core.Types.Internal.ℝ instance Data.Manifold.Riemannian.Geodesic Math.Manifold.Core.Types.Internal.ℝ instance Data.Manifold.Riemannian.Geodesic (Math.Manifold.VectorSpace.ZeroDimensional.ZeroDim s) instance (Data.Manifold.Riemannian.Geodesic a, Data.Manifold.Riemannian.Geodesic b) => Data.Manifold.Riemannian.Geodesic (a, b) instance (Data.Manifold.Riemannian.Geodesic a, Data.Manifold.Riemannian.Geodesic b, Data.Manifold.Riemannian.Geodesic c) => Data.Manifold.Riemannian.Geodesic (a, b, c) instance (Data.Manifold.Riemannian.Geodesic v, Data.VectorSpace.Free.FiniteFreeSpace v, Data.VectorSpace.Free.FiniteFreeSpace (Math.LinearMap.Category.Class.DualVector v), Math.LinearMap.Category.Class.LinearSpace v, Data.VectorSpace.Scalar v Data.Type.Equality.~ Math.Manifold.Core.Types.Internal.ℝ, Data.Manifold.Riemannian.Geodesic (Math.LinearMap.Category.Class.DualVector v), Data.VectorSpace.InnerSpace (Math.LinearMap.Category.Class.DualVector v)) => Data.Manifold.Riemannian.Geodesic (Data.Manifold.Types.Stiefel.Stiefel1 v) instance Data.Manifold.Riemannian.Geodesic Math.Manifold.Core.Types.Internal.S⁰ instance Data.Manifold.Riemannian.Geodesic Math.Manifold.Core.Types.Internal.S¹ instance Data.Manifold.Riemannian.Geodesic (Linear.V0.V0 Math.Manifold.Core.Types.Internal.ℝ) instance Data.Manifold.Riemannian.Geodesic Data.Manifold.Types.Primitive.ℝ¹ instance Data.Manifold.Riemannian.Geodesic Data.Manifold.Types.Primitive.ℝ² instance Data.Manifold.Riemannian.Geodesic Data.Manifold.Types.Primitive.ℝ³ instance Data.Manifold.Riemannian.Geodesic Data.Manifold.Types.Primitive.ℝ⁴ instance (Math.LinearMap.Category.Class.TensorSpace v, Data.VectorSpace.Scalar v Data.Type.Equality.~ Math.Manifold.Core.Types.Internal.ℝ, Math.LinearMap.Category.Class.TensorSpace w, Data.VectorSpace.Scalar w Data.Type.Equality.~ Math.Manifold.Core.Types.Internal.ℝ) => Data.Manifold.Riemannian.Geodesic (Math.LinearMap.Category.Class.Tensor Math.Manifold.Core.Types.Internal.ℝ v w) instance (Math.LinearMap.Category.Class.LinearSpace v, Data.VectorSpace.Scalar v Data.Type.Equality.~ Math.Manifold.Core.Types.Internal.ℝ, Math.LinearMap.Category.Class.TensorSpace w, Data.VectorSpace.Scalar w Data.Type.Equality.~ Math.Manifold.Core.Types.Internal.ℝ) => Data.Manifold.Riemannian.Geodesic (Math.LinearMap.Category.Class.LinearMap Math.Manifold.Core.Types.Internal.ℝ v w) instance (Math.LinearMap.Category.Class.TensorSpace v, Data.VectorSpace.Scalar v Data.Type.Equality.~ Math.Manifold.Core.Types.Internal.ℝ, Math.LinearMap.Category.Class.TensorSpace w, Data.VectorSpace.Scalar w Data.Type.Equality.~ Math.Manifold.Core.Types.Internal.ℝ) => Data.Manifold.Riemannian.Geodesic (Math.LinearMap.Asserted.LinearFunction Math.Manifold.Core.Types.Internal.ℝ v w) module Data.Manifold.Shade -- | A Shade is a very crude description of a region within a -- manifold. It can be interpreted as either an ellipsoid shape, or as -- the Gaussian peak of a normal distribution (use -- http://hackage.haskell.org/package/manifold-random for actually -- sampling from that distribution). -- -- For a precise description of an arbitrarily-shaped connected -- subset of a manifold, there is Region, whose implementation -- is vastly more complex. data Shade x [Shade] :: (Semimanifold x, SimpleSpace (Needle x)) => {_shadeCtr :: !Interior x, _shadeExpanse :: !Metric' x} -> Shade x -- | Span a Shade from a center point and multiple -- deviation-vectors. pattern (:±) :: () => (Semimanifold x, SimpleSpace (Needle x)) => Interior x -> [Needle x] -> Shade x infixl 6 :± -- | A “co-shade” can describe ellipsoid regions as well, but unlike -- Shade it can be unlimited / infinitely wide in some directions. -- It does OTOH need to have nonzero thickness, which Shade needs -- not. data Shade' x Shade' :: !Interior x -> !Metric x -> Shade' x [_shade'Ctr] :: Shade' x -> !Interior x [_shade'Narrowness] :: Shade' x -> !Metric x -- | Similar to , but instead of expanding the shade, each vector -- restricts it. Iff these form a orthogonal basis (in whatever -- sense applicable), then both methods will be equivalent. -- -- Note that |±| is only possible, as such, in an inner-product -- space; in general you need reciprocal vectors (Needle') to -- define a Shade'. (|±|) :: forall x. WithField ℝ EuclidSpace x => x -> [Needle x] -> Shade' x infixl 6 |±| class IsShade shade -- | Access the center of a Shade or a Shade'. shadeCtr :: IsShade shade => Lens' (shade x) (Interior x) shadeExpanse :: Lens' (Shade x) (Metric' x) shadeNarrowness :: Lens' (Shade' x) (Metric x) fullShade :: (Semimanifold x, SimpleSpace (Needle x)) => Interior x -> Metric' x -> Shade x fullShade' :: WithField ℝ SimpleSpace x => Interior x -> Metric x -> Shade' x -- | Attempt to find a Shade that describes the distribution of -- given points. At least in an affine space (and thus locally in any -- manifold), this can be used to estimate the parameters of a normal -- distribution from which some points were sampled. Note that some -- points will be “outside” of the shade, as happens for a normal -- distribution with some statistical likelyhood. (Use -- pointsCovers if you need to prevent that.) -- -- For nonconnected manifolds it will be necessary to yield -- separate shades for each connected component. And for an empty input -- list, there is no shade! Hence the result type is a list. pointsShades :: (WithField ℝ PseudoAffine x, SimpleSpace (Needle x)) => [Interior x] -> [Shade x] pointsShade's :: forall x. (WithField ℝ PseudoAffine x, SimpleSpace (Needle x)) => [Interior x] -> [Shade' x] -- | Like pointsShades, but ensure that all points are actually in -- the shade, i.e. if [Shade x₀ ex] is the result then -- metric (recipMetric ex) (p-x₀) ≤ 1 for all -- p in the list. pointsCovers :: forall x. (WithField ℝ PseudoAffine x, SimpleSpace (Needle x)) => [Interior x] -> [Shade x] pointsCover's :: forall x. (WithField ℝ PseudoAffine x, SimpleSpace (Needle x)) => [Interior x] -> [Shade' x] coverAllAround :: forall x s. (Fractional' s, WithField s PseudoAffine x, SimpleSpace (Needle x)) => Interior x -> [Needle x] -> Shade x -- | Check the statistical likelihood-density of a point being within a -- shade. This is taken as a normal distribution. occlusion :: (IsShade shade, PseudoAffine x, SimpleSpace (Needle x), s ~ Scalar (Needle x), RealFloat' s) => shade x -> x -> s prettyShowsPrecShade' :: LtdErrorShow m => Int -> Shade' m -> ShowS prettyShowShade' :: LtdErrorShow x => Shade' x -> String class Refinable m => LtdErrorShow m factoriseShade :: (IsShade shade, PseudoAffine x, SimpleSpace (Needle x), PseudoAffine y, SimpleSpace (Needle y), Scalar (Needle x) ~ Scalar (Needle y)) => shade (x, y) -> (shade x, shade y) -- | ASCII version of . orthoShades :: (IsShade shade, PseudoAffine x, SimpleSpace (Needle x), PseudoAffine y, SimpleSpace (Needle y), Scalar (Needle x) ~ Scalar (Needle y)) => shade x -> shade y -> shade (x, y) -- | Combine two shades on independent subspaces to a shade with the same -- properties on the subspaces (see factoriseShade) and no -- covariance. (✠) :: (IsShade shade, PseudoAffine x, SimpleSpace (Needle x), PseudoAffine y, SimpleSpace (Needle y), Scalar (Needle x) ~ Scalar (Needle y)) => shade x -> shade y -> shade (x, y) infixl 5 ✠ intersectShade's :: forall y. Refinable y => NonEmpty (Shade' y) -> Maybe (Shade' y) linIsoTransformShade :: (IsShade shade, SimpleSpace x, SimpleSpace y, Scalar x ~ Scalar y, Num' (Scalar x)) => (x +> y) -> shade x -> shade y -- | Include a shade in a higher-dimensional space. Notice that this -- behaves fundamentally different for Shade and Shade'. -- For Shade, it gives a “flat image” of the region, whereas for -- Shade' it gives an “extrusion pillar” pointing in the -- projection's orthogonal complement. embedShade :: (IsShade shade, Semimanifold x, Semimanifold y, Object (Affine s) (Interior x), Object (Affine s) (Interior y), SemiInner (Needle x), SimpleSpace (Needle y)) => Embedding (Affine s) (Interior x) (Interior y) -> shade x -> shade y -- | Squash a shade down into a lower dimensional space. projectShade :: (IsShade shade, Semimanifold x, Semimanifold y, Object (Affine s) (Interior x), Object (Affine s) (Interior y), SimpleSpace (Needle x), SemiInner (Needle y)) => Embedding (Affine s) (Interior x) (Interior y) -> shade y -> shade x -- | Class of manifolds which can use Shade' as a basic set type. -- This is easily possible for vector spaces with the default -- implementations. class (WithField ℝ PseudoAffine y, SimpleSpace (Needle y)) => Refinable y -- | a subShade' b ≡ True means a is fully -- contained in b, i.e. from minusLogOcclusion' a p -- < 1 follows also minusLogOcclusion' b p < 1. subShade' :: Refinable y => Shade' y -> Shade' y -> Bool -- | Intersection between two shades. refineShade' :: Refinable y => Shade' y -> Shade' y -> Maybe (Shade' y) convolveShade' :: Refinable y => Shade' y -> Shade' (Needle y) -> Shade' y coerceShade :: (IsShade shade, Manifold x, Manifold y, LocallyCoercible x y, SimpleSpace (Needle y)) => shade x -> shade y -- | Weakened version of intersectShade's. What this function -- calculates is rather the weighted mean of ellipsoid regions. If -- you interpret the shades as uncertain physical measurements with -- normal distribution, it gives the maximum-likelyhood result for -- multiple measurements of the same quantity. mixShade's :: forall y. (WithField ℝ Manifold y, SimpleSpace (Needle y)) => NonEmpty (Shade' y) -> Maybe (Shade' y) dualShade :: forall x. (PseudoAffine x, SimpleSpace (Needle x)) => Shade x -> Shade' x dualShade' :: forall x. (PseudoAffine x, SimpleSpace (Needle x)) => Shade' x -> Shade x wellDefinedShade' :: LinearSpace (Needle x) => Shade' x -> Maybe (Shade' x) linearProjectShade :: forall s x y. (Num' s, LinearSpace x, SimpleSpace y, Scalar x ~ s, Scalar y ~ s) => (x +> y) -> Shade x -> Shade y -- | Attempt to reduce the number of shades to fewer (ideally, a single -- one). In the simplest cases these should guaranteed cover the same -- area; for non-flat manifolds it only works in a heuristic sense. shadesMerge :: forall x. (WithField ℝ Manifold x, SimpleSpace (Needle x)) => ℝ -> [Shade x] -> [Shade x] pointsShades' :: forall x y. (WithField ℝ PseudoAffine x, SimpleSpace (Needle x)) => Metric' x -> [(x, y)] -> [([(x, y)], Shade x)] pseudoECM :: forall x y p. (WithField ℝ PseudoAffine x, SimpleSpace (Needle x), Functor p) => p x -> NonEmpty (x, y) -> (x, ([(x, y)], [(x, y)])) -- | If p is in a (red) and δ is in b -- (green), then p.+~^δ is in convolveShade' a b -- (blue). -- -- Example: -- https://nbviewer.jupyter.org/github/leftaroundabout/manifolds/blob/master/test/ShadeCombinations.ipynb#shadeConvolutions -- convolveMetric :: (Refinable y, Functor p) => p y -> Metric y -> Metric y -> Metric y -- | Essentially the same as (x,y), but not considered as a -- product topology. The Semimanifold etc. instances just copy the -- topology of x, ignoring y. data x `WithAny` y WithAny :: y -> !x -> WithAny x y [_untopological] :: WithAny x y -> y [_topological] :: WithAny x y -> !x shadeWithAny :: y -> Shade x -> Shade (x `WithAny` y) shadeWithoutAnything :: Semimanifold x => Shade (x `WithAny` y) -> Shade x -- | Warning: This function never worked properly. Use -- rangeWithinVertices. rangeOnGeodesic :: forall i m. (WithField ℝ PseudoAffine m, Geodesic m, SimpleSpace (Needle m), WithField ℝ IntervalLike i, SimpleSpace (Needle i)) => m -> m -> Maybe (Shade i -> Shade m) rangeWithinVertices :: forall s i m t. (RealFrac' s, WithField s PseudoAffine i, WithField s PseudoAffine m, Geodesic i, Geodesic m, SimpleSpace (Needle i), SimpleSpace (Needle m), AffineManifold (Interior i), AffineManifold (Interior m), Object (Affine s) (Interior i), Object (Affine s) (Interior m), Traversable t) => (Interior i, Interior m) -> t (i, m) -> Maybe (Shade i -> Shade m) instance GHC.Generics.Generic (Data.Manifold.Shade.WithAny x y) instance (GHC.Show.Show y, GHC.Show.Show x) => GHC.Show.Show (Data.Manifold.Shade.WithAny x y) instance GHC.Base.Functor (Data.Manifold.Shade.WithAny x) instance (GHC.Show.Show (Math.Manifold.Core.PseudoAffine.Interior x), GHC.Show.Show (Data.Manifold.PseudoAffine.Metric' x), Data.Manifold.PseudoAffine.WithField Math.Manifold.Core.Types.Internal.ℝ Math.Manifold.Core.PseudoAffine.PseudoAffine x) => GHC.Show.Show (Data.Manifold.Shade.Shade x) instance Data.Manifold.Shade.LtdErrorShow x => Text.Show.Pragmatic.Show (Data.Manifold.Shade.Shade' x) instance Data.Manifold.Shade.LtdErrorShow x => Text.Show.Pragmatic.Show (Data.Manifold.Shade.Shade x) instance Data.Manifold.Shade.LtdErrorShow Math.Manifold.Core.Types.Internal.ℝ⁰ instance Data.Manifold.Shade.LtdErrorShow Math.Manifold.Core.Types.Internal.ℝ instance Data.Manifold.Shade.LtdErrorShow Data.Manifold.Types.Primitive.ℝ² instance Data.Manifold.Shade.LtdErrorShow Data.Manifold.Types.Primitive.ℝ³ instance Data.Manifold.Shade.LtdErrorShow Data.Manifold.Types.Primitive.ℝ⁴ instance (Data.Manifold.Shade.LtdErrorShow x, Data.Manifold.Shade.LtdErrorShow y, Data.VectorSpace.Scalar (Math.LinearMap.Category.Class.DualVector (Data.Manifold.PseudoAffine.Needle' x)) Data.Type.Equality.~ Data.VectorSpace.Scalar (Math.LinearMap.Category.Class.DualVector (Data.Manifold.PseudoAffine.Needle' y))) => Data.Manifold.Shade.LtdErrorShow (x, y) instance (Math.VectorSpace.Docile.HilbertSpace v, Math.VectorSpace.Docile.SemiInner v, Math.VectorSpace.Docile.FiniteDimensional v, Data.Manifold.Shade.LtdErrorShow v, Data.VectorSpace.Scalar v Data.Type.Equality.~ Math.Manifold.Core.Types.Internal.ℝ) => Data.Manifold.Shade.LtdErrorShow (Math.LinearMap.Category.Class.LinearMap Math.Manifold.Core.Types.Internal.ℝ v Math.Manifold.Core.Types.Internal.ℝ) instance (Math.VectorSpace.Docile.HilbertSpace v, Math.VectorSpace.Docile.SemiInner v, Math.VectorSpace.Docile.FiniteDimensional v, Data.Manifold.Shade.LtdErrorShow v, Data.VectorSpace.Scalar v Data.Type.Equality.~ Math.Manifold.Core.Types.Internal.ℝ) => Data.Manifold.Shade.LtdErrorShow (Math.LinearMap.Category.Class.LinearMap Math.Manifold.Core.Types.Internal.ℝ v (Math.Manifold.Core.Types.Internal.ℝ, Math.Manifold.Core.Types.Internal.ℝ)) instance Data.Manifold.Shade.LtdErrorShow x => GHC.Show.Show (Data.Manifold.Shade.Shade' x) instance (Control.DeepSeq.NFData x, Control.DeepSeq.NFData y) => Control.DeepSeq.NFData (Data.Manifold.Shade.WithAny x y) instance Math.Manifold.Core.PseudoAffine.Semimanifold x => Math.Manifold.Core.PseudoAffine.Semimanifold (Data.Manifold.Shade.WithAny x y) instance Math.Manifold.Core.PseudoAffine.PseudoAffine x => Math.Manifold.Core.PseudoAffine.PseudoAffine (Data.Manifold.Shade.WithAny x y) instance Data.AffineSpace.AffineSpace x => Data.AffineSpace.AffineSpace (Data.Manifold.Shade.WithAny x y) instance (Data.VectorSpace.VectorSpace x, GHC.Base.Monoid y) => Data.VectorSpace.VectorSpace (Data.Manifold.Shade.WithAny x y) instance (Data.AdditiveGroup.AdditiveGroup x, GHC.Base.Monoid y) => Data.AdditiveGroup.AdditiveGroup (Data.Manifold.Shade.WithAny x y) instance Data.AdditiveGroup.AdditiveGroup x => GHC.Base.Applicative (Data.Manifold.Shade.WithAny x) instance Data.AdditiveGroup.AdditiveGroup x => GHC.Base.Monad (Data.Manifold.Shade.WithAny x) instance Data.Manifold.Shade.Refinable Math.Manifold.Core.Types.Internal.ℝ instance (Data.Manifold.Shade.Refinable a, Data.Manifold.Shade.Refinable b, Data.VectorSpace.Scalar (Math.LinearMap.Category.Class.DualVector (Math.LinearMap.Category.Class.DualVector (Math.Manifold.Core.PseudoAffine.Needle b))) Data.Type.Equality.~ Data.VectorSpace.Scalar (Math.LinearMap.Category.Class.DualVector (Math.LinearMap.Category.Class.DualVector (Math.Manifold.Core.PseudoAffine.Needle a)))) => Data.Manifold.Shade.Refinable (a, b) instance Data.Manifold.Shade.Refinable Math.Manifold.Core.Types.Internal.ℝ⁰ instance Data.Manifold.Shade.Refinable Data.Manifold.Types.Primitive.ℝ¹ instance Data.Manifold.Shade.Refinable Data.Manifold.Types.Primitive.ℝ² instance Data.Manifold.Shade.Refinable Data.Manifold.Types.Primitive.ℝ³ instance Data.Manifold.Shade.Refinable Data.Manifold.Types.Primitive.ℝ⁴ instance (Math.VectorSpace.Docile.SimpleSpace a, Math.VectorSpace.Docile.SimpleSpace b, Data.Manifold.Shade.Refinable a, Data.Manifold.Shade.Refinable b, Data.VectorSpace.Scalar a Data.Type.Equality.~ Math.Manifold.Core.Types.Internal.ℝ, Data.VectorSpace.Scalar b Data.Type.Equality.~ Math.Manifold.Core.Types.Internal.ℝ, Data.VectorSpace.Scalar (Math.LinearMap.Category.Class.DualVector a) Data.Type.Equality.~ Math.Manifold.Core.Types.Internal.ℝ, Data.VectorSpace.Scalar (Math.LinearMap.Category.Class.DualVector b) Data.Type.Equality.~ Math.Manifold.Core.Types.Internal.ℝ, Data.VectorSpace.Scalar (Math.LinearMap.Category.Class.DualVector (Math.LinearMap.Category.Class.DualVector a)) Data.Type.Equality.~ Math.Manifold.Core.Types.Internal.ℝ, Data.VectorSpace.Scalar (Math.LinearMap.Category.Class.DualVector (Math.LinearMap.Category.Class.DualVector b)) Data.Type.Equality.~ Math.Manifold.Core.Types.Internal.ℝ) => Data.Manifold.Shade.Refinable (Math.LinearMap.Category.Class.LinearMap Math.Manifold.Core.Types.Internal.ℝ a b) instance Data.Manifold.Shade.IsShade Data.Manifold.Shade.Shade instance Data.Manifold.Shade.IsShade Data.Manifold.Shade.Shade' instance Data.Manifold.PseudoAffine.ImpliesMetric Data.Manifold.Shade.Shade' instance Data.Manifold.Atlas.AffineManifold x => Math.Manifold.Core.PseudoAffine.Semimanifold (Data.Manifold.Shade.Shade' x) instance (Data.Manifold.PseudoAffine.WithField Math.Manifold.Core.Types.Internal.ℝ Data.Manifold.Atlas.AffineManifold x, Data.Manifold.Riemannian.Geodesic x, Math.VectorSpace.Docile.SimpleSpace (Math.Manifold.Core.PseudoAffine.Needle x)) => Data.Manifold.Riemannian.Geodesic (Data.Manifold.Shade.Shade' x) instance Data.Manifold.PseudoAffine.ImpliesMetric Data.Manifold.Shade.Shade instance Math.Manifold.Core.PseudoAffine.PseudoAffine x => Math.Manifold.Core.PseudoAffine.Semimanifold (Data.Manifold.Shade.Shade x) instance (Data.Manifold.PseudoAffine.WithField Math.Manifold.Core.Types.Internal.ℝ Math.Manifold.Core.PseudoAffine.PseudoAffine x, Data.Manifold.Riemannian.Geodesic (Math.Manifold.Core.PseudoAffine.Interior x), Math.VectorSpace.Docile.SimpleSpace (Math.Manifold.Core.PseudoAffine.Needle x)) => Data.Manifold.Riemannian.Geodesic (Data.Manifold.Shade.Shade x) module Data.Manifold.TreeCover -- | A Shade is a very crude description of a region within a -- manifold. It can be interpreted as either an ellipsoid shape, or as -- the Gaussian peak of a normal distribution (use -- http://hackage.haskell.org/package/manifold-random for actually -- sampling from that distribution). -- -- For a precise description of an arbitrarily-shaped connected -- subset of a manifold, there is Region, whose implementation -- is vastly more complex. data Shade x [Shade] :: (Semimanifold x, SimpleSpace (Needle x)) => {_shadeCtr :: !Interior x, _shadeExpanse :: !Metric' x} -> Shade x -- | Span a Shade from a center point and multiple -- deviation-vectors. pattern (:±) :: () => (Semimanifold x, SimpleSpace (Needle x)) => Interior x -> [Needle x] -> Shade x infixl 6 :± -- | A “co-shade” can describe ellipsoid regions as well, but unlike -- Shade it can be unlimited / infinitely wide in some directions. -- It does OTOH need to have nonzero thickness, which Shade needs -- not. data Shade' x Shade' :: !Interior x -> !Metric x -> Shade' x [_shade'Ctr] :: Shade' x -> !Interior x [_shade'Narrowness] :: Shade' x -> !Metric x -- | Similar to , but instead of expanding the shade, each vector -- restricts it. Iff these form a orthogonal basis (in whatever -- sense applicable), then both methods will be equivalent. -- -- Note that |±| is only possible, as such, in an inner-product -- space; in general you need reciprocal vectors (Needle') to -- define a Shade'. (|±|) :: forall x. WithField ℝ EuclidSpace x => x -> [Needle x] -> Shade' x infixl 6 |±| class IsShade shade -- | Access the center of a Shade or a Shade'. shadeCtr :: IsShade shade => Lens' (shade x) (Interior x) shadeExpanse :: Lens' (Shade x) (Metric' x) shadeNarrowness :: Lens' (Shade' x) (Metric x) fullShade :: (Semimanifold x, SimpleSpace (Needle x)) => Interior x -> Metric' x -> Shade x fullShade' :: WithField ℝ SimpleSpace x => Interior x -> Metric x -> Shade' x -- | Attempt to find a Shade that describes the distribution of -- given points. At least in an affine space (and thus locally in any -- manifold), this can be used to estimate the parameters of a normal -- distribution from which some points were sampled. Note that some -- points will be “outside” of the shade, as happens for a normal -- distribution with some statistical likelyhood. (Use -- pointsCovers if you need to prevent that.) -- -- For nonconnected manifolds it will be necessary to yield -- separate shades for each connected component. And for an empty input -- list, there is no shade! Hence the result type is a list. pointsShades :: (WithField ℝ PseudoAffine x, SimpleSpace (Needle x)) => [Interior x] -> [Shade x] pointsShade's :: forall x. (WithField ℝ PseudoAffine x, SimpleSpace (Needle x)) => [Interior x] -> [Shade' x] -- | Like pointsShades, but ensure that all points are actually in -- the shade, i.e. if [Shade x₀ ex] is the result then -- metric (recipMetric ex) (p-x₀) ≤ 1 for all -- p in the list. pointsCovers :: forall x. (WithField ℝ PseudoAffine x, SimpleSpace (Needle x)) => [Interior x] -> [Shade x] pointsCover's :: forall x. (WithField ℝ PseudoAffine x, SimpleSpace (Needle x)) => [Interior x] -> [Shade' x] coverAllAround :: forall x s. (Fractional' s, WithField s PseudoAffine x, SimpleSpace (Needle x)) => Interior x -> [Needle x] -> Shade x -- | Check the statistical likelihood-density of a point being within a -- shade. This is taken as a normal distribution. occlusion :: (IsShade shade, PseudoAffine x, SimpleSpace (Needle x), s ~ Scalar (Needle x), RealFloat' s) => shade x -> x -> s prettyShowsPrecShade' :: LtdErrorShow m => Int -> Shade' m -> ShowS prettyShowShade' :: LtdErrorShow x => Shade' x -> String factoriseShade :: (IsShade shade, PseudoAffine x, SimpleSpace (Needle x), PseudoAffine y, SimpleSpace (Needle y), Scalar (Needle x) ~ Scalar (Needle y)) => shade (x, y) -> (shade x, shade y) intersectShade's :: forall y. Refinable y => NonEmpty (Shade' y) -> Maybe (Shade' y) linIsoTransformShade :: (IsShade shade, SimpleSpace x, SimpleSpace y, Scalar x ~ Scalar y, Num' (Scalar x)) => (x +> y) -> shade x -> shade y -- | Include a shade in a higher-dimensional space. Notice that this -- behaves fundamentally different for Shade and Shade'. -- For Shade, it gives a “flat image” of the region, whereas for -- Shade' it gives an “extrusion pillar” pointing in the -- projection's orthogonal complement. embedShade :: (IsShade shade, Semimanifold x, Semimanifold y, Object (Affine s) (Interior x), Object (Affine s) (Interior y), SemiInner (Needle x), SimpleSpace (Needle y)) => Embedding (Affine s) (Interior x) (Interior y) -> shade x -> shade y -- | Squash a shade down into a lower dimensional space. projectShade :: (IsShade shade, Semimanifold x, Semimanifold y, Object (Affine s) (Interior x), Object (Affine s) (Interior y), SimpleSpace (Needle x), SemiInner (Needle y)) => Embedding (Affine s) (Interior x) (Interior y) -> shade y -> shade x -- | Class of manifolds which can use Shade' as a basic set type. -- This is easily possible for vector spaces with the default -- implementations. class (WithField ℝ PseudoAffine y, SimpleSpace (Needle y)) => Refinable y -- | a subShade' b ≡ True means a is fully -- contained in b, i.e. from minusLogOcclusion' a p -- < 1 follows also minusLogOcclusion' b p < 1. subShade' :: Refinable y => Shade' y -> Shade' y -> Bool -- | Intersection between two shades. refineShade' :: Refinable y => Shade' y -> Shade' y -> Maybe (Shade' y) convolveShade' :: Refinable y => Shade' y -> Shade' (Needle y) -> Shade' y coerceShade :: (IsShade shade, Manifold x, Manifold y, LocallyCoercible x y, SimpleSpace (Needle y)) => shade x -> shade y -- | Weakened version of intersectShade's. What this function -- calculates is rather the weighted mean of ellipsoid regions. If -- you interpret the shades as uncertain physical measurements with -- normal distribution, it gives the maximum-likelyhood result for -- multiple measurements of the same quantity. mixShade's :: forall y. (WithField ℝ Manifold y, SimpleSpace (Needle y)) => NonEmpty (Shade' y) -> Maybe (Shade' y) type ShadeTree x = x `Shaded` () -- | Build a quite nicely balanced tree from a cloud of points, on any real -- manifold. -- -- Example: -- https://nbviewer.jupyter.org/github/leftaroundabout/manifolds/blob/master/test/Trees-and-Webs.ipynb#pseudorandomCloudTree -- fromLeafPoints :: forall x. (WithField ℝ Manifold x, SimpleSpace (Needle x)) => [x] -> ShadeTree x fromLeafPoints_ :: forall x y. (WithField ℝ Manifold x, SimpleSpace (Needle x)) => [(x, y)] -> x `Shaded` y onlyLeaves :: WithField ℝ PseudoAffine x => (x `Shaded` y) -> [(x, y)] -- | Left (and, typically, also right) inverse of fromLeafNodes. onlyLeaves_ :: WithField ℝ PseudoAffine x => ShadeTree x -> [x] -- | The leaves of a shade tree are numbered. For a given index, this -- function attempts to find the leaf with that ID, within its immediate -- environment. indexShadeTree :: forall x y. (x `Shaded` y) -> Int -> Either Int ([x `Shaded` y], (x, y)) treeLeaf :: forall x y f. Functor f => Int -> (y -> f y) -> (x `Shaded` y) -> Either Int (f (x `Shaded` y)) -- | “Inverse indexing” of a tree. This is roughly a nearest-neighbour -- search, but not guaranteed to give the correct result unless evaluated -- at the precise position of a tree leaf. positionIndex :: forall x y. (WithField ℝ Manifold x, SimpleSpace (Needle x)) => Maybe (Metric x) -> (x `Shaded` y) -> x -> Maybe (Int, ([x `Shaded` y], (x, y))) entireTree :: forall x y. (WithField ℝ PseudoAffine x, SimpleSpace (Needle x)) => (x `Shaded` y) -> LeafyTree x y -- | Imitate the specialised ShadeTree structure with a simpler, -- generic tree. onlyNodes :: forall x. (WithField ℝ PseudoAffine x, SimpleSpace (Needle x)) => ShadeTree x -> Trees x trunkBranches :: (x `Shaded` y) -> NonEmpty (LeafIndex, x `Shaded` y) nLeaves :: (x `Shaded` y) -> Int treeDepth :: (x `Shaded` y) -> Int -- |
--   SimpleTree x ≅ Maybe (x, Trees x)
--   
type SimpleTree = GenericTree Maybe [] -- |
--   Trees x ≅ [(x, Trees x)]
--   
type Trees = GenericTree [] [] -- |
--   NonEmptyTree x ≅ (x, Trees x)
--   
type NonEmptyTree = GenericTree NonEmpty [] newtype GenericTree c b x GenericTree :: c (x, GenericTree b b x) -> GenericTree c b x [treeBranches] :: GenericTree c b x -> c (x, GenericTree b b x) -- | U+6733 CJK UNIFIED IDEOGRAPH tree. The main purpose of this -- is to give GenericTree a more concise Show instance. 朳 :: c (x, GenericTree b b x) -> GenericTree c b x class HasFlatView f where { type family FlatView f x; } flatView :: HasFlatView f => f x -> FlatView f x superFlatView :: HasFlatView f => f x -> [[x]] -- | Attempt to reduce the number of shades to fewer (ideally, a single -- one). In the simplest cases these should guaranteed cover the same -- area; for non-flat manifolds it only works in a heuristic sense. shadesMerge :: forall x. (WithField ℝ Manifold x, SimpleSpace (Needle x)) => ℝ -> [Shade x] -> [Shade x] allTwigs :: forall x y. WithField ℝ PseudoAffine x => (x `Shaded` y) -> [Twig x y] -- | Example: -- https://nbviewer.jupyter.org/github/leftaroundabout/manifolds/blob/master/test/Trees-and-Webs.ipynb#pseudorandomCloudTree -- twigsWithEnvirons :: forall x y. (WithField ℝ Manifold x, SimpleSpace (Needle x)) => (x `Shaded` y) -> [(Twig x y, TwigEnviron x y)] type Twig x y = (Int, x `Shaded` y) type TwigEnviron x y = [Twig x y] seekPotentialNeighbours :: forall x y. (WithField ℝ PseudoAffine x, SimpleSpace (Needle x)) => (x `Shaded` y) -> x `Shaded` (y, [Int]) completeTopShading :: forall x y. (WithField ℝ PseudoAffine x, WithField ℝ PseudoAffine y, SimpleSpace (Needle x), SimpleSpace (Needle y)) => (x `Shaded` y) -> [Shade' (x, y)] flexTwigsShading :: forall x y f. (WithField ℝ Manifold x, WithField ℝ Manifold y, SimpleSpace (Needle x), SimpleSpace (Needle y), Applicative f) => (Shade' (x, y) -> f (x, (Shade' y, LocalLinear x y))) -> (x `Shaded` y) -> f (x `Shaded` y) traverseTrunkBranchChoices :: Applicative f => ((Int, x `Shaded` y) -> (x `Shaded` y) -> f (x `Shaded` z)) -> (x `Shaded` y) -> f (x `Shaded` z) data Shaded x y PlainLeaves :: [(x, y)] -> Shaded x y DisjointBranches :: !LeafCount -> NonEmpty (x `Shaded` y) -> Shaded x y OverlappingBranches :: !LeafCount -> !Shade x -> NonEmpty (DBranch x y) -> Shaded x y fmapShaded :: (Semimanifold x, SimpleSpace (Needle x)) => (y -> υ) -> (x `Shaded` y) -> x `Shaded` υ constShaded :: y -> (x `Shaded` y₀) -> x `Shaded` y zipTreeWithList :: (x `Shaded` w) -> NonEmpty y -> x `Shaded` (w, y) stiAsIntervalMapping :: (x ~ ℝ, y ~ ℝ) => (x `Shaded` y) -> [(x, ((y, Diff y), LinearMap ℝ x y))] spanShading :: forall x y. (WithField ℝ Manifold x, WithField ℝ Manifold y, SimpleSpace (Needle x), SimpleSpace (Needle y)) => (Shade x -> Shade y) -> ShadeTree x -> x `Shaded` y type DBranch x y = DBranch' x (x `Shaded` y) data DBranch' x c DBranch :: !Needle' x -> !Hourglass c -> DBranch' x c [boughDirection] :: DBranch' x c -> !Needle' x [boughContents] :: DBranch' x c -> !Hourglass c -- | Hourglass as the geometric shape (two opposing ~conical volumes, -- sharing only a single point in the middle); has nothing to do with -- time. data Hourglass s Hourglass :: !s -> Hourglass s [upperBulb, lowerBulb] :: Hourglass s -> !s unsafeFmapTree :: (NonEmpty (x, y) -> NonEmpty (ξ, υ)) -> (Needle' x -> Needle' ξ) -> (Shade x -> Shade ξ) -> (x `Shaded` y) -> ξ `Shaded` υ -- | The AffineSpace class plus manifold constraints. type AffineManifold m = (Atlas m, Manifold m, AffineSpace m, Needle m ~ Diff m, HasTrie (ChartIndex m)) euclideanMetric :: EuclidSpace x => proxy x -> Metric x instance GHC.Generics.Generic (Data.Manifold.TreeCover.Sawboneses x) instance (Data.Traversable.Traversable c, Data.Traversable.Traversable b) => Data.Traversable.Traversable (Data.Manifold.TreeCover.GenericTree c b) instance (Data.Foldable.Foldable c, Data.Foldable.Foldable b) => Data.Foldable.Foldable (Data.Manifold.TreeCover.GenericTree c b) instance (GHC.Base.Functor c, GHC.Base.Functor b) => GHC.Base.Functor (Data.Manifold.TreeCover.GenericTree c b) instance GHC.Generics.Generic (Data.Manifold.TreeCover.GenericTree c b x) instance Data.Traversable.Traversable (Data.Manifold.TreeCover.DBranches' x) instance Data.Foldable.Foldable (Data.Manifold.TreeCover.DBranches' x) instance GHC.Base.Functor (Data.Manifold.TreeCover.DBranches' x) instance GHC.Generics.Generic (Data.Manifold.TreeCover.DBranches' x c) instance Data.Traversable.Traversable (Data.Manifold.TreeCover.Shaded x) instance Data.Foldable.Foldable (Data.Manifold.TreeCover.Shaded x) instance GHC.Base.Functor (Data.Manifold.TreeCover.Shaded x) instance GHC.Generics.Generic (Data.Manifold.TreeCover.Shaded x y) instance Data.Traversable.Traversable (Data.Manifold.TreeCover.DBranch' x) instance Data.Foldable.Foldable (Data.Manifold.TreeCover.DBranch' x) instance GHC.Base.Functor (Data.Manifold.TreeCover.DBranch' x) instance GHC.Generics.Generic (Data.Manifold.TreeCover.DBranch' x c) instance GHC.Show.Show s => GHC.Show.Show (Data.Manifold.TreeCover.Hourglass s) instance Data.Traversable.Traversable Data.Manifold.TreeCover.Hourglass instance Data.Foldable.Foldable Data.Manifold.TreeCover.Hourglass instance GHC.Base.Functor Data.Manifold.TreeCover.Hourglass instance GHC.Generics.Generic (Data.Manifold.TreeCover.Hourglass s) instance (Data.Manifold.PseudoAffine.WithField Math.Manifold.Core.Types.Internal.ℝ Math.Manifold.Core.PseudoAffine.PseudoAffine x, GHC.Show.Show x, GHC.Show.Show (Math.Manifold.Core.PseudoAffine.Interior x), GHC.Show.Show (Data.Manifold.PseudoAffine.Needle' x), GHC.Show.Show (Data.Manifold.PseudoAffine.Metric' x)) => GHC.Show.Show (Data.Manifold.TreeCover.Shaded x ()) instance (Data.Manifold.PseudoAffine.WithField Math.Manifold.Core.Types.Internal.ℝ Math.Manifold.Core.PseudoAffine.PseudoAffine x, GHC.Show.Show (Data.Manifold.PseudoAffine.Needle' x), GHC.Show.Show c) => GHC.Show.Show (Data.Manifold.TreeCover.DBranch' x c) instance (Data.Manifold.PseudoAffine.WithField Math.Manifold.Core.Types.Internal.ℝ Math.Manifold.Core.PseudoAffine.PseudoAffine x, GHC.Show.Show (Data.Manifold.PseudoAffine.Needle' x), GHC.Show.Show c) => GHC.Show.Show (Data.Manifold.TreeCover.DBranches' x c) instance GHC.Classes.Eq (c (x, Data.Manifold.TreeCover.GenericTree b b x)) => GHC.Classes.Eq (Data.Manifold.TreeCover.GenericTree c b x) instance Data.Manifold.TreeCover.HasFlatView Data.Manifold.TreeCover.Sawbones instance Data.Manifold.TreeCover.HasFlatView Data.Manifold.TreeCover.Sawboneses instance GHC.Base.Semigroup (Data.Manifold.TreeCover.Sawboneses x) instance GHC.Base.Semigroup (Data.Manifold.TreeCover.DustyEdges x) instance GHC.Base.Semigroup (Data.Manifold.TreeCover.Sawbones x) instance GHC.Base.Monoid (Data.Manifold.TreeCover.Sawbones x) instance (Control.DeepSeq.NFData x, Data.Foldable.Foldable c, Data.Foldable.Foldable b) => Control.DeepSeq.NFData (Data.Manifold.TreeCover.GenericTree c b x) instance GHC.Base.MonadPlus c => GHC.Base.Semigroup (Data.Manifold.TreeCover.GenericTree c b x) instance GHC.Base.MonadPlus c => GHC.Base.Monoid (Data.Manifold.TreeCover.GenericTree c b x) instance GHC.Show.Show (c (x, Data.Manifold.TreeCover.GenericTree b b x)) => GHC.Show.Show (Data.Manifold.TreeCover.GenericTree c b x) instance GHC.Base.Semigroup c => GHC.Base.Semigroup (Data.Manifold.TreeCover.DBranches' x c) instance (Data.Manifold.PseudoAffine.WithField Math.Manifold.Core.Types.Internal.ℝ Data.Manifold.PseudoAffine.Manifold x, Math.VectorSpace.Docile.SimpleSpace (Math.Manifold.Core.PseudoAffine.Needle x)) => GHC.Base.Semigroup (Data.Manifold.TreeCover.ShadeTree x) instance (Data.Manifold.PseudoAffine.WithField Math.Manifold.Core.Types.Internal.ℝ Data.Manifold.PseudoAffine.Manifold x, Math.VectorSpace.Docile.SimpleSpace (Math.Manifold.Core.PseudoAffine.Needle x)) => GHC.Base.Monoid (Data.Manifold.TreeCover.ShadeTree x) instance (Control.DeepSeq.NFData x, Control.DeepSeq.NFData (Data.Manifold.PseudoAffine.Needle' x), Control.DeepSeq.NFData y) => Control.DeepSeq.NFData (Data.Manifold.TreeCover.Shaded x y) instance (Control.DeepSeq.NFData x, Control.DeepSeq.NFData (Data.Manifold.PseudoAffine.Needle' x), Control.DeepSeq.NFData y) => Control.DeepSeq.NFData (Data.Manifold.TreeCover.DBranch x y) instance Control.DeepSeq.NFData s => Control.DeepSeq.NFData (Data.Manifold.TreeCover.Hourglass s) instance GHC.Base.Semigroup s => GHC.Base.Semigroup (Data.Manifold.TreeCover.Hourglass s) instance (GHC.Base.Monoid s, GHC.Base.Semigroup s) => GHC.Base.Monoid (Data.Manifold.TreeCover.Hourglass s) instance GHC.Base.Applicative Data.Manifold.TreeCover.Hourglass instance Data.Foldable.Constrained.Foldable Data.Manifold.TreeCover.Hourglass (->) (->) module Data.Manifold.Griddable data GridAxis m g GridAxInterval :: Shade m -> GridAxis m g GridAxCons :: Shade m -> g -> GridAxis m g -> GridAxis m g GridAxisClosed :: g -> GridAxis m g -> GridAxis m g class (WithField ℝ Manifold m) => Griddable m g where { data family GriddingParameters m g :: *; } mkGridding :: Griddable m g => GriddingParameters m g -> Int -> Shade m -> [GridAxis m g] instance GHC.Base.Functor (Data.Manifold.Griddable.GridAxis m) instance Data.Manifold.Griddable.Griddable Math.Manifold.Core.Types.Internal.ℝ GHC.Base.String instance (Math.VectorSpace.Docile.SimpleSpace (Math.Manifold.Core.PseudoAffine.Needle m), Math.VectorSpace.Docile.SimpleSpace (Math.Manifold.Core.PseudoAffine.Needle n), Math.VectorSpace.Docile.SimpleSpace (Math.Manifold.Core.PseudoAffine.Needle a), Data.Manifold.Griddable.Griddable m a, Data.Manifold.Griddable.Griddable n a, m Data.Type.Equality.~ Math.Manifold.Core.PseudoAffine.Interior m, n Data.Type.Equality.~ Math.Manifold.Core.PseudoAffine.Interior n) => Data.Manifold.Griddable.Griddable (m, n) a module Data.Manifold.Function.LocalModel class LocalModel ㄇ fitLocally :: (LocalModel ㄇ, ModellableRelation x y) => [(Needle x, Shade' y)] -> Maybe (ㄇ x y) tweakLocalOffset :: (LocalModel ㄇ, ModellableRelation x y) => Lens' (ㄇ x y) (Shade y) evalLocalModel :: (LocalModel ㄇ, ModellableRelation x y) => ㄇ x y -> Needle x -> Shade' y type ModellableRelation x y = (WithField ℝ Manifold x, Refinable y, Geodesic y, FlatSpace (Needle x), FlatSpace (Needle y)) data AffineModel x y AffineModel :: Shade y -> Shade (Needle x +> Needle y) -> AffineModel x y [_affineModelOffset] :: AffineModel x y -> Shade y [_affineModelLCoeff] :: AffineModel x y -> Shade (Needle x +> Needle y) data QuadraticModel x y QuadraticModel :: Shade y -> Shade (Needle x +> Needle y) -> Shade (Needle x ⊗〃+> Needle y) -> QuadraticModel x y [_quadraticModelOffset] :: QuadraticModel x y -> Shade y [_quadraticModelLCoeff] :: QuadraticModel x y -> Shade (Needle x +> Needle y) [_quadraticModelQCoeff] :: QuadraticModel x y -> Shade (Needle x ⊗〃+> Needle y) -- | Deprecated: Use fitLocally estimateLocalJacobian :: forall x y. (WithField ℝ Manifold x, Refinable y, SimpleSpace (Needle x), SimpleSpace (Needle y)) => Metric x -> [(Local x, Shade' y)] -> Maybe (Shade' (LocalLinear x y)) -- | Deprecated: Use fitLocally estimateLocalHessian :: forall x y. (WithField ℝ Manifold x, Refinable y, Geodesic y, FlatSpace (Needle x), FlatSpace (Needle y)) => NonEmpty (Local x, Shade' y) -> QuadraticModel x y propagationCenteredModel :: forall x y ㄇ. (ModellableRelation x y, LocalModel ㄇ) => LocalDataPropPlan x (Shade' y) -> ㄇ x y propagationCenteredQuadraticModel :: forall x y. ModellableRelation x y => LocalDataPropPlan x (Shade' y) -> QuadraticModel x y quadraticModel_derivatives :: forall x y. (PseudoAffine x, PseudoAffine y, SimpleSpace (Needle x), SimpleSpace (Needle y), Scalar (Needle y) ~ Scalar (Needle x)) => QuadraticModel x y -> (Shade' y, (Shade' (LocalLinear x y), Shade' (LocalBilinear x y))) type DifferentialEqn ㄇ x y = Shade (x, y) -> LocalDifferentialEqn ㄇ x y newtype LocalDifferentialEqn ㄇ x y LocalDifferentialEqn :: (ㄇ x y -> (Maybe (Shade' y), Maybe (Shade' (LocalLinear x y)))) -> LocalDifferentialEqn ㄇ x y [_rescanDifferentialEqn] :: LocalDifferentialEqn ㄇ x y -> ㄇ x y -> (Maybe (Shade' y), Maybe (Shade' (LocalLinear x y))) propagateDEqnSolution_loc :: forall x y ㄇ. (ModellableRelation x y, LocalModel ㄇ) => DifferentialEqn ㄇ x y -> LocalDataPropPlan x (Shade' y) -> Maybe (Shade' y) data LocalDataPropPlan x y LocalDataPropPlan :: !Interior x -> !Needle x -> !y -> [(Needle x, y)] -> LocalDataPropPlan x y [_sourcePosition] :: LocalDataPropPlan x y -> !Interior x [_targetPosOffset] :: LocalDataPropPlan x y -> !Needle x [_sourceData, _targetAPrioriData] :: LocalDataPropPlan x y -> !y [_relatedData] :: LocalDataPropPlan x y -> [(Needle x, y)] rangeWithinVertices :: forall s i m t. (RealFrac' s, WithField s PseudoAffine i, WithField s PseudoAffine m, Geodesic i, Geodesic m, SimpleSpace (Needle i), SimpleSpace (Needle m), AffineManifold (Interior i), AffineManifold (Interior m), Object (Affine s) (Interior i), Object (Affine s) (Interior m), Traversable t) => (Interior i, Interior m) -> t (i, m) -> Maybe (Shade i -> Shade m) instance Data.Manifold.Function.LocalModel.LocalModel Data.Manifold.Function.LocalModel.AffineModel instance Data.Manifold.Function.LocalModel.LocalModel Data.Manifold.Function.LocalModel.QuadraticModel instance (GHC.Show.Show (Data.Manifold.Shade.Shade y), GHC.Show.Show (Data.Manifold.Shade.Shade (Math.Manifold.Core.PseudoAffine.Needle x Math.LinearMap.Category.Class.+> Math.Manifold.Core.PseudoAffine.Needle y)), GHC.Show.Show (Data.Manifold.Shade.Shade (Math.Manifold.Core.PseudoAffine.Needle x Math.LinearMap.Category.Instances.⊗〃+> Math.Manifold.Core.PseudoAffine.Needle y))) => GHC.Show.Show (Data.Manifold.Function.LocalModel.QuadraticModel x y) instance (GHC.Show.Show (Data.Manifold.Shade.Shade y), GHC.Show.Show (Data.Manifold.Shade.Shade (Math.Manifold.Core.PseudoAffine.Needle x Math.LinearMap.Category.Class.+> Math.Manifold.Core.PseudoAffine.Needle y))) => GHC.Show.Show (Data.Manifold.Function.LocalModel.AffineModel x y) instance (GHC.Show.Show (Math.Manifold.Core.PseudoAffine.Interior x), GHC.Show.Show y, GHC.Show.Show (Math.Manifold.Core.PseudoAffine.Needle x)) => GHC.Show.Show (Data.Manifold.Function.LocalModel.LocalDataPropPlan x y) -- | 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. module Data.Manifold module Data.Manifold.Web.Internal type WebNodeId = Int type WebNodeIdOffset = Int data Neighbourhood x y Neighbourhood :: y -> Vector WebNodeIdOffset -> Metric x -> Maybe (Needle' x) -> Neighbourhood x y [_dataAtNode] :: Neighbourhood x y -> y [_neighbours] :: Neighbourhood x y -> Vector WebNodeIdOffset [_localScalarProduct] :: Neighbourhood x y -> Metric x [_webBoundaryAtNode] :: Neighbourhood x y -> Maybe (Needle' x) webBoundaryAtNode :: forall x_a5zIB y_a5zIC. Lens' (Neighbourhood x_a5zIB y_a5zIC) (Maybe (Needle' x_a5zIB)) neighbours :: forall x_a5zIB y_a5zIC. Lens' (Neighbourhood x_a5zIB y_a5zIC) (Vector WebNodeIdOffset) localScalarProduct :: forall x_a5zIB y_a5zIC. Lens' (Neighbourhood x_a5zIB y_a5zIC) (Metric x_a5zIB) dataAtNode :: forall x_a5zIB y_a5zIC y_a5zSq. Lens (Neighbourhood x_a5zIB y_a5zIC) (Neighbourhood x_a5zIB y_a5zSq) y_a5zIC y_a5zSq data WebLocally x y LocalWebInfo :: x -> y -> WebNodeId -> [(WebNodeId, (Needle x, WebLocally x y))] -> Metric x -> Maybe (Needle' x) -> WebLocally x y [_thisNodeCoord] :: WebLocally x y -> x [_thisNodeData] :: WebLocally x y -> y [_thisNodeId] :: WebLocally x y -> WebNodeId [_nodeNeighbours] :: WebLocally x y -> [(WebNodeId, (Needle x, WebLocally x y))] [_nodeLocalScalarProduct] :: WebLocally x y -> Metric x [_webBoundingPlane] :: WebLocally x y -> Maybe (Needle' x) webBoundingPlane :: forall x_a5zT1 y_a5zT2. Lens' (WebLocally x_a5zT1 y_a5zT2) (Maybe (Needle' x_a5zT1)) thisNodeId :: forall x_a5zT1 y_a5zT2. Lens' (WebLocally x_a5zT1 y_a5zT2) WebNodeId thisNodeData :: forall x_a5zT1 y_a5zT2. Lens' (WebLocally x_a5zT1 y_a5zT2) y_a5zT2 thisNodeCoord :: forall x_a5zT1 y_a5zT2. Lens' (WebLocally x_a5zT1 y_a5zT2) x_a5zT1 nodeNeighbours :: forall x_a5zT1 y_a5zT2. Lens' (WebLocally x_a5zT1 y_a5zT2) [(WebNodeId, (Needle x_a5zT1, WebLocally x_a5zT1 y_a5zT2))] nodeLocalScalarProduct :: forall x_a5zT1 y_a5zT2. Lens' (WebLocally x_a5zT1 y_a5zT2) (Metric x_a5zT1) data NeighbourhoodVector x NeighbourhoodVector :: Int -> Needle x -> Needle' x -> Scalar (Needle x) -> Scalar (Needle x) -> NeighbourhoodVector x [_nvectId] :: NeighbourhoodVector x -> Int [_theNVect] :: NeighbourhoodVector x -> Needle x [_nvectNormal] :: NeighbourhoodVector x -> Needle' x [_nvectLength] :: NeighbourhoodVector x -> Scalar (Needle x) [_otherNeighboursOverlap] :: NeighbourhoodVector x -> Scalar (Needle x) theNVect :: forall x_a5A7N. Lens' (NeighbourhoodVector x_a5A7N) (Needle x_a5A7N) otherNeighboursOverlap :: forall x_a5A7N. Lens' (NeighbourhoodVector x_a5A7N) (Scalar (Needle x_a5A7N)) nvectNormal :: forall x_a5A7N. Lens' (NeighbourhoodVector x_a5A7N) (Needle' x_a5A7N) nvectLength :: forall x_a5A7N. Lens' (NeighbourhoodVector x_a5A7N) (Scalar (Needle x_a5A7N)) nvectId :: forall x_a5A7N. Lens' (NeighbourhoodVector x_a5A7N) Int data PropagationInconsistency x υ PropagationInconsistency :: [(x, υ)] -> υ -> PropagationInconsistency x υ [_inconsistentPropagatedData] :: PropagationInconsistency x υ -> [(x, υ)] [_inconsistentAPrioriData] :: PropagationInconsistency x υ -> υ PropagationInconsistencies :: [PropagationInconsistency x υ] -> PropagationInconsistency x υ inconsistentPropagatedData :: forall x_a5AcZ υ_a5Ad0. Traversal' (PropagationInconsistency x_a5AcZ υ_a5Ad0) [(x_a5AcZ, υ_a5Ad0)] inconsistentAPrioriData :: forall x_a5AcZ υ_a5Ad0. Traversal' (PropagationInconsistency x_a5AcZ υ_a5Ad0) υ_a5Ad0 -- | 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. newtype PointsWeb :: * -> * -> * [PointsWeb] :: {webNodeRsc :: x `Shaded` Neighbourhood x y} -> PointsWeb x y data WebChunk x y WebChunk :: PointsWeb x y -> [(x `Shaded` Neighbourhood x y, WebNodeId)] -> WebChunk x y [_thisChunk] :: WebChunk x y -> PointsWeb x y [_layersAroundChunk] :: WebChunk x y -> [(x `Shaded` Neighbourhood x y, WebNodeId)] thisChunk :: forall x_a5AiG y_a5AiH. Lens' (WebChunk x_a5AiG y_a5AiH) (PointsWeb x_a5AiG y_a5AiH) layersAroundChunk :: forall x_a5AiG y_a5AiH. Lens' (WebChunk x_a5AiG y_a5AiH) [(Shaded x_a5AiG (Neighbourhood x_a5AiG y_a5AiH), WebNodeId)] data NodeInWeb x y NodeInWeb :: (x, Neighbourhood x y) -> [(x `Shaded` Neighbourhood x y, WebNodeId)] -> NodeInWeb x y [_thisNodeOnly] :: NodeInWeb x y -> (x, Neighbourhood x y) [_layersAroundNode] :: NodeInWeb x y -> [(x `Shaded` Neighbourhood x y, WebNodeId)] thisNodeOnly :: forall x_a5Ax5 y_a5Ax6. Lens' (NodeInWeb x_a5Ax5 y_a5Ax6) (x_a5Ax5, Neighbourhood x_a5Ax5 y_a5Ax6) layersAroundNode :: forall x_a5Ax5 y_a5Ax6. Lens' (NodeInWeb x_a5Ax5 y_a5Ax6) [(Shaded x_a5Ax5 (Neighbourhood x_a5Ax5 y_a5Ax6), WebNodeId)] data PathStep x y PathStep :: WebLocally x y -> WebLocally x y -> PathStep x y [_pathStepStart] :: PathStep x y -> WebLocally x y [_pathStepEnd] :: PathStep x y -> WebLocally x y pathStepStart :: forall x_a5Az3 y_a5Az4. Lens' (PathStep x_a5Az3 y_a5Az4) (WebLocally x_a5Az3 y_a5Az4) pathStepEnd :: forall x_a5Az3 y_a5Az4. Lens' (PathStep x_a5Az3 y_a5Az4) (WebLocally x_a5Az3 y_a5Az4) type MetricChoice x = Shade x -> Metric x traverseInnermostChunks :: forall f x y z. Applicative f => (WebChunk x y -> f (PointsWeb x z)) -> PointsWeb x y -> f (PointsWeb x z) traverseNodesInEnvi :: forall f x y z. Applicative f => (NodeInWeb x y -> f (Neighbourhood x z)) -> PointsWeb x y -> f (PointsWeb x z) fmapNodesInEnvi :: (NodeInWeb x y -> Neighbourhood x z) -> PointsWeb x y -> PointsWeb x z ixedFoci :: [a] -> [((Int, a), [a])] indexWeb :: PointsWeb x y -> WebNodeId -> Maybe (x, y) unsafeIndexWebData :: PointsWeb x y -> WebNodeId -> y jumpNodeOffset :: WebNodeIdOffset -> NodeInWeb x y -> NodeInWeb x y webAroundChunk :: WebChunk x y -> PointsWeb x y zoomoutWebChunk :: WebNodeIdOffset -> WebChunk x y -> (WebChunk x y, WebNodeId) pickNodeInWeb :: PointsWeb x y -> WebNodeId -> NodeInWeb x y webLocalInfo :: forall x y. WithField ℝ Manifold x => PointsWeb x y -> PointsWeb x (WebLocally x y) localFmapWeb :: WithField ℝ Manifold x => (WebLocally x y -> z) -> PointsWeb x y -> PointsWeb x z tweakWebGeometry :: (WithField ℝ Manifold x, SimpleSpace (Needle x)) => MetricChoice x -> (WebLocally x y -> [WebNodeId]) -> PointsWeb x y -> PointsWeb x y bidirectionaliseWebLinks :: forall x y. PointsWeb x y -> PointsWeb x y pumpHalfspace :: forall v. (SimpleSpace v, Scalar v ~ ℝ) => Norm v -> v -> (DualVector v, [v]) -> Maybe (DualVector v) smallPseudorandSeq :: [ℝ] data LinkingBadness r LinkingBadness :: !r -> !r -> LinkingBadness 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. [gatherDirectionsBadness] :: LinkingBadness r -> !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. [closeSystemBadness] :: LinkingBadness r -> !r linkingUndesirability :: ℝ -> ℝ -> LinkingBadness ℝ bestNeighbours :: forall i v. (SimpleSpace v, Scalar v ~ ℝ) => Norm v -> [(i, v)] -> ([i], Maybe (DualVector v)) bestNeighbours' :: forall i v. (SimpleSpace v, Scalar v ~ ℝ) => Norm v -> [(i, v)] -> ([(i, v)], Maybe (DualVector v)) gatherGoodNeighbours :: forall i v. (SimpleSpace v, Scalar v ~ ℝ) => Norm v -> Variance v -> DualVector v -> [v] -> [(i, v)] -> [(i, v)] -> ([(i, v)], Maybe (DualVector v)) extractSmallestOn :: Ord b => (a -> Maybe b) -> [a] -> Maybe (a, [a]) type WNIPath = [WebNodeId] type NodeSet = IntSet pathsTowards :: forall x y. (WithField ℝ Manifold x, HasCallStack) => WebNodeId -> PointsWeb x y -> [[y]] traversePathInIWeb :: forall φ x y. (WithField ℝ Manifold x, Monad φ, HasCallStack) => [WebNodeId] -> (PathStep x y -> φ y) -> PointsWeb x (WebLocally x y) -> φ (PointsWeb x (WebLocally x y)) traversePathsTowards :: forall f φ x y. (WithField ℝ Manifold x, Monad φ, Monad f, HasCallStack) => WebNodeId -> (PathStep x y -> φ y) -> (forall υ. WebLocally x y -> φ υ -> f υ) -> PointsWeb x y -> f (PointsWeb x y) instance GHC.Base.Functor Data.Manifold.Web.Internal.LinkingBadness instance GHC.Base.Functor (Data.Manifold.Web.Internal.WebLocally x) instance Data.Manifold.PseudoAffine.WithField Math.Manifold.Core.Types.Internal.ℝ Data.Manifold.PseudoAffine.Manifold x => Control.Comonad.Comonad (Data.Manifold.Web.Internal.WebLocally x) instance Data.Traversable.Traversable (Data.Manifold.Web.Internal.PointsWeb a) instance Data.Foldable.Foldable (Data.Manifold.Web.Internal.PointsWeb a) instance GHC.Base.Functor (Data.Manifold.Web.Internal.PointsWeb a) instance GHC.Generics.Generic (Data.Manifold.Web.Internal.PointsWeb a b) instance (Control.DeepSeq.NFData x, Control.DeepSeq.NFData (Data.Manifold.PseudoAffine.Metric x), Control.DeepSeq.NFData (Data.Manifold.PseudoAffine.Needle' x), Control.DeepSeq.NFData y) => Control.DeepSeq.NFData (Data.Manifold.Web.Internal.PointsWeb x y) instance Data.Foldable.Constrained.Foldable (Data.Manifold.Web.Internal.PointsWeb x) (->) (->) instance GHC.Base.Semigroup (Data.Manifold.Web.Internal.PropagationInconsistency x υ) instance GHC.Base.Monoid (Data.Manifold.Web.Internal.PropagationInconsistency x υ) instance (Control.DeepSeq.NFData x, Control.DeepSeq.NFData (Data.Manifold.PseudoAffine.Metric x), Control.DeepSeq.NFData (Data.Manifold.PseudoAffine.Needle' x), Control.DeepSeq.NFData y) => Control.DeepSeq.NFData (Data.Manifold.Web.Internal.Neighbourhood x y) instance (GHC.Show.Show x, GHC.Show.Show υ) => GHC.Show.Show (Data.Manifold.Web.Internal.PropagationInconsistency x υ) instance GHC.Generics.Generic (Data.Manifold.Web.Internal.WebLocally x y) instance (Data.Manifold.PseudoAffine.WithField Math.Manifold.Core.Types.Internal.ℝ Math.Manifold.Core.PseudoAffine.PseudoAffine x, Math.VectorSpace.Docile.SimpleSpace (Math.Manifold.Core.PseudoAffine.Needle x), GHC.Show.Show (Data.Manifold.PseudoAffine.Needle' x), GHC.Show.Show y) => GHC.Show.Show (Data.Manifold.Web.Internal.Neighbourhood x y) instance Data.Traversable.Traversable (Data.Manifold.Web.Internal.Neighbourhood x) instance Data.Foldable.Foldable (Data.Manifold.Web.Internal.Neighbourhood x) instance GHC.Base.Functor (Data.Manifold.Web.Internal.Neighbourhood x) instance GHC.Generics.Generic (Data.Manifold.Web.Internal.Neighbourhood x y) module Data.Manifold.Web -- | 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. data PointsWeb :: * -> * -> * fromWebNodes :: forall x y. (WithField ℝ Manifold x, SimpleSpace (Needle x)) => MetricChoice x -> [(x, y)] -> PointsWeb x y fromShadeTree_auto :: forall x. (WithField ℝ Manifold x, SimpleSpace (Needle x)) => ShadeTree x -> PointsWeb x () fromShadeTree :: forall x. (WithField ℝ Manifold x, SimpleSpace (Needle x)) => (Shade x -> Metric x) -> ShadeTree x -> PointsWeb x () fromShaded :: forall x y. (WithField ℝ Manifold x, SimpleSpace (Needle x)) => MetricChoice x -> (x `Shaded` y) -> PointsWeb x y -- | fmap from the co-Kleisli category of WebLocally. nearestNeighbour :: forall x y. (WithField ℝ Manifold x, SimpleSpace (Needle x)) => PointsWeb x y -> x -> Maybe (x, y) indexWeb :: PointsWeb x y -> WebNodeId -> Maybe (x, y) toGraph :: (WithField ℝ Manifold x, SimpleSpace (Needle x)) => PointsWeb x y -> (Graph, Vertex -> (x, y)) webBoundary :: WithField ℝ Manifold x => PointsWeb x y -> [(Cutplane x, y)] -- | Fetch a point between any two neighbouring web nodes on opposite sides -- of the plane, and linearly interpolate the values onto the cut plane. sliceWeb_lin :: forall x y. (WithField ℝ Manifold x, SimpleSpace (Needle x), Geodesic x, Geodesic y) => PointsWeb x y -> Cutplane x -> [(x, y)] sampleWeb_2Dcartesian_lin :: (x ~ ℝ, y ~ ℝ, Geodesic z) => PointsWeb (x, y) z -> ((x, x), Int) -> ((y, y), Int) -> [(y, [(x, Maybe z)])] sampleEntireWeb_2Dcartesian_lin :: (x ~ ℝ, y ~ ℝ, Geodesic z) => PointsWeb (x, y) z -> Int -> Int -> [(y, [(x, Maybe z)])] localFocusWeb :: WithField ℝ Manifold x => PointsWeb x y -> PointsWeb x ((x, y), [(Needle x, y)]) differentiateUncertainWebFunction :: forall x y. ModellableRelation x y => PointsWeb x (Shade' y) -> PointsWeb x (Shade' (LocalLinear x y)) differentiate²UncertainWebFunction :: forall x y. ModellableRelation x y => PointsWeb x (Shade' y) -> PointsWeb x (Shade' (Needle x ⊗〃+> Needle y)) -- | 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) localModels_CGrid :: forall x y ㄇ. (ModellableRelation x y, LocalModel ㄇ) => PointsWeb x (Shade' y) -> [(x, ㄇ x y)] 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)) iterateFilterDEqn_pathwise :: (ModellableRelation x y, MonadPlus m, Traversable 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)) 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)) filterDEqnSolutions_adaptive :: forall x y ㄇ ð badness m. (ModellableRelation x y, AffineManifold y, badness ~ ℝ, Monad m, LocalModel ㄇ) => MetricChoice x -> 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 :: (ModellableRelation x y, AffineManifold y, LocalModel ㄇ, Monad m) => MetricChoice x -> InconsistencyStrategy m x (Shade' y) -> DifferentialEqn ㄇ x y -> (x -> Shade' y -> ℝ) -> PointsWeb x (Shade' y) -> [PointsWeb x (Shade' y)] data InconsistencyStrategy m x y [AbortOnInconsistency] :: InconsistencyStrategy Maybe x y [IgnoreInconsistencies] :: InconsistencyStrategy Identity x y [HighlightInconsistencies] :: y -> InconsistencyStrategy Identity x y newtype InformationMergeStrategy n m y' y InformationMergeStrategy :: (y -> n y' -> m y) -> InformationMergeStrategy n m y' y [mergeInformation] :: InformationMergeStrategy n m y' y -> y -> n y' -> m y naïve :: (NonEmpty y -> y) -> InformationMergeStrategy [] Identity (x, y) y inconsistencyAware :: (NonEmpty y -> m y) -> InformationMergeStrategy [] m (x, y) y indicateInconsistencies :: (NonEmpty υ -> Maybe υ) -> InformationMergeStrategy [] (Except (PropagationInconsistency x υ)) (x, υ) υ postponeInconsistencies :: Monad m => (NonEmpty υ -> Maybe υ) -> InformationMergeStrategy [] (WriterT [PropagationInconsistency x υ] m) (x, υ) υ data PropagationInconsistency x υ PropagationInconsistency :: [(x, υ)] -> υ -> PropagationInconsistency x υ [_inconsistentPropagatedData] :: PropagationInconsistency x υ -> [(x, υ)] [_inconsistentAPrioriData] :: PropagationInconsistency x υ -> υ PropagationInconsistencies :: [PropagationInconsistency x υ] -> PropagationInconsistency x υ data ConvexSet x EmptyConvex :: ConvexSet x ConvexSet :: Shade' x -> [Shade' x] -> ConvexSet x -- | If p is in all intersectors, it must also be in the hull. [convexSetHull] :: ConvexSet x -> Shade' x [convexSetIntersectors] :: ConvexSet x -> [Shade' x] ellipsoid :: Shade' x -> ConvexSet x ellipsoidSet :: Embedding (->) (Maybe (Shade' x)) (ConvexSet x) coerceWebDomain :: forall a b y. (Manifold a, Manifold b, LocallyCoercible a b, SimpleSpace (Needle b)) => PointsWeb a y -> PointsWeb b y rescanPDELocally :: forall x y ㄇ. (ModellableRelation x y, LocalModel ㄇ) => DifferentialEqn ㄇ x y -> WebLocally x (Shade' y) -> Maybe (Shade' y) localOnion :: forall x y. WithField ℝ Manifold x => WebLocally x y -> [WebNodeId] -> [[(Needle x, WebLocally x y)]] webOnions :: forall x y. WithField ℝ Manifold x => PointsWeb x y -> PointsWeb x [[(x, y)]] -- | 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. knitShortcuts :: forall x y. (WithField ℝ Manifold x, SimpleSpace (Needle x)) => MetricChoice x -> PointsWeb x y -> PointsWeb x y instance GHC.Base.Functor Data.Manifold.Web.Average instance (GHC.Show.Show x, GHC.Show.Show (Math.Manifold.Core.PseudoAffine.Needle x), GHC.Show.Show (Data.Manifold.PseudoAffine.Needle' x)) => GHC.Show.Show (Data.Manifold.Web.GridPlanes x) instance (GHC.Show.Show x, GHC.Show.Show (Math.Manifold.Core.PseudoAffine.Needle x), GHC.Show.Show (Data.Manifold.PseudoAffine.Needle' x)) => GHC.Show.Show (Data.Manifold.Web.GridSetup x) instance Data.Manifold.Shade.LtdErrorShow x => GHC.Show.Show (Data.Manifold.Web.ConvexSet x) instance GHC.Base.Functor (Data.Manifold.Web.InconsistencyStrategy m x) instance GHC.Num.Num a => GHC.Base.Semigroup (Data.Manifold.Web.Average a) instance GHC.Num.Num a => GHC.Base.Monoid (Data.Manifold.Web.Average a) instance GHC.Base.Applicative Data.Manifold.Web.Average instance Data.Manifold.Shade.Refinable x => GHC.Base.Semigroup (Data.Manifold.Web.ConvexSet x) module Data.Manifold.Function.Interpolation data InterpolationFunction ㄇ x y module Data.Manifold.DifferentialEquation type DifferentialEqn ㄇ x y = Shade (x, y) -> LocalDifferentialEqn ㄇ x y -- | An ordinary differential equation is one that does not need any -- a-priori partial derivatives to compute the derivative for integration -- in some propagation direction. Classically, ODEs are usually -- understood as DifferentialEquation ℝ ℝ⁰ y, but actually -- x can at least be an arbitrary one-dimensional space (i.e. -- basically real intervals or ). In these cases, there is -- always only one partial derivative: that which we integrate over, in -- the only possible direction for propagation. type ODE x y = DifferentialEqn QuadraticModel x y constLinearDEqn :: forall x y. (SimpleSpace x, SimpleSpace y, AffineManifold y, Scalar x ~ ℝ, Scalar y ~ ℝ) => (y +> (x +> y)) -> ((x +> y) +> y) -> DifferentialEqn QuadraticModel x y constLinearODE :: forall x y. (SimpleSpace x, Scalar x ~ ℝ, AffineManifold y, SimpleSpace y, Scalar y ~ ℝ) => ((x +> y) +> y) -> ODE x y 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)) maxDeviationsGoal :: (WithField ℝ EuclidSpace y, SimpleSpace (Needle y)) => [Needle y] -> x -> Shade' y -> ℝ uncertaintyGoal :: (WithField ℝ EuclidSpace y, SimpleSpace (Needle y)) => Metric' y -> x -> Shade' y -> ℝ uncertaintyGoal' :: (WithField ℝ EuclidSpace y, SimpleSpace (Needle y)) => (x -> Metric' y) -> x -> Shade' y -> ℝ euclideanVolGoal :: (WithField ℝ EuclidSpace y, SimpleSpace (Needle y)) => ℝ -> x -> Shade' y -> ℝ data InconsistencyStrategy m x y [AbortOnInconsistency] :: InconsistencyStrategy Maybe x y [IgnoreInconsistencies] :: InconsistencyStrategy Identity x y [HighlightInconsistencies] :: y -> InconsistencyStrategy Identity x y module Data.Simplex.Abstract data family AbstractSimplex v x type Simplex m = AbstractSimplex (Needle m) m type SimplexF m y = AbstractSimplex (Needle m) (FibreBundle m y) type SimplexSpanning m = (WithField ℝ Manifold m, VectorSpace (Needle m), Traversable (AbstractSimplex (Needle m))) seenFromOneVertex :: (WithField ℝ Manifold m, Foldable (AbstractSimplex (Needle m))) => Simplex m -> (m, [Needle m]) toBarycentric :: (WithField ℝ Manifold m, Foldable (AbstractSimplex (Needle m)), SimpleSpace (Needle m)) => Simplex m -> m -> [ℝ] instance Data.Traversable.Traversable (Data.Simplex.Abstract.AbstractSimplex Math.Manifold.Core.Types.Internal.ℝ⁰) instance Data.Foldable.Foldable (Data.Simplex.Abstract.AbstractSimplex Math.Manifold.Core.Types.Internal.ℝ⁰) instance GHC.Base.Functor (Data.Simplex.Abstract.AbstractSimplex Math.Manifold.Core.Types.Internal.ℝ⁰) instance Data.Traversable.Traversable (Data.Simplex.Abstract.AbstractSimplex Math.Manifold.Core.Types.Internal.ℝ) instance Data.Foldable.Foldable (Data.Simplex.Abstract.AbstractSimplex Math.Manifold.Core.Types.Internal.ℝ) instance GHC.Base.Functor (Data.Simplex.Abstract.AbstractSimplex Math.Manifold.Core.Types.Internal.ℝ) instance Data.Traversable.Traversable (Data.Simplex.Abstract.AbstractSimplex Data.Manifold.Types.Primitive.ℝ¹) instance Data.Foldable.Foldable (Data.Simplex.Abstract.AbstractSimplex Data.Manifold.Types.Primitive.ℝ¹) instance GHC.Base.Functor (Data.Simplex.Abstract.AbstractSimplex Data.Manifold.Types.Primitive.ℝ¹) instance Data.Traversable.Traversable (Data.Simplex.Abstract.AbstractSimplex Data.Manifold.Types.Primitive.ℝ²) instance Data.Foldable.Foldable (Data.Simplex.Abstract.AbstractSimplex Data.Manifold.Types.Primitive.ℝ²) instance GHC.Base.Functor (Data.Simplex.Abstract.AbstractSimplex Data.Manifold.Types.Primitive.ℝ²) instance Data.Traversable.Traversable (Data.Simplex.Abstract.AbstractSimplex Data.Manifold.Types.Primitive.ℝ³) instance Data.Foldable.Foldable (Data.Simplex.Abstract.AbstractSimplex Data.Manifold.Types.Primitive.ℝ³) instance GHC.Base.Functor (Data.Simplex.Abstract.AbstractSimplex Data.Manifold.Types.Primitive.ℝ³) instance Data.Traversable.Traversable (Data.Simplex.Abstract.AbstractSimplex Data.Manifold.Types.Primitive.ℝ⁴) instance Data.Foldable.Foldable (Data.Simplex.Abstract.AbstractSimplex Data.Manifold.Types.Primitive.ℝ⁴) instance GHC.Base.Functor (Data.Simplex.Abstract.AbstractSimplex Data.Manifold.Types.Primitive.ℝ⁴) instance GHC.Base.Functor (Data.Simplex.Abstract.AbstractSimplex v) => GHC.Base.Functor (Data.Simplex.Abstract.AbstractSimplex (Math.Manifold.Core.Types.Internal.ℝ, v)) instance Data.Foldable.Foldable (Data.Simplex.Abstract.AbstractSimplex v) => Data.Foldable.Foldable (Data.Simplex.Abstract.AbstractSimplex (Math.Manifold.Core.Types.Internal.ℝ, v)) instance Data.Traversable.Traversable (Data.Simplex.Abstract.AbstractSimplex v) => Data.Traversable.Traversable (Data.Simplex.Abstract.AbstractSimplex (Math.Manifold.Core.Types.Internal.ℝ, v)) instance GHC.Base.Functor (Data.Simplex.Abstract.AbstractSimplex (GHC.Generics.Rep m ())) => GHC.Base.Functor (Data.Simplex.Abstract.AbstractSimplex (Math.Manifold.Core.PseudoAffine.GenericNeedle m)) instance Data.Foldable.Foldable (Data.Simplex.Abstract.AbstractSimplex (GHC.Generics.Rep m ())) => Data.Foldable.Foldable (Data.Simplex.Abstract.AbstractSimplex (Math.Manifold.Core.PseudoAffine.GenericNeedle m)) instance Data.Traversable.Traversable (Data.Simplex.Abstract.AbstractSimplex (GHC.Generics.Rep m ())) => Data.Traversable.Traversable (Data.Simplex.Abstract.AbstractSimplex (Math.Manifold.Core.PseudoAffine.GenericNeedle m)) instance GHC.Base.Functor (Data.Simplex.Abstract.AbstractSimplex (Math.Manifold.Core.PseudoAffine.Needle (f p), Math.Manifold.Core.PseudoAffine.Needle (g p))) => GHC.Base.Functor (Data.Simplex.Abstract.AbstractSimplex (Math.Manifold.Core.PseudoAffine.NeedleProductSpace f g p)) instance Data.Foldable.Foldable (Data.Simplex.Abstract.AbstractSimplex (Math.Manifold.Core.PseudoAffine.Needle (f p), Math.Manifold.Core.PseudoAffine.Needle (g p))) => Data.Foldable.Foldable (Data.Simplex.Abstract.AbstractSimplex (Math.Manifold.Core.PseudoAffine.NeedleProductSpace f g p)) instance Data.Traversable.Traversable (Data.Simplex.Abstract.AbstractSimplex (Math.Manifold.Core.PseudoAffine.Needle (f p), Math.Manifold.Core.PseudoAffine.Needle (g p))) => Data.Traversable.Traversable (Data.Simplex.Abstract.AbstractSimplex (Math.Manifold.Core.PseudoAffine.NeedleProductSpace f g p)) instance GHC.Base.Applicative (Data.Simplex.Abstract.AbstractSimplex Math.Manifold.Core.Types.Internal.ℝ⁰) module Data.Manifold.Mesh -- | A mesh is a container data structure whose nodes are in some way -- located distributed over a manifold, and are aware of the topology by -- way of having access to their neighbours. Any such grid can be seen as -- a PointsWeb, but it may have extra structure (e.g. rectangular) -- in addition to that. class SimplexSpanning (MeshDomainSpace メ) => Mesh メ where { type family MeshDomainSpace メ :: *; type family MeshGridDataConstraint メ y :: Constraint; type MeshGridDataConstraint メ y = (); } asWeb :: (Mesh メ, MeshGridDataConstraint メ y) => メ y -> PointsWeb (MeshDomainSpace メ) y meshSimplicesInWeb :: Mesh メ => メ y -> [AbstractSimplex (Needle (MeshDomainSpace メ)) WebNodeId] meshSimplices :: (Mesh メ, MeshGridDataConstraint メ y) => メ y -> [SimplexF (MeshDomainSpace メ) y] extrapolateGrid :: (Mesh メ, WithField ℝ Manifold y, Connected y, MeshGridDataConstraint メ y) => メ y -> MeshDomainSpace メ -> y -- | A mesh that “covers” the entire manifold, i.e. any point lies between -- some nodes of the mesh. class Mesh メ => CoveringMesh メ interpolateGrid :: (CoveringMesh メ, WithField ℝ Manifold y, Connected y, MeshGridDataConstraint メ y) => メ y -> MeshDomainSpace メ -> y -- | Some manifolds are “naturally” embedded within some bigger space. For -- instance, the topological spheres are readily identified with the -- geometric unit spheres in real vector spaces. -- -- An embedding is a pretty strong relationship, but often all that's -- needed is being able to map single points from the manifold to the -- enclosing space. This module offers a class which does just that. module Math.Manifold.Embedding.Simple.Class class NaturallyEmbedded m v embed :: NaturallyEmbedded m v => m -> v coEmbed :: NaturallyEmbedded m v => v -> m module Math.Manifold.Real.Coordinates -- | A coordinate is a function that can be used both to determine the -- position of a point on a manifold along the one of some family of -- (possibly curved) axes on which it lies, and for moving the point -- along that axis. Basically, this is a Lens and can indeed be -- used with the ^., .~ and %~ operators. -- --
--   Coordinate m ~ Lens' m 
--   
-- -- In addition, each type may also have a way of identifying particular -- coordinate axes. This is done with CoordinateIdentifier, which -- is what should be used for defining given coordinate axes. type Coordinate m = forall q. CoordinateIsh q m => q coordinate :: CoordinateIdentifier m -> Coordinate m -- | To give a custom type coordinate axes, first define an instance of -- this class. class HasCoordinates m where { -- | A unique description of a coordinate axis. data family CoordinateIdentifier m :: *; } -- | How to use a coordinate axis for points in the containing space. This -- is what coordinate calls under the hood. coordinateAsLens :: HasCoordinates m => CoordinateIdentifier m -> Lens' m ℝ -- | Delimiters for the possible values one may choose for a given -- coordinate, around a point on the manifold. For example, in spherical -- coordinates, the azimuth generally has a range of -- (-pi, pi), except at the poles where it's -- (0,0). validCoordinateRange :: HasCoordinates m => CoordinateIdentifier m -> m -> (ℝ, ℝ) class HasCoordinates m => HasXCoord m xCoord :: HasXCoord m => Coordinate m class HasYCoord m yCoord :: HasYCoord m => Coordinate m class HasZCoord m zCoord :: HasZCoord m => Coordinate m location's :: (HasCoordinates b, Interior b ~ b, HasCoordinates f) => CoordinateIdentifier b -> Coordinate (FibreBundle b f) class HasCoordinates m => CoordDifferential m -- | Observe local, small variations (in the tangent space) of a -- coordinate. The idea is that ((p & coord+~δc) − p) ^. delta -- coord ≈ δc, thus the name “delta”. Note however that this -- only holds exactly for flat spaces; in most manifolds it can (by -- design) only be understood in an asymptotic sense, i.e. used for -- evaluating directional derivatives of some function. In particular, -- delta azimuth is unstable near the poles of a sphere, -- because it has to compensate for the sensitive rotation of the -- unit vector. delta :: CoordDifferential m => CoordinateIdentifier m -> Coordinate (TangentBundle m) class HasAzimuth m azimuth :: HasAzimuth m => Coordinate m class HasZenithDistance m zenithAngle :: HasZenithDistance m => Coordinate m instance GHC.Show.Show (Math.Manifold.Real.Coordinates.CoordinateIdentifier Math.Manifold.Core.Types.Internal.ℝ) instance GHC.Classes.Eq (Math.Manifold.Real.Coordinates.CoordinateIdentifier Math.Manifold.Core.Types.Internal.ℝ) instance GHC.Show.Show (Math.Manifold.Real.Coordinates.CoordinateIdentifier Math.Manifold.Core.Types.Internal.S¹) instance GHC.Classes.Eq (Math.Manifold.Real.Coordinates.CoordinateIdentifier Math.Manifold.Core.Types.Internal.S¹) instance GHC.Show.Show (Math.Manifold.Real.Coordinates.CoordinateIdentifier Math.Manifold.Core.Types.Internal.S²) instance GHC.Classes.Eq (Math.Manifold.Real.Coordinates.CoordinateIdentifier Math.Manifold.Core.Types.Internal.S²) instance GHC.Show.Show (Math.Manifold.Real.Coordinates.CoordinateIdentifier Data.Manifold.Types.Primitive.ℝ²) instance GHC.Classes.Eq (Math.Manifold.Real.Coordinates.CoordinateIdentifier Data.Manifold.Types.Primitive.ℝ²) instance GHC.Show.Show (Math.Manifold.Real.Coordinates.CoordinateIdentifier Data.Manifold.Types.Primitive.ℝ³) instance GHC.Classes.Eq (Math.Manifold.Real.Coordinates.CoordinateIdentifier Data.Manifold.Types.Primitive.ℝ³) instance (GHC.Show.Show v, GHC.Show.Show (Math.LinearMap.Category.Class.DualVector v)) => GHC.Show.Show (Math.Manifold.Real.Coordinates.OriginAxisCoord v) instance (GHC.Classes.Eq v, GHC.Classes.Eq (Math.LinearMap.Category.Class.DualVector v)) => GHC.Classes.Eq (Math.Manifold.Real.Coordinates.OriginAxisCoord v) instance (GHC.Classes.Eq (Math.Manifold.Real.Coordinates.CoordinateIdentifier a), GHC.Classes.Eq (Math.Manifold.Real.Coordinates.CoordinateIdentifier b)) => GHC.Classes.Eq (Math.Manifold.Real.Coordinates.CoordinateIdentifier (a, b)) instance (GHC.Show.Show (Math.Manifold.Real.Coordinates.CoordinateIdentifier a), GHC.Show.Show (Math.Manifold.Real.Coordinates.CoordinateIdentifier b)) => GHC.Show.Show (Math.Manifold.Real.Coordinates.CoordinateIdentifier (a, b)) instance Math.Manifold.Real.Coordinates.HasZenithDistance Math.Manifold.Core.Types.Internal.S² instance Math.Manifold.Real.Coordinates.HasAzimuth Math.Manifold.Core.Types.Internal.S¹ instance Math.Manifold.Real.Coordinates.HasAzimuth Math.Manifold.Core.Types.Internal.S² instance (Math.Manifold.Real.Coordinates.CoordDifferential m, f Data.Type.Equality.~ Math.Manifold.Core.PseudoAffine.Needle m, m Data.Type.Equality.~ Math.Manifold.Core.PseudoAffine.Interior m, Test.QuickCheck.Arbitrary.Arbitrary m, Test.QuickCheck.Arbitrary.Arbitrary (Math.Manifold.Real.Coordinates.CoordinateIdentifier m), Test.QuickCheck.Arbitrary.Arbitrary (Math.Manifold.Real.Coordinates.CoordinateIdentifier f)) => Test.QuickCheck.Arbitrary.Arbitrary (Math.Manifold.Real.Coordinates.CoordinateIdentifier (Math.Manifold.Core.PseudoAffine.FibreBundle m f)) instance Math.Manifold.Real.Coordinates.CoordDifferential Math.Manifold.Core.Types.Internal.ℝ instance Math.Manifold.Real.Coordinates.CoordDifferential Data.Manifold.Types.Primitive.ℝ² instance Math.Manifold.Real.Coordinates.CoordDifferential Data.Manifold.Types.Primitive.ℝ³ instance (Math.Manifold.Real.Coordinates.CoordDifferential a, Math.Manifold.Real.Coordinates.CoordDifferential b) => Math.Manifold.Real.Coordinates.CoordDifferential (a, b) instance Math.Manifold.Real.Coordinates.CoordDifferential Math.Manifold.Core.Types.Internal.S¹ instance Math.Manifold.Real.Coordinates.CoordDifferential Math.Manifold.Core.Types.Internal.S² instance Math.Manifold.Real.Coordinates.HasZCoord Data.Manifold.Types.Primitive.ℝ³ instance Math.Manifold.Real.Coordinates.HasXCoord w => Math.Manifold.Real.Coordinates.HasZCoord ((Math.Manifold.Core.Types.Internal.ℝ, Math.Manifold.Core.Types.Internal.ℝ), w) instance Math.Manifold.Real.Coordinates.HasYCoord w => Math.Manifold.Real.Coordinates.HasZCoord (Math.Manifold.Core.Types.Internal.ℝ, w) instance Math.Manifold.Real.Coordinates.HasYCoord Data.Manifold.Types.Primitive.ℝ² instance Math.Manifold.Real.Coordinates.HasYCoord Data.Manifold.Types.Primitive.ℝ³ instance Math.Manifold.Real.Coordinates.HasCoordinates w => Math.Manifold.Real.Coordinates.HasYCoord ((Math.Manifold.Core.Types.Internal.ℝ, Math.Manifold.Core.Types.Internal.ℝ), w) instance Math.Manifold.Real.Coordinates.HasXCoord w => Math.Manifold.Real.Coordinates.HasYCoord (Math.Manifold.Core.Types.Internal.ℝ, w) instance Math.Manifold.Real.Coordinates.HasXCoord Math.Manifold.Core.Types.Internal.ℝ instance Math.Manifold.Real.Coordinates.HasXCoord Data.Manifold.Types.Primitive.ℝ² instance Math.Manifold.Real.Coordinates.HasXCoord Data.Manifold.Types.Primitive.ℝ³ instance (Math.Manifold.Real.Coordinates.HasXCoord v, Math.Manifold.Real.Coordinates.HasCoordinates w) => Math.Manifold.Real.Coordinates.HasXCoord (v, w) instance (Test.QuickCheck.Arbitrary.Arbitrary v, Data.VectorSpace.InnerSpace v, v Data.Type.Equality.~ Math.LinearMap.Category.Class.DualVector v, Data.VectorSpace.Scalar v Data.Type.Equality.~ Math.Manifold.Core.Types.Internal.ℝ) => Test.QuickCheck.Arbitrary.Arbitrary (Math.Manifold.Real.Coordinates.OriginAxisCoord v) instance Math.Manifold.Real.Coordinates.HasCoordinates Data.Manifold.Types.Primitive.ℝ² instance Math.Manifold.Real.Coordinates.HasCoordinates Data.Manifold.Types.Primitive.ℝ³ instance Math.Manifold.Real.Coordinates.CoordinateIsh (Math.Manifold.Real.Coordinates.CoordinateIdentifier m) m instance (GHC.Base.Functor f, Math.Manifold.Real.Coordinates.HasCoordinates m, a Data.Type.Equality.~ (Math.Manifold.Core.Types.Internal.ℝ -> f Math.Manifold.Core.Types.Internal.ℝ), b Data.Type.Equality.~ (m -> f m)) => Math.Manifold.Real.Coordinates.CoordinateIsh (a -> b) m instance Math.Manifold.Real.Coordinates.HasCoordinates Math.Manifold.Core.Types.Internal.ℝ⁰ instance Math.Manifold.Real.Coordinates.HasCoordinates Math.Manifold.Core.Types.Internal.ℝ instance Test.QuickCheck.Arbitrary.Arbitrary (Math.Manifold.Real.Coordinates.CoordinateIdentifier Math.Manifold.Core.Types.Internal.ℝ) instance Test.QuickCheck.Arbitrary.Arbitrary Data.Manifold.Types.Primitive.ℝ² => Test.QuickCheck.Arbitrary.Arbitrary (Math.Manifold.Real.Coordinates.CoordinateIdentifier Data.Manifold.Types.Primitive.ℝ²) instance Test.QuickCheck.Arbitrary.Arbitrary Data.Manifold.Types.Primitive.ℝ³ => Test.QuickCheck.Arbitrary.Arbitrary (Math.Manifold.Real.Coordinates.CoordinateIdentifier Data.Manifold.Types.Primitive.ℝ³) instance (Math.Manifold.Real.Coordinates.HasCoordinates a, Math.Manifold.Real.Coordinates.HasCoordinates b) => Math.Manifold.Real.Coordinates.HasCoordinates (a, b) instance (Test.QuickCheck.Arbitrary.Arbitrary (Math.Manifold.Real.Coordinates.CoordinateIdentifier a), Test.QuickCheck.Arbitrary.Arbitrary (Math.Manifold.Real.Coordinates.CoordinateIdentifier b)) => Test.QuickCheck.Arbitrary.Arbitrary (Math.Manifold.Real.Coordinates.CoordinateIdentifier (a, b)) instance (Math.Manifold.Real.Coordinates.HasCoordinates b, Math.Manifold.Real.Coordinates.HasCoordinates f) => Math.Manifold.Real.Coordinates.HasCoordinates (Math.Manifold.Core.PseudoAffine.FibreBundle b f) instance (GHC.Show.Show (Math.Manifold.Real.Coordinates.CoordinateIdentifier b), GHC.Show.Show (Math.Manifold.Real.Coordinates.CoordinateIdentifier f), GHC.Classes.Eq b, GHC.Classes.Eq (Math.Manifold.Real.Coordinates.CoordinateIdentifier f), Test.QuickCheck.Arbitrary.Arbitrary b, GHC.Show.Show b) => GHC.Show.Show (Math.Manifold.Real.Coordinates.CoordinateIdentifier (Math.Manifold.Core.PseudoAffine.FibreBundle b f)) instance Math.Manifold.Real.Coordinates.HasCoordinates Math.Manifold.Core.Types.Internal.S¹ instance Test.QuickCheck.Arbitrary.Arbitrary (Math.Manifold.Real.Coordinates.CoordinateIdentifier Math.Manifold.Core.Types.Internal.S¹) instance Math.Manifold.Real.Coordinates.HasCoordinates Math.Manifold.Core.Types.Internal.S² instance Test.QuickCheck.Arbitrary.Arbitrary (Math.Manifold.Real.Coordinates.CoordinateIdentifier Math.Manifold.Core.Types.Internal.S²)