Skip to content

Commit eb2d181

Browse files
author
hornik
committed
s/sapply/vapply.
git-svn-id: https://svn.r-project.org/R/trunk@88291 00db46b3-68df-0310-9c12-caf00c1e9a41
1 parent bce5e25 commit eb2d181

File tree

6 files changed

+37
-25
lines changed

6 files changed

+37
-25
lines changed

src/library/grid/R/primitives.R

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -797,8 +797,8 @@ validDetails.xspline <- function(x) {
797797
x$shape <- rep(x$shape, length.out=nx)
798798
# Watch out for id or id.length!
799799
index <- xsplineIndex(x)
800-
first <- sapply(index, min)
801-
last <- sapply(index, max)
800+
first <- vapply(index, min, 0)
801+
last <- vapply(index, max, 0)
802802
x$shape[c(first, last)] <- 0
803803
}
804804
x

src/library/grid/R/viewport.R

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -308,7 +308,7 @@ viewportorpath <- function(x) {
308308
}
309309

310310
vpListFromList <- function(vps) {
311-
if (all(sapply(vps, viewportorpath, simplify=TRUE))) {
311+
if (all(vapply(vps, viewportorpath, NA))) {
312312
class(vps) <- c("vpList", "viewport")
313313
vps
314314
} else {
@@ -325,7 +325,7 @@ vpList <- function(...) {
325325
# Viewports will be pushed in series
326326
vpStack <- function(...) {
327327
vps <- list(...)
328-
if (all(sapply(vps, viewportorpath, simplify=TRUE))) {
328+
if (all(vapply(vps, viewportorpath, NA))) {
329329
class(vps) <- c("vpStack", "viewport")
330330
vps
331331
} else {

src/library/stats/R/add.R

Lines changed: 18 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -172,8 +172,9 @@ add1.lm <- function(object, scope, scale = 0, test=c("none", "Chisq", "F"),
172172
class(z) <- "lm" # needed as deviance.lm calls generic residuals()
173173
RSS[1L] <- deviance(z)
174174
## workaround for PR#7842. terms.formula may have flipped interactions
175-
sTerms <- sapply(strsplit(Terms, ":", fixed=TRUE),
176-
function(x) paste(sort(x), collapse=":"))
175+
sTerms <- vapply(strsplit(Terms, ":", fixed=TRUE),
176+
function(x) paste(sort(x), collapse=":"),
177+
"")
177178
for(tt in scope) {
178179
stt <- paste(sort(strsplit(tt, ":")[[1L]]), collapse=":")
179180
usex <- match(asgn, match(stt, sTerms), 0L) > 0L
@@ -291,8 +292,9 @@ add1.glm <- function(object, scope, scale = 0,
291292
r <- z$residuals
292293
w <- z$weights
293294
## workaround for PR#7842. terms.formula may have flipped interactions
294-
sTerms <- sapply(strsplit(Terms, ":", fixed=TRUE),
295-
function(x) paste(sort(x), collapse=":"))
295+
sTerms <- vapply(strsplit(Terms, ":", fixed=TRUE),
296+
function(x) paste(sort(x), collapse=":"),
297+
"")
296298
for(tt in scope) {
297299
stt <- paste(sort(strsplit(tt, ":")[[1L]]), collapse=":")
298300
usex <- match(asgn, match(stt, sTerms), 0L) > 0L
@@ -623,10 +625,12 @@ factor.scope <- function(factor, scope)
623625
nmfac <- colnames(factor)
624626
## workaround as in PR#7842.
625627
## terms.formula may have flipped interactions
626-
nmfac0 <- sapply(strsplit(nmfac, ":", fixed=TRUE),
627-
function(x) paste(sort(x), collapse=":"))
628-
nmdrop0 <- sapply(strsplit(nmdrop, ":", fixed=TRUE),
629-
function(x) paste(sort(x), collapse=":"))
628+
nmfac0 <- vapply(strsplit(nmfac, ":", fixed=TRUE),
629+
function(x) paste(sort(x), collapse=":"),
630+
"")
631+
nmdrop0 <- vapply(strsplit(nmdrop, ":", fixed=TRUE),
632+
function(x) paste(sort(x), collapse=":"),
633+
"")
630634
where <- match(nmdrop0, nmfac0, 0L)
631635
if(any(!where))
632636
stop(sprintf(ngettext(sum(where==0),
@@ -653,10 +657,12 @@ factor.scope <- function(factor, scope)
653657
if(!is.null(nmfac)) {
654658
## workaround as in PR#7842.
655659
## terms.formula may have flipped interactions
656-
nmfac0 <- sapply(strsplit(nmfac, ":", fixed=TRUE),
657-
function(x) paste(sort(x), collapse=":"))
658-
nmadd0 <- sapply(strsplit(nmadd, ":", fixed=TRUE),
659-
function(x) paste(sort(x), collapse=":"))
660+
nmfac0 <- vapply(strsplit(nmfac, ":", fixed=TRUE),
661+
function(x) paste(sort(x), collapse=":"),
662+
"")
663+
nmadd0 <- vapply(strsplit(nmadd, ":", fixed=TRUE),
664+
function(x) paste(sort(x), collapse=":"),
665+
"")
660666
where <- match(nmfac0, nmadd0, 0L)
661667
if(any(!where))
662668
stop(sprintf(ngettext(sum(where==0),

src/library/stats/R/ansari.test.R

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -115,8 +115,10 @@ function(x, y, alternative = c("two.sided", "less", "greater"),
115115
## Compute statistics directly: computing the steps is
116116
## not faster.
117117
absigma <-
118-
sapply(sigma + c(diff(sigma)/2,
119-
sigma[length(sigma)]*1.01), ab)
118+
vapply(sigma + c(diff(sigma)/2,
119+
sigma[length(sigma)]*1.01),
120+
ab,
121+
0)
120122
switch(alternative, two.sided = cci(alpha),
121123
greater = c(cci(alpha*2)[1L], Inf),
122124
less = c(0, cci(alpha*2)[2L]))

src/library/stats/R/models.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -542,7 +542,7 @@ model.frame.default <-
542542
}
543543
if(possible_newdata && length(variables)) {
544544
## need to do this before subsetting and na.action
545-
nr2 <- max(sapply(variables, NROW))
545+
nr2 <- max(vapply(variables, NROW, 0L))
546546
if(nr2 != nr)
547547
warning(sprintf(paste0(ngettext(nr,
548548
"'newdata' had %d row",

src/library/utils/R/summRprof.R

Lines changed: 10 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -232,26 +232,30 @@ Rprof_memory_summary <- function(con, chunksize = 5000,
232232
if (label[i] == 1)
233233
newfirsts
234234
else if(label[i] > 1)
235-
sapply(chunk,
235+
vapply(chunk,
236236
function(line)
237237
paste(rev(line)[1L:min(label[i], length(line))],
238-
collapse = ":"))
238+
collapse = ":"),
239+
"")
239240
else # label[i] < 1
240-
sapply(chunk,
241+
vapply(chunk,
241242
function(line)
242243
paste(line[1L:min(-label[i], length(line))],
243-
collapse = ":")))
244+
collapse = ":"),
245+
"")
246+
)
244247
}
245248
} else if (aggregate) {
246249
index <- c(index,
247-
sapply(chunk,
250+
vapply(chunk,
248251
if(aggregate > 0)
249252
function(line)
250253
paste(rev(line)[1L:min(aggregate, length(line))], collapse = ":")
251254

252255
else # aggregate < 0
253256
function(line)
254-
paste(line[1L:min(-aggregate, length(line))], collapse = ":")))
257+
paste(line[1L:min(-aggregate, length(line))], collapse = ":"),
258+
""))
255259
}
256260

257261
if (length(chunk) < chunksize)

0 commit comments

Comments
 (0)