context("fdiff / D and fgrowth / G")
# rm(list = ls())
# TODO: test computations on irregular time series and panels
set.seed(101)
x <- abs(10*rnorm(100))
xNA <- x
xNA[sample.int(100, 20)] <- NA
f <- as.factor(rep(1:10, each = 10))
t <- as.factor(rep(1:10, 10))
data <- setRownames(wlddev[wlddev$iso3c %in% c("BLZ","IND","USA","SRB","GRL"), ])
g <- GRP(droplevels(data$iso3c))
td <- as.factor(data$year)
data <- num_vars(data)
dataNA <- na_insert(data)
m <- qM(data)
mNA <- qM(dataNA)
mNAc <- mNA
storage.mode(mNAc) <- "character"
# Creatung unordered data:
o = order(rnorm(100))
xuo = x[o]
xNAuo = xNA[o]
fuo = f[o]
tuo = t[o]
t2uo = seq_len(100)[o]
o = order(o)
od = order(rnorm(length(td)))
muo = m[od, ]
datauo = data[od, ]
guo = as_factor_GRP(g)[od]
tduo = td[od]
t2duo = seq_along(od)[od]
od = order(od)
basediff <- function(x, n = 1, diff = 1) c(rep(NA_real_, n * diff), diff.default(x, n, diff))
baselogdiff <- function(x, n = 1) c(rep(NA_real_, n), diff.default(log(x), n)*100)
basegrowth <- function(x, n = 1) c(rep(NA_real_, n), diff.default(x, n)/x[1:(length(x)-n)]*100)
# fdiff
test_that("fdiff performs like basediff", {
expect_equal(fdiff(1:10), basediff(1:10))
expect_equal(fdiff(1:10, 2), basediff(1:10, 2))
expect_equal(fdiff(1:10, 1, 2), basediff(1:10, 1, 2))
expect_equal(fdiff(1:10, 2, 2), basediff(1:10, 2, 2))
expect_equal(fdiff(-1:1), basediff(-1:1))
expect_equal(fdiff(x), basediff(x))
expect_equal(fdiff(x, 2, 2), basediff(x, 2, 2))
expect_equal(fdiff(xNA), basediff(xNA))
expect_equal(fdiff(xNA, 2, 2), basediff(xNA, 2, 2))
expect_equal(qM(fdiff(data)), setRownames(fdiff(m), NULL))
expect_equal(fdiff(m, stubs = FALSE), dapply(m, basediff))
expect_equal(fdiff(m, 2, 2, stubs = FALSE), dapply(m, basediff, 2, 2))
expect_equal(fdiff(mNA, stubs = FALSE), dapply(mNA, basediff))
expect_equal(fdiff(mNA, 2, 2, stubs = FALSE), dapply(mNA, basediff, 2, 2))
expect_equal(fdiff(data, stubs = FALSE), dapply(data, basediff))
expect_equal(fdiff(data, 2, 2, stubs = FALSE), dapply(data, basediff, 2, 2))
expect_equal(fdiff(dataNA, stubs = FALSE), dapply(dataNA, basediff))
expect_equal(fdiff(dataNA, 2, 2, stubs = FALSE), dapply(dataNA, basediff, 2, 2))
expect_equal(fdiff(x, 1, 1, f), BY(x, f, basediff, use.g.names = FALSE))
expect_equal(fdiff(x, 2, 2, f), BY(x, f, basediff, 2, 2, use.g.names = FALSE))
expect_equal(fdiff(xNA, 1, 1, f), BY(xNA, f, basediff, use.g.names = FALSE))
expect_equal(fdiff(xNA, 2, 2, f), BY(xNA, f, basediff, 2, 2, use.g.names = FALSE))
expect_equal(fdiff(m, 1, 1, g, stubs = FALSE), BY(m, g, basediff, use.g.names = FALSE))
expect_equal(fdiff(m, 2, 2, g, stubs = FALSE), BY(m, g, basediff, 2, 2, use.g.names = FALSE))
expect_equal(fdiff(mNA, 1, 1, g, stubs = FALSE), BY(mNA, g, basediff, use.g.names = FALSE))
expect_equal(fdiff(mNA, 2, 2, g, stubs = FALSE), BY(mNA, g, basediff, 2, 2, use.g.names = FALSE))
expect_equal(fdiff(data, 1, 1, g, stubs = FALSE), BY(data, g, basediff, use.g.names = FALSE))
expect_equal(fdiff(data, 2, 2, g, stubs = FALSE), BY(data, g, basediff, 2, 2, use.g.names = FALSE))
expect_equal(fdiff(dataNA, 1, 1, g, stubs = FALSE), BY(dataNA, g, basediff, use.g.names = FALSE))
expect_equal(fdiff(dataNA, 2, 2, g, stubs = FALSE), BY(dataNA, g, basediff, 2, 2, use.g.names = FALSE))
# Adding time-variable: Computing fully identified panel-differences !!
expect_equal(fdiff(x, 1, 1, f, t), BY(x, f, basediff, use.g.names = FALSE))
expect_equal(fdiff(x, 2, 2, f, t), BY(x, f, basediff, 2, 2, use.g.names = FALSE))
expect_equal(fdiff(xNA, 1, 1, f, t), BY(xNA, f, basediff, use.g.names = FALSE))
expect_equal(fdiff(xNA, 2, 2, f, t), BY(xNA, f, basediff, 2, 2, use.g.names = FALSE))
expect_equal(fdiff(m, 1, 1, g, td, stubs = FALSE), BY(m, g, basediff, use.g.names = FALSE))
expect_equal(fdiff(m, 2, 2, g, td, stubs = FALSE), BY(m, g, basediff, 2, 2, use.g.names = FALSE))
expect_equal(fdiff(mNA, 1, 1, g, td, stubs = FALSE), BY(mNA, g, basediff, use.g.names = FALSE))
expect_equal(fdiff(mNA, 2, 2, g, td, stubs = FALSE), BY(mNA, g, basediff, 2, 2, use.g.names = FALSE))
expect_equal(fdiff(data, 1, 1, g, td, stubs = FALSE), BY(data, g, basediff, use.g.names = FALSE))
expect_equal(fdiff(data, 2, 2, g, td, stubs = FALSE), BY(data, g, basediff, 2, 2, use.g.names = FALSE))
expect_equal(fdiff(dataNA, 1, 1, g, td, stubs = FALSE), BY(dataNA, g, basediff, use.g.names = FALSE))
expect_equal(fdiff(dataNA, 2, 2, g, td, stubs = FALSE), BY(dataNA, g, basediff, 2, 2, use.g.names = FALSE))
})
test_that("fdiff performs lagged/leaded and iterated (panel-) vector differences without errors", {
expect_visible(fdiff(1:10, -2:2))
expect_visible(fdiff(1:10, 1:2))
expect_visible(fdiff(1:10, -1:-2))
expect_visible(fdiff(1:10, 0))
expect_visible(fdiff(1:10, -2:2, 2))
expect_visible(fdiff(1:10, 1:2, 2))
expect_visible(fdiff(1:10, -1:-2, 2))
expect_visible(fdiff(1:10, 0, 2))
expect_visible(fdiff(1:10, -2:2, 1:2))
expect_visible(fdiff(1:10, 1:2, 1:2))
expect_visible(fdiff(1:10, -1:-2, 1:2))
expect_visible(fdiff(1:10, 0, 1:2))
expect_visible(fdiff(xNA, -2:2))
expect_visible(fdiff(xNA, 1:2))
expect_visible(fdiff(xNA, -1:-2))
expect_visible(fdiff(xNA, 0))
expect_visible(fdiff(xNA, -2:2, 2))
expect_visible(fdiff(xNA, 1:2, 2))
expect_visible(fdiff(xNA, -1:-2, 2))
expect_visible(fdiff(xNA, 0, 2))
expect_visible(fdiff(xNA, -2:2, 1:2))
expect_visible(fdiff(xNA, 1:2, 1:2))
expect_visible(fdiff(xNA, -1:-2, 1:2))
expect_visible(fdiff(xNA, 0, 1:2))
expect_visible(fdiff(xNA, -2:2, 1, f))
expect_visible(fdiff(xNA, 1:2, 1, f))
expect_visible(fdiff(xNA, -1:-2, 1, f))
expect_visible(fdiff(xNA, 0, 1, f))
expect_visible(fdiff(xNA, -2:2, 2, f))
expect_visible(fdiff(xNA, 1:2, 2, f))
expect_visible(fdiff(xNA, -1:-2, 2, f))
expect_visible(fdiff(xNA, 0, 2, f))
expect_visible(fdiff(xNA, -2:2, 1:2, f))
expect_visible(fdiff(xNA, 1:2, 1:2, f))
expect_visible(fdiff(xNA, -1:-2, 1:2, f))
expect_visible(fdiff(xNA, 0, 1:2, f))
expect_visible(fdiff(xNA, -2:2, 1, f, t))
expect_visible(fdiff(xNA, 1:2, 1, f, t))
expect_visible(fdiff(xNA, -1:-2, 1, f, t))
expect_visible(fdiff(xNA, 0, 1, f, t))
expect_visible(fdiff(xNA, -2:2, 2, f, t))
expect_visible(fdiff(xNA, 1:2, 2, f, t))
expect_visible(fdiff(xNA, -1:-2, 2, f, t))
expect_visible(fdiff(xNA, 0, 2, f, t))
expect_visible(fdiff(xNA, -2:2, 1:2, f, t))
expect_visible(fdiff(xNA, 1:2, 1:2, f, t))
expect_visible(fdiff(xNA, -1:-2, 1:2, f, t))
expect_visible(fdiff(xNA, 0, 1:2, f, t))
})
test_that("fdiff performs lagged/leaded and iterated (panel-) matrix differences without errors", {
expect_visible(fdiff(m, -2:2))
expect_visible(fdiff(m, 1:2))
expect_visible(fdiff(m, -1:-2))
expect_visible(fdiff(m, 0))
expect_visible(fdiff(m, -2:2, 2))
expect_visible(fdiff(m, 1:2, 2))
expect_visible(fdiff(m, -1:-2, 2))
expect_visible(fdiff(m, 0, 2))
expect_visible(fdiff(m, -2:2, 1:2))
expect_visible(fdiff(m, 1:2, 1:2))
expect_visible(fdiff(m, -1:-2, 1:2))
expect_visible(fdiff(m, 0, 1:2))
expect_visible(fdiff(m, -2:2, 1, g))
expect_visible(fdiff(m, 1:2, 1, g))
expect_visible(fdiff(m, -1:-2, 1, g))
expect_visible(fdiff(m, 0, 1, g))
expect_visible(fdiff(m, -2:2, 2, g))
expect_visible(fdiff(m, 1:2, 2, g))
expect_visible(fdiff(m, -1:-2, 2, g))
expect_visible(fdiff(m, 0, 2, g))
expect_visible(fdiff(m, -2:2, 1:2, g))
expect_visible(fdiff(m, 1:2, 1:2, g))
expect_visible(fdiff(m, -1:-2, 1:2, g))
expect_visible(fdiff(m, 0, 1:2, g))
expect_visible(fdiff(m, -2:2, 1, g, td))
expect_visible(fdiff(m, 1:2, 1, g, td))
expect_visible(fdiff(m, -1:-2, 1, g, td))
expect_visible(fdiff(m, 0, 1, g, td))
expect_visible(fdiff(m, -2:2, 2, g, td))
expect_visible(fdiff(m, 1:2, 2, g, td))
expect_visible(fdiff(m, -1:-2, 2, g, td))
expect_visible(fdiff(m, 0, 2, g, td))
expect_visible(fdiff(m, -2:2, 1:2, g, td))
expect_visible(fdiff(m, 1:2, 1:2, g, td))
expect_visible(fdiff(m, -1:-2, 1:2, g, td))
expect_visible(fdiff(m, 0, 1:2, g, td))
})
test_that("fdiff performs lagged/leaded and iterated (panel-) data.frame differences without errors", {
expect_visible(fdiff(data, -2:2))
expect_visible(fdiff(data, 1:2))
expect_visible(fdiff(data, -1:-2))
expect_visible(fdiff(data, 0))
expect_visible(fdiff(data, -2:2, 2))
expect_visible(fdiff(data, 1:2, 2))
expect_visible(fdiff(data, -1:-2, 2))
expect_visible(fdiff(data, 0, 2))
expect_visible(fdiff(data, -2:2, 1:2))
expect_visible(fdiff(data, 1:2, 1:2))
expect_visible(fdiff(data, -1:-2, 1:2))
expect_visible(fdiff(data, 0, 1:2))
expect_visible(fdiff(data, -2:2, 1, g))
expect_visible(fdiff(data, 1:2, 1, g))
expect_visible(fdiff(data, -1:-2, 1, g))
expect_visible(fdiff(data, 0, 1, g))
expect_visible(fdiff(data, -2:2, 2, g))
expect_visible(fdiff(data, 1:2, 2, g))
expect_visible(fdiff(data, -1:-2, 2, g))
expect_visible(fdiff(data, 0, 2, g))
expect_visible(fdiff(data, -2:2, 1:2, g))
expect_visible(fdiff(data, 1:2, 1:2, g))
expect_visible(fdiff(data, -1:-2, 1:2, g))
expect_visible(fdiff(data, 0, 1:2, g))
expect_visible(fdiff(data, -2:2, 1, g, td))
expect_visible(fdiff(data, 1:2, 1, g, td))
expect_visible(fdiff(data, -1:-2, 1, g, td))
expect_visible(fdiff(data, 0, 1, g, td))
expect_visible(fdiff(data, -2:2, 2, g, td))
expect_visible(fdiff(data, 1:2, 2, g, td))
expect_visible(fdiff(data, -1:-2, 2, g, td))
expect_visible(fdiff(data, 0, 2, g, td))
expect_visible(fdiff(data, -2:2, 1:2, g, td))
expect_visible(fdiff(data, 1:2, 1:2, g, td))
expect_visible(fdiff(data, -1:-2, 1:2, g, td))
expect_visible(fdiff(data, 0, 1:2, g, td))
})
test_that("fdiff correctly handles unordered time-series and panel-series computations", {
expect_equal(fdiff(x, -2:2, 1:2, t = 1:100), fdiff(x, -2:2, 1:2))
expect_equal(fdiff(xNA, -2:2, 1:2, t = 1:100), fdiff(xNA, -2:2, 1:2))
expect_equal(fdiff(m, -2:2, 1:2, t = seq_along(td)), fdiff(m, -2:2, 1:2))
expect_equal(fdiff(data, -2:2, 1:2, t = seq_along(td)), fdiff(data, -2:2, 1:2))
expect_equal(fdiff(xuo, -2:2, 1:2, t = t2uo)[o,], unclass(fdiff(x, -2:2, 1:2)))
expect_equal(fdiff(xNAuo, -2:2, 1:2, t = t2uo)[o,], unclass(fdiff(xNA, -2:2, 1:2)))
expect_equal(fdiff(muo, -2:2, 1:2, t = t2duo)[od,], unclass(fdiff(m, -2:2, 1:2)))
expect_equal(fdiff(datauo, -2:2, 1:2, t = t2duo)[od,], fdiff(data, -2:2, 1:2))
expect_equal(fdiff(xuo, -2:2, 1:2, fuo, tuo)[o,], unclass(fdiff(x, -2:2, 1:2, f, t)))
expect_equal(fdiff(xNAuo, -2:2, 1:2, fuo, tuo)[o,], unclass(fdiff(xNA, -2:2, 1:2, f, t)))
expect_equal(fdiff(muo, -2:2, 1:2, guo, tduo)[od,], unclass(fdiff(m, -2:2, 1:2, g, td)))
expect_equal(fdiff(datauo, -2:2, 1:2, guo, tduo)[od,], fdiff(data, -2:2, 1:2, g, td))
})
test_that("fdiff performs numerically stable in ordered computations", {
expect_true(all_obj_equal(replicate(50, fdiff(x), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fdiff(xNA), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fdiff(m), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fdiff(mNA), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fdiff(data), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fdiff(dataNA), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fdiff(x, 1, 1, f), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fdiff(x, -2:2, 1:2, f), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fdiff(xNA, 1, 1, f), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fdiff(xNA, -2:2, 1:2, f), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fdiff(m, 1, 1, g), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fdiff(m, -2:2, 1:2, g), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fdiff(mNA, 1, 1, g), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fdiff(mNA, -2:2, 1:2, g), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fdiff(data, 1, 1, g), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fdiff(data, -2:2, 1:2, g), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fdiff(dataNA, 1, 1, g), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fdiff(dataNA, -2:2, 1:2, g), simplify = FALSE)))
})
test_that("fdiff performs numerically stable in unordered computations", {
expect_true(all_obj_equal(replicate(50, fdiff(xuo, t = t2uo), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fdiff(xNAuo, t = t2uo), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fdiff(muo, t = t2duo), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fdiff(datauo, t = t2duo), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fdiff(xuo, 1, 1, fuo, tuo), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fdiff(xuo, -2:2, 1:2, fuo, tuo), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fdiff(muo, 1, 1, guo, tduo), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fdiff(muo, -2:2, 1:2, guo, tduo), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fdiff(datauo, 1, 1, guo, tduo), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fdiff(datauo, -2:2, 1:2, guo, tduo), simplify = FALSE)))
})
test_that("fdiff handles special values in the right way", {
expect_equal(fdiff(c(1,NA)), c(NA_real_,NA_real_))
expect_equal(fdiff(c(NA,1)), c(NA_real_,NA_real_))
expect_equal(fdiff(c(NaN,1)), c(NA_real_,NaN))
expect_equal(fdiff(c(1,NaN)), c(NA_real_,NaN))
expect_equal(fdiff(c(Inf,1)), c(NA,-Inf))
expect_equal(fdiff(c(1,Inf)), c(NA,Inf))
expect_equal(fdiff(c(Inf,NA)), c(NA_real_,NA_real_))
expect_equal(fdiff(c(NA,Inf)), c(NA_real_,NA_real_))
expect_equal(fdiff(c(Inf,-Inf)), c(NA,-Inf))
expect_equal(fdiff(c(-Inf,Inf)), c(NA,Inf))
expect_equal(fdiff(c(Inf,Inf)), c(NA,NaN))
expect_equal(fdiff(c(TRUE,TRUE)), c(NA_real_,0))
expect_equal(fdiff(c(TRUE,FALSE)), c(NA_real_,-1))
expect_equal(fdiff(c(FALSE,TRUE)), c(NA_real_,1))
})
test_that("fdiff produces errors for wrong input", {
# wrong type: normally guaranteed by C++
expect_error(fdiff("a")); 1
expect_error(fdiff(NA_character_)); 2
expect_error(fdiff(mNAc)); 3
expect_error(fdiff(wlddev)); 4
expect_error(fdiff(mNAc, f)); 5
expect_error(fdiff(x, "1", "2")); 6
# if n*diff equals or exceeds length(x), should give error
expect_error(fdiff(x,100)); 7
expect_error(fdiff(x,1,100)); 8
expect_error(fdiff(x,50,2)); 9
expect_error(fdiff(x,20,5)); 10
# if n*diff exceeds average group size, should give error
# expect_warning(fdiff(x,11,1,f)); 11 -> Some fail on i386 !!
# expect_warning(fdiff(x,1,11,f)); 12
# expect_warning(fdiff(x,1,11,f,t)); 13
# expect_warning(fdiff(x,11,1,f,t)); 14
# passing repeated n-values or non-positive or non-consecutive diff values should give error
expect_error(fdiff(x,c(1,1))); 15
expect_error(fdiff(x,c(-1,-1))); 16
expect_error(fdiff(x,1,c(1,1))); 17
expect_error(fdiff(x,1,c(-1,-1))); 18
expect_error(fdiff(x,1,2:1)); 19
expect_error(fdiff(x,1,0)); 20
expect_error(fdiff(x,1,-1)); 21
expect_error(fdiff(x,f)); 22 # common source of error probably is passing the factor in a wrong slot
expect_error(fdiff(x,1,f)); 23
expect_error(fdiff(x,c(1,1),1,f)); 24
expect_error(fdiff(x,c(1,1),1,f,t)); 25
expect_error(fdiff(x,1,c(1,1),f)); 26
expect_error(fdiff(x,1,c(1,1),f,t)); 27
expect_error(fdiff(x,1,2:1,f)); 28
expect_error(fdiff(x,1,2:1,f,t)); 29
expect_error(fdiff(x,1,0,f)); 30
expect_error(fdiff(x,1,0,f,t)); 31
expect_error(fdiff(x,1,-1,f)); 32
expect_error(fdiff(x,1,-1,f,t)); 33
# repeated values or gaps in time-variable should give error
expect_error(fdiff(1:3, t = c(1,1,2))); 34
expect_error(fdiff(1:3, t = c(1,2,2))); 35
expect_error(fdiff(1:3, t = c(1,2,1))); 36
expect_error(fdiff(1:10, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1,1,2,1:3,1:4))) # This is the only possible statement which does not throw a reteated timevar error because the first C++ index is 0, and omap is also initialized with 0's.
expect_error(fdiff(1:10, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1,1,1,1:3,1:4))); 37
expect_error(fdiff(1:10, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1:3,1:3,1,1,3,4))); 38
expect_error(fdiff(1:10, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1,2,2,1:3,1:4))); 39
expect_visible(fdiff(1:10, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1,2,4,1:3,1:4))); 40
expect_error(fdiff(1:10, diff = 2, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1,2,4,1:3,1:4))); 40
expect_error(fdiff(1:10, g = c(1,2,1,2,2,2,3,3,3,3), t = c(1:3,1:3,1:4))); 41
expect_visible(fdiff(1:10, g = c(1,1,1,2,2,2,3,3,4,3), t = c(1:3,1:3,1:4))); 42
expect_error(fdiff(1:10, diff = 2, g = c(1,1,1,2,2,2,3,3,4,3), t = c(1:3,1:3,1:4))); 42
# The usual stuff: Wrongly sized grouping vectors or time-variables
expect_error(fdiff(1:3, t = 1:2)); 43
expect_error(fdiff(1:3, t = 1:4)); 44
expect_error(fdiff(1:3, g = 1:2)); 45
expect_error(fdiff(1:3, g = 1:4)); 46
expect_error(fdiff(1:4, g = c(1,1,2,2), t = c(1,2,1))); 47
expect_error(fdiff(1:4, g = c(1,2,2), t = c(1,2,1,2))); 48
})
# D
test_that("D produces errors for wrong input", {
# wrong type: normally guaranteed by C++
expect_error(D("a"))
expect_error(D(NA_character_))
expect_error(D(mNAc))
expect_visible(D(wlddev))
expect_error(D(mNAc, f))
expect_error(D(x, "1", "2"))
# if n*diff equals or exceeds length(x), should give error
expect_error(D(x,100))
expect_error(D(x,1,100))
expect_error(D(x,50,2))
expect_error(D(x,20,5))
# if n*diff exceeds average group size, should give error
# expect_warning(D(x,11,1,f)) -> Some fail on i386
# expect_warning(D(x,1,11,f))
# expect_warning(D(x,1,11,f,t))
# expect_warning(D(x,11,1,f,t))
# passing repeated n-values or non-positive or non-consecutive diff values should give error
expect_error(D(x,c(1,1)))
expect_error(D(x,c(-1,-1)))
expect_error(D(x,1,c(1,1)))
expect_error(D(x,1,c(-1,-1)))
expect_error(D(x,1,2:1))
expect_error(D(x,1,0))
expect_error(D(x,1,-1))
expect_error(D(x,f)) # common source of error probably is passing the factor in a wrong slot
expect_error(D(x,1,f))
expect_error(D(x,c(1,1),1,f))
expect_error(D(x,c(1,1),1,f,t))
expect_error(D(x,1,c(1,1),f))
expect_error(D(x,1,c(1,1),f,t))
expect_error(D(x,1,2:1,f))
expect_error(D(x,1,2:1,f,t))
expect_error(D(x,1,0,f))
expect_error(D(x,1,0,f,t))
expect_error(D(x,1,-1,f))
expect_error(D(x,1,-1,f,t))
# repeated values or gaps in time-variable should give error
expect_error(D(1:3, t = c(1,1,2)))
expect_error(D(1:3, t = c(1,2,2)))
expect_error(D(1:3, t = c(1,2,1)))
expect_error(D(1:10, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1,1,2,1:3,1:4))) # This is the only possible statement which does not throw a reteated timevar error because the first C++ index is 0, and omap is also initialized with 0's.
expect_error(D(1:10, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1,1,1,1:3,1:4)))
expect_error(D(1:10, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1:3,1:3,1,1,3,4)))
expect_error(D(1:10, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1,2,2,1:3,1:4)))
expect_visible(D(1:10, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1,2,4,1:3,1:4)))
expect_error(D(1:10, diff = 2, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1,2,4,1:3,1:4)))
expect_error(D(1:10, g = c(1,2,1,2,2,2,3,3,3,3), t = c(1:3,1:3,1:4)))
expect_visible(D(1:10, g = c(1,1,1,2,2,2,3,3,4,3), t = c(1:3,1:3,1:4)))
expect_error(D(1:10, diff = 2, g = c(1,1,1,2,2,2,3,3,4,3), t = c(1:3,1:3,1:4)))
# The usual stuff: Wrongly sized grouping vectors or time-variables
expect_error(D(1:3, t = 1:2))
expect_error(D(1:3, t = 1:4))
expect_error(D(1:3, g = 1:2))
expect_error(D(1:3, g = 1:4))
expect_error(D(1:4, g = c(1,1,2,2), t = c(1,2,1)))
expect_error(D(1:4, g = c(1,2,2), t = c(1,2,1,2)))
})
test_that("D.data.frame method is foolproof", {
expect_visible(D(wlddev))
expect_visible(D(wlddev, by = wlddev$iso3c))
expect_error(D(wlddev, t = ~year))
expect_visible(D(wlddev, 1, 1, wlddev$iso3c))
expect_visible(D(wlddev, 1,1, ~iso3c))
expect_error(D(wlddev, 1, ~iso3c))
expect_visible(D(wlddev, 1, 1, ~iso3c + region))
expect_visible(D(wlddev, 1,1, wlddev$iso3c, wlddev$year))
expect_visible(D(wlddev, 1,1, ~iso3c, ~year))
expect_visible(D(wlddev, cols = 9:12))
expect_visible(D(wlddev, 1,1,~iso3c, cols = 9:12))
expect_visible(D(wlddev, 1,1,wlddev$iso3c, wlddev$year, cols = 9:12))
expect_visible(D(wlddev, 1,1,~iso3c, ~year, cols = 9:12))
expect_visible(D(wlddev, cols = c("PCGDP","LIFEEX")))
expect_visible(D(wlddev, 1,1,wlddev$iso3c, cols = c("PCGDP","LIFEEX")))
expect_visible(D(wlddev, 1,1,~iso3c, cols = c("PCGDP","LIFEEX")))
expect_visible(D(wlddev, 1,1,wlddev$iso3c, wlddev$year, cols = c("PCGDP","LIFEEX")))
expect_visible(D(wlddev, 1,1,~iso3c, ~year, cols = c("PCGDP","LIFEEX")))
expect_error(D(wlddev, cols = NULL))
expect_error(D(wlddev, 1,1,wlddev$iso3c, cols = NULL))
expect_error(D(wlddev, 1,1,~iso3c, cols = NULL))
expect_error(D(wlddev, 1,1,wlddev$iso3c, wlddev$year, cols = NULL))
expect_error(D(wlddev, 1,1,~iso3c, ~year, cols = NULL))
expect_error(D(wlddev, cols = 9:14))
expect_error(D(wlddev, 1,1,~iso3c, ~year, cols = 9:14))
expect_error(D(wlddev, cols = c("PCGDP","LIFEEX","bla")))
expect_error(D(wlddev, 1,1,~iso3c, ~year, cols = c("PCGDP","LIFEEX","bla")))
expect_warning(D(wlddev, w = 4))
expect_error(D(wlddev, t = "year"))
expect_warning(D(wlddev, g = ~year2))
expect_error(D(wlddev, t = ~year + region))
expect_error(D(wlddev, data))
expect_error(D(wlddev, 1,1,"iso3c"))
expect_error(D(wlddev, 1,1,~iso3c2))
expect_error(D(wlddev, 1,1,~iso3c + bla))
expect_error(D(wlddev, 1,1,t = rnorm(30)))
expect_warning(D(wlddev, 1,1,g = rnorm(30)))
expect_error(D(wlddev, 1,1,mtcars$mpg, 1:29))
expect_error(D(wlddev, 1,1,mtcars$mpg, mtcars$cyl)) # this gives a repeated values error first because length(g) == length(t)
expect_error(D(wlddev,1,1, ~iso3c2, ~year2))
expect_error(D(wlddev, cols = ~bla))
expect_visible(D(wlddev, 1,1,wlddev$iso3c, ~year, cols = 9:12))
expect_visible(D(wlddev, 1,1,~iso3c, wlddev$year, cols = 9:12))
expect_error(D(wlddev, 1,1,wlddev$iso3c, ~year + bla, cols = 9:12))
expect_error(D(wlddev, 2,1,~iso3c3, ~year, cols = 9:12))
expect_error(D(wlddev, cols = c("PC3GDP","LIFEEX")))
})
# fgrowth
test_that("fgrowth performs like basegrowth", {
expect_equal(fgrowth(1:10), basegrowth(1:10))
expect_equal(fgrowth(1:10, 2), basegrowth(1:10, 2))
expect_equal(fgrowth(-1:1), basegrowth(-1:1))
expect_equal(fgrowth(x), basegrowth(x))
expect_equal(fgrowth(x, 2), basegrowth(x, 2))
expect_equal(fgrowth(xNA), basegrowth(xNA))
expect_equal(fgrowth(xNA, 2), basegrowth(xNA, 2))
expect_equal(qM(fgrowth(data)), setRownames(fgrowth(m), NULL))
expect_equal(fgrowth(m, stubs = FALSE), dapply(m, basegrowth))
expect_equal(fgrowth(m, 2, stubs = FALSE), dapply(m, basegrowth, 2))
expect_equal(fgrowth(mNA, stubs = FALSE), dapply(mNA, basegrowth))
expect_equal(fgrowth(mNA, 2, stubs = FALSE), dapply(mNA, basegrowth, 2))
expect_equal(fgrowth(data, stubs = FALSE), dapply(data, basegrowth))
expect_equal(fgrowth(data, 2, stubs = FALSE), dapply(data, basegrowth, 2))
expect_equal(fgrowth(dataNA, stubs = FALSE), dapply(dataNA, basegrowth))
expect_equal(fgrowth(dataNA, 2, stubs = FALSE), dapply(dataNA, basegrowth, 2))
expect_equal(fgrowth(x, 1, 1, f), BY(x, f, basegrowth, use.g.names = FALSE))
expect_equal(fgrowth(x, 2, 1, f), BY(x, f, basegrowth, 2, use.g.names = FALSE))
expect_equal(fgrowth(xNA, 1, 1, f), BY(xNA, f, basegrowth, use.g.names = FALSE))
expect_equal(fgrowth(xNA, 2, 1, f), BY(xNA, f, basegrowth, 2, use.g.names = FALSE))
expect_equal(fgrowth(m, 1, 1, g, stubs = FALSE), BY(m, g, basegrowth, use.g.names = FALSE))
expect_equal(fgrowth(m, 2, 1, g, stubs = FALSE), BY(m, g, basegrowth, 2, use.g.names = FALSE))
expect_equal(fgrowth(mNA, 1, 1, g, stubs = FALSE), BY(mNA, g, basegrowth, use.g.names = FALSE))
expect_equal(fgrowth(mNA, 2, 1, g, stubs = FALSE), BY(mNA, g, basegrowth, 2, use.g.names = FALSE))
expect_equal(fgrowth(data, 1, 1, g, stubs = FALSE), BY(data, g, basegrowth, use.g.names = FALSE))
expect_equal(fgrowth(data, 2, 1, g, stubs = FALSE), BY(data, g, basegrowth, 2, use.g.names = FALSE))
expect_equal(fgrowth(dataNA, 1, 1, g, stubs = FALSE), BY(dataNA, g, basegrowth, use.g.names = FALSE))
expect_equal(fgrowth(dataNA, 2, 1, g, stubs = FALSE), BY(dataNA, g, basegrowth, 2, use.g.names = FALSE))
# Adding time-variable: Computing fully identified panel-growtherences !!
expect_equal(fgrowth(x, 1, 1, f, t), BY(x, f, basegrowth, use.g.names = FALSE))
expect_equal(fgrowth(x, 2, 1, f, t), BY(x, f, basegrowth, 2, use.g.names = FALSE))
expect_equal(fgrowth(xNA, 1, 1, f, t), BY(xNA, f, basegrowth, use.g.names = FALSE))
expect_equal(fgrowth(xNA, 2, 1, f, t), BY(xNA, f, basegrowth, 2, use.g.names = FALSE))
expect_equal(fgrowth(m, 1, 1, g, td, stubs = FALSE), BY(m, g, basegrowth, use.g.names = FALSE))
expect_equal(fgrowth(m, 2, 1, g, td, stubs = FALSE), BY(m, g, basegrowth, 2, use.g.names = FALSE))
expect_equal(fgrowth(mNA, 1, 1, g, td, stubs = FALSE), BY(mNA, g, basegrowth, use.g.names = FALSE))
expect_equal(fgrowth(mNA, 2, 1, g, td, stubs = FALSE), BY(mNA, g, basegrowth, 2, use.g.names = FALSE))
expect_equal(fgrowth(data, 1, 1, g, td, stubs = FALSE), BY(data, g, basegrowth, use.g.names = FALSE))
expect_equal(fgrowth(data, 2, 1, g, td, stubs = FALSE), BY(data, g, basegrowth, 2, use.g.names = FALSE))
expect_equal(fgrowth(dataNA, 1, 1, g, td, stubs = FALSE), BY(dataNA, g, basegrowth, use.g.names = FALSE))
expect_equal(fgrowth(dataNA, 2, 1, g, td, stubs = FALSE), BY(dataNA, g, basegrowth, 2, use.g.names = FALSE))
})
test_that("fgrowth performs lagged/leaded and iterated (panel-) vector growth reates without errors", {
expect_visible(fgrowth(1:10, -2:2))
expect_visible(fgrowth(1:10, 1:2))
expect_visible(fgrowth(1:10, -1:-2))
expect_visible(fgrowth(1:10, 0))
expect_visible(fgrowth(1:10, -2:2, 2))
expect_visible(fgrowth(1:10, 1:2, 2))
expect_visible(fgrowth(1:10, -1:-2, 2))
expect_visible(fgrowth(1:10, 0, 2))
expect_visible(fgrowth(1:10, -2:2, 1:2))
expect_visible(fgrowth(1:10, 1:2, 1:2))
expect_visible(fgrowth(1:10, -1:-2, 1:2))
expect_visible(fgrowth(1:10, 0, 1:2))
expect_visible(fgrowth(xNA, -2:2))
expect_visible(fgrowth(xNA, 1:2))
expect_visible(fgrowth(xNA, -1:-2))
expect_visible(fgrowth(xNA, 0))
expect_visible(fgrowth(xNA, -2:2, 2))
expect_visible(fgrowth(xNA, 1:2, 2))
expect_visible(fgrowth(xNA, -1:-2, 2))
expect_visible(fgrowth(xNA, 0, 2))
expect_visible(fgrowth(xNA, -2:2, 1:2))
expect_visible(fgrowth(xNA, 1:2, 1:2))
expect_visible(fgrowth(xNA, -1:-2, 1:2))
expect_visible(fgrowth(xNA, 0, 1:2))
expect_visible(fgrowth(xNA, -2:2, 1, f))
expect_visible(fgrowth(xNA, 1:2, 1, f))
expect_visible(fgrowth(xNA, -1:-2, 1, f))
expect_visible(fgrowth(xNA, 0, 1, f))
expect_visible(fgrowth(xNA, -2:2, 2, f))
expect_visible(fgrowth(xNA, 1:2, 2, f))
expect_visible(fgrowth(xNA, -1:-2, 2, f))
expect_visible(fgrowth(xNA, 0, 2, f))
expect_visible(fgrowth(xNA, -2:2, 1:2, f))
expect_visible(fgrowth(xNA, 1:2, 1:2, f))
expect_visible(fgrowth(xNA, -1:-2, 1:2, f))
expect_visible(fgrowth(xNA, 0, 1:2, f))
expect_visible(fgrowth(xNA, -2:2, 1, f, t))
expect_visible(fgrowth(xNA, 1:2, 1, f, t))
expect_visible(fgrowth(xNA, -1:-2, 1, f, t))
expect_visible(fgrowth(xNA, 0, 1, f, t))
expect_visible(fgrowth(xNA, -2:2, 2, f, t))
expect_visible(fgrowth(xNA, 1:2, 2, f, t))
expect_visible(fgrowth(xNA, -1:-2, 2, f, t))
expect_visible(fgrowth(xNA, 0, 2, f, t))
expect_visible(fgrowth(xNA, -2:2, 1:2, f, t))
expect_visible(fgrowth(xNA, 1:2, 1:2, f, t))
expect_visible(fgrowth(xNA, -1:-2, 1:2, f, t))
expect_visible(fgrowth(xNA, 0, 1:2, f, t))
})
test_that("fgrowth performs lagged/leaded and iterated (panel-) matrix growth rates without errors", {
expect_visible(fgrowth(m, -2:2))
expect_visible(fgrowth(m, 1:2))
expect_visible(fgrowth(m, -1:-2))
expect_visible(fgrowth(m, 0))
expect_visible(fgrowth(m, -2:2, 2))
expect_visible(fgrowth(m, 1:2, 2))
expect_visible(fgrowth(m, -1:-2, 2))
expect_visible(fgrowth(m, 0, 2))
expect_visible(fgrowth(m, -2:2, 1:2))
expect_visible(fgrowth(m, 1:2, 1:2))
expect_visible(fgrowth(m, -1:-2, 1:2))
expect_visible(fgrowth(m, 0, 1:2))
expect_visible(fgrowth(m, -2:2, 1, g))
expect_visible(fgrowth(m, 1:2, 1, g))
expect_visible(fgrowth(m, -1:-2, 1, g))
expect_visible(fgrowth(m, 0, 1, g))
expect_visible(fgrowth(m, -2:2, 2, g))
expect_visible(fgrowth(m, 1:2, 2, g))
expect_visible(fgrowth(m, -1:-2, 2, g))
expect_visible(fgrowth(m, 0, 2, g))
expect_visible(fgrowth(m, -2:2, 1:2, g))
expect_visible(fgrowth(m, 1:2, 1:2, g))
expect_visible(fgrowth(m, -1:-2, 1:2, g))
expect_visible(fgrowth(m, 0, 1:2, g))
expect_visible(fgrowth(m, -2:2, 1, g, td))
expect_visible(fgrowth(m, 1:2, 1, g, td))
expect_visible(fgrowth(m, -1:-2, 1, g, td))
expect_visible(fgrowth(m, 0, 1, g, td))
expect_visible(fgrowth(m, -2:2, 2, g, td))
expect_visible(fgrowth(m, 1:2, 2, g, td))
expect_visible(fgrowth(m, -1:-2, 2, g, td))
expect_visible(fgrowth(m, 0, 2, g, td))
expect_visible(fgrowth(m, -2:2, 1:2, g, td))
expect_visible(fgrowth(m, 1:2, 1:2, g, td))
expect_visible(fgrowth(m, -1:-2, 1:2, g, td))
expect_visible(fgrowth(m, 0, 1:2, g, td))
})
test_that("fgrowth performs lagged/leaded and iterated (panel-) data.frame growth rates without errors", {
expect_visible(fgrowth(data, -2:2))
expect_visible(fgrowth(data, 1:2))
expect_visible(fgrowth(data, -1:-2))
expect_visible(fgrowth(data, 0))
expect_visible(fgrowth(data, -2:2, 2))
expect_visible(fgrowth(data, 1:2, 2))
expect_visible(fgrowth(data, -1:-2, 2))
expect_visible(fgrowth(data, 0, 2))
expect_visible(fgrowth(data, -2:2, 1:2))
expect_visible(fgrowth(data, 1:2, 1:2))
expect_visible(fgrowth(data, -1:-2, 1:2))
expect_visible(fgrowth(data, 0, 1:2))
expect_visible(fgrowth(data, -2:2, 1, g))
expect_visible(fgrowth(data, 1:2, 1, g))
expect_visible(fgrowth(data, -1:-2, 1, g))
expect_visible(fgrowth(data, 0, 1, g))
expect_visible(fgrowth(data, -2:2, 2, g))
expect_visible(fgrowth(data, 1:2, 2, g))
expect_visible(fgrowth(data, -1:-2, 2, g))
expect_visible(fgrowth(data, 0, 2, g))
expect_visible(fgrowth(data, -2:2, 1:2, g))
expect_visible(fgrowth(data, 1:2, 1:2, g))
expect_visible(fgrowth(data, -1:-2, 1:2, g))
expect_visible(fgrowth(data, 0, 1:2, g))
expect_visible(fgrowth(data, -2:2, 1, g, td))
expect_visible(fgrowth(data, 1:2, 1, g, td))
expect_visible(fgrowth(data, -1:-2, 1, g, td))
expect_visible(fgrowth(data, 0, 1, g, td))
expect_visible(fgrowth(data, -2:2, 2, g, td))
expect_visible(fgrowth(data, 1:2, 2, g, td))
expect_visible(fgrowth(data, -1:-2, 2, g, td))
expect_visible(fgrowth(data, 0, 2, g, td))
expect_visible(fgrowth(data, -2:2, 1:2, g, td))
expect_visible(fgrowth(data, 1:2, 1:2, g, td))
expect_visible(fgrowth(data, -1:-2, 1:2, g, td))
expect_visible(fgrowth(data, 0, 1:2, g, td))
})
test_that("fgrowth correctly handles unordered time-series and panel-series computations", {
expect_equal(fgrowth(x, -2:2, 1:2, t = 1:100), fgrowth(x, -2:2, 1:2))
expect_equal(fgrowth(xNA, -2:2, 1:2, t = 1:100), fgrowth(xNA, -2:2, 1:2))
expect_equal(fgrowth(m, -2:2, 1:2, t = seq_along(td)), fgrowth(m, -2:2, 1:2))
expect_equal(fgrowth(data, -2:2, 1:2, t = seq_along(td)), fgrowth(data, -2:2, 1:2))
expect_equal(fgrowth(xuo, -2:2, 1:2, t = t2uo)[o,], unclass(fgrowth(x, -2:2, 1:2)))
expect_equal(fgrowth(xNAuo, -2:2, 1:2, t = t2uo)[o,], unclass(fgrowth(xNA, -2:2, 1:2)))
expect_equal(fgrowth(muo, -2:2, 1:2, t = t2duo)[od,], unclass(fgrowth(m, -2:2, 1:2)))
expect_equal(fgrowth(datauo, -2:2, 1:2, t = t2duo)[od,], fgrowth(data, -2:2, 1:2))
expect_equal(fgrowth(xuo, -2:2, 1:2, fuo, tuo)[o,], unclass(fgrowth(x, -2:2, 1:2, f, t)))
expect_equal(fgrowth(xNAuo, -2:2, 1:2, fuo, tuo)[o,], unclass(fgrowth(xNA, -2:2, 1:2, f, t)))
expect_equal(fgrowth(muo, -2:2, 1:2, guo, tduo)[od,], unclass(fgrowth(m, -2:2, 1:2, g, td)))
expect_equal(fgrowth(datauo, -2:2, 1:2, guo, tduo)[od,], fgrowth(data, -2:2, 1:2, g, td))
})
test_that("fgrowth performs numerically stable in ordered computations", {
expect_true(all_obj_equal(replicate(50, fgrowth(x), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(xNA), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(m), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(mNA), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(data), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(dataNA), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(x, 1, 1, f), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(x, -2:2, 1:2, f), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(xNA, 1, 1, f), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(xNA, -2:2, 1:2, f), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(m, 1, 1, g), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(m, -2:2, 1:2, g), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(mNA, 1, 1, g), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(mNA, -2:2, 1:2, g), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(data, 1, 1, g), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(data, -2:2, 1:2, g), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(dataNA, 1, 1, g), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(dataNA, -2:2, 1:2, g), simplify = FALSE)))
})
test_that("fgrowth performs numerically stable in unordered computations", {
expect_true(all_obj_equal(replicate(50, fgrowth(xuo, t = t2uo), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(xNAuo, t = t2uo), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(muo, t = t2duo), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(datauo, t = t2duo), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(xuo, 1, 1, fuo, tuo), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(xuo, -2:2, 1:2, fuo, tuo), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(muo, 1, 1, guo, tduo), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(muo, -2:2, 1:2, guo, tduo), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(datauo, 1, 1, guo, tduo), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(datauo, -2:2, 1:2, guo, tduo), simplify = FALSE)))
})
test_that("fgrowth handles special values in the right way", {
expect_equal(fgrowth(c(1,NA)), c(NA_real_,NA_real_))
expect_equal(fgrowth(c(NA,1)), c(NA_real_,NA_real_))
expect_equal(fgrowth(c(NaN,1)), c(NA_real_,NaN))
expect_equal(fgrowth(c(1,NaN)), c(NA_real_,NaN))
expect_equal(fgrowth(c(Inf,1)), c(NA,NaN))
expect_equal(fgrowth(c(1,Inf)), c(NA,Inf))
expect_equal(fgrowth(c(Inf,NA)), c(NA_real_,NA_real_))
expect_equal(fgrowth(c(NA,Inf)), c(NA_real_,NA_real_))
expect_equal(fgrowth(c(Inf,-Inf)), c(NA,NaN))
expect_equal(fgrowth(c(-Inf,Inf)), c(NA,NaN))
expect_equal(fgrowth(c(Inf,Inf)), c(NA,NaN))
expect_equal(fgrowth(c(TRUE,TRUE)), c(NA_real_,0))
expect_equal(fgrowth(c(TRUE,FALSE)), c(NA_real_,-100))
expect_equal(fgrowth(c(FALSE,TRUE)), c(NA_real_,Inf))
})
test_that("fgrowth produces errors for wrong input", {
# wrong type: normally guaranteed by C++
expect_error(fgrowth("a"))
expect_error(fgrowth(NA_character_))
expect_error(fgrowth(mNAc))
expect_error(fgrowth(wlddev))
expect_error(fgrowth(mNAc, f))
expect_error(fgrowth(x, "1", "2"))
# if n*growth equals or exceeds length(x), should give error
expect_error(fgrowth(x,100))
expect_error(fgrowth(x,1,100))
expect_error(fgrowth(x,50,2))
expect_error(fgrowth(x,20,5))
# if n*growth exceeds average group size, should give error
# expect_warning(fgrowth(x,11,1,f)) -> some fail on i386
# expect_warning(fgrowth(x,1,11,f))
# expect_warning(fgrowth(x,1,11,f,t))
# expect_warning(fgrowth(x,11,1,f,t))
# passing repeated n-values or non-positive or non-consecutive growth values should give error
expect_error(fgrowth(x,c(1,1)))
expect_error(fgrowth(x,c(-1,-1)))
expect_error(fgrowth(x,1,c(1,1)))
expect_error(fgrowth(x,1,c(-1,-1)))
expect_error(fgrowth(x,1,2:1))
expect_error(fgrowth(x,1,0))
expect_error(fgrowth(x,1,-1))
expect_error(fgrowth(x,f)) # common source of error probably is passing the factor in a wrong slot
expect_error(fgrowth(x,1,f))
expect_error(fgrowth(x,c(1,1),1,f))
expect_error(fgrowth(x,c(1,1),1,f,t))
expect_error(fgrowth(x,1,c(1,1),f))
expect_error(fgrowth(x,1,c(1,1),f,t))
expect_error(fgrowth(x,1,2:1,f))
expect_error(fgrowth(x,1,2:1,f,t))
expect_error(fgrowth(x,1,0,f))
expect_error(fgrowth(x,1,0,f,t))
expect_error(fgrowth(x,1,-1,f))
expect_error(fgrowth(x,1,-1,f,t))
# repeated values or gaps in time-variable should give error
expect_error(fgrowth(1:3, t = c(1,1,2)))
expect_error(fgrowth(1:3, t = c(1,2,2)))
expect_error(fgrowth(1:3, t = c(1,2,1)))
expect_error(fgrowth(1:10, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1,1,2,1:3,1:4))) # This is the only possible statement which does not throw a reteated timevar error because the first C++ index is 0, and omap is also initialized with 0's.
expect_error(fgrowth(1:10, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1,1,1,1:3,1:4)))
expect_error(fgrowth(1:10, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1:3,1:3,1,1,3,4)))
expect_error(fgrowth(1:10, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1,2,2,1:3,1:4)))
expect_visible(fgrowth(1:10, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1,2,4,1:3,1:4)))
expect_error(fgrowth(1:10, diff = 2, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1,2,4,1:3,1:4)))
expect_error(fgrowth(1:10, g = c(1,2,1,2,2,2,3,3,3,3), t = c(1:3,1:3,1:4)))
expect_visible(fgrowth(1:10, g = c(1,1,1,2,2,2,3,3,4,3), t = c(1:3,1:3,1:4)))
expect_error(fgrowth(1:10, diff = 2, g = c(1,1,1,2,2,2,3,3,4,3), t = c(1:3,1:3,1:4)))
# The usual stuff: Wrongly sized grouping vectors or time-variables
expect_error(fgrowth(1:3, t = 1:2))
expect_error(fgrowth(1:3, t = 1:4))
expect_error(fgrowth(1:3, g = 1:2))
expect_error(fgrowth(1:3, g = 1:4))
expect_error(fgrowth(1:4, g = c(1,1,2,2), t = c(1,2,1)))
expect_error(fgrowth(1:4, g = c(1,2,2), t = c(1,2,1,2)))
})
# G
test_that("G produces errors for wrong input", {
# wrong type: normally guaranteed by C++
expect_error(G("a"))
expect_error(G(NA_character_))
expect_error(G(mNAc))
expect_visible(G(wlddev))
expect_error(G(mNAc, f))
expect_error(G(x, "1", "2"))
# if n*diff equals or exceeds length(x), should give error
expect_error(G(x,100))
expect_error(G(x,1,100))
expect_error(G(x,50,2))
expect_error(G(x,20,5))
# if n*diff exceeds average group size, should give error
# expect_warning(G(x,11,1,f)) -> Some fail on i386
# expect_warning(G(x,1,11,f))
# expect_warning(G(x,1,11,f,t))
# expect_warning(G(x,11,1,f,t))
# passing repeated n-values or non-positive or non-consecutive diff values should give error
expect_error(G(x,c(1,1)))
expect_error(G(x,c(-1,-1)))
expect_error(G(x,1,c(1,1)))
expect_error(G(x,1,c(-1,-1)))
expect_error(G(x,1,2:1))
expect_error(G(x,1,0))
expect_error(G(x,1,-1))
expect_error(G(x,f)) # common source of error probably is passing the factor in a wrong slot
expect_error(G(x,1,f))
expect_error(G(x,c(1,1),1,f))
expect_error(G(x,c(1,1),1,f,t))
expect_error(G(x,1,c(1,1),f))
expect_error(G(x,1,c(1,1),f,t))
expect_error(G(x,1,2:1,f))
expect_error(G(x,1,2:1,f,t))
expect_error(G(x,1,0,f))
expect_error(G(x,1,0,f,t))
expect_error(G(x,1,-1,f))
expect_error(G(x,1,-1,f,t))
# repeated values or gaps in time-variable should give error
expect_error(G(1:3, t = c(1,1,2)))
expect_error(G(1:3, t = c(1,2,2)))
expect_error(G(1:3, t = c(1,2,1)))
expect_error(G(1:10, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1,1,2,1:3,1:4))) # This is the only possible statement which does not throw a reteated timevar error because the first C++ index is 0, and omap is also initialized with 0's.
expect_error(G(1:10, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1,1,1,1:3,1:4)))
expect_error(G(1:10, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1:3,1:3,1,1,3,4)))
expect_error(G(1:10, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1,2,2,1:3,1:4)))
expect_visible(G(1:10, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1,2,4,1:3,1:4)))
expect_error(G(1:10, diff = 2, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1,2,4,1:3,1:4)))
expect_error(G(1:10, g = c(1,2,1,2,2,2,3,3,3,3), t = c(1:3,1:3,1:4)))
expect_visible(G(1:10, g = c(1,1,1,2,2,2,3,3,4,3), t = c(1:3,1:3,1:4)))
expect_error(G(1:10, diff = 2, g = c(1,1,1,2,2,2,3,3,4,3), t = c(1:3,1:3,1:4)))
# The usual stuff: Wrongly sized grouping vectors or time-variables
expect_error(G(1:3, t = 1:2))
expect_error(G(1:3, t = 1:4))
expect_error(G(1:3, g = 1:2))
expect_error(G(1:3, g = 1:4))
expect_error(G(1:4, g = c(1,1,2,2), t = c(1,2,1)))
expect_error(G(1:4, g = c(1,2,2), t = c(1,2,1,2)))
})
test_that("G.data.frame method is foolproof", {
expect_visible(G(wlddev))
expect_visible(G(wlddev, by = wlddev$iso3c))
expect_error(G(wlddev, t = ~year))
expect_visible(G(wlddev, 1, 1, wlddev$iso3c))
expect_visible(G(wlddev, 1,1, ~iso3c))
expect_error(G(wlddev, 1, ~iso3c))
expect_visible(G(wlddev, 1, 1, ~iso3c + region))
expect_visible(G(wlddev, 1,1, wlddev$iso3c, wlddev$year))
expect_visible(G(wlddev, 1,1, ~iso3c, ~year))
expect_visible(G(wlddev, cols = 9:12))
expect_visible(G(wlddev, 1,1,~iso3c, cols = 9:12))
expect_visible(G(wlddev, 1,1,wlddev$iso3c, wlddev$year, cols = 9:12))
expect_visible(G(wlddev, 1,1,~iso3c, ~year, cols = 9:12))
expect_visible(G(wlddev, cols = c("PCGDP","LIFEEX")))
expect_visible(G(wlddev, 1,1,wlddev$iso3c, cols = c("PCGDP","LIFEEX")))
expect_visible(G(wlddev, 1,1,~iso3c, cols = c("PCGDP","LIFEEX")))
expect_visible(G(wlddev, 1,1,wlddev$iso3c, wlddev$year, cols = c("PCGDP","LIFEEX")))
expect_visible(G(wlddev, 1,1,~iso3c, ~year, cols = c("PCGDP","LIFEEX")))
expect_error(G(wlddev, cols = NULL))
expect_error(G(wlddev, 1,1,wlddev$iso3c, cols = NULL))
expect_error(G(wlddev, 1,1,~iso3c, cols = NULL))
expect_error(G(wlddev, 1,1,wlddev$iso3c, wlddev$year, cols = NULL))
expect_error(G(wlddev, 1,1,~iso3c, ~year, cols = NULL))
expect_error(G(wlddev, cols = 9:14))
expect_error(G(wlddev, 1,1,~iso3c, ~year, cols = 9:14))
expect_error(G(wlddev, cols = c("PCGDP","LIFEEX","bla")))
expect_error(G(wlddev, 1,1,~iso3c, ~year, cols = c("PCGDP","LIFEEX","bla")))
expect_warning(G(wlddev, w = 4))
expect_error(G(wlddev, t = "year"))
expect_warning(G(wlddev, g = ~year2))
expect_error(G(wlddev, t = ~year + region))
expect_error(G(wlddev, data))
expect_error(G(wlddev, 1,1,"iso3c"))
expect_error(G(wlddev, 1,1,~iso3c2))
expect_error(G(wlddev, 1,1,~iso3c + bla))
expect_error(G(wlddev, 1,1,t = rnorm(30)))
expect_warning(G(wlddev, 1,1,g = rnorm(30)))
expect_error(G(wlddev, 1,1,mtcars$mpg, 1:29))
expect_error(G(wlddev, 1,1,mtcars$mpg, mtcars$cyl)) # this gives a repeated values error first because length(g) == length(t)
expect_error(G(wlddev,1,1, ~iso3c2, ~year2))
expect_error(G(wlddev, cols = ~bla))
expect_visible(G(wlddev, 1,1,wlddev$iso3c, ~year, cols = 9:12))
expect_visible(G(wlddev, 1,1,~iso3c, wlddev$year, cols = 9:12))
expect_error(G(wlddev, 1,1,wlddev$iso3c, ~year + bla, cols = 9:12))
expect_error(G(wlddev, 2,1,~iso3c3, ~year, cols = 9:12))
expect_error(G(wlddev, cols = c("PC3GDP","LIFEEX")))
})
# fgrowth with logdiff option:
test_that("fgrowth with logdiff performs like baselogdiff", {
expect_equal(fgrowth(1:10, logdiff = TRUE), baselogdiff(1:10))
expect_equal(fgrowth(1:10, 2, logdiff = TRUE), baselogdiff(1:10, 2))
# expect_equal(fgrowth(-1:1, logdiff = TRUE), suppressWarnings(baselogdiff(-1:1))) # NaN -Inf mismatch
expect_equal(fgrowth(x, logdiff = TRUE), baselogdiff(x))
expect_equal(fgrowth(x, 2, logdiff = TRUE), baselogdiff(x, 2))
expect_equal(fgrowth(xNA, logdiff = TRUE), baselogdiff(xNA))
expect_equal(fgrowth(xNA, 2, logdiff = TRUE), baselogdiff(xNA, 2))
expect_equal(qM(fgrowth(data, logdiff = TRUE)), setRownames(fgrowth(m, logdiff = TRUE), NULL))
expect_equal(fgrowth(m, stubs = FALSE, logdiff = TRUE), dapply(m, baselogdiff))
expect_equal(fgrowth(m, 2, stubs = FALSE, logdiff = TRUE), dapply(m, baselogdiff, 2))
expect_equal(fgrowth(mNA, stubs = FALSE, logdiff = TRUE), dapply(mNA, baselogdiff))
expect_equal(fgrowth(mNA, 2, stubs = FALSE, logdiff = TRUE), dapply(mNA, baselogdiff, 2))
expect_equal(fgrowth(x, 1, 1, f, logdiff = TRUE), BY(x, f, baselogdiff, use.g.names = FALSE))
expect_equal(fgrowth(x, 2, 1, f, logdiff = TRUE), BY(x, f, baselogdiff, 2, use.g.names = FALSE))
expect_equal(fgrowth(xNA, 1, 1, f, logdiff = TRUE), BY(xNA, f, baselogdiff, use.g.names = FALSE))
expect_equal(fgrowth(xNA, 2, 1, f, logdiff = TRUE), BY(xNA, f, baselogdiff, 2, use.g.names = FALSE))
expect_equal(fgrowth(m, 1, 1, g, stubs = FALSE, logdiff = TRUE), BY(m, g, baselogdiff, use.g.names = FALSE))
expect_equal(fgrowth(m, 2, 1, g, stubs = FALSE, logdiff = TRUE), BY(m, g, baselogdiff, 2, use.g.names = FALSE))
expect_equal(fgrowth(mNA, 1, 1, g, stubs = FALSE, logdiff = TRUE), BY(mNA, g, baselogdiff, use.g.names = FALSE))
expect_equal(fgrowth(mNA, 2, 1, g, stubs = FALSE, logdiff = TRUE), BY(mNA, g, baselogdiff, 2, use.g.names = FALSE))
expect_equal(fgrowth(data, 1, 1, g, stubs = FALSE, logdiff = TRUE), BY(data, g, baselogdiff, use.g.names = FALSE))
expect_equal(fgrowth(data, 2, 1, g, stubs = FALSE, logdiff = TRUE), BY(data, g, baselogdiff, 2, use.g.names = FALSE))
expect_equal(fgrowth(dataNA, 1, 1, g, stubs = FALSE, logdiff = TRUE), BY(dataNA, g, baselogdiff, use.g.names = FALSE))
expect_equal(fgrowth(dataNA, 2, 1, g, stubs = FALSE, logdiff = TRUE), BY(dataNA, g, baselogdiff, 2, use.g.names = FALSE))
# Adding time-variable: Computing fully identified panel-growtherences !!
expect_equal(fgrowth(x, 1, 1, f, t, logdiff = TRUE), BY(x, f, baselogdiff, use.g.names = FALSE))
expect_equal(fgrowth(x, 2, 1, f, t, logdiff = TRUE), BY(x, f, baselogdiff, 2, use.g.names = FALSE))
expect_equal(fgrowth(xNA, 1, 1, f, t, logdiff = TRUE), BY(xNA, f, baselogdiff, use.g.names = FALSE))
expect_equal(fgrowth(xNA, 2, 1, f, t, logdiff = TRUE), BY(xNA, f, baselogdiff, 2, use.g.names = FALSE))
expect_equal(fgrowth(m, 1, 1, g, td, stubs = FALSE, logdiff = TRUE), BY(m, g, baselogdiff, use.g.names = FALSE))
expect_equal(fgrowth(m, 2, 1, g, td, stubs = FALSE, logdiff = TRUE), BY(m, g, baselogdiff, 2, use.g.names = FALSE))
expect_equal(fgrowth(mNA, 1, 1, g, td, stubs = FALSE, logdiff = TRUE), BY(mNA, g, baselogdiff, use.g.names = FALSE))
expect_equal(fgrowth(mNA, 2, 1, g, td, stubs = FALSE, logdiff = TRUE), BY(mNA, g, baselogdiff, 2, use.g.names = FALSE))
expect_equal(fgrowth(data, 1, 1, g, td, stubs = FALSE, logdiff = TRUE), BY(data, g, baselogdiff, use.g.names = FALSE))
expect_equal(fgrowth(data, 2, 1, g, td, stubs = FALSE, logdiff = TRUE), BY(data, g, baselogdiff, 2, use.g.names = FALSE))
expect_equal(fgrowth(dataNA, 1, 1, g, td, stubs = FALSE, logdiff = TRUE), BY(dataNA, g, baselogdiff, use.g.names = FALSE))
expect_equal(fgrowth(dataNA, 2, 1, g, td, stubs = FALSE, logdiff = TRUE), BY(dataNA, g, baselogdiff, 2, use.g.names = FALSE))
})
test_that("fgrowth with logdiff performs lagged/leaded and iterated (panel-) vector growth reates without errors", {
expect_visible(fgrowth(1:10, -2:2, logdiff = TRUE))
expect_visible(fgrowth(1:10, 1:2, logdiff = TRUE))
expect_visible(fgrowth(1:10, -1:-2, logdiff = TRUE))
expect_visible(fgrowth(1:10, 0, logdiff = TRUE))
expect_visible(fgrowth(1:10, -2:2, 2, logdiff = TRUE))
expect_visible(fgrowth(1:10, 1:2, 2, logdiff = TRUE))
expect_visible(fgrowth(1:10, -1:-2, 2, logdiff = TRUE))
expect_visible(fgrowth(1:10, 0, 2, logdiff = TRUE))
expect_visible(fgrowth(1:10, -2:2, 1:2, logdiff = TRUE))
expect_visible(fgrowth(1:10, 1:2, 1:2, logdiff = TRUE))
expect_visible(fgrowth(1:10, -1:-2, 1:2, logdiff = TRUE))
expect_visible(fgrowth(1:10, 0, 1:2, logdiff = TRUE))
expect_visible(fgrowth(xNA, -2:2, logdiff = TRUE))
expect_visible(fgrowth(xNA, 1:2, logdiff = TRUE))
expect_visible(fgrowth(xNA, -1:-2, logdiff = TRUE))
expect_visible(fgrowth(xNA, 0, logdiff = TRUE))
expect_visible(fgrowth(xNA, -2:2, 2, logdiff = TRUE))
expect_visible(fgrowth(xNA, 1:2, 2, logdiff = TRUE))
expect_visible(fgrowth(xNA, -1:-2, 2, logdiff = TRUE))
expect_visible(fgrowth(xNA, 0, 2, logdiff = TRUE))
expect_visible(fgrowth(xNA, -2:2, 1:2, logdiff = TRUE))
expect_visible(fgrowth(xNA, 1:2, 1:2, logdiff = TRUE))
expect_visible(fgrowth(xNA, -1:-2, 1:2, logdiff = TRUE))
expect_visible(fgrowth(xNA, 0, 1:2, logdiff = TRUE))
expect_visible(fgrowth(xNA, -2:2, 1, f, logdiff = TRUE))
expect_visible(fgrowth(xNA, 1:2, 1, f, logdiff = TRUE))
expect_visible(fgrowth(xNA, -1:-2, 1, f, logdiff = TRUE))
expect_visible(fgrowth(xNA, 0, 1, f, logdiff = TRUE))
expect_visible(fgrowth(xNA, -2:2, 2, f, logdiff = TRUE))
expect_visible(fgrowth(xNA, 1:2, 2, f, logdiff = TRUE))
expect_visible(fgrowth(xNA, -1:-2, 2, f, logdiff = TRUE))
expect_visible(fgrowth(xNA, 0, 2, f, logdiff = TRUE))
expect_visible(fgrowth(xNA, -2:2, 1:2, f, logdiff = TRUE))
expect_visible(fgrowth(xNA, 1:2, 1:2, f, logdiff = TRUE))
expect_visible(fgrowth(xNA, -1:-2, 1:2, f, logdiff = TRUE))
expect_visible(fgrowth(xNA, 0, 1:2, f, logdiff = TRUE))
expect_visible(fgrowth(xNA, -2:2, 1, f, t, logdiff = TRUE))
expect_visible(fgrowth(xNA, 1:2, 1, f, t, logdiff = TRUE))
expect_visible(fgrowth(xNA, -1:-2, 1, f, t, logdiff = TRUE))
expect_visible(fgrowth(xNA, 0, 1, f, t, logdiff = TRUE))
expect_visible(fgrowth(xNA, -2:2, 2, f, t, logdiff = TRUE))
expect_visible(fgrowth(xNA, 1:2, 2, f, t, logdiff = TRUE))
expect_visible(fgrowth(xNA, -1:-2, 2, f, t, logdiff = TRUE))
expect_visible(fgrowth(xNA, 0, 2, f, t, logdiff = TRUE))
expect_visible(fgrowth(xNA, -2:2, 1:2, f, t, logdiff = TRUE))
expect_visible(fgrowth(xNA, 1:2, 1:2, f, t, logdiff = TRUE))
expect_visible(fgrowth(xNA, -1:-2, 1:2, f, t, logdiff = TRUE))
expect_visible(fgrowth(xNA, 0, 1:2, f, t, logdiff = TRUE))
})
test_that("fgrowth with logdiff performs lagged/leaded and iterated (panel-) matrix growth rates without errors", {
expect_visible(fgrowth(m, -2:2, logdiff = TRUE))
expect_visible(fgrowth(m, 1:2, logdiff = TRUE))
expect_visible(fgrowth(m, -1:-2, logdiff = TRUE))
expect_visible(fgrowth(m, 0, logdiff = TRUE))
expect_visible(fgrowth(m, -2:2, 2, logdiff = TRUE))
expect_visible(fgrowth(m, 1:2, 2, logdiff = TRUE))
expect_visible(fgrowth(m, -1:-2, 2, logdiff = TRUE))
expect_visible(fgrowth(m, 0, 2, logdiff = TRUE))
expect_visible(fgrowth(m, -2:2, 1:2, logdiff = TRUE))
expect_visible(fgrowth(m, 1:2, 1:2, logdiff = TRUE))
expect_visible(fgrowth(m, -1:-2, 1:2, logdiff = TRUE))
expect_visible(fgrowth(m, 0, 1:2, logdiff = TRUE))
expect_visible(fgrowth(m, -2:2, 1, g, logdiff = TRUE))
expect_visible(fgrowth(m, 1:2, 1, g, logdiff = TRUE))
expect_visible(fgrowth(m, -1:-2, 1, g, logdiff = TRUE))
expect_visible(fgrowth(m, 0, 1, g, logdiff = TRUE))
expect_visible(fgrowth(m, -2:2, 2, g, logdiff = TRUE))
expect_visible(fgrowth(m, 1:2, 2, g, logdiff = TRUE))
expect_visible(fgrowth(m, -1:-2, 2, g, logdiff = TRUE))
expect_visible(fgrowth(m, 0, 2, g, logdiff = TRUE))
expect_visible(fgrowth(m, -2:2, 1:2, g, logdiff = TRUE))
expect_visible(fgrowth(m, 1:2, 1:2, g, logdiff = TRUE))
expect_visible(fgrowth(m, -1:-2, 1:2, g, logdiff = TRUE))
expect_visible(fgrowth(m, 0, 1:2, g, logdiff = TRUE))
expect_visible(fgrowth(m, -2:2, 1, g, td, logdiff = TRUE))
expect_visible(fgrowth(m, 1:2, 1, g, td, logdiff = TRUE))
expect_visible(fgrowth(m, -1:-2, 1, g, td, logdiff = TRUE))
expect_visible(fgrowth(m, 0, 1, g, td, logdiff = TRUE))
expect_visible(fgrowth(m, -2:2, 2, g, td, logdiff = TRUE))
expect_visible(fgrowth(m, 1:2, 2, g, td, logdiff = TRUE))
expect_visible(fgrowth(m, -1:-2, 2, g, td, logdiff = TRUE))
expect_visible(fgrowth(m, 0, 2, g, td, logdiff = TRUE))
expect_visible(fgrowth(m, -2:2, 1:2, g, td, logdiff = TRUE))
expect_visible(fgrowth(m, 1:2, 1:2, g, td, logdiff = TRUE))
expect_visible(fgrowth(m, -1:-2, 1:2, g, td, logdiff = TRUE))
expect_visible(fgrowth(m, 0, 1:2, g, td, logdiff = TRUE))
})
test_that("fgrowth with logdiff performs lagged/leaded and iterated (panel-) data.frame growth rates without errors", {
expect_visible(fgrowth(data, -2:2, logdiff = TRUE))
expect_visible(fgrowth(data, 1:2, logdiff = TRUE))
expect_visible(fgrowth(data, -1:-2, logdiff = TRUE))
expect_visible(fgrowth(data, 0, logdiff = TRUE))
expect_visible(fgrowth(data, -2:2, 2, logdiff = TRUE))
expect_visible(fgrowth(data, 1:2, 2, logdiff = TRUE))
expect_visible(fgrowth(data, -1:-2, 2, logdiff = TRUE))
expect_visible(fgrowth(data, 0, 2, logdiff = TRUE))
expect_visible(fgrowth(data, -2:2, 1:2, logdiff = TRUE))
expect_visible(fgrowth(data, 1:2, 1:2, logdiff = TRUE))
expect_visible(fgrowth(data, -1:-2, 1:2, logdiff = TRUE))
expect_visible(fgrowth(data, 0, 1:2, logdiff = TRUE))
expect_visible(fgrowth(data, -2:2, 1, g, logdiff = TRUE))
expect_visible(fgrowth(data, 1:2, 1, g, logdiff = TRUE))
expect_visible(fgrowth(data, -1:-2, 1, g, logdiff = TRUE))
expect_visible(fgrowth(data, 0, 1, g, logdiff = TRUE))
expect_visible(fgrowth(data, -2:2, 2, g, logdiff = TRUE))
expect_visible(fgrowth(data, 1:2, 2, g, logdiff = TRUE))
expect_visible(fgrowth(data, -1:-2, 2, g, logdiff = TRUE))
expect_visible(fgrowth(data, 0, 2, g, logdiff = TRUE))
expect_visible(fgrowth(data, -2:2, 1:2, g, logdiff = TRUE))
expect_visible(fgrowth(data, 1:2, 1:2, g, logdiff = TRUE))
expect_visible(fgrowth(data, -1:-2, 1:2, g, logdiff = TRUE))
expect_visible(fgrowth(data, 0, 1:2, g, logdiff = TRUE))
expect_visible(fgrowth(data, -2:2, 1, g, td, logdiff = TRUE))
expect_visible(fgrowth(data, 1:2, 1, g, td, logdiff = TRUE))
expect_visible(fgrowth(data, -1:-2, 1, g, td, logdiff = TRUE))
expect_visible(fgrowth(data, 0, 1, g, td, logdiff = TRUE))
expect_visible(fgrowth(data, -2:2, 2, g, td, logdiff = TRUE))
expect_visible(fgrowth(data, 1:2, 2, g, td, logdiff = TRUE))
expect_visible(fgrowth(data, -1:-2, 2, g, td, logdiff = TRUE))
expect_visible(fgrowth(data, 0, 2, g, td, logdiff = TRUE))
expect_visible(fgrowth(data, -2:2, 1:2, g, td, logdiff = TRUE))
expect_visible(fgrowth(data, 1:2, 1:2, g, td, logdiff = TRUE))
expect_visible(fgrowth(data, -1:-2, 1:2, g, td, logdiff = TRUE))
expect_visible(fgrowth(data, 0, 1:2, g, td, logdiff = TRUE))
})
test_that("fgrowth with logdiff correctly handles unordered time-series and panel-series computations", {
expect_equal(fgrowth(x, -2:2, 1:2, t = 1:100, logdiff = TRUE), fgrowth(x, -2:2, 1:2, logdiff = TRUE))
expect_equal(fgrowth(xNA, -2:2, 1:2, t = 1:100, logdiff = TRUE), fgrowth(xNA, -2:2, 1:2, logdiff = TRUE))
expect_equal(fgrowth(m, -2:2, 1:2, t = seq_along(td), logdiff = TRUE), fgrowth(m, -2:2, 1:2, logdiff = TRUE))
expect_equal(fgrowth(data, -2:2, 1:2, t = seq_along(td), logdiff = TRUE), fgrowth(data, -2:2, 1:2, logdiff = TRUE))
expect_equal(fgrowth(xuo, -2:2, 1:2, t = t2uo, logdiff = TRUE)[o,], unclass(fgrowth(x, -2:2, 1:2, logdiff = TRUE)))
expect_equal(fgrowth(xNAuo, -2:2, 1:2, t = t2uo, logdiff = TRUE)[o,], unclass(fgrowth(xNA, -2:2, 1:2, logdiff = TRUE)))
expect_equal(fgrowth(muo, -2:2, 1:2, t = t2duo, logdiff = TRUE)[od,], unclass(fgrowth(m, -2:2, 1:2, logdiff = TRUE)))
expect_equal(fgrowth(datauo, -2:2, 1:2, t = t2duo, logdiff = TRUE)[od,], fgrowth(data, -2:2, 1:2, logdiff = TRUE))
expect_equal(fgrowth(xuo, -2:2, 1:2, fuo, tuo, logdiff = TRUE)[o,], unclass(fgrowth(x, -2:2, 1:2, f, t, logdiff = TRUE)))
expect_equal(fgrowth(xNAuo, -2:2, 1:2, fuo, tuo, logdiff = TRUE)[o,], unclass(fgrowth(xNA, -2:2, 1:2, f, t, logdiff = TRUE)))
expect_equal(fgrowth(muo, -2:2, 1:2, guo, tduo, logdiff = TRUE)[od,], unclass(fgrowth(m, -2:2, 1:2, g, td, logdiff = TRUE)))
expect_equal(fgrowth(datauo, -2:2, 1:2, guo, tduo, logdiff = TRUE)[od,], fgrowth(data, -2:2, 1:2, g, td, logdiff = TRUE))
})
test_that("fgrowth with logdiff performs numerically stable in ordered computations", {
expect_true(all_obj_equal(replicate(50, fgrowth(x, logdiff = TRUE), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(xNA, logdiff = TRUE), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(m, logdiff = TRUE), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(mNA, logdiff = TRUE), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(data, logdiff = TRUE), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(dataNA, logdiff = TRUE), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(x, 1, 1, f, logdiff = TRUE), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(x, -2:2, 1:2, f, logdiff = TRUE), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(xNA, 1, 1, f, logdiff = TRUE), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(xNA, -2:2, 1:2, f, logdiff = TRUE), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(m, 1, 1, g, logdiff = TRUE), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(m, -2:2, 1:2, g, logdiff = TRUE), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(mNA, 1, 1, g, logdiff = TRUE), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(mNA, -2:2, 1:2, g, logdiff = TRUE), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(data, 1, 1, g, logdiff = TRUE), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(data, -2:2, 1:2, g, logdiff = TRUE), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(dataNA, 1, 1, g, logdiff = TRUE), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(dataNA, -2:2, 1:2, g, logdiff = TRUE), simplify = FALSE)))
})
test_that("fgrowth with logdiff performs numerically stable in unordered computations", {
expect_true(all_obj_equal(replicate(50, fgrowth(xuo, t = t2uo, logdiff = TRUE), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(xNAuo, t = t2uo, logdiff = TRUE), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(muo, t = t2duo, logdiff = TRUE), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(datauo, t = t2duo, logdiff = TRUE), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(xuo, 1, 1, fuo, tuo, logdiff = TRUE), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(xuo, -2:2, 1:2, fuo, tuo, logdiff = TRUE), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(muo, 1, 1, guo, tduo, logdiff = TRUE), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(muo, -2:2, 1:2, guo, tduo, logdiff = TRUE), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(datauo, 1, 1, guo, tduo, logdiff = TRUE), simplify = FALSE)))
expect_true(all_obj_equal(replicate(50, fgrowth(datauo, -2:2, 1:2, guo, tduo, logdiff = TRUE), simplify = FALSE)))
})
options(warn = -1)
test_that("fgrowth with logdiff handles special values in the right way", {
expect_equal(fgrowth(c(1,NA), logdiff = TRUE), c(NA_real_,NaN))
expect_equal(fgrowth(c(NA,1), logdiff = TRUE), c(NA_real_,NaN))
expect_equal(fgrowth(c(NaN,1), logdiff = TRUE), c(NA_real_,NaN))
expect_equal(fgrowth(c(1,NaN), logdiff = TRUE), c(NA_real_,NaN))
expect_equal(fgrowth(c(Inf,1), logdiff = TRUE), c(NA,-Inf)) # ??
expect_equal(fgrowth(c(1,Inf), logdiff = TRUE), c(NA,Inf))
expect_equal(fgrowth(c(Inf,NA), logdiff = TRUE), c(NA_real_,NaN))
expect_equal(fgrowth(c(NA,Inf), logdiff = TRUE), c(NA_real_,NaN))
expect_equal(fgrowth(c(Inf,-Inf), logdiff = TRUE), c(NA,NaN))
expect_equal(fgrowth(c(-Inf,Inf), logdiff = TRUE), c(NA,NaN))
expect_equal(fgrowth(c(Inf,Inf), logdiff = TRUE), c(NA,NaN))
expect_equal(fgrowth(c(TRUE,TRUE), logdiff = TRUE), c(NA_real_,0))
expect_equal(fgrowth(c(TRUE,FALSE), logdiff = TRUE), c(NA_real_,-Inf)) # ??
expect_equal(fgrowth(c(FALSE,TRUE), logdiff = TRUE), c(NA_real_,Inf))
})
test_that("fgrowth with logdiff produces errors for wrong input", {
# wrong type: normally guaranteed by C++
expect_error(fgrowth("a", logdiff = TRUE))
expect_error(fgrowth(NA_character_, logdiff = TRUE))
expect_error(fgrowth(mNAc, logdiff = TRUE))
expect_error(fgrowth(wlddev, logdiff = TRUE))
expect_error(fgrowth(mNAc, f, logdiff = TRUE))
expect_error(fgrowth(x, "1", "2", logdiff = TRUE))
# if n*growth equals or exceeds length(x), should give error
expect_error(fgrowth(x,100, logdiff = TRUE))
expect_error(fgrowth(x,1,100, logdiff = TRUE))
expect_error(fgrowth(x,50,2, logdiff = TRUE))
expect_error(fgrowth(x,20,5, logdiff = TRUE))
# if n*growth exceeds average group size, should give error
# expect_warning(fgrowth(x,11,1,f, logdiff = TRUE)) -> some fail on i386
# expect_warning(fgrowth(x,1,11,f, logdiff = TRUE))
# expect_warning(fgrowth(x,1,11,f,t, logdiff = TRUE))
# expect_warning(fgrowth(x,11,1,f,t, logdiff = TRUE))
# passing repeated n-values or non-positive or non-consecutive growth values should give error
expect_error(fgrowth(x,c(1,1), logdiff = TRUE))
expect_error(fgrowth(x,c(-1,-1), logdiff = TRUE))
expect_error(fgrowth(x,1,c(1,1), logdiff = TRUE))
expect_error(fgrowth(x,1,c(-1,-1), logdiff = TRUE))
expect_error(fgrowth(x,1,2:1, logdiff = TRUE))
expect_error(fgrowth(x,1,0, logdiff = TRUE))
expect_error(fgrowth(x,1,-1, logdiff = TRUE))
expect_error(fgrowth(x,f, logdiff = TRUE)) # common source of error probably is passing the factor in a wrong slot
expect_error(fgrowth(x,1,f, logdiff = TRUE))
expect_error(fgrowth(x,c(1,1),1,f, logdiff = TRUE))
expect_error(fgrowth(x,c(1,1),1,f,t, logdiff = TRUE))
expect_error(fgrowth(x,1,c(1,1),f, logdiff = TRUE))
expect_error(fgrowth(x,1,c(1,1),f,t, logdiff = TRUE))
expect_error(fgrowth(x,1,2:1,f, logdiff = TRUE))
expect_error(fgrowth(x,1,2:1,f,t, logdiff = TRUE))
expect_error(fgrowth(x,1,0,f, logdiff = TRUE))
expect_error(fgrowth(x,1,0,f,t, logdiff = TRUE))
expect_error(fgrowth(x,1,-1,f, logdiff = TRUE))
expect_error(fgrowth(x,1,-1,f,t, logdiff = TRUE))
# repeated values or gaps in time-variable should give error
expect_error(fgrowth(1:3, t = c(1,1,2), logdiff = TRUE))
expect_error(fgrowth(1:3, t = c(1,2,2), logdiff = TRUE))
expect_error(fgrowth(1:3, t = c(1,2,1), logdiff = TRUE))
expect_error(fgrowth(1:10, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1,1,2,1:3,1:4), logdiff = TRUE)) # This is the only possible statement which does not throw a reteated timevar error because the first C++ index is 0, and omap is also initialized with 0's.
expect_error(fgrowth(1:10, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1,1,1,1:3,1:4), logdiff = TRUE))
expect_error(fgrowth(1:10, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1:3,1:3,1,1,3,4), logdiff = TRUE))
expect_error(fgrowth(1:10, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1,2,2,1:3,1:4), logdiff = TRUE))
expect_visible(fgrowth(1:10, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1,2,4,1:3,1:4), logdiff = TRUE))
expect_error(fgrowth(1:10, diff = 2, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1,2,4,1:3,1:4), logdiff = TRUE))
expect_error(fgrowth(1:10, g = c(1,2,1,2,2,2,3,3,3,3), t = c(1:3,1:3,1:4), logdiff = TRUE))
expect_visible(fgrowth(1:10, g = c(1,1,1,2,2,2,3,3,4,3), t = c(1:3,1:3,1:4), logdiff = TRUE))
expect_error(fgrowth(1:10, diff = 2, g = c(1,1,1,2,2,2,3,3,4,3), t = c(1:3,1:3,1:4), logdiff = TRUE))
# The usual stuff: Wrongly sized grouping vectors or time-variables
expect_error(fgrowth(1:3, t = 1:2, logdiff = TRUE))
expect_error(fgrowth(1:3, t = 1:4, logdiff = TRUE))
expect_error(fgrowth(1:3, g = 1:2, logdiff = TRUE))
expect_error(fgrowth(1:3, g = 1:4, logdiff = TRUE))
expect_error(fgrowth(1:4, g = c(1,1,2,2), t = c(1,2,1), logdiff = TRUE))
expect_error(fgrowth(1:4, g = c(1,2,2), t = c(1,2,1,2), logdiff = TRUE))
})
# G with logdiff
test_that("G with logdiff produces errors for wrong input", {
# wrong type: normally guaranteed by C++
expect_error(G("a", logdiff = TRUE))
expect_error(G(NA_character_, logdiff = TRUE))
expect_error(G(mNAc, logdiff = TRUE))
expect_visible(G(wlddev, logdiff = TRUE))
expect_error(G(mNAc, f, logdiff = TRUE))
expect_error(G(x, "1", "2", logdiff = TRUE))
# if n*diff equals or exceeds length(x), should give error
expect_error(G(x,100, logdiff = TRUE))
expect_error(G(x,1,100, logdiff = TRUE))
expect_error(G(x,50,2, logdiff = TRUE))
expect_error(G(x,20,5, logdiff = TRUE))
# if n*diff exceeds average group size, should give error
# expect_warning(G(x,11,1,f, logdiff = TRUE)) -> Some fail on i386
# expect_warning(G(x,1,11,f, logdiff = TRUE))
# expect_warning(G(x,1,11,f,t, logdiff = TRUE))
# expect_warning(G(x,11,1,f,t, logdiff = TRUE))
# passing repeated n-values or non-positive or non-consecutive diff values should give error
expect_error(G(x,c(1,1), logdiff = TRUE))
expect_error(G(x,c(-1,-1), logdiff = TRUE))
expect_error(G(x,1,c(1,1), logdiff = TRUE))
expect_error(G(x,1,c(-1,-1), logdiff = TRUE))
expect_error(G(x,1,2:1, logdiff = TRUE))
expect_error(G(x,1,0, logdiff = TRUE))
expect_error(G(x,1,-1, logdiff = TRUE))
expect_error(G(x,f, logdiff = TRUE)) # common source of error probably is passing the factor in a wrong slot
expect_error(G(x,1,f, logdiff = TRUE))
expect_error(G(x,c(1,1),1,f, logdiff = TRUE))
expect_error(G(x,c(1,1),1,f,t, logdiff = TRUE))
expect_error(G(x,1,c(1,1),f, logdiff = TRUE))
expect_error(G(x,1,c(1,1),f,t, logdiff = TRUE))
expect_error(G(x,1,2:1,f, logdiff = TRUE))
expect_error(G(x,1,2:1,f,t, logdiff = TRUE))
expect_error(G(x,1,0,f, logdiff = TRUE))
expect_error(G(x,1,0,f,t, logdiff = TRUE))
expect_error(G(x,1,-1,f, logdiff = TRUE))
expect_error(G(x,1,-1,f,t, logdiff = TRUE))
# repeated values or gaps in time-variable should give error
expect_error(G(1:3, t = c(1,1,2), logdiff = TRUE))
expect_error(G(1:3, t = c(1,2,2), logdiff = TRUE))
expect_error(G(1:3, t = c(1,2,1), logdiff = TRUE))
expect_error(G(1:10, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1,1,2,1:3,1:4), logdiff = TRUE)) # This is the only possible statement which does not throw a reteated timevar error because the first C++ index is 0, and omap is also initialized with 0's.
expect_error(G(1:10, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1,1,1,1:3,1:4), logdiff = TRUE))
expect_error(G(1:10, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1:3,1:3,1,1,3,4), logdiff = TRUE))
expect_error(G(1:10, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1,2,2,1:3,1:4), logdiff = TRUE))
expect_visible(G(1:10, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1,2,4,1:3,1:4), logdiff = TRUE))
expect_error(G(1:10, diff = 2, g = c(1,1,1,2,2,2,3,3,3,3), t = c(1,2,4,1:3,1:4), logdiff = TRUE))
expect_error(G(1:10, g = c(1,2,1,2,2,2,3,3,3,3), t = c(1:3,1:3,1:4), logdiff = TRUE))
expect_visible(G(1:10, g = c(1,1,1,2,2,2,3,3,4,3), t = c(1:3,1:3,1:4), logdiff = TRUE))
expect_error(G(1:10, diff = 2, g = c(1,1,1,2,2,2,3,3,4,3), t = c(1:3,1:3,1:4), logdiff = TRUE))
# The usual stuff: Wrongly sized grouping vectors or time-variables
expect_error(G(1:3, t = 1:2, logdiff = TRUE))
expect_error(G(1:3, t = 1:4, logdiff = TRUE))
expect_error(G(1:3, g = 1:2, logdiff = TRUE))
expect_error(G(1:3, g = 1:4, logdiff = TRUE))
expect_error(G(1:4, g = c(1,1,2,2), t = c(1,2,1), logdiff = TRUE))
expect_error(G(1:4, g = c(1,2,2), t = c(1,2,1,2), logdiff = TRUE))
})
test_that("G.data.frame method with logdiff is foolproof", {
expect_visible(G(wlddev, logdiff = TRUE))
expect_visible(G(wlddev, by = wlddev$iso3c, logdiff = TRUE))
expect_error(G(wlddev, t = ~year, logdiff = TRUE))
expect_visible(G(wlddev, 1, 1, wlddev$iso3c, logdiff = TRUE))
expect_visible(G(wlddev, 1,1, ~iso3c, logdiff = TRUE))
expect_error(G(wlddev, 1, ~iso3c, logdiff = TRUE))
expect_visible(G(wlddev, 1, 1, ~iso3c + region, logdiff = TRUE))
expect_visible(G(wlddev, 1,1, wlddev$iso3c, wlddev$year, logdiff = TRUE))
expect_visible(G(wlddev, 1,1, ~iso3c, ~year, logdiff = TRUE))
expect_visible(G(wlddev, cols = 9:12, logdiff = TRUE))
expect_visible(G(wlddev, 1,1,~iso3c, cols = 9:12, logdiff = TRUE))
expect_visible(G(wlddev, 1,1,wlddev$iso3c, wlddev$year, cols = 9:12, logdiff = TRUE))
expect_visible(G(wlddev, 1,1,~iso3c, ~year, cols = 9:12, logdiff = TRUE))
expect_visible(G(wlddev, cols = c("PCGDP","LIFEEX"), logdiff = TRUE))
expect_visible(G(wlddev, 1,1,wlddev$iso3c, cols = c("PCGDP","LIFEEX"), logdiff = TRUE))
expect_visible(G(wlddev, 1,1,~iso3c, cols = c("PCGDP","LIFEEX"), logdiff = TRUE))
expect_visible(G(wlddev, 1,1,wlddev$iso3c, wlddev$year, cols = c("PCGDP","LIFEEX"), logdiff = TRUE))
expect_visible(G(wlddev, 1,1,~iso3c, ~year, cols = c("PCGDP","LIFEEX"), logdiff = TRUE))
expect_error(G(wlddev, cols = NULL, logdiff = TRUE))
expect_error(G(wlddev, 1,1,wlddev$iso3c, cols = NULL, logdiff = TRUE))
expect_error(G(wlddev, 1,1,~iso3c, cols = NULL, logdiff = TRUE))
expect_error(G(wlddev, 1,1,wlddev$iso3c, wlddev$year, cols = NULL, logdiff = TRUE))
expect_error(G(wlddev, 1,1,~iso3c, ~year, cols = NULL, logdiff = TRUE))
expect_error(G(wlddev, cols = 9:14, logdiff = TRUE))
expect_error(G(wlddev, 1,1,~iso3c, ~year, cols = 9:14, logdiff = TRUE))
expect_error(G(wlddev, cols = c("PCGDP","LIFEEX","bla"), logdiff = TRUE))
expect_error(G(wlddev, 1,1,~iso3c, ~year, cols = c("PCGDP","LIFEEX","bla"), logdiff = TRUE))
expect_warning(G(wlddev, w = 4, logdiff = TRUE))
expect_error(G(wlddev, t = "year", logdiff = TRUE))
expect_warning(G(wlddev, g = ~year2, logdiff = TRUE))
expect_error(G(wlddev, t = ~year + region, logdiff = TRUE))
expect_error(G(wlddev, data, logdiff = TRUE))
expect_error(G(wlddev, 1,1,"iso3c", logdiff = TRUE))
expect_error(G(wlddev, 1,1,~iso3c2, logdiff = TRUE))
expect_error(G(wlddev, 1,1,~iso3c + bla, logdiff = TRUE))
expect_error(G(wlddev, 1,1,t = rnorm(30), logdiff = TRUE))
expect_warning(G(wlddev, 1,1,g = rnorm(30), logdiff = TRUE))
expect_error(G(wlddev, 1,1,mtcars$mpg, 1:29, logdiff = TRUE))
expect_error(G(wlddev, 1,1,mtcars$mpg, mtcars$cyl, logdiff = TRUE)) # this gives a repeated values error first because length(g) == length(t)
expect_error(G(wlddev,1,1, ~iso3c2, ~year2, logdiff = TRUE))
expect_error(G(wlddev, cols = ~bla, logdiff = TRUE))
expect_visible(G(wlddev, 1,1,wlddev$iso3c, ~year, cols = 9:12, logdiff = TRUE))
expect_visible(G(wlddev, 1,1,~iso3c, wlddev$year, cols = 9:12, logdiff = TRUE))
expect_error(G(wlddev, 1,1,wlddev$iso3c, ~year + bla, cols = 9:12, logdiff = TRUE))
expect_error(G(wlddev, 2,1,~iso3c3, ~year, cols = 9:12, logdiff = TRUE))
expect_error(G(wlddev, cols = c("PC3GDP","LIFEEX"), logdiff = TRUE))
})
options(warn = 1)
Add the following code to your website.
For more information on customizing the embed code, read Embedding Snippets.