diff --git a/com.oracle.truffle.r.native/gnur/tests/src/Examples/Sweave-test-1.R b/com.oracle.truffle.r.native/gnur/tests/src/Examples/Sweave-test-1.R index 2d69b7229b7645311532972155c76ddb5bd5e951..7dd3afaa300d07a25f7a34e01af9a3d5d3fa82f4 100644 --- a/com.oracle.truffle.r.native/gnur/tests/src/Examples/Sweave-test-1.R +++ b/com.oracle.truffle.r.native/gnur/tests/src/Examples/Sweave-test-1.R @@ -39,13 +39,17 @@ summary(iris) ################################################### ### code chunk number 6: Sweave-test-1.Rnw:53-55 ################################################### +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use library(graphics) pairs(iris) +} # [FastR] END Test snippet disabled due to graphics package use ################################################### ### code chunk number 7: Sweave-test-1.Rnw:63-64 ################################################### +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use boxplot(Sepal.Length~Species, data=iris) +} # [FastR] END Test snippet disabled due to graphics package use diff --git a/com.oracle.truffle.r.native/gnur/tests/src/Examples/base-Ex.R b/com.oracle.truffle.r.native/gnur/tests/src/Examples/base-Ex.R index 9617422e0ba6f57b3d40a64ac4f857ca648ceceb..c23dd0c01448592e36d1328b5d4894923dc13d09 100644 --- a/com.oracle.truffle.r.native/gnur/tests/src/Examples/base-Ex.R +++ b/com.oracle.truffle.r.native/gnur/tests/src/Examples/base-Ex.R @@ -23,6 +23,7 @@ x %/% 5 +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("Bessel") ### * Bessel @@ -104,6 +105,7 @@ title(expression(besselY(x, nu) * " " * graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("Colon") ### * Colon @@ -457,6 +459,7 @@ factor(letters[7:10])[2:3, drop = TRUE] +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("Extremes") ### * Extremes @@ -492,6 +495,7 @@ stopifnot(identical(D, cut01(D) ), +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("La_library") ### * La_library @@ -600,6 +604,7 @@ outer(x, x, "|") ## OR table +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("MathFun") ### * MathFun @@ -621,6 +626,7 @@ lines(spline(xx, sqrt(abs(xx)), n=101), col = "pink") +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("NA") ### * NA @@ -1027,6 +1033,7 @@ signif(x2, 3) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("Special") ### * Special @@ -1111,6 +1118,7 @@ stopifnot(all.equal( (choose(1/2, k.) -> ck.), graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("Startup") ### * Startup @@ -1396,7 +1404,8 @@ tx[ (x %% 1) %in% c(0, 0.5) ,] options(op) - + +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("Vectorize") ### * Vectorize @@ -1446,6 +1455,8 @@ combnV(4, 1:4, sum) +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("Version") ### * Version @@ -1470,6 +1481,7 @@ if(grepl("^darwin", R.version$os)) message("running on macOS") +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("abbreviate") ### * abbreviate @@ -1738,6 +1750,7 @@ apply(z, 3, function(x) seq_len(max(x))) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("args") ### * args @@ -1773,6 +1786,7 @@ args(`if`) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("array") ### * array @@ -2230,6 +2244,7 @@ stopifnot(identical(body(f), substitute({ y <- x^2; return(y) }))) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("bquote") ### * bquote @@ -2261,6 +2276,7 @@ bquote( function(x, y = .(default)) x+y ) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("by") ### * by @@ -2854,6 +2870,7 @@ comment(x) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("complex") ### * complex @@ -2899,6 +2916,7 @@ showC(NA_complex_) # always == (R = NA, I = NA) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("conditions") ### * conditions @@ -3161,6 +3179,7 @@ aggregate(1:24, list(day = cut(tm, "days", right = TRUE)), mean) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("cut") ### * cut @@ -3217,6 +3236,7 @@ cbind(lower = as.numeric( sub("\\((.+),.*", "\\1", labs) ), +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("data.class") ### * data.class @@ -3400,6 +3420,7 @@ stopifnot(identical(unname(le), lapply(exps, eval))) # and another "Ho!" +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("deparse") ### * deparse @@ -3431,6 +3452,7 @@ deparse(e, control = "all") +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("det") ### * det @@ -5671,6 +5693,7 @@ l10n_info() +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("lapply") ### * lapply @@ -5715,6 +5738,7 @@ bar(5, x = 3) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("length") ### * length @@ -5917,6 +5941,7 @@ library.dynam() +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("list") ### * list @@ -5959,6 +5984,7 @@ as.list(e1) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("list.files") ### * list.files @@ -6907,6 +6933,7 @@ flush(stderr()); flush(stdout()) ### ** Examples +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("notyet") ### * notyet @@ -6925,6 +6952,7 @@ barplot(1:5, inside = TRUE) # 'inside' is not yet used +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("nrow") ### * nrow @@ -7169,6 +7197,7 @@ fmode <- as.octmode("170") (fmode | "644") & "755" +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("on.exit") ### * on.exit @@ -7193,6 +7222,7 @@ par(opar) graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("options") ### * options @@ -9120,6 +9150,7 @@ withAutoprint({ formals(sourceDir); body(sourceDir) }, +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("split") ### * split @@ -9176,6 +9207,7 @@ split(1:10, 1:2) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("sprintf") ### * sprintf @@ -9554,6 +9586,7 @@ subset(state.x77, grepl("^M", nm), Illiteracy:Murder) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("substitute") ### * substitute @@ -9595,6 +9628,7 @@ typeof(s2(a)) # "symbol" +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("substr") ### * substr @@ -10284,7 +10318,9 @@ require(stats) ## Very simple use trace(sum) +if(FALSE) { # [FastR] BEGIN Following command triggers graphics package use hist(rnorm(100)) # shows about 3-4 calls to sum() +} # [FastR] END Following command triggers graphics package use untrace(sum) ## Show how pt() is called from inside power.t.test(): @@ -10569,6 +10605,7 @@ for(x in ll) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("unname") ### * unname @@ -10593,6 +10630,7 @@ barplot(unname(z), axes = FALSE) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("userhooks") ### * userhooks @@ -10852,6 +10890,7 @@ stopifnot(identical(which.min(list(A = 7, pi = pi)), c(pi = 2L))) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("with") ### * with @@ -10914,6 +10953,7 @@ legend(2, 9, c("Ascorbic acid", "Orange juice"), +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("withVisible") ### * withVisible diff --git a/com.oracle.truffle.r.native/gnur/tests/src/Examples/example-1_def.R b/com.oracle.truffle.r.native/gnur/tests/src/Examples/example-1_def.R index 6fbbf48cd8b928c11707abac654bf2dfb6e53b83..d0de21aca96ca85c27a6fb796118aa3edced7430 100644 --- a/com.oracle.truffle.r.native/gnur/tests/src/Examples/example-1_def.R +++ b/com.oracle.truffle.r.native/gnur/tests/src/Examples/example-1_def.R @@ -17,7 +17,9 @@ kruskal.test(Ozone ~ Month, data = airquality) ################################################### ### code chunk number 3: example-1.Rnw:27-29 ################################################### +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use library("graphics") boxplot(Ozone ~ Month, data = airquality) +} # [FastR] END Test snippet disabled due to graphics package use diff --git a/com.oracle.truffle.r.native/gnur/tests/src/Examples/example-1_myA-noF.R b/com.oracle.truffle.r.native/gnur/tests/src/Examples/example-1_myA-noF.R index 4121a94b198fd9a3d7aee883f0623952bed541cb..93f627cd9b27628ebae29bcc2d4bba9194728998 100644 --- a/com.oracle.truffle.r.native/gnur/tests/src/Examples/example-1_myA-noF.R +++ b/com.oracle.truffle.r.native/gnur/tests/src/Examples/example-1_myA-noF.R @@ -7,7 +7,9 @@ kruskal.test(Ozone ~ Month, data = airquality) ### chunk #3: example-1.Rnw:27-29 +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use library("graphics") boxplot(Ozone ~ Month, data = airquality) +} # [FastR] END Test snippet disabled due to graphics package use diff --git a/com.oracle.truffle.r.native/gnur/tests/src/Examples/example-1_myA.R b/com.oracle.truffle.r.native/gnur/tests/src/Examples/example-1_myA.R index 405b4d9e1a97533f52290d31398b5d44920cdce6..c0d8cf24592583f94cb07746bd8c99323d5dc179 100644 --- a/com.oracle.truffle.r.native/gnur/tests/src/Examples/example-1_myA.R +++ b/com.oracle.truffle.r.native/gnur/tests/src/Examples/example-1_myA.R @@ -11,7 +11,9 @@ kruskal.test(Ozone ~ Month, data = airquality) ### chunk #3: example-1.Rnw:27-29 +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use library("graphics") boxplot(Ozone ~ Month, data = airquality) +} # [FastR] END Test snippet disabled due to graphics package use diff --git a/com.oracle.truffle.r.native/gnur/tests/src/Examples/grDevices-Ex.R b/com.oracle.truffle.r.native/gnur/tests/src/Examples/grDevices-Ex.R index b3b94be9b86feb99f1d94cd9be0ae61264c552b5..468e0353714b0daa179399168eb7747b437456b0 100644 --- a/com.oracle.truffle.r.native/gnur/tests/src/Examples/grDevices-Ex.R +++ b/com.oracle.truffle.r.native/gnur/tests/src/Examples/grDevices-Ex.R @@ -1,6 +1,7 @@ pkgname <- "grDevices" source(file.path(R.home("share"), "R", "examples-header.R")) options(warn = 1) +if(FALSE) { # [FastR] BEGIN Test body disabled due to graphics package use library('grDevices') base::assign(".oldSearch", base::search(), pos = 'CheckExEnv') @@ -1596,6 +1597,7 @@ xyz.coords(data.frame(x = -1:9, y = 2:12, z = 3:13), y = NULL, z = NULL, +} # [FastR] END Test body disabled due to graphics package use ### * <FOOTER> ### options(digits = 7L) diff --git a/com.oracle.truffle.r.native/gnur/tests/src/Examples/graphics-Ex.R b/com.oracle.truffle.r.native/gnur/tests/src/Examples/graphics-Ex.R index 8569b769f756e4d576c6d29cc9a03a2aa2a1b96d..9f788564c285de80ecce9d0a111ef1a4f0fab5fc 100644 --- a/com.oracle.truffle.r.native/gnur/tests/src/Examples/graphics-Ex.R +++ b/com.oracle.truffle.r.native/gnur/tests/src/Examples/graphics-Ex.R @@ -1,6 +1,7 @@ pkgname <- "graphics" source(file.path(R.home("share"), "R", "examples-header.R")) options(warn = 1) +if(FALSE) { # [FastR] BEGIN Test body disabled due to graphics package use library('graphics') base::assign(".oldSearch", base::search(), pos = 'CheckExEnv') @@ -2683,6 +2684,7 @@ arrows(res$x[nr-3], res$y[nr-3], res$x[nr], res$y[nr], code = 2, length = 0.1) graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test body disabled due to graphics package use ### * <FOOTER> ### options(digits = 7L) diff --git a/com.oracle.truffle.r.native/gnur/tests/src/Examples/stats-Ex.R b/com.oracle.truffle.r.native/gnur/tests/src/Examples/stats-Ex.R index 293e974c7b2ff9a85984c1e7a2743a77928c63ea..9c3222d6b94b7e7dab2ac85e27cc3f89a0f9dab6 100644 --- a/com.oracle.truffle.r.native/gnur/tests/src/Examples/stats-Ex.R +++ b/com.oracle.truffle.r.native/gnur/tests/src/Examples/stats-Ex.R @@ -96,6 +96,7 @@ x <- seq(0, 1, length = 21) dbeta(x, 1, 1) pbeta(x, 1, 1) +if(FALSE) { # [FastR] BEGIN Test snippet disabled since abline() uses graphics package ## Visualization, including limit cases: pl.beta <- function(a,b, asp = if(isLim) 1, ylim = if(isLim) c(0,1.1)) { if(isLim <- a == 0 || b == 0 || a == Inf || b == Inf) { @@ -129,9 +130,11 @@ pl.beta(Inf, 2) ## point mass at 1 ; the same as pl.beta(3, 0) pl.beta(Inf, Inf)# point mass at 1/2 +} # [FastR] END Test snippet disabled since abline() uses graphics package +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("Binomial") ### * Binomial @@ -162,6 +165,7 @@ mtext("log(dbinom(k))", col = "red", adj = 1) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("Cauchy") ### * Cauchy @@ -179,6 +183,7 @@ dcauchy(-1:4) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("Chisquare") ### * Chisquare @@ -217,6 +222,7 @@ stopifnot(all.equal(p00, exp(-lam/2)), +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("Exponential") ### * Exponential @@ -236,7 +242,9 @@ dexp(1) - exp(-1) #-> 0 rsunif <- function(n) { n1 <- n+1 cE <- cumsum(rexp(n1)); cE[seq_len(n)]/cE[n1] } plot(rsunif(1000), ylim=0:1, pch=".") +if(FALSE) { # [FastR] BEGIN Test snippet disabled since abline() uses graphics package abline(0,1/(1000+1), col=adjustcolor(1, 0.5)) +} # [FastR] END Test snippet disabled since abline() uses graphics package @@ -309,6 +317,7 @@ Ni <- rgeom(20, prob = 1/4); table(factor(Ni, 0:max(Ni))) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("HoltWinters") ### * HoltWinters @@ -349,6 +358,7 @@ options(od) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("Hypergeometric") ### * Hypergeometric @@ -554,6 +564,7 @@ NLSstRtAsymptote( DN.srt ) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("NegBinomial") ### * NegBinomial @@ -595,6 +606,8 @@ barplot(rbind(h1$counts, h2$counts, h3$counts), +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("Normal") ### * Normal @@ -640,6 +653,8 @@ erfcinv <- function (x) qnorm(x/2, lower = FALSE)/sqrt(2) graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("Poisson") ### * Poisson @@ -675,6 +690,7 @@ stopifnot(identical(dpois(0,0), 1), graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("SSD") ### * SSD @@ -713,6 +729,7 @@ estVar(mlmfit) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("SSasymp") ### * SSasymp @@ -770,6 +787,8 @@ require(graphics) graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("SSasympOff") ### * SSasympOff @@ -820,6 +839,8 @@ require(graphics) graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("SSasympOrig") ### * SSasympOrig @@ -859,6 +880,8 @@ require(graphics) graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("SSbiexp") ### * SSbiexp @@ -903,6 +926,7 @@ summary(fm1) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("SSfol") ### * SSfol @@ -927,6 +951,7 @@ summary(fm1) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("SSfpl") ### * SSfpl @@ -982,6 +1007,7 @@ require(graphics) graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("SSgompertz") ### * SSgompertz @@ -1008,6 +1034,7 @@ summary(fm1) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("SSlogis") ### * SSlogis @@ -1048,6 +1075,8 @@ require(graphics) graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("SSmicmen") ### * SSmicmen @@ -1098,6 +1127,7 @@ require(graphics) graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("SSweibull") ### * SSweibull @@ -1122,6 +1152,7 @@ summary(fm1) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("SignRank") ### * SignRank @@ -1153,6 +1184,8 @@ stopifnot(round(dsignrank(0:56, n = 10)* 2^10) == c(p, rev(p), 0), graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("StructTS") ### * StructTS @@ -1187,6 +1220,8 @@ StructTS(log10(UKgas), type = "BSM", fixed = c(0.1,0.001,NA,NA), graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("TDist") ### * TDist @@ -1219,6 +1254,7 @@ plot(function(x) dt(x, df = 3, ncp = 2), -3, 11, ylim = c(0, 0.32), +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("Tukey") ### * Tukey @@ -1240,6 +1276,7 @@ if(interactive()) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("TukeyHSD") ### * TukeyHSD @@ -1261,6 +1298,7 @@ plot(TukeyHSD(fm1, "tension")) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("Uniform") ### * Uniform @@ -1307,6 +1345,7 @@ all.equal(qweibull(x/11, shape = 1, scale = pi), qexp(x/11, rate = 1/pi)) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("Wilcoxon") ### * Wilcoxon @@ -1350,6 +1389,8 @@ text(n+.2, n+.5, labels = tU, col = "red") +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("acf") ### * acf @@ -1382,6 +1423,7 @@ pacf(presidents, na.action = na.pass) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("acf2AR") ### * acf2AR @@ -1400,6 +1442,7 @@ acf2AR(Acf) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("add1") ### * add1 @@ -1436,6 +1479,7 @@ options(od) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("addmargins") ### * addmargins @@ -1622,6 +1666,7 @@ anova(fit4, fit2, fit0, test = "F") # unconventional order +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("anova.mlm") ### * anova.mlm @@ -1670,6 +1715,7 @@ plot(colMeans(reacttime)) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("ansari.test") ### * ansari.test @@ -1732,6 +1778,7 @@ options(op) # reset to previous base::options(contrasts = c(unordered = "contr.treatment",ordered = "contr.poly")) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("approxfun") ### * approxfun @@ -1777,6 +1824,7 @@ approx(x, y, xout = x, ties = max)$y graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("ar") ### * ar @@ -1830,6 +1878,7 @@ ar.ols(x, order.max = 6, demean = FALSE, intercept = TRUE) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("arima") ### * arima @@ -1875,6 +1924,8 @@ predict(fit3, 3) +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("arima.sim") ### * arima.sim @@ -1902,6 +1953,7 @@ ts.plot(ts.sim) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("arima0") ### * arima0 @@ -1976,6 +2028,7 @@ asOneSidedFormula(~ age) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("ave") ### * ave @@ -2007,6 +2060,8 @@ detach() +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("bandwidth") ### * bandwidth @@ -2035,6 +2090,8 @@ legend(55, 0.035, +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("bartlett.test") ### * bartlett.test @@ -2056,6 +2113,7 @@ bartlett.test(count ~ spray, data = InsectSprays) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("binom.test") ### * binom.test @@ -2083,6 +2141,7 @@ binom.test(682, 682 + 243, p = 3/4) # The same. +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("biplot.princomp") ### * biplot.princomp @@ -2101,6 +2160,8 @@ biplot(princomp(USArrests)) +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("birthday") ### * birthday @@ -2141,6 +2202,7 @@ pbirthday(1000, coincident = 100) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("box.test") ### * box.test @@ -2255,6 +2317,7 @@ chisq.test(table(x)) # NOT 'chisq.test(x)'! +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("cmdscale") ### * cmdscale @@ -2280,6 +2343,7 @@ text(x, y, rownames(loc), cex = 0.6) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("coef") ### * coef @@ -2410,6 +2474,7 @@ contrasts(fff) <- contr.sum(5)[, 1:2]; contrasts(fff) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("convolve") ### * convolve @@ -2446,6 +2511,8 @@ lines(x[-c(1:2, (n-1):n)], Han(Han(y)), lwd = 2, col = "dark blue") +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("cophenetic") ### * cophenetic @@ -2480,6 +2547,7 @@ cor(d0, d.coph) # 0.9911 +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("cor") ### * cor @@ -2553,6 +2621,7 @@ summary(abs(1 - EV(Rp)/EV(R.)) / abs(1 - EV(Rc)/EV(R.))) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("cor.test") ### * cor.test @@ -2596,6 +2665,7 @@ cor.test(~ CONT + INTG, data = USJudgeRatings) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("cov.wt") ### * cov.wt @@ -2616,6 +2686,7 @@ flush(stderr()); flush(stdout()) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("cpgram") ### * cpgram @@ -2641,6 +2712,7 @@ cpgram(ldeaths) graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("cutree") ### * cutree @@ -2665,6 +2737,7 @@ table(grp2 = g24[,"2"], grp4 = g24[,"4"]) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("decompose") ### * decompose @@ -2695,6 +2768,7 @@ round(decompose(x)$figure / 10, 2) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("delete.response") ### * delete.response @@ -2732,6 +2806,7 @@ stopifnot(identical( ~ var, reformulate("var")), +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("dendrapply") ### * dendrapply @@ -2777,6 +2852,8 @@ par(op) graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("dendrogram") ### * dendrogram @@ -2867,6 +2944,8 @@ plot(d3e, nodePar = nP, leaflab = "textlike") graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("density") ### * density @@ -2959,6 +3038,7 @@ legend(55, 0.035, legend = kernels, col = seq(kernels), lty = 1) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("deriv") ### * deriv @@ -3070,6 +3150,7 @@ diffinv(d, xi = 1) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("dist") ### * dist @@ -3133,6 +3214,7 @@ dist(rbind(x, y), method = "manhattan") # 2.4 +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("dummy.coef") ### * dummy.coef @@ -3157,6 +3239,7 @@ dummy.coef(npk.aovE) base::options(contrasts = c(unordered = "contr.treatment",ordered = "contr.poly")) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("ecdf") ### * ecdf @@ -3226,6 +3309,7 @@ par(op) graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("eff.aovlist") ### * eff.aovlist @@ -3582,6 +3666,7 @@ fivenum(c(rnorm(100), -1:1/0)) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("fligner.test") ### * fligner.test @@ -3604,6 +3689,7 @@ fligner.test(count ~ spray, data = InsectSprays) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("formula") ### * formula @@ -3842,6 +3928,7 @@ flush(stderr()); flush(stdout()) ### ** Examples +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("hclust") ### * hclust @@ -3897,6 +3984,8 @@ par(opar) graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("heatmap") ### * heatmap @@ -3958,6 +4047,7 @@ utils::str(hU$Colv) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("identify.hclust") ### * identify.hclust @@ -3992,6 +4082,7 @@ flush(stderr()); flush(stdout()) ## End(Not run) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("influence.measures") ### * influence.measures @@ -4061,6 +4152,7 @@ stopifnot(all.equal(imI$infmat[,"cook.d"], +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("integrate") ### * integrate @@ -4110,6 +4202,7 @@ integrate(dnorm, 0:1, 20) #-> error! +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("interaction.plot") ### * interaction.plot @@ -4162,6 +4255,7 @@ rm(esophNA) # to clear up +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("is.empty") ### * is.empty @@ -4182,6 +4276,7 @@ is.empty.model(lm(y ~ 0)) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("isoreg") ### * isoreg @@ -4219,6 +4314,7 @@ stopifnot(all.equal(with(m, yf[iKnots]), +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("kernapply") ### * kernapply @@ -4237,6 +4333,7 @@ flush(stderr()); flush(stdout()) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("kernel") ### * kernel @@ -4277,6 +4374,8 @@ spectrum(sunspot.year, kernel = kernel("daniell", c(11,7,3)), log = "no") +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("kmeans") ### * kmeans @@ -4329,6 +4428,8 @@ points(cl$centers, col = 1:5, pch = 8) +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("kruskal.test") ### * kruskal.test @@ -4365,6 +4466,8 @@ kruskal.test(Ozone ~ Month, data = airquality) +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("ks.test") ### * ks.test @@ -4399,6 +4502,8 @@ ks.test(x, x2, alternative = "l") +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("ksmooth") ### * ksmooth @@ -4422,6 +4527,7 @@ with(cars, { +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("lag") ### * lag @@ -4439,6 +4545,7 @@ lag(ldeaths, 12) # starts one year earlier +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("lag.plot") ### * lag.plot @@ -4468,6 +4575,8 @@ lag.plot(sqrt(sunspots), set = c(1:4, 9:12), pch = ".", col = "gold") +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("line") ### * line @@ -4491,6 +4600,8 @@ plot(residuals(z) ~ fitted(z), main = deparse(z$call)) +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("lm") ### * lm @@ -4527,6 +4638,7 @@ stopifnot(identical(lm(weight ~ group, method = "model.frame"), graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("lm.influence") ### * lm.influence @@ -4682,6 +4794,7 @@ fm +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("lowess") ### * lowess @@ -4704,6 +4817,7 @@ legend(5, 120, c(paste("f = ", c("2/3", ".2"))), lty = 1, col = 2:3) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("ls.diag") ### * ls.diag @@ -4764,6 +4878,7 @@ c(mad(x, constant = 1), +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("mahalanobis") ### * mahalanobis @@ -4798,6 +4913,7 @@ abline(0, 1, col = 'gray') +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("make.link") ### * make.link @@ -4815,6 +4931,7 @@ utils::str(make.link("logit")) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("makepredictcall") ### * makepredictcall @@ -4842,6 +4959,7 @@ lines(ht, predict(fm, data.frame(height = ht))) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("manova") ### * manova @@ -5024,6 +5142,7 @@ median(c(1:3, 100, 1000)) # = 3 [odd, robust] +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("medpolish") ### * medpolish @@ -5057,6 +5176,7 @@ all(deaths == +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("model.extract") ### * model.extract @@ -5145,6 +5265,7 @@ flush(stderr()); flush(stdout()) ### ** Examples +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("monthplot") ### * monthplot @@ -5180,6 +5301,7 @@ monthplot(co2, phase = quarter) graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("mood.test") ### * mood.test @@ -5329,6 +5451,7 @@ flush(stderr()); flush(stdout()) ### ** Examples +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("nls") ### * nls @@ -5466,6 +5589,7 @@ options(od) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("nls.control") ### * nls.control @@ -5546,6 +5670,7 @@ flush(stderr()); flush(stdout()) ### ** Examples +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("optimize") ### * optimize @@ -5578,6 +5703,7 @@ optimize(fp, c(-7, 20)) # ok +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("order.dendrogram") ### * order.dendrogram @@ -5606,6 +5732,7 @@ stopifnot(identical(labels(d2), +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("p.adjust") ### * p.adjust @@ -5652,6 +5779,7 @@ round((pN.a / p.adj)[1:20, ] , 4) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("pairwise.prop.test") ### * pairwise.prop.test @@ -5715,6 +5843,7 @@ detach() +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("plot.acf") ### * plot.acf @@ -5738,6 +5867,8 @@ acf(z7) # multi-page +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("plot.isoreg") ### * plot.isoreg @@ -5774,6 +5905,8 @@ plot(ir <- isoreg(sample(10), sample(10, replace = TRUE)), +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("plot.lm") ### * plot.lm @@ -5823,6 +5956,8 @@ plot(lm(long.var.name.1 ~ graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("plot.ppr") ### * plot.ppr @@ -5850,6 +5985,8 @@ plot(update(rock.ppr, sm.method = "gcv", gcvpen = 2), graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("plot.profile.nls") ### * plot.profile.nls @@ -5881,6 +6018,8 @@ par(opar) graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("plot.stepfun") ### * plot.stepfun @@ -5924,6 +6063,8 @@ plot.stepfun(rt(50, df = 3), col.vert = "gray20") graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("plot.ts") ### * plot.ts @@ -5965,6 +6106,7 @@ plot(lag(SMI, 20), SMI, pch = ".", log = "xy", +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("poisson.test") ### * poisson.test @@ -6123,6 +6265,7 @@ PP.test(y) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("ppoints") ### * ppoints @@ -6172,6 +6315,8 @@ if(!any("MASS" == lNs)) unloadNamespace("MASS") graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("ppr") ### * ppr @@ -6226,6 +6371,7 @@ detach() graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("prcomp") ### * prcomp @@ -6257,6 +6403,7 @@ stopifnot(ncol(pZ$rotation) == 14, ncol(pz3$rotation) == 3, +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("predict.HoltWinters") ### * predict.HoltWinters @@ -6278,6 +6425,7 @@ plot(m, p) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("predict") ### * predict @@ -6335,6 +6483,7 @@ options(od) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("predict.glm") ### * predict.glm @@ -6371,6 +6520,8 @@ lines(2^ld, predict(budworm.lg, data.frame(ldose = ld, +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("predict.lm") ### * predict.lm @@ -6418,6 +6569,7 @@ stopifnot(all.equal(pt[,1:4], pt., +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("predict.loess") ### * predict.loess @@ -6440,6 +6592,7 @@ predict(cars.lo2, data.frame(speed = seq(5, 30, 1)), se = TRUE) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("predict.nls") ### * predict.nls @@ -6475,6 +6628,8 @@ options(od) graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("predict.smooth.spline") ### * predict.smooth.spline @@ -6529,6 +6684,8 @@ detach(); par(op) graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("princomp") ### * princomp @@ -6571,6 +6728,7 @@ pc.cr <- princomp(~ Murder + Assault + UrbanPop, (pc.cl <- princomp(stackloss)) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("print.power.htest") ### * print.power.htest @@ -6748,6 +6906,7 @@ prop.trend.test(smokers, patients, c(0,0,0,1)) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("qqnorm") ### * qqnorm @@ -6780,6 +6939,7 @@ mtext("qqline(*, dist = qchisq(., df=3), prob = c(0.1, 0.6))") +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("quade.test") ### * quade.test @@ -6965,6 +7125,7 @@ write.ftable(ft22, quote = FALSE, method="compact") +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("rect.hclust") ### * rect.hclust @@ -6988,6 +7149,7 @@ x +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("relevel") ### * relevel @@ -7006,6 +7168,7 @@ summary(lm(breaks ~ wool + tension, data = warpbreaks)) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("reorder.dendrogram") ### * reorder.dendrogram @@ -7036,6 +7199,8 @@ par(op) graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("reorder.factor") ### * reorder.factor @@ -7059,6 +7224,7 @@ boxplot(count ~ bymedian, data = InsectSprays, +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("replications") ### * replications @@ -7149,6 +7315,7 @@ reshape(wide) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("runmed") ### * runmed @@ -7195,6 +7362,8 @@ legend(length(y),max(y), c("data", "lowess(y, f = 0.3)", "runmed(y, 7)"), +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("scatter.smooth") ### * scatter.smooth @@ -7217,6 +7386,8 @@ with(cars, scatter.smooth(speed, dist, lpars = +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("screeplot") ### * screeplot @@ -7243,6 +7414,7 @@ screeplot(fit, npcs = 24, type = "lines") +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("sd") ### * sd @@ -7529,6 +7701,7 @@ S4 <- simulate(modb2, nsim = 4) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("smooth") ### * smooth @@ -7577,6 +7750,8 @@ lines(sm, col = 2, lwd = 1.25) +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("smooth.spline") ### * smooth.spline @@ -7651,6 +7826,8 @@ stopifnot(all.equal(s2[nn], s2.[nn], tol = 7e-7), # seen 6.86e-8 ## End(Don't show) +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("smoothEnds") ### * smoothEnds @@ -7682,6 +7859,7 @@ stopifnot(identical(s7m, smoothEnds(s7k, 7))) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("sortedXyData") ### * sortedXyData @@ -7700,6 +7878,7 @@ sortedXyData( expression(log(conc)), expression(density), DNase.2 ) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("spec.ar") ### * spec.ar @@ -7727,6 +7906,8 @@ spec.ar(log(lynx), method = "ols", add = TRUE, col = "blue") +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("spec.pgram") ### * spec.pgram @@ -7775,6 +7956,8 @@ plot(sales.spc, plot.type = "phase") +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("spectrum") ### * spectrum @@ -7813,6 +7996,8 @@ spectrum(ldeaths, method = "ar") graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("splinefun") ### * splinefun @@ -7919,6 +8104,7 @@ legend("topright", graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("stat.anova") ### * stat.anova @@ -7993,6 +8179,7 @@ stopifnot(identical(y0[-1], sfun0 (1:3)), # right = FALSE +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("stl") ### * stl @@ -8032,6 +8219,7 @@ par(op) # reset graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("summary.aov") ### * summary.aov @@ -8152,6 +8340,7 @@ print(summary(princomp(USArrests, cor = TRUE), +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("supsmu") ### * supsmu @@ -8175,6 +8364,7 @@ with(cars, { +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("symnum") ### * symnum @@ -8226,6 +8416,7 @@ noquote(cbind(P.val = format(pval), Signif = symp)) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("t.test") ### * t.test @@ -8253,6 +8444,8 @@ t.test(extra ~ group, data = sleep) +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("termplot") ### * termplot @@ -8285,6 +8478,7 @@ if(!had.splines && rs) detach("package:splines") graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("terms.object") ### * terms.object @@ -8310,6 +8504,7 @@ terms(y ~ x + x:z + s(x), specials = "s", keep.order = TRUE) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("time") ### * time @@ -8331,6 +8526,7 @@ plot(as.vector(time(presidents)), as.vector(presidents), type = "l") +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("toeplitz") ### * toeplitz @@ -8349,6 +8545,7 @@ toeplitz (x) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("ts") ### * ts @@ -8385,6 +8582,8 @@ plot(nhtemp, lag(nhtemp, 1), cex = .8, col = "blue", +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("ts.plot") ### * ts.plot @@ -8405,6 +8604,7 @@ ts.plot(ldeaths, mdeaths, fdeaths, +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("ts.union") ### * ts.union @@ -8669,6 +8869,7 @@ weighted.residuals(lmxy, drop0 = FALSE) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("wilcox.test") ### * wilcox.test @@ -8719,6 +8920,7 @@ wilcox.test(Ozone ~ Month, data = airquality, +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("window") ### * window diff --git a/com.oracle.truffle.r.native/gnur/tests/src/Examples/utils-Ex.R b/com.oracle.truffle.r.native/gnur/tests/src/Examples/utils-Ex.R index 2b93341d8b68731e1061322e686da805781f74bb..32e43e71c79a807b1617f21720a7ba043d948e5c 100644 --- a/com.oracle.truffle.r.native/gnur/tests/src/Examples/utils-Ex.R +++ b/com.oracle.truffle.r.native/gnur/tests/src/Examples/utils-Ex.R @@ -268,7 +268,9 @@ Sweave(testfile) ## create an R source file from the code chunks Stangle(testfile) ## which can be sourced, e.g. +if(FALSE) { # [FastR] BEGIN Test snippet disabled since the source calls pairs() which uses graphics package source("Sweave-test-1.R") +} # [FastR] END Test snippet disabled since the source calls pairs() which uses graphics package ## Don't show: if(!interactive()) unlink("Sweave-test-1*") @@ -1077,7 +1079,9 @@ flush(stderr()); flush(stdout()) ### ** Examples +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use example(InsectSprays) +} # [FastR] END Test snippet disabled due to graphics package use ## force use of the standard package 'stats': example("smooth", package = "stats", lib.loc = .Library) @@ -1724,6 +1728,7 @@ flush(stderr()); flush(stdout()) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("methods") ### * methods @@ -1762,6 +1767,7 @@ print(attr(m, "info")) # more extensive information +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("modifyList") ### * modifyList @@ -2034,6 +2040,7 @@ toBibtex(b) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("prompt") ### * prompt @@ -2067,6 +2074,7 @@ unlink("sunspots.Rd") +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("promptData") ### * promptData @@ -2524,6 +2532,7 @@ stack(pg, select = -ctrl) # omitting one vector +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use cleanEx() nameEx("str") ### * str @@ -2625,6 +2634,7 @@ if(!had.stats4 && rs) detach("package:stats4") graphics::par(get("par.postscript", pos = 'CheckExEnv')) +} # [FastR] END Test snippet disabled due to graphics package use cleanEx() nameEx("strcapture") ### * strcapture diff --git a/com.oracle.truffle.r.native/gnur/tests/src/demos.R b/com.oracle.truffle.r.native/gnur/tests/src/demos.R index b9528c993ebbbf92b8ba4b2d8777dfa42ac03e95..63149f5ddcb4a5fe038950ef92c365b42d57c880 100644 --- a/com.oracle.truffle.r.native/gnur/tests/src/demos.R +++ b/com.oracle.truffle.r.native/gnur/tests/src/demos.R @@ -9,7 +9,9 @@ dont <- list(graphics = c("Hershey", "Japanese", "plotmath"), stats = c("lm.glm", "nlm") ) ## don't take tcltk here -for(pkg in c("base", "graphics", "stats")) { +# [FastR] Skip "graphics" package demos +#for(pkg in c("base", "graphics", "stats")) { +for(pkg in c("base", "stats")) { demos <- list.files(file.path(system.file(package = pkg), "demo"), pattern = "\\.R$") diff --git a/com.oracle.truffle.r.native/gnur/tests/src/reg-S4-examples.R b/com.oracle.truffle.r.native/gnur/tests/src/reg-S4-examples.R index a52a11fdfabc6d4a2e9b07881b91818c725d2de6..f39e761406f640d538946d31b9a7f8dcb4021953 100644 --- a/com.oracle.truffle.r.native/gnur/tests/src/reg-S4-examples.R +++ b/com.oracle.truffle.r.native/gnur/tests/src/reg-S4-examples.R @@ -7,6 +7,7 @@ setClass("trackMultiCurve", slots = c(x="numeric", y="matrix", smooth="matrix"), prototype = list(x=numeric(), y=matrix(0,0,0), smooth= matrix(0,0,0))) +if(FALSE) { # [FastR] BEGIN Test body disabled due to graphics package use require(graphics) @@ -355,3 +356,4 @@ m1 <- cbind(group, weight) setClass("MatX", contains = "matrix", slots = c(date = "Date")) mx1 <- new("MatX", m1, date = Sys.Date()) stopifnot(identical(m1, S3Part(mx1, strict = TRUE))) +} # [FastR] END Test body disabled due to graphics package use diff --git a/com.oracle.truffle.r.native/gnur/tests/src/reg-examples1.R b/com.oracle.truffle.r.native/gnur/tests/src/reg-examples1.R index b135b9a46a266e1901df16f88f48cdd7c1af41d9..1e1ce9e3bdd60cf50788912ae7fd2b3e3a5475d5 100644 --- a/com.oracle.truffle.r.native/gnur/tests/src/reg-examples1.R +++ b/com.oracle.truffle.r.native/gnur/tests/src/reg-examples1.R @@ -47,7 +47,9 @@ example(news, run.donttest = TRUE) example(sessionInfo, run.donttest = TRUE) ## datasets +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use example(JohnsonJohnson, run.donttest = TRUE) +} # [FastR] END Test snippet disabled due to graphics package use example(ability.cov, run.donttest = TRUE) example(npk, run.donttest = TRUE) diff --git a/com.oracle.truffle.r.native/gnur/tests/src/reg-examples2.R b/com.oracle.truffle.r.native/gnur/tests/src/reg-examples2.R index 0e17c822a6570cc9347880c1671f972b8535e960..b364e10a2b81bc89dad7b378eda95ed35771e616 100644 --- a/com.oracle.truffle.r.native/gnur/tests/src/reg-examples2.R +++ b/com.oracle.truffle.r.native/gnur/tests/src/reg-examples2.R @@ -30,7 +30,9 @@ example(ls.diag, run.donttest = TRUE) example(model.tables, run.donttest = TRUE) example(nlminb, run.donttest = TRUE) example(optim, run.donttest = TRUE) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use example(prcomp, run.donttest = TRUE) +} # [FastR] END Test snippet disabled due to graphics package use example(step, run.donttest = TRUE) example(summary.manova, run.donttest = TRUE) example(uniroot, run.donttest = TRUE) diff --git a/com.oracle.truffle.r.native/gnur/tests/src/reg-examples3.R b/com.oracle.truffle.r.native/gnur/tests/src/reg-examples3.R index 0fcaeb7f1be118e72deed81ccffc1ac72de8311f..59a22b2cbf205bb9635fef6fbcde06818482b35e 100644 --- a/com.oracle.truffle.r.native/gnur/tests/src/reg-examples3.R +++ b/com.oracle.truffle.r.native/gnur/tests/src/reg-examples3.R @@ -20,6 +20,7 @@ x2 <- matrix(rnorm(1e3, mean = 3, sd = 1.5), ncol = 2) x <- rbind(x1, x2) dcols <- densCols(x) +if(FALSE) { # [FastR] BEGIN graphics::plot() disabled due to graphics package use graphics::plot(x, col = dcols, pch = 20, main = "n = 1000") @@ -51,6 +52,7 @@ pairs(y, panel = function(...) smoothScatter(..., nrpoints = 0, add = TRUE)) par(oldpar) +} # [FastR] END graphics::plot() disabled due to graphics package use ## From stats # alias.Rd diff --git a/com.oracle.truffle.r.native/gnur/tests/src/reg-plot-latin1.R b/com.oracle.truffle.r.native/gnur/tests/src/reg-plot-latin1.R index 6d990d634d1e030f8de136e8fb6117fb64318040..834ee048f85ee3051f6bd0d4d936755db7467f32 100644 --- a/com.oracle.truffle.r.native/gnur/tests/src/reg-plot-latin1.R +++ b/com.oracle.truffle.r.native/gnur/tests/src/reg-plot-latin1.R @@ -1,5 +1,7 @@ pdf(file = "reg-plot-latin1.pdf", encoding = "ISOLatin1", width = 7, height = 7, paper = "a4r", compress = FALSE) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use library(graphics) # to be sure example(text) # has examples that need to he plotted in latin-1 +} # [FastR] END Test snippet disabled due to graphics package use q("no") diff --git a/com.oracle.truffle.r.native/gnur/tests/src/reg-plot.R b/com.oracle.truffle.r.native/gnur/tests/src/reg-plot.R index e567e3cfc7f09ed0f7da5b41ff2107cb11cfba41..3a7a0bbf8b32c593cd72958615cd0b445fd9367e 100644 --- a/com.oracle.truffle.r.native/gnur/tests/src/reg-plot.R +++ b/com.oracle.truffle.r.native/gnur/tests/src/reg-plot.R @@ -22,14 +22,18 @@ stopifnot(all.equal( par(pty="s") plot(c(-1,16), c(-1,16), type="n", xlab="", ylab="", xaxs="i", yaxs="i") +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use title("Centred chars in default char set (ISO Latin1)") grid(17, 17, lty=1) +} # [FastR] END Test snippet disabled due to graphics package use known <- c(32:126, 160:255) for(i in known) { x <- i %% 16 y <- i %/% 16 +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use points(x, y, pch=-i) +} # [FastR] END Test snippet disabled due to graphics package use } par(pty="m") @@ -38,6 +42,7 @@ par(pty="m") ### Prior to 1.2.2, the label sizes were unaffected by cex. +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use dotchart(VADeaths, main = "Death Rates in Virginia - 1940", cex = 0.5) dotchart(VADeaths, main = "Death Rates in Virginia - 1940", cex = 1.5) @@ -47,8 +52,10 @@ t1 <- ts(0:100) plot(t1, log = "y") plot(cbind(t1, 10*t1, t1 - 4), log="y", plot.type = "single") stopifnot(par("usr")[4] > 3) # log10: ylim[2] = 1000 +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use ## This one needs to be looked at. ## lty = "blank" killed the fill colour too. plot(1:10, type="n") @@ -58,6 +65,7 @@ rect(6, 6, 10, 10, col="blue", border="red", lty="blank") with(trees, symbols(Height, Volume, circles=Girth/24, inches=FALSE, lty="blank", bg="blue")) ## in 1.5.0 ignored the lty. +} # [FastR] END Test snippet disabled due to graphics package use ## axis() and par(mgp < 0) {keep this example S+ compatible!}: lt <- if(is.R()) "31" else 2 @@ -66,6 +74,7 @@ op <- par(tck= +0.02, mgp = -c(3,2,0)) plot(x, x^2 - 1.2, xaxt = "n", xlab="", type ='l', col = 2, main = "mgp < 0: all ticks and labels inside `frame'") x <- -2:3 +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use lines(x, x^2 - 1.2, type ="h", col = 3, lwd=3) axis(1, pos = 0, at=-1:1, lty = lt, col=4)## col & lty work only from R 1.6 par(op) @@ -79,7 +88,9 @@ plot(UCBAdmissions, xlab = "x label", ylab = "YY")# wrong in 1.5.1 plot(tt <- table(c(rep(0,7), rep(1,4), rep(5, 3))), axes = FALSE) plot(tt, xaxt = "n") ## wrong till (incl.) 1.6.x +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use ## legend with call lo <- legend(2,2, substitute(hat(theta) == that, list(that= pi))) stopifnot(length(lo$text$x) == 1) @@ -87,7 +98,9 @@ stopifnot(length(lo$text$x) == 1) plot(ecdf(c(1:4,8,12)), ylab = "ECDF", main=NULL) ## ylab didn't work till 1.8.0 +} # [FastR] END Test snippet disabled due to graphics package use +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use plot(1:10, pch = NA) # gave error till 1.9.0 points(1:3, pch=c("o",NA,"x"))# used "N" try(points(4, pch=c(NA,FALSE)))# still give an error @@ -96,6 +109,7 @@ try(points(4, pch=c(NA,FALSE)))# still give an error legend(1,10, c("A","bcd"), lwd = 2:3, pch= 21:22, pt.bg="skyblue", col = 2:3, bg = "thistle") ## (gave an error for 2 days in "2.0.0 unstable") +} # [FastR] END Test snippet disabled due to graphics package use x <- 2^seq(1,1001, length=20) plot(x, x^0.9, type="l", log="xy") @@ -104,6 +118,7 @@ plot(x, x^0.9, type="l", log="xy") plot(as.Date("2001/1/1") + 12*(1:9), 1:9) ## used bad 'xlab/ylab' in some versions of R 2.2.0(unstable) +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use ## dotchart() restoring par() Opar <- par(no.readonly=TRUE) ; dotchart(1:4, cex= 0.7) Npar <- par(no.readonly=TRUE) @@ -137,6 +152,7 @@ curve(5*exp(-x), 0.1, 100, n = 3, log="x", ylab="", axes=FALSE) curve(5*exp(-x), add=TRUE, n = 3, col=2,lwd=3) ## should fully overplot; wrong default xlim in 2.6.1 ## (and *slightly* wrong up to 2.6.0) +} # [FastR] END Test snippet disabled due to graphics package use ## Axis() calls via plot() {[xy]axt to keep *.ps small} x <- as.Date("2008-04-22 09:45") + (i <- c(0,4)) @@ -144,6 +160,7 @@ plot(x, xaxt="n")# not ok in 2.6.2, nor 2.7.0 plot(x, i, yaxt="n")# ok in 2.6.2 and 2.7.0 plot(i, x, xaxt="n")# ok in 2.6.2 and not in 2.7.0 +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use ## table methods should be bypassed: dotchart(table(infert$education)) ## failed in 2.12.[12] @@ -152,6 +169,7 @@ dotchart(table(infert$education)) hc <- hclust(dst <- dist(c(1:2, 5)), method="ave") plot(hc, cex = 2, axes=FALSE, ann=FALSE) ## cex was not used in 3.0.[01] +} # [FastR] END Test snippet disabled due to graphics package use ## axis.Date() and axis.POSIXct() with reversed 'xlim' toD <- as.Date("2016-08-19"); dates <- c(toD - 10, toD) diff --git a/com.oracle.truffle.r.native/gnur/tests/src/reg-tests-1a.R b/com.oracle.truffle.r.native/gnur/tests/src/reg-tests-1a.R index 0a886b2a60b54e8b704cae13bcd75f681c1dc131..4eb0ba5e6738afa62ec32ed966047394cd7504b7 100644 --- a/com.oracle.truffle.r.native/gnur/tests/src/reg-tests-1a.R +++ b/com.oracle.truffle.r.native/gnur/tests/src/reg-tests-1a.R @@ -2796,6 +2796,7 @@ stopifnot(r1 == r2) ## +if(FALSE) { # [FastR] BEGIN Test snippet disabled since points() uses graphics package ## PR#6652, points.formula with subset and extra arguments. roller <- data.frame(weight = c(1.9, 3.1, 3.3, 4.8, 5.3, 6.1, 6.4, 7.6, 9.8, 12.4), @@ -2806,6 +2807,7 @@ with(roller, points( depression~weight, subset=8:10, col=2:4)) plot(depression ~ weight, data=roller, type="n") points(depression~weight, subset=8:10, col=2:4, data=roller) ## first two gave error in 1.8.1 +} # [FastR] END Test snippet disabled since points() uses graphics package ## PR#4558 part 2 @@ -4134,6 +4136,7 @@ stopifnot(is.na(mean(NA))) ## failed in R 2.3.0 +if(FALSE) { # [FastR] BEGIN Test snippet disabled since title() uses graphics package ## title etc failed if passed col etc of length > 1 plot(1:2) title("foo", col=1:3) @@ -4142,6 +4145,7 @@ title("foo", lty=1:3) title("foo", lwd=1:3) title("foo", bg=4:7) ## threw errors in R <= 2.3.0 +} # [FastR] END Test snippet disabled since title() uses graphics package ## glm did not allow array offsets diff --git a/com.oracle.truffle.r.native/gnur/tests/src/reg-tests-1b.R b/com.oracle.truffle.r.native/gnur/tests/src/reg-tests-1b.R index 59fb16133f44731bcf5f2a195e3c8c397ea01f6d..145cc0d99051b17ca5e478fc5e0c437d8a8c5908 100644 --- a/com.oracle.truffle.r.native/gnur/tests/src/reg-tests-1b.R +++ b/com.oracle.truffle.r.native/gnur/tests/src/reg-tests-1b.R @@ -16,11 +16,12 @@ x <- structure(list(2), class="foo") str(x) ## gave infinite recursion < 2.6.0 - +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use curve(sin, -2*pi, 3*pi); pu1 <- par("usr")[1:2] curve(cos, add = NA) # add = NA new in 2.14.0 stopifnot(all.equal(par("usr")[1:2], pu1)) ## failed in R <= 2.6.0 +} # [FastR] END Test snippet disabled due to graphics package use ## tests of side-effects with CHARSXP caching @@ -255,11 +256,13 @@ p2 <- predict(fit.log, log(nd)) stopifnot(all.equal(p1, p2)) +if(FALSE) { # [FastR] BEGIN Test snippet disabled since segments() uses graphics package ## wishlist PR#11192 plot(1:10) segments(1, 1, 10, 10, col='green') segments(numeric(0), numeric(0), numeric(0), numeric(0), col='green') ## last was error in R < 2.8.0 +} # [FastR] END Test snippet disabled since segments() uses graphics package ## merging with a zero-row data frame @@ -412,11 +415,13 @@ nls(y ~ ((g1)*exp((log(g2/g1))*(1-exp(-k*(x-Ta)))/(1-exp(-k*(Tb-Ta))))), ## failed for find weights in R <= 2.7.1 +if(FALSE) { # [FastR] BEGIN Test snippet disabled due to graphics package use ## barplot(log = "y") with NAs (PR#11585) dat <- matrix(1:25, 5) dat[2,3] <- NA barplot(dat, beside = TRUE, log = "y") ## failed in 2.7.1 +} # [FastR] END Test snippet disabled due to graphics package use ## related to PR#12551 @@ -481,6 +486,7 @@ close(zz) ## was " .haha" (not according to DCF standard) +if(FALSE) { # [FastR] BEGIN Test snippet disabled since text() uses graphics package ## pdf() with CIDfonts active -- they need MBCS to be supported pdf(file = "testCID.pdf", family="Japan1") # << for CIDfonts, pd->fonts is NULL try({ @@ -498,6 +504,7 @@ plot(1,1,pch="", axes=FALSE) try(text(1,1,"A",family="Japan1")) unlink("testCID.ps") ## error instead of seg.fault +} # [FastR] END Test snippet disabled since text() uses graphics package ## splinefun with derivatives evaluated to the left of first knot @@ -568,14 +575,17 @@ stopifnot(length(deparse(quote(foo(1,2,3)), width.cutoff = 20, nlines=7)) ==1) ## was 7. +if(FALSE) { # [FastR] BEGIN Test snippet disabled since legend() uses graphics package ## legend did not reset xpd correctly (PR#12756) par(xpd = FALSE) plot(1) legend("top", legend="Tops", xpd=NA, inset=-0.1) stopifnot(identical(par("xpd"), FALSE)) ## left xpd as NA +} # [FastR] END Test snippet disabled since legend() uses graphics package +if(FALSE) { # [FastR] BEGIN Test snippet disabled since lines() uses graphics package ## lines.formula with 'subset' and no 'data' needed a tweak ## (R-help, John Field, 20008-11-14) x <- 1:5 @@ -583,6 +593,7 @@ y <- c(1,3,NA,2,5) plot(y ~ x, type="n") lines(y ~ x, subset = !is.na(y), col="red") ## error in 2.8.0 +} # [FastR] END Test snippet disabled since lines() uses graphics package ## prettyNum(*, drop0trailing) erronously dropped 0 in '1e10': diff --git a/com.oracle.truffle.r.native/gnur/tests/src/reg-tests-1c.R b/com.oracle.truffle.r.native/gnur/tests/src/reg-tests-1c.R index c3d42ddd60add143939819bde70e1e87678dc9ba..639e750e8aecfe81294f49edc8bd16db6dc95ecc 100644 --- a/com.oracle.truffle.r.native/gnur/tests/src/reg-tests-1c.R +++ b/com.oracle.truffle.r.native/gnur/tests/src/reg-tests-1c.R @@ -75,9 +75,11 @@ try ( k. <- kmeans(r., 3) ) # after rounding, have only two distinct points k. <- kmeans(r., 2) # fine +if(FALSE) { # [FastR] BEGIN Test snippet disabled since stem() uses graphics package ## PR#15376 stem(c(1, Inf)) ## hung in 3.0.1 +} # [FastR] END Test snippet disabled since stem() uses graphics package ## PR#15377, very long variable names @@ -203,11 +205,13 @@ agg <- aggregate.data.frame(x, by, mean) stopifnot(nrow(unique(by)) == nrow(agg)) ## rounding caused groups to be falsely merged +if(FALSE) { # [FastR] BEGIN Test snippet disabled since contour() uses graphics package ## PR#15454 set.seed(357) z <- matrix(c(runif(50, -1, 1), runif(50, -1e-190, 1e-190)), nrow = 10) contour(z) ## failed because rounding made crossing tests inconsistent +} # [FastR] END Test snippet disabled since contour() uses graphics package ## Various cases where zero length vectors were not handled properly ## by functions in base and utils, including PR#15499 diff --git a/com.oracle.truffle.r.native/gnur/tests/src/reg-tests-1d.R b/com.oracle.truffle.r.native/gnur/tests/src/reg-tests-1d.R index d460051fdcb07c27fd869d145f21ef9d45adf435..a189897798b3ebff289a8a07190b70e0bc2c8042 100644 --- a/com.oracle.truffle.r.native/gnur/tests/src/reg-tests-1d.R +++ b/com.oracle.truffle.r.native/gnur/tests/src/reg-tests-1d.R @@ -259,10 +259,12 @@ stopifnot(tt == 1, length(nt <- names(tt)) == 4, is.na(nt[4]) options(op) # (revert to default) +if(FALSE) { # [FastR] BEGIN Test snippet disabled since contour() uses graphics package ## contour() did not check args sufficiently tryCatch(contour(matrix(rnorm(100), 10, 10), levels = 0, labels = numeric()), error = function(e) e$message) ## caused segfault in R 3.3.1 and earlier +} # [FastR] END Test snippet disabled since contour() uses graphics package ## unique.warnings() needs better duplicated(): diff --git a/com.oracle.truffle.r.native/gnur/tests/src/reg-tests-2.R b/com.oracle.truffle.r.native/gnur/tests/src/reg-tests-2.R index cf09fd49224dc8b49783b29d1b5de741d93084a9..73adb38ea7dcefa30d7c1c6dd30ea383926e8b49 100644 --- a/com.oracle.truffle.r.native/gnur/tests/src/reg-tests-2.R +++ b/com.oracle.truffle.r.native/gnur/tests/src/reg-tests-2.R @@ -36,6 +36,7 @@ for(m in marg) print(apply(arr, print(m), sum)) for(m in marg) ## 75% of the time here was spent on the names print(dim(apply(arr, print(m), quantile, names=FALSE)) == c(5,d.arr[m])) +if(FALSE) { # [FastR] BEGIN Test snippet disabled since legend() and besselY() use graphics package ## Bessel nus <- c(0:5,10,20) @@ -58,6 +59,7 @@ which(bY >= 0) summary(bY <- besselY(2,nu = nu <- seq(3,300,len=51))) summary(bI <- besselI(x = x <- 10:700, 1)) ## end of moved from Bessel.Rd +} # [FastR] END Test snippet disabled since legend() and besselY() use graphics package ## data.frame set.seed(123) @@ -1172,6 +1174,7 @@ summary(sample.aov) ## failed in 1.8.1 +if(FALSE) { # [FastR] BEGIN Test snippet disabled since stem() uses graphics package ## PR#6645 stem() with near-constant values stem(rep(1, 100)) stem(rep(0.1, 10)) @@ -1179,6 +1182,7 @@ stem(c(rep(1, 10), 1+1.e-8)) stem(c(rep(1, 10), 1+1.e-9)) stem(c(rep(1, 10), 1+1.e-10), atom=0) # integer-overflow is avoided. ## had integer overflows in 1.8.1, and silly shifts of decimal point +} # [FastR] END Test snippet disabled since stem() uses graphics package ## PR#6633 warnings with vector op matrix, and more @@ -1232,9 +1236,11 @@ try(x[-c(1, NA)]) ## worked on some platforms, segfaulted on others in 1.8.1 +if(FALSE) { # [FastR] BEGIN Test snippet disabled since boxplot() uses graphics package ## vector 'border' (and no 'pch', 'cex' nor 'bg'): boxplot(count ~ spray, data = InsectSprays, border=2:7) ## gave warnings in 1.9.0 +} # [FastR] END Test snippet disabled since boxplot() uses graphics package summary(as.Date(paste("2002-12", 26:31, sep="-"))) ## printed all "2002.-12-29" in 1.9.1 {because digits was too small} @@ -1682,9 +1688,11 @@ a.frame ### end of tests added in 2.2.0 patched ### +if(FALSE) { # [FastR] BEGIN Test snippet disabled since pairs() uses graphics package ## test of fix of trivial warning PR#8252 pairs(iris[1:4], oma=rep(3,4)) ## warned in 2.2.0 only +} # [FastR] END Test snippet disabled since pairs() uses graphics package ## str(<dendrogram>)