-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Native, complete, matrix-free linear algebra. -- -- The term numerical linear algebra is often used almost -- synonymous with matrix modifications. However, what's -- interesting for most applications are really just points in some -- vector space and linear mappings between them, not matrices (which -- represent points or mappings, but inherently depend on a particular -- choice of basis / coordinate system). -- -- This library implements the crucial LA operations like solving linear -- equations and eigenvalue problems, without requiring that the vectors -- are represented in some particular basis. Apart from conceptual -- elegance (only operations that are actually geometrically sensible -- will typecheck – this is far stronger than just confirming that the -- dimensions match, as some other libraries do), this also opens up good -- optimisation possibilities: the vectors can be unboxed, use dedicated -- sparse compression, possibly carry out the computations on accelerated -- hardware (GPU etc.). The spaces can even be infinite-dimensional (e.g. -- function spaces). -- -- The linear algebra algorithms in this package only require the vectors -- to support fundamental operations like addition, scalar products, -- double-dual-space coercion and tensor products; none of this requires -- a basis representation. @package linearmap-category @version 0.4.2.0 module Math.VectorSpace.MiscUtil.MultiConstraints type family SameScalar (c :: Type -> Constraint) (vs :: [Type]) :: Constraint module Math.VectorSpace.ZeroDimensional data ZeroDim s Origin :: ZeroDim s module Math.VectorSpace.Dual data Dualness Vector :: Dualness Functional :: Dualness type family Dual (dn :: Dualness) data DualityWitness (dn :: Dualness) [DualityWitness] :: (ValidDualness (Dual dn), Dual (Dual dn) ~ dn) => DualityWitness dn class ValidDualness (dn :: Dualness) where { type family Space dn v :: Type; } dualityWitness :: ValidDualness dn => DualityWitness dn decideDualness :: ValidDualness dn => DualnessSingletons dn usingAnyDualness :: forall rc dn. ValidDualness dn => rc 'Vector -> rc 'Functional -> rc dn data DualnessSingletons (dn :: Dualness) [VectorWitness] :: DualnessSingletons Vector [FunctionalWitness] :: DualnessSingletons Functional instance Math.VectorSpace.Dual.ValidDualness 'Math.VectorSpace.Dual.Vector instance Math.VectorSpace.Dual.ValidDualness 'Math.VectorSpace.Dual.Functional module Math.LinearMap.Category.Instances.Deriving -- | Given a type V that is already a VectorSpace and -- HasBasis, generate the other class instances that are needed to -- use the type with this library. -- -- Prerequisites: (these can often be derived automatically, using either -- the newtype / via strategy or generics / anyclass) -- --
--   instance AdditiveGroup V
--   
--   instance VectorSpace V where
--     type Scalar V = -- a simple number type, usually Double
--   
--   instance HasBasis V where
--     type Basis V = -- a type with an instance of HasTrie
--   
-- -- Note that the Basis does not need to be orthonormal – in -- fact it is not necessary to have a scalar product (i.e. an -- InnerSpace instance) at all. -- -- This macro, invoked like makeLinearSpaceFromBasis [t| V |] -- -- will then generate V-instances for the classes -- Semimanifold, PseudoAffine, AffineSpace, -- TensorSpace and LinearSpace. makeLinearSpaceFromBasis :: Q Type -> DecsQ -- | Like makeLinearSpaceFromBasis, but additionally generate -- instances for FiniteDimensional and SemiInner. makeFiniteDimensionalFromBasis :: Q Type -> DecsQ class AdditiveGroup Diff p => AffineSpace p where { -- | Associated vector space type family Diff p; type Diff p = GenericDiff p; } -- | Subtract points (.-.) :: AffineSpace p => p -> p -> Diff p -- | Point plus vector (.+^) :: AffineSpace p => p -> Diff p -> p infixl 6 .+^ infix 6 .-. class AdditiveGroup Needle x => Semimanifold x where { -- | The space of “ways” starting from some reference point and going to -- some particular target point. Hence, the name: like a compass needle, -- but also with an actual length. For affine spaces, Needle is -- simply the space of line segments (aka vectors) between two points, -- i.e. the same as Diff. The AffineManifold constraint -- makes that requirement explicit. -- -- This space should be isomorphic to the tangent space (and in fact -- serves an in many ways similar role), however whereas the tangent -- space of a manifold is really infinitesimally small, needles actually -- allow macroscopic displacements. type family Needle x; type Needle x = GenericNeedle x; } -- | Generalisation of the translation operation .+^ to possibly -- non-flat manifolds, instead of affine spaces. (.+~^) :: Semimanifold x => x -> Needle x -> 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 -- eventually scale down even faster: as O (η²). For large -- vectors, it may however behave differently, except in flat spaces -- (where all this should be equivalent to the AffineSpace -- instance). (.-~^) :: Semimanifold x => x -> Needle x -> x semimanifoldWitness :: Semimanifold x => SemimanifoldWitness x infixl 6 .+~^ infixl 6 .-~^ -- | This is the class underlying what we understand as manifolds. -- -- The interface is 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). -- -- The Semimanifold and PseudoAffine classes can be -- anyclass-derived or empty-instantiated based on -- Generic for product types (including newtypes) of existing -- PseudoAffine instances. For example, the definition -- --
--   data Cylinder = CylinderPolar { zCyl :: !D¹, φCyl :: !S¹ }
--     deriving (Generic, Semimanifold, PseudoAffine)
--   
-- -- is equivalent to -- --
--   data Cylinder = CylinderPolar { zCyl :: !D¹, φCyl :: !S¹ }
--   
--   data CylinderNeedle = CylinderPolarNeedle { δzCyl :: !(Needle D¹), δφCyl :: !(Needle S¹) }
--   
--   instance Semimanifold Cylinder where
--     type Needle Cylinder = CylinderNeedle
--     CylinderPolar z φ .+~^ CylinderPolarNeedle δz δφ
--          = CylinderPolar (z.+~^δz) (φ.+~^δφ)
--   
--   instance PseudoAffine Cylinder where
--     CylinderPolar z₁ φ₁ .-~. CylinderPolar z₀ φ₀
--          = CylinderPolarNeedle $ z₁.-~.z₀ * φ₁.-~.φ₀
--     CylinderPolar z₁ φ₁ .-~! CylinderPolar z₀ φ₀
--          = CylinderPolarNeedle (z₁.-~!z₀) (φ₁.-~.φ₀)
--   
class Semimanifold x => PseudoAffine x -- | The path reaching from one point to another. Should only yield -- Nothing if the points are on disjoint segments of a -- non–path-connected space. -- -- For a connected manifold, you may define this method as -- --
--   p.-~.q = pure (p.-~!q)
--   
(.-~.) :: PseudoAffine x => x -> x -> Maybe (Needle x) -- | Unsafe version of .-~.. If the two points lie in disjoint -- regions, the behaviour is undefined. -- -- Whenever p and q lie in a connected region, the -- identity -- --
--   p .+~^ (q.-~.p) ≡ q
--   
-- -- should hold (up to possible floating point rounding etc.). Meanwhile, -- you will in general have -- --
--   (p.+~^v).-~^v ≠ p
--   
-- -- (though in many instances this is at least for sufficiently small -- v approximately equal). (.-~!) :: PseudoAffine x => x -> x -> Needle x pseudoAffineWitness :: PseudoAffine x => PseudoAffineWitness x infix 6 .-~. infix 6 .-~! class (VectorSpace v, PseudoAffine v) => TensorSpace v where { -- | The internal representation of a Tensor product. -- -- For Euclidean spaces, this is generally constructed by replacing each -- s scalar field in the v vector with an entire -- w vector. I.e., you have then a “nested vector” or, if -- v is a DualVector / “row vector”, a matrix. type family TensorProduct v w :: *; } scalarSpaceWitness :: TensorSpace v => ScalarSpaceWitness v linearManifoldWitness :: TensorSpace v => LinearManifoldWitness v zeroTensor :: (TensorSpace v, TensorSpace w, Scalar w ~ Scalar v) => v ⊗ w toFlatTensor :: TensorSpace v => v -+> (v ⊗ Scalar v) fromFlatTensor :: TensorSpace v => (v ⊗ Scalar v) -+> v addTensors :: (TensorSpace v, TensorSpace w, Scalar w ~ Scalar v) => (v ⊗ w) -> (v ⊗ w) -> v ⊗ w addTensors :: (TensorSpace v, AdditiveGroup (TensorProduct v w)) => (v ⊗ w) -> (v ⊗ w) -> v ⊗ w subtractTensors :: (TensorSpace v, TensorSpace v, TensorSpace w, Scalar w ~ Scalar v) => (v ⊗ w) -> (v ⊗ w) -> v ⊗ w subtractTensors :: (TensorSpace v, AdditiveGroup (TensorProduct v w)) => (v ⊗ w) -> (v ⊗ w) -> v ⊗ w scaleTensor :: (TensorSpace v, TensorSpace w, Scalar w ~ Scalar v) => Bilinear (Scalar v) (v ⊗ w) (v ⊗ w) scaleTensor :: (TensorSpace v, VectorSpace (TensorProduct v w), Scalar (TensorProduct v w) ~ Scalar v) => Bilinear (Scalar v) (v ⊗ w) (v ⊗ w) negateTensor :: (TensorSpace v, TensorSpace w, Scalar w ~ Scalar v) => (v ⊗ w) -+> (v ⊗ w) negateTensor :: (TensorSpace v, AdditiveGroup (TensorProduct v w)) => (v ⊗ w) -+> (v ⊗ w) tensorProduct :: (TensorSpace v, TensorSpace w, Scalar w ~ Scalar v) => Bilinear v w (v ⊗ w) tensorProducts :: (TensorSpace v, TensorSpace w, Scalar w ~ Scalar v) => [(v, w)] -> v ⊗ w transposeTensor :: (TensorSpace v, TensorSpace w, Scalar w ~ Scalar v) => (v ⊗ w) -+> (w ⊗ v) fmapTensor :: (TensorSpace v, TensorSpace w, TensorSpace x, Scalar w ~ Scalar v, Scalar x ~ Scalar v) => Bilinear (w -+> x) (v ⊗ w) (v ⊗ x) fzipTensorWith :: (TensorSpace v, TensorSpace u, TensorSpace w, TensorSpace x, Scalar u ~ Scalar v, Scalar w ~ Scalar v, Scalar x ~ Scalar v) => Bilinear ((w, x) -+> u) (v ⊗ w, v ⊗ x) (v ⊗ u) coerceFmapTensorProduct :: (TensorSpace v, Functor p) => p v -> Coercion a b -> Coercion (TensorProduct v a) (TensorProduct v b) -- | “Sanity-check” a vector. This typically amounts to detecting any NaN -- components, which should trigger a Nothing result. Otherwise, -- the result should be Just the input, but may also be -- optimised / memoised if applicable (i.e. for function spaces). wellDefinedVector :: TensorSpace v => v -> Maybe v -- | “Sanity-check” a vector. This typically amounts to detecting any NaN -- components, which should trigger a Nothing result. Otherwise, -- the result should be Just the input, but may also be -- optimised / memoised if applicable (i.e. for function spaces). wellDefinedVector :: (TensorSpace v, Eq v) => v -> Maybe v wellDefinedTensor :: (TensorSpace v, TensorSpace w, Scalar w ~ Scalar v) => (v ⊗ w) -> Maybe (v ⊗ w) -- | The class of vector spaces v for which LinearMap s -- v w is well-implemented. class (TensorSpace v, Num (Scalar v)) => LinearSpace v where { -- | Suitable representation of a linear map from the space v to -- its field. -- -- For the usual euclidean spaces, you can just define -- DualVector v = v. (In this case, a dual vector will be -- just a “row vector” if you consider v-vectors as “column -- vectors”. LinearMap will then effectively have a matrix -- layout.) type family DualVector v :: *; } dualSpaceWitness :: LinearSpace v => DualSpaceWitness v linearId :: LinearSpace v => v +> v idTensor :: LinearSpace v => v ⊗ DualVector v sampleLinearFunction :: (LinearSpace v, TensorSpace w, Scalar v ~ Scalar w) => (v -+> w) -+> (v +> w) toLinearForm :: LinearSpace v => DualVector v -+> (v +> Scalar v) fromLinearForm :: LinearSpace v => (v +> Scalar v) -+> DualVector v coerceDoubleDual :: LinearSpace v => Coercion v (DualVector (DualVector v)) trace :: LinearSpace v => (v +> v) -+> Scalar v contractTensorMap :: (LinearSpace v, TensorSpace w, Scalar w ~ Scalar v) => (v +> (v ⊗ w)) -+> w contractMapTensor :: (LinearSpace v, TensorSpace w, Scalar w ~ Scalar v) => (v ⊗ (v +> w)) -+> w contractTensorFn :: forall w. (LinearSpace v, TensorSpace w, Scalar w ~ Scalar v) => (v -+> (v ⊗ w)) -+> w contractLinearMapAgainst :: (LinearSpace v, LinearSpace w, Scalar w ~ Scalar v) => Bilinear (v +> w) (w -+> v) (Scalar v) applyDualVector :: (LinearSpace v, LinearSpace v) => Bilinear (DualVector v) v (Scalar v) applyLinear :: (LinearSpace v, TensorSpace w, Scalar w ~ Scalar v) => Bilinear (v +> w) v w composeLinear :: (LinearSpace v, LinearSpace w, TensorSpace x, Scalar w ~ Scalar v, Scalar x ~ Scalar v) => Bilinear (w +> x) (v +> w) (v +> x) tensorId :: (LinearSpace v, LinearSpace w, Scalar w ~ Scalar v) => (v ⊗ w) +> (v ⊗ w) applyTensorFunctional :: (LinearSpace v, LinearSpace u, Scalar u ~ Scalar v) => Bilinear (DualVector (v ⊗ u)) (v ⊗ u) (Scalar v) applyTensorLinMap :: (LinearSpace v, LinearSpace u, TensorSpace w, Scalar u ~ Scalar v, Scalar w ~ Scalar v) => Bilinear ((v ⊗ u) +> w) (v ⊗ u) w useTupleLinearSpaceComponents :: (LinearSpace v, v ~ (x, y)) => ((LinearSpace x, LinearSpace y, Scalar x ~ Scalar y) => φ) -> φ class (LSpace v, Eq v) => FiniteDimensional v where { -- | Whereas Basis-values refer to a single basis vector, a single -- SubBasis value represents a collection of such basis vectors, -- which can be used to associate a vector with a list of coefficients. -- -- For spaces with a canonical finite basis, SubBasis does not -- actually need to contain any information, it can simply have the full -- finite basis as its only value. Even for large sparse spaces, it -- should only have a very coarse structure that can be shared by many -- vectors. data family SubBasis v :: *; } entireBasis :: FiniteDimensional v => SubBasis v enumerateSubBasis :: FiniteDimensional v => SubBasis v -> [v] subbasisDimension :: FiniteDimensional v => SubBasis v -> Int -- | Split up a linear map in “column vectors” WRT some suitable basis. decomposeLinMap :: (FiniteDimensional v, LSpace w, Scalar w ~ Scalar v) => (v +> w) -> (SubBasis v, DList w) -- | Expand in the given basis, if possible. Else yield a superbasis of the -- given one, in which this is possible, and the decomposition -- therein. decomposeLinMapWithin :: (FiniteDimensional v, LSpace w, Scalar w ~ Scalar v) => SubBasis v -> (v +> w) -> Either (SubBasis v, DList w) (DList w) -- | Assemble a vector from coefficients in some basis. Return any excess -- coefficients. recomposeSB :: FiniteDimensional v => SubBasis v -> [Scalar v] -> (v, [Scalar v]) recomposeSBTensor :: (FiniteDimensional v, FiniteDimensional w, Scalar w ~ Scalar v) => SubBasis v -> SubBasis w -> [Scalar v] -> (v ⊗ w, [Scalar v]) recomposeLinMap :: (FiniteDimensional v, LSpace w, Scalar w ~ Scalar v) => SubBasis v -> [w] -> (v +> w, [w]) -- | Given a function that interprets a coefficient-container as a vector -- representation, build a linear function mapping to that space. recomposeContraLinMap :: (FiniteDimensional v, LinearSpace w, Scalar w ~ Scalar v, Functor f) => (f (Scalar w) -> w) -> f (DualVector v) -> v +> w recomposeContraLinMapTensor :: (FiniteDimensional v, FiniteDimensional u, LinearSpace w, Scalar u ~ Scalar v, Scalar w ~ Scalar v, Functor f) => (f (Scalar w) -> w) -> f (v +> DualVector u) -> (v ⊗ u) +> w -- | The existance of a finite basis gives us an isomorphism between a -- space and its dual space. Note that this isomorphism is not natural -- (i.e. it depends on the actual choice of basis, unlike everything else -- in this library). uncanonicallyFromDual :: FiniteDimensional v => DualVector v -+> v uncanonicallyToDual :: FiniteDimensional v => v -+> DualVector v tensorEquality :: (FiniteDimensional v, TensorSpace w, Eq w, Scalar w ~ Scalar v) => (v ⊗ w) -> (v ⊗ w) -> Bool dualFinitenessWitness :: FiniteDimensional v => DualFinitenessWitness v dualFinitenessWitness :: (FiniteDimensional v, FiniteDimensional (DualVector v)) => DualFinitenessWitness v -- | SemiInner is the class of vector spaces with finite subspaces -- in which you can define a basis that can be used to project from the -- whole space into the subspace. The usual application is for using a -- kind of Galerkin method to give an approximate solution (see -- \$) to a linear equation in a possibly infinite-dimensional -- space. -- -- Of course, this also works for spaces which are already -- finite-dimensional themselves. class LinearSpace v => SemiInner v -- | Lazily enumerate choices of a basis of functionals that can be made -- dual to the given vectors, in order of preference (which roughly -- means, large in the normal direction.) I.e., if the vector 𝑣 -- is assigned early to the dual vector 𝑣', then (𝑣' $ -- 𝑣) should be large and all the other products comparably small. -- -- The purpose is that we should be able to make this basis orthonormal -- with a ~Gaussian-elimination approach, in a way that stays numerically -- stable. This is otherwise known as the choice of a pivot -- element. -- -- For simple finite-dimensional array-vectors, you can easily define -- this method using cartesianDualBasisCandidates. dualBasisCandidates :: SemiInner v => [(Int, v)] -> Forest (Int, DualVector v) tensorDualBasisCandidates :: (SemiInner v, SemiInner w, Scalar w ~ Scalar v) => [(Int, v ⊗ w)] -> Forest (Int, DualVector (v ⊗ w)) symTensorDualBasisCandidates :: SemiInner v => [(Int, SymmetricTensor (Scalar v) v)] -> Forest (Int, SymmetricTensor (Scalar v) (DualVector v)) symTensorTensorDualBasisCandidates :: forall w. (SemiInner v, SemiInner w, Scalar w ~ Scalar v) => [(Int, SymmetricTensor (Scalar v) v ⊗ w)] -> Forest (Int, SymmetricTensor (Scalar v) v +> DualVector w) -- | Do not manually instantiate this class. It is used internally by -- makeLinearSpaceFromBasis. class (HasBasis v, Num' (Scalar v), LinearSpace v, DualVector v ~ DualVectorFromBasis v) => BasisGeneratedSpace v proveTensorProductIsTrie :: forall w φ. BasisGeneratedSpace v => (TensorProduct v w ~ (Basis v :->: w) => φ) -> φ data LinearSpaceFromBasisDerivationConfig -- | The default value for this type. def :: Default a => a instance Data.Basis.HasBasis v => Data.Basis.HasBasis (Math.LinearMap.Category.Instances.Deriving.DualVectorFromBasis v) instance Data.VectorSpace.VectorSpace v => Data.VectorSpace.VectorSpace (Math.LinearMap.Category.Instances.Deriving.DualVectorFromBasis v) instance Data.AdditiveGroup.AdditiveGroup v => Data.AdditiveGroup.AdditiveGroup (Math.LinearMap.Category.Instances.Deriving.DualVectorFromBasis v) instance GHC.Classes.Eq v => GHC.Classes.Eq (Math.LinearMap.Category.Instances.Deriving.DualVectorFromBasis v) instance (Math.LinearMap.Category.Instances.Deriving.BasisGeneratedSpace v, Data.VectorSpace.Scalar (Data.VectorSpace.Scalar v) GHC.Types.~ Data.VectorSpace.Scalar v, Data.MemoTrie.HasTrie (Data.Basis.Basis v), GHC.Classes.Eq v, GHC.Classes.Eq (Data.Basis.Basis v)) => Math.LinearMap.Category.Class.LinearSpace (Math.LinearMap.Category.Instances.Deriving.DualVectorFromBasis v) instance (Math.LinearMap.Category.Instances.Deriving.BasisGeneratedSpace v, Math.VectorSpace.Docile.FiniteDimensional v, Data.VectorSpace.Scalar (Data.VectorSpace.Scalar v) GHC.Types.~ Data.VectorSpace.Scalar v, Data.MemoTrie.HasTrie (Data.Basis.Basis v), GHC.Classes.Ord (Data.Basis.Basis v), GHC.Classes.Eq v, GHC.Classes.Eq (Data.Basis.Basis v)) => Math.VectorSpace.Docile.FiniteDimensional (Math.LinearMap.Category.Instances.Deriving.DualVectorFromBasis v) instance (Math.LinearMap.Category.Instances.Deriving.BasisGeneratedSpace v, Math.VectorSpace.Docile.FiniteDimensional v, GHC.Real.Real (Data.VectorSpace.Scalar v), Data.VectorSpace.Scalar (Data.VectorSpace.Scalar v) GHC.Types.~ Data.VectorSpace.Scalar v, Data.MemoTrie.HasTrie (Data.Basis.Basis v), GHC.Classes.Ord (Data.Basis.Basis v), GHC.Classes.Eq v, GHC.Classes.Eq (Data.Basis.Basis v)) => Math.VectorSpace.Docile.SemiInner (Math.LinearMap.Category.Instances.Deriving.DualVectorFromBasis v) instance Data.AdditiveGroup.AdditiveGroup v => Math.Manifold.Core.PseudoAffine.Semimanifold (Math.LinearMap.Category.Instances.Deriving.DualVectorFromBasis v) instance Data.AdditiveGroup.AdditiveGroup v => Data.AffineSpace.AffineSpace (Math.LinearMap.Category.Instances.Deriving.DualVectorFromBasis v) instance Data.AdditiveGroup.AdditiveGroup v => Math.Manifold.Core.PseudoAffine.PseudoAffine (Math.LinearMap.Category.Instances.Deriving.DualVectorFromBasis v) instance (Data.Basis.HasBasis v, Math.LinearMap.Category.Class.Num' (Data.VectorSpace.Scalar v), Data.VectorSpace.Scalar (Data.VectorSpace.Scalar v) GHC.Types.~ Data.VectorSpace.Scalar v, Data.MemoTrie.HasTrie (Data.Basis.Basis v), GHC.Classes.Eq v) => Math.LinearMap.Category.Class.TensorSpace (Math.LinearMap.Category.Instances.Deriving.DualVectorFromBasis v) instance Data.Default.Class.Default Math.LinearMap.Category.Instances.Deriving.FiniteDimensionalFromBasisDerivationConfig instance Data.Default.Class.Default Math.LinearMap.Category.Instances.Deriving.LinearSpaceFromBasisDerivationConfig -- | Warning: These lenses will probably change their domain in the -- future. module Math.LinearMap.Category.Derivatives (/∂) :: forall s x y v q. (Num' s, LinearSpace x, LinearSpace y, LinearSpace v, LinearSpace q, s ~ Scalar x, s ~ Scalar y, s ~ Scalar v, s ~ Scalar q) => Lens' y v -> Lens' x q -> Lens' (LinearMap s x y) (LinearMap s q v) infixr 7 /∂ (*∂) :: forall s a q v. (Num' s, OneDimensional q, LinearSpace q, LinearSpace v, s ~ Scalar a, s ~ Scalar q, s ~ Scalar v) => q -> Lens' a (LinearMap s q v) -> Lens' a v infixr 7 *∂ (.∂) :: forall s x z. (Fractional' s, LinearSpace x, s ~ Scalar x, LinearSpace z, s ~ Scalar z) => (forall w. (LinearSpace w, Scalar w ~ s) => Lens' (TensorProduct x w) w) -> Lens' x z -> Lens' (SymmetricTensor s x) z infixr 7 .∂ module Math.LinearMap.Category -- | A linear map, represented simply as a Haskell function tagged with the -- type of scalar with respect to which it is linear. Many (sparse) -- linear mappings can actually be calculated much more efficiently if -- you don't represent them with any kind of matrix, but just as a -- function (which is after all, mathematically speaking, what a linear -- map foremostly is). -- -- However, if you sum up many LinearFunctions – which you can -- simply do with the VectorSpace instance – they will become ever -- slower to calculate, because the summand-functions are actually -- computed individually and only the results summed. That's where -- LinearMap is generally preferrable. You can always convert -- between these equivalent categories using arr. newtype LinearFunction s v w LinearFunction :: (v -> w) -> LinearFunction s v w [getLinearFunction] :: LinearFunction s v w -> v -> w -- | Infix synonym of LinearFunction, without explicit mention of -- the scalar type. type v -+> w = LinearFunction (Scalar w) v w -- | A bilinear function is a linear function mapping to a linear function, -- or equivalently a 2-argument function that's linear in each argument -- independently. Note that this can not be uncurried to a linear -- function with a tuple argument (this would not be linear but -- quadratic). type Bilinear v w y = LinearFunction (Scalar v) v (LinearFunction (Scalar v) w y) -- | Use a function as a linear map. This is only well-defined if the -- function is linear (this condition is not checked). lfun :: (EnhancedCat f (LinearFunction s), LinearSpace u, TensorSpace v, Scalar u ~ s, Scalar v ~ s, Object f u, Object f v) => (u -> v) -> f u v (-+$>) :: LinearFunction s v w -> v -> w infixr 0 -+$> -- | The tensor product between one space's dual space and another space is -- the space spanned by vector–dual-vector pairs, in bra-ket -- notation written as -- --
--   m = ∑ |w⟩⟨v|
--   
-- -- Any linear mapping can be written as such a (possibly infinite) sum. -- The TensorProduct data structure only stores the linear -- independent parts though; for simple finite-dimensional spaces this -- means e.g. LinearMap ℝ ℝ³ ℝ³ effectively boils down to -- an ordinary matrix type, namely an array of column-vectors -- |w⟩. -- -- (The ⟨v| dual-vectors are then simply assumed to come from -- the canonical basis.) -- -- For bigger spaces, the tensor product may be implemented in a more -- efficient sparse structure; this can be defined in the -- TensorSpace instance. newtype LinearMap s v w LinearMap :: TensorProduct (DualVector v) w -> LinearMap s v w [getLinearMap] :: LinearMap s v w -> TensorProduct (DualVector v) w -- | Infix synonym for LinearMap, without explicit mention of the -- scalar type. type v +> w = LinearMap (Scalar v) v w -- | The dual operation to the tuple constructor, or rather to the -- &&& fanout operation: evaluate two (linear) -- functions in parallel and sum up the results. The typical use is to -- concatenate “row vectors” in a matrix definition. (⊕) :: (u +> w) -> (v +> w) -> (u, v) +> w infixr 6 ⊕ -- | ASCII version of (>+<) :: (u +> w) -> (v +> w) -> (u, v) +> w infixr 6 >+< -- | For real matrices, this boils down to transpose. For free -- complex spaces it also incurs complex conjugation. -- -- The signature can also be understood as -- --
--   adjoint :: (v +> w) -> (DualVector w +> DualVector v)
--   
-- -- Or -- --
--   adjoint :: (DualVector v +> DualVector w) -> (w +> v)
--   
-- -- But not (v+>w) -> (w+>v), in general (though -- in a Hilbert space, this too is equivalent, via riesz -- isomorphism). adjoint :: forall v w. (LinearSpace v, LinearSpace w, Scalar v ~ Scalar w) => (v +> DualVector w) -+> (w +> DualVector v) (<.>^) :: LinearSpace v => DualVector v -> v -> Scalar v infixr 7 <.>^ -- | A linear map that simply projects from a dual vector in u to -- a vector in v. -- --
--   (du -+|> v) u  ≡  v ^* (du <.>^ u)
--   
(-+|>) :: (EnhancedCat f (LinearFunction s), LSpace u, LSpace v, Scalar u ~ s, Scalar v ~ s, Object f u, Object f v) => DualVector u -> v -> f u v infixr 7 -+|> -- | Tensor products are most interesting because they can be used to -- implement linear mappings, but they also form a useful vector space on -- their own right. newtype Tensor s v w Tensor :: TensorProduct v w -> Tensor s v w [getTensorProduct] :: Tensor s v w -> TensorProduct v w -- | Infix synonym for Tensor, without explicit mention of the -- scalar type. type v ⊗ w = Tensor (Scalar v) v w infixl 7 ⊗ -- | Infix version of tensorProduct. (⊗) :: forall v w. (TensorSpace v, TensorSpace w, Scalar w ~ Scalar v, Num' (Scalar v)) => v -> w -> v ⊗ w infixl 7 ⊗ newtype SymmetricTensor s v SymTensor :: Tensor s v v -> SymmetricTensor s v [getSymmetricTensor] :: SymmetricTensor s v -> Tensor s v v squareV :: (Num' s, s ~ Scalar v) => TensorSpace v => v -> SymmetricTensor s v squareVs :: (Num' s, s ~ Scalar v) => TensorSpace v => [v] -> SymmetricTensor s v type v ⊗〃+> w = LinearMap (Scalar v) (SymmetricTensor (Scalar v) v) w currySymBilin :: LinearSpace v => (v ⊗〃+> w) -+> (v +> (v +> w)) -- | A positive (semi)definite symmetric bilinear form. This gives rise to -- a norm thus: -- --
--   Norm n |$| v = √(n v <.>^ v)
--   
--   
-- -- Strictly speaking, this type is neither strong enough nor general -- enough to deserve the name Norm: it includes proper -- Seminorms (i.e. m|$|v ≡ 0 does not guarantee v == -- zeroV), but not actual norms such as the ℓ₁-norm on ℝⁿ (Taxcab -- norm) or the supremum norm. However, 𝐿₂-like norms are the only ones -- that can really be formulated without any basis reference; and -- guaranteeing positive definiteness through the type system is scarcely -- practical. newtype Norm v Norm :: (v -+> DualVector v) -> Norm v [applyNorm] :: Norm v -> v -+> DualVector v -- | A “norm” that may explicitly be degenerate, with m|$|v ⩵ 0 -- for some v ≠ zeroV. type Seminorm v = Norm v -- | A seminorm defined by -- --
--   ‖v‖ = √(∑ᵢ ⟨dᵢ|v⟩²)
--   
-- -- for some dual vectors dᵢ. If given a complete basis of the -- dual space, this generates a proper Norm. -- -- If the dᵢ are a complete orthonormal system, you get the -- euclideanNorm (in an inefficient form). spanNorm :: forall v. LSpace v => [DualVector v] -> Seminorm v -- | The canonical standard norm (2-norm) on inner-product / Hilbert -- spaces. euclideanNorm :: HilbertSpace v => Norm v -- | Use a Norm to measure the length / norm of a vector. -- --
--   euclideanNorm |$| v  ≡  √(v <.> v)
--   
(|$|) :: (LSpace v, Floating (Scalar v)) => Seminorm v -> v -> Scalar v infixr 0 |$| -- | The squared norm. More efficient than |$| because that needs to -- take the square root. normSq :: LSpace v => Seminorm v -> v -> Scalar v -- | “Partially apply” a norm, yielding a dual vector (i.e. a linear form -- that accepts the second argument of the scalar product). -- --
--   (euclideanNorm <$| v) <.>^ w  ≡  v <.> w
--   
-- -- See also |&>. (<$|) :: LSpace v => Norm v -> v -> DualVector v infixr 0 <$| -- | Scale the result of a norm with the absolute of the given number. -- --
--   scaleNorm μ n |$| v = abs μ * (n|$|v)
--   
-- -- Equivalently, this scales the norm's unit ball by the reciprocal of -- that factor. scaleNorm :: forall v. LSpace v => Scalar v -> Norm v -> Norm v normSpanningSystem :: SimpleSpace v => Seminorm v -> [DualVector v] normSpanningSystem' :: (FiniteDimensional v, IEEE (Scalar v)) => Seminorm v -> [v] -- | A multidimensional variance of points v with some -- distribution can be considered a norm on the dual space, quantifying -- for a dual vector dv the expectation value of -- (dv.^v)^2. type Variance v = Norm (DualVector v) spanVariance :: forall v. LSpace v => [v] -> Variance v -- | Flipped, “ket” version of <$|. -- --
--   v <.>^ (w |&> euclideanNorm)  ≡  v <.> w
--   
(|&>) :: LSpace v => DualVector v -> Variance v -> v infixl 1 |&> -- | Inverse of spanVariance. Equivalent to -- normSpanningSystem on the dual space. varianceSpanningSystem :: forall v. SimpleSpace v => Variance v -> [v] -- | A proper norm induces a norm on the dual space – the “reciprocal -- norm”. (The orthonormal systems of the norm and its dual are mutually -- conjugate.) The dual norm of a seminorm is undefined. dualNorm :: SimpleSpace v => Norm v -> Variance v -- | dualNorm in the opposite direction. This is actually -- self-inverse; with dualSpaceWitness you can replace each with -- the other direction. dualNorm' :: forall v. SimpleSpace v => Variance v -> Norm v -- | Interpret a variance as a covariance between two subspaces, and -- normalise it by the variance on u. The result is effectively -- the linear regression coefficient of a simple regression of the -- vectors spanning the variance. dependence :: forall u v. (SimpleSpace u, SimpleSpace v, Scalar u ~ Scalar v) => Variance (u, v) -> u +> v -- | spanNorm / spanVariance are inefficient if the number of -- vectors is similar to the dimension of the space, or even larger than -- it. Use this function to optimise the underlying operator to a dense -- matrix representation. densifyNorm :: forall v. LSpace v => Norm v -> Norm v -- | Like densifyNorm, but also perform a “sanity check” to -- eliminate NaN etc. problems. wellDefinedNorm :: forall v. LinearSpace v => Norm v -> Maybe (Norm v) -- | Inverse function application, aka solving of a linear system: -- --
--   f \$ f $ v  ≡  v
--   
--   f $ f \$ u  ≡  u
--   
-- -- If f does not have full rank, the behaviour is undefined. -- However, it does not need to be a proper isomorphism: the first of the -- above equations is still fulfilled if only f is -- injective (overdetermined system) and the second if it is -- surjective. -- -- If you want to solve for multiple RHS vectors, be sure to partially -- apply this operator to the linear map, like -- --
--   map (f \$) [v₁, v₂, ...]
--   
-- -- Since most of the work is actually done in triangularising the -- operator, this may be much faster than -- --
--   [f \$ v₁, f \$ v₂, ...]
--   
(\$) :: forall u v. (SimpleSpace u, SimpleSpace v, Scalar u ~ Scalar v) => (u +> v) -> v -> u infixr 0 \$ pseudoInverse :: forall u v. (SimpleSpace u, SimpleSpace v, Scalar u ~ Scalar v) => (u +> v) -> v +> u -- | Approximation of the determinant. roughDet :: (FiniteDimensional v, IEEE (Scalar v)) => (v +> v) -> Scalar v -- | Simple wrapper of linearRegression. linearRegressionW :: forall s x m y. (LinearSpace x, SimpleSpace y, SimpleSpace m, Scalar x ~ s, Scalar y ~ s, Scalar m ~ s, RealFrac' s) => Norm y -> (x -> m +> y) -> [(x, y)] -> m linearRegression :: forall s x m y. (LinearSpace x, SimpleSpace y, SimpleSpace m, Scalar x ~ s, Scalar y ~ s, Scalar m ~ s, RealFrac' s) => (x -> m +> y) -> [(x, (y, Norm y))] -> LinearRegressionResult x y m data LinearRegressionResult x y m -- | How well the data uncertainties match the deviations from the model's -- synthetic data. χν² = 1ν · ∑ δy² σy² Where -- ν is the number of degrees of freedom (data values minus -- model parameters), δy = m x - yd is the deviation from given -- data to the data the model would predict (for each sample point), and -- σy is the a-priori measurement uncertainty of the data -- points. -- -- Values χν²>1 indicate that the data could not be described -- satisfyingly; χν²≪1 suggests overfitting or that the data -- uncertainties have been postulated too high. -- -- http://adsabs.harvard.edu/abs/1997ieas.book.....T -- -- If the model is exactly determined or even underdetermined (i.e. -- ν≤0) then χν² is undefined. linearFit_χν² :: LinearRegressionResult x y m -> Scalar m -- | The model that best corresponds to the data, in a least-squares sense -- WRT the supplied norm on the data points. In other words, this is the -- model that minimises ∑ δy² / σy². linearFit_bestModel :: LinearRegressionResult x y m -> m linearFit_modelUncertainty :: LinearRegressionResult x y m -> Norm m -- | Simple automatic finding of the eigenvalues and -vectors of a -- Hermitian operator, in reasonable approximation. -- -- This works by spanning a QR-stabilised Krylov basis with -- constructEigenSystem until it is complete -- (roughEigenSystem), and then properly decoupling the system -- with finishEigenSystem (based on two iterations of shifted -- Givens rotations). -- -- This function is a tradeoff in performance vs. accuracy. Use -- constructEigenSystem and finishEigenSystem directly for -- more quickly computing a (perhaps incomplete) approximation, or for -- more precise results. eigen :: (FiniteDimensional v, HilbertSpace v, IEEE (Scalar v)) => (v +> v) -> [(Scalar v, v)] -- | Lazily compute the eigenbasis of a linear map. The algorithm is -- essentially a hybrid of Lanczos/Arnoldi style Krylov-spanning and -- QR-diagonalisation, which we don't do separately but interleave -- at each step. -- -- The size of the eigen-subbasis increases with each step until the -- space's dimension is reached. (But the algorithm can also be used for -- infinite-dimensional spaces.) constructEigenSystem :: (LSpace v, RealFloat (Scalar v)) => Norm v -> Scalar v -> (v -+> v) -> [v] -> [[Eigenvector v]] -- | Find a system of vectors that approximate the eigensytem, in the sense -- that: each true eigenvalue is represented by an approximate one, and -- that is closer to the true value than all the other approximate EVs. -- -- This function does not make any guarantees as to how well a single -- eigenvalue is approximated, though. roughEigenSystem :: (FiniteDimensional v, IEEE (Scalar v)) => Norm v -> (v +> v) -> [Eigenvector v] finishEigenSystem :: forall v. (LSpace v, RealFloat (Scalar v)) => Norm v -> [Eigenvector v] -> [Eigenvector v] data Eigenvector v Eigenvector :: Scalar v -> v -> v -> v -> Scalar v -> Eigenvector v -- | The estimated eigenvalue λ. [ev_Eigenvalue] :: Eigenvector v -> Scalar v -- | Normalised vector v that gets mapped to a multiple, namely: [ev_Eigenvector] :: Eigenvector v -> v -- | f $ v ≡ λ *^ v . [ev_FunctionApplied] :: Eigenvector v -> v -- | Deviation of v to (f$v)^/λ. Ideally, this would of -- course be equal. [ev_Deviation] :: Eigenvector v -> v -- | Squared norm of the deviation. [ev_Badness] :: Eigenvector v -> Scalar v -- | The workhorse of this package: most functions here work on vector -- spaces that fulfill the LSpace v constraint. -- -- In summary, this is a VectorSpace with an implementation for -- TensorProduct v w, for any other space w, and -- with a DualVector space. This fulfills DualVector -- (DualVector v) ~ v (this constraint is encapsulated in -- DualSpaceWitness). -- -- To make a new space of yours an LSpace, you must define -- instances of TensorSpace and LinearSpace. In fact, -- LSpace is equivalent to LinearSpace, but makes the -- condition explicit that the scalar and dual vectors also form a linear -- space. LinearSpace only stores that constraint in -- dualSpaceWitness (to avoid UndecidableSuperclasses). type LSpace v = (LinearSpace v, LinearSpace (Scalar v), LinearSpace (DualVector v), Num' (Scalar v)) class (VectorSpace v, PseudoAffine v) => TensorSpace v where { -- | The internal representation of a Tensor product. -- -- For Euclidean spaces, this is generally constructed by replacing each -- s scalar field in the v vector with an entire -- w vector. I.e., you have then a “nested vector” or, if -- v is a DualVector / “row vector”, a matrix. type family TensorProduct v w :: *; } scalarSpaceWitness :: TensorSpace v => ScalarSpaceWitness v linearManifoldWitness :: TensorSpace v => LinearManifoldWitness v zeroTensor :: (TensorSpace v, TensorSpace w, Scalar w ~ Scalar v) => v ⊗ w toFlatTensor :: TensorSpace v => v -+> (v ⊗ Scalar v) fromFlatTensor :: TensorSpace v => (v ⊗ Scalar v) -+> v addTensors :: (TensorSpace v, TensorSpace w, Scalar w ~ Scalar v) => (v ⊗ w) -> (v ⊗ w) -> v ⊗ w addTensors :: (TensorSpace v, AdditiveGroup (TensorProduct v w)) => (v ⊗ w) -> (v ⊗ w) -> v ⊗ w subtractTensors :: (TensorSpace v, TensorSpace v, TensorSpace w, Scalar w ~ Scalar v) => (v ⊗ w) -> (v ⊗ w) -> v ⊗ w subtractTensors :: (TensorSpace v, AdditiveGroup (TensorProduct v w)) => (v ⊗ w) -> (v ⊗ w) -> v ⊗ w scaleTensor :: (TensorSpace v, TensorSpace w, Scalar w ~ Scalar v) => Bilinear (Scalar v) (v ⊗ w) (v ⊗ w) scaleTensor :: (TensorSpace v, VectorSpace (TensorProduct v w), Scalar (TensorProduct v w) ~ Scalar v) => Bilinear (Scalar v) (v ⊗ w) (v ⊗ w) negateTensor :: (TensorSpace v, TensorSpace w, Scalar w ~ Scalar v) => (v ⊗ w) -+> (v ⊗ w) negateTensor :: (TensorSpace v, AdditiveGroup (TensorProduct v w)) => (v ⊗ w) -+> (v ⊗ w) tensorProduct :: (TensorSpace v, TensorSpace w, Scalar w ~ Scalar v) => Bilinear v w (v ⊗ w) tensorProducts :: (TensorSpace v, TensorSpace w, Scalar w ~ Scalar v) => [(v, w)] -> v ⊗ w transposeTensor :: (TensorSpace v, TensorSpace w, Scalar w ~ Scalar v) => (v ⊗ w) -+> (w ⊗ v) fmapTensor :: (TensorSpace v, TensorSpace w, TensorSpace x, Scalar w ~ Scalar v, Scalar x ~ Scalar v) => Bilinear (w -+> x) (v ⊗ w) (v ⊗ x) fzipTensorWith :: (TensorSpace v, TensorSpace u, TensorSpace w, TensorSpace x, Scalar u ~ Scalar v, Scalar w ~ Scalar v, Scalar x ~ Scalar v) => Bilinear ((w, x) -+> u) (v ⊗ w, v ⊗ x) (v ⊗ u) coerceFmapTensorProduct :: (TensorSpace v, Functor p) => p v -> Coercion a b -> Coercion (TensorProduct v a) (TensorProduct v b) -- | “Sanity-check” a vector. This typically amounts to detecting any NaN -- components, which should trigger a Nothing result. Otherwise, -- the result should be Just the input, but may also be -- optimised / memoised if applicable (i.e. for function spaces). wellDefinedVector :: TensorSpace v => v -> Maybe v -- | “Sanity-check” a vector. This typically amounts to detecting any NaN -- components, which should trigger a Nothing result. Otherwise, -- the result should be Just the input, but may also be -- optimised / memoised if applicable (i.e. for function spaces). wellDefinedVector :: (TensorSpace v, Eq v) => v -> Maybe v wellDefinedTensor :: (TensorSpace v, TensorSpace w, Scalar w ~ Scalar v) => (v ⊗ w) -> Maybe (v ⊗ w) -- | The class of vector spaces v for which LinearMap s -- v w is well-implemented. class (TensorSpace v, Num (Scalar v)) => LinearSpace v where { -- | Suitable representation of a linear map from the space v to -- its field. -- -- For the usual euclidean spaces, you can just define -- DualVector v = v. (In this case, a dual vector will be -- just a “row vector” if you consider v-vectors as “column -- vectors”. LinearMap will then effectively have a matrix -- layout.) type family DualVector v :: *; } dualSpaceWitness :: LinearSpace v => DualSpaceWitness v linearId :: LinearSpace v => v +> v idTensor :: LinearSpace v => v ⊗ DualVector v sampleLinearFunction :: (LinearSpace v, TensorSpace w, Scalar v ~ Scalar w) => (v -+> w) -+> (v +> w) toLinearForm :: LinearSpace v => DualVector v -+> (v +> Scalar v) fromLinearForm :: LinearSpace v => (v +> Scalar v) -+> DualVector v coerceDoubleDual :: LinearSpace v => Coercion v (DualVector (DualVector v)) trace :: LinearSpace v => (v +> v) -+> Scalar v contractTensorMap :: (LinearSpace v, TensorSpace w, Scalar w ~ Scalar v) => (v +> (v ⊗ w)) -+> w contractMapTensor :: (LinearSpace v, TensorSpace w, Scalar w ~ Scalar v) => (v ⊗ (v +> w)) -+> w contractTensorFn :: forall w. (LinearSpace v, TensorSpace w, Scalar w ~ Scalar v) => (v -+> (v ⊗ w)) -+> w contractLinearMapAgainst :: (LinearSpace v, LinearSpace w, Scalar w ~ Scalar v) => Bilinear (v +> w) (w -+> v) (Scalar v) applyDualVector :: (LinearSpace v, LinearSpace v) => Bilinear (DualVector v) v (Scalar v) applyLinear :: (LinearSpace v, TensorSpace w, Scalar w ~ Scalar v) => Bilinear (v +> w) v w composeLinear :: (LinearSpace v, LinearSpace w, TensorSpace x, Scalar w ~ Scalar v, Scalar x ~ Scalar v) => Bilinear (w +> x) (v +> w) (v +> x) tensorId :: (LinearSpace v, LinearSpace w, Scalar w ~ Scalar v) => (v ⊗ w) +> (v ⊗ w) applyTensorFunctional :: (LinearSpace v, LinearSpace u, Scalar u ~ Scalar v) => Bilinear (DualVector (v ⊗ u)) (v ⊗ u) (Scalar v) applyTensorLinMap :: (LinearSpace v, LinearSpace u, TensorSpace w, Scalar u ~ Scalar v, Scalar w ~ Scalar v) => Bilinear ((v ⊗ u) +> w) (v ⊗ u) w useTupleLinearSpaceComponents :: (LinearSpace v, v ~ (x, y)) => ((LinearSpace x, LinearSpace y, Scalar x ~ Scalar y) => φ) -> φ -- | SemiInner is the class of vector spaces with finite subspaces -- in which you can define a basis that can be used to project from the -- whole space into the subspace. The usual application is for using a -- kind of Galerkin method to give an approximate solution (see -- \$) to a linear equation in a possibly infinite-dimensional -- space. -- -- Of course, this also works for spaces which are already -- finite-dimensional themselves. class LinearSpace v => SemiInner v -- | Lazily enumerate choices of a basis of functionals that can be made -- dual to the given vectors, in order of preference (which roughly -- means, large in the normal direction.) I.e., if the vector 𝑣 -- is assigned early to the dual vector 𝑣', then (𝑣' $ -- 𝑣) should be large and all the other products comparably small. -- -- The purpose is that we should be able to make this basis orthonormal -- with a ~Gaussian-elimination approach, in a way that stays numerically -- stable. This is otherwise known as the choice of a pivot -- element. -- -- For simple finite-dimensional array-vectors, you can easily define -- this method using cartesianDualBasisCandidates. dualBasisCandidates :: SemiInner v => [(Int, v)] -> Forest (Int, DualVector v) tensorDualBasisCandidates :: (SemiInner v, SemiInner w, Scalar w ~ Scalar v) => [(Int, v ⊗ w)] -> Forest (Int, DualVector (v ⊗ w)) symTensorDualBasisCandidates :: SemiInner v => [(Int, SymmetricTensor (Scalar v) v)] -> Forest (Int, SymmetricTensor (Scalar v) (DualVector v)) symTensorTensorDualBasisCandidates :: forall w. (SemiInner v, SemiInner w, Scalar w ~ Scalar v) => [(Int, SymmetricTensor (Scalar v) v ⊗ w)] -> Forest (Int, SymmetricTensor (Scalar v) v +> DualVector w) cartesianDualBasisCandidates :: [DualVector v] -> (v -> [ℝ]) -> [(Int, v)] -> Forest (Int, DualVector v) embedFreeSubspace :: forall v t r. (HasCallStack, SemiInner v, RealFrac' (Scalar v), Traversable t) => t v -> Maybe (ReifiedLens' v (t (Scalar v))) class (LSpace v, Eq v) => FiniteDimensional v where { -- | Whereas Basis-values refer to a single basis vector, a single -- SubBasis value represents a collection of such basis vectors, -- which can be used to associate a vector with a list of coefficients. -- -- For spaces with a canonical finite basis, SubBasis does not -- actually need to contain any information, it can simply have the full -- finite basis as its only value. Even for large sparse spaces, it -- should only have a very coarse structure that can be shared by many -- vectors. data family SubBasis v :: *; } entireBasis :: FiniteDimensional v => SubBasis v enumerateSubBasis :: FiniteDimensional v => SubBasis v -> [v] subbasisDimension :: FiniteDimensional v => SubBasis v -> Int -- | Split up a linear map in “column vectors” WRT some suitable basis. decomposeLinMap :: (FiniteDimensional v, LSpace w, Scalar w ~ Scalar v) => (v +> w) -> (SubBasis v, DList w) -- | Expand in the given basis, if possible. Else yield a superbasis of the -- given one, in which this is possible, and the decomposition -- therein. decomposeLinMapWithin :: (FiniteDimensional v, LSpace w, Scalar w ~ Scalar v) => SubBasis v -> (v +> w) -> Either (SubBasis v, DList w) (DList w) -- | Assemble a vector from coefficients in some basis. Return any excess -- coefficients. recomposeSB :: FiniteDimensional v => SubBasis v -> [Scalar v] -> (v, [Scalar v]) recomposeSBTensor :: (FiniteDimensional v, FiniteDimensional w, Scalar w ~ Scalar v) => SubBasis v -> SubBasis w -> [Scalar v] -> (v ⊗ w, [Scalar v]) recomposeLinMap :: (FiniteDimensional v, LSpace w, Scalar w ~ Scalar v) => SubBasis v -> [w] -> (v +> w, [w]) -- | Given a function that interprets a coefficient-container as a vector -- representation, build a linear function mapping to that space. recomposeContraLinMap :: (FiniteDimensional v, LinearSpace w, Scalar w ~ Scalar v, Functor f) => (f (Scalar w) -> w) -> f (DualVector v) -> v +> w recomposeContraLinMapTensor :: (FiniteDimensional v, FiniteDimensional u, LinearSpace w, Scalar u ~ Scalar v, Scalar w ~ Scalar v, Functor f) => (f (Scalar w) -> w) -> f (v +> DualVector u) -> (v ⊗ u) +> w -- | The existance of a finite basis gives us an isomorphism between a -- space and its dual space. Note that this isomorphism is not natural -- (i.e. it depends on the actual choice of basis, unlike everything else -- in this library). uncanonicallyFromDual :: FiniteDimensional v => DualVector v -+> v uncanonicallyToDual :: FiniteDimensional v => v -+> DualVector v tensorEquality :: (FiniteDimensional v, TensorSpace w, Eq w, Scalar w ~ Scalar v) => (v ⊗ w) -> (v ⊗ w) -> Bool dualFinitenessWitness :: FiniteDimensional v => DualFinitenessWitness v dualFinitenessWitness :: (FiniteDimensional v, FiniteDimensional (DualVector v)) => DualFinitenessWitness v addV :: AdditiveGroup w => LinearFunction s (w, w) w scale :: VectorSpace v => Bilinear (Scalar v) v v inner :: InnerSpace v => Bilinear v v (Scalar v) flipBilin :: Bilinear v w y -> Bilinear w v y bilinearFunction :: (v -> w -> y) -> Bilinear v w y (.⊗) :: (TensorSpace v, HasBasis v, TensorSpace w, Num' (Scalar v), Scalar v ~ Scalar w) => Basis v -> w -> v ⊗ w infixr 7 .⊗ -- | Generalised multiplication operation. This subsumes <.>^ -- and *^. For scalars therefore also *, and for -- InnerSpace, <.>. (·) :: TensorQuot v w => (v ⨸ w) -> v -> w infixl 7 · type DualSpace v = v +> Scalar v -- | The Riesz representation theorem provides an isomorphism -- between a Hilbert space and its (continuous) dual space. riesz :: forall v. (FiniteDimensional v, InnerSpace v, SimpleSpace v) => DualVector v -+> v coRiesz :: forall v. (LSpace v, InnerSpace v) => v -+> DualVector v -- | Functions are generally a pain to display, but since linear -- functionals in a Hilbert space can be represented by vectors in -- that space, this can be used for implementing a Show instance. showsPrecAsRiesz :: forall v. (FiniteDimensional v, InnerSpace v, Show v, HasBasis (Scalar v), Basis (Scalar v) ~ ()) => Int -> DualSpace v -> ShowS -- | Outer product of a general v-vector and a basis element from -- w. Note that this operation is in general pretty inefficient; -- it is provided mostly to lay out matrix definitions neatly. (.<) :: (FiniteDimensional v, Num' (Scalar v), InnerSpace v, LSpace w, HasBasis w, Scalar v ~ Scalar w) => Basis w -> v -> v +> w infixl 7 .< class (FiniteDimensional v, HasBasis v) => TensorDecomposable v tensorDecomposition :: TensorDecomposable v => (v ⊗ w) -> [(Basis v, w)] showsPrecBasis :: TensorDecomposable v => Int -> Basis v -> ShowS class TensorDecomposable u => RieszDecomposable u rieszDecomposition :: (RieszDecomposable u, FiniteDimensional v, v ~ DualVector v, Scalar v ~ Scalar u) => (v +> u) -> [(Basis u, v)] tensorDecomposeShowsPrec :: forall u v s. (TensorDecomposable u, FiniteDimensional v, Show v, Scalar u ~ s, Scalar v ~ s) => Int -> Tensor s u v -> ShowS -- | This is the preferred method for showing linear maps, resulting in a -- matrix view involving the .< operator. We don't provide a -- generic Show instance; to make linear maps with your own -- finite-dimensional type V (with scalar S) showable, -- this is the recommended way: -- --
--   instance RieszDecomposable V where
--     rieszDecomposition = ...
--   instance (FiniteDimensional w, w ~ DualVector w, Scalar w ~ S, Show w)
--         => Show (LinearMap S w V) where
--     showsPrec = rieszDecomposeShowsPrec
--   
--   
-- -- Note that the custom type should always be the codomain type, -- whereas the domain should be kept parametric. rieszDecomposeShowsPrec :: forall u v s. (RieszDecomposable u, FiniteDimensional v, v ~ DualVector v, Show v, Scalar u ~ s, Scalar v ~ s) => Int -> LinearMap s v u -> ShowS type HilbertSpace v = (LSpace v, InnerSpace v, DualVector v ~ v) type SimpleSpace v = (FiniteDimensional v, FiniteDimensional (DualVector v), SemiInner v, SemiInner (DualVector v), RealFrac' (Scalar v)) -- | A space in which you can use · both for scaling with a real -- number, and as dot-product for obtaining such a number. type RealSpace v = (LinearSpace v, Scalar v ~ ℝ, TensorQuot v ℝ, (v ⨸ ℝ) ~ DualVector v, TensorQuot v v, (v ⨸ v) ~ ℝ) class (Num s, LinearSpace s, FreeVectorSpace s) => Num' s closedScalarWitness :: Num' s => ClosedScalarWitness s closedScalarWitness :: (Num' s, Scalar s ~ s, DualVector s ~ s) => ClosedScalarWitness s trivialTensorWitness :: Num' s => TrivialTensorWitness s w trivialTensorWitness :: (Num' s, w ~ TensorProduct s w) => TrivialTensorWitness s w type Fractional' s = (Num' s, Fractional s, Eq s, VectorSpace s) type RealFrac' s = (Fractional' s, IEEE s, InnerSpace s) type RealFloat' s = (RealFrac' s, Floating s) type LinearShowable v = (Show v, RieszDecomposable v) data ClosedScalarWitness s [ClosedScalarWitness] :: (Scalar s ~ s, DualVector s ~ s) => ClosedScalarWitness s data TrivialTensorWitness s w [TrivialTensorWitness] :: w ~ TensorProduct s w => TrivialTensorWitness s w data ScalarSpaceWitness v [ScalarSpaceWitness] :: (Num' (Scalar v), Scalar (Scalar v) ~ Scalar v) => ScalarSpaceWitness v data DualSpaceWitness v [DualSpaceWitness] :: (LinearSpace (Scalar v), DualVector (Scalar v) ~ Scalar v, LinearSpace (DualVector v), Scalar (DualVector v) ~ Scalar v, DualVector (DualVector v) ~ v) => DualSpaceWitness v data LinearManifoldWitness v [LinearManifoldWitness] :: (Needle v ~ v, AffineSpace v, Diff v ~ v) => LinearManifoldWitness v data DualFinitenessWitness v [DualFinitenessWitness] :: FiniteDimensional (DualVector v) => DualSpaceWitness v -> DualFinitenessWitness v -- | Modify a norm in such a way that the given vectors lie within its unit -- ball. (Not optimally – the unit ball may be bigger than -- necessary.) relaxNorm :: forall v. SimpleSpace v => Norm v -> [v] -> Norm v transformNorm :: forall v w. (LSpace v, LSpace w, Scalar v ~ Scalar w) => (v +> w) -> Norm w -> Norm v transformVariance :: forall v w. (LSpace v, LSpace w, Scalar v ~ Scalar w) => (v +> w) -> Variance v -> Variance w -- | The unique positive number whose norm is 1 (if the norm is not -- constant zero). findNormalLength :: forall s. RealFrac' s => Norm s -> Maybe s -- | Unsafe version of findNormalLength, only works reliable if the -- norm is actually positive definite. normalLength :: forall s. RealFrac' s => Norm s -> s summandSpaceNorms :: forall u v. (SimpleSpace u, SimpleSpace v, Scalar u ~ Scalar v) => Norm (u, v) -> (Norm u, Norm v) sumSubspaceNorms :: forall u v. (LSpace u, LSpace v, Scalar u ~ Scalar v) => Norm u -> Norm v -> Norm (u, v) -- | For any two norms, one can find a system of co-vectors that, with -- suitable coefficients, spans either of them: if shSys = -- sharedNormSpanningSystem n₀ n₁, then -- --
--   n₀ = spanNorm $ fst$shSys
--   
-- -- and -- --
--   n₁ = spanNorm [dv^*η | (dv,η)<-shSys]
--   
-- -- A rather crude approximation (roughEigenSystem) is used in this -- function, so do not expect the above equations to hold with great -- accuracy. sharedNormSpanningSystem :: SimpleSpace v => Norm v -> Seminorm v -> [(DualVector v, Scalar v)] -- | Like 'sharedNormSpanningSystem n₀ n₁', but allows either of the -- norms to be singular. -- --
--   n₀ = spanNorm [dv | (dv, Just _)<-shSys]
--   
-- -- and -- --
--   n₁ = spanNorm $ [dv^*η | (dv, Just η)<-shSys]
--                   ++ [ dv | (dv, Nothing)<-shSys]
--   
-- -- You may also interpret a Nothing here as an “infinite -- eigenvalue”, i.e. it is so small as an spanning vector of n₀ -- that you would need to scale it by ∞ to use it for spanning -- n₁. sharedSeminormSpanningSystem :: forall v. SimpleSpace v => Seminorm v -> Seminorm v -> [(DualVector v, Maybe (Scalar v))] -- | A system of vectors which are orthogonal with respect to both of the -- given seminorms. (In general they are not orthonormal to either -- of them.) sharedSeminormSpanningSystem' :: forall v. SimpleSpace v => Seminorm v -> Seminorm v -> [v] convexPolytopeHull :: forall v. SimpleSpace v => [v] -> [DualVector v] symmetricPolytopeOuterVertices :: forall v. SimpleSpace v => [DualVector v] -> [v] instance (GHC.Show.Show v, GHC.Show.Show (Data.VectorSpace.Scalar v)) => GHC.Show.Show (Math.LinearMap.Category.Eigenvector v) instance Math.LinearMap.Category.Class.LSpace v => GHC.Base.Monoid (Math.LinearMap.Category.Seminorm v) instance Math.LinearMap.Category.Class.LSpace v => GHC.Base.Semigroup (Math.LinearMap.Category.Norm v) instance (Math.VectorSpace.Docile.SimpleSpace v, GHC.Show.Show (Math.LinearMap.Category.Class.DualVector v)) => GHC.Show.Show (Math.LinearMap.Category.Norm v)