Skip to content

Commit

Permalink
Disallow using '0 significant digits' in the summary (which will brea…
Browse files Browse the repository at this point in the history
…k under R 4.2).
  • Loading branch information
Alain Hauser committed Jun 6, 2021
1 parent ae1df0c commit 7e0f59f
Show file tree
Hide file tree
Showing 6 changed files with 22 additions and 21 deletions.
6 changes: 3 additions & 3 deletions DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Package: CausalImpact
Title: Inferring Causal Effects using Bayesian Structural Time-Series Models
Date: 2021-02-21
Date: 2021-06-04
Author: Kay H. Brodersen <[email protected]>,
Alain Hauser <[email protected]>
Maintainer: Alain Hauser <[email protected]>
Expand All @@ -9,8 +9,8 @@ Description: Implements a Bayesian approach to causal impact estimation in time
series, as described in Brodersen et al. (2015) <DOI:10.1214/14-AOAS788>.
See the package documentation on GitHub
<https://google.github.io/CausalImpact/> to get started.
Copyright: Copyright (C) 2014-2020 Google, Inc.
Version: 1.2.6
Copyright: Copyright (C) 2014-2021 Google, Inc.
Version: 1.2.7
VignetteBuilder: knitr
License: Apache License 2.0 | file LICENSE
Imports: assertthat (>= 0.2.0), Boom, dplyr, ggplot2, zoo
Expand Down
19 changes: 10 additions & 9 deletions R/impact_analysis.R
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
# Copyright 2014-2020 Google Inc. All rights reserved.
# Copyright 2014-2021 Google Inc. All rights reserved.
#
# Licensed under the Apache License, Version 2.0 (the "License");
# you may not use this file except in compliance with the License.
Expand Down Expand Up @@ -511,10 +511,12 @@ PrintSummary <- function(impact, digits = 2L) {
# impact: A \code{CausalImpact} results object, as returned by
# \code{CausalImpact()}.
#
# digits: Number of digits to print for all numbers.
# digits: Number of significant digits to print for all numbers.

# Check input
assert_that(class(impact) == "CausalImpact")
assert_that(is.numeric(digits), is.scalar(digits), as.integer(digits) > 0,
msg = "<digits> must be a positive integer")
summary <- impact$summary
alpha <- impact$model$alpha
assert_that(!is.null(alpha) && alpha > 0,
Expand All @@ -528,19 +530,18 @@ PrintSummary <- function(impact, digits = 2L) {
}

# Define formatting helper functions
StrTrim <- function (x) gsub("^\\s+|\\s+$", "", x)
FormatNumber <- function(x) StrTrim(format(x, digits = digits))
FormatNumber <- function(x) format(x, digits = digits, trim = TRUE)
FormatPercent <- function(x) {
StrTrim(paste0(format(x * 100, digits = digits), "%"))
paste0(format(x * 100, digits = digits, trim = TRUE), "%")
}
FormatCI <- function(a, b) {
paste0("[", StrTrim(format(a, digits = min(digits, 2))),
", ", StrTrim(format(b, digits = min(digits, 2))),
paste0("[", format(a, digits = min(digits, 2), trim = TRUE),
", ", format(b, digits = min(digits, 2), trim = TRUE),
"]")
}
FormatPercentCI <- function(a, b) {
paste0("[", StrTrim(format(a * 100, digits = min(digits, 2))),
"%, ", StrTrim(format(b * 100, digits = min(digits, 2))),
paste0("[", format(a * 100, digits = min(digits, 2), trim = TRUE),
"%, ", format(b * 100, digits = min(digits, 2), trim = TRUE),
"%]")
}

Expand Down
2 changes: 1 addition & 1 deletion R/impact_misc.R
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
# Copyright 2014-2017 Google Inc. All rights reserved.
# Copyright 2014-2021 Google Inc. All rights reserved.
#
# Licensed under the Apache License, Version 2.0 (the "License");
# you may not use this file except in compliance with the License.
Expand Down
2 changes: 1 addition & 1 deletion R/impact_model.R
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
# Copyright 2014-2020 Google Inc. All rights reserved.
# Copyright 2014-2021 Google Inc. All rights reserved.
#
# Licensed under the Apache License, Version 2.0 (the "License");
# you may not use this file except in compliance with the License.
Expand Down
9 changes: 5 additions & 4 deletions tests/testthat/test-impact-analysis.R
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
# Copyright 2014-2020 Google Inc. All rights reserved.
# Copyright 2014-2021 Google Inc. All rights reserved.
#
# Licensed under the Apache License, Version 2.0 (the "License");
# you may not use this file except in compliance with the License.
Expand Down Expand Up @@ -483,7 +483,7 @@ test_that("CausalImpact.RunWithData.StandardizeData", {
post.period <- c(251, 500)
data <- cbind(y, x1)
suppressWarnings(impact1 <- CausalImpact(
data, pre.period, post.period,
data, pre.period, post.period,
model.args = list(niter = 500, standardize.data = FALSE)))
estimates1 <- colMeans(impact1$model$bsts.model$coefficients)
expect_equal(as.vector(estimates1)[2], beta[2], tolerance = 0.05)
Expand Down Expand Up @@ -581,7 +581,7 @@ test_that("CausalImpact.RunWithData.MissingTimePoint", {

# Missing in pre-period. Suppressing the warning that there might not be
# enough MCMC samples.
suppressWarnings(impact <- CausalImpact(series[-10, ], pre.period,
suppressWarnings(impact <- CausalImpact(series[-10, ], pre.period,
post.period, model.args))
indices <- time(impact$series)
expect_equal(indices, time(series)[-10])
Expand Down Expand Up @@ -708,8 +708,9 @@ test_that("PrintSummary", {
suppressWarnings(impact <- CausalImpact(data, pre.period, post.period,
model.args))
expect_output(PrintSummary(impact), "\\([0-9.]{3}[0-9]*\\)")
expect_output(PrintSummary(impact, digits = 0), "\\([0-9]+\\)")
expect_output(PrintSummary(impact, digits = 10), "\\([0-9.]{11}[0-9]*\\)")
expect_error(PrintSummary(impact, digits = 0), "positive")
expect_error(PrintSummary(impact, digits = "test"), "positive")
})

test_that("PrintReport", {
Expand Down
5 changes: 2 additions & 3 deletions tests/testthat/test-impact-model.R
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
# Copyright 2014-2020 Google Inc. All rights reserved.
# Copyright 2014-2021 Google Inc. All rights reserved.
#
# Licensed under the Apache License, Version 2.0 (the "License");
# you may not use this file except in compliance with the License.
Expand All @@ -12,7 +12,7 @@
# See the License for the specific language governing permissions and
# limitations under the License.

testthat::context("Unit tests for impact_model_ss.R")
testthat::context("Unit tests for impact_model.R")

# Author: [email protected] (Kay Brodersen)

Expand Down Expand Up @@ -129,7 +129,6 @@ test_that("FormatInputForConstructModel", {
# Test bad <max.flips>
bad.max.flips <- list(-2, 9.1, "foo", c(100, 200))
lapply(bad.max.flips, function(max.flips) {
print(max.flips)
expect_error(FormatInputForConstructModel(data,
list(max.flips = max.flips))) })
})
Expand Down

0 comments on commit 7e0f59f

Please sign in to comment.