-- 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.1.0.1 module Math.VectorSpace.ZeroDimensional data ZeroDim s Origin :: ZeroDim s instance GHC.Base.Monoid (Math.VectorSpace.ZeroDimensional.ZeroDim s) instance Data.AffineSpace.AffineSpace (Math.VectorSpace.ZeroDimensional.ZeroDim s) instance Data.AdditiveGroup.AdditiveGroup (Math.VectorSpace.ZeroDimensional.ZeroDim s) instance Data.VectorSpace.VectorSpace (Math.VectorSpace.ZeroDimensional.ZeroDim s) instance Data.Basis.HasBasis (Math.VectorSpace.ZeroDimensional.ZeroDim s) 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) -- | 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 -- | ASCII version of '⊕' (>+<) :: (u +> w) -> (v +> w) -> (u, v) +> w -- | 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 :: (LSpace v, LSpace w, Scalar v ~ Scalar w) => (v +> DualVector w) -+> (w +> DualVector v) (<.>^) :: LSpace v => DualVector v -> v -> Scalar v -- | 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 -- | Infix version of tensorProduct. (⊗) :: (LSpace v, LSpace w, Scalar w ~ Scalar v) => v -> w -> 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 :: 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 -- | 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 --(<$|) :: LSpace v => Norm v -> v -> DualVector v -- | 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 :: LSpace v => Scalar v -> Norm v -> Norm v normSpanningSystem :: SimpleSpace v => Norm v -> [DualVector v] normSpanningSystem' :: (FiniteDimensional v, IEEE (Scalar v)) => Norm 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 :: LSpace v => [v] -> Variance 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 -- | 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 :: (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 :: LSpace v => Norm v -> 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₂, ...] --(\$) :: (SimpleSpace u, SimpleSpace v, Scalar u ~ Scalar v) => (u +> v) -> v -> u pseudoInverse :: (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 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 :: (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 these two supposedly equivalent expressions. [ev_Deviation] :: Eigenvector v -> v -- | Squared norm of the deviation, normalised by the eigenvalue. [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: -- --
-- n₀ = spanNorm $ fst$shSys ---- -- and -- --
-- n₁ = spanNorm [dv^*η | (dv,η)<-shSys] --sharedNormSpanningSystem :: SimpleSpace v => Norm v -> Norm v -> [(DualVector v, Scalar 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 => Data.Semigroup.Semigroup (Math.LinearMap.Category.Norm v) instance Math.LinearMap.Category.Class.LSpace v => GHC.Base.Monoid (Math.LinearMap.Category.Seminorm v) instance (Math.VectorSpace.Docile.SimpleSpace v, GHC.Show.Show (Math.LinearMap.Category.Class.DualVector v)) => GHC.Show.Show (Math.LinearMap.Category.Norm v)