From 3625d913a19ac8119c89e09e36097fdfd261b0a3 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Paul-Christian=20B=C3=BCrkner?= Date: Mon, 13 Nov 2023 08:44:11 +0100 Subject: [PATCH] remove some remaining uses of Stan's old array syntax --- DESCRIPTION | 4 ++-- NEWS.md | 4 ++++ R/families.R | 2 +- R/stan-response.R | 2 +- R/stanvars.R | 2 +- inst/chunks/fun_is_equal.stan | 2 +- inst/chunks/fun_multinomial_logit.stan | 2 +- inst/chunks/fun_normal_time.stan | 10 ++++++---- inst/chunks/fun_normal_time_se.stan | 12 ++++++------ inst/chunks/fun_scale_r_cor_by.stan | 2 +- inst/chunks/fun_scale_r_cor_by_cov.stan | 4 ++-- inst/chunks/fun_scale_time_err.stan | 4 ++-- inst/chunks/fun_sequence.stan | 2 +- inst/chunks/fun_sparse_car_lpdf.stan | 2 +- inst/chunks/fun_sparse_icar_lpdf.stan | 2 +- inst/chunks/fun_stack_vectors.stan | 4 ++-- inst/chunks/fun_student_t_time.stan | 16 ++++++++-------- inst/chunks/fun_student_t_time_se.stan | 16 ++++++++-------- inst/chunks/fun_which_range.stan | 6 +++--- man/custom_family.Rd | 2 +- tests/local/tests.models-2.R | 2 +- 21 files changed, 54 insertions(+), 48 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 2d69184de..2301f269a 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -2,8 +2,8 @@ Package: brms Encoding: UTF-8 Type: Package Title: Bayesian Regression Models using 'Stan' -Version: 2.20.5 -Date: 2023-09-25 +Version: 2.20.6 +Date: 2023-11-13 Authors@R: c(person("Paul-Christian", "Bürkner", email = "paul.buerkner@gmail.com", role = c("aut", "cre")), diff --git a/NEWS.md b/NEWS.md index fd044c614..ff1ef85cf 100644 --- a/NEWS.md +++ b/NEWS.md @@ -5,6 +5,10 @@ * No longer automatically canonicalize the Stan code if cmdstanr is used as backend. (#1544) +### Bug Fixes + +* Remove some remaining uses of Stan's old array syntax. + # brms 2.20.3 diff --git a/R/families.R b/R/families.R index c05f4a528..79c2c77e9 100644 --- a/R/families.R +++ b/R/families.R @@ -1122,7 +1122,7 @@ mixture <- function(..., flist = NULL, nmix = 1, order = NULL) { #' #' # define the corresponding Stan density function #' stan_density_vec <- " -#' real beta_binomial2_lpmf(int[] y, vector mu, real phi, int[] N) { +#' real beta_binomial2_lpmf(array[] int y, vector mu, real phi, array[] int N) { #' return beta_binomial_lpmf(y | N, mu * phi, (1 - mu) * phi); #' } #' " diff --git a/R/stan-response.R b/R/stan-response.R index eae1ef143..16b8dcbc6 100644 --- a/R/stan-response.R +++ b/R/stan-response.R @@ -36,7 +36,7 @@ stan_response <- function(bterms, data, normalize) { str_add(out$data) <- glue( " array[N{resp}, ncat{resp}] int Y{resp}; // response array\n" ) - str_add(out$pll_args) <- glue(", data int[,] Y{resp}") + str_add(out$pll_args) <- glue(", data array[,] int Y{resp}") } } else { if (rtype == "real") { diff --git a/R/stanvars.R b/R/stanvars.R index 59249c8c1..c1c7a6ef0 100644 --- a/R/stanvars.R +++ b/R/stanvars.R @@ -123,7 +123,7 @@ stanvar <- function(x = NULL, name = NULL, scode = NULL, if (length(x) == 1L) { pll_type <- paste0(pll_type, "int") } else { - pll_type <- paste0(pll_type, "int[]") + pll_type <- paste0(pll_type, "array[] int") } } else if (is.vector(x)) { if (length(x) == 1L) { diff --git a/inst/chunks/fun_is_equal.stan b/inst/chunks/fun_is_equal.stan index 1fbff55ac..e1d3654dd 100644 --- a/inst/chunks/fun_is_equal.stan +++ b/inst/chunks/fun_is_equal.stan @@ -1,5 +1,5 @@ // are two 1D integer arrays equal? - int is_equal(int[] a, int[] b) { + int is_equal(array[] int a, array[] int b) { int n_a = size(a); int n_b = size(b); if (n_a != n_b) { diff --git a/inst/chunks/fun_multinomial_logit.stan b/inst/chunks/fun_multinomial_logit.stan index cb8d72cf2..9373c4302 100644 --- a/inst/chunks/fun_multinomial_logit.stan +++ b/inst/chunks/fun_multinomial_logit.stan @@ -5,6 +5,6 @@ * Returns: * a scalar to be added to the log posterior */ - real multinomial_logit2_lpmf(int[] y, vector mu) { + real multinomial_logit2_lpmf(array[] int y, vector mu) { return multinomial_lpmf(y | softmax(mu)); } diff --git a/inst/chunks/fun_normal_time.stan b/inst/chunks/fun_normal_time.stan index 973e2e783..300aeb0c1 100644 --- a/inst/chunks/fun_normal_time.stan +++ b/inst/chunks/fun_normal_time.stan @@ -12,7 +12,7 @@ * sum of the log-PDF values of all observations */ real normal_time_hom_lpdf(vector y, vector mu, real sigma, matrix chol_cor, - int[] nobs, int[] begin, int[] end) { + array[] int nobs, array[] int begin, array[] int end) { int I = size(nobs); vector[I] lp; matrix[rows(chol_cor), cols(chol_cor)] L = sigma * chol_cor; @@ -32,7 +32,7 @@ * sum of the log-PDF values of all observations */ real normal_time_het_lpdf(vector y, vector mu, vector sigma, matrix chol_cor, - int[] nobs, int[] begin, int[] end) { + array[] int nobs, array[] int begin, array[] int end) { int I = size(nobs); vector[I] lp; for (i in 1:I) { @@ -53,7 +53,8 @@ * sum of the log-PDF values of all observations */ real normal_time_hom_flex_lpdf(vector y, vector mu, real sigma, matrix chol_cor, - int[] nobs, int[] begin, int[] end, int[,] Jtime) { + array[] int nobs, array[] int begin, array[] int end, + array[,] int Jtime) { real lp = 0.0; int I = size(nobs); array[I] int has_lp = rep_array(0, I); @@ -103,7 +104,8 @@ * sum of the log-PDF values of all observations */ real normal_time_het_flex_lpdf(vector y, vector mu, vector sigma, matrix chol_cor, - int[] nobs, int[] begin, int[] end, int[,] Jtime) { + array[] int nobs, array[] int begin, array[] int end, + array[,] int Jtime) { int I = size(nobs); vector[I] lp; array[I] int has_lp = rep_array(0, I); diff --git a/inst/chunks/fun_normal_time_se.stan b/inst/chunks/fun_normal_time_se.stan index ec43de249..beb168322 100644 --- a/inst/chunks/fun_normal_time_se.stan +++ b/inst/chunks/fun_normal_time_se.stan @@ -14,7 +14,7 @@ * sum of the log-PDF values of all observations */ real normal_time_hom_se_lpdf(vector y, vector mu, real sigma, data vector se2, - matrix chol_cor, int[] nobs, int[] begin, int[] end) { + matrix chol_cor, array[] int nobs, array[] int begin, array[] int end) { int I = size(nobs); vector[I] lp; matrix[rows(chol_cor), cols(chol_cor)] Cov; @@ -36,7 +36,7 @@ * sum of the log-PDF values of all observations */ real normal_time_het_se_lpdf(vector y, vector mu, vector sigma, data vector se2, - matrix chol_cor, int[] nobs, int[] begin, int[] end) { + matrix chol_cor, array[] int nobs, array[] int begin, array[] int end) { int I = size(nobs); vector[I] lp; for (i in 1:I) { @@ -59,8 +59,8 @@ * sum of the log-PDF values of all observations */ real normal_time_hom_se_flex_lpdf(vector y, vector mu, real sigma, data vector se2, - matrix chol_cor, int[] nobs, int[] begin, - int[] end, int[,] Jtime) { + matrix chol_cor, array[] int nobs, array[] int begin, + array[] int end, array[,] int Jtime) { int I = size(nobs); vector[I] lp; matrix[rows(chol_cor), cols(chol_cor)] Cov; @@ -84,8 +84,8 @@ * sum of the log-PDF values of all observations */ real normal_time_het_se_flex_lpdf(vector y, vector mu, vector sigma, data vector se2, - matrix chol_cor, int[] nobs, int[] begin, - int[] end, int[,] Jtime) { + matrix chol_cor, array[] int nobs, array[] int begin, + array[] int end, array[,] int Jtime) { int I = size(nobs); vector[I] lp; matrix[rows(chol_cor), cols(chol_cor)] Cor; diff --git a/inst/chunks/fun_scale_r_cor_by.stan b/inst/chunks/fun_scale_r_cor_by.stan index c0080ee1e..73f596e2f 100644 --- a/inst/chunks/fun_scale_r_cor_by.stan +++ b/inst/chunks/fun_scale_r_cor_by.stan @@ -7,7 +7,7 @@ * Returns: * matrix of scaled group-level effects */ - matrix scale_r_cor_by(matrix z, matrix SD, matrix[] L, int[] Jby) { + matrix scale_r_cor_by(matrix z, matrix SD, array[] matrix L, array[] int Jby) { // r is stored in another dimension order than z matrix[cols(z), rows(z)] r; array[size(L)] matrix[rows(L[1]), cols(L[1])] LC; diff --git a/inst/chunks/fun_scale_r_cor_by_cov.stan b/inst/chunks/fun_scale_r_cor_by_cov.stan index 583ff13bf..2d3aa073a 100644 --- a/inst/chunks/fun_scale_r_cor_by_cov.stan +++ b/inst/chunks/fun_scale_r_cor_by_cov.stan @@ -9,8 +9,8 @@ * Returns: * matrix of scaled group-level effects */ - matrix scale_r_cor_by_cov(matrix z, matrix SD, matrix[] L, - int[] Jby, matrix Lcov) { + matrix scale_r_cor_by_cov(matrix z, matrix SD, array[] matrix L, + array[] int Jby, matrix Lcov) { vector[num_elements(z)] z_flat = to_vector(z); vector[num_elements(z)] r = rep_vector(0, num_elements(z)); array[size(L)] matrix[rows(L[1]), cols(L[1])] LC; diff --git a/inst/chunks/fun_scale_time_err.stan b/inst/chunks/fun_scale_time_err.stan index 7f5d4079d..936a952cc 100644 --- a/inst/chunks/fun_scale_time_err.stan +++ b/inst/chunks/fun_scale_time_err.stan @@ -11,7 +11,7 @@ * vector of scaled and correlated residuals */ vector scale_time_err(vector zerr, real sderr, matrix chol_cor, - int[] nobs, int[] begin, int[] end) { + array[] int nobs, array[] int begin, array[] int end) { vector[rows(zerr)] err; for (i in 1:size(nobs)) { matrix[nobs[i], nobs[i]] L_i; @@ -28,7 +28,7 @@ * vector of scaled and correlated residuals */ vector scale_time_err_flex(vector zerr, real sderr, matrix chol_cor, - int[] nobs, int[] begin, int[] end, int[,] Jtime) { + array[] int nobs, array[] int begin, array[] int end, array[,] int Jtime) { vector[rows(zerr)] err; int I = size(nobs); array[I] int has_err = rep_array(0, I); diff --git a/inst/chunks/fun_sequence.stan b/inst/chunks/fun_sequence.stan index 9ba3f976a..c4ef2833a 100644 --- a/inst/chunks/fun_sequence.stan +++ b/inst/chunks/fun_sequence.stan @@ -5,7 +5,7 @@ * Returns: * an integer sequence from start to end */ - int[] sequence(int start, int end) { + array[] int sequence(int start, int end) { array[end - start + 1] int seq; for (n in 1:num_elements(seq)) { seq[n] = n + start - 1; diff --git a/inst/chunks/fun_sparse_car_lpdf.stan b/inst/chunks/fun_sparse_car_lpdf.stan index ebdc8a5dd..bbe10c4a8 100644 --- a/inst/chunks/fun_sparse_car_lpdf.stan +++ b/inst/chunks/fun_sparse_car_lpdf.stan @@ -17,7 +17,7 @@ */ real sparse_car_lpdf(vector phi, real car, real sdcar, int Nloc, int Nedges, data vector Nneigh, data vector eigenW, - int[] edges1, int[] edges2) { + array[] int edges1, array[] int edges2) { real tau; // precision parameter row_vector[Nloc] phit_D; // phi' * D row_vector[Nloc] phit_W; // phi' * W diff --git a/inst/chunks/fun_sparse_icar_lpdf.stan b/inst/chunks/fun_sparse_icar_lpdf.stan index db1fadee1..09d3c6384 100644 --- a/inst/chunks/fun_sparse_icar_lpdf.stan +++ b/inst/chunks/fun_sparse_icar_lpdf.stan @@ -16,7 +16,7 @@ */ real sparse_icar_lpdf(vector phi, real sdcar, int Nloc, int Nedges, data vector Nneigh, data vector eigenW, - int[] edges1, int[] edges2) { + array[] int edges1, array[] int edges2) { real tau; // precision parameter row_vector[Nloc] phit_D; // phi' * D row_vector[Nloc] phit_W; // phi' * W diff --git a/inst/chunks/fun_stack_vectors.stan b/inst/chunks/fun_stack_vectors.stan index cbb9bd595..4b35ced73 100644 --- a/inst/chunks/fun_stack_vectors.stan +++ b/inst/chunks/fun_stack_vectors.stan @@ -1,8 +1,8 @@ /* grouped data stored linearly in "data" as indexed by begin and end * is repacked to be stacked into an array of vectors. */ - vector[] stack_vectors(vector long_data, int n, int[] stack, - int[] begin, int[] end) { + vector[] stack_vectors(vector long_data, int n, array[] int stack, + array[] int begin, array[] int end) { int S = sum(stack); int G = size(stack); array[S] vector[n] stacked; diff --git a/inst/chunks/fun_student_t_time.stan b/inst/chunks/fun_student_t_time.stan index 089222fde..7cb352249 100644 --- a/inst/chunks/fun_student_t_time.stan +++ b/inst/chunks/fun_student_t_time.stan @@ -13,8 +13,8 @@ * sum of the log-PDF values of all observations */ real student_t_time_hom_lpdf(vector y, real nu, vector mu, real sigma, - matrix chol_cor, int[] nobs, int[] begin, - int[] end) { + matrix chol_cor, array[] int nobs, array[] int begin, + array[] int end) { int I = size(nobs); vector[I] lp; for (i in 1:I) { @@ -35,8 +35,8 @@ * sum of the log-PDF values of all observations */ real student_t_time_het_lpdf(vector y, real nu, vector mu, vector sigma, - matrix chol_cor, int[] nobs, int[] begin, - int[] end) { + matrix chol_cor, array[] int nobs, array[] int begin, + array[] int end) { int I = size(nobs); vector[I] lp; for (i in 1:I) { @@ -58,8 +58,8 @@ * sum of the log-PDF values of all observations */ real student_t_time_hom_flex_lpdf(vector y, real nu, vector mu, real sigma, - matrix chol_cor, int[] nobs, int[] begin, - int[] end, int[,] Jtime) { + matrix chol_cor, array[] int nobs, array[] int begin, + array[] int end, array[,] int Jtime) { int I = size(nobs); vector[I] lp; matrix[rows(chol_cor), cols(chol_cor)] Cov; @@ -83,8 +83,8 @@ * sum of the log-PDF values of all observations */ real student_t_time_het_flex_lpdf(vector y, real nu, vector mu, vector sigma, - matrix chol_cor, int[] nobs, int[] begin, - int[] end, int[,] Jtime) { + matrix chol_cor, array[] int nobs, array[] int begin, + array[] int end, array[,] int Jtime) { int I = size(nobs); vector[I] lp; matrix[rows(chol_cor), cols(chol_cor)] Cor; diff --git a/inst/chunks/fun_student_t_time_se.stan b/inst/chunks/fun_student_t_time_se.stan index 6568e5265..00c5cbd2c 100644 --- a/inst/chunks/fun_student_t_time_se.stan +++ b/inst/chunks/fun_student_t_time_se.stan @@ -15,8 +15,8 @@ * sum of the log-PDF values of all observations */ real student_t_time_hom_se_lpdf(vector y, real nu, vector mu, real sigma, - data vector se2, matrix chol_cor, int[] nobs, - int[] begin, int[] end) { + data vector se2, matrix chol_cor, array[] int nobs, + array[] int begin, array[] int end) { int I = size(nobs); vector[I] lp; matrix[rows(chol_cor), cols(chol_cor)] Cov; @@ -38,8 +38,8 @@ * sum of the log-PDF values of all observations */ real student_t_time_het_se_lpdf(vector y, real nu, vector mu, vector sigma, - data vector se2, matrix chol_cor, int[] nobs, - int[] begin, int[] end) { + data vector se2, matrix chol_cor, array[] int nobs, + array[] int begin, array[] int end) { int I = size(nobs); vector[I] lp; for (i in 1:I) { @@ -61,8 +61,8 @@ * sum of the log-PDF values of all observations */ real student_t_time_hom_se_flex_lpdf(vector y, real nu, vector mu, real sigma, - data vector se2, matrix chol_cor, int[] nobs, - int[] begin, int[] end, int[,] Jtime) { + data vector se2, matrix chol_cor, array[] int nobs, + array[] int begin, array[] int end, array[,] int Jtime) { int I = size(nobs); vector[I] lp; matrix[rows(chol_cor), cols(chol_cor)] Cov; @@ -86,8 +86,8 @@ * sum of the log-PDF values of all observations */ real student_t_time_het_se_flex_lpdf(vector y, real nu, vector mu, vector sigma, - data vector se2, matrix chol_cor, int[] nobs, - int[] begin, int[] end, int[,] Jtime) { + data vector se2, matrix chol_cor, array[] int nobs, + array[] int begin, array[] int end, array[,] int Jtime) { int I = size(nobs); vector[I] lp; matrix[rows(chol_cor), cols(chol_cor)] Cor; diff --git a/inst/chunks/fun_which_range.stan b/inst/chunks/fun_which_range.stan index bd3713ea2..ed690a541 100644 --- a/inst/chunks/fun_which_range.stan +++ b/inst/chunks/fun_which_range.stan @@ -6,7 +6,7 @@ * Returns: * a scalar integer */ - int size_range(int[] x, int start, int end) { + int size_range(array[] int x, int start, int end) { int out = 0; for (i in 1:size(x)) { out += (x[i] >= start && x[i] <= end); @@ -21,7 +21,7 @@ * Returns: * an integer array */ - int[] which_range(int[] x, int start, int end) { + array[] int which_range(array[] int x, int start, int end) { array[size_range(x, start, end)] int out; int j = 1; for (i in 1:size(x)) { @@ -39,7 +39,7 @@ * Returns: * an integer array */ - int[] start_at_one(int[] x, int start) { + array[] int start_at_one(array[] int x, int start) { array[size(x)] int out; for (i in 1:size(x)) { out[i] = x[i] - start + 1; diff --git a/man/custom_family.Rd b/man/custom_family.Rd index 3804c299e..3ebdc41dc 100644 --- a/man/custom_family.Rd +++ b/man/custom_family.Rd @@ -162,7 +162,7 @@ beta_binomial2_vec <- custom_family( # define the corresponding Stan density function stan_density_vec <- " - real beta_binomial2_lpmf(int[] y, vector mu, real phi, int[] N) { + real beta_binomial2_lpmf(array[] int y, vector mu, real phi, array[] int N) { return beta_binomial_lpmf(y | N, mu * phi, (1 - mu) * phi); } " diff --git a/tests/local/tests.models-2.R b/tests/local/tests.models-2.R index 8f15c97ba..1e1d6a756 100644 --- a/tests/local/tests.models-2.R +++ b/tests/local/tests.models-2.R @@ -238,7 +238,7 @@ test_that("Nested non-linear models work correctly", { test_that("Non-linear non-looped model predictions work correctly in blocked order", { loss_alt <- transform(loss, row=as.integer(1:nrow(loss)), nr=nrow(loss), test=as.integer(0)) scode_growth <- " - vector growth_test(vector ult, int[] dev, vector theta, vector omega, int[] row, int[] test) { + vector growth_test(vector ult, array[] int dev, vector theta, vector omega, array[] int row, array[] int test) { int N = rows(ult); vector[N] mu; int rows_sorted = 1;