@@ -150,6 +150,7 @@ pkgplan_async_download_internal <- function(self, private, what, which) {
150150 what $ download_status <- vcapply(dls , " [[" , " download_status" )
151151 what $ download_error <- lapply(dls , function (x ) x $ download_error [[1 ]])
152152 what $ file_size <- vdapply(dls , " [[" , " file_size" )
153+ what $ used_cached_binary <- vlapply(dls , " [[" , " used_cached_binary" )
153154 class(what ) <- c(" pkgplan_downloads" , class(what ))
154155 attr(what , " metadata" )$ download_start <- start
155156 attr(what , " metadata" )$ download_end <- Sys.time()
@@ -197,9 +198,16 @@ download_remote <- function(
197198 ) {
198199 stop(" Failed to download " , res $ type , " package " , res $ package )
199200 }
201+
202+ dlres <- res
200203 if (! grepl(" ^Had" , s ) && ! identical(s , " Got" ) && ! identical(s , " Current" ))
201204 s <- " Got"
202- dlres <- res
205+ if (grepl(" ^Had-binary-" , s )) {
206+ dlres $ used_cached_binary <- TRUE
207+ s <- " Had"
208+ } else {
209+ dlres $ used_cached_binary <- FALSE
210+ }
203211 dlres $ fulltarget <- target
204212 dlres $ fulltarget_tree <- target_tree
205213 dlres $ download_status <- s
@@ -208,6 +216,7 @@ download_remote <- function(
208216 dlres
209217 })$ catch(error = function (err ) {
210218 dlres <- res
219+ dlres $ used_cached_binary <- NA
211220 dlres $ fulltarget <- target
212221 dlres $ fulltarget_tree <- target_tree
213222 dlres $ download_status <- " Failed"
@@ -304,16 +313,17 @@ download_ping_if_no_sha <- function(
304313 length(rver ) == 1
305314 ) {
306315 # # Try to find a binary in the cache
316+ cplt <- current_r_platform()
307317 bin <- cache $ package $ copy_to(
308318 target ,
309319 package = resolution $ package ,
310320 version = resolution $ version ,
311- platform = current_r_platform() ,
321+ platform = cplt ,
312322 built = TRUE ,
313323 rversion = rver
314324 )
315325 if (nrow(bin )) {
316- return (async_constant(" Had" ))
326+ return (async_constant(paste0( " Had-binary- " , cplt ) ))
317327 }
318328 }
319329
0 commit comments