From 7bf0d787f8ffd9c53433488c38c2dc2a70956951 Mon Sep 17 00:00:00 2001 From: Matthew L Fidler Date: Thu, 24 Oct 2024 00:40:01 -0500 Subject: [PATCH 1/5] PopED + babelmixr2 for windows --- R/Doptim.R | 2 +- R/LEDoptim.R | 1 + R/LinMatrixH.R | 5 ++++- R/LinMatrixL.R | 2 +- R/LinMatrixLH.R | 3 +++ R/LinMatrixL_occ.R | 1 + R/RS_opt.R | 2 +- R/a_line_search.R | 1 + R/blockexp.R | 5 ++++- R/blockfinal.R | 1 + R/blockheader.R | 1 + R/blockopt.R | 5 +++-- R/blockother.R | 1 + R/calc_ofv_and_fim.R | 6 ++++-- R/convert_variables.R | 1 + R/create_ofv.R | 2 +- R/d2fimdalpha2.R | 1 + R/dfimdalpha.R | 3 ++- R/downsizing_general_design.R | 1 + R/ed_laplace_ofv.R | 1 + R/ed_mftot.R | 1 + R/evaluate.e.ofv.fim.R | 2 +- R/evaluate.fim.R | 2 +- R/evaluate_design.R | 3 ++- R/evaluate_fim_map.R | 4 ++-- R/evaluate_power.R | 3 ++- R/get_all_params.R | 1 + R/get_cv.R | 3 ++- R/get_fim_size.R | 1 + R/get_unfixed_params.R | 2 +- R/grad_bpop.R | 5 +++-- R/graddetmf.R | 1 + R/graddetmf_ext.R | 2 +- R/gradff.R | 1 + R/gradfg.R | 1 + R/gradfg_occ.R | 1 + R/gradofv_a.R | 2 +- R/gradofv_xt.R | 2 +- R/gradtrmf.R | 2 +- R/helper.R | 3 ++- R/hessian_eta_complex.R | 2 +- R/hesskalpha2.R | 1 + R/ind_estimates.R | 3 ++- R/ind_likelihood.R | 1 + R/m1.R | 1 + R/m2.R | 1 + R/m3.R | 2 +- R/mf3.R | 2 +- R/mf7.R | 2 +- R/mf_all.R | 2 +- R/mfea.R | 2 +- R/mftot.R | 1 + R/ofv_fim.R | 2 +- R/optimize_n.R | 8 +++++--- R/par_and_space_tbl.R | 4 +++- R/pargen.R | 2 +- R/plot_efficiency_of_windows.R | 4 ++-- R/plot_model_prediction.R | 1 + R/poped_optim.R | 2 +- R/poped_optim_1.R | 2 +- R/poped_optim_2.R | 2 +- R/poped_optim_3.R | 2 +- R/poped_optimize.R | 2 +- R/shrinkage.R | 4 ++-- R/start_parallel.R | 11 ++++++++++- R/v.R | 2 +- R/write_iterationfile.R | 2 +- 67 files changed, 106 insertions(+), 51 deletions(-) diff --git a/R/Doptim.R b/R/Doptim.R index 85183879..7122e603 100644 --- a/R/Doptim.R +++ b/R/Doptim.R @@ -73,7 +73,7 @@ Doptim <- function(poped.db,ni, xt, model_switch, x, a, bpopdescr, iter_tot=poped.db$settings$iNumSearchIterationsIfNotLineSearch, iter_max=10, ...){ - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 ## update poped.db with options supplied in function called_args <- match.call() diff --git a/R/LEDoptim.R b/R/LEDoptim.R index c7c23f6c..0e1fc9d2 100644 --- a/R/LEDoptim.R +++ b/R/LEDoptim.R @@ -52,6 +52,7 @@ LEDoptim <- function(poped.db, laplace.fim=FALSE, use_RS=poped.db$settings$bUseRandomSearch, ...){ + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 #+++++++++++++++++++++ D CONTINUOUS VARIABLE OPTIMIZATION FUNCTION # ------------- downsizing of general design diff --git a/R/LinMatrixH.R b/R/LinMatrixH.R index 3b241b84..b533a61b 100644 --- a/R/LinMatrixH.R +++ b/R/LinMatrixH.R @@ -23,13 +23,15 @@ ## Function translated automatically using 'matlab.to.r()' ## Author: Andrew Hooker -LinMatrixH <- function(model_switch,xt_ind,x,a,bpop,b_ind,bocc_ind,poped.db){ +LinMatrixH <- function(model_switch,xt_ind,x,a,bpop,b_ind,bocc_ind, +poped.db){ #----------Model linearization with respect to epsilon. # # size of return is (samples per individual x number of epsilons) # # derivative of model w$r.t. eps eval at e=0 # + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 NumEPS = size(poped.db$parameters$sigma,1) if((NumEPS==0)){ y=0 @@ -61,6 +63,7 @@ LinMatrixH <- function(model_switch,xt_ind,x,a,bpop,b_ind,bocc_ind,poped.db){ #' @keywords internal #' gradf_eps <- function(model_switch,xt_ind,x,a,bpop,b_ind,bocc_ind,num_eps,poped.db){ + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 #----------Model linearization with respect to epsilon. # # size of return is (samples per individual x number of epsilons) diff --git a/R/LinMatrixL.R b/R/LinMatrixL.R index 29eba463..361294cc 100644 --- a/R/LinMatrixL.R +++ b/R/LinMatrixL.R @@ -22,7 +22,7 @@ ## Author: Andrew Hooker LinMatrixL <- function(model_switch,xt_ind,x,a,bpop,b_ind,bocc_ind,poped.db){ - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 if((poped.db$parameters$NumRanEff==0)){ y=0 } else { diff --git a/R/LinMatrixLH.R b/R/LinMatrixLH.R index 27e4e1a5..6bed8d01 100644 --- a/R/LinMatrixLH.R +++ b/R/LinMatrixLH.R @@ -20,6 +20,7 @@ ## Author: Andrew Hooker LinMatrixLH <- function(model_switch,xt_ind,x,a,bpop,b_ind,bocc_ind,NumEPS,poped.db){ + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 #----------Model linearization with respect to epsilon. # # size of return is (samples per individual x (number of sigma x number of omega)) @@ -56,6 +57,8 @@ LinMatrixLH <- function(model_switch,xt_ind,x,a,bpop,b_ind,bocc_ind,NumEPS,poped #Helper function to get the hessian for the AD derivative new_ferror_file <- function(model_switch,deriv_vec,xt_ind,x,a,bpop,bocc_ind,poped.db){ + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 + fg0=feval(poped.db$model$fg_pointer,x,a,bpop,deriv_vec(1:poped.db$parameters$NumRanEff),bocc_ind) #Interaction returnArgs <- feval(poped.db$model$ferror_pointer,model_switch,xt_ind,fg0,deriv_vec(poped.db$parameters$NumRanEff+1:length(deriv_vec)),poped.db) f_error <- returnArgs[[1]] diff --git a/R/LinMatrixL_occ.R b/R/LinMatrixL_occ.R index 722ff497..f4df5ed2 100644 --- a/R/LinMatrixL_occ.R +++ b/R/LinMatrixL_occ.R @@ -18,6 +18,7 @@ ## Author: Andrew Hooker LinMatrixL_occ <- function(model_switch,xt_ind,x,a,bpop,b_ind,bocc_ind,iCurrentOcc,poped.db){ + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 # # size: (samples per individual x number of iovs) # diff --git a/R/RS_opt.R b/R/RS_opt.R index 703bb182..570de71e 100644 --- a/R/RS_opt.R +++ b/R/RS_opt.R @@ -73,7 +73,7 @@ RS_opt <- function(poped.db, out_file=NULL, compute_inv=TRUE, ...){ - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 # Only get inputs that are needed, not double inputs # needed inputs to function: get first then run function diff --git a/R/a_line_search.R b/R/a_line_search.R index c7a37ce6..37411b3f 100644 --- a/R/a_line_search.R +++ b/R/a_line_search.R @@ -48,6 +48,7 @@ a_line_search <- function(poped.db, opt_samps=poped.db$settings$optsw[1], opt_inds=poped.db$settings$optsw[5], ls_step_size=poped.db$settings$ls_step_size){ + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 optsw <- cbind(opt_samps,opt_xt,opt_x,opt_a,opt_inds) # diff --git a/R/blockexp.R b/R/blockexp.R index 4bb6a248..d98174b8 100644 --- a/R/blockexp.R +++ b/R/blockexp.R @@ -25,7 +25,8 @@ blockexp <- function(fn,poped.db,e_flag=FALSE, opt_xt=poped.db$settings$optsw[2],opt_a=poped.db$settings$optsw[4],opt_x=poped.db$settings$optsw[4], opt_samps=poped.db$settings$optsw[1],opt_inds=poped.db$settings$optsw[5]){ - + + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 fprintf(fn,'==============================================================================\n') fprintf(fn,'Model description : %s \n',poped.db$settings$modtit) fprintf(fn,'\n') @@ -155,6 +156,8 @@ blockexp <- function(fn,poped.db,e_flag=FALSE, } print_params <- function (params,name_str, fn, poped.db, param_sqrt=FALSE,head_txt=NULL,matrix_elements=F,e_flag=FALSE) { + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 + if(is.null(head_txt)) head_txt <- "Parameter Values" uncer_txt <- "" if(e_flag) uncer_txt <- " (Uncertainty Distribution)" diff --git a/R/blockfinal.R b/R/blockfinal.R index 5e67eb65..ee0cbac4 100644 --- a/R/blockfinal.R +++ b/R/blockfinal.R @@ -31,6 +31,7 @@ blockfinal <- function(fn,fmf,dmf,groupsize,ni,xt,x,a,model_switch,bpop,d,docc,s compute_inv=TRUE,out_file=NULL,trflag=TRUE,footer_flag=TRUE, run_time = NULL, ...){ + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 time_value <- NULL if(!trflag) return(invisible() ) diff --git a/R/blockheader.R b/R/blockheader.R index b06d473d..80f4f2b5 100644 --- a/R/blockheader.R +++ b/R/blockheader.R @@ -37,6 +37,7 @@ blockheader <- function(poped.db,name="Default",iter=NULL, header_flag=TRUE, ...) { + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 # BLOCKHEADER_2 # filename to write to is # poped.db$settings$strOutputFilePath,poped.db$settings$strOutputFileName,NAME,iter,poped.db$settings$strOutputFileExtension diff --git a/R/blockopt.R b/R/blockopt.R index 79338488..a6a7ff46 100644 --- a/R/blockopt.R +++ b/R/blockopt.R @@ -20,7 +20,8 @@ ## Author: Andrew Hooker blockopt <- function(fn,poped.db,opt_method=""){ - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 + if(any(opt_method==c("RS","SG","DO"))){ fprintf(fn,'==============================================================================\n') fprintf(fn,'Optimization Settings\n\n') @@ -50,4 +51,4 @@ blockopt <- function(fn,poped.db,opt_method=""){ fprintf(fn,"\n") } return( ) -} \ No newline at end of file +} diff --git a/R/blockother.R b/R/blockother.R index 4d07b831..2fde0ac1 100644 --- a/R/blockother.R +++ b/R/blockother.R @@ -2,6 +2,7 @@ ## Author: Andrew Hooker blockother <- function(fn,poped.db,d_switch=poped.db$settings$d_switch){ + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 fprintf(fn,'==============================================================================\n') fprintf(fn,'Criterion Specification\n\n') diff --git a/R/calc_ofv_and_fim.R b/R/calc_ofv_and_fim.R index 47f2be76..b2ae8ede 100644 --- a/R/calc_ofv_and_fim.R +++ b/R/calc_ofv_and_fim.R @@ -47,7 +47,9 @@ calc_ofv_and_fim <- function (poped.db, ofv_fun = poped.db$settings$ofv_fun, evaluate_fim = TRUE, ...) { - + + + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 ## compute the OFV if((ofv==0)){ if(d_switch){ @@ -177,4 +179,4 @@ calc_ofv_and_fim <- function (poped.db, fim <- fmf } return(list(ofv=ofv,fim=fim)) -} \ No newline at end of file +} diff --git a/R/convert_variables.R b/R/convert_variables.R index b5f83e93..8d79fdbe 100644 --- a/R/convert_variables.R +++ b/R/convert_variables.R @@ -16,6 +16,7 @@ ## Author: Andrew Hooker convert_variables <- function(poped.db){ + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 design = poped.db$design design_space = poped.db$design_space diff --git a/R/create_ofv.R b/R/create_ofv.R index 03c2cf5b..f49e2f02 100644 --- a/R/create_ofv.R +++ b/R/create_ofv.R @@ -15,7 +15,7 @@ create_ofv <- function(poped.db, ofv_fun = poped.db$settings$ofv_fun, transform_parameters=T, ...){ - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 #------------ update poped.db with options supplied in function called_args <- match.call() default_args <- formals() diff --git a/R/d2fimdalpha2.R b/R/d2fimdalpha2.R index 765bb5c0..ba9b7abb 100644 --- a/R/d2fimdalpha2.R +++ b/R/d2fimdalpha2.R @@ -1,4 +1,5 @@ d2fimdalpha2 <- function(alpha, model_switch,groupsize,ni,xtoptn,xoptn,aoptn,bpopdescr,ddescr,covd,sigma,docc,poped.db,ha){ + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 bpop=bpopdescr[,2,drop=F] bpop[bpopdescr[,1,drop=F]!=0]=alpha[1:sum(bpopdescr[,1,drop=F]!=0)] d=ddescr[,2,drop=F] diff --git a/R/dfimdalpha.R b/R/dfimdalpha.R index ee072bfc..b574ec11 100644 --- a/R/dfimdalpha.R +++ b/R/dfimdalpha.R @@ -1,5 +1,6 @@ dfimdalpha <- function(alpha, model_switch,groupsize,ni,xtoptn,xoptn,aoptn,bpopdescr,ddescr,covd,sigma,docc,poped.db,ha){ + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 bpop=bpopdescr[,2,drop=F] bpop[bpopdescr[,1,drop=F]!=0]=alpha[1:sum(bpopdescr[,1,drop=F]!=0)] d=ddescr[,2,drop=F] @@ -33,4 +34,4 @@ dfimdalpha <- function(alpha, model_switch,groupsize,ni,xtoptn,xoptn,aoptn,bpopd } return(list( grad= grad,fim =fim )) } - \ No newline at end of file + diff --git a/R/downsizing_general_design.R b/R/downsizing_general_design.R index 0bd92d95..a790965f 100644 --- a/R/downsizing_general_design.R +++ b/R/downsizing_general_design.R @@ -24,6 +24,7 @@ downsizing_general_design <- function(poped.db){ + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 # ------------- downsizing of general design ni=poped.db$design$ni[1:poped.db$design$m,,drop=F] diff --git a/R/ed_laplace_ofv.R b/R/ed_laplace_ofv.R index c5171701..031c8c84 100644 --- a/R/ed_laplace_ofv.R +++ b/R/ed_laplace_ofv.R @@ -492,6 +492,7 @@ calc_k <- function(alpha, model_switch,groupsize,ni,xtoptn,xoptn,aoptn,bpopdescr if(return_gradient){ comp_grad_1 <- function(alpha, model_switch, groupsize, ni, xtoptn, xoptn, aoptn, bpopdescr, ddescr, covd, sigma, docc, poped.db, grad_p) { + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 returnArgs <- dfimdalpha(alpha,model_switch,groupsize,ni,xtoptn,xoptn,aoptn,bpopdescr,ddescr,covd,sigma,docc,poped.db,1e-6) d_fim <- returnArgs[[1]] fim <- returnArgs[[2]] diff --git a/R/ed_mftot.R b/R/ed_mftot.R index 6f32fa66..49d8faf6 100644 --- a/R/ed_mftot.R +++ b/R/ed_mftot.R @@ -27,6 +27,7 @@ ed_mftot <- function(model_switch,groupsize,ni,xtoptn,xoptn,aoptn,bpopdescr,ddescr,covd,sigma,docc,poped.db, calc_fim=TRUE,...){ + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 #+++++++++++++++++++++++ ED OFV(MF) VALUE s=0 s1=0 diff --git a/R/evaluate.e.ofv.fim.R b/R/evaluate.e.ofv.fim.R index 705ddb39..0eab613d 100644 --- a/R/evaluate.e.ofv.fim.R +++ b/R/evaluate.e.ofv.fim.R @@ -45,7 +45,7 @@ evaluate.e.ofv.fim <- function(poped.db, use_laplace=poped.db$settings$iEDCalculationType, laplace.fim=FALSE, ...){ - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 ## update poped.db with options supplied in function called_args <- match.call() default_args <- formals() diff --git a/R/evaluate.fim.R b/R/evaluate.fim.R index 4b871fde..e2ade131 100644 --- a/R/evaluate.fim.R +++ b/R/evaluate.fim.R @@ -71,7 +71,7 @@ evaluate.fim <- function(poped.db, groupsize=NULL, deriv.type = NULL, ...){ - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 if(is.null(bpop.val)) bpop.val <- poped.db$parameters$param.pt.val$bpop if(is.null(d_full)) d_full <- poped.db$parameters$param.pt.val$d diff --git a/R/evaluate_design.R b/R/evaluate_design.R index da0826b5..d30fcf17 100644 --- a/R/evaluate_design.R +++ b/R/evaluate_design.R @@ -12,6 +12,7 @@ #' @family evaluate_design evaluate_design <- function(poped.db, ...) { + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 out <- calc_ofv_and_fim(poped.db,...) if(is.null(out$fim)){ out$rse <- NULL @@ -23,4 +24,4 @@ evaluate_design <- function(poped.db, ...) { colnames(out$fim) <- names(out$rse) } return(out) -} \ No newline at end of file +} diff --git a/R/evaluate_fim_map.R b/R/evaluate_fim_map.R index 4bbdc13f..2f1bbc95 100644 --- a/R/evaluate_fim_map.R +++ b/R/evaluate_fim_map.R @@ -37,7 +37,7 @@ evaluate_fim_map <- function(poped.db, num_sim_ids = 1000, use_purrr = FALSE, shrink_mat=F){ - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 # if (poped.db$design$m > 1) { # warning("Shrinkage should only be computed for a single arm, please adjust your script accordingly.") # } @@ -176,4 +176,4 @@ evaluate_fim_map <- function(poped.db, return(out_df) -} \ No newline at end of file +} diff --git a/R/evaluate_power.R b/R/evaluate_power.R index 2925f0d9..0dabd120 100644 --- a/R/evaluate_power.R +++ b/R/evaluate_power.R @@ -38,6 +38,7 @@ evaluate_power <- function(poped.db, bpop_idx, h0=0, alpha=0.05, power=0.80, twoSided=TRUE, find_min_n=TRUE, fim=NULL, out=NULL,...) { + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 # If two-sided then halve the alpha if (twoSided == TRUE) alpha = alpha/2 @@ -85,4 +86,4 @@ evaluate_power <- function(poped.db, bpop_idx, h0=0, alpha=0.05, power=0.80, two } return(out) -} \ No newline at end of file +} diff --git a/R/get_all_params.R b/R/get_all_params.R index 6880ba2c..e7ce86e4 100644 --- a/R/get_all_params.R +++ b/R/get_all_params.R @@ -20,6 +20,7 @@ ## Author: Andrew Hooker get_all_params <- function(poped.db){ + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 #Return all params (in a vector all) with the specified order above #bpop = poped.db$parameters$bpop[,2,drop=F] diff --git a/R/get_cv.R b/R/get_cv.R index 13e0162c..3e6c344a 100644 --- a/R/get_cv.R +++ b/R/get_cv.R @@ -1,4 +1,5 @@ get_cv <- function(param_vars,poped.db){ + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 #Return the RSE,CV of parameters ## Author: Andrew Hooker params_all <- get_all_params(poped.db)[[8]] @@ -62,7 +63,7 @@ get_rse <- function (fim, poped.db, prior_fim = poped.db$settings$prior_fim, #pseudo_on_fail = FALSE, ...) { - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 ## update poped.db with options supplied in function called_args <- match.call() default_args <- formals() diff --git a/R/get_fim_size.R b/R/get_fim_size.R index 856b7e56..1f6c856e 100644 --- a/R/get_fim_size.R +++ b/R/get_fim_size.R @@ -2,6 +2,7 @@ ## Author: Andrew Hooker get_fim_size <- function(poped.db){ + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 #Returns the size of FIM, i$e. col or row size numnotfixed_bpop = sum(poped.db$parameters$notfixed_bpop) numnotfixed_d = sum(poped.db$parameters$notfixed_d) diff --git a/R/get_unfixed_params.R b/R/get_unfixed_params.R index 813b40df..a914450b 100644 --- a/R/get_unfixed_params.R +++ b/R/get_unfixed_params.R @@ -15,7 +15,7 @@ #' @export #' @keywords internal get_unfixed_params <- function(poped.db,params=NULL){ - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 if(is.null(params)){ bpop = poped.db$parameters$bpop[,2,drop=F] d = poped.db$parameters$d[,2,drop=F] diff --git a/R/grad_bpop.R b/R/grad_bpop.R index 7999b340..61ba636f 100644 --- a/R/grad_bpop.R +++ b/R/grad_bpop.R @@ -2,6 +2,7 @@ ## Author: Andrew Hooker grad_bpop <- function(func,select_par,nout,model_switch,xt_ind,x,a,bpop,b_ind,bocc_ind,d,sigma,docc,poped.db,subset=poped.db$parameters$notfixed_bpop, offdiag = FALSE){ + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 #----------Model linearization with respect to pop parameters # # use helper function to check for/include EBEs @@ -13,7 +14,7 @@ grad_bpop <- function(func,select_par,nout,model_switch,xt_ind,x,a,bpop,b_ind,bo # helper for m2 helper_v_EBE <- function(model_switch,xt_ind,x,a,bpop,b_ind,bocc_ind,d,sigma,docc,poped.db) { - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 if((poped.db$settings$bCalculateEBE)){ #zeros(size(b_ind)[1],size(b_ind)[2]) b_ind_x = ind_estimates(poped.db$mean_data,bpop,d,sigma,t(b_ind),(poped.db$settings$iApproximationMethod==2),FALSE,model_switch,xt_ind,x,a,b_ind,bocc_ind,poped.db) @@ -28,7 +29,7 @@ helper_v_EBE <- function(model_switch,xt_ind,x,a,bpop,b_ind,bocc_ind,d,sigma,doc # helper for m1 helper_LinMatrix <- function(model_switch,xt_ind,x,a,bpop,b_ind,bocc_ind,d,sigma,docc,poped.db) { - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 epsi0 = zeros(1,length(poped.db$parameters$notfixed_sigma)) # create linearized model diff --git a/R/graddetmf.R b/R/graddetmf.R index ee1fe9e6..fcca6b78 100644 --- a/R/graddetmf.R +++ b/R/graddetmf.R @@ -3,6 +3,7 @@ graddetmf <- function(model_switch,aX,groupsize,ni,xt,x,a,bpop,d,sigma,docc,poped.db,lndet=FALSE,gradxt=FALSE){ + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 n = get_fim_size(poped.db) m=size(ni,1) if (gradxt == FALSE) { diff --git a/R/graddetmf_ext.R b/R/graddetmf_ext.R index b8e8190e..76abdaba 100644 --- a/R/graddetmf_ext.R +++ b/R/graddetmf_ext.R @@ -2,7 +2,7 @@ ## Author: Andrew Hooker graddetmf_ext <- function(model_switch,aX,groupsize,ni,xt,x,a,bpop,d,sigma,docc,poped.db,lndet=FALSE,gradxt=FALSE){ - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 n = get_fim_size(poped.db) m=size(ni,1) if (gradxt==FALSE) { diff --git a/R/gradff.R b/R/gradff.R index 18952a28..260f80be 100644 --- a/R/gradff.R +++ b/R/gradff.R @@ -9,6 +9,7 @@ gradff <- function(model_switch,xt_ind,x,a,bpop,b_ind,bocc_ind,poped.db){ # derivative of model w.r.t. g eval at b=b_ind # # + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 fg0 = feval(poped.db$model$fg_pointer,x,a,bpop,b_ind,bocc_ind) epsi0 = zeros(1,length(poped.db$parameters$notfixed_sigma)) diff --git a/R/gradfg.R b/R/gradfg.R index da5b693c..865d9414 100644 --- a/R/gradfg.R +++ b/R/gradfg.R @@ -2,6 +2,7 @@ ## Author: Andrew Hooker gradfg <- function(x,a,bpop,b_ind,bocc_ind,poped.db){ + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 # # # size: (number of g's x number of random effects) diff --git a/R/gradfg_occ.R b/R/gradfg_occ.R index d57891be..7d2a7a79 100644 --- a/R/gradfg_occ.R +++ b/R/gradfg_occ.R @@ -5,6 +5,7 @@ gradfg_occ <- function(x,a,bpop,b_ind,bocc_ind,currentOcc,poped.db){ # # deriv of g's w$r.t. bocc's eval at b_ind, bocc_ind at occ currentOcc # + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 dfg_db0 = grad_all(poped.db$model$fg_pointer,5,poped.db$parameters$ng,x,a,bpop,b_ind,bocc_ind,poped.db,currentOcc = currentOcc,noPopED = TRUE) return(dfg_db0) } diff --git a/R/gradofv_a.R b/R/gradofv_a.R index 42d7ae1a..d7353d88 100644 --- a/R/gradofv_a.R +++ b/R/gradofv_a.R @@ -2,7 +2,7 @@ ## Author: Andrew Hooker gradofv_a <- function(model_switch,aa,groupsize,ni,xt,x,a,bpop,d,sigma,docc,poped.db){ - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 #Input: the prior FIM or (empty) and all the other things to calculate the #grad with for a #Return a vector that is the gradient diff --git a/R/gradofv_xt.R b/R/gradofv_xt.R index 2b3f603e..4821a063 100644 --- a/R/gradofv_xt.R +++ b/R/gradofv_xt.R @@ -2,7 +2,7 @@ ## Author: Andrew Hooker gradofv_xt <- function(model_switch,axt,groupsize,ni,xt,x,a,bpop,d,sigma,docc,poped.db){ - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 #Input: the prior FIM or (empty) and all the other things to calculate the #grad with #Return a vector that is the gradient and the global structure diff --git a/R/gradtrmf.R b/R/gradtrmf.R index 53db2470..6568d72c 100644 --- a/R/gradtrmf.R +++ b/R/gradtrmf.R @@ -3,7 +3,7 @@ gradtrmf <- function(model_switch,aX,groupsize,ni,xt,x,a,bpop,d,sigma,docc,poped # Looks at the gradient of tr(FIM^-1) with respect to time (xt) or covariate (a). # problems can arise when a or xt goes negative. So only do forward # differencing. - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 m=size(ni,1) if (gradxt == FALSE) { gdmf=matrix(1,m,size(a,2)) diff --git a/R/helper.R b/R/helper.R index e8aa2c01..280a6a1c 100644 --- a/R/helper.R +++ b/R/helper.R @@ -96,6 +96,7 @@ tryCatch.W.E <- function(expr){ get_fim_size <- function(poped.db) { + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 numnotfixed_bpop = sum(poped.db$parameters$notfixed_bpop) numnotfixed_d = sum(poped.db$parameters$notfixed_d) numnotfixed_covd = sum(poped.db$parameters$notfixed_covd) @@ -109,4 +110,4 @@ get_fim_size <- function(poped.db) { numnotfixed_covdocc+numnotfixed_sigma+numnotfixed_covsigma fim_size <- n_fixed_eff+n_rand_eff return(fim_size) -} \ No newline at end of file +} diff --git a/R/hessian_eta_complex.R b/R/hessian_eta_complex.R index abd98194..629f54fc 100644 --- a/R/hessian_eta_complex.R +++ b/R/hessian_eta_complex.R @@ -1,6 +1,6 @@ #Hessian over eta, evaluated at eta_hat => laplace approximation possible hessian_eta_complex <- function(model_switch,xt_ind,x,a,bpop,b_ind,bocc_ind,poped.db,return_gradient=F){ - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 bAutomatic = FALSE epsi0 = zeros(1,length(poped.db$parameters$notfixed_sigma)) n=length(b_ind) diff --git a/R/hesskalpha2.R b/R/hesskalpha2.R index 7df387e2..c4cd1719 100644 --- a/R/hesskalpha2.R +++ b/R/hesskalpha2.R @@ -1,5 +1,6 @@ hesskalpha2 <- function(alpha, model_switch,groupsize,ni,xtoptn,xoptn,aoptn,bpopdescr,ddescr,covd,sigma,docc,poped.db,ha,Engine){ + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 #D2KALPHA2 calculates the hessian of k with respect to alpha # Detailed explanation goes here returnArgs <- log_prior_pdf(alpha,bpopdescr,ddescr,return_gradient=T,return_hessian=T) diff --git a/R/ind_estimates.R b/R/ind_estimates.R index 3e85e20d..49b84cdf 100644 --- a/R/ind_estimates.R +++ b/R/ind_estimates.R @@ -1,7 +1,7 @@ #Get the emperical bayes estimates for one individual #Written for PopED by JN ind_estimates <- function(data,bpop,d,sigma,start_bind,bInter,bUDDLike,model_switch,xt_ind,x,a,b_ind,bocc_ind,poped.db){ - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 b_i = t(start_bind) c1 = length(t(start_bind))/2*log(2*pi) c2 = 1/2*log(det(d)) @@ -33,6 +33,7 @@ ind_estimates <- function(data,bpop,d,sigma,start_bind,bInter,bUDDLike,model_swi #This is the function that should be minimized, w$r.t eta min_function <- function(data,bpop,d,sigma,bInter,bUDDLike,model_switch,xt_ind,x,a,bocc_ind,poped.db,c1,c2,c3,lC,det_res_var,b_ind,return_deriv=F){ + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 bAnalytic = FALSE li = ind_likelihood(data,bpop,d,sigma,bInter,bUDDLike,model_switch,xt_ind,x,a,bocc_ind,poped.db,lC,det_res_var,b_ind) #Individual log likelihood ret =c1+c2+1/2*t(b_ind)*c3*b_ind-li diff --git a/R/ind_likelihood.R b/R/ind_likelihood.R index 036f72e8..b2d1bae7 100644 --- a/R/ind_likelihood.R +++ b/R/ind_likelihood.R @@ -23,6 +23,7 @@ # log(det(RR))+ (res'/RR)*res; ind_likelihood <- function(data,bpop,d,sigma,bInter,bUDDLike,model_switch,xt_ind,x,a,bocc_ind,poped.db,lC,det_res_var,b_ind){ + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 # % from davidian and giltinan p 173 if((!bUDDLike)){ #browser() diff --git a/R/m1.R b/R/m1.R index 80c1e588..35437b9a 100644 --- a/R/m1.R +++ b/R/m1.R @@ -2,6 +2,7 @@ ## Author: Andrew Hooker m1 <- function(model_switch,xt_ind,x,a,bpop,b_ind,bocc_ind,d,sigma,poped.db){ + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 # # function computes the derivative of the # linerarized model function w$r.t. bpop diff --git a/R/m2.R b/R/m2.R index d4c4e478..cf95b9f4 100644 --- a/R/m2.R +++ b/R/m2.R @@ -2,6 +2,7 @@ ## Author: Andrew Hooker m2 <- function(model_switch,xt_ind,x,a,bpop,b_ind,bocc_ind,d,sigma,docc,poped.db){ + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 # M2 derivative of the vectorized variance w$r.t. bpops # # the output is a matrix with dimensions (ind_samps^2 X nbpop) diff --git a/R/m3.R b/R/m3.R index 989da56b..4291969d 100644 --- a/R/m3.R +++ b/R/m3.R @@ -4,7 +4,7 @@ m3 <- function(model_switch,xt_ind,x,a,bpop,b_ind,bocc_ind,d,sigma,docc,bUseVarSigmaDerivative,poped.db){ # # size: (samps per subject^2 x (number of random effects + number of occasion variances + number of sigmas)) - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 dv_dd = NULL dv_covd = NULL dv_ddocc = NULL diff --git a/R/mf3.R b/R/mf3.R index cc589cca..992643ed 100644 --- a/R/mf3.R +++ b/R/mf3.R @@ -22,7 +22,7 @@ ## Author: Andrew Hooker mf3 <- function(model_switch,xt,x,a,bpop,d,sigma,docc,poped.db){ - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 numnotfixed_bpop = sum(poped.db$parameters$notfixed_bpop) numnotfixed_d = sum(poped.db$parameters$notfixed_d) numnotfixed_covd = sum(poped.db$parameters$notfixed_covd) diff --git a/R/mf7.R b/R/mf7.R index e7aaa6d5..d49a47ce 100644 --- a/R/mf7.R +++ b/R/mf7.R @@ -19,7 +19,7 @@ ## Author: Andrew Hooker mf7 <- function(model_switch,xt_ind,x,a,bpop,d,sigma,docc,poped.db){ - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 #This calculation of FIM divides the calculation up into one calculation #per model switch diff --git a/R/mf_all.R b/R/mf_all.R index 369b6c7d..f0007adf 100644 --- a/R/mf_all.R +++ b/R/mf_all.R @@ -3,7 +3,7 @@ ## Author: Andrew Hooker mf_all <- function(model_switch,xt_ind,x,a,bpop,d,sigma,docc,poped.db){ - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 returnArgs <- switch(poped.db$settings$iFIMCalculationType+1, mf3(model_switch,xt_ind,x,a,bpop,d,sigma,docc,poped.db), #Default (with no assumption that bpop and b are uncorrelated) mf3(model_switch,xt_ind,x,a,bpop,d,sigma,docc,poped.db), #Reduced FIM diff --git a/R/mfea.R b/R/mfea.R index d019f424..dedda2b8 100644 --- a/R/mfea.R +++ b/R/mfea.R @@ -36,7 +36,7 @@ mfea <- function(poped.db,model_switch,ni,xt,x,a,bpopdescr,ddescr,maxxt,minxt,ma #opt_inds=poped.db$settings$optsw[5], trflag=T, ...){ - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 if((poped.db$settings$EACriteria!=1)){ stop(sprintf('The criteria that can be used is Modified Fedorov Exchange Algorithm (EACriteria = 1)')) } diff --git a/R/mftot.R b/R/mftot.R index 0f63c73b..1da3690f 100644 --- a/R/mftot.R +++ b/R/mftot.R @@ -30,6 +30,7 @@ ## Author: Andrew Hooker mftot <- function(model_switch,groupsize,ni,xt,x,a,bpop,d,sigma,docc,poped.db,...){ + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 m=size(ni,1) s=0 for(i in 1:m){ diff --git a/R/ofv_fim.R b/R/ofv_fim.R index 5e27d4e7..9b31e7c0 100644 --- a/R/ofv_fim.R +++ b/R/ofv_fim.R @@ -37,7 +37,7 @@ ofv_fim <- function(fmf,poped.db, ds_index=poped.db$parameters$ds_index, use_log = TRUE, ...){ - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 #Input: the FIM #Return the single value that should be maximized diff --git a/R/optimize_n.R b/R/optimize_n.R index 403b0bcf..bb8ae53a 100644 --- a/R/optimize_n.R +++ b/R/optimize_n.R @@ -9,6 +9,7 @@ #' @keywords internal #' extract_norm_group_fim <- function (poped.db,...) { + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 num_groups <- poped.db$design$m fim_group <- list() for(i in 1:num_groups){ @@ -62,7 +63,7 @@ optimize_groupsize <- props = c(poped.db$design$groupsize/sum(poped.db$design$groupsize)), trace=1, ...){ - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 # need to fix: # limits on the proportions to account for max and min values of N in each group # return actual values. @@ -115,6 +116,7 @@ optimize_groupsize <- norm_group_fim <- extract_norm_group_fim(poped.db) ofv_fun <- function(props,norm_group_fim,n_tot, poped.db, ...){ + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 fim_tmp <- combine_norm_group_fim(norm_group_fim,props*n_tot) ofv_fim(fim_tmp,poped.db,...) } @@ -231,7 +233,7 @@ optimize_n_rse <- function(poped.db, allowed_values = seq(poped.db$design$m, sum(poped.db$design$groupsize)*5, by=poped.db$design$m)){ - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 n_per_group = poped.db$design$groupsize n_tot <- sum(n_per_group) props = c(n_per_group/n_tot) @@ -275,7 +277,7 @@ optimize_n_eff <- function(poped.db, ofv_ref, norm_group_fim = NULL, ...){ - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 n_per_group = poped.db$design$groupsize n_tot <- sum(n_per_group) props = c(n_per_group/n_tot) diff --git a/R/par_and_space_tbl.R b/R/par_and_space_tbl.R index d529ddc6..fa609c64 100644 --- a/R/par_and_space_tbl.R +++ b/R/par_and_space_tbl.R @@ -1,4 +1,5 @@ par_and_space_tbl <- function(poped.db) { + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 df <- NULL allowed_values <- allowed_values_2 <- cont <- lower <- upper <- par <- NULL @@ -264,7 +265,8 @@ get_par_and_space_optim <- function(poped.db, cont_cat = "both", warn_when_none=TRUE) { - + + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 type <- index <- fixed <- cont <- par <- lower <- upper <- NULL #----------- checks diff --git a/R/pargen.R b/R/pargen.R index bde9b221..2e7d8f6f 100644 --- a/R/pargen.R +++ b/R/pargen.R @@ -29,7 +29,7 @@ ## Author: Andrew Hooker pargen <- function(par,user_dist_pointer,sample_size,bLHS,sample_number,poped.db){ - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 nvar=size(par,1) ret=zeros(sample_size,nvar) diff --git a/R/plot_efficiency_of_windows.R b/R/plot_efficiency_of_windows.R index 64dc21fd..9e91d39c 100644 --- a/R/plot_efficiency_of_windows.R +++ b/R/plot_efficiency_of_windows.R @@ -69,7 +69,7 @@ plot_efficiency_of_windows <- function(poped.db, #mrgsolve_model=NULL, seed=round(runif(1,0,10000000)), ...){ - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 if(!is.null(seed)) set.seed(seed) design = poped.db$design @@ -394,4 +394,4 @@ plot_efficiency_of_windows <- function(poped.db, p <- p+ylab("Value in %")+xlab("Simulation number of design sampled from defined windows") #p <- p + stat_summary(fun.y = "mean", geom="hline") return(p) -} \ No newline at end of file +} diff --git a/R/plot_model_prediction.R b/R/plot_model_prediction.R index 68c0c589..8a89f90a 100644 --- a/R/plot_model_prediction.R +++ b/R/plot_model_prediction.R @@ -93,6 +93,7 @@ plot_model_prediction <- function(poped.db, PI_alpha=0.3, #PI_fill="blue", ...){ + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 PI_u <- PI_l <- NULL df <- model_prediction(poped.db, #models_to_use, diff --git a/R/poped_optim.R b/R/poped_optim.R index d6e15aff..6fe3eee0 100644 --- a/R/poped_optim.R +++ b/R/poped_optim.R @@ -105,7 +105,7 @@ poped_optim <- function(poped.db, allow_replicates_xt=TRUE, allow_replicates_a=TRUE, ...){ - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 #------------ update argument list with called arguments diff --git a/R/poped_optim_1.R b/R/poped_optim_1.R index 217bd877..f42a555d 100644 --- a/R/poped_optim_1.R +++ b/R/poped_optim_1.R @@ -92,7 +92,7 @@ poped_optim_1 <- function(poped.db, ofv_fun = poped.db$settings$ofv_fun, maximize=T, ...){ - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 #------------ update poped.db with options supplied in function called_args <- match.call() default_args <- formals() diff --git a/R/poped_optim_2.R b/R/poped_optim_2.R index e77a8422..62361965 100644 --- a/R/poped_optim_2.R +++ b/R/poped_optim_2.R @@ -94,7 +94,7 @@ poped_optim_2 <- function(poped.db, maximize=T, transform_parameters = F, ...){ - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 #------------ update poped.db with options supplied in function called_args <- match.call() default_args <- formals() diff --git a/R/poped_optim_3.R b/R/poped_optim_3.R index 3dee7851..eff507fc 100644 --- a/R/poped_optim_3.R +++ b/R/poped_optim_3.R @@ -96,7 +96,7 @@ poped_optim_3 <- function(poped.db, allow_replicates_xt=TRUE, allow_replicates_a=TRUE, ...){ - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 #------------ update poped.db with options supplied in function called_args <- match.call() default_args <- formals() diff --git a/R/poped_optimize.R b/R/poped_optimize.R index 7399eef7..e93517af 100644 --- a/R/poped_optimize.R +++ b/R/poped_optimize.R @@ -67,7 +67,7 @@ poped_optimize <- function(poped.db, bLHS=poped.db$settings$bLHS, use_laplace=poped.db$settings$iEDCalculationType, ...){ - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 ## update poped.db with options supplied in function called_args <- match.call() default_args <- formals() diff --git a/R/shrinkage.R b/R/shrinkage.R index 0eb4e86b..e3b447bd 100644 --- a/R/shrinkage.R +++ b/R/shrinkage.R @@ -31,7 +31,7 @@ shrinkage <- function(poped.db, use_mc = FALSE, num_sim_ids = 1000, use_purrr = FALSE){ - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 # if (poped.db$design$m > 1) { # warning("Shrinkage should only be computed for a single arm, please adjust your script accordingly.") # } @@ -200,4 +200,4 @@ shrinkage <- function(poped.db, return(out_df) -} \ No newline at end of file +} diff --git a/R/start_parallel.R b/R/start_parallel.R index ca7e5d73..884068de 100644 --- a/R/start_parallel.R +++ b/R/start_parallel.R @@ -1,3 +1,5 @@ +start_parallel_env <- new.env(parent=emptyenv()) +start_parallel_env$babelmixr2 <- NULL #' Start parallel computational processes #' #' This tool chooses the type of parallelization process to use based on the @@ -87,6 +89,13 @@ start_parallel <- function(parallel=TRUE, } parallel::clusterCall(cl, mrgsolve::loadso, x=mrgsolve_model) } + if (!is.null(start_parallel_env$babelmixr2)) { + if (!requireNamespace("babelmixr2", quietly=TRUE)) { + stop("babelmixr2 package needed for this function to work. Please install it.", + call.=FALSE) + } + parallel::clusterCall(cl, babelmixr2::.popedCluster, start_parallel_env$babelmixr2) + } # if(!is.null(cpp_files)){ # for(i in cpp_files){ # parallel::clusterCall(cl, @@ -108,4 +117,4 @@ start_parallel <- function(parallel=TRUE, } return(parallel) -} \ No newline at end of file +} diff --git a/R/v.R b/R/v.R index 7b0b89b0..f399085d 100644 --- a/R/v.R +++ b/R/v.R @@ -3,7 +3,7 @@ v <- function(model_switch,xt_ind,x,a,bpop,b_ind,bocc_ind,d,sigma,docc,poped.db){ # number of samples X number of samples (per individual) - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 bUseAutoCorrelation = !isempty(poped.db$model$auto_pointer) bUseFullSigmaCorrelation = FALSE diff --git a/R/write_iterationfile.R b/R/write_iterationfile.R index acbc3196..ad879cee 100644 --- a/R/write_iterationfile.R +++ b/R/write_iterationfile.R @@ -3,7 +3,7 @@ ## Author: Andrew Hooker write_iterationfile <- function(strSearch,iteration,xt,a,x,ni,groupsize,fim,ofv,poped.db){ - + start_parallel_env$babelmixr2 <- poped.db$babelmixr2 ## #Make sure that this doesn't crash the search ## try ## fn = file(poped.db$settings$strIterationFileName, 'w') From c8be2997883894977805673611a7ce74888a84df Mon Sep 17 00:00:00 2001 From: Matthew L Fidler Date: Thu, 24 Oct 2024 00:54:03 -0500 Subject: [PATCH 2/5] Add babelmixr2 to suggests --- DESCRIPTION | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/DESCRIPTION b/DESCRIPTION index f0f30702..8a1fb581 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -32,7 +32,8 @@ Suggests: gridExtra, covr, devtools, - mrgsolve + mrgsolve, + babelmixr2 Authors@R: c( person("Andrew C.","Hooker", email="andrew.hooker@farmaci.uu.se", role=c("aut","cre","trl","cph"), From bf0584cf440832a37cdaf10437ca94efc8865e33 Mon Sep 17 00:00:00 2001 From: Matthew L Fidler Date: Thu, 24 Oct 2024 00:56:31 -0500 Subject: [PATCH 3/5] Add to news --- NEWS.md | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/NEWS.md b/NEWS.md index 7a1b6557..36e0cc2d 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,3 +1,7 @@ +# PopED development verson + +* Make parallelization work with `babelmixr2` models on windows (#79) + # PopED 0.7.0 * `create.poped.database()` now uses a better method of identifying the total number of parameters of each type (bpop, d, sigma, etc.) in a user defined model parameter function (the `ff_fun` argument in `create.poped.database()`) (#73). From 4b136a024736ed46cdd34c1da82bd503473bfcb0 Mon Sep 17 00:00:00 2001 From: Matthew L Fidler Date: Thu, 24 Oct 2024 01:02:40 -0500 Subject: [PATCH 4/5] add babelmixr2 dev for check --- .github/workflows/R-CMD-check.yaml | 18 +++++++++++++++++- .github/workflows/test-coverage.yaml | 19 ++++++++++++++++++- 2 files changed, 35 insertions(+), 2 deletions(-) diff --git a/.github/workflows/R-CMD-check.yaml b/.github/workflows/R-CMD-check.yaml index d46a6175..93515f18 100644 --- a/.github/workflows/R-CMD-check.yaml +++ b/.github/workflows/R-CMD-check.yaml @@ -43,7 +43,23 @@ jobs: - uses: r-lib/actions/setup-r-dependencies@v2 with: - extra-packages: any::rcmdcheck + extra-packages: | + any::rcmdcheck + nlmixr2/n1qn1c + nlmixr2/lbfgsb3c + nlmixr2/PreciseSums + nlmixr2/dparser-R + nlmixr2/lotri + nlmixr2/rxode2ll + nlmixr2/rxode2 + nlmixr2/nlmixr2est + nlmixr2/nlmixr2extra + nlmixr2/nlmixr2plot + nlmixr2/nlmixr2 + nlmixr2/nonmem2rx + nlmixr2/monolix2rx + nlmixr2/babelmixr2 + lixoftConnectors=?ignore needs: check - uses: r-lib/actions/check-r-package@v2 diff --git a/.github/workflows/test-coverage.yaml b/.github/workflows/test-coverage.yaml index 98822609..77b45620 100644 --- a/.github/workflows/test-coverage.yaml +++ b/.github/workflows/test-coverage.yaml @@ -25,7 +25,24 @@ jobs: - uses: r-lib/actions/setup-r-dependencies@v2 with: - extra-packages: any::covr, any::xml2 + extra-packages: | + any::covr + any::xml2 + nlmixr2/n1qn1c + nlmixr2/lbfgsb3c + nlmixr2/PreciseSums + nlmixr2/dparser-R + nlmixr2/lotri + nlmixr2/rxode2ll + nlmixr2/rxode2 + nlmixr2/nlmixr2est + nlmixr2/nlmixr2extra + nlmixr2/nlmixr2plot + nlmixr2/nlmixr2 + nlmixr2/nonmem2rx + nlmixr2/monolix2rx + nlmixr2/babelmixr2 + lixoftConnectors=?ignore needs: coverage - name: Test coverage From 63f3442e6d08f177923a3d0bb48f068d3d8bb2d6 Mon Sep 17 00:00:00 2001 From: Matthew Fidler Date: Thu, 7 Nov 2024 15:36:20 -0600 Subject: [PATCH 5/5] Revert "add babelmixr2 dev for check" This reverts commit 4b136a024736ed46cdd34c1da82bd503473bfcb0. --- .github/workflows/R-CMD-check.yaml | 18 +----------------- .github/workflows/test-coverage.yaml | 19 +------------------ 2 files changed, 2 insertions(+), 35 deletions(-) diff --git a/.github/workflows/R-CMD-check.yaml b/.github/workflows/R-CMD-check.yaml index 93515f18..d46a6175 100644 --- a/.github/workflows/R-CMD-check.yaml +++ b/.github/workflows/R-CMD-check.yaml @@ -43,23 +43,7 @@ jobs: - uses: r-lib/actions/setup-r-dependencies@v2 with: - extra-packages: | - any::rcmdcheck - nlmixr2/n1qn1c - nlmixr2/lbfgsb3c - nlmixr2/PreciseSums - nlmixr2/dparser-R - nlmixr2/lotri - nlmixr2/rxode2ll - nlmixr2/rxode2 - nlmixr2/nlmixr2est - nlmixr2/nlmixr2extra - nlmixr2/nlmixr2plot - nlmixr2/nlmixr2 - nlmixr2/nonmem2rx - nlmixr2/monolix2rx - nlmixr2/babelmixr2 - lixoftConnectors=?ignore + extra-packages: any::rcmdcheck needs: check - uses: r-lib/actions/check-r-package@v2 diff --git a/.github/workflows/test-coverage.yaml b/.github/workflows/test-coverage.yaml index 77b45620..98822609 100644 --- a/.github/workflows/test-coverage.yaml +++ b/.github/workflows/test-coverage.yaml @@ -25,24 +25,7 @@ jobs: - uses: r-lib/actions/setup-r-dependencies@v2 with: - extra-packages: | - any::covr - any::xml2 - nlmixr2/n1qn1c - nlmixr2/lbfgsb3c - nlmixr2/PreciseSums - nlmixr2/dparser-R - nlmixr2/lotri - nlmixr2/rxode2ll - nlmixr2/rxode2 - nlmixr2/nlmixr2est - nlmixr2/nlmixr2extra - nlmixr2/nlmixr2plot - nlmixr2/nlmixr2 - nlmixr2/nonmem2rx - nlmixr2/monolix2rx - nlmixr2/babelmixr2 - lixoftConnectors=?ignore + extra-packages: any::covr, any::xml2 needs: coverage - name: Test coverage