Skip to content

Commit

Permalink
Fixes #15
Browse files Browse the repository at this point in the history
Updates on #13
  • Loading branch information
spsanderson committed Jul 16, 2024
1 parent 15dcad5 commit eb1760e
Show file tree
Hide file tree
Showing 7 changed files with 220 additions and 23 deletions.
1 change: 1 addition & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
# Generated by roxygen2: do not edit by hand

export(random_normal_walk)
export(rw30)
15 changes: 8 additions & 7 deletions R/auto-rw30.R
Original file line number Diff line number Diff line change
Expand Up @@ -47,19 +47,20 @@ rw30 <- function() {
# Create a tibble with the walks
walks_tibble <- dplyr::tibble(
x = 1:num_steps,
!!!stats::setNames(walks, paste0("walk_", 1:num_walks))
!!!stats::setNames(walks, 1:num_walks)
#!!!stats::setNames(walks, paste0("walk_", 1:num_walks))
)

# Pivot the tibble longer
walks_long <- tidyr::pivot_longer(
walks_tibble,
cols = dplyr::starts_with("walk_"),
names_to = "walk",
values_to = "value"
cols = -x,
names_to = "walk_number",
values_to = "y"
) |>
dplyr::arrange(walk, x) |>
dplyr::select(walk, x, value) |>
dplyr::mutate(walk = factor(walk))
dplyr::mutate(walk_number = factor(walk_number)) |>
dplyr::select(walk_number, x, y) |>
dplyr::arrange(walk_number, x)

attr(walks_long, "num_walks") <- num_walks
attr(walks_long, "num_steps") <- num_steps
Expand Down
119 changes: 119 additions & 0 deletions R/gen-random-normal-walk.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,119 @@
#' Generate Multiple Random Normal Walks
#'
#' @family Generator Functions
#'
#' @author Steven P. Sanderson II, MPH
#'
#' @details
#' This function generates multiple random walks, which are sequences of steps
#' where each step is a random draw from a normal distribution. The user can
#' specify the number of walks, the number of steps in each walk, and the
#' parameters of the normal distribution (mean and standard deviation). The
#' function also allows for sampling a proportion of the steps and optionally
#' sampling with replacement.
#'
#' The output tibble includes several computed columns for each walk, such as the
#' cumulative sum, product, minimum, and maximum of the steps.
#'
#' @description
#' The `random_normal_walk` function is useful for simulating random processes
#' and can be applied in various fields such as finance, physics, and biology
#' to model different stochastic behaviors.
#'
#' @param .num_walks An integer specifying the number of random walks to generate. Default is 25.
#' @param .n An integer specifying the number of steps in each walk. Default is 100.
#' @param .mu A numeric value indicating the mean of the normal distribution. Default is 0.
#' @param .sd A numeric value indicating the standard deviation of the normal distribution. Default is 0.1.
#' @param .initial_value A numeric value indicating the initial value of the walks. Default is 0.
#' @param .samp A logical value indicating whether to sample the normal distribution values. Default is TRUE.
#' @param .replace A logical value indicating whether sampling is with replacement. Default is TRUE.
#' @param .sample_size A numeric value between 0 and 1 specifying the proportion of `.n` to sample. Default is 0.8.
#'
#' @return A tibble containing the generated random walks with the following columns:
#' \itemize{
#' \item `walk_number`: Factor representing the walk number.
#' \item `x`: Step index.
#' \item `y`: Normal distribution values.
#' \item `cum_sum`: Cumulative sum of `y`.
#' \item `cum_prod`: Cumulative product of `y`.
#' \item `cum_min`: Cumulative minimum of `y`.
#' \item `cum_max`: Cumulative maximum of `y`.
#' }
#' The tibble includes attributes for the function parameters.
#'
#' @examples
#' # Generate 10 random walks with 50 steps each
#' random_normal_walk(.num_walks = 10, .n = 50)
#'
#' # Generate random walks with different mean and standard deviation
#' random_normal_walk(.num_walks = 5, .n = 100, .mu = 0.5, .sd = 0.2)
#'
#' @name random_normal_walk
NULL
#' @rdname random_normal_walk
#' @export
random_normal_walk <- function(.num_walks = 25, .n = 100, .mu = 0, .sd = .1,
.initial_value = 0, .samp = TRUE, .replace = TRUE,
.sample_size = 0.8) {

# Defensive checks
if (.num_walks < 0) {
rlang::abort(".num_walks cannot be less than 0", use_cli_format = TRUE)
}
if (.n < 0) {
rlang::abort(".n cannot be less than 0", use_cli_format = TRUE)
}
if (.mu < 0) {
rlang::abort(".mu cannot be less than 0", use_cli_format = TRUE)
}
if (.sd < 0) {
rlang::abort(".sd cannot be less than 0", use_cli_format = TRUE)
}
if (.sample_size < 0 || .sample_size > 1) {
rlang::abort(".sample_size cannot be less than 0 or more than 1", use_cli_format = TRUE)
}

# Variables
num_walks <- as.integer(.num_walks)
n <- as.integer(.n)
mu <- as.numeric(.mu)
sd <- as.numeric(.sd)
initial_value <- as.numeric(.initial_value)
replace <- as.logical(.replace)
samp <- as.logical(.samp)
samp_size <- round(.sample_size * n, 0)

res <- dplyr::tibble(walk_number = 1:num_walks |>
factor()) |>
dplyr::group_by(walk_number) |>
dplyr::mutate(
x = dplyr::case_when(
samp == TRUE ~ list(1:samp_size),
.default = list(1:n)
)) |>
dplyr::mutate(
y = dplyr::case_when(
samp == TRUE ~ list(sample(rnorm(n, mu, sd), replace = replace,
size = samp_size)),
.default = list(rnorm(n, mu, sd))
)) |>
tidyr::unnest(cols = c(x, y)) |>
dplyr::mutate(cum_sum = initial_value + cumsum(y)) |>
dplyr::mutate(cum_prod = initial_value * cumprod(1 + y)) |>
dplyr::mutate(cum_min = initial_value + cummin(y)) |>
dplyr::mutate(cum_max = initial_value + cummax(y)) |>
dplyr::ungroup()

# Attributes
attr(res, "num_walks") <- num_walks
attr(res, "n") <- n
attr(res, "mu") <- mu
attr(res, "sd") <- sd
attr(res, "initial_value") <- initial_value
attr(res, "replace") <- replace
attr(res, "samp") <- samp
attr(res, "samp_size") <- samp_size

# Return
return(res)
}
3 changes: 2 additions & 1 deletion README.Rmd
Original file line number Diff line number Diff line change
Expand Up @@ -43,5 +43,6 @@ This is a basic example which shows you how to solve a common problem:
```{r example}
library(RandomWalker)
## basic example code
rw30()
rw30() |>
head()
```
26 changes: 11 additions & 15 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -36,19 +36,15 @@ This is a basic example which shows you how to solve a common problem:
``` r
library(RandomWalker)
## basic example code
rw30()
#> # A tibble: 3,000 × 3
#> walk x value
#> <fct> <int> <dbl>
#> 1 walk_1 1 0
#> 2 walk_1 2 0.916
#> 3 walk_1 3 1.26
#> 4 walk_1 4 1.84
#> 5 walk_1 5 2.53
#> 6 walk_1 6 1.39
#> 7 walk_1 7 1.94
#> 8 walk_1 8 2.42
#> 9 walk_1 9 1.86
#> 10 walk_1 10 2.27
#> # ℹ 2,990 more rows
rw30() |>
head()
#> # A tibble: 6 × 3
#> walk_number x y
#> <fct> <int> <dbl>
#> 1 1 1 0
#> 2 1 2 -0.859
#> 3 1 3 -2.52
#> 4 1 4 -2.88
#> 5 1 5 -2.74
#> 6 1 6 -3.90
```
4 changes: 4 additions & 0 deletions _pkgdown.yml
Original file line number Diff line number Diff line change
Expand Up @@ -23,5 +23,9 @@ reference:
desc: Functions that generate non-modifiable random walks
contents:
- has_concept("Auto Random Walk")
- title: Generator Functions
desc: Functions that generate modifiable random walks
contents:
- has_concept("Generator Functions")

search:
75 changes: 75 additions & 0 deletions man/random_normal_walk.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

0 comments on commit eb1760e

Please sign in to comment.