Skip to content

Commit

Permalink
improved logo
Browse files Browse the repository at this point in the history
  • Loading branch information
Daan de Jong committed Nov 28, 2023
1 parent c4adc2b commit 423e523
Show file tree
Hide file tree
Showing 6 changed files with 37 additions and 32 deletions.
2 changes: 2 additions & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@ S3method(residuals,hystar_fit)
S3method(summary,hystar_fit)
S3method(summary,hystar_sim)
export(hystar_fit)
export(hystar_info)
export(hystar_sim)
export(z_sim)
importFrom(Rcpp,sourceCpp)
Expand All @@ -28,5 +29,6 @@ importFrom(stats,qnorm)
importFrom(stats,quantile)
importFrom(stats,residuals)
importFrom(stats,rnorm)
importFrom(utils,browseURL)
importFrom(utils,combn)
useDynLib(hystar, .registration = TRUE)
2 changes: 1 addition & 1 deletion NEWS.md
Original file line number Diff line number Diff line change
Expand Up @@ -18,5 +18,5 @@

# `hystar` 1.0.0

* First CRAN release! 🎉
* First CRAN release!

9 changes: 8 additions & 1 deletion R/optimize.R
Original file line number Diff line number Diff line change
Expand Up @@ -35,13 +35,20 @@ get_optims <- function(y, eff, x, z, p0, p1, grid) {
prev <- rep(-9L, times = length(eff))

for (i in 1:nrow(grid)) {
message("\rsearching delay, r0, r1 for p0 = ", p0, " and p1 = ", p1,
". ", round(100 * i / nrow(grid), 0), "%", appendLF = FALSE)
#message("Searching delay, r0, r1: ",
# paste(grid[i, "d"], round(grid[i, "r0"], 2), round(grid[i, "r1"], 2),
# sep = ", "),
# "\r", appendLF = FALSE)
H <- ts_hys(z[eff - grid[i, "d"]], grid[i, "r0"], grid[i, "r1"])
R <- ts_reg(H, start = grid[i, "s"])
if (all(R == prev)) {
results[i] <- results[i-1]
} else {
X <- create_X(x, p0, p1, R)
results[i] <- fit(y[eff], X)$rss
results[i] <- Inf
try(results[i] <- fit(y[eff], X)$rss, silent = TRUE)
}
prev <- R
}
Expand Down
2 changes: 1 addition & 1 deletion R/print.R
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,7 @@ print.hystar_sim <- function(x, ...) {
}

print_hystar <- function(n, d, r0, r1, coe0, coe1, rv0, rv1, simfit, tar) {
model <- if (tar) "TAR model " else "HysTAR model "
model <- if (tar) "\nTAR model " else "\nHysTAR model "
cat(paste0(model, simfit, " ", n, " observations."),
"\n\n",
"if R[t] = 0:\n", make_formula(coe0, rv0),
Expand Down
29 changes: 0 additions & 29 deletions R/welcome.R

This file was deleted.

25 changes: 25 additions & 0 deletions R/zzz.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,25 @@
.onAttach <- function(libname, pkgname) {
hystar_string <- "
__ __
/ /_ __ ______/ /_________
/ _ / // (_ -/ _/ _ / __\\
/_//_/\\_, /___)\\__/\\_,_/_/
/___/ 1.2.0
Estimation and simulation of the HysTAR Model.
For function help, run `?hystar_fit`, `?hystar_sim` or `?z_sim`.
For more information, run `hystar_info()` (opens a URL in your browser).
"

packageStartupMessage(hystar_string)
}

#' @export
#' @importFrom utils browseURL
hystar_info <- function() {
browseURL("https://daandejongen.github.io/hystar/index.html")
}




0 comments on commit 423e523

Please sign in to comment.