Skip to content

Commit

Permalink
involvedVariables
Browse files Browse the repository at this point in the history
  • Loading branch information
stla committed May 7, 2024
1 parent 8631f77 commit 06e17d3
Show file tree
Hide file tree
Showing 8 changed files with 99 additions and 31 deletions.
1 change: 1 addition & 0 deletions .Rbuildignore
Original file line number Diff line number Diff line change
Expand Up @@ -6,3 +6,4 @@
^inst/trash$
^inst/RDS$
^cran-comments\.md$
^CRAN-SUBMISSION$
7 changes: 4 additions & 3 deletions DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Package: symbolicQspray
Title: Multivariate Polynomials with Symbolic Parameters in their Coefficients
Version: 1.0.0
Version: 1.0.0.9000
Authors@R:
person("Stéphane", "Laurent", , "laurent_step@outlook.fr", role = c("aut", "cre"))
Description: Introduces the 'symbolicQspray' objects. Such an object
Expand All @@ -16,9 +16,10 @@ Description: Introduces the 'symbolicQspray' objects. Such an object
License: GPL-3
URL: https://github.com/stla/symbolicQspray
BugReports: https://github.com/stla/symbolicQspray/issues
Remotes: stla/qspray, stla/ratioOfQsprays
Depends:
qspray (>= 3.0.0),
ratioOfQsprays
qspray (>= 3.0.0.9000),
ratioOfQsprays (>= 1.0.0.9000)
Imports:
gmp,
methods,
Expand Down
2 changes: 2 additions & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -24,6 +24,7 @@ exportMethods(changeVariables)
exportMethods(compactSymmetricQspray)
exportMethods(getCoefficient)
exportMethods(getConstantTerm)
exportMethods(involvedVariables)
exportMethods(isConstant)
exportMethods(isQone)
exportMethods(isQzero)
Expand All @@ -48,6 +49,7 @@ importFrom(qspray,compactSymmetricQspray)
importFrom(qspray,evalQspray)
importFrom(qspray,getCoefficient)
importFrom(qspray,getConstantTerm)
importFrom(qspray,involvedVariables)
importFrom(qspray,isConstant)
importFrom(qspray,isQone)
importFrom(qspray,isQzero)
Expand Down
4 changes: 2 additions & 2 deletions R/internal.R
Original file line number Diff line number Diff line change
Expand Up @@ -115,8 +115,8 @@ arity <- function(qspray) {
}

powersMatrix <- function(qspray) {
n <- arity(qspray)
if(n == -Inf) {
n <- numberOfVariables(qspray)
if(n == 0L) {
matrix(NA_integer_, 0L, 0L)
} else {
do.call(rbind, lapply(qspray@powers, grow, n = n))
Expand Down
61 changes: 47 additions & 14 deletions R/queries.R
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@
NULL

setGeneric("numberOfVariables")
setGeneric("involvedVariables")
setGeneric("numberOfTerms")
setGeneric("getCoefficient")
setGeneric("getConstantTerm")
Expand All @@ -14,13 +15,14 @@ setGeneric("isQone")
#' @aliases numberOfVariables,symbolicQspray-method
#' @docType methods
#' @importFrom qspray numberOfVariables
#' @title Number of variables in a 'symbolicQspray' polynomial
#' @title Number of variables of a 'symbolicQspray' polynomial
#' @description Number of variables involved in a \code{symbolicQspray} object.
#'
#' @param x a \code{symbolicQspray} object
#'
#' @return An integer.
#' @export
#' @seealso \code{\link{involvedVariables}}.
#' @note The number of variables in the \code{symbolicQspray} object
#' \code{Qlone(d)} is \code{d}, not \code{1}.
setMethod(
Expand All @@ -30,6 +32,39 @@ setMethod(
}
)

#' @name involvedVariables
#' @aliases involvedVariables,symbolicQspray-method
#' @docType methods
#' @importFrom qspray involvedVariables
#' @title Variables involved in a 'symbolicQspray' polynomial
#' @description Variables involved in a \code{symbolicQspray} object.
#'
#' @param x a \code{symbolicQspray} object
#'
#' @return A vector of integers. Each integer represents the index of a
#' variable involved in \code{x}.
#' @export
#' @seealso \code{\link{numberOfVariables}}.
#' @examples
#' a1 <- qlone(1); a2 <- qlone(2)
#' X <- Qlone(1); Z <- Qlone(3)
#' Qspray <- (a1/a2)*X^2 + (a1/(a1+a2))*X*Z + a2^2/a1
#' involvedVariables(Qspray) # should be c(1L, 3L)
setMethod(
"involvedVariables", "symbolicQspray",
function(x) {
if(isConstant(x)) {
integer(0L)
} else {
M <- powersMatrix(x)
tests <- apply(M, 2L, function(col) {
any(col != 0L)
})
which(tests)
}
}
)

#' @name numberOfTerms
#' @aliases numberOfTerms,symbolicQspray-method
#' @docType methods
Expand All @@ -54,27 +89,25 @@ setMethod(
#' @docType methods
#' @importFrom qspray getCoefficient
#' @title Get a coefficient in a 'symbolicQspray' polynomial
#' @description Get the coefficient corresponding to the given sequence of
#' exponents.
#' @description Get the coefficient of the term with the given monomial.
#'
#' @param qspray a \code{symbolicQspray} object
#' @param exponents a vector of exponents
#' @param exponents a vector of exponents, thereby defining a monomial;
#' trailing zeros are ignored
#'
#' @return The coefficient as a \code{ratioOfQsprays} object.
#' @return The coefficient, \code{ratioOfQsprays} object.
#' @export
#' @importFrom gmp as.bigq
#' @importFrom ratioOfQsprays showRatioOfQspraysOption<-
#' @importFrom ratioOfQsprays showRatioOfQspraysOption<- as.ratioOfQsprays
#'
#' @examples
#' library(qspray)
#' x <- qlone(1)
#' y <- qlone(2)
#' p <- 2*x^2 + 3*y - 5
#' getCoefficient(p, 2) # coefficient of x^2
#' a1 <- qlone(1); a2 <- qlone(2)
#' X <- Qlone(1); Y <- Qlone(2)
#' p <- 2*(a1/a2)*X^2 + (a1/(a1+a2))*Y + a2^2/a1
#' getCoefficient(p, 2) # coefficient of X^2
#' getCoefficient(p, c(2, 0)) # same as getCoefficient(p, 2)
#' getCoefficient(p, c(0, 1)) # coefficient of y (= x^0.y^1)
#' getCoefficient(p, c(0, 1)) # coefficient of Y (because Y=X^0.Y^1)
#' getCoefficient(p, 0) # the constant term
#' getCoefficient(p, 3) # coefficient of x^3
#' getCoefficient(p, 3) # coefficient of X^3
setMethod(
"getCoefficient", c("symbolicQspray", "numeric"),
function(qspray, exponents) {
Expand Down
21 changes: 10 additions & 11 deletions man/getCoefficient.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

29 changes: 29 additions & 0 deletions man/involvedVariables.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

5 changes: 4 additions & 1 deletion man/numberOfVariables.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

0 comments on commit 06e17d3

Please sign in to comment.