@@ -1038,7 +1038,21 @@ install_package <- function(pkg_name, pkg_spec, args) {
10381038 # Simple version constraint string - CRAN package
10391039 log_info(paste0(" [INSTALL] " , pkg_name , " " , pkg_spec , " from CRAN" ), args $ quiet )
10401040 if (! args $ dry_run ) {
1041- remotes :: install_version(pkg_name , version = pkg_spec , upgrade = " never" , quiet = args $ quiet )
1041+ tryCatch(
1042+ remotes :: install_version(
1043+ pkg_name ,
1044+ version = pkg_spec ,
1045+ upgrade = " never" ,
1046+ quiet = args $ quiet
1047+ ),
1048+ error = function (e ) {
1049+ abort(c(
1050+ " Package installation failed" ,
1051+ " x" = paste(" Failed to install" , pkg_name , " from CRAN" ),
1052+ " i" = e $ message
1053+ ), call = NULL )
1054+ }
1055+ )
10421056 }
10431057 } else if (is.list(pkg_spec )) {
10441058 # Complex specification
@@ -1057,45 +1071,93 @@ install_package <- function(pkg_name, pkg_spec, args) {
10571071
10581072 log_info(paste0(" [INSTALL] " , pkg_name , " from GitHub: " , repo_spec ), args $ quiet )
10591073 if (! args $ dry_run ) {
1060- remotes :: install_github(repo_spec , upgrade = " never" , quiet = args $ quiet )
1074+ tryCatch(
1075+ remotes :: install_github(repo_spec , upgrade = " never" , quiet = args $ quiet ),
1076+ error = function (e ) {
1077+ abort(c(
1078+ " Package installation failed" ,
1079+ " x" = paste(" Failed to install" , pkg_name , " from GitHub:" , repo_spec ),
1080+ " i" = e $ message
1081+ ), call = NULL )
1082+ }
1083+ )
10611084 }
1062- } else if (! is_null(pkg_spec $ repos )) {
1063- # Custom repository
1064- version_str <- if (! is_null(pkg_spec $ version )) pkg_spec $ version else " *"
1085+ } else if (! is_null(pkg_spec $ version )) {
1086+ # CRAN with version (optionally with custom repo)
1087+ force_str <- if (! is_null(pkg_spec $ force ) && pkg_spec $ force ) " (forced)" else " "
1088+
1089+ # Build repos list
1090+ repos <- if (! is_null(pkg_spec $ repos )) {
1091+ c(pkg_spec $ repos , getOption(" repos" ))
1092+ } else {
1093+ getOption(" repos" )
1094+ }
1095+
1096+ repo_str <- if (! is_null(pkg_spec $ repos )) {
1097+ paste0(" from " , pkg_spec $ repos )
1098+ } else {
1099+ " from CRAN"
1100+ }
1101+
10651102 log_info(
1066- paste0(" [INSTALL] " , pkg_name , " " , version_str , " from " , pkg_spec $ repos ),
1103+ paste0(" [INSTALL] " , pkg_name , " " , pkg_spec $ version , repo_str , force_str ),
10671104 args $ quiet
10681105 )
10691106 if (! args $ dry_run ) {
1070- remotes :: install_version(
1071- pkg_name ,
1072- version = version_str ,
1073- repos = pkg_spec $ repos ,
1074- upgrade = " never" ,
1075- quiet = args $ quiet
1107+ tryCatch(
1108+ remotes :: install_version(
1109+ pkg_name ,
1110+ version = pkg_spec $ version ,
1111+ repos = repos ,
1112+ upgrade = " never" ,
1113+ quiet = args $ quiet
1114+ ),
1115+ error = function (e ) {
1116+ abort(c(
1117+ " Package installation failed" ,
1118+ " x" = paste(" Failed to install" , pkg_name , pkg_spec $ version , repo_str ),
1119+ " i" = e $ message
1120+ ), call = NULL )
1121+ }
10761122 )
10771123 }
1078- } else if (! is_null(pkg_spec $ version )) {
1079- # CRAN with version
1124+ } else if (! is_null(pkg_spec $ repos )) {
1125+ # Custom repo without version - install latest from custom repo
10801126 force_str <- if (! is_null(pkg_spec $ force ) && pkg_spec $ force ) " (forced)" else " "
1127+
1128+ # Build repos list with custom repo first
1129+ repos <- c(pkg_spec $ repos , getOption(" repos" ))
1130+
10811131 log_info(
1082- paste0(" [INSTALL] " , pkg_name , " " , pkg_spec $ version , " from CRAN " , force_str ),
1132+ paste0(" [INSTALL] " , pkg_name , " from " , pkg_spec $ repos , force_str ),
10831133 args $ quiet
10841134 )
10851135 if (! args $ dry_run ) {
1086- remotes :: install_version(
1087- pkg_name ,
1088- version = pkg_spec $ version ,
1089- upgrade = " never" ,
1090- quiet = args $ quiet
1136+ tryCatch(
1137+ remotes :: install_cran(
1138+ pkg_name ,
1139+ repos = repos ,
1140+ upgrade = " never" ,
1141+ quiet = args $ quiet
1142+ ),
1143+ error = function (e ) {
1144+ abort(c(
1145+ " Package installation failed" ,
1146+ " x" = paste(" Failed to install" , pkg_name , " from" , pkg_spec $ repos ),
1147+ " i" = e $ message
1148+ ), call = NULL )
1149+ }
10911150 )
10921151 }
10931152 } else {
10941153 # Unknown spec - this shouldn't happen with valid TOML
10951154 abort(c(
10961155 " Invalid package specification" ,
10971156 " x" = paste(" Package" , pkg_name , " has unknown specification format" ),
1098- " i" = " Expected 'version', 'github', or 'repos' field in rpixi.toml"
1157+ " i" = paste(
1158+ " Expected 'version' (optionally with 'repos'), 'repos'," ,
1159+ " or 'github' field in rpixi.toml"
1160+ )
10991161 ), call = caller_env())
11001162 }
11011163 } else {
@@ -1113,7 +1175,7 @@ install_package <- function(pkg_name, pkg_spec, args) {
11131175# ' Categorize package by installation type
11141176# '
11151177# ' @param pkg_spec Character or List. Package specification
1116- # ' @return Character. One of: "cran_unversioned", "cran_versioned", "github ", "custom_repo "
1178+ # ' @return Character. One of: "cran_unversioned", "cran_versioned", "cran_custom_repo ", "github "
11171179categorize_package_type <- function (pkg_spec ) {
11181180 if (is_string(pkg_spec )) {
11191181 # String specs with content are versioned
@@ -1126,11 +1188,14 @@ categorize_package_type <- function(pkg_spec) {
11261188 if (! is_null(pkg_spec $ github )) {
11271189 return (" github" )
11281190 } else if (! is_null(pkg_spec $ repos )) {
1129- return (" custom_repo" )
1130- } else if (! is_null(pkg_spec $ version )) {
1191+ # Has custom repo - must install individually to apply repo correctly
1192+ # Don't batch these packages as the custom repo should only apply to this package
1193+ return (" cran_custom_repo" )
1194+ } else if (! is_null(pkg_spec $ version ) && nzchar(pkg_spec $ version ) && pkg_spec $ version != " *" ) {
1195+ # Has explicit non-wildcard version
11311196 return (" cran_versioned" )
11321197 } else {
1133- # No version, github, or repos specified
1198+ # No version, no custom repo - can be batched
11341199 return (" cran_unversioned" )
11351200 }
11361201 }
@@ -1145,40 +1210,84 @@ categorize_package_type <- function(pkg_spec) {
11451210
11461211# ' Batch install non-versioned CRAN packages
11471212# '
1148- # ' @param pkg_names Character vector. Names of packages to install
1213+ # ' @param pkg_list Named list. Package names as names, specs as values
11491214# ' @param args List. Parsed arguments (for install options and logging)
11501215# ' @return List with 'installed' and 'skipped' counts
1151- install_cran_batch <- function (pkg_names , args ) {
1152- if (length(pkg_names ) == 0 ) {
1216+ install_cran_batch <- function (pkg_list , args ) {
1217+ if (length(pkg_list ) == 0 ) {
11531218 return (list (installed = 0 , skipped = 0 ))
11541219 }
11551220
1221+ pkg_names <- names(pkg_list )
1222+
11561223 # Filter out already-installed packages if skip_installed is enabled
1157- to_install <- pkg_names
1224+ to_install_names <- pkg_names
11581225 skipped <- 0
11591226
11601227 if (args $ skip_installed && ! args $ force ) {
1161- to_install <- Filter(function (pkg ) ! is_package_installed(pkg ), pkg_names )
1162- skipped <- length(pkg_names ) - length(to_install )
1228+ to_install_names <- Filter(function (pkg ) ! is_package_installed(pkg ), pkg_names )
1229+ skipped <- length(pkg_names ) - length(to_install_names )
11631230
11641231 # Log skipped packages
11651232 if (skipped > 0 ) {
1166- skipped_names <- setdiff(pkg_names , to_install )
1233+ skipped_names <- setdiff(pkg_names , to_install_names )
11671234 for (pkg in skipped_names ) {
11681235 log_info(paste0(" [SKIP] " , pkg , " (already installed)" ), args $ quiet )
11691236 }
11701237 }
11711238 }
11721239
11731240 # Install remaining packages
1174- if (length(to_install ) > 0 ) {
1175- log_info(paste0(" [INSTALL] Batch installing " , length(to_install ), " packages from CRAN" ), args $ quiet )
1241+ if (length(to_install_names ) > 0 ) {
1242+ # Note: Packages with custom repos are installed individually,
1243+ # so this batch only contains regular CRAN packages
1244+
1245+ log_info(
1246+ paste0(
1247+ " [INSTALL] Batch installing " ,
1248+ length(to_install_names ),
1249+ " packages from CRAN"
1250+ ),
1251+ args $ quiet
1252+ )
11761253 if (! args $ dry_run ) {
1177- remotes :: install_cran(to_install , upgrade = " never" , quiet = args $ quiet )
1254+ # Capture warnings during installation
1255+ install_warnings <- list ()
1256+ tryCatch(
1257+ withCallingHandlers(
1258+ remotes :: install_cran(
1259+ to_install_names ,
1260+ repos = getOption(" repos" ),
1261+ upgrade = " never" ,
1262+ quiet = args $ quiet
1263+ ),
1264+ warning = function (w ) {
1265+ install_warnings [[length(install_warnings ) + 1 ]] <<- w $ message
1266+ invokeRestart(" muffleWarning" )
1267+ }
1268+ ),
1269+ error = function (e ) {
1270+ # Show captured warnings
1271+ if (length(install_warnings ) > 0 ) {
1272+ cat(" \n Installation warnings:\n " , file = stderr())
1273+ for (w in install_warnings ) {
1274+ cat(" " , w , " \n " , sep = " " , file = stderr())
1275+ }
1276+ }
1277+ abort(c(
1278+ " Batch package installation failed" ,
1279+ " x" = paste(
1280+ " Failed to install one or more packages from:" ,
1281+ paste(to_install_names , collapse = " , " )
1282+ ),
1283+ " i" = e $ message
1284+ ), call = NULL )
1285+ }
1286+ )
11781287 }
11791288 }
11801289
1181- list (installed = length(to_install ), skipped = skipped )
1290+ list (installed = length(to_install_names ), skipped = skipped )
11821291}
11831292
11841293# ' Install packages for an environment
@@ -1215,8 +1324,8 @@ install_environment <- function(env_name, config, args) {
12151324 }
12161325
12171326 # Categorize packages by type and force flag
1218- cran_unversioned_normal <- character ()
1219- cran_unversioned_forced <- character ()
1327+ cran_unversioned_normal <- list () # named list of package specs
1328+ cran_unversioned_forced <- list () # named list of package specs
12201329 other_packages <- list () # list of lists: list(name, spec, forced)
12211330
12221331 for (pkg_name in names(all_packages )) {
@@ -1226,12 +1335,12 @@ install_environment <- function(env_name, config, args) {
12261335
12271336 if (pkg_type == " cran_unversioned" ) {
12281337 if (is_forced ) {
1229- cran_unversioned_forced <- c( cran_unversioned_forced , pkg_name )
1338+ cran_unversioned_forced [[ pkg_name ]] <- pkg_spec
12301339 } else {
1231- cran_unversioned_normal <- c( cran_unversioned_normal , pkg_name )
1340+ cran_unversioned_normal [[ pkg_name ]] <- pkg_spec
12321341 }
12331342 } else {
1234- # All other types: install sequentially
1343+ # All other types: install sequentially (versioned CRAN, GitHub)
12351344 other_packages [[length(other_packages ) + 1 ]] <- list (
12361345 name = pkg_name ,
12371346 spec = pkg_spec ,
@@ -1246,15 +1355,29 @@ install_environment <- function(env_name, config, args) {
12461355
12471356 # Batch install non-versioned CRAN packages (non-forced)
12481357 if (length(cran_unversioned_normal ) > 0 ) {
1249- log_info(paste0(" \n Batch installing " , length(cran_unversioned_normal ), " non-versioned CRAN packages..." ), args $ quiet )
1358+ log_info(
1359+ paste0(
1360+ " \n Batch installing " ,
1361+ length(cran_unversioned_normal ),
1362+ " non-versioned CRAN packages..."
1363+ ),
1364+ args $ quiet
1365+ )
12501366 result <- install_cran_batch(cran_unversioned_normal , args )
12511367 total_installed <- total_installed + result $ installed
12521368 total_skipped <- total_skipped + result $ skipped
12531369 }
12541370
12551371 # Batch install non-versioned CRAN packages (forced)
12561372 if (length(cran_unversioned_forced ) > 0 ) {
1257- log_info(paste0(" \n Batch installing " , length(cran_unversioned_forced ), " non-versioned CRAN packages (forced)..." ), args $ quiet )
1373+ log_info(
1374+ paste0(
1375+ " \n Batch installing " ,
1376+ length(cran_unversioned_forced ),
1377+ " non-versioned CRAN packages (forced)..."
1378+ ),
1379+ args $ quiet
1380+ )
12581381 # Set force flag temporarily
12591382 args_forced <- args
12601383 args_forced $ force <- TRUE
@@ -1263,9 +1386,16 @@ install_environment <- function(env_name, config, args) {
12631386 total_skipped <- total_skipped + result $ skipped
12641387 }
12651388
1266- # Install other packages sequentially (versioned CRAN, GitHub, custom repos )
1389+ # Install other packages sequentially (versioned CRAN, GitHub)
12671390 if (length(other_packages ) > 0 ) {
1268- log_info(paste0(" \n Installing " , length(other_packages ), " packages (versioned/GitHub/custom)..." ), args $ quiet )
1391+ log_info(
1392+ paste0(
1393+ " \n Installing " ,
1394+ length(other_packages ),
1395+ " packages (versioned/GitHub)..."
1396+ ),
1397+ args $ quiet
1398+ )
12691399
12701400 for (pkg_info in other_packages ) {
12711401 pkg_name <- pkg_info $ name
0 commit comments