Skip to content

Commit

Permalink
substitute
Browse files Browse the repository at this point in the history
  • Loading branch information
stla committed Apr 22, 2024
1 parent 7b44608 commit 945f37a
Show file tree
Hide file tree
Showing 8 changed files with 164 additions and 28 deletions.
2 changes: 2 additions & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,8 @@ export(rSymbolicQspray)
export(showSymbolicQspray)
export(showSymbolicQsprayX1X2X3)
export(showSymbolicQsprayXYZ)
export(substituteParameters)
export(substituteVariables)
export(symbolicQspray_from_list)
exportMethods(as.symbolicQspray)
exportMethods(changeVariables)
Expand Down
81 changes: 69 additions & 12 deletions R/evaluation.R
Original file line number Diff line number Diff line change
@@ -1,11 +1,71 @@
#' @title Evaluation of a 'symbolicQspray' object
#' @description Evaluates a \code{symbolicQspray} object by substituting some
#' values to the exterior variables or the main variables or both.
#' @title Assign values to the parameters of a 'symbolicQspray'
#' @description Substitutes some values to the parameters of a
#' \code{symbolicQspray} polynomial.
#'
#' @param Qspray a \code{symbolicQspray} object
#' @param a vector of values to be substituted to the exterior variables:
#' @param values vector of values to be substituted to the parameters; these
#' values must be coercable to \code{bigq} numbers
#'
#' @return A \code{qspray} object.
#' @export
#'
#' @seealso Use \code{\link{changeParameters}} to apply a transformation of the
#' parameters. Use \code{\link{substituteVariables}} to substitute some
#' values to the variables.
#'
#' @examples
#' library(symbolicQspray)
#' f <- function(a1, a2, X, Y) {
#' (a1 + 2)*X^2*Y + (a2/(a1^2+a2))*X*Y
#' }
#' Qspray <- f(qlone(1), qlone(2), Qlone(1), Qlone(2))
#' a <- c(2, "2/3")
#' ( qspray <- substituteParameters(Qspray, values = a) )
#' a <- gmp::as.bigq(a)
#' qspray == f(a[1], a[2], qlone(1), qlone(2)) ## should be TRUE
substituteParameters <- function(Qspray, values) {
evalSymbolicQspray(Qspray, a = values, X = NULL)
}

#' @title Assign values to the variables of a 'symbolicQspray'
#' @description Substitutes some values to the variables of a
#' \code{symbolicQspray} polynomial.
#'
#' @param Qspray a \code{symbolicQspray} object
#' @param values vector of values to be substituted to the parameters; these
#' values must be coercable to \code{bigq} numbers
#'
#' @return A \code{ratioOfQsprays} object.
#' @export
#'
#' @seealso Use \code{\link{changeVariables}} to apply a transformation of the
#' variables. Use \code{\link{substituteParameters}} to substitute some
#' values to the parameters.
#'
#' @examples
#' library(symbolicQspray)
#' f <- function(a1, a2, X, Y) {
#' (a1 + 2)*X^2*Y + (a2/(a1^2+a2))*X*Y
#' }
#' a1 <- qlone(1); a2 <- qlone(2)
#' Qspray <- f(a1, a2, Qlone(1), Qlone(2))
#' values <- c(3, "2/3")
#' ( rOQ <- substituteVariables(Qspray, values) )
#' values <- gmp::as.bigq(values)
#' rOQ == f(a1, a2, values[1], values[2]) ## should be TRUE
substituteVariables <- function(Qspray, values) {
evalSymbolicQspray(Qspray, a = NULL, X = values)
}

#' @title Evaluation of a 'symbolicQspray' polynomial
#' @description Evaluates a \code{symbolicQspray} polynomial by substituting
#' some values to the parameters (same as \code{\link{substituteParameters}})
#' or to the variables (same as \code{\link{substituteVariables}}) or both.
#'
#' @param Qspray a \code{symbolicQspray} object
#' @param a vector of values to be substituted to the parameters;
#' these values must be coercable to \code{bigq} numbers
#' @param X vector of values to be substituted to the main variables: these
#' @param X vector of values to be substituted to the variables; these
#' values must be coercable to \code{bigq} numbers
#'
#' @return If both \code{a} and \code{X} are \code{NULL}, this returns the
Expand All @@ -19,19 +79,16 @@
#'
#' @examples
#' library(symbolicQspray)
#' a1 <- qlone(1)
#' a2 <- qlone(2)
#' X1 <- Qlone(1)
#' X2 <- Qlone(2)
#' X3 <- Qlone(3)
#' a1 <- qlone(1); a2 <- qlone(2)
#' X1 <- Qlone(1); X2 <- Qlone(2); X3 <- Qlone(3)
#' ( Qspray <- (a1 + 2)*X1^2*X2 + (a2/(a1^2+a2))*X1*X2*X3 )
#' a <- c(2, 3)
#' X <- c(4, 3, 2)
#' ( qspray <- evalSymbolicQspray(Qspray, a = a) )
#' ( roq <- evalSymbolicQspray(Qspray, X = X) )
#' ( rOQ <- evalSymbolicQspray(Qspray, X = X) )
#' evalSymbolicQspray(Qspray, a = a, X = X)
#' evalQspray(qspray, X)
#' evalRatioOfQsprays(roq, a)
#' evalRatioOfQsprays(rOQ, a)
evalSymbolicQspray <- function(Qspray, a = NULL, X = NULL) {
if(!is.null(a)) {
coeffs <- c_bigq(lapply(Qspray@coeffs, evalRatioOfQsprays, values_re = a))
Expand Down
6 changes: 4 additions & 2 deletions R/transformation.R
Original file line number Diff line number Diff line change
Expand Up @@ -173,7 +173,8 @@ setGeneric("changeVariables")
#' @export
#'
#' @seealso If you want to change the parameters of a symbolic qspray, use
#' \code{\link{changeParameters}}.
#' \code{\link{changeParameters}}. If you want to assign some values to
#' its variables, see \code{\link{substituteVariables}}.
#'
#' @examples
#' library(symbolicQspray)
Expand Down Expand Up @@ -237,7 +238,8 @@ setMethod(
#' @export
#'
#' @seealso If you want to change the variables of a symbolic qspray, use
#' \code{\link{changeVariables}}.
#' \code{\link{changeVariables}}. If you want to assign some values to
#' its parameters, use \code{\link{substituteParameters}}.
#'
#' @examples
#' library(symbolicQspray)
Expand Down
3 changes: 2 additions & 1 deletion man/changeParameters.Rd

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

3 changes: 2 additions & 1 deletion man/changeVariables.Rd

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

22 changes: 10 additions & 12 deletions man/evalSymbolicQspray.Rd

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

37 changes: 37 additions & 0 deletions man/substituteParameters.Rd

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

38 changes: 38 additions & 0 deletions man/substituteVariables.Rd

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

0 comments on commit 945f37a

Please sign in to comment.