diff --git a/R/matrixq.R b/R/matrixq.R index a72e99e5e86ec69d8bf62d06edbf4c84fa1b72ef..a7b6433bb71795a8e3f1ebc87fafb99349192f83 100644 --- a/R/matrixq.R +++ b/R/matrixq.R @@ -34,10 +34,10 @@ as.vector.bigq <- function(x, mode="any") { t.bigq <- function(x) .Call(bigq_transposeR, x) -cbind.bigq <- function(..., recursive = FALSE) +cbind.bigq <- function(..., deparse.level = 1) .Call(bigrational_cbind, list(...)) -rbind.bigq <- function(..., recursive = FALSE) +rbind.bigq <- function(..., deparse.level = 1) .Call(bigrational_rbind, list(...)) apply.bigq <- function(X, MARGIN, FUN, ...) diff --git a/R/matrixz.R b/R/matrixz.R index 9cb9fbc39051b1aa12b34001f06aaefa7959f3b7..e0312704c9869ddcef6c75e11b860a3bdb964875 100644 --- a/R/matrixz.R +++ b/R/matrixz.R @@ -103,11 +103,24 @@ ncol.bigz <- .ncolZQ ncol.bigq <- .ncolZQ -cbind.bigz <- function(..., recursive = FALSE) - .Call(biginteger_cbind, list(...)) +cbind.bigz <- function(..., deparse.level = 1) +{ + argL <- list(...) + if(any(vapply(argL, inherits, NA, what="bigq"))) + .Call(bigrational_cbind, argL) + else + .Call(biginteger_cbind, argL) +} + +rbind.bigz <- function(..., deparse.level = 1) +{ + argL <- list(...) + if(any(vapply(argL, inherits, NA, what="bigq"))) + .Call(bigrational_rbind, argL) + else + .Call(biginteger_rbind, argL) +} -rbind.bigz <- function(..., recursive = FALSE) - .Call(biginteger_rbind, list(...)) apply <- function(X, MARGIN, FUN, ...) UseMethod("apply") diff --git a/man/extract.Rd b/man/extract.Rd index 812d6775339903ec37dbaa0dc07c584b41ca38ff..be2ee3586e6865b81512132f4b3de2c7f13dfbfd 100644 --- a/man/extract.Rd +++ b/man/extract.Rd @@ -1,7 +1,7 @@ \name{extract} -\title{Extract or Replace Parts of an Object} - +\title{Extract or Replace Parts of a 'bigz' or 'bigq' Object} \alias{[.bigz} +%F\alias{[<-}% otherwise warning " Objects in \usage w/o \alias : '[<-' " \alias{[<-.bigz} \alias{[[.bigz} \alias{[[<-.bigz} @@ -13,23 +13,20 @@ \alias{[<-.bigq} \alias{[[.bigq} \alias{[[<-.bigq} - +%- \alias{c.bigq} \alias{rep.bigq} \alias{length.bigq} \alias{length<-.bigq} - \description{ Operators acting on vectors, arrays and lists to extract or replace subsets. } \usage{ \method{[}{bigz}(x, i=NULL, j=NULL, drop = TRUE) \method{[}{bigq}(x, i=NULL, j=NULL, drop = TRUE) - -##_______ In the following, only the bigq method is mentioned: ______ -%%FIXME: R-Rd bug in "rendering" this ( '[' is ok ) -%%FIXME \method{[<-}{bigq}(x, i=NULL, j=NULL, value) ==> "the same", manually : -%% x[i, j] <- value | But this gives ... WARNING .. Objects in \usage w/o \alias +%F \method{[<-}{bigq}(x, i=NULL, j=NULL, value) % ==> "the same", manually -- R check-bug: +%F x[i=NULL, j=NULL] <- value % still WARNING .. usage in doc.. .. but not in code: `[<-` +##___ In the following, only the bigq method is mentioned (but 'bigz' is "the same"): ___ \method{c}{bigq}(\dots, recursive = FALSE) \method{rep}{bigq}(x, times=1, length.out=NA, each=1, \dots) } @@ -37,18 +34,13 @@ \item{x}{\R object of class \code{"bigz"} or \code{"bigq"}, respectively.} \item{\dots}{further arguments, notably for \code{c()}.} \item{i,j}{indices, see standard \R subsetting and subassignment.} - \item{drop}{logical, unused here.} -%%FIXME \item{value}{\R object, typically of same \code{\link{class}} as -%%FIXME \code{x}, or also \code{\link{numeric}}.} + \item{drop}{logical, unused here, i.e., matrix subsetting \bold{always} returns a matrix, here!} +%F \item{value}{\R object, typically of same \code{\link{class}} as +%F \code{x}, or also \code{\link{numeric}}.} \item{times, length.out, each}{integer; typically only \emph{one} is specified; for more see \code{\link{rep}} (standard \R, package \pkg{base}). } - \item{recursive}{unused here} -} - -\note{ - Unlike standard matrices, \code{x[i]} and \code{x[i,]} do the same. - %% MM: hmm, just because of lazyness ?? + \item{recursive}{from \code{c()}'s default method; disregarded here} } \examples{ @@ -63,11 +55,11 @@ ## repeate a 5 times rep(a,5) - ## with matrix + ## with matrix: 3 x 2 m <- matrix.bigz(1:6,3) - ## these do the same: - m[1,] + m[1,] # the first row + m[1,, drop=TRUE] # the same: drop does *not* drop m[1] m[-c(2,3),] m[-c(2,3)] @@ -83,4 +75,3 @@ m[2,-1] <- 11 } \keyword{arith} - diff --git a/man/matrix.Rd b/man/matrix.Rd index 01353e9f613c59fa5dd6f4ce0c86ff9db65ea1cf..3d0bfe3204838d35e263a19ff2ac0dfb06cc36b8 100644 --- a/man/matrix.Rd +++ b/man/matrix.Rd @@ -73,6 +73,9 @@ is.matrixZQ(x) \S3method{\%*\%}{bigq}(x, y) \S3method{crossprod}{bigq}(x, y=NULL,...) \S3method{tcrossprod}{bigz}(x, y=NULL,...) + +\S3method{cbind}{bigz}(..., deparse.level=1) +\S3method{rbind}{bigq}(..., deparse.level=1) ## ..... etc } \arguments{ @@ -83,9 +86,11 @@ is.matrixZQ(x) columns, otherwise the matrix is filled by rows.} \item{dimnames}{not implemented for \code{"bigz"} or \code{"bigq"} matrices.} \item{mod}{optional modulus (when \code{data} is \code{"bigz"}).} - \item{...}{Not used} \item{x,y}{numeric, \code{bigz}, or \code{bigq} matrices or vectors.} + + \item{..., deparse.level}{arguments from the generic; \emph{not} made use + of, i.e., disregarded here.} } \details{ The extract function (\code{"["}) is the same use for vector or @@ -120,8 +125,14 @@ is.matrixZQ(x) \code{dim()}, \code{ncol()}, etc: integer or \code{NULL}, as for simple matrices. + + \code{cbind(x,y,...)} and \code{rbind(x,y,...)} now (2024-01, since + \pkg{gmp} version 0.9-5), do drop \code{deparse.level=.} instead of + wrongly creating an extra column or row \emph{and} the \code{"bigz"} + method takes all arguments into account and calls the \code{"bigq"} + method in case of arguments inheriting from \code{"\link{bigq}"}. } -\author{Antoine Lucas} +\author{Antoine Lucas and Martin Maechler} \seealso{Solving a linear system: \code{\link{solve.bigz}}. \code{\link[base]{matrix}} diff --git a/tests/basic-ex.R b/tests/basic-ex.R index 54dce267d4bcba8bc32c26c519b6ed22e2cbdd94..a83330aef621dbd28c12cbbb9d93e3d6783f273c 100644 --- a/tests/basic-ex.R +++ b/tests/basic-ex.R @@ -1,18 +1,6 @@ library(gmp) -## From ~/R/Pkgs/Matrix/inst/test-tools-1.R -- only for R <= 3.0.1 -- -##' @title Ensure evaluating 'expr' signals an error -##' @param expr -##' @return the caught error, invisibly -##' @author Martin Maechler -assertError <- function(expr, verbose=getOption("verbose")) { - d.expr <- deparse(substitute(expr)) - t.res <- tryCatch(expr, error = function(e) e) - if(!inherits(t.res, "error")) - stop(d.expr, "\n\t did not give an error", call. = FALSE) - if(verbose) cat("Asserted Error:", conditionMessage(t.res),"\n") - invisible(t.res) -} +assertError <- tools::assertError Z1 <- as.bigz(1) ; Z1[FALSE] Q1 <- as.bigq(1) ; Q1[FALSE] @@ -226,3 +214,26 @@ rev(B) # is sorted is.unsorted(rev(B))# TRUE but should be FALSE if(FALSE) ## not yet identical(sort(B), rev(B)) + +## all.equal() +stopifnot(exprs = { + is.character(all.equal(as.bigz(7), rep(7, 3))) +}) + +##------------------ cbind(), rbind() ------------------------------- + +a <- as.bigz(123); a[2] <- a[1] ; a[4] <- -4 +stopifnot(all.equal(a, c(123, 123, NA, -4))) # bigz <--> numeric + +(caa <- cbind(a,a)) # ok +stopifnot(exprs = { + identical(caa, cbind(a,a, deparse.level=1)) # did prepend a column of 1 + identical(t(caa), rbind(a,a, deparse.level=0)) # did prepend a row of 0 + identical(ca2 <- cbind(a/2, a, deparse.level=0), + cbind(a, a/2)[, 2:1]) # wrongly remained bigz, just using numerator... + identical(ra2 <- rbind(a/2, a, deparse.level=0), + rbind(a, a/2)[2:1, ]) # wrongly remained bigz ... + identical(dim(ca2), c(4L, 2L)) + identical(dim(ra2), c(2L, 4L)) +}) + diff --git a/tests/gmp-test.Rout.save b/tests/gmp-test.Rout.save index 151d32d706a47738fe580ebaa270cfb7d2eaba60..63ef3abe64842bfcad1e632b0b39eb2378a5bee1 100644 --- a/tests/gmp-test.Rout.save +++ b/tests/gmp-test.Rout.save @@ -1,6 +1,6 @@ -R Under development (unstable) (2022-10-23 r83164) -- "Unsuffered Consequences" -Copyright (C) 2022 The R Foundation for Statistical Computing +R version 4.3.2 Patched (2024-01-28 r85841) -- "Eye Holes" +Copyright (C) 2024 The R Foundation for Statistical Computing Platform: x86_64-pc-linux-gnu (64-bit) R is free software and comes with ABSOLUTELY NO WARRANTY. @@ -1171,7 +1171,7 @@ as.bgq((3,23)) 3 3 3 0 0 0 0 0 0 0 as.bigz(34) 34 34 34 34 34 34 as.bg(32,7) 32/7 32/7 32/7 32/7 32/7 32/7 -as.b(31,45) (31 %% 45) (31 %% 45) (31 %% 45) (31 %% 45) (31 %% 45) (31 %% 45) +as.b(31,45) (31 %% 45) (31 %% 45) 31 (31 %% 45) (31 %% 45) 31 NULL 23 23 23 3 3 3 NA <NA> NA NA <NA> NA NA -3L -3 -3 -3 -3 -3 -3 @@ -1189,7 +1189,7 @@ as.bgq((3,23)) 3 3 3 3 3 0 0 0 0 0 0 0 0 0 as.bigz(34) 34 34 34 34 34 34 34 34 as.bg(32,7) 32/7 32/7 32/7 32/7 32/7 32/7 32/7 32/7 -as.b(31,45) (31 %% 45) (31 %% 45) (31 %% 45) (31 %% 45) (31 %% 45) (31 %% 45) (31 %% 45) (31 %% 45) +as.b(31,45) (31 %% 45) (31 %% 45) (31 %% 45) (31 %% 45) (31 %% 45) (31 %% 45) 31 (31 %% 45) NULL 25 2.3 -4 4 0 34 32/7 (31 %% 45) NA <NA> <NA> <NA> <NA> <NA> NA NA NA -3L -3 -3 -3 -3 -3 -3 -3 -3 @@ -1229,7 +1229,7 @@ as.bgq((3,23)) 3 3 3 0 0 0 0 0 0 0 as.bigz(34) 34 34 34 34 34 34 as.bg(32,7) 32/7 32/7 32/7 32/7 32/7 32/7 -as.b(31,45) (31 %% 45) (31 %% 45) (31 %% 45) (31 %% 45) (31 %% 45) (31 %% 45) +as.b(31,45) (31 %% 45) (31 %% 45) 31 (31 %% 45) (31 %% 45) 31 NULL 23 23 23 3 3 3 NA <NA> NA NA <NA> NA NA -3L -3 -3 -3 -3 -3 -3 @@ -1247,7 +1247,7 @@ as.bgq((3,23)) 3 3 3 3 3 0 0 0 0 0 0 0 0 0 as.bigz(34) 34 34 34 34 34 34 34 34 as.bg(32,7) 32/7 32/7 32/7 32/7 32/7 32/7 32/7 32/7 -as.b(31,45) (31 %% 45) (31 %% 45) (31 %% 45) (31 %% 45) (31 %% 45) (31 %% 45) (31 %% 45) (31 %% 45) +as.b(31,45) (31 %% 45) (31 %% 45) (31 %% 45) (31 %% 45) (31 %% 45) (31 %% 45) 31 (31 %% 45) NULL 25 2.3 -4 4 0 34 32/7 (31 %% 45) NA <NA> <NA> <NA> <NA> <NA> NA NA NA -3L -3 -3 -3 -3 -3 -3 -3 -3