-- 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.2.3.0 module Data.LinearMap.HerMetric -- | HerMetric is a portmanteau of Hermitian and -- metric (in the sense as used in e.g. general relativity – -- though those particular ones aren't positive definite and thus not -- really metrics). -- -- Mathematically, there are two directly equivalent ways to describe -- such a metric: as a bilinear mapping of two vectors to a scalar, or as -- a linear mapping from a vector space to its dual space. We choose the -- latter, though you can always as well think of metrics as “quadratic -- dual vectors”. -- -- Yet other possible interpretations of this type include density -- matrix (as in quantum mechanics), standard range of statistical -- fluctuations, and volume element. newtype HerMetric v HerMetric :: Maybe (Linear (Scalar v) v (DualSpace v)) -> HerMetric v [metricMatrix] :: HerMetric v -> Maybe (Linear (Scalar v) v (DualSpace v)) -- | A metric on the dual space; equivalent to a linear mapping from the -- dual space to the original vector space. -- -- Prime-versions of the functions in this module target those dual-space -- metrics, so we can avoid some explicit handling of double-dual spaces. newtype HerMetric' v HerMetric' :: Maybe (Linear (Scalar v) (DualSpace v) v) -> HerMetric' v [metricMatrix'] :: HerMetric' v -> Maybe (Linear (Scalar v) (DualSpace v) v) toDualWith :: HasMetric v => HerMetric v -> v -> DualSpace v fromDualWith :: HasMetric v => HerMetric' v -> DualSpace v -> v -- | Evaluate a vector through a metric. For the canonical metric on a -- Hilbert space, this will be simply magnitudeSq. metricSq :: HasMetric v => HerMetric v -> v -> Scalar v metricSq' :: HasMetric v => HerMetric' v -> DualSpace v -> Scalar v -- | Evaluate a vector's “magnitude” through a metric. This assumes an -- actual mathematical metric, i.e. positive definite – otherwise the -- internally used square root may get negative arguments (though it can -- still produce results if the scalars are complex; however, complex -- spaces aren't supported yet). metric :: (HasMetric v, Floating (Scalar v)) => HerMetric v -> v -> Scalar v metric' :: (HasMetric v, Floating (Scalar v)) => HerMetric' v -> DualSpace v -> Scalar v -- | Square-sum over the metrics for each dual-space vector. -- --
--   metrics m vs ≡ sqrt . sum $ metricSq m <$> vs
--   
metrics :: (HasMetric v, Floating (Scalar v)) => HerMetric v -> [v] -> Scalar v metrics' :: (HasMetric v, Floating (Scalar v)) => HerMetric' v -> [DualSpace v] -> Scalar v -- | A metric on v that simply yields the squared overlap of a -- vector with the given dual-space reference. -- -- It will perhaps be the most common way of defining HerMetric -- values to start with such dual-space vectors and superimpose the -- projectors using the VectorSpace instance; e.g. -- projector (1,0) ^+^ projector (0,2) -- yields a hermitian operator describing the ellipsoid span of the -- vectors e₀ and 2⋅e₁. Metrics generated this way are -- positive definite if no negative coefficients have been introduced -- with the *^ scaling operator or with ^-^. -- -- Note: projector a ^+^ projector b ^+^ ... is more efficiently -- written as projectors [a, b, ...] projector :: HasMetric v => DualSpace v -> HerMetric v projector' :: HasMetric v => v -> HerMetric' v -- | Efficient shortcut for the sumV of multiple projectors. projectors :: HasMetric v => [DualSpace v] -> HerMetric v projector's :: HasMetric v => [v] -> HerMetric' v euclideanMetric' :: (HasMetric v, InnerSpace v) => HerMetric v spanHilbertSubspace :: (HasMetric v, Scalar v ~ s, IsFreeSpace w, Scalar w ~ s) => HerMetric v -> [v] -> Option (Embedding (Linear s) w v) -- | Same as spanHilbertSubspace, but with the standard -- euclideanMetric (i.e., the basis vectors will be orthonormal -- in the usual sense, in both w and v). spanSubHilbertSpace :: (HasMetric v, InnerSpace v, Scalar v ~ s, IsFreeSpace w, Scalar w ~ s) => [v] -> Option (Embedding (Linear s) w v) -- | Class of spaces that directly represent a free vector space, i.e. that -- are simply n-fold products of the base field. This class -- basically contains 'ℝ', 'ℝ²', 'ℝ³' etc., in future also the complex -- and probably integral versions. class (FiniteDimensional v, KnownNat (FreeDimension v)) => IsFreeSpace v where identityMatrix = fromInversePair emb proj where emb@(DenseLinear i) = canonicalIdentityMatrix proj = DenseLinear i -- | Project a metric on each of the factors of a product space. This works -- by projecting the eigenvectors into both subspaces. factoriseMetric :: (HasMetric v, HasMetric w, Scalar v ~ ℝ, Scalar w ~ ℝ) => HerMetric (v, w) -> (HerMetric v, HerMetric w) factoriseMetric' :: (HasMetric v, HasMetric w, Scalar v ~ ℝ, Scalar w ~ ℝ) => HerMetric' (v, w) -> (HerMetric' v, HerMetric' w) productMetric :: (HasMetric v, HasMetric w, Scalar v ~ ℝ, Scalar w ~ ℝ) => HerMetric v -> HerMetric w -> HerMetric (v, w) productMetric' :: (HasMetric v, HasMetric w, Scalar v ~ ℝ, Scalar w ~ ℝ) => HerMetric' v -> HerMetric' w -> HerMetric' (v, w) tryMetricAsLength :: HerMetric ℝ -> Option ℝ -- | Unsafe version of tryMetricAsLength, only works reliable if the -- metric is strictly positive definite. metricAsLength :: HerMetric ℝ -> ℝ metricFromLength :: ℝ -> HerMetric ℝ metric'AsLength :: HerMetric' ℝ -> ℝ transformMetric :: (HasMetric v, HasMetric w, Scalar v ~ s, Scalar w ~ s) => Linear s w v -> HerMetric v -> HerMetric w transformMetric' :: (HasMetric v, HasMetric w, Scalar v ~ s, Scalar w ~ s) => Linear s v w -> HerMetric' v -> HerMetric' w -- | This does something vaguely like \s t -> (s⋅t)², but -- without actually requiring an inner product on the covectors. Used for -- calculating the superaffine term of multiplications in -- Differentiable categories. dualCoCoProduct :: (HasMetric v, HasMetric w, Scalar v ~ s, Scalar w ~ s) => Linear s w v -> Linear s w v -> HerMetric w -- | This doesn't really do anything at all, since HerMetric -- v is essentially a synonym for HerMetric -- (DualSpace v). dualiseMetric :: HasMetric v => HerMetric (DualSpace v) -> HerMetric' v dualiseMetric' :: HasMetric v => HerMetric' v -> HerMetric (DualSpace v) -- | The inverse mapping of a metric tensor. Since a metric maps from a -- space to its dual, the inverse maps from the dual into the -- (double-dual) space – i.e., it is a metric on the dual space. -- Deprecated: the singular case isn't properly handled. recipMetric :: HasMetric v => HerMetric' v -> HerMetric v recipMetric' :: HasMetric v => HerMetric v -> HerMetric' v safeRecipMetric :: HasMetric v => HerMetric' v -> Option (HerMetric v) safeRecipMetric' :: HasMetric v => HerMetric v -> Option (HerMetric' v) -- | The eigenbasis of a metric, with each eigenvector scaled to the square -- root of the eigenvalue. If the metric is not positive definite (i.e. -- if it has zero eigenvalues), then the eigenSpan will contain -- zero vectors. -- -- This constitutes, in a sense, a decomposition of a metric into a set -- of projector' vectors. If those are sumVed again (use -- projectors's for this), then the original metric is obtained. -- (This holds even for non-Hilbert/Banach spaces, although the concept -- of eigenbasis and “scaled length” doesn't really make sense there.) eigenSpan :: (HasMetric v, Scalar v ~ ℝ) => HerMetric' v -> [v] eigenSpan' :: (HasMetric v, Scalar v ~ ℝ) => HerMetric v -> [DualSpace v] -- | The reciprocal-space counterparts of the nonzero-EV eigenvectors, as -- can be obtained from eigenSpan. The systems of vectors/dual -- vectors behave as orthonormal groups WRT each other, i.e. for each -- f in eigenCoSpan m there will be exactly one -- v in eigenSpan m such that f.^v ≡ -- 1; the other f.^v pairings are zero. -- -- Furthermore, metric m f ≡ 1 for each f in the -- co-span, which might be seen as the actual defining characteristic of -- these span/co-span systems. eigenCoSpan :: (HasMetric v, Scalar v ~ ℝ) => HerMetric' v -> [DualSpace v] eigenCoSpan' :: (HasMetric v, Scalar v ~ ℝ) => HerMetric v -> [v] class HasEigenSystem m where type family EigenVector m :: * -- | Generalised combination of eigenSpan and eigenCoSpan; -- this will give a maximum spanning set of vector-covector pairs -- (f,v) such that f.^v ≡ 1 and metric m f ≡ -- 1, whereas all f and v' from different tuples -- are orthogonal. It also yields the kernel of singular metric, -- spanned by a set of stiefel-manifold points, i.e. vectors of -- unspecified length that correspond to the eigenvalue 0. -- -- You may also consider this as a factorisation of a linear -- operator 𝐴 : 𝑉 → 𝑉' into mappings 𝑅 : 𝑉 → ℝⁿ and -- 𝐿 : ℝⁿ → 𝑉' (or, equivalently because ℝⁿ is a Hilbert space, -- 𝑅' : ℝⁿ → V' and 𝐿' : V → ℝⁿ, which gives you an -- SVD-style inverse). eigenSystem :: HasEigenSystem m => m -> ([Stiefel1 (EigenVector m)], [(EigenVector m, DualSpace (EigenVector m))]) -- | Divide a vector by its own norm, according to metric, i.e. normalise -- it or “project to the metric's boundary”. metriNormalise :: (HasMetric v, Floating (Scalar v)) => HerMetric v -> v -> v metriNormalise' :: (HasMetric v, Floating (Scalar v)) => HerMetric' v -> DualSpace v -> DualSpace v metriScale' :: (HasMetric v, Floating (Scalar v)) => HerMetric' v -> DualSpace v -> DualSpace v -- | “Anti-normalise” a vector: multiply with its own norm, -- according to metric. metriScale :: (HasMetric v, Floating (Scalar v)) => HerMetric v -> v -> v volumeRatio :: HasMetric v => HerMetric v -> HerMetric v -> Scalar v euclideanRelativeMetricVolume :: (HasMetric v, InnerSpace v) => HerMetric v -> Scalar v -- | Transpose a linear operator. Contrary to popular belief, this does not -- just inverse the direction of mapping between the spaces, but also -- switch to their duals. adjoint :: (HasMetric v, HasMetric w, s ~ Scalar v, s ~ Scalar w) => (Linear s v w) -> Linear s (DualSpace w) (DualSpace v) extendMetric :: (HasMetric v, Scalar v ~ ℝ) => HerMetric v -> v -> HerMetric v applyLinMapMetric :: (HasMetric v, HasMetric w, Scalar v ~ ℝ, Scalar w ~ ℝ) => HerMetric (Linear ℝ v w) -> DualSpace v -> HerMetric w applyLinMapMetric' :: (HasMetric v, HasMetric w, Scalar v ~ ℝ, Scalar w ~ ℝ) => HerMetric' (Linear ℝ v w) -> v -> HerMetric' w imitateMetricSpanChange :: (HasMetric v, Scalar v ~ ℝ) => HerMetric v -> HerMetric' v -> Linear ℝ v v type HasMetric v = (HasMetric' v, HasMetric' (DualSpace v), DualSpace (DualSpace v) ~ v) -- | While the main purpose of this class is to express HerMetric, -- it's actually all about dual spaces. class (FiniteDimensional v, FiniteDimensional (DualSpace v), VectorSpace (DualSpace v), HasBasis (DualSpace v), MetricScalar (Scalar v), Scalar v ~ Scalar (DualSpace v)) => HasMetric' v where type family DualSpace v :: * DualSpace v = v basisInDual = bid where bid :: forall v. HasMetric' v => Tagged v (Basis v -> Basis (DualSpace v)) bid = Tagged $ bi >>> ib' where Tagged bi = basisIndex :: Tagged v (Basis v -> Int) Tagged ib' = indexBasis :: Tagged (DualSpace v) (Int -> Basis (DualSpace v)) -- | Apply a dual space vector (aka linear functional) to a vector. (<.>^) :: HasMetric' v => DualSpace v -> v -> Scalar v -- | Interpret a functional as a dual-space vector. Like linear, -- this assumes (completely unchecked) that the supplied function -- is linear. functional :: HasMetric' v => (v -> Scalar v) -> DualSpace v -- | While isomorphism between a space and its dual isn't generally -- canonical, the double-dual space should be canonically -- isomorphic in pretty much all relevant cases. Indeed, it is -- recommended that they are the very same type; this condition is -- enforced by the HasMetric constraint (which is recommended over -- using HasMetric' itself in signatures). doubleDual :: (HasMetric' v, HasMetric' (DualSpace v)) => v -> DualSpace (DualSpace v) doubleDual' :: (HasMetric' v, HasMetric' (DualSpace v)) => DualSpace (DualSpace v) -> v basisInDual :: HasMetric' v => Tagged v (Basis v -> Basis (DualSpace v)) -- | Simple flipped version of <.>^. (^<.>) :: HasMetric v => v -> DualSpace v -> Scalar v -- | Constraint that a space's scalars need to fulfill so it can be used -- for HerMetric. type MetricScalar s = (SmoothScalar s, Ord s) -- | Many linear algebra operations are best implemented via packed, dense -- Matrixes. For one thing, that makes common general vector -- operations quite efficient, in particular on high-dimensional spaces. -- More importantly, hmatrix offers linear facilities such as -- inverse and eigenbasis transformations, which aren't available in the -- vector-space library yet. But the classes from that library -- are strongly preferrable to plain matrices and arrays, conceptually. -- -- The FiniteDimensional class is used to convert between both -- representations. It would be nice not to have the requirement of -- finite dimension on HerMetric, but it's probably not feasible -- to get rid of it in forseeable time. -- -- Instead of the run-time dimension information, we would rather -- have a compile-time type Dimension v :: Nat, but type-level -- naturals are not mature enough yet. This will almost certainly change -- in the future. class (HasBasis v, HasTrie (Basis v), SmoothScalar (Scalar v)) => FiniteDimensional v where completeBasis = liftA2 (\ dim f -> f <$> [0 .. dim - 1]) dimension indexBasis completeBasisValues = defCBVs where defCBVs :: forall v. FiniteDimensional v => [v] defCBVs = basisValue <$> cb where Tagged cb = completeBasis :: Tagged v [Basis v] asPackedVector v = fromList $ snd <$> decompose v asPackedMatrix = defaultAsPackedMatrix where defaultAsPackedMatrix :: forall v w s. (FiniteDimensional v, FiniteDimensional w, s ~ Scalar v, s ~ Scalar w) => (v :-* w) -> Matrix s defaultAsPackedMatrix m = fromColumns $ asPackedVector . atBasis m <$> cb where (Tagged cb) = completeBasis :: Tagged v [Basis v] fromPackedVector v = result where result = recompose $ zip cb (toList v) cb = witness completeBasis result fromPackedMatrix = defaultFromPackedMatrix where defaultFromPackedMatrix :: forall v w s. (FiniteDimensional v, FiniteDimensional w, s ~ Scalar v, s ~ Scalar w) => Matrix s -> (v :-* w) defaultFromPackedMatrix m = linear $ fromPackedVector . app m . asPackedVector dimension :: FiniteDimensional v => Tagged v Int basisIndex :: FiniteDimensional v => Tagged v (Basis v -> Int) -- | Index must be in [0 .. dimension-1], otherwise this is -- undefined. indexBasis :: FiniteDimensional v => Tagged v (Int -> Basis v) completeBasis :: FiniteDimensional v => Tagged v [Basis v] completeBasisValues :: FiniteDimensional v => [v] asPackedVector :: FiniteDimensional v => v -> Vector (Scalar v) asPackedMatrix :: (FiniteDimensional v, FiniteDimensional w, Scalar w ~ Scalar v) => (v :-* w) -> Matrix (Scalar v) fromPackedVector :: FiniteDimensional v => Vector (Scalar v) -> v fromPackedMatrix :: (FiniteDimensional v, FiniteDimensional w, Scalar w ~ Scalar v) => Matrix (Scalar v) -> (v :-* w) -- | The n-th Stiefel manifold is the space of all possible -- configurations of n orthonormal vectors. In the case n = -- 1, simply the subspace of normalised vectors, i.e. equivalent to the -- UnitSphere. Even so, it strictly speaking requires the -- containing space to be at least metric (if not Hilbert); we would -- however like to be able to use this concept also in spaces with no -- inner product, therefore we define this space not as normalised -- vectors, but rather as all vectors modulo scaling by positive factors. newtype Stiefel1 v Stiefel1 :: DualSpace v -> Stiefel1 v [getStiefel1N] :: Stiefel1 v -> DualSpace v linMapAsTensProd :: (FiniteDimensional v, FiniteDimensional w, Scalar v ~ Scalar w) => v :-* w -> DualSpace v ⊗ w linMapFromTensProd :: (FiniteDimensional v, FiniteDimensional w, Scalar v ~ Scalar w) => DualSpace v ⊗ w -> v :-* w covariance :: (HasMetric v, HasMetric w, Scalar v ~ ℝ, Scalar w ~ ℝ) => HerMetric' (v, w) -> Option (Linear ℝ v w) outerProducts :: (HasMetric v, FiniteDimensional w, Scalar v ~ s, Scalar w ~ s) => [(w, DualSpace v)] -> Linear s v w orthogonalComplementSpan :: (HasMetric v, Scalar v ~ ℝ) => [Stiefel1 (DualSpace v)] -> [Stiefel1 v] instance Data.LinearMap.HerMetric.HasMetric v => Data.AdditiveGroup.AdditiveGroup (Data.LinearMap.HerMetric.HerMetric v) instance Data.LinearMap.HerMetric.HasMetric v => Data.VectorSpace.VectorSpace (Data.LinearMap.HerMetric.HerMetric v) instance Data.LinearMap.HerMetric.HasMetric v => Data.AdditiveGroup.AdditiveGroup (Data.LinearMap.HerMetric.HerMetric' v) instance Data.LinearMap.HerMetric.HasMetric v => Data.VectorSpace.VectorSpace (Data.LinearMap.HerMetric.HerMetric' v) instance (Data.LinearMap.HerMetric.HasMetric v, Data.VectorSpace.Scalar v ~ Data.Manifold.Types.Primitive.ℝ) => Data.LinearMap.HerMetric.HasEigenSystem (Data.LinearMap.HerMetric.HerMetric' v) instance (Data.LinearMap.HerMetric.HasMetric v, Data.VectorSpace.Scalar v ~ Data.Manifold.Types.Primitive.ℝ) => Data.LinearMap.HerMetric.HasEigenSystem (Data.LinearMap.HerMetric.HerMetric v) instance (Data.LinearMap.HerMetric.HasMetric v, Data.VectorSpace.Scalar v ~ Data.Manifold.Types.Primitive.ℝ) => Data.LinearMap.HerMetric.HasEigenSystem (Data.LinearMap.HerMetric.HerMetric' v, Data.LinearMap.HerMetric.HerMetric' v) instance (Data.LinearMap.HerMetric.HasMetric v, Data.VectorSpace.Scalar v ~ Data.Manifold.Types.Primitive.ℝ) => Data.LinearMap.HerMetric.HasEigenSystem (Data.LinearMap.HerMetric.HerMetric v, Data.LinearMap.HerMetric.HerMetric v) instance Data.LinearMap.HerMetric.MetricScalar k => Data.LinearMap.HerMetric.HasMetric' (Data.Manifold.Types.Primitive.ZeroDim k) instance Data.LinearMap.HerMetric.HasMetric' GHC.Types.Double instance (Data.LinearMap.HerMetric.HasMetric v, Data.LinearMap.HerMetric.HasMetric w, Data.VectorSpace.Scalar v ~ Data.VectorSpace.Scalar w) => Data.LinearMap.HerMetric.HasMetric' (v, w) instance (Data.VectorSpace.FiniteDimensional.SmoothScalar s, GHC.Classes.Ord s, Data.CoNat.KnownNat n) => Data.LinearMap.HerMetric.HasMetric' (s Data.CoNat.^ n) instance (Data.LinearMap.HerMetric.HasMetric v, s ~ Data.VectorSpace.Scalar v) => Data.LinearMap.HerMetric.HasMetric' (Data.VectorSpace.FiniteDimensional.FinVecArrRep t v s) instance (Data.LinearMap.HerMetric.HasMetric v, Data.LinearMap.HerMetric.HasMetric w, s ~ Data.VectorSpace.Scalar v, s ~ Data.VectorSpace.Scalar w) => Data.LinearMap.HerMetric.HasMetric' (Data.LinearMap.Category.Linear s v w) instance (Data.LinearMap.HerMetric.HasMetric v, v ~ Data.LinearMap.HerMetric.DualSpace v, GHC.Num.Num (Data.VectorSpace.Scalar v)) => GHC.Num.Num (Data.LinearMap.HerMetric.HerMetric v) instance (Data.LinearMap.HerMetric.HasMetric v, v ~ Data.VectorSpace.Scalar v, v ~ Data.LinearMap.HerMetric.DualSpace v, GHC.Real.Fractional v) => GHC.Real.Fractional (Data.LinearMap.HerMetric.HerMetric v) instance (Data.LinearMap.HerMetric.HasMetric v, v ~ Data.VectorSpace.Scalar v, v ~ Data.LinearMap.HerMetric.DualSpace v, GHC.Float.Floating v) => GHC.Float.Floating (Data.LinearMap.HerMetric.HerMetric v) instance (Data.LinearMap.HerMetric.HasMetric v, Data.VectorSpace.Scalar v ~ GHC.Types.Double, GHC.Show.Show (Data.LinearMap.HerMetric.DualSpace v)) => GHC.Show.Show (Data.LinearMap.HerMetric.HerMetric v) instance (Data.LinearMap.HerMetric.HasMetric v, Data.VectorSpace.Scalar v ~ GHC.Types.Double, GHC.Show.Show v) => GHC.Show.Show (Data.LinearMap.HerMetric.HerMetric' v) instance (Data.LinearMap.HerMetric.HasMetric v, Data.VectorSpace.FiniteDimensional.FiniteDimensional w, GHC.Show.Show (Data.LinearMap.HerMetric.DualSpace v), GHC.Show.Show w, Data.VectorSpace.Scalar v ~ s, Data.VectorSpace.Scalar w ~ s) => GHC.Show.Show (Data.LinearMap.Category.Linear s v w) -- | 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, LinearManifold (Needle m), Interior m ~ m) => Manifold m class (AdditiveGroup (Needle x), Interior (Interior x) ~ Interior x) => Semimanifold x where type family Needle x :: * type family Interior x :: * Interior x = x (.+~^) = addvp where addvp :: forall x. Semimanifold x => Interior x -> Needle x -> x addvp p = fromInterior . tp p where (Tagged tp) = translateP :: Tagged x (Interior x -> Needle x -> Interior x) fromInterior p = p .+~^ zeroV p .-~^ v = p .+~^ negateV v -- | 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 -> Option (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 -- | 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 = DualSpace (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, Semimanifold (Interior x), Needle (Interior x) ~ Needle x, Interior (Interior x) ~ Interior x) => PseudoAffine x where p .-~. q = return $ p .-~! q p .-~! q = case p .-~. q of { Option (Just v) -> v } -- | 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 -> Interior x -> Option (Needle x) -- | Unsafe version of .-~.. If the two points lie in disjoint -- regions, the behaviour is undefined. (.-~!) :: PseudoAffine x => x -> Interior x -> Needle x -- | The word “metric” is used in the sense as in general relativity. Cf. -- HerMetric. type Metric x = HerMetric (Needle x) type Metric' x = HerMetric' (Needle x) euclideanMetric :: EuclidSpace x => proxy x -> Metric 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 -- | The RealFloat class plus manifold constraints. type RealDimension r = (PseudoAffine r, Interior r ~ r, Needle r ~ r, HasMetric r, DualSpace r ~ r, Scalar r ~ r, RealFloat r, r ~ ℝ) -- | The AffineSpace class plus manifold constraints. type AffineManifold m = (PseudoAffine m, Interior m ~ m, AffineSpace m, Needle m ~ Diff m, LinearManifold' (Diff m)) -- | Basically just an “updated” version of the VectorSpace class. -- Every vector space is a manifold, this constraint makes it explicit. -- -- (Actually, LinearManifold is stronger than VectorSpace -- at the moment, since HasMetric requires -- FiniteDimensional. This might be lifted in the future.) type LinearManifold x = (AffineManifold x, Needle x ~ x, HasMetric x) -- | Require some constraint on a manifold, and also fix the type of the -- manifold's underlying field. For example, WithField ℝ -- HilbertSpace 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)) -- | A Hilbert space is a complete inner product space. Being a -- vector space, it is also a manifold. -- -- (Stricly speaking, that doesn't have much to do with the completeness -- criterion; but since Manifolds are at the moment confined to -- finite dimension, they are in fact (trivially) complete.) type HilbertSpace x = (LinearManifold x, InnerSpace x, Interior x ~ x, Needle x ~ x, DualSpace x ~ x, Floating (Scalar x)) -- | An euclidean space is a real affine space whose tangent space is a -- Hilbert space. type EuclidSpace x = (AffineManifold x, InnerSpace (Diff x), DualSpace (Diff x) ~ Diff x, Floating (Scalar (Diff x))) type LocallyScalable s x = (PseudoAffine x, HasMetric (Needle x), s ~ Scalar (Needle x)) type LocalLinear x y = Linear (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 :: Manifold x => Interior x -> Interior x -> Option (Scalar (Needle x) -> x) -- | Like palerp, but actually restricted to the interval between -- the points, with a signature like geodesicBetween rather than -- alerp. palerpB :: WithField ℝ Manifold x => Interior x -> Interior x -> Option (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 (PseudoAffine x, PseudoAffine ξ, Scalar (Needle x) ~ Scalar (Needle ξ)) => LocallyCoercible x ξ -- | Must be compatible with the canonical isomorphism on the tangent -- spaces, i.e. locallyTrivialDiffeomorphism (p .+~^ -- fromPackedVector v) ≡ locallyTrivialDiffeomorphism p .+~^ -- fromPackedVector v locallyTrivialDiffeomorphism :: LocallyCoercible x ξ => x -> ξ class ImpliesMetric s where type family MetricRequirement s x :: Constraint MetricRequirement s x = Semimanifold x inferMetric = safeRecipMetric <=< inferMetric' inferMetric' = safeRecipMetric' <=< inferMetric inferMetric :: (ImpliesMetric s, MetricRequirement s x, HasMetric (Needle x)) => s x -> Option (Metric x) inferMetric' :: (ImpliesMetric s, MetricRequirement s x, HasMetric (Needle x)) => s x -> Option (Metric' x) instance (Data.Manifold.PseudoAffine.PseudoAffine m, Data.Manifold.PseudoAffine.LinearManifold (Data.Manifold.PseudoAffine.Needle m), Data.Manifold.PseudoAffine.Interior m ~ m) => Data.Manifold.PseudoAffine.Manifold m instance Data.Manifold.PseudoAffine.LocallyCoercible Data.Manifold.Types.Primitive.ℝ Data.Manifold.Types.Primitive.ℝ instance Data.Manifold.PseudoAffine.LocallyCoercible (Data.Manifold.Types.Primitive.ℝ, Data.Manifold.Types.Primitive.ℝ) (Data.Manifold.Types.Primitive.ℝ, Data.Manifold.Types.Primitive.ℝ) instance Data.Manifold.PseudoAffine.LocallyCoercible (Data.Manifold.Types.Primitive.ℝ, (Data.Manifold.Types.Primitive.ℝ, Data.Manifold.Types.Primitive.ℝ)) (Data.Manifold.Types.Primitive.ℝ, (Data.Manifold.Types.Primitive.ℝ, Data.Manifold.Types.Primitive.ℝ)) instance Data.Manifold.PseudoAffine.LocallyCoercible ((Data.Manifold.Types.Primitive.ℝ, Data.Manifold.Types.Primitive.ℝ), Data.Manifold.Types.Primitive.ℝ) ((Data.Manifold.Types.Primitive.ℝ, Data.Manifold.Types.Primitive.ℝ), Data.Manifold.Types.Primitive.ℝ) instance Data.Manifold.PseudoAffine.Semimanifold GHC.Types.Double instance Data.Manifold.PseudoAffine.PseudoAffine GHC.Types.Double instance Data.Manifold.PseudoAffine.Semimanifold GHC.Real.Rational instance Data.Manifold.PseudoAffine.PseudoAffine GHC.Real.Rational instance Data.VectorSpace.FiniteDimensional.SmoothScalar s => Data.Manifold.PseudoAffine.Semimanifold (Data.VectorSpace.FiniteDimensional.FinVecArrRep t b s) instance Data.VectorSpace.FiniteDimensional.SmoothScalar s => Data.Manifold.PseudoAffine.PseudoAffine (Data.VectorSpace.FiniteDimensional.FinVecArrRep t b s) instance Data.VectorSpace.FiniteDimensional.SmoothScalar s => Data.Manifold.PseudoAffine.LocallyCoercible (Data.VectorSpace.FiniteDimensional.FinVecArrRep t b s) (Data.VectorSpace.FiniteDimensional.FinVecArrRep t b s) instance (Data.VectorSpace.FiniteDimensional.SmoothScalar s, Data.Manifold.PseudoAffine.LinearManifold b, Data.VectorSpace.Scalar b ~ s) => Data.Manifold.PseudoAffine.LocallyCoercible (Data.VectorSpace.FiniteDimensional.FinVecArrRep t b s) b instance (Data.VectorSpace.FiniteDimensional.SmoothScalar s, Data.Manifold.PseudoAffine.LinearManifold b, Data.VectorSpace.Scalar b ~ s) => Data.Manifold.PseudoAffine.LocallyCoercible b (Data.VectorSpace.FiniteDimensional.FinVecArrRep t b s) instance Data.Manifold.PseudoAffine.Semimanifold (Data.Manifold.Types.Primitive.ZeroDim k) instance Data.Manifold.PseudoAffine.PseudoAffine (Data.Manifold.Types.Primitive.ZeroDim k) instance (Data.Manifold.PseudoAffine.Semimanifold a, Data.Manifold.PseudoAffine.Semimanifold b) => Data.Manifold.PseudoAffine.Semimanifold (a, b) instance (Data.Manifold.PseudoAffine.PseudoAffine a, Data.Manifold.PseudoAffine.PseudoAffine b) => Data.Manifold.PseudoAffine.PseudoAffine (a, b) instance (Data.Manifold.PseudoAffine.PseudoAffine a, Data.Manifold.PseudoAffine.PseudoAffine b, Data.Manifold.PseudoAffine.PseudoAffine c) => Data.Manifold.PseudoAffine.LocallyCoercible (a, (b, c)) ((a, b), c) instance (Data.Manifold.PseudoAffine.PseudoAffine a, Data.Manifold.PseudoAffine.PseudoAffine b, Data.Manifold.PseudoAffine.PseudoAffine c) => Data.Manifold.PseudoAffine.LocallyCoercible ((a, b), c) (a, (b, c)) instance (Data.Manifold.PseudoAffine.Semimanifold a, Data.Manifold.PseudoAffine.Semimanifold b, Data.Manifold.PseudoAffine.Semimanifold c) => Data.Manifold.PseudoAffine.Semimanifold (a, b, c) instance (Data.Manifold.PseudoAffine.PseudoAffine a, Data.Manifold.PseudoAffine.PseudoAffine b, Data.Manifold.PseudoAffine.PseudoAffine c) => Data.Manifold.PseudoAffine.PseudoAffine (a, b, c) instance (Data.Manifold.PseudoAffine.PseudoAffine a, Data.Manifold.PseudoAffine.PseudoAffine b, Data.Manifold.PseudoAffine.PseudoAffine c) => Data.Manifold.PseudoAffine.LocallyCoercible (a, b, c) ((a, b), c) instance (Data.Manifold.PseudoAffine.PseudoAffine a, Data.Manifold.PseudoAffine.PseudoAffine b, Data.Manifold.PseudoAffine.PseudoAffine c) => Data.Manifold.PseudoAffine.LocallyCoercible (a, b, c) (a, (b, c)) instance (Data.Manifold.PseudoAffine.PseudoAffine a, Data.Manifold.PseudoAffine.PseudoAffine b, Data.Manifold.PseudoAffine.PseudoAffine c) => Data.Manifold.PseudoAffine.LocallyCoercible ((a, b), c) (a, b, c) instance (Data.Manifold.PseudoAffine.PseudoAffine a, Data.Manifold.PseudoAffine.PseudoAffine b, Data.Manifold.PseudoAffine.PseudoAffine c) => Data.Manifold.PseudoAffine.LocallyCoercible (a, (b, c)) (a, b, c) instance (Data.LinearMap.HerMetric.MetricScalar a, Data.CoNat.KnownNat n) => Data.Manifold.PseudoAffine.Semimanifold (Data.CoNat.FreeVect n a) instance (Data.LinearMap.HerMetric.MetricScalar a, Data.CoNat.KnownNat n) => Data.Manifold.PseudoAffine.PseudoAffine (Data.CoNat.FreeVect n a) instance Data.Manifold.PseudoAffine.LocallyCoercible Data.Manifold.Types.Primitive.ℝ (Data.Manifold.Types.Primitive.ℝ Data.CoNat.^ 'Data.CoNat.S 'Data.CoNat.Z) instance Data.Manifold.PseudoAffine.LocallyCoercible (Data.Manifold.Types.Primitive.ℝ Data.CoNat.^ 'Data.CoNat.S 'Data.CoNat.Z) Data.Manifold.Types.Primitive.ℝ instance (Data.LinearMap.HerMetric.HasMetric a, Data.VectorSpace.FiniteDimensional.FiniteDimensional b, Data.VectorSpace.Scalar a ~ Data.VectorSpace.Scalar b) => Data.Manifold.PseudoAffine.Semimanifold (a Data.Manifold.Types.Primitive.⊗ b) instance (Data.LinearMap.HerMetric.HasMetric a, Data.VectorSpace.FiniteDimensional.FiniteDimensional b, Data.VectorSpace.Scalar a ~ Data.VectorSpace.Scalar b) => Data.Manifold.PseudoAffine.PseudoAffine (a Data.Manifold.Types.Primitive.⊗ b) instance (Data.LinearMap.HerMetric.HasMetric a, Data.VectorSpace.FiniteDimensional.FiniteDimensional b, Data.VectorSpace.Scalar a ~ Data.VectorSpace.Scalar b) => Data.Manifold.PseudoAffine.Semimanifold (a Data.LinearMap.:-* b) instance (Data.LinearMap.HerMetric.HasMetric a, Data.VectorSpace.FiniteDimensional.FiniteDimensional b, Data.VectorSpace.Scalar a ~ Data.VectorSpace.Scalar b) => Data.Manifold.PseudoAffine.PseudoAffine (a Data.LinearMap.:-* b) instance (Data.LinearMap.HerMetric.HasMetric a, Data.VectorSpace.FiniteDimensional.FiniteDimensional b, Data.VectorSpace.Scalar a ~ s, Data.VectorSpace.Scalar b ~ s) => Data.Manifold.PseudoAffine.Semimanifold (Data.LinearMap.Category.Linear s a b) instance (Data.LinearMap.HerMetric.HasMetric a, Data.VectorSpace.FiniteDimensional.FiniteDimensional b, Data.VectorSpace.Scalar a ~ s, Data.VectorSpace.Scalar b ~ s) => Data.Manifold.PseudoAffine.PseudoAffine (Data.LinearMap.Category.Linear s a b) instance Data.Manifold.PseudoAffine.Semimanifold Data.Manifold.Types.Primitive.S⁰ instance Data.Manifold.PseudoAffine.PseudoAffine Data.Manifold.Types.Primitive.S⁰ instance Data.Manifold.PseudoAffine.Semimanifold Data.Manifold.Types.Primitive.S¹ instance Data.Manifold.PseudoAffine.PseudoAffine Data.Manifold.Types.Primitive.S¹ instance Data.Manifold.PseudoAffine.Semimanifold Data.Manifold.Types.Primitive.D¹ instance Data.Manifold.PseudoAffine.PseudoAffine Data.Manifold.Types.Primitive.D¹ instance Data.Manifold.PseudoAffine.Semimanifold Data.Manifold.Types.Primitive.S² instance Data.Manifold.PseudoAffine.PseudoAffine Data.Manifold.Types.Primitive.S² instance Data.Manifold.PseudoAffine.Semimanifold Data.Manifold.Types.Primitive.ℝP² instance Data.Manifold.PseudoAffine.PseudoAffine Data.Manifold.Types.Primitive.ℝP² instance Data.Manifold.PseudoAffine.ImpliesMetric Data.LinearMap.HerMetric.HerMetric instance Data.Manifold.PseudoAffine.ImpliesMetric Data.LinearMap.HerMetric.HerMetric' module Data.SimplicialComplex -- | An n-simplex is a connection of n+1 points in a simply -- connected region of a manifold. data Simplex :: Nat -> * -> * ZS :: !x -> Simplex Z x (:<|) :: !x -> !(Simplex n x) -> Simplex (S n) x -- | Use this together with :<| to easily build simplices, like -- you might construct lists. E.g. (0,0) :<| (1,0) -- .<. (0,1) :: Simplex Two ℝ². (.<.) :: x -> x -> Simplex One x makeSimplex :: KnownNat n => x ^ S n -> Simplex n x makeSimplex' :: KnownNat n => [x] -> Option (Simplex n x) simplexVertices :: Simplex n x -> x ^ S n simplexVertices' :: Simplex n x -> [x] -- | An n-dimensional abstract simplicial complex is a -- collection of n-simplices which are “glued together” in some -- way. The preferred way to construct such complexes is to run a -- TriangT builder. data Triangulation (n :: Nat) (x :: *) -- | Consider a single simplex as a simplicial complex, consisting only of -- this simplex and its faces. singleSimplex :: KnownNat n => Simplex n x -> Triangulation n x -- | A “conservative” state monad containing a Triangulation. It can -- be extended by new simplices, which can then be indexed using -- SimplexIT. The universally-quantified t argument -- ensures you can't index simplices that don't actually exist in this -- triangulation. data TriangT t n x m y evalTriangT :: (KnownNat n, HaskMonad m) => (forall t. TriangT t n x m y) -> m y runTriangT :: (forall t. TriangT t n x m y) -> Triangulation n x -> m (y, Triangulation n x) doTriangT :: KnownNat n => (forall t. TriangT t n x m y) -> m (y, Triangulation n x) getTriang :: (HaskMonad m, KnownNat k, KnownNat n) => TriangT t n x m (Option (Triangulation k x)) data SimplexIT (t :: *) (n :: Nat) (x :: *) simplexITList :: (HaskMonad m, KnownNat k, KnownNat n) => TriangT t n x m [SimplexIT t k x] lookSimplex :: (HaskMonad m, KnownNat k, KnownNat n) => SimplexIT t k x -> TriangT t n x m (Simplex k x) -- | Reference the k-faces of a given simplex in a triangulation. lookSplxFacesIT :: (HaskMonad m, KnownNat k, KnownNat n) => SimplexIT t (S k) x -> TriangT t n x m (SimplexIT t k x ^ S (S k)) lookSupersimplicesIT :: (HaskMonad m, KnownNat k, KnownNat j, KnownNat n) => SimplexIT t k x -> TriangT t n x m [SimplexIT t j x] -- | A unique (for the given dimension) ID of a triagulation's simplex. It -- is the index where that simplex can be found in the -- simplexITList. tgetSimplexIT :: SimplexIT t n x -> Int lookVertexIT :: (HaskMonad m, KnownNat n) => SimplexIT t Z x -> TriangT t n x m x lookSplxVerticesIT :: (HaskMonad m, KnownNat k, KnownNat n) => SimplexIT t k x -> TriangT t n x m (SimplexIT t Z x ^ S k) sharedBoundary :: (HaskMonad m, KnownNat k, KnownNat n) => SimplexIT t (S k) x -> SimplexIT t (S k) x -> TriangT t n x m (Option (SimplexIT t k x)) distinctSimplices :: (HaskMonad m, KnownNat k, KnownNat n) => SimplexIT t (S k) x -> SimplexIT t (S k) x -> TriangT t n x m (Option (NeighbouringSimplices t k x)) type NeighbouringSimplices t n x = ((SimplexIT t Z x, SimplexIT t Z x), SimplexIT t n x) -- | Import an entire triangulation, as disjoint from everything already in -- the monad. disjointTriangulation :: (KnownNat n, HaskMonad m) => Triangulation n x -> TriangT t n x m [SimplexIT t n x] disjointSimplex :: (KnownNat n, HaskMonad m) => Simplex n x -> TriangT t n x m (SimplexIT t n x) -- | Import a triangulation like with disjointTriangulation, -- together with references to some of its subsimplices. mixinTriangulation :: (KnownNat n, KnownNat k, HaskMonad m, Functor f (->) (->)) => (forall s. TriangT s n x m (f (SimplexIT s k x))) -> TriangT t n x m (f (SimplexIT t k x)) introVertToTriang :: (HaskMonad m, KnownNat n) => x -> [SimplexIT t n x] -> TriangT t (S n) x m (SimplexIT t Z x) webinateTriang :: (HaskMonad m, KnownNat n) => SimplexIT t Z x -> SimplexIT t n x -> TriangT t (S n) x m (SimplexIT t (S n) x) type HaskMonad m = (Applicative m, Monad m) liftInTriangT :: (HaskMonad m, MonadTrans μ) => TriangT t n x m y -> TriangT t n x (μ m) y unliftInTriangT :: (HaskMonad m, MonadTrans μ) => (forall m' a. μ m a -> m a) -> TriangT t n x (μ m) y -> TriangT t n x m y -- | Mainly intended to be used as a data kind. Of course, we'd rather use -- GHC.TypeLits naturals, but they aren't mature enough yet. data Nat -- | Type-level zero of kind Nat. type Zero = Z type One = S Zero type Two = S One type Three = S Two type Succ = S instance GHC.Show.Show (Data.SimplicialComplex.SimplexIT t n x) instance GHC.Classes.Ord (Data.SimplicialComplex.SimplexIT t n x) instance GHC.Classes.Eq (Data.SimplicialComplex.SimplexIT t n x) instance GHC.Base.Functor m => GHC.Base.Functor (Data.SimplicialComplex.TriangT t n x m) instance GHC.Show.Show x => GHC.Show.Show (Data.SimplicialComplex.Simplex n x) instance GHC.Show.Show x => GHC.Show.Show (Data.SimplicialComplex.Triangulation n x) instance GHC.Base.Functor (Data.SimplicialComplex.Simplex n) instance GHC.Base.Functor (Data.SimplicialComplex.Triangulation n) instance Data.CoNat.KnownNat n => Data.Semigroup.Semigroup (Data.SimplicialComplex.Triangulation n x) instance Data.CoNat.KnownNat n => GHC.Base.Monoid (Data.SimplicialComplex.Triangulation n x) instance (GHC.Base.Functor m, Control.Monad.Constrained.Monad m (->)) => GHC.Base.Applicative (Data.SimplicialComplex.TriangT t n x m) instance (GHC.Base.Functor m, Control.Monad.Constrained.Monad m (->)) => GHC.Base.Monad (Data.SimplicialComplex.TriangT t n x m) instance Control.Monad.Trans.Class.MonadTrans (Data.SimplicialComplex.TriangT t n x) 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) => RWDfblFuncValue n c a -> RWDfblFuncValue n c b -> RWDfblFuncValue n c b -- | 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) => RWDfblFuncValue n a n -> RWDfblFuncValue n a n -> RWDfblFuncValue n a n -- | Return the RHS, if it is greater than the LHS. (?<) :: (RealDimension n, LocallyScalable n a) => RWDfblFuncValue n a n -> RWDfblFuncValue n a n -> RWDfblFuncValue n a n -- | 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) => RWDfblFuncValue n a b -> RWDfblFuncValue n a b -> RWDfblFuncValue n a b -- | 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 => Int -> ℝInterval -> (RieMetric ℝ, RieMetric y) -> (Differentiable ℝ ℝ y) -> [(ℝ, y)] discretisePathSegs :: WithField ℝ Manifold 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 ℝ ℝ ℝ -> ℝ -> Option ((ℝ, ℝ), ℝ -> Option ℝ) intervalImages :: Int -> (RieMetric ℝ, RieMetric ℝ) -> RWDiffable ℝ ℝ ℝ -> ([(ℝInterval, ℝInterval)], [(ℝInterval, ℝInterval)]) instance Data.LinearMap.HerMetric.MetricScalar s => Control.Category.Constrained.Category (Data.Function.Differentiable.Data.Differentiable s) instance Data.Manifold.PseudoAffine.RealDimension s => Control.Arrow.Constrained.EnhancedCat (->) (Data.Function.Differentiable.Data.Differentiable s) instance Data.LinearMap.HerMetric.MetricScalar s => Control.Category.Constrained.Cartesian (Data.Function.Differentiable.Data.Differentiable s) instance Data.LinearMap.HerMetric.MetricScalar s => Control.Arrow.Constrained.Morphism (Data.Function.Differentiable.Data.Differentiable s) instance Data.LinearMap.HerMetric.MetricScalar s => Control.Arrow.Constrained.PreArrow (Data.Function.Differentiable.Data.Differentiable s) instance Data.LinearMap.HerMetric.MetricScalar s => Control.Arrow.Constrained.WellPointed (Data.Function.Differentiable.Data.Differentiable s) instance Data.LinearMap.HerMetric.MetricScalar s => Control.Category.Constrained.HasAgent (Data.Function.Differentiable.Data.Differentiable s) instance Data.LinearMap.HerMetric.MetricScalar s => Control.Arrow.Constrained.CartesianAgent (Data.Function.Differentiable.Data.Differentiable s) instance Data.LinearMap.HerMetric.MetricScalar s => Control.Arrow.Constrained.PointAgent (Data.Function.Differentiable.DfblFuncValue s) (Data.Function.Differentiable.Data.Differentiable s) a x instance (Data.Manifold.PseudoAffine.WithField s Data.Manifold.PseudoAffine.LinearManifold v, Data.Manifold.PseudoAffine.LocallyScalable s a, GHC.Float.Floating s) => Data.AdditiveGroup.AdditiveGroup (Data.Function.Differentiable.DfblFuncValue s a v) instance (Data.Manifold.PseudoAffine.RealDimension n, Data.Manifold.PseudoAffine.LocallyScalable n a) => GHC.Num.Num (Data.Function.Differentiable.DfblFuncValue n a n) instance Data.Manifold.PseudoAffine.RealDimension s => Control.Category.Constrained.Category (Data.Function.Differentiable.Data.RWDiffable s) instance Data.Manifold.PseudoAffine.RealDimension s => Control.Arrow.Constrained.EnhancedCat (Data.Function.Differentiable.Data.RWDiffable s) (Data.Function.Differentiable.Data.Differentiable s) instance Data.Manifold.PseudoAffine.RealDimension s => Control.Category.Constrained.Cartesian (Data.Function.Differentiable.Data.RWDiffable s) instance Data.Manifold.PseudoAffine.RealDimension s => Control.Arrow.Constrained.Morphism (Data.Function.Differentiable.Data.RWDiffable s) instance Data.Manifold.PseudoAffine.RealDimension s => Control.Arrow.Constrained.PreArrow (Data.Function.Differentiable.Data.RWDiffable s) instance Data.Manifold.PseudoAffine.RealDimension s => Control.Arrow.Constrained.WellPointed (Data.Function.Differentiable.Data.RWDiffable s) instance Data.Manifold.PseudoAffine.RealDimension s => Control.Category.Constrained.HasAgent (Data.Function.Differentiable.Data.RWDiffable s) instance Data.Manifold.PseudoAffine.RealDimension s => Control.Arrow.Constrained.CartesianAgent (Data.Function.Differentiable.Data.RWDiffable s) instance Data.Manifold.PseudoAffine.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.EuclidSpace v, Data.AdditiveGroup.AdditiveGroup v, v ~ Data.Manifold.PseudoAffine.Needle (Data.Manifold.PseudoAffine.Interior (Data.Manifold.PseudoAffine.Needle v)), Data.Manifold.PseudoAffine.LocallyScalable s a, Data.Manifold.PseudoAffine.RealDimension s) => Data.AdditiveGroup.AdditiveGroup (Data.Function.Differentiable.RWDfblFuncValue s a v) instance (Data.Manifold.PseudoAffine.RealDimension n, Data.Manifold.PseudoAffine.LocallyScalable n a) => GHC.Num.Num (Data.Function.Differentiable.RWDfblFuncValue n a n) instance (Data.Manifold.PseudoAffine.RealDimension n, Data.Manifold.PseudoAffine.LocallyScalable n a) => GHC.Real.Fractional (Data.Function.Differentiable.RWDfblFuncValue n a n) instance (Data.Manifold.PseudoAffine.RealDimension n, Data.Manifold.PseudoAffine.LocallyScalable n a) => GHC.Float.Floating (Data.Function.Differentiable.RWDfblFuncValue n a n) -- | 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 Projective1 = ℝP¹ type Projective2 = ℝP² type Disk1 = D¹ type Disk2 = D² type Cone = CD¹ type OpenCone = Cℝay -- | A single point. Can be considered a zero-dimensional vector space, WRT -- any scalar. data ZeroDim k Origin :: ZeroDim k type ℝ⁰ = ZeroDim ℝ type ℝ = Double type ℝ² = (ℝ, ℝ) type ℝ³ = (ℝ², ℝ) -- | The n-th Stiefel manifold is the space of all possible -- configurations of n orthonormal vectors. In the case n = -- 1, simply the subspace of normalised vectors, i.e. equivalent to the -- UnitSphere. Even so, it strictly speaking requires the -- containing space to be at least metric (if not Hilbert); we would -- however like to be able to use this concept also in spaces with no -- inner product, therefore we define this space not as normalised -- vectors, but rather as all vectors modulo scaling by positive factors. data Stiefel1 v stiefel1Project :: LinearManifold v => DualSpace v -> Stiefel1 v stiefel1Embed :: HilbertSpace v => Stiefel1 v -> v class (PseudoAffine v, InnerSpace v, NaturallyEmbedded (UnitSphere v) (DualSpace v)) => HasUnitSphere v where type family UnitSphere v :: * stiefel = Stiefel1 . embed unstiefel = coEmbed . getStiefel1N 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¹ :: Double -> S¹ -- | Must be in range [-π, π[. [φParamS¹] :: S¹ -> Double -- | The ordinary unit sphere. data S² S² :: !Double -> !Double -> S² -- | Range [0, π[. [ϑParamS²] :: S² -> !Double -- | Range [-π, π[. [φParamS²] :: S² -> !Double type ℝP¹ = S¹ -- | The two-dimensional real projective space, implemented as a unit disk -- with opposing points on the rim glued together. data ℝP² ℝP² :: !Double -> !Double -> ℝP² -- | Range [0, 1]. [rParamℝP²] :: ℝP² -> !Double -- | Range [-π, π[. [φParamℝP²] :: ℝP² -> !Double -- | 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 'S¹', -- but not in the the obvious, “flat” way. (And not at all, despite the -- identical ADT definition, to the projective space 'ℝP²'!) data D² D² :: !Double -> !Double -> D² -- | Range [0, 1]. [rParamD²] :: D² -> !Double -- | Range [-π, π[. [φParamD²] :: D² -> !Double -- | 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 'D¹' 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 'D²') in the special case x = 'S¹'. 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 :: WithField ℝ Manifold 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) fathomCutDistance :: WithField ℝ Manifold x => Cutplane x -> HerMetric' (Needle x) -> x -> Option ℝ sideOfCut :: WithField ℝ Manifold x => Cutplane x -> x -> Option S⁰ cutPosBetween :: WithField ℝ Manifold x => Cutplane x -> (x, x) -> Option D¹ -- | A linear mapping between finite-dimensional spaces, implemeted as a -- dense matrix. -- -- Note that this is equivalent to the tensor product -- DualSpace a ⊗ b. One of the types should be -- deprecated in the future, or either implemented in terms of the other. data Linear s a b type LocalLinear x y = Linear (Scalar (Needle x)) (Needle x) (Needle y) denseLinear :: (FiniteDimensional v, FiniteDimensional w, Scalar w ~ s) => (v -> w) -> Linear s v w instance Data.VectorSpace.FiniteDimensional.FiniteDimensional v => Data.MemoTrie.HasTrie (Data.Manifold.Types.Stiefel1Basis v) instance (Data.VectorSpace.FiniteDimensional.SmoothScalar (Data.VectorSpace.Scalar v), Data.VectorSpace.FiniteDimensional.FiniteDimensional v) => Data.AdditiveGroup.AdditiveGroup (Data.Manifold.Types.Stiefel1Needle v) instance (Data.VectorSpace.FiniteDimensional.SmoothScalar (Data.VectorSpace.Scalar v), Data.VectorSpace.FiniteDimensional.FiniteDimensional v) => Data.VectorSpace.VectorSpace (Data.Manifold.Types.Stiefel1Needle v) instance (Data.VectorSpace.FiniteDimensional.SmoothScalar (Data.VectorSpace.Scalar v), Data.VectorSpace.FiniteDimensional.FiniteDimensional v) => Data.Basis.HasBasis (Data.Manifold.Types.Stiefel1Needle v) instance (Data.VectorSpace.FiniteDimensional.SmoothScalar (Data.VectorSpace.Scalar v), Data.VectorSpace.FiniteDimensional.FiniteDimensional v) => Data.VectorSpace.FiniteDimensional.FiniteDimensional (Data.Manifold.Types.Stiefel1Needle v) instance (Data.VectorSpace.FiniteDimensional.SmoothScalar (Data.VectorSpace.Scalar v), Data.VectorSpace.FiniteDimensional.FiniteDimensional v) => Data.AffineSpace.AffineSpace (Data.Manifold.Types.Stiefel1Needle v) instance (Data.VectorSpace.FiniteDimensional.SmoothScalar (Data.VectorSpace.Scalar v), Data.VectorSpace.FiniteDimensional.FiniteDimensional v) => Data.Manifold.PseudoAffine.Semimanifold (Data.Manifold.Types.Stiefel1Needle v) instance (Data.VectorSpace.FiniteDimensional.SmoothScalar (Data.VectorSpace.Scalar v), Data.VectorSpace.FiniteDimensional.FiniteDimensional v) => Data.Manifold.PseudoAffine.PseudoAffine (Data.Manifold.Types.Stiefel1Needle v) instance (Data.LinearMap.HerMetric.MetricScalar (Data.VectorSpace.Scalar v), Data.VectorSpace.FiniteDimensional.FiniteDimensional v) => Data.LinearMap.HerMetric.HasMetric' (Data.Manifold.Types.Stiefel1Needle v) instance (Data.Manifold.PseudoAffine.WithField k Data.Manifold.PseudoAffine.LinearManifold v, GHC.Real.Real k) => Data.Manifold.PseudoAffine.Semimanifold (Data.LinearMap.HerMetric.Stiefel1 v) instance (Data.Manifold.PseudoAffine.WithField k Data.Manifold.PseudoAffine.LinearManifold v, GHC.Real.Real k) => Data.Manifold.PseudoAffine.PseudoAffine (Data.LinearMap.HerMetric.Stiefel1 v) instance Data.Manifold.PseudoAffine.WithField Data.Manifold.Types.Primitive.ℝ Data.Manifold.PseudoAffine.HilbertSpace x => Data.Manifold.Cone.ConeSemimfd (Data.LinearMap.HerMetric.Stiefel1 x) -- | 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 -- 'S¹' × 'S¹', not from the “doughnut” embedding; the cone over -- is simply treated as the unit disk, etc..) module Data.Manifold.Riemannian class Semimanifold x => Geodesic x geodesicBetween :: Geodesic x => x -> x -> Option (D¹ -> x) interpolate :: (Geodesic x, IntervalLike i) => x -> x -> Option (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 instance Data.Manifold.Riemannian.Geodesic Data.Manifold.Types.Primitive.ℝ instance Data.Manifold.Riemannian.Geodesic (Data.Manifold.Types.Primitive.ZeroDim Data.Manifold.Types.Primitive.ℝ) 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.CoNat.KnownNat n => Data.Manifold.Riemannian.Geodesic (Data.CoNat.FreeVect n Data.Manifold.Types.Primitive.ℝ) instance Data.Manifold.PseudoAffine.PseudoAffine v => Data.Manifold.Riemannian.Geodesic (Data.VectorSpace.FiniteDimensional.FinVecArrRep t v Data.Manifold.Types.Primitive.ℝ) instance (Data.Manifold.Riemannian.Geodesic v, Data.Manifold.PseudoAffine.WithField Data.Manifold.Types.Primitive.ℝ Data.Manifold.PseudoAffine.HilbertSpace v) => Data.Manifold.Riemannian.Geodesic (Data.LinearMap.HerMetric.Stiefel1 v) instance Data.Manifold.Riemannian.Geodesic Data.Manifold.Types.Primitive.S⁰ instance Data.Manifold.Riemannian.Geodesic Data.Manifold.Types.Primitive.S¹ instance Data.Manifold.Riemannian.Geodesic (Data.Manifold.Types.Primitive.Cℝay Data.Manifold.Types.Primitive.S⁰) instance Data.Manifold.Riemannian.Geodesic (Data.Manifold.Types.Primitive.CD¹ Data.Manifold.Types.Primitive.S⁰) instance Data.Manifold.Riemannian.Geodesic (Data.Manifold.Types.Primitive.Cℝay Data.Manifold.Types.Primitive.S¹) instance Data.Manifold.Riemannian.Geodesic (Data.Manifold.Types.Primitive.CD¹ Data.Manifold.Types.Primitive.S¹) instance Data.Manifold.Riemannian.Geodesic (Data.Manifold.Types.Primitive.Cℝay Data.Manifold.Types.Primitive.S²) instance Data.Manifold.Riemannian.Geodesic (Data.Manifold.Types.Primitive.CD¹ Data.Manifold.Types.Primitive.S²) instance Data.Manifold.Riemannian.Geodesic (Data.Manifold.Types.Primitive.Cℝay Data.Manifold.Types.Primitive.ℝ) instance Data.Manifold.Riemannian.Geodesic (Data.Manifold.Types.Primitive.CD¹ Data.Manifold.Types.Primitive.ℝ) instance Data.Manifold.Riemannian.Geodesic (Data.Manifold.Types.Primitive.Cℝay Data.Manifold.Types.Primitive.ℝ⁰) instance Data.Manifold.Riemannian.Geodesic (Data.Manifold.Types.Primitive.CD¹ Data.Manifold.Types.Primitive.ℝ⁰) instance (Data.Manifold.PseudoAffine.WithField Data.Manifold.Types.Primitive.ℝ Data.Manifold.PseudoAffine.HilbertSpace a, Data.Manifold.PseudoAffine.WithField Data.Manifold.Types.Primitive.ℝ Data.Manifold.PseudoAffine.HilbertSpace b, Data.Manifold.Riemannian.Geodesic (a, b)) => Data.Manifold.Riemannian.Geodesic (Data.Manifold.Types.Primitive.Cℝay (a, b)) instance (Data.Manifold.PseudoAffine.WithField Data.Manifold.Types.Primitive.ℝ Data.Manifold.PseudoAffine.HilbertSpace a, Data.Manifold.PseudoAffine.WithField Data.Manifold.Types.Primitive.ℝ Data.Manifold.PseudoAffine.HilbertSpace b, Data.Manifold.Riemannian.Geodesic (a, b)) => Data.Manifold.Riemannian.Geodesic (Data.Manifold.Types.Primitive.CD¹ (a, b)) instance Data.CoNat.KnownNat n => Data.Manifold.Riemannian.Geodesic (Data.Manifold.Types.Primitive.Cℝay (Data.CoNat.FreeVect n Data.Manifold.Types.Primitive.ℝ)) instance Data.CoNat.KnownNat n => Data.Manifold.Riemannian.Geodesic (Data.Manifold.Types.Primitive.CD¹ (Data.CoNat.FreeVect n Data.Manifold.Types.Primitive.ℝ)) instance (Data.Manifold.Riemannian.Geodesic v, Data.Manifold.PseudoAffine.WithField Data.Manifold.Types.Primitive.ℝ Data.Manifold.PseudoAffine.HilbertSpace v) => Data.Manifold.Riemannian.Geodesic (Data.Manifold.Types.Primitive.Cℝay (Data.VectorSpace.FiniteDimensional.FinVecArrRep t v Data.Manifold.Types.Primitive.ℝ)) instance (Data.Manifold.Riemannian.Geodesic v, Data.Manifold.PseudoAffine.WithField Data.Manifold.Types.Primitive.ℝ Data.Manifold.PseudoAffine.HilbertSpace v) => Data.Manifold.Riemannian.Geodesic (Data.Manifold.Types.Primitive.CD¹ (Data.VectorSpace.FiniteDimensional.FinVecArrRep t v Data.Manifold.Types.Primitive.ℝ)) instance Data.Manifold.Riemannian.IntervalLike Data.Manifold.Types.Primitive.D¹ instance Data.Manifold.Riemannian.IntervalLike (Data.Manifold.Types.Primitive.CD¹ Data.Manifold.Types.Primitive.S⁰) instance Data.Manifold.Riemannian.IntervalLike (Data.Manifold.Types.Primitive.Cℝay Data.Manifold.Types.Primitive.S⁰) instance Data.Manifold.Riemannian.IntervalLike (Data.Manifold.Types.Primitive.CD¹ Data.Manifold.Types.Primitive.ℝ⁰) instance Data.Manifold.Riemannian.IntervalLike (Data.Manifold.Types.Primitive.Cℝay Data.Manifold.Types.Primitive.ℝ⁰) instance Data.Manifold.Riemannian.IntervalLike Data.Manifold.Types.Primitive.ℝ instance Data.Manifold.Riemannian.Riemannian Data.Manifold.Types.Primitive.ℝ 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 :: !(Interior x) -> !(Metric' x) -> Shade x [_shadeCtr] :: Shade x -> !(Interior x) [_shadeExpanse] :: Shade x -> !(Metric' x) -- | Span a Shade from a center point and multiple -- deviation-vectors. -- | 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'. (|±|) :: WithField ℝ EuclidSpace x => x -> [Needle x] -> Shade' x class IsShade shade -- | Access the center of a Shade or a Shade'. shadeCtr :: IsShade shade => Lens' (shade x) (Interior x) -- | Check the statistical likelihood-density of a point being within a -- shade. This is taken as a normal distribution. occlusion :: (IsShade shade, Manifold x, s ~ (Scalar (Needle x)), RealDimension s) => shade x -> x -> s factoriseShade :: (IsShade shade, Manifold x, RealDimension (Scalar (Needle x)), Manifold y, RealDimension (Scalar (Needle y))) => shade (x, y) -> (shade x, shade y) coerceShade :: (IsShade shade, Manifold x, Manifold y, LocallyCoercible x y) => shade x -> shade y shadeExpanse :: Lens' (Shade x) (Metric' x) shadeNarrowness :: Lens' (Shade' x) (Metric x) fullShade :: WithField ℝ Manifold x => x -> Metric' x -> Shade x fullShade' :: WithField ℝ Manifold x => 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 ℝ Manifold x => [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 :: WithField ℝ Manifold x => [x] -> [Shade x] intersectShade's :: Refinable y => NonEmpty (Shade' y) -> Option (Shade' y) -- | 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 ℝ Manifold y) => Refinable y where subShade' (Shade' ac ae) tsh = all ((< 1) . minusLogOcclusion' tsh) [ac .+~^ σ *^ v | σ <- [- 1, 1], v <- eigenCoSpan' ae] refineShade' (Shade' c₀ (HerMetric (Just e₁))) (Shade' c₀₂ (HerMetric (Just e₂))) | Option (Just c₂) <- c₀₂ .-~. c₀, e₁c₂ <- e₁ $ c₂, e₂c₂ <- e₂ $ c₂, cc <- σe <\$ e₂c₂, cc₂ <- cc ^-^ c₂, e₁cc <- e₁ $ cc, e₂cc <- e₂ $ cc, α <- 2 + cc₂ <.>^ e₂c₂, α > 0, ee <- σe ^/ α, c₂e₁c₂ <- c₂ ^<.> e₁c₂, c₂e₂c₂ <- c₂ ^<.> e₂c₂, c₂eec₂ <- (c₂e₁c₂ + c₂e₂c₂) / α, [γ₁, γ₂] <- middle . sort $ quadraticEqnSol c₂e₁c₂ (2 * (c₂ ^<.> e₁cc)) (cc ^<.> e₁cc - 1) ++ quadraticEqnSol c₂e₂c₂ (2 * (c₂ ^<.> e₂cc - c₂e₂c₂)) (cc ^<.> e₂cc - 2 * (cc ^<.> e₂c₂) + c₂e₂c₂ - 1), cc' <- cc ^+^ ((γ₁ + γ₂) / 2) *^ c₂, rγ <- abs (γ₁ - γ₂) / 2, η <- if rγ * c₂eec₂ /= 0 && 1 - rγ ^ 2 * c₂eec₂ > 0 then sqrt (1 - rγ ^ 2 * c₂eec₂) / (rγ * c₂eec₂) else 0 = return $ Shade' (c₀ .+~^ cc') (HerMetric (Just ee) ^+^ projector (ee $ c₂ ^* η)) | otherwise = empty where σe = e₁ ^+^ e₂ quadraticEqnSol a b c | a /= 0 && disc > 0 = [(σ * sqrt disc - b) / (2 * a) | σ <- [- 1, 1]] | otherwise = [0] where disc = b ^ 2 - 4 * a * c middle (_ : x : y : _) = [x, y] middle l = l refineShade' (Shade' _ (HerMetric Nothing)) s₂ = pure s₂ refineShade' s₁ (Shade' _ (HerMetric Nothing)) = pure s₁ convolveShade' (Shade' y₀ ey) (Shade' δ₀ eδ) = Shade' (y₀ .+~^ δ₀) (projectors [f ^* ζ crl | (f, _) <- eδsp | crl <- corelap]) where (_, eδsp) = eigenSystem (ey, eδ) corelap = map (metric ey . snd) eδsp ζ = case filter (> 0) corelap of { [] -> const 0 nzrelap -> let cre₁ = 1 / minimum nzrelap cre₂ = maximum nzrelap edgeFactor = sqrt ((1 + cre₁) ^ 2 + (1 + cre₂) ^ 2) / (sqrt (1 + cre₁ ^ 2) + sqrt (1 + cre₂ ^ 2)) in \case { 0 -> 0 sq -> edgeFactor / (recip sq + 1) } } -- | 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 refineShade' :: Refinable y => Shade' y -> Shade' y -> Option (Shade' 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 -- convolveShade' :: Refinable y => Shade' y -> Shade' (Needle y) -> Shade' y data ShadeTree x PlainLeaves :: [x] -> ShadeTree x DisjointBranches :: !Int -> (NonEmpty (ShadeTree x)) -> ShadeTree x OverlappingBranches :: !Int -> !(Shade x) -> (NonEmpty (DBranch x)) -> ShadeTree x -- | 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 :: WithField ℝ Manifold x => [x] -> ShadeTree x -- | Left (and, typically, also right) inverse of fromLeafNodes. onlyLeaves :: WithField ℝ Manifold 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 :: WithField ℝ Manifold x => ShadeTree x -> Int -> Either Int ([ShadeTree x], x) -- | “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 :: WithField ℝ Manifold x => Option (Metric x) -> ShadeTree x -> x -> Option (Int, ([ShadeTree x], x)) -- | Imitate the specialised ShadeTree structure with a simpler, -- generic tree. onlyNodes :: WithField ℝ Manifold x => ShadeTree x -> Trees x -- |
--   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) -- | Saw a tree into the domains covered by the respective branches of -- another tree. sShSaw :: WithField ℝ Manifold x => ShadeTree x -> ShadeTree x -> Sawboneses x chainsaw :: WithField ℝ Manifold x => Cutplane x -> ShadeTree x -> Sawbones 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 :: WithField ℝ Manifold x => ℝ -> [Shade x] -> [Shade x] smoothInterpolate :: (WithField ℝ Manifold x, WithField ℝ LinearManifold y) => NonEmpty (x, y) -> x -> y twigsWithEnvirons :: WithField ℝ Manifold x => ShadeTree x -> [((Int, ShadeTree x), [(Int, ShadeTree x)])] completeTopShading :: (WithField ℝ Manifold x, WithField ℝ Manifold y) => x `Shaded` y -> [Shade' (x, y)] flexTwigsShading :: (WithField ℝ Manifold x, WithField ℝ Manifold y, Applicative f) => (Shade' (x, y) -> f (x, (Shade' y, LocalLinear x y))) -> x `Shaded` y -> f (x `Shaded` 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 WithAny x y WithAny :: y -> !x -> WithAny x y [_untopological] :: WithAny x y -> y [_topological] :: WithAny x y -> !x -- | This is to ShadeTree as Map is to Set. type Shaded x y = ShadeTree (x `WithAny` y) fmapShaded :: (y -> υ) -> (x `Shaded` y) -> (x `Shaded` υ) stiAsIntervalMapping :: (x ~ ℝ, y ~ ℝ) => x `Shaded` y -> [(x, ((y, Diff y), Linear ℝ x y))] spanShading :: (WithField ℝ Manifold x, WithField ℝ Manifold y) => (Shade x -> Shade y) -> ShadeTree x -> x `Shaded` y constShaded :: y -> ShadeTree x -> x `Shaded` y stripShadedUntopological :: x `Shaded` y -> ShadeTree x type DifferentialEqn x y = Shade (x, y) -> Shade' (LocalLinear x y) propagateDEqnSolution_loc :: (WithField ℝ Manifold x, Refinable y) => DifferentialEqn x y -> ((x, Shade' y), NonEmpty (Needle x, Shade' y)) -> NonEmpty (Shade' y) type TriangBuild t n x = TriangT t (S n) x (State (Map (SimplexIT t n x) (Metric x, ISimplex (S n) x))) doTriangBuild :: KnownNat n => (forall t. TriangBuild t n x ()) -> [Simplex (S n) x] singleFullSimplex :: (KnownNat n, WithField ℝ Manifold x) => ISimplex n x -> FullTriang t n x (SimplexIT t n x) -- | BUGGY: this does connect the supplied triangulations, but it doesn't -- choose the right boundary simplices yet. Probable cause: inconsistent -- internal numbering of the subsimplices. autoglueTriangulation :: (KnownNat n'', WithField ℝ Manifold x, n ~ S n', n' ~ S n'') => (forall t'. TriangBuild t' n' x ()) -> TriangBuild t n' x () data AutoTriang n x elementaryTriang :: (KnownNat n', n ~ S n', WithField ℝ EuclidSpace x) => Simplex n x -> AutoTriang n x breakdownAutoTriang :: (KnownNat n', n ~ S n') => AutoTriang n x -> [Simplex n x] instance GHC.Generics.Selector Data.Manifold.TreeCover.S1_0_1WithAny instance GHC.Generics.Selector Data.Manifold.TreeCover.S1_0_0WithAny instance GHC.Generics.Constructor Data.Manifold.TreeCover.C1_0WithAny instance GHC.Generics.Datatype Data.Manifold.TreeCover.D1WithAny instance GHC.Generics.Constructor Data.Manifold.TreeCover.C1_1Sawboneses instance GHC.Generics.Constructor Data.Manifold.TreeCover.C1_0Sawboneses instance GHC.Generics.Datatype Data.Manifold.TreeCover.D1Sawboneses instance GHC.Generics.Selector Data.Manifold.TreeCover.S1_0_0GenericTree instance GHC.Generics.Constructor Data.Manifold.TreeCover.C1_0GenericTree instance GHC.Generics.Datatype Data.Manifold.TreeCover.D1GenericTree instance GHC.Generics.Constructor Data.Manifold.TreeCover.C1_0DBranches' instance GHC.Generics.Datatype Data.Manifold.TreeCover.D1DBranches' instance GHC.Generics.Constructor Data.Manifold.TreeCover.C1_2ShadeTree instance GHC.Generics.Constructor Data.Manifold.TreeCover.C1_1ShadeTree instance GHC.Generics.Constructor Data.Manifold.TreeCover.C1_0ShadeTree instance GHC.Generics.Datatype Data.Manifold.TreeCover.D1ShadeTree instance GHC.Generics.Selector Data.Manifold.TreeCover.S1_0_1DBranch' instance GHC.Generics.Selector Data.Manifold.TreeCover.S1_0_0DBranch' instance GHC.Generics.Constructor Data.Manifold.TreeCover.C1_0DBranch' instance GHC.Generics.Datatype Data.Manifold.TreeCover.D1DBranch' instance GHC.Generics.Selector Data.Manifold.TreeCover.S1_0_1Hourglass instance GHC.Generics.Selector Data.Manifold.TreeCover.S1_0_0Hourglass instance GHC.Generics.Constructor Data.Manifold.TreeCover.C1_0Hourglass instance GHC.Generics.Datatype Data.Manifold.TreeCover.D1Hourglass instance GHC.Generics.Generic (Data.Manifold.TreeCover.WithAny x y) instance (GHC.Show.Show x, GHC.Show.Show y) => GHC.Show.Show (Data.Manifold.TreeCover.WithAny x y) instance GHC.Base.Functor (Data.Manifold.TreeCover.WithAny 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.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 GHC.Generics.Generic (Data.Manifold.TreeCover.ShadeTree 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 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 (GHC.Show.Show x, GHC.Show.Show (Data.Manifold.PseudoAffine.Needle x), Data.Manifold.PseudoAffine.WithField Data.Manifold.Types.Primitive.ℝ Data.Manifold.PseudoAffine.Manifold x) => GHC.Show.Show (Data.Manifold.TreeCover.Shade x) instance (GHC.Show.Show x, GHC.Show.Show (Data.LinearMap.HerMetric.DualSpace (Data.Manifold.PseudoAffine.Needle x)), Data.Manifold.PseudoAffine.WithField Data.Manifold.Types.Primitive.ℝ Data.Manifold.PseudoAffine.Manifold x) => GHC.Show.Show (Data.Manifold.TreeCover.Shade' 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 Data.Manifold.TreeCover.IsShade Data.Manifold.TreeCover.Shade instance Data.Manifold.PseudoAffine.ImpliesMetric Data.Manifold.TreeCover.Shade instance Data.Manifold.PseudoAffine.ImpliesMetric Data.Manifold.TreeCover.Shade' instance Data.Manifold.TreeCover.IsShade Data.Manifold.TreeCover.Shade' instance Data.Manifold.PseudoAffine.AffineManifold x => Data.Manifold.PseudoAffine.Semimanifold (Data.Manifold.TreeCover.Shade x) instance (Data.Manifold.PseudoAffine.WithField Data.Manifold.Types.Primitive.ℝ Data.Manifold.PseudoAffine.AffineManifold x, Data.Manifold.Riemannian.Geodesic x) => Data.Manifold.Riemannian.Geodesic (Data.Manifold.TreeCover.Shade x) instance Data.Manifold.PseudoAffine.AffineManifold x => Data.Manifold.PseudoAffine.Semimanifold (Data.Manifold.TreeCover.Shade' x) instance (Data.Manifold.PseudoAffine.WithField Data.Manifold.Types.Primitive.ℝ Data.Manifold.PseudoAffine.AffineManifold x, Data.Manifold.Riemannian.Geodesic x) => Data.Manifold.Riemannian.Geodesic (Data.Manifold.TreeCover.Shade' x) instance Control.DeepSeq.NFData s => Control.DeepSeq.NFData (Data.Manifold.TreeCover.Hourglass s) instance Data.Semigroup.Semigroup s => Data.Semigroup.Semigroup (Data.Manifold.TreeCover.Hourglass s) instance (GHC.Base.Monoid s, Data.Semigroup.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 (->) (->) instance Data.Semigroup.Semigroup c => Data.Semigroup.Semigroup (Data.Manifold.TreeCover.DBranches' x c) instance (Control.DeepSeq.NFData x, Control.DeepSeq.NFData (Data.Manifold.PseudoAffine.Needle' x)) => Control.DeepSeq.NFData (Data.Manifold.TreeCover.ShadeTree x) instance (Control.DeepSeq.NFData x, Control.DeepSeq.NFData (Data.Manifold.PseudoAffine.Needle' x)) => Control.DeepSeq.NFData (Data.Manifold.TreeCover.DBranch x) instance Data.Manifold.PseudoAffine.AffineManifold x => Data.Manifold.PseudoAffine.Semimanifold (Data.Manifold.TreeCover.ShadeTree x) instance Data.Manifold.PseudoAffine.WithField Data.Manifold.Types.Primitive.ℝ Data.Manifold.PseudoAffine.Manifold x => Data.Semigroup.Semigroup (Data.Manifold.TreeCover.ShadeTree x) instance Data.Manifold.PseudoAffine.WithField Data.Manifold.Types.Primitive.ℝ Data.Manifold.PseudoAffine.Manifold x => GHC.Base.Monoid (Data.Manifold.TreeCover.ShadeTree x) instance Data.Manifold.PseudoAffine.ImpliesMetric Data.Manifold.TreeCover.ShadeTree instance Data.Manifold.TreeCover.Refinable Data.Manifold.Types.Primitive.ℝ instance (Data.Manifold.TreeCover.Refinable a, Data.Manifold.TreeCover.Refinable b) => Data.Manifold.TreeCover.Refinable (a, b) instance Data.CoNat.KnownNat n => Data.AffineSpace.AffineSpace (Data.Manifold.TreeCover.BaryCoords n) instance Data.CoNat.KnownNat n => Data.Manifold.PseudoAffine.Semimanifold (Data.Manifold.TreeCover.BaryCoords n) instance Data.CoNat.KnownNat n => Data.Manifold.PseudoAffine.PseudoAffine (Data.Manifold.TreeCover.BaryCoords n) instance (Data.CoNat.KnownNat n, Data.Manifold.PseudoAffine.WithField Data.Manifold.Types.Primitive.ℝ Data.Manifold.PseudoAffine.Manifold x) => Data.Semigroup.Semigroup (Data.Manifold.TreeCover.AutoTriang ('Data.CoNat.S ('Data.CoNat.S n)) 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 => Data.Semigroup.Semigroup (Data.Manifold.TreeCover.GenericTree c b x) instance GHC.Base.MonadPlus c => GHC.Base.Monoid (Data.Manifold.TreeCover.GenericTree c b x) instance Data.Semigroup.Semigroup (Data.Manifold.TreeCover.Sawbones x) instance GHC.Base.Monoid (Data.Manifold.TreeCover.Sawbones x) instance Data.Semigroup.Semigroup (Data.Manifold.TreeCover.DustyEdges x) instance Data.Semigroup.Semigroup (Data.Manifold.TreeCover.Sawboneses x) instance (Control.DeepSeq.NFData x, Control.DeepSeq.NFData y) => Control.DeepSeq.NFData (Data.Manifold.TreeCover.WithAny x y) instance Data.Manifold.PseudoAffine.Semimanifold x => Data.Manifold.PseudoAffine.Semimanifold (Data.Manifold.TreeCover.WithAny x y) instance Data.Manifold.PseudoAffine.PseudoAffine x => Data.Manifold.PseudoAffine.PseudoAffine (Data.Manifold.TreeCover.WithAny x y) instance Data.AffineSpace.AffineSpace x => Data.AffineSpace.AffineSpace (Data.Manifold.TreeCover.WithAny x y) instance (Data.VectorSpace.VectorSpace x, GHC.Base.Monoid y) => Data.VectorSpace.VectorSpace (Data.Manifold.TreeCover.WithAny x y) instance (Data.AdditiveGroup.AdditiveGroup x, GHC.Base.Monoid y) => Data.AdditiveGroup.AdditiveGroup (Data.Manifold.TreeCover.WithAny x y) instance Data.AdditiveGroup.AdditiveGroup x => GHC.Base.Applicative (Data.Manifold.TreeCover.WithAny x) instance Data.AdditiveGroup.AdditiveGroup x => GHC.Base.Monad (Data.Manifold.TreeCover.WithAny x) instance Data.Manifold.TreeCover.HasFlatView Data.Manifold.TreeCover.Sawbones instance Data.Manifold.TreeCover.HasFlatView Data.Manifold.TreeCover.Sawboneses 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 :: WithField ℝ Manifold x => (MetricChoice x) -> [(x, y)] -> PointsWeb x y fromShadeTree_auto :: WithField ℝ Manifold x => ShadeTree x -> PointsWeb x () fromShadeTree :: WithField ℝ Manifold x => (Shade x -> Metric x) -> ShadeTree x -> PointsWeb x () fromShaded :: WithField ℝ Manifold x => (MetricChoice x) -> (x `Shaded` y) -> PointsWeb x y nearestNeighbour :: WithField ℝ Manifold x => PointsWeb x y -> x -> Option (x, y) indexWeb :: WithField ℝ Manifold x => PointsWeb x y -> WebNodeId -> Option (x, y) webEdges :: WithField ℝ Manifold x => PointsWeb x y -> [((x, y), (x, y))] toGraph :: WithField ℝ Manifold x => PointsWeb x y -> (Graph, Vertex -> (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 :: (WithField ℝ Manifold x, Geodesic x, Geodesic y) => PointsWeb x y -> Cutplane x -> [(x, y)] localFocusWeb :: WithField ℝ Manifold x => PointsWeb x y -> PointsWeb x ((x, y), [(Needle x, y)]) filterDEqnSolution_static :: (WithField ℝ Manifold x, Refinable y) => DifferentialEqn x y -> PointsWeb x (Shade' y) -> Option (PointsWeb x (Shade' y)) iterateFilterDEqn_static :: (WithField ℝ Manifold x, Refinable y) => DifferentialEqn x y -> PointsWeb x (Shade' y) -> [PointsWeb x (Shade' y)] filterDEqnSolutions_adaptive :: (WithField ℝ Manifold x, Refinable y, badness ~ ℝ) => MetricChoice x -> DifferentialEqn x y -> (x -> Shade' y -> badness) -> PointsWeb x (SolverNodeState y) -> Option (PointsWeb x (SolverNodeState y)) iterateFilterDEqn_adaptive :: (WithField ℝ Manifold x, Refinable y) => MetricChoice x -> DifferentialEqn x y -> (x -> Shade' y -> ℝ) -> PointsWeb x (Shade' y) -> [PointsWeb x (Shade' y)] 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 instance GHC.Base.Functor (Data.Manifold.Web.WebLocally x) instance Data.Manifold.PseudoAffine.WithField Data.Manifold.Types.Primitive.ℝ Data.Manifold.PseudoAffine.Manifold x => Control.Comonad.Comonad (Data.Manifold.Web.WebLocally x) instance Data.Manifold.TreeCover.Refinable x => Data.Semigroup.Semigroup (Data.Manifold.Web.ConvexSet x) instance GHC.Generics.Selector Data.Manifold.Web.S1_0_6WebLocally instance GHC.Generics.Selector Data.Manifold.Web.S1_0_5WebLocally instance GHC.Generics.Selector Data.Manifold.Web.S1_0_4WebLocally instance GHC.Generics.Selector Data.Manifold.Web.S1_0_3WebLocally instance GHC.Generics.Selector Data.Manifold.Web.S1_0_2WebLocally instance GHC.Generics.Selector Data.Manifold.Web.S1_0_1WebLocally instance GHC.Generics.Selector Data.Manifold.Web.S1_0_0WebLocally instance GHC.Generics.Constructor Data.Manifold.Web.C1_0WebLocally instance GHC.Generics.Datatype Data.Manifold.Web.D1WebLocally instance GHC.Generics.Selector Data.Manifold.Web.S1_0_1PointsWeb instance GHC.Generics.Selector Data.Manifold.Web.S1_0_0PointsWeb instance GHC.Generics.Constructor Data.Manifold.Web.C1_0PointsWeb instance GHC.Generics.Datatype Data.Manifold.Web.D1PointsWeb instance GHC.Generics.Selector Data.Manifold.Web.S1_0_1Neighbourhood instance GHC.Generics.Selector Data.Manifold.Web.S1_0_0Neighbourhood instance GHC.Generics.Constructor Data.Manifold.Web.C1_0Neighbourhood instance GHC.Generics.Datatype Data.Manifold.Web.D1Neighbourhood instance GHC.Generics.Generic (Data.Manifold.Web.WebLocally x y) instance Data.Traversable.Traversable (Data.Manifold.Web.PointsWeb a) instance Data.Foldable.Foldable (Data.Manifold.Web.PointsWeb a) instance GHC.Base.Functor (Data.Manifold.Web.PointsWeb a) instance GHC.Generics.Generic (Data.Manifold.Web.PointsWeb a b) instance GHC.Generics.Generic (Data.Manifold.Web.Neighbourhood x) instance (Control.DeepSeq.NFData x, Control.DeepSeq.NFData (Data.LinearMap.HerMetric.HerMetric (Data.Manifold.PseudoAffine.Needle x))) => Control.DeepSeq.NFData (Data.Manifold.Web.Neighbourhood x) instance (Control.DeepSeq.NFData x, Control.DeepSeq.NFData (Data.LinearMap.HerMetric.HerMetric (Data.Manifold.PseudoAffine.Needle x)), Control.DeepSeq.NFData (Data.Manifold.PseudoAffine.Needle' x), Control.DeepSeq.NFData y) => Control.DeepSeq.NFData (Data.Manifold.Web.PointsWeb x y) instance Data.Foldable.Constrained.Foldable (Data.Manifold.Web.PointsWeb x) (->) (->) instance Data.Traversable.Constrained.Traversable (Data.Manifold.Web.PointsWeb x) (Data.Manifold.Web.PointsWeb x) (->) (->) module Data.Manifold.DifferentialEquation type DifferentialEqn x y = Shade (x, y) -> Shade' (LocalLinear x y) constLinearDEqn :: (WithField ℝ LinearManifold x, WithField ℝ LinearManifold y) => Linear ℝ (DualSpace y) (Linear ℝ y x) -> DifferentialEqn x y filterDEqnSolution_static :: (WithField ℝ Manifold x, Refinable y) => DifferentialEqn x y -> PointsWeb x (Shade' y) -> Option (PointsWeb x (Shade' y)) iterateFilterDEqn_static :: (WithField ℝ Manifold x, Refinable y) => DifferentialEqn x y -> PointsWeb x (Shade' y) -> [PointsWeb x (Shade' y)] maxDeviationsGoal :: WithField ℝ EuclidSpace y => [Needle y] -> x -> Shade' y -> ℝ uncertaintyGoal :: WithField ℝ EuclidSpace y => Metric' y -> x -> Shade' y -> ℝ uncertaintyGoal' :: WithField ℝ EuclidSpace y => (x -> Metric' y) -> x -> Shade' y -> ℝ euclideanVolGoal :: WithField ℝ EuclidSpace y => ℝ -> x -> Shade' y -> ℝ 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 Data.Manifold.Types.Primitive.ℝ GHC.Base.String instance (Data.Manifold.Griddable.Griddable m a, Data.Manifold.Griddable.Griddable n a) => Data.Manifold.Griddable.Griddable (m, n) a -- | 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