Skip to content

Commit 3eccae9

Browse files
committed
More consistent style using lintr
1 parent 1eeb6bb commit 3eccae9

File tree

7 files changed

+152
-132
lines changed

7 files changed

+152
-132
lines changed

R/Delaporte.R

+28-27
Original file line numberDiff line numberDiff line change
@@ -15,14 +15,14 @@ pdelap <- function(q, alpha, beta, lambda, lower.tail = TRUE, log.p = FALSE) {
1515
# These interrupts throw errors even using expect_error. Excluding for now
1616
# nocov start
1717
if (any(q[is.finite(q)] >= 2^63)) {
18-
stop('Function cannot handle values >= 2^63')
18+
stop("Function cannot handle values >= 2^63")
1919
}
2020
if (any(q[is.finite(q)] >= 2^15)) {
2121
cat("There are values >= 32768.",
2222
"This may take minutes if not hours to compute. Are you sure?\n")
23-
resp <- readline('Press "y" to continue.\n')
24-
if (tolower(resp) != 'y') {
25-
cat('Stopping\n')
23+
resp <- readline("Press 'y' to continue.\n")
24+
if (tolower(resp) != "y") {
25+
cat("Stopping\n")
2626
return(invisible(NULL))
2727
}
2828
}
@@ -33,7 +33,8 @@ pdelap <- function(q, alpha, beta, lambda, lower.tail = TRUE, log.p = FALSE) {
3333
as.double(lambda), lt_f, lp_f)
3434
}
3535

36-
qdelap <- function(p, alpha, beta, lambda, lower.tail = TRUE, log.p = FALSE, exact = TRUE) {
36+
qdelap <- function(p, alpha, beta, lambda, lower.tail = TRUE, log.p = FALSE,
37+
exact = TRUE) {
3738
p <- as.double(p)
3839
alpha <- as.double(alpha)
3940
beta <- as.double(beta)
@@ -45,9 +46,9 @@ qdelap <- function(p, alpha, beta, lambda, lower.tail = TRUE, log.p = FALSE, exa
4546
} else {
4647
if (length(alpha) > 1 || length(beta) > 1 || length(lambda) > 1 ||
4748
any(is.nan(p)) || anyNA(p)) {
48-
stop(paste('Quantile approximation relies on pooling and is not accurate',
49-
'when passed vector-valued parameters, NaNs, or NAs.',
50-
'Please use exact version.'))
49+
stop("Quantile approximation relies on pooling and is not accurate when",
50+
"passed vector-valued parameters, NaNs, or NAs. Please use exact",
51+
"version.")
5152
}
5253
if (any(alpha <= 0) || any(beta <= 0) || any(lambda <= 0)) {
5354
QDLAP <- rep.int(NaN, length(p))
@@ -59,22 +60,22 @@ qdelap <- function(p, alpha, beta, lambda, lower.tail = TRUE, log.p = FALSE, exa
5960
p0 <- p[p == 0]
6061
pInf <- p[p >= 1]
6162
n <- min(10 ^ (ceiling(log(alpha * beta + lambda, 10)) + 5), 1e7)
62-
ShiftedGammas <- rgamma(n, shape = alpha, scale = beta)
63-
DP <- rpois(n, lambda = (ShiftedGammas + lambda))
64-
QValid <- as.vector(quantile(DP, pValid, na.rm = TRUE, type = 8))
65-
QNeg <- rep.int(NaN, times = length(pNeg))
66-
Q0 <- rep.int(0, times = length(p0))
67-
QInf <- rep.int(Inf, times = length(pInf))
68-
QDLAP <- as.vector(c(QNeg, Q0, QValid, QInf), mode = 'double')
63+
shiftedGammas <- rgamma(n, shape = alpha, scale = beta)
64+
DP <- rpois(n, lambda = (shiftedGammas + lambda))
65+
qValid <- as.vector(quantile(DP, pValid, na.rm = TRUE, type = 8))
66+
qNeg <- rep.int(NaN, times = length(pNeg))
67+
q0 <- rep.int(0, times = length(p0))
68+
qInf <- rep.int(Inf, times = length(pInf))
69+
QDLAP <- as.vector(c(qNeg, q0, qValid, qInf), mode = "double")
6970
}
7071
}
71-
if (any(is.nan(QDLAP))) warning('NaNs produced')
72+
if (any(is.nan(QDLAP))) warning("NaNs produced")
7273
return(QDLAP)
7374
}
7475

7576
rdelap <- function(n, alpha, beta, lambda, exact = TRUE) {
7677
if (n < 0) {
77-
stop('invalid arguments')
78+
stop("invalid arguments")
7879
}
7980
n <- as.integer(n)
8081
alpha <- as.double(alpha)
@@ -84,25 +85,25 @@ rdelap <- function(n, alpha, beta, lambda, exact = TRUE) {
8485
if (any(alpha <= 0) || any(beta <= 0) || any(lambda <= 0)) {
8586
RDLAP <- (rep.int(NaN, n))
8687
} else {
87-
ShiftedGammas <- rgamma(n, shape = alpha, scale = beta)
88-
RDLAP <- rpois(n, lambda = (ShiftedGammas + lambda))
88+
shiftedGammas <- rgamma(n, shape = alpha, scale = beta)
89+
RDLAP <- rpois(n, lambda = (shiftedGammas + lambda))
8990
}
9091
} else {
9192
RDLAP <- .Call(rdelap_C, n, alpha, beta, lambda)
9293
}
93-
if (any(is.nan(RDLAP))) warning('NaNs produced')
94+
if (any(is.nan(RDLAP))) warning("NaNs produced")
9495
return(RDLAP)
9596
}
9697

97-
MoMdelap <- function(x, type = 2L) {
98+
MoMdelap <- function(x, type = 2L) { #nolint
9899
type <- as.integer(type)
99-
if (!(type %in% c(1L, 2L, 3L))) stop('Skew type must be one of 1, 2, or 3.')
100-
MoMDLAP <- .Call(MoMdelap_C, as.double(x), type)
101-
if (any(MoMDLAP <= 0)) {
102-
stop(paste("Method of moments not appropriate for this data;",
103-
"results include non-positive parameters."))
100+
if (!(type %in% c(1L, 2L, 3L))) stop("Skew type must be one of 1, 2, or 3.")
101+
moMDLAP <- .Call(MoMdelap_C, as.double(x), type)
102+
if (any(moMDLAP <= 0)) {
103+
stop("Method of moments not appropriate for this data; results include ",
104+
"non-positive parameters.")
104105
}
105-
return(MoMDLAP)
106+
return(moMDLAP)
106107
}
107108

108109
.onUnload <- function(libpath) {

inst/tinytest/test-citation.r

+2-2
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,3 @@
11
# Test Citation
2-
expect_true(any(grepl(packageVersion('Delaporte'),
3-
toBibtex(citation('Delaporte')), fixed = TRUE)))
2+
expect_true(any(grepl(packageVersion("Delaporte"),
3+
toBibtex(citation("Delaporte")), fixed = TRUE)))

inst/tinytest/test-ddelap.r

+24-21
Original file line numberDiff line numberDiff line change
@@ -1,46 +1,49 @@
1-
nonIntErr <- 'Non-integers passed to ddelap. These will have 0 probability.'
2-
nanWarn <- 'NaNs produced'
3-
VAL <- data.frame(read.csv(file = "./RawTest.csv", header = TRUE))
1+
tol <- sqrt(.Machine$double.eps)
2+
nonIntErr <- "Non-integers passed to ddelap. These will have 0 probability."
3+
nanWarn <- "NaNs produced"
4+
VAL <- data.frame(read.csv(file = file.path(".", "RawTest.csv"), header = TRUE))
45

56
# Singleton function accuracy"
6-
expect_equal(ddelap(0:36, 1, 4, 2), VAL$DDELAP_1)
7+
expect_equal(ddelap(0:36, 1, 4, 2), VAL$DDELAP_1, tolerance = tol)
78

89
# alpha < 0.8"
9-
expect_equal(ddelap(4, 0.5, 4, 0.2), 0.0547024400602606)
10+
expect_equal(ddelap(4L, 0.5, 4, 0.2), 0.0547024400602606, tolerance = tol)
1011

1112
# Singleton log"
12-
expect_equal(ddelap(0:36, 5, 3, 8, log = TRUE), log(ddelap(0:36, 5, 3, 8)))
13+
expect_equal(ddelap(0:36, 5, 3, 8, log = TRUE), log(ddelap(0:36, 5, 3, 8)),
14+
tolerance = tol)
1315

1416
# Singleton NA"
15-
expect_warning(ddelap(1, NA, 2, 3), nanWarn)
17+
expect_warning(ddelap(1L, NA, 2, 3), nanWarn)
1618
expect_identical(suppressWarnings(ddelap(1:3, 4, NA, 3)), rep(NaN, 3))
1719

1820
# Singleton NaN"
19-
expect_warning(ddelap(1, 0, 1, 2), nanWarn)
21+
expect_warning(ddelap(1L, 0, 1, 2), nanWarn)
2022
expect_warning(ddelap(1:10, 0, 1, 2), nanWarn)
21-
expect_warning(ddelap(1, -2, 1, 2), nanWarn)
22-
expect_warning(ddelap(0, 1, 0, 2), nanWarn)
23-
expect_warning(ddelap(0, 1, -4, 2), nanWarn)
24-
expect_warning(ddelap(0, 1, 4, 0), nanWarn)
25-
expect_warning(ddelap(0, 1, 4, -3), nanWarn)
26-
expect_warning(ddelap(0, 1, 4, -3), nanWarn)
23+
expect_warning(ddelap(1L, -2, 1, 2), nanWarn)
24+
expect_warning(ddelap(0L, 1, 0, 2), nanWarn)
25+
expect_warning(ddelap(0L, 1, -4, 2), nanWarn)
26+
expect_warning(ddelap(0L, 1, 4, 0), nanWarn)
27+
expect_warning(ddelap(0L, 1, 4, -3), nanWarn)
28+
expect_warning(ddelap(0L, 1, 4, -3), nanWarn)
2729
expect_warning(ddelap(NaN, 1, 4, 6), nanWarn)
2830
expect_warning(ddelap(NA, 1, 4, 12), nanWarn)
2931
tst <- suppressWarnings(ddelap(c(NA, 4, NaN), 0.5, 4, 0.2))
30-
expect_equal(tst, c(NaN, ddelap(4, 0.5, 4, 0.2), NaN))
32+
expect_equal(tst, c(NaN, ddelap(4L, 0.5, 4, 0.2), NaN), tolerance = tol)
3133

3234
# Vector function accuracy"
3335
expect_equal(ddelap(0:36, c(1, 2, 3), c(4, 1, 2), c(2, 5, 7)),
34-
VAL$DDELAP_Triple)
36+
VAL$DDELAP_Triple, tolerance = tol)
3537
# Vector log
3638
expect_equal(ddelap(0:100, c(4, 9, 2), c(6, 12, 8), c(7, 14, 9), log = TRUE),
37-
log(ddelap(0:100, c(4, 9, 2), c(6, 12, 8), c(7, 14, 9))))
39+
log(ddelap(0:100, c(4, 9, 2), c(6, 12, 8), c(7, 14, 9))),
40+
tolerance = tol)
3841

3942
# Vector NA
4043
expect_identical(suppressWarnings(ddelap(1:3, c(4, 1, 2), c(1, 5, 3), NA)),
4144
rep(NaN, 3))
4245
tst <- suppressWarnings(ddelap(c(4, 4, 4), c(1, 0.5, NA), 4, c(NaN, 0.2, 4)))
43-
expect_equal(tst, c(NaN, ddelap(4, 0.5, 4, 0.2), NaN))
46+
expect_equal(tst, c(NaN, ddelap(4, 0.5, 4, 0.2), NaN), tolerance = tol)
4447

4548
# Vector NaN
4649
expect_warning(ddelap(1:3, c(0, 1, 2), c(1, 0, 2), c(1, 2, 0)), nanWarn)
@@ -49,15 +52,15 @@ expect_warning(ddelap(c(NA, 2), c(2, 1, 2), c(1, 3, 2), c(1, 2, 4)))
4952
expect_warning(ddelap(c(3, NaN), c(2, 1, 2), c(1, 3, 2), c(1, 2, 4)))
5053
tst <- suppressWarnings(ddelap(c(NA, 0, NaN), c(1, 2, 3), c(4, 1, 2),
5154
c(2, 5, 7)))
52-
expect_equal(tst, c(NaN, ddelap(0, 2, 1, 5), NaN))
55+
expect_equal(tst, c(NaN, ddelap(0, 2, 1, 5), NaN), tolerance = tol)
5356

5457
# Non-integer warning
5558
expect_warning(ddelap(1.1, 1, 2, 3), nonIntErr)
5659
expect_warning(ddelap(c(1, 1.1, 1.2, 3), c(1, 1), 2, 3), nonIntErr)
57-
expect_warning(ddelap(seq(2, 3, .1), c(1, 1), 2, 3), nonIntErr)
60+
expect_warning(ddelap(seq(2, 3, 0.1), c(1, 1), 2, 3), nonIntErr)
5861

5962
# Non-double parameters converted
60-
expect_equal(ddelap(2L, 1L, 2L, 3L), ddelap(2L, 1, 2, 3))
63+
expect_equal(ddelap(2L, 1L, 2L, 3L), ddelap(2L, 1, 2, 3), tolerance = tol)
6164

6265
# Infinite values
6366
expect_identical(ddelap(Inf, 1L, 2L, 3L), 0)

inst/tinytest/test-momdelap.r

+34-32
Original file line numberDiff line numberDiff line change
@@ -1,53 +1,55 @@
1-
TestData <- c(5, 7, 9, 9, 10, 11, 11, 13, 17, 24)
2-
MTD <- mean(TestData)
3-
VTD <- var(TestData)
4-
VmMTD <- VTD - MTD
1+
tol <- 1e-12
2+
testData <- c(5, 7, 9, 9, 10, 11, 11, 13, 17, 24)
3+
inapp <- paste("Method of moments not appropriate for this data;",
4+
"results include non-positive parameters.")
5+
MTD <- mean(testData)
6+
VTD <- var(testData)
7+
vmMTD <- VTD - MTD
58
SK1 <- 1.1944183061921252 # Three values from skewness in e1071 package
69
SK2 <- 1.4164058724628172
710
SK3 <- 1.0198122281732285
811

912
# Function accuracy - type 1 explicit
10-
MoM <- MoMdelap(TestData, type = 1L)
11-
P2 <- 0.5 * (SK1 * (VTD ^ 1.5) - MTD - 3 * VmMTD) / VmMTD
12-
P1 <- VmMTD / (P2 ^ 2)
13+
mom <- MoMdelap(testData, type = 1L)
14+
P2 <- 0.5 * (SK1 * (VTD ^ 1.5) - MTD - 3 * vmMTD) / vmMTD
15+
P1 <- vmMTD / (P2 ^ 2)
1316
P3 <- MTD - P1 * P2
14-
expect_equal(MoM[[1]], P1)
15-
expect_equal(MoM[[2]], P2)
16-
expect_equal(MoM[[3]], P3)
17+
expect_equal(mom[[1]], P1, tolerance = tol)
18+
expect_equal(mom[[2]], P2, tolerance = tol)
19+
expect_equal(mom[[3]], P3, tolerance = tol)
1720

1821
# Function accuracy - type 2 implicit
19-
MoM <- MoMdelap(TestData)
20-
P2 <- 0.5 * (SK2 * (VTD ^ 1.5) - MTD - 3 * VmMTD) / VmMTD
21-
P1 <- VmMTD / (P2 ^ 2)
22+
mom <- MoMdelap(testData)
23+
P2 <- 0.5 * (SK2 * (VTD ^ 1.5) - MTD - 3 * vmMTD) / vmMTD
24+
P1 <- vmMTD / (P2 ^ 2)
2225
P3 <- MTD - P1 * P2
23-
expect_equal(MoM[[1]], P1)
24-
expect_equal(MoM[[2]], P2)
25-
expect_equal(MoM[[3]], P3)
26+
expect_equal(mom[[1]], P1, tolerance = tol)
27+
expect_equal(mom[[2]], P2, tolerance = tol)
28+
expect_equal(mom[[3]], P3, tolerance = tol)
2629

2730
# Function accuracy - type 2 explicit
28-
MoM <- MoMdelap(TestData, type = 2)
29-
expect_equal(MoM[[1]], 0.88342721893491116)
30-
expect_equal(MoM[[2]], 4.51388888888888928)
31-
expect_equal(MoM[[3]], 7.61230769230769155)
31+
mom <- MoMdelap(testData, type = 2)
32+
expect_equal(mom[[1]], 0.88342721893491116, tolerance = tol)
33+
expect_equal(mom[[2]], 4.51388888888888928, tolerance = tol)
34+
expect_equal(mom[[3]], 7.61230769230769155, tolerance = tol)
3235

3336
# Function accuracy - type 3 explicit
34-
MoM <- MoMdelap(TestData, type = 3)
35-
P2 <- 0.5 * (SK3 * (VTD ^ 1.5) - MTD - 3 * VmMTD) / VmMTD
36-
P1 <- VmMTD / (P2 ^ 2)
37+
mom <- MoMdelap(testData, type = 3)
38+
P2 <- 0.5 * (SK3 * (VTD ^ 1.5) - MTD - 3 * vmMTD) / vmMTD
39+
P1 <- vmMTD / (P2 ^ 2)
3740
P3 <- MTD - P1 * P2
38-
expect_equal(MoM[[1]], P1)
39-
expect_equal(MoM[[2]], P2)
40-
expect_equal(MoM[[3]], P3)
41+
expect_equal(mom[[1]], P1, tolerance = tol)
42+
expect_equal(mom[[2]], P2, tolerance = tol)
43+
expect_equal(mom[[3]], P3, tolerance = tol)
4144

4245
# MoMdelap traps bad types
43-
expect_error(MoMdelap(TestData, type = 4),
44-
'Skew type must be one of 1, 2, or 3.')
46+
expect_error(MoMdelap(testData, type = 4),
47+
"Skew type must be one of 1, 2, or 3.")
4548

4649
# MoMdelap traps bad parameters
47-
TestData <- c(3, 2, 12, 11, 1, 7, 1, 4, 0, 4)
48-
expect_error(MoMdelap(TestData),
49-
'Method of moments not appropriate for this data; results include non-positive parameters.')
50+
testData <- c(3, 2, 12, 11, 1, 7, 1, 4, 0, 4)
51+
expect_error(MoMdelap(testData), inapp)
5052

5153
# Non-double vector converted
5254
expect_equal(MoMdelap(c(30L, 32L, 39L, 50L), type = 2L),
53-
MoMdelap(c(30, 32, 39, 50), type = 2L))
55+
MoMdelap(c(30, 32, 39, 50), type = 2L), tolerance = tol)

inst/tinytest/test-pdelap.r

+24-18
Original file line numberDiff line numberDiff line change
@@ -1,20 +1,23 @@
1-
VAL <- data.frame(read.csv(file = "./RawTest.csv", header = TRUE))
2-
nanWarn <- 'NaNs produced'
1+
tol <- sqrt(.Machine$double.eps)
2+
VAL <- data.frame(read.csv(file = file.path(".", "RawTest.csv"), header = TRUE))
3+
nanWarn <- "NaNs produced"
34

45
# Singleton function accuracy
5-
expect_equal(pdelap(0:36, 2, 1, 5), VAL$PDELAP_2)
6+
expect_equal(pdelap(0:36, 2, 1, 5), VAL$PDELAP_2, tolerance = tol)
67

78
# Singleton log.p
8-
expect_equal(pdelap(0:36, 4, 5, 1, log.p = TRUE), log(pdelap(0:36, 4, 5, 1)))
9+
expect_equal(pdelap(0:36, 4, 5, 1, log.p = TRUE), log(pdelap(0:36, 4, 5, 1)),
10+
tolerance = tol)
911

1012
# Singleton lower.tail
1113
expect_equal(pdelap(0:100, 8, 10, 6, lower.tail = FALSE),
12-
1 - pdelap(0:100, 8, 10, 6))
13-
expect_equal(pdelap(6, 2.9647, 0.005/2.9647, 0.0057, lower.tail = FALSE), 0)
14+
1 - pdelap(0:100, 8, 10, 6), tolerance = tol)
15+
expect_equal(pdelap(6, 2.9647, 0.005 / 2.9647, 0.0057, lower.tail = FALSE), 0,
16+
tolerance = tol)
1417

1518
# Singleton lower.tail & log.p
16-
expect_equal(pdelap(0:100, 8, 10, 6, lower.tail = FALSE, log.p = TRUE),
17-
log(1 - pdelap(0:100, 8, 10, 6)))
19+
expect_equal(pdelap(0:100, 8, 10, 6, lower.tail = FALSE, log.p = TRUE),
20+
log(1 - pdelap(0:100, 8, 10, 6)), tolerance = tol)
1821

1922
# Singleton NaN
2023
expect_warning(pdelap(1, 0, 1, 2), nanWarn)
@@ -26,26 +29,28 @@ expect_warning(pdelap(0, 1, 4, -1e-3), nanWarn)
2629
expect_warning(ddelap(NaN, 1, 4, 6), nanWarn)
2730
expect_warning(ddelap(NA, 1, 4, 12), nanWarn)
2831
tst <- suppressWarnings(pdelap(c(NA, 4, NaN), 0.5, 4, 0.2))
29-
expect_equal(tst, c(NaN, pdelap(4, 0.5, 4, 0.2), NaN))
32+
expect_equal(tst, c(NaN, pdelap(4, 0.5, 4, 0.2), NaN), tolerance = tol)
3033
expect_identical(suppressWarnings(pdelap(c(NA, NaN), 0.5, 4, 0.2)), rep(NaN, 2))
3134

3235
# Vector function accuracy
3336
expect_equal(pdelap(0:36, c(1, 2, 3), c(4, 1, 2), c(2, 5, 7)),
34-
VAL$PDELAP_Triple)
37+
VAL$PDELAP_Triple, tolerance = tol)
3538

3639
# Vector log.p
3740
expect_equal(pdelap(0:36, c(1, 2, 3), c(4, 1, 2), c(2, 5, 7), log.p = TRUE),
38-
log(VAL$PDELAP_Triple))
41+
log(VAL$PDELAP_Triple), tolerance = tol)
3942

4043
# Vector lower.tail
4144
expect_equal(pdelap(0:100, c(4, 9, 2), c(6, 12, 8), c(7, 14, 9),
4245
lower.tail = FALSE),
43-
1 - pdelap(0:100, c(4, 9, 2), c(6, 12, 8), c(7, 14, 9)))
46+
1 - pdelap(0:100, c(4, 9, 2), c(6, 12, 8), c(7, 14, 9)),
47+
tolerance = tol)
4448

4549
# Vector lower.tail & log.p
4650
expect_equal(pdelap(0:100, c(4, 9, 2), c(6, 12, 8), c(7, 14, 9),
4751
lower.tail = FALSE, log.p = TRUE),
48-
log(1 - pdelap(0:100, c(4, 9, 2), c(6, 12, 8), c(7, 14, 9))))
52+
log(1 - pdelap(0:100, c(4, 9, 2), c(6, 12, 8), c(7, 14, 9))),
53+
tolerance = tol)
4954

5055
# Vector NaN
5156
expect_warning(pdelap(1:10, 0, 1, 2), nanWarn)
@@ -55,24 +60,25 @@ expect_warning(pdelap(c(NA, 2), c(2, 1, 2), c(1, 3, 2), c(1, 2, 4)))
5560
expect_warning(pdelap(c(3, NaN), c(2, 1, 2), c(1, 3, 2), c(1, 2, 4)))
5661
tst <- suppressWarnings(pdelap(c(NA, 0, NaN), c(1, 2, 3), c(4, 1, 2),
5762
c(2, 5, 7)))
58-
expect_equal(tst, c(NaN, pdelap(0, 2, 1, 5), NaN))
63+
expect_equal(tst, c(NaN, pdelap(0, 2, 1, 5), NaN), tolerance = tol)
5964
tst <- suppressWarnings(pdelap(c(0, 0, 0), c(NA, 2, 3), c(4, 1, 2),
6065
c(2, 5, NaN)))
61-
expect_equal(tst, c(NaN, pdelap(0, 2, 1, 5), NaN))
66+
expect_equal(tst, c(NaN, pdelap(0, 2, 1, 5), NaN), tolerance = tol)
6267

6368
# Negative values due to floating point issues are 0
6469
if (R.Version()$arch == "x86_64") {
6570
expect_identical(pdelap(500, 13.08251, 0.02414521, 0.04421658, FALSE, FALSE), 0)
6671
} else {
67-
expect_equal(pdelap(500, 13.08251, 0.02414521, 0.04421658, FALSE, FALSE), 0)
72+
expect_equal(pdelap(500, 13.08251, 0.02414521, 0.04421658, FALSE, FALSE), 0,
73+
tolerance = tol)
6874
}
6975

7076
# Non-double parameters converted
71-
expect_equal(pdelap(2L, 1L, 2L, 3L), pdelap(2L, 1, 2, 3))
77+
expect_equal(pdelap(2L, 1L, 2L, 3L), pdelap(2L, 1, 2, 3), tolerance = tol)
7278

7379
# Floating point issues do not lead to CDF > 1
7480
# print(pdelap(1000, 8, 15, 100), digits = 17) used to be 1.0000000000001035
75-
expect_true(pdelap(1000, 8, 15, 100) <= 1)
81+
expect_true(pdelap(1000, 8, 15, 100) <= 1)
7682

7783
# Infinite values
7884
expect_identical(pdelap(Inf, 1L, 2L, 3L), 1)

0 commit comments

Comments
 (0)