| Copyright | (c) Ross Paterson 2021 |
|---|---|
| License | BSD-style (see the file LICENSE) |
| Maintainer | [email protected] |
| Stability | provisional |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Data.YAP.FiniteMap
Description
An example instance of the algebraic classes: the monoid, group,
semiring or ring of functions with finite support (i.e. mapping
finitely inputs to non-zero outputs), or equivalently a free module
extended to a with multiplication by convolution.
These functions may be interpreted as generalized formal polynomials, mapping exponents to corresponding coefficients (a monoid algebra).
Synopsis
- data FiniteMap i a
- constant :: (Monoid i, Eq a, AdditiveMonoid a) => a -> FiniteMap i a
- indeterminate :: Semiring a => i -> FiniteMap i a
- fromAssocs :: (Ord i, Eq a, AdditiveMonoid a) => [(i, a)] -> FiniteMap i a
- find :: (Ord i, AdditiveMonoid a) => FiniteMap i a -> i -> a
- assocs :: FiniteMap i a -> [(i, a)]
- evaluateWith :: Semiring b => (i -> b) -> (a -> b) -> FiniteMap i a -> b
- type Multiset a = FiniteMap a Natural
- type FreeRing v a = FiniteMap [v] a
- type OrdinaryPolynomial a = FiniteMap (Sum Natural) a
- type LaurentPolynomial a = FiniteMap (Sum Integer) a
- type GenPolynomial v a = FiniteMap (Sum (Multiset v)) a
- genIndeterminate :: Semiring a => v -> GenPolynomial v a
- prettyGenPolynomial :: (Eq a, Show a, Semiring a, Ord v) => (v -> String) -> GenPolynomial v a -> String
- newtype Xs = X Natural
- prettyXs :: Xs -> String
Functions with finite support
A function with finite support to an additive monoid,
i.e. mapping all but a finite number of inputs to zero.
The special case where the element type a is the Boolean semiring
is equivalent to Data.YAP.FiniteSet.
Instances
| (Show i, Show a) => Show (FiniteMap i a) Source # | |
| (Eq i, Eq a) => Eq (FiniteMap i a) Source # | |
| (Ord i, Ord a) => Ord (FiniteMap i a) Source # | |
Defined in Data.YAP.FiniteMap Methods compare :: FiniteMap i a -> FiniteMap i a -> Ordering # (<) :: FiniteMap i a -> FiniteMap i a -> Bool # (<=) :: FiniteMap i a -> FiniteMap i a -> Bool # (>) :: FiniteMap i a -> FiniteMap i a -> Bool # (>=) :: FiniteMap i a -> FiniteMap i a -> Bool # | |
| (Ord i, Eq a, AbelianGroup a) => AbelianGroup (FiniteMap i a) Source # | |
| (Ord i, Eq a, AdditiveMonoid a) => AdditiveMonoid (FiniteMap i a) Source # | Pointwise addition |
| (Ord i, Monoid i, Eq a, FromRational a) => FromRational (FiniteMap i a) Source # | |
Defined in Data.YAP.FiniteMap Methods fromRational :: Rational -> FiniteMap i a # | |
| (Ord i, Monoid i, Eq a, Ring a) => Ring (FiniteMap i a) Source # | |
Defined in Data.YAP.FiniteMap Methods fromInteger :: Integer -> FiniteMap i a # | |
| (Ord i, Monoid i, Eq a, Semiring a) => Semiring (FiniteMap i a) Source # | Discrete convolution |
Construction
indeterminate :: Semiring a => i -> FiniteMap i a Source #
A named indeterminate. Satisfies:
indeterminate mempty = one
indeterminate (i <> j) = indeterminate i * indeterminate j
indeterminate i * constant a = constant a * indeterminate i
fromAssocs :: (Ord i, Eq a, AdditiveMonoid a) => [(i, a)] -> FiniteMap i a Source #
Composite value
fromAssocs ts = sum [indeterminate i * constant a | (i, a) <- ts]
Queries
evaluateWith :: Semiring b => (i -> b) -> (a -> b) -> FiniteMap i a -> b Source #
Evaluate a finite map interpreted as a generalized polynomial, given valuations for the indeterminates and coefficients.
evaluateWith indeterminate constant = id
evaluateWith f g (indeterminate i) = f i
evaluateWith f g (constant a) = g a
Applications
type FreeRing v a = FiniteMap [v] a Source #
The free ring generated by non-commuting variables v and ring a.
Additive monoids: generalized polynomials
type OrdinaryPolynomial a = FiniteMap (Sum Natural) a Source #
Semiring (or ring) of ordinary polynomials in one indeterminate.
type LaurentPolynomial a = FiniteMap (Sum Integer) a Source #
Semiring (or ring) of Laurent polynomials in one indeterminate.
type GenPolynomial v a = FiniteMap (Sum (Multiset v)) a Source #
An implementation of semirings (or rings) of polynomials in several indeterminates, using a multiset to record the multiplicity of each indeterminate.
genIndeterminate :: Semiring a => v -> GenPolynomial v a Source #
A polynomial consisting of a single indeterminate
prettyGenPolynomial :: (Eq a, Show a, Semiring a, Ord v) => (v -> String) -> GenPolynomial v a -> String Source #
Pretty-print a general polynomial.
Counting partitions: Bell polynomials
A more involved example is exponential generating functions for Bell polynomials, which encode the ways a set of size \(n\) can be partitioned into \(k\) parts.
Using Data.YAP.PowerSeries.Maclaurin, an exponential generating function for the sequence of variables,
\[ \bar x (t) = \sum_{n=1}^\infty x_n \frac{t^n}{n!} \]
can be defined as
xs :: PowerSeries (GenPolynomial Xs Natural) xs = fromDerivatives (zero:map (genIndeterminate . X) (iterate (+one) one))
The exponential generating function for complete Bell polynomials is obtained by applying the exponential transform to this series:
\[ e^{ \bar x (t) } = 1 + \sum_{n=1}^\infty B_n(x_1,\ldots, x_n) \frac{t^n}{n!} \]
completeBell :: PowerSeries (GenPolynomial Xs Natural) completeBell = compose expS xs
In these polynomials, subscripts denote the size of each part, superscripts denote the number of parts of that size, and coefficients denote the number of ways of partitioning \(n\) elements into parts of those sizes. For example, the 4th entry is:
>>>(!!4) $ derivatives $ completeBellfromAssocs [ (Sum (fromAssocs [(X 1,1),(X 3,1)]),4), (Sum (fromAssocs [(X 1,2),(X 2,1)]),6), (Sum (fromAssocs [(X 1,4)]),1), (Sum (fromAssocs [(X 2,2)]),3), (Sum (fromAssocs [(X 4,1)]),1)]
This encodes the Bell polynomial
\[ B_4(x_1, x_2, x_3, x_4) = 4 x_1 x_3 + 6 x_1^2 x_2 + x_1^4 + 3 x_2^2 + x_4 \]
which says that a set of 4 elements may be partitioned in 4 ways into sets of size 1 and 3, in 6 ways into 2 sets of size 1 and one of size 2, in 1 way into 4 sets of size 1, and so on.
Each complete Bell polynomial \(B_n\) is the sum of \(n\) partial Bell polynomials \(B_{n,k}\) each describing partitions into \(k\) parts:
\[ B_n(x_1, \ldots, x_n) = \sum_{k=1}^n B_{n,k}(x_1,\ldots,x_{n-k+1}) \]
The exponential generating function for partial Bell polynomials is
\[ e^{ u \bar x (t) } = 1 + \sum_{n=1}^\infty \left( \sum_{k=1}^n B_{n,k}(x_1,\ldots,x_{n-k+1}) u^k \right) \frac{t^n}{n!} \]
partialBell :: PowerSeries (Polynomial (GenPolynomial Xs Natural)) partialBell = binomialType xs
For example, the 4th entry is:
>>>(!!4) $ derivatives $ partialBellfromCoefficients [ fromAssocs [], fromAssocs [(Sum (fromAssocs [(X 4,1)]),1)], fromAssocs [(Sum (fromAssocs [(X 1,1),(X 3,1)]),4),(Sum (fromAssocs [(X 2,2)]),3)], fromAssocs [(Sum (fromAssocs [(X 1,2),(X 2,1)]),6)], fromAssocs [(Sum (fromAssocs [(X 1,4)]),1)]]
This is a polynomial whose \(k\)th coefficient is the partial Bell polynomial \(B_{4,k}\):
\[ B_{4,1}(x_1, x_2, x_3, x_4) = x_4 \]
\[ B_{4,2}(x_1, x_2, x_3) = 4 x_1 x_3 + 3 x_2^2 \]
\[ B_{4,3}(x_1, x_2) = 6 x_1^2 x_2 \]
\[ B_{4,4}(x_1) = x_1^4 \]
For example, \(B_{4,2}\) describes the ways in which 4 elements can be divided into 2 parts: 4 ways into parts of sizes 1 and 3, and 3 ways into 2 parts of size 2.
Counting integer compositions
A similar construction with ordinary generating functions counts compositions of a non-negative integer \(n\), or equivalently segmentations of lists of length \(n\).
Using Data.YAP.PowerSeries, an ordinary generating function for the sequence of variables,
\[ \bar x (t) = \sum_{n=1}^\infty x_n t^n \]
can be defined as
xs :: PowerSeries (GenPolynomial Xs Natural) xs = fromDerivatives (zero:map (genIndeterminate . X) (iterate (+one) one))
The counterpart of the complete Bell polynomials is generated by \( 1 \over 1 - \bar x (t) \). In these polynomials, subscripts denote the size of each part, superscripts denote the number of those parts, and coefficients denote the number of ways of composing \(n\) elements into those parts. For example, the 4th entry is:
>>>(!!4) $ coefficients $ recipOneMinus `compose` xsfromAssocs [ (Sum (fromAssocs [(X 1,1),(X 3,1)]),2) (Sum (fromAssocs [(X 1,2),(X 2,1)]),3) (Sum (fromAssocs [(X 1,4)]),1) (Sum (fromAssocs [(X 2,2)]),1) (Sum (fromAssocs [(X 4,1)]),1)]
which encodes the polynomial
\[ 2 x_1 x_3 + 3 x_1^2 x_2 + x_1^4 + x_2^2 + x_4 \]
which says that 4 may be composed in 4 ways from 1 and 3 (1+3 and 3+1), in 3 ways from two 1s and one 2 (1+1+2, 1+2+1 and 2+1+1), and in 1 way from four 1s, two 2s or one 4.
>>>(!!4) $ coefficients $ riordan one xs
The counterpart of the partial Bell polynomials is generated by \( 1 \over 1 - u \bar x (t) \), an example of a Riordan array. For example, the 4th entry is:
>>>(!!4) $ coefficients $ riordan one xsfromCoefficients [ fromAssocs [] fromAssocs [(Sum (fromAssocs [(X 4,1)]),1)] fromAssocs [(Sum (fromAssocs [(X 1,1),(X 3,1)]),2),(Sum (fromAssocs [(X 2,2)]),1)] fromAssocs [(Sum (fromAssocs [(X 1,2),(X 2,1)]),3)] fromAssocs [(Sum (fromAssocs [(X 1,4)]),1)]]
which encodes the polynomials describing the compositions of 1, 2, 3 and 4 numbers respectively: \( x_4 \), \( 2 x_1 x_3 + x_2^2 \), \( 3 x_1^2 x_2 \) and \( x_1^4 \). For example, the compositions of two numbers forming 4 are two compositions of 1 and 3 and one composition of two 2s.
Switching from FiniteMap to FiniteSet would count
integer partitions.