Skip to content

Commit

Permalink
README
Browse files Browse the repository at this point in the history
  • Loading branch information
stla committed Apr 20, 2024
1 parent f51ee7b commit 0af65a9
Show file tree
Hide file tree
Showing 4 changed files with 291 additions and 21 deletions.
2 changes: 1 addition & 1 deletion R/JacobiPolynomial.R
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,7 @@
JacobiPolynomial <- function(n) {
stopifnot(isPositiveInteger(n))
if(n == 0L) {
as.symbolicQspray(1L)
Qone()
} else if(n == 1L) {
X <- Qlone(1)
alpha <- qlone(1)
Expand Down
2 changes: 1 addition & 1 deletion R/queries.R
Original file line number Diff line number Diff line change
Expand Up @@ -210,5 +210,5 @@ setMethod(
#' JP <- JacobiPolynomial(4) # Jacobi polynomials have two parameters
#' numberOfParameters(JP)
numberOfParameters <- function(Qspray) {
max(vapply(Qspray@coeffs, numberOfVariables, integer(1L)))
max(c(0L, vapply(Qspray@coeffs, numberOfVariables, integer(1L))))
}
151 changes: 141 additions & 10 deletions README.Rmd
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,8 @@ title: "The 'symbolicQspray' package"
author: "Stéphane Laurent"
date: "`r Sys.Date()`"
output: github_document
editor_options:
chunk_output_type: console
---

***Multivariate polynomials with symbolic coefficients.***
Expand All @@ -11,21 +13,35 @@ output: github_document
[![R-CMD-check](https://github.com/stla/symbolicQspray/actions/workflows/R-CMD-check.yaml/badge.svg)](https://github.com/stla/symbolicQspray/actions/workflows/R-CMD-check.yaml)
<!-- badges: end -->

```{r setup, include=FALSE}
knitr::opts_chunk$set(echo = TRUE, collapse = TRUE, message = FALSE)
```

___

These notes about the **symbolicQspray** package assume that the reader is a
bit familiar with the [**qspray** package](https://github.com/stla/qspray)
and the [**ratioOfQsprays** package](https://github.com/stla/ratioOfQsprays).

A `symbolicQspray` object represents a multivariate polynomial whose
coefficients are fractions of polynomials with rational coefficients.
For example:
Actually (see our discussion in the next section), a `symbolicQspray` object
represents a *multivariate polynomial with parameters*. The parameters are
the variables of the fractions of polynomials.

```{r, message=FALSE, collapse=TRUE}
To construct a `symbolicQspray` polynomial, use `qlone` (from the **qspray**
package) to introduce the parameters and use `Qlone` to introduce the variables
of the polynomial:

```{r}
library(symbolicQspray)
f <- function(a1, a2, X1, X2, X3) {
(a1/(a2^2+1)) * X1^2*X2 + (a2+1) * X3 + a1/a2
}
# "exterior" variables, the ones occurring in the coefficients:
# parameters, the variables occurring in the coefficients:
a1 <- qlone(1)
a2 <- qlone(2)
# "main" variables:
# variables:
X1 <- Qlone(1)
X2 <- Qlone(2)
X3 <- Qlone(3)
Expand All @@ -35,13 +51,13 @@ X3 <- Qlone(3)

The fractions of polynomials such as the first coefficient `a1/(a2^2+1)`
in the above example are
[**ratioOfSprays**](https://github.com/stla/ratioOfQsprays) objects,
[**ratioOfQsprays**](https://github.com/stla/ratioOfQsprays) objects,
and the numerator and the denominator of a `ratioOfQsprays` are
[**qspray**](https://github.com/stla/qspray) objects.

Arithmetic on `symbolicQspray` objects is available:

```{r, message=FALSE, collapse=TRUE}
```{r}
Qspray^2
Qspray - Qspray
(Qspray - 1)^2
Expand All @@ -52,16 +68,16 @@ Qspray^2 - 2*Qspray + 1
## Evaluating a `symbolicQspray`

Substituting the "exterior" variables (the variables occurring in the ratios of
polynomials) yields a `qspray`:
polynomials, also called the *parameters* - see below) yields a `qspray` object:

```{r, message=FALSE, collapse=TRUE}
```{r}
a <- c(2, "3/2")
( qspray <- evalSymbolicQspray(Qspray, a = a) )
```

Substituting the "main" variables yields a `ratioOfQsprays` object:

```{r, message=FALSE, collapse=TRUE}
```{r}
X <- c(4, 3, "2/5")
( ratioOfQsprays <- evalSymbolicQspray(Qspray, X = X) )
```
Expand All @@ -73,7 +89,7 @@ that the polynomial variables `X`, `Y` and `Z` represent some indeterminate
with `ratioOfQsprays` objects. However this is not allowed.
We will discuss that, just after checking the consistency:

```{r, message=FALSE, collapse=TRUE}
```{r}
evalSymbolicQspray(Qspray, a = a, X = X)
evalQspray(qspray, X)
evalRatioOfQsprays(ratioOfQsprays, a)
Expand Down Expand Up @@ -108,13 +124,41 @@ The package provides some functions to perform elementary queries on a

```{r, collapse=TRUE}
numberOfVariables(Qspray)
numberOfParameters(Qspray)
numberOfTerms(Qspray)
getCoefficient(Qspray, c(2, 1))
getConstantTerm(Qspray)
isUnivariate(Qspray)
isConstant(Qspray)
```

## Transforming a `symbolicQspray`

You can derivate a `symbolicQspray` polynomial:

```{r}
derivSymbolicQspray(Qspray, 2) # derivative w.r.t. Y
```

You can permute its variables:

```{r}
swapVariables(Qspray, 2, 3) == f(a1, a2, X1, X3, X2)
```

You can perform polynomial transformations of its variables:

```{r}
changeVariables(Qspray, list(X1+1, X2^2, X1+X2+X3)) ==
f(a1, a2, X1+1, X2^2, X1+X2+X3)
```

You can also perform polynomial transformations of its parameters:

```{r}
changeParameters(Qspray, list(a1^2, a2^2)) == f(a1^2, a2^2, X1, X2, X3)
```


## Showing a `symbolicQspray`

Expand All @@ -133,6 +177,7 @@ When this is possible, the result of an arithmetic operation between two
`symbolicQspray` objects inherits the show options of the first operand:

```{r, collapse=TRUE}
set.seed(421)
( Q <- rSymbolicQspray() ) # a random symbolicQspray
Qspray + Q
```
Expand All @@ -142,6 +187,92 @@ This behavior is the same as the ones implemented in **qspray** and in
to use **symbolicQspray**.


## Application: Jacobi polynomials

The [Jacobi polynomials](https://en.wikipedia.org/wiki/Jacobi_polynomials)
are univariate polynomials depending on two parameters that we will denote by
`alpha` and `beta`. They are implemented in this package:

```{r}
JP <- JacobiPolynomial(2)
isUnivariate(JP)
numberOfParameters(JP)
showSymbolicQsprayOption(JP, "showRatioOfQsprays") <-
showRatioOfQspraysXYZ(c("alpha", "beta"))
JP
```

The implementation constructs these polynomials by using the
[recurrence relation](https://en.wikipedia.org/wiki/Jacobi_polynomials#Recurrence_relations).
This is a child game, one just has to copy the first two terms and this
recurrence relation:

```{r, eval=FALSE}
JacobiPolynomial <- function(n) {
stopifnot(isPositiveInteger(n))
if(n == 0) {
Qone()
} else if(n == 1) {
alpha <- qlone(1)
beta <- qlone(2)
X <- Qlone(1)
(alpha + 1) + (alpha + beta + 2) * (X - 1)/2
} else {
alpha <- qlone(1)
beta <- qlone(2)
X <- Qlone(1)
a <- n + alpha
b <- n + beta
c <- a + b
K <- 2 * n * (c - n) * (c - 2)
lambda1 <- ((c - 1) * (c * (c - 2) * X + (a - b) * (c - 2*n))) / K
lambda2 <- (2 * (a - 1) * (b - 1) * c) / K
(lambda1 * JacobiPolynomial(n - 1) - lambda2 * JacobiPolynomial(n - 2))
}
}
```

Up to a factor, the
[Gegenbauer polynomials](https://en.wikipedia.org/wiki/Gegenbauer_polynomials)
with parameter `alpha` coincide with the Jacobi polynomials with parameters
`alpha - 1/2` and `alpha - 1/2`. Let's derive them from the Jacobi polynomials,
as an exercise. The factor can be implemented as follows (see Wikipedia for its
formula):

```{r}
risingFactorial <- function(theta, n) {
toMultiply <- c(theta, lapply(seq_len(n-1), function(i) theta + i))
Reduce(`*`, toMultiply)
}
theFactor <- function(alpha, n) {
risingFactorial(2*alpha, n) / risingFactorial((2*alpha + 1)/2, n)
}
```

Now let's apply the formula given in the Wikipedia article:

```{r}
GegenbauerPolynomial <- function(n) {
alpha <- qlone(1)
P <- changeParameters(
JacobiPolynomial(n), list(alpha - "1/2", alpha - "1/2")
)
theFactor(alpha, n) * P
}
```

Let's check the recurrence relation given in the Wikipedia article is fulfilled:

```{r}
n <- 5
alpha <- qlone(1)
X <- Qlone(1)
(n+1)*GegenbauerPolynomial(n+1) ==
2*(n+alpha)*X*GegenbauerPolynomial(n) -
(n+2*alpha-1)*GegenbauerPolynomial(n-1)
```


## Application to Jack polynomials

The **symbolicQspray** package is used by the
Expand Down
Loading

0 comments on commit 0af65a9

Please sign in to comment.