From 3cb2998a949a185d7536dfdf389c81e666226149 Mon Sep 17 00:00:00 2001 From: Yisreal Date: Fri, 12 Jul 2024 14:54:48 +0800 Subject: [PATCH 1/7] Update met2model.FATES to generate three monthly files, including precipitation, solar radiation and temperature+humidity --- models/fates/R/met2model.FATES.R | 253 +++++++++++++++++-------------- 1 file changed, 139 insertions(+), 114 deletions(-) mode change 100644 => 100755 models/fates/R/met2model.FATES.R diff --git a/models/fates/R/met2model.FATES.R b/models/fates/R/met2model.FATES.R old mode 100644 new mode 100755 index df232462351..a421d4c5988 --- a/models/fates/R/met2model.FATES.R +++ b/models/fates/R/met2model.FATES.R @@ -16,148 +16,173 @@ ##' @param in.path location on disk where inputs are stored ##' @param in.prefix prefix of input and output files ##' @param outfolder location on disk where outputs will be stored -##' @param start_date the start date of the data to be downloaded (will only use the year part of the date) -##' @param end_date the end date of the data to be downloaded (will only use the year part of the date) +##' @param start_date the start date of the data to be downloaded +##' @param end_date the end date of the data to be downloaded ##' @param lst timezone offset to GMT in hours ##' @param overwrite should existing files be overwritten -##' @param verbose should the function be very verbosefor(year in start_year:end_year) +##' @param verbose should the function be very verbose for(year in start_year:end_year) ##' @importFrom ncdf4 ncvar_get ncdim_def ncatt_get ncvar_put -met2model.FATES <- function(in.path, in.prefix, outfolder, start_date, end_date, lst = 0, lat, lon, - overwrite = FALSE, verbose = FALSE, ...) { - + +met2model.FATES <- function(in.path,in.prefix,outfolder,start_date,end_date,lst=0,lat, lon, overwrite = FALSE, verbose = FALSE, ...) { # General Structure- FATES Uses Netcdf so we need to rename vars, split files from years into months, and generate the header file # Get Met file from inpath. # Loop over years (Open nc.file,rename vars,change dimensions as needed,close/save .nc file) # close # defining temporal dimension needs to be figured out. If we configure FATES to use same tstep then we may not need to change dimensions - - - insert <- function(ncout, name, unit, data) { - var <- ncdf4::ncvar_def(name = name, units = unit, dim = dim, missval = -6999, verbose = verbose) - ncout <- ncdf4::ncvar_add(nc = ncout, v = var, verbose = verbose) - ncvar_put(nc = ncout, varid = name, vals = data) + insert <- function(ncout, name, unit, data, dim) { + var <- ncdf4::ncvar_def(name, unit, dim = dim, missval = as.numeric(1.0e36), verbose = verbose) + ncout <- ncdf4::ncvar_add(ncout, var) + ncdf4::ncvar_put(nc = ncout, varid = name, vals = data) return(invisible(ncout)) } - sm <- c(0, 31, 59, 90, 120, 151, 181, 212, 243, 273, 304, 334, 365) * 86400 ## day of year thresholds ## Create output directory - dir.create(outfolder) + if (!file.exists(outfolder)){ + dir.create(outfolder) + } - # Process start and end dates - start_date <- as.POSIXlt(start_date, tz = "UTC") - end_date <- as.POSIXlt(end_date, tz = "UTC") + ## Process start, end dates + start_date <- as.POSIXlt(start_date, tz = "UTC", origin = "1700-01-01") + end_date <- as.POSIXlt(end_date, tz = "UTC", origin = "1700-01-01") start_year <- lubridate::year(start_date) end_year <- lubridate::year(end_date) - + ## Build met for (year in start_year:end_year) { - + + ## Process time + base_time <- difftime(paste0(year,"-01-01"),"1700-01-01", units="days") ## days of the year + if (lubridate::leap_year(year)){ # True + sm <- c(0, 31, 58, 90, 120, 151, 181, 212, 243, 273, 304, 334, 365) + } + else { + sm <- c(0, 31, 59, 91, 121, 152, 182, 213, 244, 274, 305, 335, 366) + } + in.file <- file.path(in.path, paste(in.prefix, year, "nc", sep = ".")) - if (file.exists(in.file)) { - + ## Open netcdf file nc <- ncdf4::nc_open(in.file) - + ## extract variables. These need to be read in and converted to CLM names (all units are correct) - time <- ncvar_get(nc, "time") - latitude <- ncvar_get(nc, "latitude") - longitude <- ncvar_get(nc, "longitude") - FLDS <- ncvar_get(nc, "surface_downwelling_longwave_flux_in_air") ## W/m2 - FSDS <- ncvar_get(nc, "surface_downwelling_shortwave_flux_in_air") ## W/m2 - PRECTmms <- ncvar_get(nc, "precipitation_flux") ## kg/m2/s -> mm/s (same val, diff name) - PSRF <- ncvar_get(nc, "air_pressure") ## Pa - SHUM <- ncvar_get(nc, "specific_humidity") ## g/g -> kg/kg - TBOT <- ncvar_get(nc, "air_temperature") ## K - WIND <- sqrt(ncvar_get(nc, "eastward_wind") ^ 2 + ncvar_get(nc, "northward_wind") ^ 2) ## m/s + time <- ncdf4::ncvar_get(nc, "time") + LATIXY <- ncdf4::ncvar_get(nc, "latitude") + LONGXY <- ncdf4::ncvar_get(nc, "longitude") + FLDS <- ncdf4::ncvar_get(nc, "surface_downwelling_longwave_flux_in_air") ## W/m2 + FSDS <- ncdf4::ncvar_get(nc, "surface_downwelling_shortwave_flux_in_air") ## W/m2 + PRECTmms <- ncdf4::ncvar_get(nc, "precipitation_flux") ## kg/m2/s -> mm/s (same val, diff name) + PSRF <- ncdf4::ncvar_get(nc, "air_pressure") ## Pa + QBOT <- ncdf4::ncvar_get(nc, "specific_humidity") ## g/g -> kg/kg + TBOT <- ncdf4::ncvar_get(nc, "air_temperature") ## K + WIND <- sqrt(ncdf4::ncvar_get(nc, "eastward_wind") ^ 2 + ncdf4::ncvar_get(nc, "northward_wind") ^ 2) ## m/s ## CREATE MONTHLY FILES for (mo in 1:12) { - tsel <- which(time > sm[mo] & time <= sm[mo + 1]) - outfile <- file.path(outfolder, paste0(formatC(year, width = 4, flag = "0"), "-", - formatC(mo, width = 2, flag = "0"), ".nc")) - if (file.exists(outfile) & overwrite == FALSE) { + if (((year==start_year) & (molubridate::month(end_date)))){ next } - - lat.dim <- ncdim_def(name = "latitude", units = "", vals = 1:1, create_dimvar = FALSE) - lon.dim <- ncdim_def(name = "longitude", units = "", vals = 1:1, create_dimvar = FALSE) - time.dim <- ncdim_def(name = "time", units = "seconds", vals = time, - create_dimvar = TRUE, unlim = TRUE) - dim <- list(lat.dim, lon.dim, time.dim) ## docs say this should be time,lat,lon but get error writing unlimited first - ## http://www.cesm.ucar.edu/models/cesm1.2/clm/models/lnd/clm/doc/UsersGuide/x12979.html - - # LATITUDE - var <- ncdf4::ncvar_def(name = "latitude", units = "degree_north", - dim = list(lat.dim, lon.dim), missval = as.numeric(-9999)) - ncout <- ncdf4::nc_create(outfile, vars = var, verbose = verbose) - ncvar_put(nc = ncout, varid = "latitude", vals = latitude) - - # LONGITUDE - var <- ncdf4::ncvar_def(name = "longitude", units = "degree_east", - dim = list(lat.dim, lon.dim), missval = as.numeric(-9999)) - ncout <- ncdf4::ncvar_add(nc = ncout, v = var, verbose = verbose) - ncvar_put(nc = ncout, varid = "longitude", vals = longitude) - - ## surface_downwelling_longwave_flux_in_air - ncout <- insert(ncout, "FLDS", "W m-2", FLDS) - - ## surface_downwelling_shortwave_flux_in_air - ncout <- insert(ncout, "FSDS", "W m-2", FSDS) - - ## precipitation_flux - ncout <- insert(ncout, "PRECTmms", "mm/s", PRECTmms) - - ## air_pressure - ncout <- insert(ncout, "PSRF", "Pa", PSRF) - - ## specific_humidity - ncout <- insert(ncout, "SHUM", "kg/kg", SHUM) - - ## air_temperature - ncout <- insert(ncout, "TBOT", "K", TBOT) - - ## eastward_wind & northward_wind - ncout <- insert(ncout, "WIND", "m/s", WIND) - - ncdf4::nc_close(ncout) - - # ncvar_rename(ncfile,varid="LONGXY") - # ncvar_rename(ncfile,varid="LATIXY") - # # - # # double EDGEW(scalar) ; - # # EDGEW:long_name = "western edge in atmospheric data" ; - # # EDGEW:units = "degrees E" ; - # EDGEW = ncvar_rename(ncfile,"EDGEW","EDGEW") - # - # # double EDGEE(scalar) ; - # # EDGEE:long_name = "eastern edge in atmospheric data" ; - # # EDGEE:units = "degrees E" ; - # EDGEE = ncvar_rename(ncfile,"EDGEE","EDGEE") - # - # # double EDGES(scalar) ; - # # EDGES:long_name = "southern edge in atmospheric data" ; - # # EDGES:units = "degrees N" ; - # EDGES = ncvar_rename(ncfile,"EDGES","EDGES") - # # - # # double EDGEN(scalar) ; - # # EDGEN:long_name = "northern edge in atmospheric data" ; - # # EDGEN:units = "degrees N" ; - # EDGEN = ncvar_rename(ncfile,"EDGEN","EDGEN") + else { + # slice + tsel <- which(time > base_time+sm[mo] & time <= base_time+sm[mo+1]) + print(mo) + if (length(tsel)!=0){ + # define dim + lat.dim <- ncdf4::ncdim_def(name = "lat", units = "", vals = 1:1, create_dimvar=FALSE) + lon.dim <- ncdf4::ncdim_def(name = "lon", units = "", vals = 1:1, create_dimvar=FALSE) + time.dim <- ncdf4::ncdim_def(name = "time", units = "", vals = 1:length(time[tsel]),create_dimvar = TRUE, calendar="standard", unlim = FALSE) #left to CTSM automatically transfer + scalar.dim <- ncdf4::ncdim_def(name="scalar", units = "", vals = 1:1) + dim <- list(time.dim, lat.dim, lon.dim) + + # LATITUDE + var_lat <- ncdf4::ncvar_def(name = "LATIXY", units = "degree_north", + dim = list(lat.dim, lon.dim), missval = as.numeric(-9999)) + # LONGITUDE + var_long <- ncdf4::ncvar_def(name = "LONGXY", units = "degree_east", + dim = list(lat.dim, lon.dim), missval = as.numeric(-9999)) + # time + var_time <- ncdf4::ncvar_def(name = "time", units = "days since 1700-01-01", prec = "float", + dim = list(time.dim), missval = as.numeric(-9999)) + # EDGEE + var_E <- ncdf4::ncvar_def(name = "EDGEE", units = "degrees_east", + dim = list(scalar.dim, lat.dim, lon.dim), missval = as.numeric(-9999)) + # EDGEW edge for resolution , edge-central 0.005, # PEcAn provide range of grid? + var_W <- ncdf4::ncvar_def(name = "EDGEW", units = "degrees_west", + dim = list(scalar.dim, lat.dim, lon.dim), missval = as.numeric(-9999)) + # EDGES + var_S <- ncdf4::ncvar_def(name = "EDGES", units = "degrees_south", + dim = list(scalar.dim, lat.dim, lon.dim), missval = as.numeric(-9999)) + # EDGEN + var_N <- ncdf4::ncvar_def(name = "EDGEN", units = "degrees_north", + dim = list(scalar.dim, lat.dim, lon.dim), missval = as.numeric(-9999)) + + ## SAPERATELY CREATE FILES + put_var <- function(ncout){ + ncdf4::ncvar_put(nc = ncout, varid = "LATIXY", vals = LATIXY) #same with FATES + ncdf4::ncvar_put(nc = ncout, varid = "LONGXY", vals = LONGXY) + ncdf4::ncvar_put(nc = ncout, varid = "EDGEE", vals = LONGXY+0.005) + ncdf4::ncvar_put(nc = ncout, varid = "EDGEW", vals = LONGXY-0.005) + ncdf4::ncvar_put(nc = ncout, varid = "EDGES", vals = LATIXY-0.005) + ncdf4::ncvar_put(nc = ncout, varid = "EDGEN", vals = LATIXY+0.005) + } + ## Precipitation + outfile_prec <- file.path(outfolder, paste0("Prec", formatC(year, width = 4, flag = "0"), "-", + formatC(mo, width = 2, flag = "0"), ".nc")) + if (file.exists(outfile_prec) & overwrite == FALSE) { + next + } + ncout_prec <- ncdf4::nc_create(outfile_prec, vars = list(var_lat,var_long,var_E,var_W,var_S,var_N), verbose = verbose) + put_var(ncout_prec) + ## precipitation_flux + ncout_prec <- insert(ncout_prec, "PRECTmms", "mm/s", PRECTmms[tsel], dim) + ncdf4::nc_close(ncout_prec) + + ## Solar + outfile_slr <- file.path(outfolder, paste0("Slr", formatC(year, width = 4, flag = "0"), "-", + formatC(mo, width = 2, flag = "0"), ".nc")) + if (file.exists(outfile_slr) & overwrite == FALSE) { + next + } + ncout_slr <- ncdf4::nc_create(outfile_slr, vars = list(var_lat,var_long,var_E,var_W,var_S,var_N), verbose = verbose) + put_var(ncout_slr) + ## surface_downwelling_shortwave_flux_in_air + ncout_slr <- insert(ncout_slr, "FSDS", "W m-2", FSDS[tsel], dim) + ncdf4::nc_close(ncout_slr) + + ## Temerature and humidity + outfile_tem <- file.path(outfolder, paste0("Tem", formatC(year, width = 4, flag = "0"), "-", + formatC(mo, width = 2, flag = "0"), ".nc")) + if (file.exists(outfile_tem) & overwrite == FALSE) { + next + } + ncout_tem <- ncdf4::nc_create(outfile_tem, vars = list(var_lat,var_long,var_E,var_W,var_S,var_N), verbose = verbose) + put_var(ncout_tem) + ## surface_downwelling_longwave_flux_in_air + ncout_tem <- insert(ncout_tem, "FLDS", "W m-2", FLDS[tsel], dim) + ## air_pressure + ncout_tem <- insert(ncout_tem, "PSRF", "Pa", PSRF[tsel], dim) + ## specific_humidity + ncout_tem <- insert(ncout_tem, "QBOT", "kg/kg", QBOT[tsel], dim) + ## air_temperature + ncout_tem <- insert(ncout_tem, "TBOT", "K", TBOT[tsel], dim) + ## eastward_wind & northward_wind + ncout_tem <- insert(ncout_tem, "WIND", "m/s", WIND[tsel], dim) + ncdf4::nc_close(ncout_tem) + } + } } - - ncdf4::nc_close(nc) - } ## end file exists - } ### end loop over met files + ncdf4::nc_close(nc) + } ## end input file + } ## end year loop over met files + results <- data.frame(file = paste0(outfolder, "/"), + host = c(PEcAn.remote::fqdn()), + mimetype = c("application/x-netcdf"), + formatname = c("CLM met"), + startdate = c(start_date), + enddate = c(end_date), + dbfile.name = "", + stringsAsFactors = FALSE) PEcAn.logger::logger.info("Done with met2model.FATES") - - return(data.frame(file = paste0(outfolder, "/"), - host = c(PEcAn.remote::fqdn()), - mimetype = c("application/x-netcdf"), - formatname = c("CLM met"), - startdate = c(start_date), - enddate = c(end_date), - dbfile.name = "", - stringsAsFactors = FALSE)) + return(invisible(results)) } # met2model.FATES From 7e6d88f625de03d9c868f2974ad8d41fcd45e7f5 Mon Sep 17 00:00:00 2001 From: Yisreal Date: Fri, 12 Jul 2024 14:56:43 +0800 Subject: [PATCH 2/7] Update met2model wrapper for FATES --- models/fates/man/met2model.FATES.Rd | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/models/fates/man/met2model.FATES.Rd b/models/fates/man/met2model.FATES.Rd index 3899e5360ea..9ad044a42a4 100644 --- a/models/fates/man/met2model.FATES.Rd +++ b/models/fates/man/met2model.FATES.Rd @@ -25,15 +25,15 @@ met2model.FATES( \item{outfolder}{location on disk where outputs will be stored} -\item{start_date}{the start date of the data to be downloaded (will only use the year part of the date)} +\item{start_date}{the start date of the data to be downloaded} -\item{end_date}{the end date of the data to be downloaded (will only use the year part of the date)} +\item{end_date}{the end date of the data to be downloaded} \item{lst}{timezone offset to GMT in hours} \item{overwrite}{should existing files be overwritten} -\item{verbose}{should the function be very verbosefor(year in start_year:end_year)} +\item{verbose}{should the function be very verbose for(year in start_year:end_year)} } \description{ met2model wrapper for FATES From 712f121731d394a1459fb962732d98192d0b0ad3 Mon Sep 17 00:00:00 2001 From: Yisreal Date: Fri, 12 Jul 2024 14:59:03 +0800 Subject: [PATCH 3/7] Update model2netcdf wrapper for FATES by adding new arguments --- models/fates/man/model2netcdf.FATES.Rd | 26 +++++++++++++++++++++++--- 1 file changed, 23 insertions(+), 3 deletions(-) diff --git a/models/fates/man/model2netcdf.FATES.Rd b/models/fates/man/model2netcdf.FATES.Rd index b1338622936..d6de25b0649 100644 --- a/models/fates/man/model2netcdf.FATES.Rd +++ b/models/fates/man/model2netcdf.FATES.Rd @@ -4,10 +4,30 @@ \alias{model2netcdf.FATES} \title{Code to convert FATES netcdf output into into CF standard} \usage{ -model2netcdf.FATES(outdir) +model2netcdf.FATES( + outdir, + sitelat, + sitelon, + start_date, + end_date, + vars_names, + pfts +) } \arguments{ -\item{outdir}{Location of FATES model output} +\item{outdir}{Location of FATES model output (e.g. a path to a single ensemble output)} + +\item{sitelat}{Latitude of the site} + +\item{sitelon}{Longitude of the site} + +\item{start_date}{Start time of the simulation} + +\item{end_date}{End time of the simulation} + +\item{vars_names}{Names of Selected variables in PEcAn format} + +\item{pfts}{a named vector of PFT numbers where the names are PFT names} } \description{ Code to convert FATES netcdf output into into CF standard @@ -16,7 +36,7 @@ Code to convert FATES netcdf output into into CF standard \dontrun{ example.output <- system.file("case.clm2.h0.2004-01-01-00000.nc",package="PEcAn.FATES") -model2netcdf.FATES(outdir="~/") +model2netcdf.FATES(outdir="~/",sitelat, sitelon, start_date, end_date, vars_names, pfts) } } From 148991ff63983f40d0c80a6abad67e1996f914ac Mon Sep 17 00:00:00 2001 From: Yisreal Date: Fri, 12 Jul 2024 15:02:41 +0800 Subject: [PATCH 4/7] Update model2netcdf.FATES to turn monthly PFT level output and grid level output variables of FATES into yearly file in PEcAn format --- models/fates/R/model2netcdf.FATES.R | 696 ++++++---------------------- 1 file changed, 139 insertions(+), 557 deletions(-) diff --git a/models/fates/R/model2netcdf.FATES.R b/models/fates/R/model2netcdf.FATES.R index b85cf946d38..ee493b36755 100644 --- a/models/fates/R/model2netcdf.FATES.R +++ b/models/fates/R/model2netcdf.FATES.R @@ -10,581 +10,163 @@ ##' @name model2netcdf.FATES ##' @title Code to convert FATES netcdf output into into CF standard ##' -##' @param outdir Location of FATES model output +##' @param outdir Location of FATES model output (e.g. a path to a single ensemble output) +##' @param sitelat Latitude of the site +##' @param sitelon Longitude of the site +##' @param start_date Start time of the simulation +##' @param end_date End time of the simulation +##' @param vars_names Names of Selected variables in PEcAn format +##' @param pfts a named vector of PFT numbers where the names are PFT names ##' ##' @examples ##' \dontrun{ ##' example.output <- system.file("case.clm2.h0.2004-01-01-00000.nc",package="PEcAn.FATES") -##' model2netcdf.FATES(outdir="~/") +##' model2netcdf.FATES(outdir="~/",sitelat, sitelon, start_date, end_date, vars_names, pfts) ##' } -##' -##' @export ##' ##' @author Michael Dietze, Shawn Serbin -model2netcdf.FATES <- function(outdir) { +## modified Yucong Hu 10/07/24 +##' +##' @export - # E.g. var_update("AR","AutoResp","kgC m-2 s-1", "Autotrophic Respiration") - # currently only works for xyt variables, need to expand to work for cohort-level outputs, - # age bins, soils, etc - var_update <- function(out,oldname,newname,newunits=NULL,long_name=NULL){ - if (oldname %in% ncin_names) { - ## define variable - oldunits <- ncdf4::ncatt_get(ncin,oldname,"units")$value - if (oldunits=="gC/m^2/s") oldunits <- "gC m-2 s-1" - if (oldname=="TLAI" && oldunits=="none") oldunits <- "m2 m-2" - if(is.null(newunits)) newunits = oldunits - newvar <- ncdf4::ncvar_def(name = newname, units = newunits, longname=long_name, dim = xyt) - - ## convert data - dat <- ncdf4::ncvar_get(ncin,oldname) - dat.new <- PEcAn.utils::misc.convert(dat,oldunits,newunits) - - ## prep for writing - if(is.null(out)) { - out <- list(var <- list(),dat <- list()) - out$var[[1]] <- newvar - out$dat[[1]] <- dat.new - } else { - i <- length(out$var) + 1 - out$var[[i]] <- newvar - out$dat[[i]] <- dat.new - } +model2netcdf.FATES <- function(outdir, sitelat, sitelon, start_date, end_date, vars_names, pfts){ + ## matched_var could be expanded for more selected variables in argument:vars_names + matched_var <- list(list("FATES_GPP_PF","GPP","kgC m-2 s-1","Gross Primary Productivity"), + list("NEE","NEE","kgC m-2 s-1", "Net Ecosystem Exchange of carbon, includes fire and hrv_xsmrpool"), + list("TLAI","LAI","m2 m-2","Total projected leaf area index"), + list("ER","TotalResp","kgC m-2 s-1","Total Respiration"), + list("AR","AutoResp","kgC m-2 s-1","Autotrophic respiration (MR + GR)"), + list("HR","HeteroResp","kgC m-2 s-1","Total heterotrophic respiration"), + list("SR","SoilResp","kgC m-2 s-1","Total soil respiration (HR + root resp)"), + list("Qle","Evap","Evap","kgC m-2 s-1","Total evaporation"), + list("QVEGT","Transp","kg m-2 s-1","Canopy transpiration")) + + var_update <- function(out,oldname,newname,nc_month,nc_month_names,newunits=NULL,long_name=NULL){ + if (oldname %in% nc_month_names) { + + ## define units of variables + oldunits <- ncdf4::ncatt_get(nc_month,oldname,"units")$value + if (oldunits=="gC/m^2/s") oldunits <- "gC m-2 s-1" + if (oldname=="TLAI") oldunits <- "m2 m-2" # delete old unit ='none' + if (is.null(newunits)) newunits = oldunits + + ## check pft dimensions + d_name <- c() + for (i in (nc_month$var[[oldname]]$dim)){ + d_name <- append(d_name, i$name) + } + if (any(grepl('pft',d_name))){ + dimension <- xypt # include fates_levpft + }else{ + dimension <- xyt + } # only xyt + + ## transpose dimensions into (,t) + if (d_name[length(d_name)]=='time'){ + dat_0 <- ncdf4::ncvar_get(nc_month,oldname) # time at the tail of dims + dat.new <- PEcAn.utils::misc.convert(dat_0,oldunits,newunits) # convert data units + } + newvar <- ncdf4::ncvar_def(name = newname, units = newunits, longname=long_name, dim = dimension) + ## Adding target variables into out + if(is.null(out)) { + out <- list(var <- list(),dat <- list(), dimm<-list()) + out$var[[1]] <- newvar + out$dat[[1]] <- dat.new + out$dimm[[1]]<- length(dimension) } else { - ## correct way to "skip" and output variables that may be missing in the HLM-FATES output? - PEcAn.logger::logger.info(paste0("HLM-FATES variable: ", oldname," not present. Skipping conversion")) + i <- length(out$var) + 1 + out$var[[i]] <- newvar + out$dat[[i]] <- dat.new + out$dimm[[i]]<- length(dimension) } - return(out) + return(out) } + } - ## Get files and years - files <- dir(outdir, "*clm2.h0.*.nc", full.names = TRUE) # currently specific to clm2.h0 files - file.dates <- as.Date(sub(".nc", "", sub(".*clm2.h0.", "", files))) - years <- lubridate::year(file.dates) - init_year <- unique(years)[1] + ## Get files and years + files <- dir(outdir, "*clm2.h0.*.nc", full.names = TRUE) # currently specific to clm2.h0 files + start_year <- lubridate::year(start_date) + end_year <- lubridate::year(end_date) + start_month <- lubridate::month(start_date) + end_month <- lubridate::month(end_date) - ## Loop over years - for (year in unique(years)) { - ysel <- which(years == year) ## subselect files for selected year - if (length(ysel) > 1) { - PEcAn.logger::logger.warn("PEcAn.FATES::model2netcdf.FATES does not currently support multiple files per year") + ## Loop over years + for (year in start_year:end_year){ + oname <- file.path(dirname(files[1]), paste0(year, ".nc")) + out <- NULL + + ## Monthly write files + for (mo in 1:12){ + if (((year == start_year) & mo < start_month) | ((year == end_year) & mo > end_month)){ + next ## skip unselected months + } + else{ + if (mo<10){ + month_file <- paste0(gsub("h0.*.nc","",files[1]),"h0.",year,"-0",mo,".nc") + }else{ + month_file <- paste0(gsub("h0.*.nc","",files[1]),"h0.",year,"-",mo,".nc") } + nc_month <- ncdf4::nc_open(month_file) # read monthly output file of FATES model + nc_month_names <- names(nc_month$var) + + ## Create time bounds to populate time_bounds variable iteratively + var_bound <- ncdf4::ncvar_get(nc_month, "time_bounds") # start,end day of month - fname <- files[ysel[1]] - oname <- file.path(dirname(fname), paste0(year, ".nc")) - PEcAn.logger::logger.info(paste("model2netcdf.FATES - Converting:", fname, "to", oname)) - ncin <- ncdf4::nc_open(fname, write = TRUE) - ncin_names <- names(ncin$var) # get netCDF variable names in HLM-FATES output - + ## Define dimensions + t <- ncdf4::ncdim_def(name = "time", units = "days since 1700-01-01 00:00:00", + vals = as.double(1.0:1.0), calendar = "noleap", unlim = TRUE) + time_interval <- ncdf4::ncdim_def(name = "hist_interval", + longname = "history time interval endpoint dimensions",vals = 1:2, units = "") + lat <- ncdf4::ncdim_def("lat", "degrees_north", vals = as.double(1.0:1.0), longname = "coordinate_latitude") + #print(lat) + lon <- ncdf4::ncdim_def("lon", "degrees_east", vals = as.double(1.0:1.0), longname = "coordinate_longitude") + pft <- ncdf4::ncdim_def('pft', '', vals=1:12, longname = "FATES pft number") + xyt <- list(lon, lat, t) + xypt <- list(lon, lat, pft, t) - ## FATES time is in multiple columns, create 'time' - mcdate <- ncdf4::ncvar_get(ncin, "mcdate") # current date (YYYYMMDD) - if (length(mcdate)==1) { - ## do we need to bother converting outputs where FATES provides only a single timepoint for a date? - ## usually happens when the model starts/finishes at the end/start of a new year - PEcAn.logger::logger.debug("*** Skipping conversion for output with only a single timepoint ***") - next + ## Write monthly files with start(1,1,i) + for (var_s in vars_names){ + for (name_param in matched_var){ + if (var_s == name_param[2]){ ## select variables + out <- var_update(out,name_param[1],name_param[2],name_param[3],name_param[4],nc_month,nc_month_names) # convert monthly fates output into one variable + } + } } - cal_dates <- as.Date(as.character(mcdate),format="%Y%m%d") # in standard YYYY-MM-DD format - julian_dates <- lubridate::yday(cal_dates) # current year DOY values - day <- ncdf4::ncvar_get(ncin, "mdcur") # current day (from base day) - sec <- ncdf4::ncvar_get(ncin, "mscur") # current seconds of current day - nstep <- ncdf4::ncvar_get(ncin, "nstep") # model time step - time <- day + sec / 86400 # fractional time since base date (typically first day of full model simulation) - iter_per_day <- length(unique(sec)) # how many outputs per day (e.g. 1, 24, 48) - timesteps <- utils::head(seq(0, 1, by = 1 / iter_per_day), -1) # time of day fraction - current_year_tvals <- (julian_dates-1 + timesteps) # fractional DOY of current year - nt <- length(time) # output length - nc_time <- ncin$dim$time$vals # days since "start_date" + out$var[[length(out$var) + 1]] <- ncdf4::ncvar_def(name="time_bounds", units='', + longname = "history time interval endpoints", dim=list(time_interval,t), prec = "double") + out$dat[[length(out$dat) + 1]] <- c(rbind(var_bound[1], var_bound[2])) #start, end days of the year + out$dimm[[length(out$dimm) + 1]] <- 2 - # !! Is this a useful/reasonable check? That is that our calculated time - # matches FATES internal time var. - if (length(time)!=length(nc_time)) { - PEcAn.logger::logger.severe("Time dimension mismatch in output, simulation error?") + ## Define vars + if (((year != start_year) & (mo == 1)) | ((year == start_year) & (mo == start_month))){ + ncout <- ncdf4::nc_create(oname,out$var) # create yearly nc file + # HYC: define var time, lon, lat, and put var lon, lat + time_var <- ncdf4::ncvar_def(name = "time", units = paste0("days since 1700-01-01 00:00:00"),longname = "time", dim = list(t), prec = "double") + lat_var <- ncdf4::ncvar_def(name = "lat", units = "degrees_north", longname = "coordinate_latitude", dim=list(lat), prec = "double") + lon_var <- ncdf4::ncvar_def(name = "lon", units = "degrees_east", longname = "coordinate_longitude", dim=list(lon), prec = "double") + ncdf4::ncvar_put(ncout, lat_var, sitelat, start=c(1)) + ncdf4::ncvar_put(ncout, lon_var, sitelon, start=c(1)) } - ## Create time bounds to populate time_bounds variable - bounds <- array(data = NA, dim = c(length(time), 2)) - bounds[, 1] <- time - bounds[, 2] <- bounds[, 1] + (1 / iter_per_day) - bounds <- round(bounds, 4) # create time bounds for each timestep in t, t+1; t+1, t+2... format - - #******************** Declare netCDF dimensions ********************# - nc_var <- list() - sitelat <- ncdf4::ncvar_get(ncin,"lat") - sitelon <- ncdf4::ncvar_get(ncin,"lon") - ## time variable based on internal calc, nc$dim$time is the FATES output time - t <- ncdf4::ncdim_def(name = "time", units = paste0("days since ", init_year, "-01-01 00:00:00"), - vals = as.vector(time), calendar = "noleap", unlim = TRUE) - time_interval <- ncdf4::ncdim_def(name = "hist_interval", - longname = "history time interval endpoint dimensions", - vals = 1:2, units = "") - lat <- ncdf4::ncdim_def("lat", "degrees_north", vals = as.numeric(sitelat), longname = "coordinate_latitude") - lon <- ncdf4::ncdim_def("lon", "degrees_east", vals = as.numeric(sitelon), longname = "coordinate_longitude") - xyt <- list(lon, lat, t) - - ### build netCDF data - ## !! TODO: ADD MORE OUTPUTS HERE - out <- NULL - out <- var_update(out,"AR","AutoResp","kgC m-2 s-1","Autotrophic Respiration") - out <- var_update(out,"HR","HeteroResp","kgC m-2 s-1","Heterotrophic Respiration") - out <- var_update(out,"GPP","GPP","kgC m-2 s-1","Gross Primary Productivity") - out <- var_update(out,"NPP","NPP","kgC m-2 s-1","Net Primary Productivity") - out <- var_update(out,"NEP","NEE","kgC m-2 s-1", "Net Ecosystem Exchange") - out <- var_update(out,"FLDS","LWdown","W m-2","Surface incident longwave radiation") - out <- var_update(out,"FSDS","SWdown","W m-2","Surface incident shortwave radiation") - out <- var_update(out,"TBOT","Tair","K","Near surface air temperature") # not certain these are equivelent yet - out <- var_update(out,"QBOT","Qair","kg kg-1","Near surface specific humidity") # not certain these are equivelent yet - out <- var_update(out,"RH","RH","%","Relative Humidity") - out <- var_update(out,"WIND","Wind","m s-1","Near surface module of the wind") # not certain these are equivelent yet - out <- var_update(out,"EFLX_LH_TOT","Qle","W m-2","Latent heat") - out <- var_update(out,"QVEGT","Transp","mm s-1","Total Transpiration") ## equiv to std of kg m-2 s but don't trust udunits to get right - out <- var_update(out,"ED_balive","TotLivBiom","kgC m-2","Total living biomass") - out <- var_update(out,"ED_biomass","AbvGrndWood","kgC m-2","Above ground woody biomass") # not actually correct, need to update - out <- var_update(out,"AGB","AGB","kgC m-2","Total aboveground biomass") # not actually correct, need to update - out <- var_update(out,"ED_bleaf","leaf_carbon_content","kgC m-2","Leaf Carbon Content") - out <- var_update(out,"TLAI","LAI","m2 m-2","Leaf Area Index") - out <- var_update(out,"TSOI_10CM","SoilTemp","K","Average Layer Soil Temperature at 10cm") - - ## put in time_bounds before writing out new nc file - length(out$var) - out$var[[length(out$var) + 1]] <- ncdf4::ncvar_def(name="time_bounds", units='', - longname = "history time interval endpoints", - dim=list(time_interval,time = t), - prec = "double") - out$dat[[length(out$dat) + 1]] <- c(rbind(bounds[, 1], bounds[, 2])) - - ## close input nc file - try(ncdf4::nc_close(ncin)) - - ## write netCDF data - ncout <- ncdf4::nc_create(oname,out$var) - ncdf4::ncatt_put(ncout, "time", "bounds", "time_bounds", prec=NA) + ## Put time and vars + ncdf4::ncvar_put(ncout, time_var, mean(var_bound), start=c(month), count=c(1)) for (i in seq_along(out$var)) { - ncdf4::ncvar_put(ncout, out$var[[i]], out$dat[[i]]) - } - - ## extract variable and long names to VAR file for PEcAn vis - utils::write.table(sapply(ncout$var, function(x) { x$longname }), - file = paste0(oname, ".var"), - col.names = FALSE, - row.names = TRUE, - quote = FALSE) - - - try(ncdf4::nc_close(ncout)) - - } # end of year for loop -} # model2netcdf.FATES - -### !!! NOTES -### extract variables. These need to be read in and converted to PEcAN standard - -# levgrnd:long_name = "coordinate soil levels" ; -# levlak:long_name = "coordinate lake levels" ; -# levdcmp:long_name = "coordinate soil levels" ; -# mcdate:long_name = "current date (YYYYMMDD)" ; -# mcsec:long_name = "current seconds of current date" ; -# mdcur:long_name = "current day (from base day)" ; -# mscur:long_name = "current seconds of current day" ; -# nstep:long_name = "time step" ; -# lon:long_name = "coordinate longitude" ; -# lat:long_name = "coordinate latitude" ; -# area:long_name = "grid cell areas" ; -# topo:long_name = "grid cell topography" ; -# landfrac:long_name = "land fraction" ; -# landmask:long_name = "land/ocean mask (0.=ocean and 1.=land)" ; -# pftmask:long_name = "pft real/fake mask (0.=fake and 1.=real)" ; -# ZSOI:long_name = "soil depth" ; -# DZSOI:long_name = "soil thickness" ; -# WATSAT:long_name = "saturated soil water content (porosity)" ; -# SUCSAT:long_name = "saturated soil matric potential" ; -# BSW:long_name = "slope of soil water retention curve" ; -# HKSAT:long_name = "saturated hydraulic conductivity" ; -# ZLAKE:long_name = "lake layer node depth" ; -# DZLAKE:long_name = "lake layer thickness" ; -# ACTUAL_IMMOB:long_name = "actual N immobilization" ; -# AGNPP:long_name = "aboveground NPP" ; -# ALT:long_name = "current active layer thickness" ; -# ALTMAX:long_name = "maximum annual active layer thickness" ; -# ALTMAX_LASTYEAR:long_name = "maximum prior year active layer thickness" ; -# AR:long_name = "autotrophic respiration (MR + GR)" ; -# BAF_CROP:long_name = "fractional area burned for crop" ; -# BAF_PEATF:long_name = "fractional area burned in peatland" ; -# BCDEP:long_name = "total BC deposition (dry+wet) from atmosphere" ; -# BGNPP:long_name = "belowground NPP" ; -# BUILDHEAT:long_name = "heat flux from urban building interior to walls and roof" ; -# COL_CTRUNC:long_name = "column-level sink for C truncation" ; -# COL_FIRE_CLOSS:long_name = "total column-level fire C loss for non-peat fires outside land-type converted region" ; -# COL_FIRE_NLOSS:long_name = "total column-level fire N loss" ; -# COL_NTRUNC:long_name = "column-level sink for N truncation" ; -# CPOOL:long_name = "temporary photosynthate C pool" ; -# CWDC:long_name = "CWD C" ; -# CWDC_HR:long_name = "coarse woody debris C heterotrophic respiration" ; -# CWDC_LOSS:long_name = "coarse woody debris C loss" ; -# CWDC_TO_LITR2C:long_name = "decomp. of coarse woody debris C to litter 2 C" ; -# CWDC_TO_LITR3C:long_name = "decomp. of coarse woody debris C to litter 3 C" ; -# CWDN:long_name = "CWD N" ; -# CWDN_TO_LITR2N:long_name = "decomp. of coarse woody debris N to litter 2 N" ; -# CWDN_TO_LITR3N:long_name = "decomp. of coarse woody debris N to litter 3 N" ; -# DEADCROOTC:long_name = "dead coarse root C" ; -# DEADCROOTN:long_name = "dead coarse root N" ; -# DEADSTEMC:long_name = "dead stem C" ; -# DEADSTEMN:long_name = "dead stem N" ; -# DENIT:long_name = "total rate of denitrification" ; -# DISPVEGC:long_name = "displayed veg carbon, excluding storage and cpool" -# DISPVEGN:long_name = "displayed vegetation nitrogen" ; -# DSTDEP:long_name = "total dust deposition (dry+wet) from atmosphere" ; -# DSTFLXT:long_name = "total surface dust emission" ; -# DWT_CLOSS:long_name = "total carbon loss from land cover conversion" ; -# DWT_CONV_CFLUX:long_name = "conversion C flux (immediate loss to atm)" ; -# DWT_CONV_NFLUX:long_name = "conversion N flux (immediate loss to atm)" ; -# DWT_NLOSS:long_name = "total nitrogen loss from landcover conversion" ; -# DWT_PROD100C_GAIN:long_name = "landcover change-driven addition to 100-yr wood product pool" ; -# DWT_PROD100N_GAIN:long_name = "addition to 100-yr wood product pool" ; -# DWT_PROD10C_GAIN:long_name = "landcover change-driven addition to 10-yr wood product pool" ; -# DWT_PROD10N_GAIN:long_name = "addition to 10-yr wood product pool" ; -# DWT_SEEDC_TO_DEADSTEM:long_name = "seed source to patch-level deadstem" ; -# DWT_SEEDC_TO_LEAF:long_name = "seed source to patch-level leaf" ; -# DWT_SEEDN_TO_DEADSTEM:long_name = "seed source to PFT-level deadstem" ; -# DWT_SEEDN_TO_LEAF:long_name = "seed source to PFT-level leaf" ; -# EFLX_DYNBAL:long_name = "dynamic land cover change conversion energy flux" ; -# EFLX_GRND_LAKE:long_name = "net heat flux into lake/snow surface, excluding light transmission" ; -# EFLX_LH_TOT:long_name = "total latent heat flux [+ to atm]" ; -# EFLX_LH_TOT_R:long_name = "Rural total evaporation" ; -# EFLX_LH_TOT_U:long_name = "Urban total evaporation" ; -# ELAI:long_name = "exposed one-sided leaf area index" ; -# ER:long_name = "total ecosystem respiration, autotrophic + heterotrophic" ; -# ERRH2O:long_name = "total water conservation error" ; -# ERRH2OSNO:long_name = "imbalance in snow depth (liquid water)" ; -# ERRSEB:long_name = "surface energy conservation error" ; -# ERRSOI:long_name = "soil/lake energy conservation error" ; -# ERRSOL:long_name = "solar radiation conservation error" ; -# ESAI:long_name = "exposed one-sided stem area index" ; -# FAREA_BURNED:long_name = "timestep fractional area burned" ; -# FCEV:long_name = "canopy evaporation" ; -# FCOV:long_name = "fractional impermeable area" ; -# FCTR:long_name = "canopy transpiration" ; -# FGEV:long_name = "ground evaporation" ; -# FGR:long_name = "heat flux into soil/snow including snow melt and lake / snow light transmission" ; -# FGR12:long_name = "heat flux between soil layers 1 and 2" ; -# FGR_R:long_name = "Rural heat flux into soil/snow including snow melt and snow light transmission" ; -# FGR_U:long_name = "Urban heat flux into soil/snow including snow melt" ; -# FH2OSFC:long_name = "fraction of ground covered by surface water" ; -# FIRA:long_name = "net infrared (longwave) radiation" ; -# FIRA_R:long_name = "Rural net infrared (longwave) radiation" ; -# FIRA_U:long_name = "Urban net infrared (longwave) radiation" ; -# FIRE:long_name = "emitted infrared (longwave) radiation" ; -# FIRE_R:long_name = "Rural emitted infrared (longwave) radiation" ; -# FIRE_U:long_name = "Urban emitted infrared (longwave) radiation" ; -# FLDS:long_name = "atmospheric longwave radiation" ; -# FPG:long_name = "fraction of potential gpp" ; -# FPI:long_name = "fraction of potential immobilization" ; -# FPSN:long_name = "photosynthesis" ; -# FPSN_WC:long_name = "Rubisco-limited photosynthesis" ; -# FPSN_WJ:long_name = "RuBP-limited photosynthesis" ; -# FPSN_WP:long_name = "Product-limited photosynthesis" ; -# FROOTC:long_name = "fine root C" ; -# FROOTC_ALLOC:long_name = "fine root C allocation" ; -# FROOTC_LOSS:long_name = "fine root C loss" ; -# FROOTN:long_name = "fine root N" ; -# FSA:long_name = "absorbed solar radiation" ; -# FSAT:long_name = "fractional area with water table at surface" ; -# FSA_R:long_name = "Rural absorbed solar radiation" ; -# FSA_U:long_name = "Urban absorbed solar radiation" ; -# FSDS:long_name = "atmospheric incident solar radiation" ; -# FSDSND:long_name = "direct nir incident solar radiation" ; -# FSDSNDLN:long_name = "direct nir incident solar radiation at local noon" ; -# FSDSNI:long_name = "diffuse nir incident solar radiation" ; -# FSDSVD:long_name = "direct vis incident solar radiation" ; -# FSDSVDLN:long_name = "direct vis incident solar radiation at local noon" ; -# FSDSVI:long_name = "diffuse vis incident solar radiation" ; -# FSDSVILN:long_name = "diffuse vis incident solar radiation at local noon" ; -# FSH:long_name = "sensible heat" ; -# FSH_G:long_name = "sensible heat from ground" ; -# FSH_NODYNLNDUSE:long_name = "sensible heat not including correction for land use change" ; -# FSH_R:long_name = "Rural sensible heat" ; -# FSH_U:long_name = "Urban sensible heat" ; -# FSH_V:long_name = "sensible heat from veg" ; -# FSM:long_name = "snow melt heat flux" ; -# FSM_R:long_name = "Rural snow melt heat flux" ; -# FSM_U:long_name = "Urban snow melt heat flux" ; -# FSNO:long_name = "fraction of ground covered by snow" ; -# FSNO_EFF:long_name = "effective fraction of ground covered by snow" ; -# FSR:long_name = "reflected solar radiation" ; -# FSRND:long_name = "direct nir reflected solar radiation" ; -# FSRNDLN:long_name = "direct nir reflected solar radiation at local noon" ; -# FSRNI:long_name = "diffuse nir reflected solar radiation" ; -# FSRVD:long_name = "direct vis reflected solar radiation" ; -# FSRVDLN:long_name = "direct vis reflected solar radiation at local noon" ; -# FSRVI:long_name = "diffuse vis reflected solar radiation" ; -# FUELC:long_name = "fuel load" ; -# GC_HEAT1:long_name = "initial gridcell total heat content" ; -# GC_ICE1:long_name = "initial gridcell total ice content" ; -# GC_LIQ1:long_name = "initial gridcell total liq content" ; -# GPP:long_name = "gross primary production" ; -# GR:long_name = "total growth respiration" ; -# GROSS_NMIN:long_name = "gross rate of N mineralization" ; -# H2OCAN:long_name = "intercepted water" ; -# H2OSFC:long_name = "surface water depth" ; -# H2OSNO:long_name = "snow depth (liquid water)" ; -# H2OSNO_TOP:long_name = "mass of snow in top snow layer" ; -# HC:long_name = "heat content of soil/snow/lake" ; -# HCSOI:long_name = "soil heat content" ; -# HEAT_FROM_AC:long_name = "sensible heat flux put into canyon due to heat removed from air conditioning" ; -# HR:long_name = "total heterotrophic respiration" ; -# HTOP:long_name = "canopy top" ; -# LAISHA:long_name = "shaded projected leaf area index" ; -# LAISUN:long_name = "sunlit projected leaf area index" ; -# LAKEICEFRAC:long_name = "lake layer ice mass fraction" ; -# LAKEICETHICK:long_name = "thickness of lake ice (including physical expansion on freezing)" ; -# LAND_UPTAKE:long_name = "NEE minus LAND_USE_FLUX, negative for update" ; -# LAND_USE_FLUX:long_name = "total C emitted from land cover conversion and wood product pools" ; -# LEAFC:long_name = "leaf C" ; -# LEAFC_ALLOC:long_name = "leaf C allocation" ; -# LEAFC_LOSS:long_name = "leaf C loss" ; -# LEAFN:long_name = "leaf N" ; -# LEAF_MR:long_name = "leaf maintenance respiration" ; -# LFC2:long_name = "conversion area fraction of BET and BDT that burned" ; -# LF_CONV_CFLUX:long_name = "conversion carbon due to BET and BDT area decreasing" ; -# LITFALL:long_name = "litterfall (leaves and fine roots)" ; -# LITHR:long_name = "litter heterotrophic respiration" ; -# LITR1C:long_name = "LITR1 C" ; -# LITR1C_TO_SOIL1C:long_name = "decomp. of litter 1 C to soil 1 C" ; -# LITR1N:long_name = "LITR1 N" ; -# LITR1N_TNDNCY_VERT_TRANS:long_name = "litter 1 N tendency due to vertical transport" ; -# LITR1N_TO_SOIL1N:long_name = "decomp. of litter 1 N to soil 1 N" ; -# LITR1_HR:long_name = "Het. Resp. from litter 1" ; -# LITR2C:long_name = "LITR2 C" ; -# LITR2C_TO_SOIL2C:long_name = "decomp. of litter 2 C to soil 2 C" ; -# LITR2N:long_name = "LITR2 N" ; -# LITR2N_TNDNCY_VERT_TRANS:long_name = "litter 2 N tendency due to vertical transport" ; -# LITR2N_TO_SOIL2N:long_name = "decomp. of litter 2 N to soil 2 N" ; -# LITR2_HR:long_name = "Het. Resp. from litter 2" ; -# LITR3C:long_name = "LITR3 C" ; -# LITR3C_TO_SOIL3C:long_name = "decomp. of litter 3 C to soil 3 C" ; -# LITR3N:long_name = "LITR3 N" ; -# LITR3N_TNDNCY_VERT_TRANS:long_name = "litter 3 N tendency due to vertical transport" ; -# LITR3N_TO_SOIL3N:long_name = "decomp. of litter 3 N to soil 3 N" ; -# LITR3_HR:long_name = "Het. Resp. from litter 3" ; -# LITTERC:long_name = "litter C" ; -# LITTERC_HR:long_name = "litter C heterotrophic respiration" ; -# LITTERC_LOSS:long_name = "litter C loss" ; -# LIVECROOTC:long_name = "live coarse root C" ; -# LIVECROOTN:long_name = "live coarse root N" ; -# LIVESTEMC:long_name = "live stem C" ; -# LIVESTEMN:long_name = "live stem N" ; -# MEG_acetaldehyde:long_name = "MEGAN flux" ; -# MEG_acetic_acid:long_name = "MEGAN flux" ; -# MEG_acetone:long_name = "MEGAN flux" ; -# MEG_carene_3:long_name = "MEGAN flux" ; -# MEG_ethanol:long_name = "MEGAN flux" ; -# MEG_formaldehyde:long_name = "MEGAN flux" ; -# MEG_isoprene:long_name = "MEGAN flux" ; -# MEG_methanol:long_name = "MEGAN flux" ; -# MEG_pinene_a:long_name = "MEGAN flux" ; -# MEG_thujene_a:long_name = "MEGAN flux" ; -# MR:long_name = "maintenance respiration" ; -# M_LITR1C_TO_LEACHING:long_name = "litter 1 C leaching loss" ; -# M_LITR2C_TO_LEACHING:long_name = "litter 2 C leaching loss" ; -# M_LITR3C_TO_LEACHING:long_name = "litter 3 C leaching loss" ; -# M_SOIL1C_TO_LEACHING:long_name = "soil 1 C leaching loss" ; -# M_SOIL2C_TO_LEACHING:long_name = "soil 2 C leaching loss" ; -# M_SOIL3C_TO_LEACHING:long_name = "soil 3 C leaching loss" ; -# M_SOIL4C_TO_LEACHING:long_name = "soil 4 C leaching loss" ; -# NBP:long_name = "net biome production, includes fire, landuse, and harvest flux, positive for sink" ; -# NDEPLOY:long_name = "total N deployed in new growth" ; -# NDEP_TO_SMINN:long_name = "atmospheric N deposition to soil mineral N" ; -# NEE:long_name = "net ecosystem exchange of carbon, includes fire, landuse, harvest, and hrv_xsmrpool flux, positive for source" ; -# NEP:long_name = "net ecosystem production, excludes fire, landuse, and harvest flux, positive for sink" ; -# NET_NMIN:long_name = "net rate of N mineralization" ; -# NFIRE:long_name = "fire counts valid only in Reg.C" ; -# NFIX_TO_SMINN:long_name = "symbiotic/asymbiotic N fixation to soil mineral N" ; -# NPP:long_name = "net primary production" ; -# OCDEP:long_name = "total OC deposition (dry+wet) from atmosphere" ; -# O_SCALAR:long_name = "fraction by which decomposition is reduced due to anoxia" ; -# PARVEGLN:long_name = "absorbed par by vegetation at local noon" ; -# PBOT:long_name = "atmospheric pressure" ; -# PCO2:long_name = "atmospheric partial pressure of CO2" ; -# PCT_LANDUNIT:long_name = "% of each landunit on grid cell" ; -# PCT_NAT_PFT:long_name = "% of each PFT on the natural vegetation (i.e., soil) landunit" ; -# PFT_CTRUNC:long_name = "patch-level sink for C truncation" ; -# PFT_FIRE_CLOSS:long_name = "total patch-level fire C loss for non-peat fires outside land-type converted region" ; -# PFT_FIRE_NLOSS:long_name = "total pft-level fire N loss" ; -# PFT_NTRUNC:long_name = "pft-level sink for N truncation" ; -# PLANT_NDEMAND:long_name = "N flux required to support initial GPP" ; -# POTENTIAL_IMMOB:long_name = "potential N immobilization" ; -# PROD100C:long_name = "100-yr wood product C" ; -# PROD100C_LOSS:long_name = "loss from 100-yr wood product pool" ; -# PROD100N:long_name = "100-yr wood product N" ; -# PROD100N_LOSS:long_name = "loss from 100-yr wood product pool" ; -# PROD10C:long_name = "10-yr wood product C" ; -# PROD10C_LOSS:long_name = "loss from 10-yr wood product pool" ; -# PROD10N:long_name = "10-yr wood product N" ; -# PROD10N_LOSS:long_name = "loss from 10-yr wood product pool" ; -# PRODUCT_CLOSS:long_name = "total carbon loss from wood product pools" ; -# PRODUCT_NLOSS:long_name = "total N loss from wood product pools" ; -# PSNSHA:long_name = "shaded leaf photosynthesis" ; -# PSNSHADE_TO_CPOOL:long_name = "C fixation from shaded canopy" ; -# PSNSUN:long_name = "sunlit leaf photosynthesis" ; -# PSNSUN_TO_CPOOL:long_name = "C fixation from sunlit canopy" ; -# Q2M:long_name = "2m specific humidity" ; -# QBOT:long_name = "atmospheric specific humidity" ; -# QDRAI:long_name = "sub-surface drainage" ; -# QDRAI_PERCH:long_name = "perched wt drainage" ; -# QDRAI_XS:long_name = "saturation excess drainage" ; -# QDRIP:long_name = "throughfall" ; -# QFLOOD:long_name = "runoff from river flooding" ; -# QFLX_ICE_DYNBAL:long_name = "ice dynamic land cover change conversion runoff flux" ; -# QFLX_LIQ_DYNBAL:long_name = "liq dynamic land cover change conversion runoff flux" ; -# QH2OSFC:long_name = "surface water runoff" ; -# QINFL:long_name = "infiltration" ; -# QINTR:long_name = "interception" ; -# QIRRIG:long_name = "water added through irrigation" ; -# QOVER:long_name = "surface runoff" ; -# QRGWL:long_name = "surface runoff at glaciers (liquid only), wetlands, lakes" ; -# QRUNOFF:long_name = "total liquid runoff (does not include QSNWCPICE)" ; -# QRUNOFF_NODYNLNDUSE:long_name = "total liquid runoff (does not include QSNWCPICE) not including correction for land use change" ; -# QRUNOFF_R:long_name = "Rural total runoff" ; -# QRUNOFF_U:long_name = "Urban total runoff" ; -# QSNOMELT:long_name = "snow melt" ; -# QSNWCPICE:long_name = "excess snowfall due to snow capping" ; -# QSNWCPICE_NODYNLNDUSE:long_name = "excess snowfall due to snow capping not including correction for land use change" ; -# QSOIL:long_name = "Ground evaporation (soil/snow evaporation + soil/snow sublimation - dew)" ; -# QVEGE:long_name = "canopy evaporation" ; -# QVEGT:long_name = "canopy transpiration" ; -# RAIN:long_name = "atmospheric rain" ; -# RETRANSN:long_name = "plant pool of retranslocated N" ; -# RETRANSN_TO_NPOOL:long_name = "deployment of retranslocated N" ; -# RH2M:long_name = "2m relative humidity" ; -# RH2M_R:long_name = "Rural 2m specific humidity" ; -# RH2M_U:long_name = "Urban 2m relative humidity" ; -# RR:long_name = "root respiration (fine root MR + total root GR)" ; -# RSCANOPY:long_name = "canopy resistance" ; -# SABG:long_name = "solar rad absorbed by ground" ; -# SABG_PEN:long_name = "Rural solar rad penetrating top soil or snow layer" ; -# SABV:long_name = "solar rad absorbed by veg" ; -# SEEDC:long_name = "pool for seeding new Patches" ; -# SEEDN:long_name = "pool for seeding new PFTs" ; -# SMINN:long_name = "soil mineral N" ; -# SMINN_LEACHED:long_name = "soil mineral N pool loss to leaching" ; -# SMINN_TO_DENIT_L1S1:long_name = "denitrification for decomp. of litter 1to SOIL1" ; -# SMINN_TO_DENIT_L2S2:long_name = "denitrification for decomp. of litter 2to SOIL2" ; -# SMINN_TO_DENIT_L3S3:long_name = "denitrification for decomp. of litter 3to SOIL3" ; -# SMINN_TO_DENIT_S1S2:long_name = "denitrification for decomp. of soil 1to SOIL2" ; -# SMINN_TO_DENIT_S2S3:long_name = "denitrification for decomp. of soil 2to SOIL3" ; -# SMINN_TO_DENIT_S3S4:long_name = "denitrification for decomp. of soil 3to SOIL4" ; -# SMINN_TO_DENIT_S4:long_name = "denitrification for decomp. of soil 4to atmosphe" ; -# SMINN_TO_NPOOL:long_name = "deployment of soil mineral N uptake" ; -# SMINN_TO_PLANT:long_name = "plant uptake of soil mineral N" ; -# SMINN_TO_SOIL1N_L1:long_name = "mineral N flux for decomp. of LITR1to SOIL1" ; -# SMINN_TO_SOIL2N_L2:long_name = "mineral N flux for decomp. of LITR2to SOIL2" ; -# SMINN_TO_SOIL2N_S1:long_name = "mineral N flux for decomp. of SOIL1to SOIL2" ; -# SMINN_TO_SOIL3N_L3:long_name = "mineral N flux for decomp. of LITR3to SOIL3" ; -# SMINN_TO_SOIL3N_S2:long_name = "mineral N flux for decomp. of SOIL2to SOIL3" ; -# SMINN_TO_SOIL4N_S3:long_name = "mineral N flux for decomp. of SOIL3to SOIL4" ; -# SNOBCMCL:long_name = "mass of BC in snow column" ; -# SNOBCMSL:long_name = "mass of BC in top snow layer" ; -# SNODSTMCL:long_name = "mass of dust in snow column" ; -# SNODSTMSL:long_name = "mass of dust in top snow layer" ; -# SNOINTABS:long_name = "Percent of incoming solar absorbed by lower snow layers" ; -# SNOOCMCL:long_name = "mass of OC in snow column" ; -# SNOOCMSL:long_name = "mass of OC in top snow layer" ; -# SNOW:long_name = "atmospheric snow" ; -# SNOWDP:long_name = "gridcell mean snow height" ; -# SNOWICE:long_name = "snow ice" ; -# SNOWLIQ:long_name = "snow liquid water" ; -# SNOW_DEPTH:long_name = "snow height of snow covered area" ; -# SNOW_SINKS:long_name = "snow sinks (liquid water)" ; -# SNOW_SOURCES:long_name = "snow sources (liquid water)" ; -# SOIL1C:long_name = "SOIL1 C" ; -# SOIL1C_TO_SOIL2C:long_name = "decomp. of soil 1 C to soil 2 C" ; -# SOIL1N:long_name = "SOIL1 N" ; -# SOIL1N_TNDNCY_VERT_TRANS:long_name = "soil 1 N tendency due to vertical transport" ; -# SOIL1N_TO_SOIL2N:long_name = "decomp. of soil 1 N to soil 2 N" ; -# SOIL1_HR:long_name = "Het. Resp. from soil 1" ; -# SOIL2C:long_name = "SOIL2 C" ; -# SOIL2C_TO_SOIL3C:long_name = "decomp. of soil 2 C to soil 3 C" ; -# SOIL2N:long_name = "SOIL2 N" ; -# SOIL2N_TNDNCY_VERT_TRANS:long_name = "soil 2 N tendency due to vertical transport" ; -# SOIL2N_TO_SOIL3N:long_name = "decomp. of soil 2 N to soil 3 N" ; -# SOIL2_HR:long_name = "Het. Resp. from soil 2" ; -# SOIL3C:long_name = "SOIL3 C" ; -# SOIL3C_TO_SOIL4C:long_name = "decomp. of soil 3 C to soil 4 C" ; -# SOIL3N:long_name = "SOIL3 N" ; -# SOIL3N_TNDNCY_VERT_TRANS:long_name = "soil 3 N tendency due to vertical transport" ; -# SOIL3N_TO_SOIL4N:long_name = "decomp. of soil 3 N to soil 4 N" ; -# SOIL3_HR:long_name = "Het. Resp. from soil 3" ; -# SOIL4C:long_name = "SOIL4 C" ; -# SOIL4N:long_name = "SOIL4 N" ; -# SOIL4N_TNDNCY_VERT_TRANS:long_name = "soil 4 N tendency due to vertical transport" ; -# SOIL4N_TO_SMINN:long_name = "mineral N flux for decomp. of SOIL4" ; -# SOIL4_HR:long_name = "Het. Resp. from soil 4" ; -# SOILC:long_name = "soil C" ; -# SOILC_HR:long_name = "soil C heterotrophic respiration" ; -# SOILC_LOSS:long_name = "soil C loss" ; -# SOILPSI:long_name = "soil water potential in each soil layer" ; -# SOMC_FIRE:long_name = "C loss due to peat burning" ; -# SOMHR:long_name = "soil organic matter heterotrophic respiration" ; -# SOM_C_LEACHED:long_name = "total flux of C from SOM pools due to leaching" ; -# SR:long_name = "total soil respiration (HR + root resp)" ; -# STORVEGC:long_name = "stored vegetation carbon, excluding cpool" ; -# STORVEGN:long_name = "stored vegetation nitrogen" ; -# SUPPLEMENT_TO_SMINN:long_name = "supplemental N supply" ; -# SoilAlpha:long_name = "factor limiting ground evap" ; -# SoilAlpha_U:long_name = "urban factor limiting ground evap" ; -# TAUX:long_name = "zonal surface stress" ; -# TAUY:long_name = "meridional surface stress" ; -# TBOT:long_name = "atmospheric air temperature" ; -# TBUILD:long_name = "internal urban building temperature" ; -# TG:long_name = "ground temperature" ; -# TG_R:long_name = "Rural ground temperature" ; -# TG_U:long_name = "Urban ground temperature" ; -# TH2OSFC:long_name = "surface water temperature" ; -# THBOT:long_name = "atmospheric air potential temperature" ; -# TKE1:long_name = "top lake level eddy thermal conductivity" ; -# TLAI:long_name = "total projected leaf area index" ; -# TLAKE:long_name = "lake temperature" ; -# TOTCOLC:long_name = "total column carbon, incl veg and cpool" ; -# TOTCOLN:long_name = "total column-level N" ; -# TOTECOSYSC:long_name = "total ecosystem carbon, incl veg but excl cpool" ; -# TOTECOSYSN:long_name = "total ecosystem N" ; -# TOTLITC:long_name = "total litter carbon" ; -# TOTLITN:long_name = "total litter N" ; -# TOTPFTC:long_name = "total patch-level carbon, including cpool" ; -# TOTPFTN:long_name = "total PFT-level nitrogen" ; -# TOTPRODC:long_name = "total wood product C" ; -# TOTPRODN:long_name = "total wood product N" ; -# TOTSOMC:long_name = "total soil organic matter carbon" ; -# TOTSOMN:long_name = "total soil organic matter N" ; -# TOTVEGC:long_name = "total vegetation carbon, excluding cpool" ; -# TOTVEGN:long_name = "total vegetation nitrogen" ; -# TREFMNAV:long_name = "daily minimum of average 2-m temperature" ; -# TREFMNAV_R:long_name = "Rural daily minimum of average 2-m temperature" ; -# TREFMNAV_U:long_name = "Urban daily minimum of average 2-m temperature" ; -# TREFMXAV:long_name = "daily maximum of average 2-m temperature" ; -# TREFMXAV_R:long_name = "Rural daily maximum of average 2-m temperature" ; -# TREFMXAV_U:long_name = "Urban daily maximum of average 2-m temperature" ; -# TSA:long_name = "2m air temperature" ; -# TSAI:long_name = "total projected stem area index" ; -# TSA_R:long_name = "Rural 2m air temperature" ; -# TSA_U:long_name = "Urban 2m air temperature" ; -# TSOI_10CM:long_name = "soil temperature in top 10cm of soil" ; -# TV:long_name = "vegetation temperature" ; -# TWS:long_name = "total water storage" ; -# T_SCALAR:long_name = "temperature inhibition of decomposition" ; -# U10:long_name = "10-m wind" ; -# URBAN_AC:long_name = "urban air conditioning flux" ; -# URBAN_HEAT:long_name = "urban heating flux" ; -# VOCFLXT:long_name = "total VOC flux into atmosphere" ; -# VOLR:long_name = "river channel water storage" ; -# WASTEHEAT:long_name = "sensible heat flux from heating/cooling sources of urban waste heat" ; -# WF:long_name = "soil water as frac. of whc for top 0.05 m" ; -# WIND:long_name = "atmospheric wind velocity magnitude" ; -# WOODC:long_name = "wood C" ; -# WOODC_ALLOC:long_name = "wood C eallocation" ; -# WOODC_LOSS:long_name = "wood C loss" ; -# WOOD_HARVESTC:long_name = "wood harvest carbon (to product pools)" ; -# WOOD_HARVESTN:long_name = "wood harvest N (to product pools)" ; -# W_SCALAR:long_name = "Moisture (dryness) inhibition of decomposition" -## ==================================================================================================# -## EOF + if(out$dimm[[i]]==4){ # xypt + ncdf4::ncvar_put(ncout, out$var[[i]], out$dat[[i]], start=c(1,1,1,month), count=c(1,1,12,1)) + }else if (out$dimm[[i]]==3) { # xyt + ncdf4::ncvar_put(ncout, out$var[[i]], out$dat[[i]], start=c(1,1,month)) + }else{ # time_bounds + ncdf4::ncvar_put(ncout, out$var[[i]], out$dat[[i]], start=c(1,month)) + } + } + } + } ## monthly convert variable into PEcAn format + } + ## extract variable and long names to VAR file for PEcAn vis + utils::write.table(sapply(ncout$var, function(x) { x$longname }), + file = paste0(oname, ".var"), + col.names = FALSE, + row.names = TRUE, + quote = FALSE) + try(ncdf4::nc_close(ncout)) ## end of year for loop +} ## model2netcdf.FATES \ No newline at end of file From 2b75a413313787eb3532a89fe8285e0350cf8922 Mon Sep 17 00:00:00 2001 From: Yisreal Date: Fri, 12 Jul 2024 15:13:33 +0800 Subject: [PATCH 5/7] Add a package named fates --- docker-compose.yml | 13 +++++++++++++ 1 file changed, 13 insertions(+) diff --git a/docker-compose.yml b/docker-compose.yml index 75d5233c7b3..c8dcb7d373c 100644 --- a/docker-compose.yml +++ b/docker-compose.yml @@ -206,6 +206,19 @@ services: # ---------------------------------------------------------------------- # PEcAn models, list each model you want to run below # ---------------------------------------------------------------------- + # PEcAn FATES model runner + fates: + user: "${UID:-1001}:${GID:-1001}" + image: ghcr.io/noresmhub/ctsm-api:latest + restart: unless-stopped + networks: + - pecan + environment: + - RABBITMQ_URI=${RABBITMQ_URI:-amqp://guest:guest@rabbitmq/%2F} + depends_on: + - rabbitmq + volumes: + - pecan:/data # PEcAn basgra model runner basgra: From 43b9ddc995a1bbd6050eeab6b5b0326836934ed0 Mon Sep 17 00:00:00 2001 From: Yisreal Date: Fri, 12 Jul 2024 22:00:34 +0800 Subject: [PATCH 6/7] fix bugs --- docker/depends/pecan_package_dependencies.csv | 1349 +++++++++-------- models/fates/DESCRIPTION | 3 +- models/fates/R/model2netcdf.FATES.R | 89 +- 3 files changed, 723 insertions(+), 718 deletions(-) diff --git a/docker/depends/pecan_package_dependencies.csv b/docker/depends/pecan_package_dependencies.csv index c101b181f51..b076a44a51c 100644 --- a/docker/depends/pecan_package_dependencies.csv +++ b/docker/depends/pecan_package_dependencies.csv @@ -1,674 +1,675 @@ -"package","version","needed_by_dir","type","is_pecan" -"abind","*","modules/assim.batch","Imports",FALSE -"abind",">= 1.4.5","base/utils","Imports",FALSE -"abind",">= 1.4.5","models/ed","Imports",FALSE -"abind",">= 1.4.5","modules/data.atmosphere","Imports",FALSE -"amerifluxr","*","modules/data.atmosphere","Imports",FALSE -"arrow","*","modules/data.atmosphere","Imports",FALSE -"assertthat","*","models/ed","Imports",FALSE -"assertthat","*","modules/data.atmosphere","Imports",FALSE -"BayesianTools","*","modules/assim.batch","Imports",FALSE -"BayesianTools","*","modules/rtm","Imports",FALSE -"BioCro","*","models/biocro","Suggests",FALSE -"bit64","*","base/db","Suggests",FALSE -"BrownDog","*","modules/benchmark","Suggests",FALSE -"coda","*","models/maespa","Suggests",FALSE -"coda","*","models/sipnet","Suggests",FALSE -"coda","*","modules/assim.sequential","Imports",FALSE -"coda","*","modules/data.land","Imports",FALSE -"coda","*","modules/rtm","Imports",FALSE -"coda",">= 0.18","base/utils","Suggests",FALSE -"coda",">= 0.18","modules/allometry","Imports",FALSE -"coda",">= 0.18","modules/assim.batch","Imports",FALSE -"coda",">= 0.18","modules/emulator","Imports",FALSE -"coda",">= 0.18","modules/meta.analysis","Imports",FALSE -"coda",">= 0.18","modules/photosynthesis","Imports",FALSE -"corrplot","*","modules/assim.sequential","Suggests",FALSE -"curl","*","base/db","Imports",FALSE -"curl","*","base/utils","Imports",FALSE -"curl","*","modules/data.atmosphere","Imports",FALSE -"curl","*","modules/data.land","Imports",FALSE -"curl","*","modules/data.remote","Imports",FALSE -"data.table","*","base/db","Suggests",FALSE -"data.table","*","base/utils","Suggests",FALSE -"data.table","*","base/visualization","Imports",FALSE -"data.table","*","models/biocro","Imports",FALSE -"data.table","*","modules/data.remote","Suggests",FALSE -"dataone","*","modules/data.land","Suggests",FALSE -"datapack","*","modules/data.land","Imports",FALSE -"DBI","*","base/db","Imports",FALSE -"DBI","*","modules/data.remote","Imports",FALSE -"dbplyr",">= 2.4.0","base/db","Imports",FALSE -"devtools","*","models/ed","Suggests",FALSE -"doParallel","*","modules/data.atmosphere","Suggests",FALSE -"doParallel","*","modules/data.remote","Imports",FALSE -"doSNOW","*","base/remote","Suggests",FALSE -"dplR","*","modules/data.land","Imports",FALSE -"dplyr","*","base/qaqc","Imports",FALSE -"dplyr","*","base/remote","Imports",FALSE -"dplyr","*","base/utils","Imports",FALSE -"dplyr","*","base/workflow","Imports",FALSE -"dplyr","*","models/biocro","Imports",FALSE -"dplyr","*","models/ed","Imports",FALSE -"dplyr","*","models/ldndc","Imports",FALSE -"dplyr","*","models/stics","Imports",FALSE -"dplyr","*","modules/assim.sequential","Imports",FALSE -"dplyr","*","modules/benchmark","Imports",FALSE -"dplyr","*","modules/data.land","Imports",FALSE -"dplyr","*","modules/data.remote","Suggests",FALSE -"dplyr","*","modules/uncertainty","Imports",FALSE -"dplyr",">= 0.8.1","modules/data.atmosphere","Imports",FALSE -"dplyr",">= 1.1.2","base/db","Imports",FALSE -"ellipse","*","modules/assim.batch","Imports",FALSE -"emdbook","*","modules/assim.sequential","Suggests",FALSE -"foreach","*","base/remote","Imports",FALSE -"foreach","*","modules/data.atmosphere","Suggests",FALSE -"foreach","*","modules/data.remote","Imports",FALSE -"fs","*","base/db","Imports",FALSE -"fs","*","modules/data.land","Imports",FALSE -"furrr","*","base/remote","Imports",FALSE -"furrr","*","modules/assim.sequential","Imports",FALSE -"furrr","*","modules/data.atmosphere","Suggests",FALSE -"furrr","*","modules/data.land","Imports",FALSE -"furrr","*","modules/data.remote","Imports",FALSE -"future","*","modules/assim.sequential","Imports",FALSE -"future","*","modules/data.atmosphere","Suggests",FALSE -"future","*","modules/data.land","Imports",FALSE -"future","*","modules/data.remote","Imports",FALSE -"GEDI4R","*","modules/data.remote","Suggests",FALSE -"geonames","> 0.998","modules/data.atmosphere","Imports",FALSE -"getPass","*","base/remote","Suggests",FALSE -"getPass","*","modules/data.land","Suggests",FALSE -"getPass","*","modules/data.remote","Suggests",FALSE -"ggmcmc","*","modules/meta.analysis","Suggests",FALSE -"ggplot2","*","base/utils","Suggests",FALSE -"ggplot2","*","base/visualization","Imports",FALSE -"ggplot2","*","modules/assim.sequential","Imports",FALSE -"ggplot2","*","modules/benchmark","Imports",FALSE -"ggplot2","*","modules/data.atmosphere","Imports",FALSE -"ggplot2","*","modules/data.remote","Suggests",FALSE -"ggplot2","*","modules/meta.analysis","Suggests",FALSE -"ggplot2","*","modules/priors","Imports",FALSE -"ggplot2","*","modules/uncertainty","Imports",FALSE -"ggpubr","*","modules/assim.sequential","Suggests",FALSE -"ggrepel","*","modules/assim.sequential","Suggests",FALSE -"glue","*","base/db","Imports",FALSE -"glue","*","models/ed","Imports",FALSE -"glue","*","modules/assim.sequential","Suggests",FALSE -"glue","*","modules/data.atmosphere","Imports",FALSE -"glue","*","modules/data.land","Suggests",FALSE -"glue","*","modules/data.remote","Imports",FALSE -"graphics","*","base/qaqc","Imports",FALSE -"graphics","*","modules/allometry","Imports",FALSE -"graphics","*","modules/assim.batch","Imports",FALSE -"graphics","*","modules/photosynthesis","Imports",FALSE -"grDevices","*","modules/allometry","Imports",FALSE -"grDevices","*","modules/assim.batch","Imports",FALSE -"grDevices","*","modules/benchmark","Imports",FALSE -"grDevices","*","modules/data.remote","Suggests",FALSE -"grid","*","base/visualization","Suggests",FALSE -"gridExtra","*","modules/assim.sequential","Suggests",FALSE -"gridExtra","*","modules/benchmark","Imports",FALSE -"gridExtra","*","modules/uncertainty","Imports",FALSE -"hdf5r","*","models/ed","Imports",FALSE -"here","*","base/db","Suggests",FALSE -"httr","*","base/remote","Imports",FALSE -"httr","*","modules/data.atmosphere","Imports",FALSE -"httr","*","modules/data.land","Imports",FALSE -"httr","*","modules/data.remote","Suggests",FALSE -"IDPmisc","*","modules/assim.batch","Imports",FALSE -"jsonlite","*","base/remote","Imports",FALSE -"jsonlite","*","models/stics","Imports",FALSE -"jsonlite","*","modules/data.atmosphere","Imports",FALSE -"jsonlite","*","modules/data.remote","Suggests",FALSE -"knitr",">= 1.42","base/db","Suggests",FALSE -"knitr",">= 1.42","base/qaqc","Suggests",FALSE -"knitr",">= 1.42","modules/allometry","Suggests",FALSE -"knitr",">= 1.42","modules/assim.batch","Suggests",FALSE -"knitr",">= 1.42","modules/meta.analysis","Suggests",FALSE -"knitr",">= 1.42","modules/photosynthesis","Suggests",FALSE -"knitr",">= 1.42","modules/rtm","Suggests",FALSE -"lattice","*","modules/meta.analysis","Imports",FALSE -"linkages","*","models/linkages","Suggests",FALSE -"lqmm","*","modules/assim.batch","Imports",FALSE -"lubridate","*","base/db","Imports",FALSE -"lubridate","*","models/basgra","Imports",FALSE -"lubridate","*","models/dvmdostem","Imports",FALSE -"lubridate","*","models/ed","Imports",FALSE -"lubridate","*","models/ldndc","Imports",FALSE -"lubridate","*","models/stics","Imports",FALSE -"lubridate","*","modules/data.land","Imports",FALSE -"lubridate","*","modules/data.remote","Suggests",FALSE -"lubridate",">= 1.6.0","base/settings","Imports",FALSE -"lubridate",">= 1.6.0","base/utils","Imports",FALSE -"lubridate",">= 1.6.0","models/dalec","Imports",FALSE -"lubridate",">= 1.6.0","models/fates","Imports",FALSE -"lubridate",">= 1.6.0","models/gday","Imports",FALSE -"lubridate",">= 1.6.0","models/jules","Imports",FALSE -"lubridate",">= 1.6.0","models/linkages","Imports",FALSE -"lubridate",">= 1.6.0","models/lpjguess","Imports",FALSE -"lubridate",">= 1.6.0","models/maat","Imports",FALSE -"lubridate",">= 1.6.0","models/maespa","Imports",FALSE -"lubridate",">= 1.6.0","models/preles","Imports",FALSE -"lubridate",">= 1.6.0","models/sipnet","Imports",FALSE -"lubridate",">= 1.6.0","modules/assim.batch","Imports",FALSE -"lubridate",">= 1.6.0","modules/assim.sequential","Imports",FALSE -"lubridate",">= 1.6.0","modules/benchmark","Imports",FALSE -"lubridate",">= 1.6.0","modules/data.atmosphere","Imports",FALSE -"lubridate",">= 1.6.0","modules/rtm","Imports",FALSE -"lubridate",">= 1.7.0","models/biocro","Imports",FALSE -"Maeswrap","*","models/maespa","Suggests",FALSE -"magic",">= 1.5.0","modules/assim.sequential","Suggests",FALSE -"magrittr","*","base/db","Imports",FALSE -"magrittr","*","base/utils","Imports",FALSE -"magrittr","*","models/ed","Imports",FALSE -"magrittr","*","modules/assim.sequential","Imports",FALSE -"magrittr","*","modules/benchmark","Imports",FALSE -"magrittr","*","modules/data.land","Imports",FALSE -"magrittr","*","modules/data.remote","Imports",FALSE -"markdown","*","modules/allometry","Suggests",FALSE -"markdown","*","modules/photosynthesis","Suggests",FALSE -"MASS","*","base/utils","Suggests",FALSE -"MASS","*","modules/assim.batch","Imports",FALSE -"MASS","*","modules/data.atmosphere","Imports",FALSE -"MASS","*","modules/meta.analysis","Imports",FALSE -"MASS","*","modules/priors","Imports",FALSE -"MASS","*","modules/rtm","Imports",FALSE -"Matrix","*","modules/assim.sequential","Imports",FALSE -"mclust","*","modules/rtm","Suggests",FALSE -"MCMCpack","*","modules/allometry","Imports",FALSE -"MCMCpack","*","modules/assim.batch","Imports",FALSE -"MCMCpack","*","modules/emulator","Imports",FALSE -"methods","*","base/db","Imports",FALSE -"methods","*","base/settings","Depends",FALSE -"methods","*","modules/allometry","Imports",FALSE -"methods","*","modules/assim.batch","Imports",FALSE -"methods","*","modules/assim.sequential","Suggests",FALSE -"methods","*","modules/emulator","Imports",FALSE -"mgcv","*","modules/data.atmosphere","Imports",FALSE -"minpack.lm","*","modules/rtm","Suggests",FALSE -"mlegp","*","modules/assim.batch","Imports",FALSE -"mockery","*","base/all","Suggests",FALSE -"mockery","*","base/qaqc","Suggests",FALSE -"mockery","*","base/remote","Suggests",FALSE -"mockery","*","base/settings","Suggests",FALSE -"mockery","*","base/utils","Suggests",FALSE -"mockery","*","base/visualization","Suggests",FALSE -"mockery","*","base/workflow","Suggests",FALSE -"mockery","*","modules/data.atmosphere","Suggests",FALSE -"mockery",">= 0.3.0","models/biocro","Suggests",FALSE -"mockery",">= 0.4.3","base/db","Suggests",FALSE -"MODISTools",">= 1.1.0","modules/data.remote","Imports",FALSE -"mvbutils","*","base/qaqc","Suggests",FALSE -"mvtnorm","*","modules/allometry","Imports",FALSE -"mvtnorm","*","modules/assim.batch","Imports",FALSE -"mvtnorm","*","modules/assim.sequential","Imports",FALSE -"mvtnorm","*","modules/data.land","Imports",FALSE -"mvtnorm","*","modules/emulator","Imports",FALSE -"ncdf4","*","base/db","Imports",FALSE -"ncdf4","*","models/basgra","Imports",FALSE -"ncdf4","*","models/dvmdostem","Imports",FALSE -"ncdf4","*","models/ldndc","Imports",FALSE -"ncdf4","*","models/sibcasa","Imports",FALSE -"ncdf4","*","models/stics","Imports",FALSE -"ncdf4","*","modules/assim.sequential","Imports",FALSE -"ncdf4","*","modules/data.remote","Imports",FALSE -"ncdf4",">= 1.15","base/utils","Imports",FALSE -"ncdf4",">= 1.15","base/visualization","Imports",FALSE -"ncdf4",">= 1.15","models/biocro","Imports",FALSE -"ncdf4",">= 1.15","models/clm45","Imports",FALSE -"ncdf4",">= 1.15","models/dalec","Imports",FALSE -"ncdf4",">= 1.15","models/ed","Imports",FALSE -"ncdf4",">= 1.15","models/fates","Imports",FALSE -"ncdf4",">= 1.15","models/gday","Imports",FALSE -"ncdf4",">= 1.15","models/jules","Imports",FALSE -"ncdf4",">= 1.15","models/linkages","Imports",FALSE -"ncdf4",">= 1.15","models/lpjguess","Imports",FALSE -"ncdf4",">= 1.15","models/maat","Imports",FALSE -"ncdf4",">= 1.15","models/maespa","Imports",FALSE -"ncdf4",">= 1.15","models/preles","Imports",FALSE -"ncdf4",">= 1.15","models/sipnet","Imports",FALSE -"ncdf4",">= 1.15","modules/assim.batch","Imports",FALSE -"ncdf4",">= 1.15","modules/benchmark","Imports",FALSE -"ncdf4",">= 1.15","modules/data.atmosphere","Imports",FALSE -"ncdf4",">= 1.15","modules/data.land","Imports",FALSE -"neonstore","*","modules/data.land","Imports",FALSE -"neonUtilities","*","modules/data.land","Imports",FALSE -"nimble","*","modules/assim.sequential","Imports",FALSE -"nneo","*","modules/data.atmosphere","Imports",FALSE -"optparse","*","base/settings","Imports",FALSE -"parallel","*","modules/assim.batch","Imports",FALSE -"parallel","*","modules/data.atmosphere","Suggests",FALSE -"parallel","*","modules/data.remote","Imports",FALSE -"PEcAn.allometry","*","base/all","Suggests",TRUE -"PEcAn.assim.batch","*","base/all","Depends",TRUE -"PEcAn.assim.batch","*","modules/rtm","Imports",TRUE -"PEcAn.benchmark","*","base/all","Depends",TRUE -"PEcAn.benchmark","*","modules/assim.batch","Imports",TRUE -"PEcAn.benchmark","*","modules/assim.sequential","Suggests",TRUE -"PEcAn.benchmark","*","modules/data.land","Imports",TRUE -"PEcAn.BIOCRO","*","base/all","Suggests",TRUE -"PEcAn.BIOCRO","*","base/qaqc","Suggests",TRUE -"PEcAn.DALEC","*","base/all","Suggests",TRUE -"PEcAn.data.atmosphere","*","base/all","Depends",TRUE -"PEcAn.data.atmosphere","*","base/workflow","Imports",TRUE -"PEcAn.data.atmosphere","*","models/basgra","Imports",TRUE -"PEcAn.data.atmosphere","*","models/biocro","Imports",TRUE -"PEcAn.data.atmosphere","*","models/ed","Imports",TRUE -"PEcAn.data.atmosphere","*","models/jules","Imports",TRUE -"PEcAn.data.atmosphere","*","models/ldndc","Imports",TRUE -"PEcAn.data.atmosphere","*","models/linkages","Imports",TRUE -"PEcAn.data.atmosphere","*","models/maat","Imports",TRUE -"PEcAn.data.atmosphere","*","models/maespa","Imports",TRUE -"PEcAn.data.atmosphere","*","models/preles","Imports",TRUE -"PEcAn.data.atmosphere","*","models/sipnet","Depends",TRUE -"PEcAn.data.land","*","base/all","Depends",TRUE -"PEcAn.data.land","*","base/workflow","Imports",TRUE -"PEcAn.data.land","*","models/biocro","Imports",TRUE -"PEcAn.data.land","*","models/ed","Imports",TRUE -"PEcAn.data.land","*","models/ldndc","Imports",TRUE -"PEcAn.data.land","*","modules/assim.sequential","Suggests",TRUE -"PEcAn.data.land","*","modules/benchmark","Suggests",TRUE -"PEcAn.data.remote","*","base/all","Depends",TRUE -"PEcAn.data.remote","*","modules/assim.sequential","Suggests",TRUE -"PEcAn.DB","*","base/all","Depends",TRUE -"PEcAn.DB","*","base/qaqc","Imports",TRUE -"PEcAn.DB","*","base/settings","Imports",TRUE -"PEcAn.DB","*","base/workflow","Imports",TRUE -"PEcAn.DB","*","models/biocro","Suggests",TRUE -"PEcAn.DB","*","models/template","Imports",TRUE -"PEcAn.DB","*","modules/allometry","Imports",TRUE -"PEcAn.DB","*","modules/assim.batch","Imports",TRUE -"PEcAn.DB","*","modules/assim.sequential","Imports",TRUE -"PEcAn.DB","*","modules/benchmark","Imports",TRUE -"PEcAn.DB","*","modules/data.atmosphere","Imports",TRUE -"PEcAn.DB","*","modules/data.land","Imports",TRUE -"PEcAn.DB","*","modules/data.remote","Imports",TRUE -"PEcAn.DB","*","modules/meta.analysis","Imports",TRUE -"PEcAn.DB","*","modules/uncertainty","Imports",TRUE -"PEcAn.ED2","*","base/all","Suggests",TRUE -"PEcAn.ED2","*","base/qaqc","Suggests",TRUE -"PEcAn.ED2","*","modules/rtm","Suggests",TRUE -"PEcAn.emulator","*","base/all","Depends",TRUE -"PEcAn.emulator","*","modules/assim.batch","Imports",TRUE -"PEcAn.emulator","*","modules/uncertainty","Imports",TRUE -"PEcAn.LINKAGES","*","base/all","Suggests",TRUE -"PEcAn.logger","*","base/all","Depends",TRUE -"PEcAn.logger","*","base/db","Imports",TRUE -"PEcAn.logger","*","base/qaqc","Imports",TRUE -"PEcAn.logger","*","base/remote","Imports",TRUE -"PEcAn.logger","*","base/settings","Imports",TRUE -"PEcAn.logger","*","base/utils","Imports",TRUE -"PEcAn.logger","*","base/visualization","Imports",TRUE -"PEcAn.logger","*","base/workflow","Imports",TRUE -"PEcAn.logger","*","models/basgra","Imports",TRUE -"PEcAn.logger","*","models/biocro","Imports",TRUE -"PEcAn.logger","*","models/cable","Imports",TRUE -"PEcAn.logger","*","models/clm45","Depends",TRUE -"PEcAn.logger","*","models/dalec","Imports",TRUE -"PEcAn.logger","*","models/dvmdostem","Imports",TRUE -"PEcAn.logger","*","models/ed","Imports",TRUE -"PEcAn.logger","*","models/fates","Imports",TRUE -"PEcAn.logger","*","models/gday","Imports",TRUE -"PEcAn.logger","*","models/jules","Imports",TRUE -"PEcAn.logger","*","models/ldndc","Imports",TRUE -"PEcAn.logger","*","models/linkages","Imports",TRUE -"PEcAn.logger","*","models/lpjguess","Imports",TRUE -"PEcAn.logger","*","models/maat","Imports",TRUE -"PEcAn.logger","*","models/maespa","Imports",TRUE -"PEcAn.logger","*","models/preles","Imports",TRUE -"PEcAn.logger","*","models/sibcasa","Imports",TRUE -"PEcAn.logger","*","models/sipnet","Imports",TRUE -"PEcAn.logger","*","models/stics","Imports",TRUE -"PEcAn.logger","*","models/template","Imports",TRUE -"PEcAn.logger","*","modules/assim.batch","Imports",TRUE -"PEcAn.logger","*","modules/assim.sequential","Imports",TRUE -"PEcAn.logger","*","modules/benchmark","Imports",TRUE -"PEcAn.logger","*","modules/data.atmosphere","Imports",TRUE -"PEcAn.logger","*","modules/data.land","Imports",TRUE -"PEcAn.logger","*","modules/data.remote","Imports",TRUE -"PEcAn.logger","*","modules/meta.analysis","Imports",TRUE -"PEcAn.logger","*","modules/priors","Imports",TRUE -"PEcAn.logger","*","modules/rtm","Imports",TRUE -"PEcAn.logger","*","modules/uncertainty","Imports",TRUE -"PEcAn.MA","*","base/all","Depends",TRUE -"PEcAn.MA","*","modules/assim.batch","Imports",TRUE -"PEcAn.MA","*","modules/priors","Imports",TRUE -"PEcAn.photosynthesis","*","base/all","Suggests",TRUE -"PEcAn.priors","*","base/all","Depends",TRUE -"PEcAn.priors","*","modules/uncertainty","Imports",TRUE -"PEcAn.remote","*","base/all","Depends",TRUE -"PEcAn.remote","*","base/db","Imports",TRUE -"PEcAn.remote","*","base/settings","Imports",TRUE -"PEcAn.remote","*","base/workflow","Imports",TRUE -"PEcAn.remote","*","models/biocro","Imports",TRUE -"PEcAn.remote","*","models/dalec","Imports",TRUE -"PEcAn.remote","*","models/ed","Imports",TRUE -"PEcAn.remote","*","models/fates","Imports",TRUE -"PEcAn.remote","*","models/gday","Imports",TRUE -"PEcAn.remote","*","models/jules","Imports",TRUE -"PEcAn.remote","*","models/ldndc","Imports",TRUE -"PEcAn.remote","*","models/linkages","Imports",TRUE -"PEcAn.remote","*","models/lpjguess","Imports",TRUE -"PEcAn.remote","*","models/maat","Imports",TRUE -"PEcAn.remote","*","models/maespa","Imports",TRUE -"PEcAn.remote","*","models/sipnet","Imports",TRUE -"PEcAn.remote","*","models/stics","Imports",TRUE -"PEcAn.remote","*","modules/assim.batch","Imports",TRUE -"PEcAn.remote","*","modules/assim.sequential","Imports",TRUE -"PEcAn.remote","*","modules/data.atmosphere","Imports",TRUE -"PEcAn.remote","*","modules/data.land","Imports",TRUE -"PEcAn.remote","*","modules/data.remote","Imports",TRUE -"PEcAn.settings","*","base/all","Depends",TRUE -"PEcAn.settings","*","base/workflow","Imports",TRUE -"PEcAn.settings","*","models/biocro","Imports",TRUE -"PEcAn.settings","*","models/ed","Imports",TRUE -"PEcAn.settings","*","models/maat","Imports",TRUE -"PEcAn.settings","*","models/stics","Imports",TRUE -"PEcAn.settings","*","modules/assim.batch","Imports",TRUE -"PEcAn.settings","*","modules/assim.sequential","Imports",TRUE -"PEcAn.settings","*","modules/benchmark","Imports",TRUE -"PEcAn.settings","*","modules/data.atmosphere","Suggests",TRUE -"PEcAn.settings","*","modules/data.land","Suggests",TRUE -"PEcAn.settings","*","modules/meta.analysis","Imports",TRUE -"PEcAn.settings","*","modules/uncertainty","Imports",TRUE -"PEcAn.SIPNET","*","base/all","Suggests",TRUE -"PEcAn.SIPNET","*","base/qaqc","Suggests",TRUE -"PEcAn.uncertainty","*","base/all","Depends",TRUE -"PEcAn.uncertainty","*","base/workflow","Imports",TRUE -"PEcAn.uncertainty","*","modules/assim.batch","Imports",TRUE -"PEcAn.uncertainty","*","modules/assim.sequential","Imports",TRUE -"PEcAn.utils","*","base/all","Depends",TRUE -"PEcAn.utils","*","base/db","Imports",TRUE -"PEcAn.utils","*","base/qaqc","Suggests",TRUE -"PEcAn.utils","*","base/settings","Imports",TRUE -"PEcAn.utils","*","base/workflow","Imports",TRUE -"PEcAn.utils","*","models/biocro","Imports",TRUE -"PEcAn.utils","*","models/clm45","Depends",TRUE -"PEcAn.utils","*","models/dalec","Imports",TRUE -"PEcAn.utils","*","models/ed","Imports",TRUE -"PEcAn.utils","*","models/fates","Imports",TRUE -"PEcAn.utils","*","models/gday","Depends",TRUE -"PEcAn.utils","*","models/jules","Imports",TRUE -"PEcAn.utils","*","models/linkages","Depends",TRUE -"PEcAn.utils","*","models/lpjguess","Imports",TRUE -"PEcAn.utils","*","models/maat","Imports",TRUE -"PEcAn.utils","*","models/maespa","Imports",TRUE -"PEcAn.utils","*","models/preles","Depends",TRUE -"PEcAn.utils","*","models/preles","Imports",TRUE -"PEcAn.utils","*","models/sipnet","Imports",TRUE -"PEcAn.utils","*","modules/assim.batch","Imports",TRUE -"PEcAn.utils","*","modules/assim.sequential","Suggests",TRUE -"PEcAn.utils","*","modules/benchmark","Imports",TRUE -"PEcAn.utils","*","modules/data.atmosphere","Imports",TRUE -"PEcAn.utils","*","modules/data.land","Imports",TRUE -"PEcAn.utils","*","modules/data.remote","Imports",TRUE -"PEcAn.utils","*","modules/meta.analysis","Imports",TRUE -"PEcAn.utils","*","modules/rtm","Suggests",TRUE -"PEcAn.utils","*","modules/uncertainty","Imports",TRUE -"PEcAn.utils",">= 1.4.8","models/basgra","Imports",TRUE -"PEcAn.utils",">= 1.4.8","models/cable","Imports",TRUE -"PEcAn.utils",">= 1.4.8","models/dvmdostem","Imports",TRUE -"PEcAn.utils",">= 1.4.8","models/ldndc","Imports",TRUE -"PEcAn.utils",">= 1.4.8","models/sibcasa","Imports",TRUE -"PEcAn.utils",">= 1.4.8","models/stics","Imports",TRUE -"PEcAn.utils",">= 1.4.8","models/template","Imports",TRUE -"PEcAn.visualization","*","modules/assim.sequential","Suggests",TRUE -"PEcAn.visualization","*","modules/data.land","Imports",TRUE -"PEcAn.visualization","*","modules/priors","Suggests",TRUE -"PEcAn.workflow","*","base/all","Depends",TRUE -"PEcAn.workflow","*","modules/assim.batch","Imports",TRUE -"PEcAn.workflow","*","modules/assim.sequential","Imports",TRUE -"plotrix","*","base/qaqc","Imports",FALSE -"plotrix","*","modules/assim.sequential","Suggests",FALSE -"plyr",">= 1.8.4","base/visualization","Imports",FALSE -"plyr",">= 1.8.4","modules/assim.sequential","Suggests",FALSE -"plyr",">= 1.8.4","modules/uncertainty","Imports",FALSE -"png","*","base/visualization","Suggests",FALSE -"prodlim","*","modules/assim.batch","Imports",FALSE -"progress","*","modules/data.atmosphere","Suggests",FALSE -"purrr","*","base/db","Imports",FALSE -"purrr","*","base/settings","Imports",FALSE -"purrr","*","base/utils","Imports",FALSE -"purrr","*","models/ed","Imports",FALSE -"purrr","*","modules/assim.sequential","Imports",FALSE -"purrr","*","modules/data.land","Imports",FALSE -"purrr","*","modules/data.remote","Imports",FALSE -"purrr","*","modules/uncertainty","Imports",FALSE -"purrr",">= 0.2.3","base/workflow","Imports",FALSE -"purrr",">= 0.2.3","modules/data.atmosphere","Imports",FALSE -"pwr","*","modules/rtm","Suggests",FALSE -"R.utils","*","base/db","Imports",FALSE -"randomForest","*","modules/assim.sequential","Suggests",FALSE -"randtoolbox","*","base/utils","Suggests",FALSE -"randtoolbox","*","modules/uncertainty","Imports",FALSE -"raster","*","base/visualization","Suggests",FALSE -"raster","*","modules/assim.sequential","Suggests",FALSE -"raster","*","modules/data.atmosphere","Imports",FALSE -"raster","*","modules/data.land","Suggests",FALSE -"raster","*","modules/data.remote","Suggests",FALSE -"rcrossref","*","base/db","Suggests",FALSE -"readr","*","models/ldndc","Imports",FALSE -"readr","*","modules/assim.sequential","Suggests",FALSE -"REddyProc","*","modules/data.atmosphere","Imports",FALSE -"redland","*","modules/data.land","Suggests",FALSE -"reshape","*","modules/data.remote","Suggests",FALSE -"reshape2","*","base/visualization","Imports",FALSE -"reshape2","*","modules/benchmark","Imports",FALSE -"reshape2","*","modules/data.atmosphere","Imports",FALSE -"reshape2",">= 1.4.2","modules/assim.sequential","Suggests",FALSE -"reticulate","*","modules/data.atmosphere","Suggests",FALSE -"reticulate","*","modules/data.land","Suggests",FALSE -"reticulate","*","modules/data.remote","Imports",FALSE -"rjags","*","base/utils","Suggests",FALSE -"rjags","*","modules/assim.batch","Imports",FALSE -"rjags","*","modules/data.land","Imports",FALSE -"rjags","*","modules/meta.analysis","Imports",FALSE -"rjags","*","modules/photosynthesis","Depends",FALSE -"rjson","*","models/dvmdostem","Imports",FALSE -"rlang","*","base/db","Imports",FALSE -"rlang","*","base/qaqc","Imports",FALSE -"rlang","*","base/utils","Imports",FALSE -"rlang","*","base/visualization","Imports",FALSE -"rlang","*","models/biocro","Imports",FALSE -"rlang","*","models/ed","Imports",FALSE -"rlang","*","models/ldndc","Imports",FALSE -"rlang","*","modules/assim.sequential","Imports",FALSE -"rlang","*","modules/benchmark","Imports",FALSE -"rlang","*","modules/data.land","Imports",FALSE -"rlang","*","modules/data.remote","Imports",FALSE -"rlang","*","modules/uncertainty","Imports",FALSE -"rlang",">= 0.2.0","modules/data.atmosphere","Imports",FALSE -"rlist","*","modules/assim.sequential","Suggests",FALSE -"rmarkdown",">= 2.19","base/db","Suggests",FALSE -"rmarkdown",">= 2.19","base/qaqc","Suggests",FALSE -"rmarkdown",">= 2.19","modules/allometry","Suggests",FALSE -"rmarkdown",">= 2.19","modules/assim.batch","Suggests",FALSE -"rmarkdown",">= 2.19","modules/meta.analysis","Suggests",FALSE -"rmarkdown",">= 2.19","modules/photosynthesis","Suggests",FALSE -"roxygen2","== 7.3.2","base/all","Roxygen",FALSE -"roxygen2","== 7.3.2","base/db","Roxygen",FALSE -"roxygen2","== 7.3.2","base/logger","Roxygen",FALSE -"roxygen2","== 7.3.2","base/qaqc","Roxygen",FALSE -"roxygen2","== 7.3.2","base/remote","Roxygen",FALSE -"roxygen2","== 7.3.2","base/settings","Roxygen",FALSE -"roxygen2","== 7.3.2","base/utils","Roxygen",FALSE -"roxygen2","== 7.3.2","base/visualization","Roxygen",FALSE -"roxygen2","== 7.3.2","base/workflow","Roxygen",FALSE -"roxygen2","== 7.3.2","models/basgra","Roxygen",FALSE -"roxygen2","== 7.3.2","models/biocro","Roxygen",FALSE -"roxygen2","== 7.3.2","models/cable","Roxygen",FALSE -"roxygen2","== 7.3.2","models/clm45","Roxygen",FALSE -"roxygen2","== 7.3.2","models/dalec","Roxygen",FALSE -"roxygen2","== 7.3.2","models/dvmdostem","Roxygen",FALSE -"roxygen2","== 7.3.2","models/ed","Roxygen",FALSE -"roxygen2","== 7.3.2","models/fates","Roxygen",FALSE -"roxygen2","== 7.3.2","models/gday","Roxygen",FALSE -"roxygen2","== 7.3.2","models/jules","Roxygen",FALSE -"roxygen2","== 7.3.2","models/ldndc","Roxygen",FALSE -"roxygen2","== 7.3.2","models/linkages","Roxygen",FALSE -"roxygen2","== 7.3.2","models/lpjguess","Roxygen",FALSE -"roxygen2","== 7.3.2","models/maat","Roxygen",FALSE -"roxygen2","== 7.3.2","models/maespa","Roxygen",FALSE -"roxygen2","== 7.3.2","models/preles","Roxygen",FALSE -"roxygen2","== 7.3.2","models/sibcasa","Roxygen",FALSE -"roxygen2","== 7.3.2","models/sipnet","Roxygen",FALSE -"roxygen2","== 7.3.2","models/stics","Roxygen",FALSE -"roxygen2","== 7.3.2","models/template","Roxygen",FALSE -"roxygen2","== 7.3.2","modules/allometry","Roxygen",FALSE -"roxygen2","== 7.3.2","modules/assim.batch","Roxygen",FALSE -"roxygen2","== 7.3.2","modules/assim.sequential","Roxygen",FALSE -"roxygen2","== 7.3.2","modules/benchmark","Roxygen",FALSE -"roxygen2","== 7.3.2","modules/data.atmosphere","Roxygen",FALSE -"roxygen2","== 7.3.2","modules/data.land","Roxygen",FALSE -"roxygen2","== 7.3.2","modules/data.remote","Roxygen",FALSE -"roxygen2","== 7.3.2","modules/emulator","Roxygen",FALSE -"roxygen2","== 7.3.2","modules/meta.analysis","Roxygen",FALSE -"roxygen2","== 7.3.2","modules/photosynthesis","Roxygen",FALSE -"roxygen2","== 7.3.2","modules/priors","Roxygen",FALSE -"roxygen2","== 7.3.2","modules/rtm","Roxygen",FALSE -"roxygen2","== 7.3.2","modules/uncertainty","Roxygen",FALSE -"RPostgres","*","base/db","Suggests",FALSE -"RPostgreSQL","*","base/db","Suggests",FALSE -"RPostgreSQL","*","models/biocro","Suggests",FALSE -"Rpreles","*","models/preles","Suggests",FALSE -"RSQLite","*","base/db","Suggests",FALSE -"sessioninfo","*","base/all","Suggests",FALSE -"sf","*","modules/assim.sequential","Suggests",FALSE -"sf","*","modules/data.atmosphere","Imports",FALSE -"sf","*","modules/data.land","Imports",FALSE -"sf","*","modules/data.remote","Suggests",FALSE -"SimilarityMeasures","*","modules/benchmark","Imports",FALSE -"sirt","*","modules/data.land","Imports",FALSE -"sp","*","base/visualization","Suggests",FALSE -"sp","*","modules/assim.sequential","Suggests",FALSE -"sp","*","modules/data.atmosphere","Imports",FALSE -"sp","*","modules/data.land","Imports",FALSE -"sp","*","modules/data.remote","Imports",FALSE -"stats","*","base/qaqc","Imports",FALSE -"stats","*","modules/allometry","Imports",FALSE -"stats","*","modules/assim.batch","Imports",FALSE -"stats","*","modules/assim.sequential","Suggests",FALSE -"stats","*","modules/photosynthesis","Imports",FALSE -"SticsRFiles","*","models/stics","Suggests",FALSE -"stringi","*","base/logger","Imports",FALSE -"stringi","*","base/utils","Imports",FALSE -"stringr","*","models/fates","Imports",FALSE -"stringr","*","modules/assim.sequential","Imports",FALSE -"stringr","*","modules/benchmark","Imports",FALSE -"stringr","*","modules/data.land","Imports",FALSE -"stringr",">= 1.1.0","base/visualization","Imports",FALSE -"stringr",">= 1.1.0","models/ed","Imports",FALSE -"stringr",">= 1.1.0","modules/data.atmosphere","Imports",FALSE -"suntools","*","modules/data.atmosphere","Imports",FALSE -"swfscMisc","*","modules/data.land","Imports",FALSE -"terra","*","modules/assim.sequential","Suggests",FALSE -"terra","*","modules/data.atmosphere","Imports",FALSE -"terra","*","modules/data.land","Imports",FALSE -"terra","*","modules/data.remote","Imports",FALSE -"testthat","*","base/all","Suggests",FALSE -"testthat","*","base/logger","Suggests",FALSE -"testthat","*","base/remote","Suggests",FALSE -"testthat","*","base/workflow","Suggests",FALSE -"testthat","*","modules/assim.sequential","Suggests",FALSE -"testthat","*","modules/priors","Suggests",FALSE -"testthat",">= 1.0.2","base/visualization","Suggests",FALSE -"testthat",">= 1.0.2","models/basgra","Suggests",FALSE -"testthat",">= 1.0.2","models/cable","Suggests",FALSE -"testthat",">= 1.0.2","models/clm45","Suggests",FALSE -"testthat",">= 1.0.2","models/dalec","Suggests",FALSE -"testthat",">= 1.0.2","models/dvmdostem","Suggests",FALSE -"testthat",">= 1.0.2","models/ed","Suggests",FALSE -"testthat",">= 1.0.2","models/fates","Suggests",FALSE -"testthat",">= 1.0.2","models/gday","Suggests",FALSE -"testthat",">= 1.0.2","models/jules","Suggests",FALSE -"testthat",">= 1.0.2","models/ldndc","Suggests",FALSE -"testthat",">= 1.0.2","models/linkages","Suggests",FALSE -"testthat",">= 1.0.2","models/lpjguess","Suggests",FALSE -"testthat",">= 1.0.2","models/maat","Suggests",FALSE -"testthat",">= 1.0.2","models/maespa","Suggests",FALSE -"testthat",">= 1.0.2","models/preles","Suggests",FALSE -"testthat",">= 1.0.2","models/sipnet","Suggests",FALSE -"testthat",">= 1.0.2","models/stics","Suggests",FALSE -"testthat",">= 1.0.2","models/template","Suggests",FALSE -"testthat",">= 1.0.2","modules/allometry","Suggests",FALSE -"testthat",">= 1.0.2","modules/assim.batch","Suggests",FALSE -"testthat",">= 1.0.2","modules/data.land","Suggests",FALSE -"testthat",">= 1.0.2","modules/data.remote","Suggests",FALSE -"testthat",">= 1.0.2","modules/meta.analysis","Suggests",FALSE -"testthat",">= 1.0.2","modules/rtm","Suggests",FALSE -"testthat",">= 1.0.2","modules/uncertainty","Suggests",FALSE -"testthat",">= 2.0.0","base/db","Suggests",FALSE -"testthat",">= 2.0.0","base/settings","Suggests",FALSE -"testthat",">= 2.0.0","base/utils","Suggests",FALSE -"testthat",">= 2.0.0","models/biocro","Suggests",FALSE -"testthat",">= 2.0.0","modules/benchmark","Suggests",FALSE -"testthat",">= 2.0.0","modules/data.atmosphere","Suggests",FALSE -"testthat",">= 3.0.0","models/sibcasa","Suggests",FALSE -"testthat",">= 3.0.4","base/qaqc","Suggests",FALSE -"tibble","*","base/db","Imports",FALSE -"tibble","*","models/ed","Imports",FALSE -"tibble","*","models/lpjguess","Imports",FALSE -"tibble","*","modules/data.atmosphere","Imports",FALSE -"tibble","*","modules/data.remote","Suggests",FALSE -"tictoc","*","modules/assim.sequential","Suggests",FALSE -"tidyr","*","base/db","Imports",FALSE -"tidyr","*","models/ed","Imports",FALSE -"tidyr","*","modules/assim.sequential","Suggests",FALSE -"tidyr","*","modules/data.atmosphere","Imports",FALSE -"tidyr","*","modules/data.land","Imports",FALSE -"tidyselect","*","modules/benchmark","Imports",FALSE -"tidyselect","*","modules/data.atmosphere","Imports",FALSE -"tidyselect","*","modules/data.land","Imports",FALSE -"tidyverse","*","base/db","Suggests",FALSE -"tools","*","base/remote","Suggests",FALSE -"tools","*","modules/allometry","Imports",FALSE -"traits","*","modules/data.land","Imports",FALSE -"TruncatedNormal",">= 2.2","modules/assim.batch","Imports",FALSE -"truncnorm","*","modules/data.atmosphere","Imports",FALSE -"units","*","base/db","Imports",FALSE -"units","*","base/utils","Imports",FALSE -"units","*","modules/benchmark","Imports",FALSE -"units","*","modules/data.atmosphere","Imports",FALSE -"urltools","*","base/remote","Imports",FALSE -"utils","*","base/all","Imports",FALSE -"utils","*","base/logger","Imports",FALSE -"utils","*","models/ed","Imports",FALSE -"utils","*","modules/allometry","Imports",FALSE -"utils","*","modules/assim.batch","Imports",FALSE -"utils","*","modules/assim.sequential","Suggests",FALSE -"utils","*","modules/benchmark","Imports",FALSE -"utils","*","modules/data.remote","Suggests",FALSE -"utils","*","modules/photosynthesis","Imports",FALSE -"vdiffr",">= 1.0.2","base/qaqc","Suggests",FALSE -"withr","*","base/db","Suggests",FALSE -"withr","*","base/logger","Suggests",FALSE -"withr","*","base/qaqc","Suggests",FALSE -"withr","*","base/remote","Suggests",FALSE -"withr","*","base/settings","Suggests",FALSE -"withr","*","base/utils","Suggests",FALSE -"withr","*","base/visualization","Suggests",FALSE -"withr","*","base/workflow","Suggests",FALSE -"withr","*","models/basgra","Suggests",FALSE -"withr","*","models/ed","Suggests",FALSE -"withr","*","models/sibcasa","Suggests",FALSE -"withr","*","modules/allometry","Suggests",FALSE -"withr","*","modules/data.atmosphere","Suggests",FALSE -"XML","*","base/db","Imports",FALSE -"XML","*","base/workflow","Imports",FALSE -"XML","*","models/biocro","Imports",FALSE -"XML","*","models/maat","Imports",FALSE -"XML","*","models/stics","Imports",FALSE -"XML","*","modules/assim.batch","Imports",FALSE -"XML","*","modules/assim.sequential","Suggests",FALSE -"XML","*","modules/data.remote","Imports",FALSE -"XML","*","modules/rtm","Suggests",FALSE -"XML",">= 3.98-1.3","base/settings","Imports",FALSE -"XML",">= 3.98-1.4","models/ed","Imports",FALSE -"XML",">= 3.98-1.4","modules/benchmark","Imports",FALSE -"XML",">= 3.98-1.4","modules/data.atmosphere","Imports",FALSE -"XML",">= 3.98-1.4","modules/data.land","Imports",FALSE -"xtable","*","base/utils","Suggests",FALSE -"xts","*","modules/data.atmosphere","Imports",FALSE -"zoo","*","modules/benchmark","Imports",FALSE -"zoo","*","modules/data.atmosphere","Imports",FALSE +package,version,needed_by_dir,type,is_pecan +abind,*,modules/assim.batch,Imports,FALSE +abind,>= 1.4.5,base/utils,Imports,FALSE +abind,>= 1.4.5,models/ed,Imports,FALSE +abind,>= 1.4.5,modules/data.atmosphere,Imports,FALSE +amerifluxr,*,modules/data.atmosphere,Imports,FALSE +arrow,*,modules/data.atmosphere,Imports,FALSE +assertthat,*,models/ed,Imports,FALSE +assertthat,*,modules/data.atmosphere,Imports,FALSE +BayesianTools,*,modules/assim.batch,Imports,FALSE +BayesianTools,*,modules/rtm,Imports,FALSE +BioCro,*,models/biocro,Suggests,FALSE +bit64,*,base/db,Suggests,FALSE +BrownDog,*,modules/benchmark,Suggests,FALSE +coda,*,models/maespa,Suggests,FALSE +coda,*,models/sipnet,Suggests,FALSE +coda,*,modules/assim.sequential,Imports,FALSE +coda,*,modules/data.land,Imports,FALSE +coda,*,modules/rtm,Imports,FALSE +coda,>= 0.18,base/utils,Suggests,FALSE +coda,>= 0.18,modules/allometry,Imports,FALSE +coda,>= 0.18,modules/assim.batch,Imports,FALSE +coda,>= 0.18,modules/emulator,Imports,FALSE +coda,>= 0.18,modules/meta.analysis,Imports,FALSE +coda,>= 0.18,modules/photosynthesis,Imports,FALSE +corrplot,*,modules/assim.sequential,Suggests,FALSE +curl,*,base/db,Imports,FALSE +curl,*,base/utils,Imports,FALSE +curl,*,modules/data.atmosphere,Imports,FALSE +curl,*,modules/data.land,Imports,FALSE +curl,*,modules/data.remote,Imports,FALSE +data.table,*,base/db,Suggests,FALSE +data.table,*,base/utils,Suggests,FALSE +data.table,*,base/visualization,Imports,FALSE +data.table,*,models/biocro,Imports,FALSE +data.table,*,modules/data.remote,Suggests,FALSE +dataone,*,modules/data.land,Suggests,FALSE +datapack,*,modules/data.land,Imports,FALSE +DBI,*,base/db,Imports,FALSE +DBI,*,modules/data.remote,Imports,FALSE +dbplyr,>= 2.4.0,base/db,Imports,FALSE +devtools,*,models/ed,Suggests,FALSE +doParallel,*,modules/data.atmosphere,Suggests,FALSE +doParallel,*,modules/data.remote,Imports,FALSE +doSNOW,*,base/remote,Suggests,FALSE +dplR,*,modules/data.land,Imports,FALSE +dplyr,*,base/qaqc,Imports,FALSE +dplyr,*,base/remote,Imports,FALSE +dplyr,*,base/utils,Imports,FALSE +dplyr,*,base/workflow,Imports,FALSE +dplyr,*,models/biocro,Imports,FALSE +dplyr,*,models/ed,Imports,FALSE +dplyr,*,models/ldndc,Imports,FALSE +dplyr,*,models/stics,Imports,FALSE +dplyr,*,modules/assim.sequential,Imports,FALSE +dplyr,*,modules/benchmark,Imports,FALSE +dplyr,*,modules/data.land,Imports,FALSE +dplyr,*,modules/data.remote,Suggests,FALSE +dplyr,*,modules/uncertainty,Imports,FALSE +dplyr,>= 0.8.1,modules/data.atmosphere,Imports,FALSE +dplyr,>= 1.1.2,base/db,Imports,FALSE +ellipse,*,modules/assim.batch,Imports,FALSE +emdbook,*,modules/assim.sequential,Suggests,FALSE +foreach,*,base/remote,Imports,FALSE +foreach,*,modules/data.atmosphere,Suggests,FALSE +foreach,*,modules/data.remote,Imports,FALSE +fs,*,base/db,Imports,FALSE +fs,*,modules/data.land,Imports,FALSE +furrr,*,base/remote,Imports,FALSE +furrr,*,modules/assim.sequential,Imports,FALSE +furrr,*,modules/data.atmosphere,Suggests,FALSE +furrr,*,modules/data.land,Imports,FALSE +furrr,*,modules/data.remote,Imports,FALSE +future,*,modules/assim.sequential,Imports,FALSE +future,*,modules/data.atmosphere,Suggests,FALSE +future,*,modules/data.land,Imports,FALSE +future,*,modules/data.remote,Imports,FALSE +GEDI4R,*,modules/data.remote,Suggests,FALSE +geonames,> 0.998,modules/data.atmosphere,Imports,FALSE +getPass,*,base/remote,Suggests,FALSE +getPass,*,modules/data.land,Suggests,FALSE +getPass,*,modules/data.remote,Suggests,FALSE +ggmcmc,*,modules/meta.analysis,Suggests,FALSE +ggplot2,*,base/utils,Suggests,FALSE +ggplot2,*,base/visualization,Imports,FALSE +ggplot2,*,modules/assim.sequential,Imports,FALSE +ggplot2,*,modules/benchmark,Imports,FALSE +ggplot2,*,modules/data.atmosphere,Imports,FALSE +ggplot2,*,modules/data.remote,Suggests,FALSE +ggplot2,*,modules/meta.analysis,Suggests,FALSE +ggplot2,*,modules/priors,Imports,FALSE +ggplot2,*,modules/uncertainty,Imports,FALSE +ggpubr,*,modules/assim.sequential,Suggests,FALSE +ggrepel,*,modules/assim.sequential,Suggests,FALSE +glue,*,base/db,Imports,FALSE +glue,*,models/ed,Imports,FALSE +glue,*,modules/assim.sequential,Suggests,FALSE +glue,*,modules/data.atmosphere,Imports,FALSE +glue,*,modules/data.land,Suggests,FALSE +glue,*,modules/data.remote,Imports,FALSE +graphics,*,base/qaqc,Imports,FALSE +graphics,*,modules/allometry,Imports,FALSE +graphics,*,modules/assim.batch,Imports,FALSE +graphics,*,modules/photosynthesis,Imports,FALSE +grDevices,*,modules/allometry,Imports,FALSE +grDevices,*,modules/assim.batch,Imports,FALSE +grDevices,*,modules/benchmark,Imports,FALSE +grDevices,*,modules/data.remote,Suggests,FALSE +grid,*,base/visualization,Suggests,FALSE +gridExtra,*,modules/assim.sequential,Suggests,FALSE +gridExtra,*,modules/benchmark,Imports,FALSE +gridExtra,*,modules/uncertainty,Imports,FALSE +hdf5r,*,models/ed,Imports,FALSE +here,*,base/db,Suggests,FALSE +httr,*,base/remote,Imports,FALSE +httr,*,modules/data.atmosphere,Imports,FALSE +httr,*,modules/data.land,Imports,FALSE +httr,*,modules/data.remote,Suggests,FALSE +IDPmisc,*,modules/assim.batch,Imports,FALSE +jsonlite,*,base/remote,Imports,FALSE +jsonlite,*,models/stics,Imports,FALSE +jsonlite,*,modules/data.atmosphere,Imports,FALSE +jsonlite,*,modules/data.remote,Suggests,FALSE +knitr,>= 1.42,base/db,Suggests,FALSE +knitr,>= 1.42,base/qaqc,Suggests,FALSE +knitr,>= 1.42,modules/allometry,Suggests,FALSE +knitr,>= 1.42,modules/assim.batch,Suggests,FALSE +knitr,>= 1.42,modules/meta.analysis,Suggests,FALSE +knitr,>= 1.42,modules/photosynthesis,Suggests,FALSE +knitr,>= 1.42,modules/rtm,Suggests,FALSE +lattice,*,modules/meta.analysis,Imports,FALSE +linkages,*,models/linkages,Suggests,FALSE +lqmm,*,modules/assim.batch,Imports,FALSE +lubridate,*,base/db,Imports,FALSE +lubridate,*,models/basgra,Imports,FALSE +lubridate,*,models/dvmdostem,Imports,FALSE +lubridate,*,models/ed,Imports,FALSE +lubridate,*,models/ldndc,Imports,FALSE +lubridate,*,models/stics,Imports,FALSE +lubridate,*,modules/data.land,Imports,FALSE +lubridate,*,modules/data.remote,Suggests,FALSE +lubridate,>= 1.6.0,base/settings,Imports,FALSE +lubridate,>= 1.6.0,base/utils,Imports,FALSE +lubridate,>= 1.6.0,models/dalec,Imports,FALSE +lubridate,>= 1.6.0,models/fates,Imports,FALSE +lubridate,>= 1.6.0,models/gday,Imports,FALSE +lubridate,>= 1.6.0,models/jules,Imports,FALSE +lubridate,>= 1.6.0,models/linkages,Imports,FALSE +lubridate,>= 1.6.0,models/lpjguess,Imports,FALSE +lubridate,>= 1.6.0,models/maat,Imports,FALSE +lubridate,>= 1.6.0,models/maespa,Imports,FALSE +lubridate,>= 1.6.0,models/preles,Imports,FALSE +lubridate,>= 1.6.0,models/sipnet,Imports,FALSE +lubridate,>= 1.6.0,modules/assim.batch,Imports,FALSE +lubridate,>= 1.6.0,modules/assim.sequential,Imports,FALSE +lubridate,>= 1.6.0,modules/benchmark,Imports,FALSE +lubridate,>= 1.6.0,modules/data.atmosphere,Imports,FALSE +lubridate,>= 1.6.0,modules/rtm,Imports,FALSE +lubridate,>= 1.7.0,models/biocro,Imports,FALSE +Maeswrap,*,models/maespa,Suggests,FALSE +magic,>= 1.5.0,modules/assim.sequential,Suggests,FALSE +magrittr,*,base/db,Imports,FALSE +magrittr,*,base/utils,Imports,FALSE +magrittr,*,models/ed,Imports,FALSE +magrittr,*,modules/assim.sequential,Imports,FALSE +magrittr,*,modules/benchmark,Imports,FALSE +magrittr,*,modules/data.land,Imports,FALSE +magrittr,*,modules/data.remote,Imports,FALSE +markdown,*,modules/allometry,Suggests,FALSE +markdown,*,modules/photosynthesis,Suggests,FALSE +MASS,*,base/utils,Suggests,FALSE +MASS,*,modules/assim.batch,Imports,FALSE +MASS,*,modules/data.atmosphere,Imports,FALSE +MASS,*,modules/meta.analysis,Imports,FALSE +MASS,*,modules/priors,Imports,FALSE +MASS,*,modules/rtm,Imports,FALSE +Matrix,*,modules/assim.sequential,Imports,FALSE +mclust,*,modules/rtm,Suggests,FALSE +MCMCpack,*,modules/allometry,Imports,FALSE +MCMCpack,*,modules/assim.batch,Imports,FALSE +MCMCpack,*,modules/emulator,Imports,FALSE +methods,*,base/db,Imports,FALSE +methods,*,base/settings,Depends,FALSE +methods,*,modules/allometry,Imports,FALSE +methods,*,modules/assim.batch,Imports,FALSE +methods,*,modules/assim.sequential,Suggests,FALSE +methods,*,modules/emulator,Imports,FALSE +mgcv,*,modules/data.atmosphere,Imports,FALSE +minpack.lm,*,modules/rtm,Suggests,FALSE +mlegp,*,modules/assim.batch,Imports,FALSE +mockery,*,base/all,Suggests,FALSE +mockery,*,base/qaqc,Suggests,FALSE +mockery,*,base/remote,Suggests,FALSE +mockery,*,base/settings,Suggests,FALSE +mockery,*,base/utils,Suggests,FALSE +mockery,*,base/visualization,Suggests,FALSE +mockery,*,base/workflow,Suggests,FALSE +mockery,*,modules/data.atmosphere,Suggests,FALSE +mockery,>= 0.3.0,models/biocro,Suggests,FALSE +mockery,>= 0.4.3,base/db,Suggests,FALSE +MODISTools,>= 1.1.0,modules/data.remote,Imports,FALSE +mvbutils,*,base/qaqc,Suggests,FALSE +mvtnorm,*,modules/allometry,Imports,FALSE +mvtnorm,*,modules/assim.batch,Imports,FALSE +mvtnorm,*,modules/assim.sequential,Imports,FALSE +mvtnorm,*,modules/data.land,Imports,FALSE +mvtnorm,*,modules/emulator,Imports,FALSE +ncdf4,*,base/db,Imports,FALSE +ncdf4,*,models/basgra,Imports,FALSE +ncdf4,*,models/dvmdostem,Imports,FALSE +ncdf4,*,models/ldndc,Imports,FALSE +ncdf4,*,models/sibcasa,Imports,FALSE +ncdf4,*,models/stics,Imports,FALSE +ncdf4,*,modules/assim.sequential,Imports,FALSE +ncdf4,*,modules/data.remote,Imports,FALSE +ncdf4,>= 1.15,base/utils,Imports,FALSE +ncdf4,>= 1.15,base/visualization,Imports,FALSE +ncdf4,>= 1.15,models/biocro,Imports,FALSE +ncdf4,>= 1.15,models/clm45,Imports,FALSE +ncdf4,>= 1.15,models/dalec,Imports,FALSE +ncdf4,>= 1.15,models/ed,Imports,FALSE +ncdf4,>= 1.15,models/fates,Imports,FALSE +ncdf4,>= 1.15,models/gday,Imports,FALSE +ncdf4,>= 1.15,models/jules,Imports,FALSE +ncdf4,>= 1.15,models/linkages,Imports,FALSE +ncdf4,>= 1.15,models/lpjguess,Imports,FALSE +ncdf4,>= 1.15,models/maat,Imports,FALSE +ncdf4,>= 1.15,models/maespa,Imports,FALSE +ncdf4,>= 1.15,models/preles,Imports,FALSE +ncdf4,>= 1.15,models/sipnet,Imports,FALSE +ncdf4,>= 1.15,modules/assim.batch,Imports,FALSE +ncdf4,>= 1.15,modules/benchmark,Imports,FALSE +ncdf4,>= 1.15,modules/data.atmosphere,Imports,FALSE +ncdf4,>= 1.15,modules/data.land,Imports,FALSE +neonstore,*,modules/data.land,Imports,FALSE +neonUtilities,*,modules/data.land,Imports,FALSE +nimble,*,modules/assim.sequential,Imports,FALSE +nneo,*,modules/data.atmosphere,Imports,FALSE +optparse,*,base/settings,Imports,FALSE +parallel,*,modules/assim.batch,Imports,FALSE +parallel,*,modules/data.atmosphere,Suggests,FALSE +parallel,*,modules/data.remote,Imports,FALSE +PEcAn.allometry,*,base/all,Suggests,TRUE +PEcAn.assim.batch,*,base/all,Depends,TRUE +PEcAn.assim.batch,*,modules/rtm,Imports,TRUE +PEcAn.benchmark,*,base/all,Depends,TRUE +PEcAn.benchmark,*,modules/assim.batch,Imports,TRUE +PEcAn.benchmark,*,modules/assim.sequential,Suggests,TRUE +PEcAn.benchmark,*,modules/data.land,Imports,TRUE +PEcAn.BIOCRO,*,base/all,Suggests,TRUE +PEcAn.BIOCRO,*,base/qaqc,Suggests,TRUE +PEcAn.DALEC,*,base/all,Suggests,TRUE +PEcAn.data.atmosphere,*,base/all,Depends,TRUE +PEcAn.data.atmosphere,*,base/workflow,Imports,TRUE +PEcAn.data.atmosphere,*,models/basgra,Imports,TRUE +PEcAn.data.atmosphere,*,models/biocro,Imports,TRUE +PEcAn.data.atmosphere,*,models/ed,Imports,TRUE +PEcAn.data.atmosphere,*,models/jules,Imports,TRUE +PEcAn.data.atmosphere,*,models/ldndc,Imports,TRUE +PEcAn.data.atmosphere,*,models/linkages,Imports,TRUE +PEcAn.data.atmosphere,*,models/maat,Imports,TRUE +PEcAn.data.atmosphere,*,models/maespa,Imports,TRUE +PEcAn.data.atmosphere,*,models/preles,Imports,TRUE +PEcAn.data.atmosphere,*,models/sipnet,Depends,TRUE +PEcAn.data.land,*,base/all,Depends,TRUE +PEcAn.data.land,*,base/workflow,Imports,TRUE +PEcAn.data.land,*,models/biocro,Imports,TRUE +PEcAn.data.land,*,models/ed,Imports,TRUE +PEcAn.data.land,*,models/ldndc,Imports,TRUE +PEcAn.data.land,*,modules/assim.sequential,Suggests,TRUE +PEcAn.data.land,*,modules/benchmark,Suggests,TRUE +PEcAn.data.remote,*,base/all,Depends,TRUE +PEcAn.data.remote,*,modules/assim.sequential,Suggests,TRUE +PEcAn.DB,*,base/all,Depends,TRUE +PEcAn.DB,*,base/qaqc,Imports,TRUE +PEcAn.DB,*,base/settings,Imports,TRUE +PEcAn.DB,*,base/workflow,Imports,TRUE +PEcAn.DB,*,models/biocro,Suggests,TRUE +PEcAn.DB,*,models/template,Imports,TRUE +PEcAn.DB,*,modules/allometry,Imports,TRUE +PEcAn.DB,*,modules/assim.batch,Imports,TRUE +PEcAn.DB,*,modules/assim.sequential,Imports,TRUE +PEcAn.DB,*,modules/benchmark,Imports,TRUE +PEcAn.DB,*,modules/data.atmosphere,Imports,TRUE +PEcAn.DB,*,modules/data.land,Imports,TRUE +PEcAn.DB,*,modules/data.remote,Imports,TRUE +PEcAn.DB,*,modules/meta.analysis,Imports,TRUE +PEcAn.DB,*,modules/uncertainty,Imports,TRUE +PEcAn.ED2,*,base/all,Suggests,TRUE +PEcAn.ED2,*,base/qaqc,Suggests,TRUE +PEcAn.ED2,*,modules/rtm,Suggests,TRUE +PEcAn.emulator,*,base/all,Depends,TRUE +PEcAn.emulator,*,modules/assim.batch,Imports,TRUE +PEcAn.emulator,*,modules/uncertainty,Imports,TRUE +PEcAn.LINKAGES,*,base/all,Suggests,TRUE +PEcAn.logger,*,base/all,Depends,TRUE +PEcAn.logger,*,base/db,Imports,TRUE +PEcAn.logger,*,base/qaqc,Imports,TRUE +PEcAn.logger,*,base/remote,Imports,TRUE +PEcAn.logger,*,base/settings,Imports,TRUE +PEcAn.logger,*,base/utils,Imports,TRUE +PEcAn.logger,*,base/visualization,Imports,TRUE +PEcAn.logger,*,base/workflow,Imports,TRUE +PEcAn.logger,*,models/basgra,Imports,TRUE +PEcAn.logger,*,models/biocro,Imports,TRUE +PEcAn.logger,*,models/cable,Imports,TRUE +PEcAn.logger,*,models/clm45,Depends,TRUE +PEcAn.logger,*,models/dalec,Imports,TRUE +PEcAn.logger,*,models/dvmdostem,Imports,TRUE +PEcAn.logger,*,models/ed,Imports,TRUE +PEcAn.logger,*,models/fates,Imports,TRUE +PEcAn.logger,*,models/gday,Imports,TRUE +PEcAn.logger,*,models/jules,Imports,TRUE +PEcAn.logger,*,models/ldndc,Imports,TRUE +PEcAn.logger,*,models/linkages,Imports,TRUE +PEcAn.logger,*,models/lpjguess,Imports,TRUE +PEcAn.logger,*,models/maat,Imports,TRUE +PEcAn.logger,*,models/maespa,Imports,TRUE +PEcAn.logger,*,models/preles,Imports,TRUE +PEcAn.logger,*,models/sibcasa,Imports,TRUE +PEcAn.logger,*,models/sipnet,Imports,TRUE +PEcAn.logger,*,models/stics,Imports,TRUE +PEcAn.logger,*,models/template,Imports,TRUE +PEcAn.logger,*,modules/assim.batch,Imports,TRUE +PEcAn.logger,*,modules/assim.sequential,Imports,TRUE +PEcAn.logger,*,modules/benchmark,Imports,TRUE +PEcAn.logger,*,modules/data.atmosphere,Imports,TRUE +PEcAn.logger,*,modules/data.land,Imports,TRUE +PEcAn.logger,*,modules/data.remote,Imports,TRUE +PEcAn.logger,*,modules/meta.analysis,Imports,TRUE +PEcAn.logger,*,modules/priors,Imports,TRUE +PEcAn.logger,*,modules/rtm,Imports,TRUE +PEcAn.logger,*,modules/uncertainty,Imports,TRUE +PEcAn.MA,*,base/all,Depends,TRUE +PEcAn.MA,*,modules/assim.batch,Imports,TRUE +PEcAn.MA,*,modules/priors,Imports,TRUE +PEcAn.photosynthesis,*,base/all,Suggests,TRUE +PEcAn.priors,*,base/all,Depends,TRUE +PEcAn.priors,*,modules/uncertainty,Imports,TRUE +PEcAn.remote,*,base/all,Depends,TRUE +PEcAn.remote,*,base/db,Imports,TRUE +PEcAn.remote,*,base/settings,Imports,TRUE +PEcAn.remote,*,base/workflow,Imports,TRUE +PEcAn.remote,*,models/biocro,Imports,TRUE +PEcAn.remote,*,models/dalec,Imports,TRUE +PEcAn.remote,*,models/ed,Imports,TRUE +PEcAn.remote,*,models/fates,Imports,TRUE +PEcAn.remote,*,models/gday,Imports,TRUE +PEcAn.remote,*,models/jules,Imports,TRUE +PEcAn.remote,*,models/ldndc,Imports,TRUE +PEcAn.remote,*,models/linkages,Imports,TRUE +PEcAn.remote,*,models/lpjguess,Imports,TRUE +PEcAn.remote,*,models/maat,Imports,TRUE +PEcAn.remote,*,models/maespa,Imports,TRUE +PEcAn.remote,*,models/sipnet,Imports,TRUE +PEcAn.remote,*,models/stics,Imports,TRUE +PEcAn.remote,*,modules/assim.batch,Imports,TRUE +PEcAn.remote,*,modules/assim.sequential,Imports,TRUE +PEcAn.remote,*,modules/data.atmosphere,Imports,TRUE +PEcAn.remote,*,modules/data.land,Imports,TRUE +PEcAn.remote,*,modules/data.remote,Imports,TRUE +PEcAn.settings,*,base/all,Depends,TRUE +PEcAn.settings,*,base/workflow,Imports,TRUE +PEcAn.settings,*,models/biocro,Imports,TRUE +PEcAn.settings,*,models/ed,Imports,TRUE +PEcAn.settings,*,models/maat,Imports,TRUE +PEcAn.settings,*,models/stics,Imports,TRUE +PEcAn.settings,*,modules/assim.batch,Imports,TRUE +PEcAn.settings,*,modules/assim.sequential,Imports,TRUE +PEcAn.settings,*,modules/benchmark,Imports,TRUE +PEcAn.settings,*,modules/data.atmosphere,Suggests,TRUE +PEcAn.settings,*,modules/data.land,Suggests,TRUE +PEcAn.settings,*,modules/meta.analysis,Imports,TRUE +PEcAn.settings,*,modules/uncertainty,Imports,TRUE +PEcAn.SIPNET,*,base/all,Suggests,TRUE +PEcAn.SIPNET,*,base/qaqc,Suggests,TRUE +PEcAn.uncertainty,*,base/all,Depends,TRUE +PEcAn.uncertainty,*,base/workflow,Imports,TRUE +PEcAn.uncertainty,*,modules/assim.batch,Imports,TRUE +PEcAn.uncertainty,*,modules/assim.sequential,Imports,TRUE +PEcAn.utils,*,base/all,Depends,TRUE +PEcAn.utils,*,base/db,Imports,TRUE +PEcAn.utils,*,base/qaqc,Suggests,TRUE +PEcAn.utils,*,base/settings,Imports,TRUE +PEcAn.utils,*,base/workflow,Imports,TRUE +PEcAn.utils,*,models/biocro,Imports,TRUE +PEcAn.utils,*,models/clm45,Depends,TRUE +PEcAn.utils,*,models/dalec,Imports,TRUE +PEcAn.utils,*,models/ed,Imports,TRUE +PEcAn.utils,*,models/fates,Imports,TRUE +PEcAn.utils,*,models/gday,Depends,TRUE +PEcAn.utils,*,models/jules,Imports,TRUE +PEcAn.utils,*,models/linkages,Depends,TRUE +PEcAn.utils,*,models/lpjguess,Imports,TRUE +PEcAn.utils,*,models/maat,Imports,TRUE +PEcAn.utils,*,models/maespa,Imports,TRUE +PEcAn.utils,*,models/preles,Depends,TRUE +PEcAn.utils,*,models/preles,Imports,TRUE +PEcAn.utils,*,models/sipnet,Imports,TRUE +PEcAn.utils,*,modules/assim.batch,Imports,TRUE +PEcAn.utils,*,modules/assim.sequential,Suggests,TRUE +PEcAn.utils,*,modules/benchmark,Imports,TRUE +PEcAn.utils,*,modules/data.atmosphere,Imports,TRUE +PEcAn.utils,*,modules/data.land,Imports,TRUE +PEcAn.utils,*,modules/data.remote,Imports,TRUE +PEcAn.utils,*,modules/meta.analysis,Imports,TRUE +PEcAn.utils,*,modules/rtm,Suggests,TRUE +PEcAn.utils,*,modules/uncertainty,Imports,TRUE +PEcAn.utils,>= 1.4.8,models/basgra,Imports,TRUE +PEcAn.utils,>= 1.4.8,models/cable,Imports,TRUE +PEcAn.utils,>= 1.4.8,models/dvmdostem,Imports,TRUE +PEcAn.utils,>= 1.4.8,models/ldndc,Imports,TRUE +PEcAn.utils,>= 1.4.8,models/sibcasa,Imports,TRUE +PEcAn.utils,>= 1.4.8,models/stics,Imports,TRUE +PEcAn.utils,>= 1.4.8,models/template,Imports,TRUE +PEcAn.visualization,*,modules/assim.sequential,Suggests,TRUE +PEcAn.visualization,*,modules/data.land,Imports,TRUE +PEcAn.visualization,*,modules/priors,Suggests,TRUE +PEcAn.workflow,*,base/all,Depends,TRUE +PEcAn.workflow,*,modules/assim.batch,Imports,TRUE +PEcAn.workflow,*,modules/assim.sequential,Imports,TRUE +plotrix,*,base/qaqc,Imports,FALSE +plotrix,*,modules/assim.sequential,Suggests,FALSE +plyr,>= 1.8.4,base/visualization,Imports,FALSE +plyr,>= 1.8.4,modules/assim.sequential,Suggests,FALSE +plyr,>= 1.8.4,modules/uncertainty,Imports,FALSE +png,*,base/visualization,Suggests,FALSE +prodlim,*,modules/assim.batch,Imports,FALSE +progress,*,modules/data.atmosphere,Suggests,FALSE +purrr,*,base/db,Imports,FALSE +purrr,*,base/settings,Imports,FALSE +purrr,*,base/utils,Imports,FALSE +purrr,*,models/ed,Imports,FALSE +purrr,*,modules/assim.sequential,Imports,FALSE +purrr,*,modules/data.land,Imports,FALSE +purrr,*,modules/data.remote,Imports,FALSE +purrr,*,modules/uncertainty,Imports,FALSE +purrr,>= 0.2.3,base/workflow,Imports,FALSE +purrr,>= 0.2.3,modules/data.atmosphere,Imports,FALSE +pwr,*,modules/rtm,Suggests,FALSE +R.utils,*,base/db,Imports,FALSE +randomForest,*,modules/assim.sequential,Suggests,FALSE +randtoolbox,*,base/utils,Suggests,FALSE +randtoolbox,*,modules/uncertainty,Imports,FALSE +raster,*,base/visualization,Suggests,FALSE +raster,*,modules/assim.sequential,Suggests,FALSE +raster,*,modules/data.atmosphere,Imports,FALSE +raster,*,modules/data.land,Suggests,FALSE +raster,*,modules/data.remote,Suggests,FALSE +rcrossref,*,base/db,Suggests,FALSE +readr,*,models/ldndc,Imports,FALSE +readr,*,modules/assim.sequential,Suggests,FALSE +REddyProc,*,modules/data.atmosphere,Imports,FALSE +redland,*,modules/data.land,Suggests,FALSE +reshape,*,modules/data.remote,Suggests,FALSE +reshape2,*,base/visualization,Imports,FALSE +reshape2,*,modules/benchmark,Imports,FALSE +reshape2,*,modules/data.atmosphere,Imports,FALSE +reshape2,>= 1.4.2,modules/assim.sequential,Suggests,FALSE +reticulate,*,modules/data.atmosphere,Suggests,FALSE +reticulate,*,modules/data.land,Suggests,FALSE +reticulate,*,modules/data.remote,Imports,FALSE +rjags,*,base/utils,Suggests,FALSE +rjags,*,modules/assim.batch,Imports,FALSE +rjags,*,modules/data.land,Imports,FALSE +rjags,*,modules/meta.analysis,Imports,FALSE +rjags,*,modules/photosynthesis,Depends,FALSE +rjson,*,models/dvmdostem,Imports,FALSE +rlang,*,base/db,Imports,FALSE +rlang,*,base/qaqc,Imports,FALSE +rlang,*,base/utils,Imports,FALSE +rlang,*,base/visualization,Imports,FALSE +rlang,*,models/biocro,Imports,FALSE +rlang,*,models/ed,Imports,FALSE +rlang,*,models/ldndc,Imports,FALSE +rlang,*,modules/assim.sequential,Imports,FALSE +rlang,*,modules/benchmark,Imports,FALSE +rlang,*,modules/data.land,Imports,FALSE +rlang,*,modules/data.remote,Imports,FALSE +rlang,*,modules/uncertainty,Imports,FALSE +rlang,>= 0.2.0,modules/data.atmosphere,Imports,FALSE +rlist,*,modules/assim.sequential,Suggests,FALSE +rmarkdown,>= 2.19,base/db,Suggests,FALSE +rmarkdown,>= 2.19,base/qaqc,Suggests,FALSE +rmarkdown,>= 2.19,modules/allometry,Suggests,FALSE +rmarkdown,>= 2.19,modules/assim.batch,Suggests,FALSE +rmarkdown,>= 2.19,modules/meta.analysis,Suggests,FALSE +rmarkdown,>= 2.19,modules/photosynthesis,Suggests,FALSE +roxygen2,== 7.3.2,base/all,Roxygen,FALSE +roxygen2,== 7.3.2,base/db,Roxygen,FALSE +roxygen2,== 7.3.2,base/logger,Roxygen,FALSE +roxygen2,== 7.3.2,base/qaqc,Roxygen,FALSE +roxygen2,== 7.3.2,base/remote,Roxygen,FALSE +roxygen2,== 7.3.2,base/settings,Roxygen,FALSE +roxygen2,== 7.3.2,base/utils,Roxygen,FALSE +roxygen2,== 7.3.2,base/visualization,Roxygen,FALSE +roxygen2,== 7.3.2,base/workflow,Roxygen,FALSE +roxygen2,== 7.3.2,models/basgra,Roxygen,FALSE +roxygen2,== 7.3.2,models/biocro,Roxygen,FALSE +roxygen2,== 7.3.2,models/cable,Roxygen,FALSE +roxygen2,== 7.3.2,models/clm45,Roxygen,FALSE +roxygen2,== 7.3.2,models/dalec,Roxygen,FALSE +roxygen2,== 7.3.2,models/dvmdostem,Roxygen,FALSE +roxygen2,== 7.3.2,models/ed,Roxygen,FALSE +roxygen2,== 7.3.2,models/fates,Roxygen,FALSE +roxygen2,== 7.3.2,models/gday,Roxygen,FALSE +roxygen2,== 7.3.2,models/jules,Roxygen,FALSE +roxygen2,== 7.3.2,models/ldndc,Roxygen,FALSE +roxygen2,== 7.3.2,models/linkages,Roxygen,FALSE +roxygen2,== 7.3.2,models/lpjguess,Roxygen,FALSE +roxygen2,== 7.3.2,models/maat,Roxygen,FALSE +roxygen2,== 7.3.2,models/maespa,Roxygen,FALSE +roxygen2,== 7.3.2,models/preles,Roxygen,FALSE +roxygen2,== 7.3.2,models/sibcasa,Roxygen,FALSE +roxygen2,== 7.3.2,models/sipnet,Roxygen,FALSE +roxygen2,== 7.3.2,models/stics,Roxygen,FALSE +roxygen2,== 7.3.2,models/template,Roxygen,FALSE +roxygen2,== 7.3.2,modules/allometry,Roxygen,FALSE +roxygen2,== 7.3.2,modules/assim.batch,Roxygen,FALSE +roxygen2,== 7.3.2,modules/assim.sequential,Roxygen,FALSE +roxygen2,== 7.3.2,modules/benchmark,Roxygen,FALSE +roxygen2,== 7.3.2,modules/data.atmosphere,Roxygen,FALSE +roxygen2,== 7.3.2,modules/data.land,Roxygen,FALSE +roxygen2,== 7.3.2,modules/data.remote,Roxygen,FALSE +roxygen2,== 7.3.2,modules/emulator,Roxygen,FALSE +roxygen2,== 7.3.2,modules/meta.analysis,Roxygen,FALSE +roxygen2,== 7.3.2,modules/photosynthesis,Roxygen,FALSE +roxygen2,== 7.3.2,modules/priors,Roxygen,FALSE +roxygen2,== 7.3.2,modules/rtm,Roxygen,FALSE +roxygen2,== 7.3.2,modules/uncertainty,Roxygen,FALSE +RPostgres,*,base/db,Suggests,FALSE +RPostgreSQL,*,base/db,Suggests,FALSE +RPostgreSQL,*,models/biocro,Suggests,FALSE +Rpreles,*,models/preles,Suggests,FALSE +RSQLite,*,base/db,Suggests,FALSE +sessioninfo,*,base/all,Suggests,FALSE +sf,*,modules/assim.sequential,Suggests,FALSE +sf,*,modules/data.atmosphere,Imports,FALSE +sf,*,modules/data.land,Imports,FALSE +sf,*,modules/data.remote,Suggests,FALSE +SimilarityMeasures,*,modules/benchmark,Imports,FALSE +sirt,*,modules/data.land,Imports,FALSE +sp,*,base/visualization,Suggests,FALSE +sp,*,modules/assim.sequential,Suggests,FALSE +sp,*,modules/data.atmosphere,Imports,FALSE +sp,*,modules/data.land,Imports,FALSE +sp,*,modules/data.remote,Imports,FALSE +stats,*,base/qaqc,Imports,FALSE +stats,*,modules/allometry,Imports,FALSE +stats,*,modules/assim.batch,Imports,FALSE +stats,*,modules/assim.sequential,Suggests,FALSE +stats,*,modules/photosynthesis,Imports,FALSE +SticsRFiles,*,models/stics,Suggests,FALSE +stringi,*,base/logger,Imports,FALSE +stringi,*,base/utils,Imports,FALSE +stringr,*,models/fates,Imports,FALSE +stringr,*,modules/assim.sequential,Imports,FALSE +stringr,*,modules/benchmark,Imports,FALSE +stringr,*,modules/data.land,Imports,FALSE +stringr,>= 1.1.0,base/visualization,Imports,FALSE +stringr,>= 1.1.0,models/ed,Imports,FALSE +stringr,>= 1.1.0,modules/data.atmosphere,Imports,FALSE +suntools,*,modules/data.atmosphere,Imports,FALSE +swfscMisc,*,modules/data.land,Imports,FALSE +terra,*,modules/assim.sequential,Suggests,FALSE +terra,*,modules/data.atmosphere,Imports,FALSE +terra,*,modules/data.land,Imports,FALSE +terra,*,modules/data.remote,Imports,FALSE +testthat,*,base/all,Suggests,FALSE +testthat,*,base/logger,Suggests,FALSE +testthat,*,base/remote,Suggests,FALSE +testthat,*,base/workflow,Suggests,FALSE +testthat,*,modules/assim.sequential,Suggests,FALSE +testthat,*,modules/priors,Suggests,FALSE +testthat,>= 1.0.2,base/visualization,Suggests,FALSE +testthat,>= 1.0.2,models/basgra,Suggests,FALSE +testthat,>= 1.0.2,models/cable,Suggests,FALSE +testthat,>= 1.0.2,models/clm45,Suggests,FALSE +testthat,>= 1.0.2,models/dalec,Suggests,FALSE +testthat,>= 1.0.2,models/dvmdostem,Suggests,FALSE +testthat,>= 1.0.2,models/ed,Suggests,FALSE +testthat,>= 1.0.2,models/fates,Suggests,FALSE +testthat,>= 1.0.2,models/gday,Suggests,FALSE +testthat,>= 1.0.2,models/jules,Suggests,FALSE +testthat,>= 1.0.2,models/ldndc,Suggests,FALSE +testthat,>= 1.0.2,models/linkages,Suggests,FALSE +testthat,>= 1.0.2,models/lpjguess,Suggests,FALSE +testthat,>= 1.0.2,models/maat,Suggests,FALSE +testthat,>= 1.0.2,models/maespa,Suggests,FALSE +testthat,>= 1.0.2,models/preles,Suggests,FALSE +testthat,>= 1.0.2,models/sipnet,Suggests,FALSE +testthat,>= 1.0.2,models/stics,Suggests,FALSE +testthat,>= 1.0.2,models/template,Suggests,FALSE +testthat,>= 1.0.2,modules/allometry,Suggests,FALSE +testthat,>= 1.0.2,modules/assim.batch,Suggests,FALSE +testthat,>= 1.0.2,modules/data.land,Suggests,FALSE +testthat,>= 1.0.2,modules/data.remote,Suggests,FALSE +testthat,>= 1.0.2,modules/meta.analysis,Suggests,FALSE +testthat,>= 1.0.2,modules/rtm,Suggests,FALSE +testthat,>= 1.0.2,modules/uncertainty,Suggests,FALSE +testthat,>= 2.0.0,base/db,Suggests,FALSE +testthat,>= 2.0.0,base/settings,Suggests,FALSE +testthat,>= 2.0.0,base/utils,Suggests,FALSE +testthat,>= 2.0.0,models/biocro,Suggests,FALSE +testthat,>= 2.0.0,modules/benchmark,Suggests,FALSE +testthat,>= 2.0.0,modules/data.atmosphere,Suggests,FALSE +testthat,>= 3.0.0,models/sibcasa,Suggests,FALSE +testthat,>= 3.0.4,base/qaqc,Suggests,FALSE +tibble,*,base/db,Imports,FALSE +tibble,*,models/ed,Imports,FALSE +tibble,*,models/fates,Imports,FALSE +tibble,*,models/lpjguess,Imports,FALSE +tibble,*,modules/data.atmosphere,Imports,FALSE +tibble,*,modules/data.remote,Suggests,FALSE +tictoc,*,modules/assim.sequential,Suggests,FALSE +tidyr,*,base/db,Imports,FALSE +tidyr,*,models/ed,Imports,FALSE +tidyr,*,modules/assim.sequential,Suggests,FALSE +tidyr,*,modules/data.atmosphere,Imports,FALSE +tidyr,*,modules/data.land,Imports,FALSE +tidyselect,*,modules/benchmark,Imports,FALSE +tidyselect,*,modules/data.atmosphere,Imports,FALSE +tidyselect,*,modules/data.land,Imports,FALSE +tidyverse,*,base/db,Suggests,FALSE +tools,*,base/remote,Suggests,FALSE +tools,*,modules/allometry,Imports,FALSE +traits,*,modules/data.land,Imports,FALSE +TruncatedNormal,>= 2.2,modules/assim.batch,Imports,FALSE +truncnorm,*,modules/data.atmosphere,Imports,FALSE +units,*,base/db,Imports,FALSE +units,*,base/utils,Imports,FALSE +units,*,modules/benchmark,Imports,FALSE +units,*,modules/data.atmosphere,Imports,FALSE +urltools,*,base/remote,Imports,FALSE +utils,*,base/all,Imports,FALSE +utils,*,base/logger,Imports,FALSE +utils,*,models/ed,Imports,FALSE +utils,*,modules/allometry,Imports,FALSE +utils,*,modules/assim.batch,Imports,FALSE +utils,*,modules/assim.sequential,Suggests,FALSE +utils,*,modules/benchmark,Imports,FALSE +utils,*,modules/data.remote,Suggests,FALSE +utils,*,modules/photosynthesis,Imports,FALSE +vdiffr,>= 1.0.2,base/qaqc,Suggests,FALSE +withr,*,base/db,Suggests,FALSE +withr,*,base/logger,Suggests,FALSE +withr,*,base/qaqc,Suggests,FALSE +withr,*,base/remote,Suggests,FALSE +withr,*,base/settings,Suggests,FALSE +withr,*,base/utils,Suggests,FALSE +withr,*,base/visualization,Suggests,FALSE +withr,*,base/workflow,Suggests,FALSE +withr,*,models/basgra,Suggests,FALSE +withr,*,models/ed,Suggests,FALSE +withr,*,models/sibcasa,Suggests,FALSE +withr,*,modules/allometry,Suggests,FALSE +withr,*,modules/data.atmosphere,Suggests,FALSE +XML,*,base/db,Imports,FALSE +XML,*,base/workflow,Imports,FALSE +XML,*,models/biocro,Imports,FALSE +XML,*,models/maat,Imports,FALSE +XML,*,models/stics,Imports,FALSE +XML,*,modules/assim.batch,Imports,FALSE +XML,*,modules/assim.sequential,Suggests,FALSE +XML,*,modules/data.remote,Imports,FALSE +XML,*,modules/rtm,Suggests,FALSE +XML,>= 3.98-1.3,base/settings,Imports,FALSE +XML,>= 3.98-1.4,models/ed,Imports,FALSE +XML,>= 3.98-1.4,modules/benchmark,Imports,FALSE +XML,>= 3.98-1.4,modules/data.atmosphere,Imports,FALSE +XML,>= 3.98-1.4,modules/data.land,Imports,FALSE +xtable,*,base/utils,Suggests,FALSE +xts,*,modules/data.atmosphere,Imports,FALSE +zoo,*,modules/benchmark,Imports,FALSE +zoo,*,modules/data.atmosphere,Imports,FALSE \ No newline at end of file diff --git a/models/fates/DESCRIPTION b/models/fates/DESCRIPTION index b0ba63028e6..a44c6011931 100644 --- a/models/fates/DESCRIPTION +++ b/models/fates/DESCRIPTION @@ -21,7 +21,8 @@ Imports: PEcAn.remote, PEcAn.utils, lubridate (>= 1.6.0), - ncdf4 (>= 1.15) + ncdf4 (>= 1.15), + tibble Suggests: testthat (>= 1.0.2) License: BSD_3_clause + file LICENSE diff --git a/models/fates/R/model2netcdf.FATES.R b/models/fates/R/model2netcdf.FATES.R index ee493b36755..5f0cc66c317 100644 --- a/models/fates/R/model2netcdf.FATES.R +++ b/models/fates/R/model2netcdf.FATES.R @@ -13,9 +13,9 @@ ##' @param outdir Location of FATES model output (e.g. a path to a single ensemble output) ##' @param sitelat Latitude of the site ##' @param sitelon Longitude of the site -##' @param start_date Start time of the simulation -##' @param end_date End time of the simulation -##' @param vars_names Names of Selected variables in PEcAn format +##' @param start_date Start time of the simulation, not string +##' @param end_date End time of the simulation, not string +##' @param vars_names Names of Selected variables in PEcAn format, (e.g. c("","")) ##' @param pfts a named vector of PFT numbers where the names are PFT names ##' ##' @examples @@ -25,22 +25,26 @@ ##' } ##' ##' @author Michael Dietze, Shawn Serbin -## modified Yucong Hu 10/07/24 +## modified Yucong Hu 22/07/24 ##' ##' @export model2netcdf.FATES <- function(outdir, sitelat, sitelon, start_date, end_date, vars_names, pfts){ - ## matched_var could be expanded for more selected variables in argument:vars_names - matched_var <- list(list("FATES_GPP_PF","GPP","kgC m-2 s-1","Gross Primary Productivity"), - list("NEE","NEE","kgC m-2 s-1", "Net Ecosystem Exchange of carbon, includes fire and hrv_xsmrpool"), - list("TLAI","LAI","m2 m-2","Total projected leaf area index"), - list("ER","TotalResp","kgC m-2 s-1","Total Respiration"), - list("AR","AutoResp","kgC m-2 s-1","Autotrophic respiration (MR + GR)"), - list("HR","HeteroResp","kgC m-2 s-1","Total heterotrophic respiration"), - list("SR","SoilResp","kgC m-2 s-1","Total soil respiration (HR + root resp)"), - list("Qle","Evap","Evap","kgC m-2 s-1","Total evaporation"), - list("QVEGT","Transp","kg m-2 s-1","Canopy transpiration")) - + ## Tips: matched_var could be expanded for more selected variables + matched_var <- tibble::tribble( + ~fatesname, ~pecanname, ~pecanunits, ~longname, + "FATES_GPP_PF","GPP","kgC m-2 s-1","Gross Primary Productivity", + "FATES_NPP_PF","NPP","kg m-2 yr-1", "Total PFT-level NPP in kg carbon per m2 land area per second", + "NEE","NEE","kgC m-2 s-1", "Net Ecosystem Exchange of carbon, includes fire and hrv_xsmrpool", + "TLAI","LAI","m2 m-2","Total projected leaf area index", + "ER","TotalResp","kgC m-2 s-1","Total Respiration", + "AR","AutoResp","kgC m-2 s-1","Autotrophic respiration (MR + GR)", + "HR","HeteroResp","kgC m-2 s-1","Total heterotrophic respiration", + "SR","SoilResp","kgC m-2 s-1","Total soil respiration (HR + root resp)", + "Qle","Evap","kgC m-2 s-1","Total evaporation", + "QVEGT","Transp","kg m-2 s-1","Canopy transpiration") + + ## Update unit, dimension and var_update <- function(out,oldname,newname,nc_month,nc_month_names,newunits=NULL,long_name=NULL){ if (oldname %in% nc_month_names) { @@ -58,8 +62,8 @@ model2netcdf.FATES <- function(outdir, sitelat, sitelon, start_date, end_date, v if (any(grepl('pft',d_name))){ dimension <- xypt # include fates_levpft }else{ - dimension <- xyt - } # only xyt + dimension <- xyt # only xyt + } ## transpose dimensions into (,t) if (d_name[length(d_name)]=='time'){ @@ -67,7 +71,8 @@ model2netcdf.FATES <- function(outdir, sitelat, sitelon, start_date, end_date, v dat.new <- PEcAn.utils::misc.convert(dat_0,oldunits,newunits) # convert data units } newvar <- ncdf4::ncvar_def(name = newname, units = newunits, longname=long_name, dim = dimension) - ## Adding target variables into out + + ## adding target variables into out if(is.null(out)) { out <- list(var <- list(),dat <- list(), dimm<-list()) out$var[[1]] <- newvar @@ -95,13 +100,13 @@ model2netcdf.FATES <- function(outdir, sitelat, sitelon, start_date, end_date, v oname <- file.path(dirname(files[1]), paste0(year, ".nc")) out <- NULL - ## Monthly write files + ## monthly write files for (mo in 1:12){ if (((year == start_year) & mo < start_month) | ((year == end_year) & mo > end_month)){ next ## skip unselected months } else{ - if (mo<10){ + if (mo < 10){ month_file <- paste0(gsub("h0.*.nc","",files[1]),"h0.",year,"-0",mo,".nc") }else{ month_file <- paste0(gsub("h0.*.nc","",files[1]),"h0.",year,"-",mo,".nc") @@ -109,54 +114,52 @@ model2netcdf.FATES <- function(outdir, sitelat, sitelon, start_date, end_date, v nc_month <- ncdf4::nc_open(month_file) # read monthly output file of FATES model nc_month_names <- names(nc_month$var) - ## Create time bounds to populate time_bounds variable iteratively + ## create time bounds to populate time_bounds variable iteratively var_bound <- ncdf4::ncvar_get(nc_month, "time_bounds") # start,end day of month - ## Define dimensions + ## define dimensions t <- ncdf4::ncdim_def(name = "time", units = "days since 1700-01-01 00:00:00", vals = as.double(1.0:1.0), calendar = "noleap", unlim = TRUE) time_interval <- ncdf4::ncdim_def(name = "hist_interval", longname = "history time interval endpoint dimensions",vals = 1:2, units = "") - lat <- ncdf4::ncdim_def("lat", "degrees_north", vals = as.double(1.0:1.0), longname = "coordinate_latitude") - #print(lat) + lat <- ncdf4::ncdim_def("lat", "degrees_north", vals = as.double(1.0:1.0), longname = "coordinate_latitude") lon <- ncdf4::ncdim_def("lon", "degrees_east", vals = as.double(1.0:1.0), longname = "coordinate_longitude") pft <- ncdf4::ncdim_def('pft', '', vals=1:12, longname = "FATES pft number") xyt <- list(lon, lat, t) xypt <- list(lon, lat, pft, t) - ## Write monthly files with start(1,1,i) + ## write monthly files with start(1,1,i) for (var_s in vars_names){ - for (name_param in matched_var){ - if (var_s == name_param[2]){ ## select variables - out <- var_update(out,name_param[1],name_param[2],name_param[3],name_param[4],nc_month,nc_month_names) # convert monthly fates output into one variable - } - } + matched_ind <- which(matched_var$pecanname == var_s) + out <- var_update(out, matched_var$fatesname[matched_ind],matched_var$pecanname[matched_ind], + nc_month,nc_month_names,matched_var$pecanunits[matched_ind],matched_var$longname[matched_ind]) } out$var[[length(out$var) + 1]] <- ncdf4::ncvar_def(name="time_bounds", units='', longname = "history time interval endpoints", dim=list(time_interval,t), prec = "double") out$dat[[length(out$dat) + 1]] <- c(rbind(var_bound[1], var_bound[2])) #start, end days of the year out$dimm[[length(out$dimm) + 1]] <- 2 - ## Define vars + ## define vars if (((year != start_year) & (mo == 1)) | ((year == start_year) & (mo == start_month))){ - ncout <- ncdf4::nc_create(oname,out$var) # create yearly nc file - # HYC: define var time, lon, lat, and put var lon, lat - time_var <- ncdf4::ncvar_def(name = "time", units = paste0("days since 1700-01-01 00:00:00"),longname = "time", dim = list(t), prec = "double") - lat_var <- ncdf4::ncvar_def(name = "lat", units = "degrees_north", longname = "coordinate_latitude", dim=list(lat), prec = "double") - lon_var <- ncdf4::ncvar_def(name = "lon", units = "degrees_east", longname = "coordinate_longitude", dim=list(lon), prec = "double") - ncdf4::ncvar_put(ncout, lat_var, sitelat, start=c(1)) - ncdf4::ncvar_put(ncout, lon_var, sitelon, start=c(1)) + ncout <- ncdf4::nc_create(oname, out$var) # create yearly nc file + time_var <- ncdf4::ncvar_def(name = "time", units = "days since 1700-01-01 00:00:00",longname = "time", dim = list(t), prec = "double") + lat_var <- ncdf4::ncvar_def(name = "lat", units = "degrees_north", longname = "coordinate_latitude", dim = list(lat), prec = "double") + lon_var <- ncdf4::ncvar_def(name = "lon", units = "degrees_east", longname = "coordinate_longitude", dim = list(lon), prec = "double") + + ncdf4::ncvar_put(ncout, lat_var, sitelat, start = c(1)) + ncdf4::ncvar_put(ncout, lon_var, sitelon, start = c(1)) } - ## Put time and vars - ncdf4::ncvar_put(ncout, time_var, mean(var_bound), start=c(month), count=c(1)) + ## put time and vars + ncdf4::ncvar_put(ncout, time_var, mean(var_bound), start=c(mo), count=c(1)) + for (i in seq_along(out$var)) { if(out$dimm[[i]]==4){ # xypt - ncdf4::ncvar_put(ncout, out$var[[i]], out$dat[[i]], start=c(1,1,1,month), count=c(1,1,12,1)) + ncdf4::ncvar_put(ncout, out$var[[i]], out$dat[[i]], start=c(1,1,1,mo), count=c(1,1,12,1)) }else if (out$dimm[[i]]==3) { # xyt - ncdf4::ncvar_put(ncout, out$var[[i]], out$dat[[i]], start=c(1,1,month)) + ncdf4::ncvar_put(ncout, out$var[[i]], out$dat[[i]], start=c(1,1,mo)) }else{ # time_bounds - ncdf4::ncvar_put(ncout, out$var[[i]], out$dat[[i]], start=c(1,month)) + ncdf4::ncvar_put(ncout, out$var[[i]], out$dat[[i]], start=c(1,mo)) } } } From 25c852a29db647229f4ac8e8f99bc8293251f66a Mon Sep 17 00:00:00 2001 From: Chris Black Date: Thu, 25 Jul 2024 21:44:32 -0700 Subject: [PATCH 7/7] regenerate dependency list --- docker/depends/pecan_package_dependencies.csv | 1350 ++++++++--------- 1 file changed, 675 insertions(+), 675 deletions(-) diff --git a/docker/depends/pecan_package_dependencies.csv b/docker/depends/pecan_package_dependencies.csv index b076a44a51c..53bdb389898 100644 --- a/docker/depends/pecan_package_dependencies.csv +++ b/docker/depends/pecan_package_dependencies.csv @@ -1,675 +1,675 @@ -package,version,needed_by_dir,type,is_pecan -abind,*,modules/assim.batch,Imports,FALSE -abind,>= 1.4.5,base/utils,Imports,FALSE -abind,>= 1.4.5,models/ed,Imports,FALSE -abind,>= 1.4.5,modules/data.atmosphere,Imports,FALSE -amerifluxr,*,modules/data.atmosphere,Imports,FALSE -arrow,*,modules/data.atmosphere,Imports,FALSE -assertthat,*,models/ed,Imports,FALSE -assertthat,*,modules/data.atmosphere,Imports,FALSE -BayesianTools,*,modules/assim.batch,Imports,FALSE -BayesianTools,*,modules/rtm,Imports,FALSE -BioCro,*,models/biocro,Suggests,FALSE -bit64,*,base/db,Suggests,FALSE -BrownDog,*,modules/benchmark,Suggests,FALSE -coda,*,models/maespa,Suggests,FALSE -coda,*,models/sipnet,Suggests,FALSE -coda,*,modules/assim.sequential,Imports,FALSE -coda,*,modules/data.land,Imports,FALSE -coda,*,modules/rtm,Imports,FALSE -coda,>= 0.18,base/utils,Suggests,FALSE -coda,>= 0.18,modules/allometry,Imports,FALSE -coda,>= 0.18,modules/assim.batch,Imports,FALSE -coda,>= 0.18,modules/emulator,Imports,FALSE -coda,>= 0.18,modules/meta.analysis,Imports,FALSE -coda,>= 0.18,modules/photosynthesis,Imports,FALSE -corrplot,*,modules/assim.sequential,Suggests,FALSE -curl,*,base/db,Imports,FALSE -curl,*,base/utils,Imports,FALSE -curl,*,modules/data.atmosphere,Imports,FALSE -curl,*,modules/data.land,Imports,FALSE -curl,*,modules/data.remote,Imports,FALSE -data.table,*,base/db,Suggests,FALSE -data.table,*,base/utils,Suggests,FALSE -data.table,*,base/visualization,Imports,FALSE -data.table,*,models/biocro,Imports,FALSE -data.table,*,modules/data.remote,Suggests,FALSE -dataone,*,modules/data.land,Suggests,FALSE -datapack,*,modules/data.land,Imports,FALSE -DBI,*,base/db,Imports,FALSE -DBI,*,modules/data.remote,Imports,FALSE -dbplyr,>= 2.4.0,base/db,Imports,FALSE -devtools,*,models/ed,Suggests,FALSE -doParallel,*,modules/data.atmosphere,Suggests,FALSE -doParallel,*,modules/data.remote,Imports,FALSE -doSNOW,*,base/remote,Suggests,FALSE -dplR,*,modules/data.land,Imports,FALSE -dplyr,*,base/qaqc,Imports,FALSE -dplyr,*,base/remote,Imports,FALSE -dplyr,*,base/utils,Imports,FALSE -dplyr,*,base/workflow,Imports,FALSE -dplyr,*,models/biocro,Imports,FALSE -dplyr,*,models/ed,Imports,FALSE -dplyr,*,models/ldndc,Imports,FALSE -dplyr,*,models/stics,Imports,FALSE -dplyr,*,modules/assim.sequential,Imports,FALSE -dplyr,*,modules/benchmark,Imports,FALSE -dplyr,*,modules/data.land,Imports,FALSE -dplyr,*,modules/data.remote,Suggests,FALSE -dplyr,*,modules/uncertainty,Imports,FALSE -dplyr,>= 0.8.1,modules/data.atmosphere,Imports,FALSE -dplyr,>= 1.1.2,base/db,Imports,FALSE -ellipse,*,modules/assim.batch,Imports,FALSE -emdbook,*,modules/assim.sequential,Suggests,FALSE -foreach,*,base/remote,Imports,FALSE -foreach,*,modules/data.atmosphere,Suggests,FALSE -foreach,*,modules/data.remote,Imports,FALSE -fs,*,base/db,Imports,FALSE -fs,*,modules/data.land,Imports,FALSE -furrr,*,base/remote,Imports,FALSE -furrr,*,modules/assim.sequential,Imports,FALSE -furrr,*,modules/data.atmosphere,Suggests,FALSE -furrr,*,modules/data.land,Imports,FALSE -furrr,*,modules/data.remote,Imports,FALSE -future,*,modules/assim.sequential,Imports,FALSE -future,*,modules/data.atmosphere,Suggests,FALSE -future,*,modules/data.land,Imports,FALSE -future,*,modules/data.remote,Imports,FALSE -GEDI4R,*,modules/data.remote,Suggests,FALSE -geonames,> 0.998,modules/data.atmosphere,Imports,FALSE -getPass,*,base/remote,Suggests,FALSE -getPass,*,modules/data.land,Suggests,FALSE -getPass,*,modules/data.remote,Suggests,FALSE -ggmcmc,*,modules/meta.analysis,Suggests,FALSE -ggplot2,*,base/utils,Suggests,FALSE -ggplot2,*,base/visualization,Imports,FALSE -ggplot2,*,modules/assim.sequential,Imports,FALSE -ggplot2,*,modules/benchmark,Imports,FALSE -ggplot2,*,modules/data.atmosphere,Imports,FALSE -ggplot2,*,modules/data.remote,Suggests,FALSE -ggplot2,*,modules/meta.analysis,Suggests,FALSE -ggplot2,*,modules/priors,Imports,FALSE -ggplot2,*,modules/uncertainty,Imports,FALSE -ggpubr,*,modules/assim.sequential,Suggests,FALSE -ggrepel,*,modules/assim.sequential,Suggests,FALSE -glue,*,base/db,Imports,FALSE -glue,*,models/ed,Imports,FALSE -glue,*,modules/assim.sequential,Suggests,FALSE -glue,*,modules/data.atmosphere,Imports,FALSE -glue,*,modules/data.land,Suggests,FALSE -glue,*,modules/data.remote,Imports,FALSE -graphics,*,base/qaqc,Imports,FALSE -graphics,*,modules/allometry,Imports,FALSE -graphics,*,modules/assim.batch,Imports,FALSE -graphics,*,modules/photosynthesis,Imports,FALSE -grDevices,*,modules/allometry,Imports,FALSE -grDevices,*,modules/assim.batch,Imports,FALSE -grDevices,*,modules/benchmark,Imports,FALSE -grDevices,*,modules/data.remote,Suggests,FALSE -grid,*,base/visualization,Suggests,FALSE -gridExtra,*,modules/assim.sequential,Suggests,FALSE -gridExtra,*,modules/benchmark,Imports,FALSE -gridExtra,*,modules/uncertainty,Imports,FALSE -hdf5r,*,models/ed,Imports,FALSE -here,*,base/db,Suggests,FALSE -httr,*,base/remote,Imports,FALSE -httr,*,modules/data.atmosphere,Imports,FALSE -httr,*,modules/data.land,Imports,FALSE -httr,*,modules/data.remote,Suggests,FALSE -IDPmisc,*,modules/assim.batch,Imports,FALSE -jsonlite,*,base/remote,Imports,FALSE -jsonlite,*,models/stics,Imports,FALSE -jsonlite,*,modules/data.atmosphere,Imports,FALSE -jsonlite,*,modules/data.remote,Suggests,FALSE -knitr,>= 1.42,base/db,Suggests,FALSE -knitr,>= 1.42,base/qaqc,Suggests,FALSE -knitr,>= 1.42,modules/allometry,Suggests,FALSE -knitr,>= 1.42,modules/assim.batch,Suggests,FALSE -knitr,>= 1.42,modules/meta.analysis,Suggests,FALSE -knitr,>= 1.42,modules/photosynthesis,Suggests,FALSE -knitr,>= 1.42,modules/rtm,Suggests,FALSE -lattice,*,modules/meta.analysis,Imports,FALSE -linkages,*,models/linkages,Suggests,FALSE -lqmm,*,modules/assim.batch,Imports,FALSE -lubridate,*,base/db,Imports,FALSE -lubridate,*,models/basgra,Imports,FALSE -lubridate,*,models/dvmdostem,Imports,FALSE -lubridate,*,models/ed,Imports,FALSE -lubridate,*,models/ldndc,Imports,FALSE -lubridate,*,models/stics,Imports,FALSE -lubridate,*,modules/data.land,Imports,FALSE -lubridate,*,modules/data.remote,Suggests,FALSE -lubridate,>= 1.6.0,base/settings,Imports,FALSE -lubridate,>= 1.6.0,base/utils,Imports,FALSE -lubridate,>= 1.6.0,models/dalec,Imports,FALSE -lubridate,>= 1.6.0,models/fates,Imports,FALSE -lubridate,>= 1.6.0,models/gday,Imports,FALSE -lubridate,>= 1.6.0,models/jules,Imports,FALSE -lubridate,>= 1.6.0,models/linkages,Imports,FALSE -lubridate,>= 1.6.0,models/lpjguess,Imports,FALSE -lubridate,>= 1.6.0,models/maat,Imports,FALSE -lubridate,>= 1.6.0,models/maespa,Imports,FALSE -lubridate,>= 1.6.0,models/preles,Imports,FALSE -lubridate,>= 1.6.0,models/sipnet,Imports,FALSE -lubridate,>= 1.6.0,modules/assim.batch,Imports,FALSE -lubridate,>= 1.6.0,modules/assim.sequential,Imports,FALSE -lubridate,>= 1.6.0,modules/benchmark,Imports,FALSE -lubridate,>= 1.6.0,modules/data.atmosphere,Imports,FALSE -lubridate,>= 1.6.0,modules/rtm,Imports,FALSE -lubridate,>= 1.7.0,models/biocro,Imports,FALSE -Maeswrap,*,models/maespa,Suggests,FALSE -magic,>= 1.5.0,modules/assim.sequential,Suggests,FALSE -magrittr,*,base/db,Imports,FALSE -magrittr,*,base/utils,Imports,FALSE -magrittr,*,models/ed,Imports,FALSE -magrittr,*,modules/assim.sequential,Imports,FALSE -magrittr,*,modules/benchmark,Imports,FALSE -magrittr,*,modules/data.land,Imports,FALSE -magrittr,*,modules/data.remote,Imports,FALSE -markdown,*,modules/allometry,Suggests,FALSE -markdown,*,modules/photosynthesis,Suggests,FALSE -MASS,*,base/utils,Suggests,FALSE -MASS,*,modules/assim.batch,Imports,FALSE -MASS,*,modules/data.atmosphere,Imports,FALSE -MASS,*,modules/meta.analysis,Imports,FALSE -MASS,*,modules/priors,Imports,FALSE -MASS,*,modules/rtm,Imports,FALSE -Matrix,*,modules/assim.sequential,Imports,FALSE -mclust,*,modules/rtm,Suggests,FALSE -MCMCpack,*,modules/allometry,Imports,FALSE -MCMCpack,*,modules/assim.batch,Imports,FALSE -MCMCpack,*,modules/emulator,Imports,FALSE -methods,*,base/db,Imports,FALSE -methods,*,base/settings,Depends,FALSE -methods,*,modules/allometry,Imports,FALSE -methods,*,modules/assim.batch,Imports,FALSE -methods,*,modules/assim.sequential,Suggests,FALSE -methods,*,modules/emulator,Imports,FALSE -mgcv,*,modules/data.atmosphere,Imports,FALSE -minpack.lm,*,modules/rtm,Suggests,FALSE -mlegp,*,modules/assim.batch,Imports,FALSE -mockery,*,base/all,Suggests,FALSE -mockery,*,base/qaqc,Suggests,FALSE -mockery,*,base/remote,Suggests,FALSE -mockery,*,base/settings,Suggests,FALSE -mockery,*,base/utils,Suggests,FALSE -mockery,*,base/visualization,Suggests,FALSE -mockery,*,base/workflow,Suggests,FALSE -mockery,*,modules/data.atmosphere,Suggests,FALSE -mockery,>= 0.3.0,models/biocro,Suggests,FALSE -mockery,>= 0.4.3,base/db,Suggests,FALSE -MODISTools,>= 1.1.0,modules/data.remote,Imports,FALSE -mvbutils,*,base/qaqc,Suggests,FALSE -mvtnorm,*,modules/allometry,Imports,FALSE -mvtnorm,*,modules/assim.batch,Imports,FALSE -mvtnorm,*,modules/assim.sequential,Imports,FALSE -mvtnorm,*,modules/data.land,Imports,FALSE -mvtnorm,*,modules/emulator,Imports,FALSE -ncdf4,*,base/db,Imports,FALSE -ncdf4,*,models/basgra,Imports,FALSE -ncdf4,*,models/dvmdostem,Imports,FALSE -ncdf4,*,models/ldndc,Imports,FALSE -ncdf4,*,models/sibcasa,Imports,FALSE -ncdf4,*,models/stics,Imports,FALSE -ncdf4,*,modules/assim.sequential,Imports,FALSE -ncdf4,*,modules/data.remote,Imports,FALSE -ncdf4,>= 1.15,base/utils,Imports,FALSE -ncdf4,>= 1.15,base/visualization,Imports,FALSE -ncdf4,>= 1.15,models/biocro,Imports,FALSE -ncdf4,>= 1.15,models/clm45,Imports,FALSE -ncdf4,>= 1.15,models/dalec,Imports,FALSE -ncdf4,>= 1.15,models/ed,Imports,FALSE -ncdf4,>= 1.15,models/fates,Imports,FALSE -ncdf4,>= 1.15,models/gday,Imports,FALSE -ncdf4,>= 1.15,models/jules,Imports,FALSE -ncdf4,>= 1.15,models/linkages,Imports,FALSE -ncdf4,>= 1.15,models/lpjguess,Imports,FALSE -ncdf4,>= 1.15,models/maat,Imports,FALSE -ncdf4,>= 1.15,models/maespa,Imports,FALSE -ncdf4,>= 1.15,models/preles,Imports,FALSE -ncdf4,>= 1.15,models/sipnet,Imports,FALSE -ncdf4,>= 1.15,modules/assim.batch,Imports,FALSE -ncdf4,>= 1.15,modules/benchmark,Imports,FALSE -ncdf4,>= 1.15,modules/data.atmosphere,Imports,FALSE -ncdf4,>= 1.15,modules/data.land,Imports,FALSE -neonstore,*,modules/data.land,Imports,FALSE -neonUtilities,*,modules/data.land,Imports,FALSE -nimble,*,modules/assim.sequential,Imports,FALSE -nneo,*,modules/data.atmosphere,Imports,FALSE -optparse,*,base/settings,Imports,FALSE -parallel,*,modules/assim.batch,Imports,FALSE -parallel,*,modules/data.atmosphere,Suggests,FALSE -parallel,*,modules/data.remote,Imports,FALSE -PEcAn.allometry,*,base/all,Suggests,TRUE -PEcAn.assim.batch,*,base/all,Depends,TRUE -PEcAn.assim.batch,*,modules/rtm,Imports,TRUE -PEcAn.benchmark,*,base/all,Depends,TRUE -PEcAn.benchmark,*,modules/assim.batch,Imports,TRUE -PEcAn.benchmark,*,modules/assim.sequential,Suggests,TRUE -PEcAn.benchmark,*,modules/data.land,Imports,TRUE -PEcAn.BIOCRO,*,base/all,Suggests,TRUE -PEcAn.BIOCRO,*,base/qaqc,Suggests,TRUE -PEcAn.DALEC,*,base/all,Suggests,TRUE -PEcAn.data.atmosphere,*,base/all,Depends,TRUE -PEcAn.data.atmosphere,*,base/workflow,Imports,TRUE -PEcAn.data.atmosphere,*,models/basgra,Imports,TRUE -PEcAn.data.atmosphere,*,models/biocro,Imports,TRUE -PEcAn.data.atmosphere,*,models/ed,Imports,TRUE -PEcAn.data.atmosphere,*,models/jules,Imports,TRUE -PEcAn.data.atmosphere,*,models/ldndc,Imports,TRUE -PEcAn.data.atmosphere,*,models/linkages,Imports,TRUE -PEcAn.data.atmosphere,*,models/maat,Imports,TRUE -PEcAn.data.atmosphere,*,models/maespa,Imports,TRUE -PEcAn.data.atmosphere,*,models/preles,Imports,TRUE -PEcAn.data.atmosphere,*,models/sipnet,Depends,TRUE -PEcAn.data.land,*,base/all,Depends,TRUE -PEcAn.data.land,*,base/workflow,Imports,TRUE -PEcAn.data.land,*,models/biocro,Imports,TRUE -PEcAn.data.land,*,models/ed,Imports,TRUE -PEcAn.data.land,*,models/ldndc,Imports,TRUE -PEcAn.data.land,*,modules/assim.sequential,Suggests,TRUE -PEcAn.data.land,*,modules/benchmark,Suggests,TRUE -PEcAn.data.remote,*,base/all,Depends,TRUE -PEcAn.data.remote,*,modules/assim.sequential,Suggests,TRUE -PEcAn.DB,*,base/all,Depends,TRUE -PEcAn.DB,*,base/qaqc,Imports,TRUE -PEcAn.DB,*,base/settings,Imports,TRUE -PEcAn.DB,*,base/workflow,Imports,TRUE -PEcAn.DB,*,models/biocro,Suggests,TRUE -PEcAn.DB,*,models/template,Imports,TRUE -PEcAn.DB,*,modules/allometry,Imports,TRUE -PEcAn.DB,*,modules/assim.batch,Imports,TRUE -PEcAn.DB,*,modules/assim.sequential,Imports,TRUE -PEcAn.DB,*,modules/benchmark,Imports,TRUE -PEcAn.DB,*,modules/data.atmosphere,Imports,TRUE -PEcAn.DB,*,modules/data.land,Imports,TRUE -PEcAn.DB,*,modules/data.remote,Imports,TRUE -PEcAn.DB,*,modules/meta.analysis,Imports,TRUE -PEcAn.DB,*,modules/uncertainty,Imports,TRUE -PEcAn.ED2,*,base/all,Suggests,TRUE -PEcAn.ED2,*,base/qaqc,Suggests,TRUE -PEcAn.ED2,*,modules/rtm,Suggests,TRUE -PEcAn.emulator,*,base/all,Depends,TRUE -PEcAn.emulator,*,modules/assim.batch,Imports,TRUE -PEcAn.emulator,*,modules/uncertainty,Imports,TRUE -PEcAn.LINKAGES,*,base/all,Suggests,TRUE -PEcAn.logger,*,base/all,Depends,TRUE -PEcAn.logger,*,base/db,Imports,TRUE -PEcAn.logger,*,base/qaqc,Imports,TRUE -PEcAn.logger,*,base/remote,Imports,TRUE -PEcAn.logger,*,base/settings,Imports,TRUE -PEcAn.logger,*,base/utils,Imports,TRUE -PEcAn.logger,*,base/visualization,Imports,TRUE -PEcAn.logger,*,base/workflow,Imports,TRUE -PEcAn.logger,*,models/basgra,Imports,TRUE -PEcAn.logger,*,models/biocro,Imports,TRUE -PEcAn.logger,*,models/cable,Imports,TRUE -PEcAn.logger,*,models/clm45,Depends,TRUE -PEcAn.logger,*,models/dalec,Imports,TRUE -PEcAn.logger,*,models/dvmdostem,Imports,TRUE -PEcAn.logger,*,models/ed,Imports,TRUE -PEcAn.logger,*,models/fates,Imports,TRUE -PEcAn.logger,*,models/gday,Imports,TRUE -PEcAn.logger,*,models/jules,Imports,TRUE -PEcAn.logger,*,models/ldndc,Imports,TRUE -PEcAn.logger,*,models/linkages,Imports,TRUE -PEcAn.logger,*,models/lpjguess,Imports,TRUE -PEcAn.logger,*,models/maat,Imports,TRUE -PEcAn.logger,*,models/maespa,Imports,TRUE -PEcAn.logger,*,models/preles,Imports,TRUE -PEcAn.logger,*,models/sibcasa,Imports,TRUE -PEcAn.logger,*,models/sipnet,Imports,TRUE -PEcAn.logger,*,models/stics,Imports,TRUE -PEcAn.logger,*,models/template,Imports,TRUE -PEcAn.logger,*,modules/assim.batch,Imports,TRUE -PEcAn.logger,*,modules/assim.sequential,Imports,TRUE -PEcAn.logger,*,modules/benchmark,Imports,TRUE -PEcAn.logger,*,modules/data.atmosphere,Imports,TRUE -PEcAn.logger,*,modules/data.land,Imports,TRUE -PEcAn.logger,*,modules/data.remote,Imports,TRUE -PEcAn.logger,*,modules/meta.analysis,Imports,TRUE -PEcAn.logger,*,modules/priors,Imports,TRUE -PEcAn.logger,*,modules/rtm,Imports,TRUE -PEcAn.logger,*,modules/uncertainty,Imports,TRUE -PEcAn.MA,*,base/all,Depends,TRUE -PEcAn.MA,*,modules/assim.batch,Imports,TRUE -PEcAn.MA,*,modules/priors,Imports,TRUE -PEcAn.photosynthesis,*,base/all,Suggests,TRUE -PEcAn.priors,*,base/all,Depends,TRUE -PEcAn.priors,*,modules/uncertainty,Imports,TRUE -PEcAn.remote,*,base/all,Depends,TRUE -PEcAn.remote,*,base/db,Imports,TRUE -PEcAn.remote,*,base/settings,Imports,TRUE -PEcAn.remote,*,base/workflow,Imports,TRUE -PEcAn.remote,*,models/biocro,Imports,TRUE -PEcAn.remote,*,models/dalec,Imports,TRUE -PEcAn.remote,*,models/ed,Imports,TRUE -PEcAn.remote,*,models/fates,Imports,TRUE -PEcAn.remote,*,models/gday,Imports,TRUE -PEcAn.remote,*,models/jules,Imports,TRUE -PEcAn.remote,*,models/ldndc,Imports,TRUE -PEcAn.remote,*,models/linkages,Imports,TRUE -PEcAn.remote,*,models/lpjguess,Imports,TRUE -PEcAn.remote,*,models/maat,Imports,TRUE -PEcAn.remote,*,models/maespa,Imports,TRUE -PEcAn.remote,*,models/sipnet,Imports,TRUE -PEcAn.remote,*,models/stics,Imports,TRUE -PEcAn.remote,*,modules/assim.batch,Imports,TRUE -PEcAn.remote,*,modules/assim.sequential,Imports,TRUE -PEcAn.remote,*,modules/data.atmosphere,Imports,TRUE -PEcAn.remote,*,modules/data.land,Imports,TRUE -PEcAn.remote,*,modules/data.remote,Imports,TRUE -PEcAn.settings,*,base/all,Depends,TRUE -PEcAn.settings,*,base/workflow,Imports,TRUE -PEcAn.settings,*,models/biocro,Imports,TRUE -PEcAn.settings,*,models/ed,Imports,TRUE -PEcAn.settings,*,models/maat,Imports,TRUE -PEcAn.settings,*,models/stics,Imports,TRUE -PEcAn.settings,*,modules/assim.batch,Imports,TRUE -PEcAn.settings,*,modules/assim.sequential,Imports,TRUE -PEcAn.settings,*,modules/benchmark,Imports,TRUE -PEcAn.settings,*,modules/data.atmosphere,Suggests,TRUE -PEcAn.settings,*,modules/data.land,Suggests,TRUE -PEcAn.settings,*,modules/meta.analysis,Imports,TRUE -PEcAn.settings,*,modules/uncertainty,Imports,TRUE -PEcAn.SIPNET,*,base/all,Suggests,TRUE -PEcAn.SIPNET,*,base/qaqc,Suggests,TRUE -PEcAn.uncertainty,*,base/all,Depends,TRUE -PEcAn.uncertainty,*,base/workflow,Imports,TRUE -PEcAn.uncertainty,*,modules/assim.batch,Imports,TRUE -PEcAn.uncertainty,*,modules/assim.sequential,Imports,TRUE -PEcAn.utils,*,base/all,Depends,TRUE -PEcAn.utils,*,base/db,Imports,TRUE -PEcAn.utils,*,base/qaqc,Suggests,TRUE -PEcAn.utils,*,base/settings,Imports,TRUE -PEcAn.utils,*,base/workflow,Imports,TRUE -PEcAn.utils,*,models/biocro,Imports,TRUE -PEcAn.utils,*,models/clm45,Depends,TRUE -PEcAn.utils,*,models/dalec,Imports,TRUE -PEcAn.utils,*,models/ed,Imports,TRUE -PEcAn.utils,*,models/fates,Imports,TRUE -PEcAn.utils,*,models/gday,Depends,TRUE -PEcAn.utils,*,models/jules,Imports,TRUE -PEcAn.utils,*,models/linkages,Depends,TRUE -PEcAn.utils,*,models/lpjguess,Imports,TRUE -PEcAn.utils,*,models/maat,Imports,TRUE -PEcAn.utils,*,models/maespa,Imports,TRUE -PEcAn.utils,*,models/preles,Depends,TRUE -PEcAn.utils,*,models/preles,Imports,TRUE -PEcAn.utils,*,models/sipnet,Imports,TRUE -PEcAn.utils,*,modules/assim.batch,Imports,TRUE -PEcAn.utils,*,modules/assim.sequential,Suggests,TRUE -PEcAn.utils,*,modules/benchmark,Imports,TRUE -PEcAn.utils,*,modules/data.atmosphere,Imports,TRUE -PEcAn.utils,*,modules/data.land,Imports,TRUE -PEcAn.utils,*,modules/data.remote,Imports,TRUE -PEcAn.utils,*,modules/meta.analysis,Imports,TRUE -PEcAn.utils,*,modules/rtm,Suggests,TRUE -PEcAn.utils,*,modules/uncertainty,Imports,TRUE -PEcAn.utils,>= 1.4.8,models/basgra,Imports,TRUE -PEcAn.utils,>= 1.4.8,models/cable,Imports,TRUE -PEcAn.utils,>= 1.4.8,models/dvmdostem,Imports,TRUE -PEcAn.utils,>= 1.4.8,models/ldndc,Imports,TRUE -PEcAn.utils,>= 1.4.8,models/sibcasa,Imports,TRUE -PEcAn.utils,>= 1.4.8,models/stics,Imports,TRUE -PEcAn.utils,>= 1.4.8,models/template,Imports,TRUE -PEcAn.visualization,*,modules/assim.sequential,Suggests,TRUE -PEcAn.visualization,*,modules/data.land,Imports,TRUE -PEcAn.visualization,*,modules/priors,Suggests,TRUE -PEcAn.workflow,*,base/all,Depends,TRUE -PEcAn.workflow,*,modules/assim.batch,Imports,TRUE -PEcAn.workflow,*,modules/assim.sequential,Imports,TRUE -plotrix,*,base/qaqc,Imports,FALSE -plotrix,*,modules/assim.sequential,Suggests,FALSE -plyr,>= 1.8.4,base/visualization,Imports,FALSE -plyr,>= 1.8.4,modules/assim.sequential,Suggests,FALSE -plyr,>= 1.8.4,modules/uncertainty,Imports,FALSE -png,*,base/visualization,Suggests,FALSE -prodlim,*,modules/assim.batch,Imports,FALSE -progress,*,modules/data.atmosphere,Suggests,FALSE -purrr,*,base/db,Imports,FALSE -purrr,*,base/settings,Imports,FALSE -purrr,*,base/utils,Imports,FALSE -purrr,*,models/ed,Imports,FALSE -purrr,*,modules/assim.sequential,Imports,FALSE -purrr,*,modules/data.land,Imports,FALSE -purrr,*,modules/data.remote,Imports,FALSE -purrr,*,modules/uncertainty,Imports,FALSE -purrr,>= 0.2.3,base/workflow,Imports,FALSE -purrr,>= 0.2.3,modules/data.atmosphere,Imports,FALSE -pwr,*,modules/rtm,Suggests,FALSE -R.utils,*,base/db,Imports,FALSE -randomForest,*,modules/assim.sequential,Suggests,FALSE -randtoolbox,*,base/utils,Suggests,FALSE -randtoolbox,*,modules/uncertainty,Imports,FALSE -raster,*,base/visualization,Suggests,FALSE -raster,*,modules/assim.sequential,Suggests,FALSE -raster,*,modules/data.atmosphere,Imports,FALSE -raster,*,modules/data.land,Suggests,FALSE -raster,*,modules/data.remote,Suggests,FALSE -rcrossref,*,base/db,Suggests,FALSE -readr,*,models/ldndc,Imports,FALSE -readr,*,modules/assim.sequential,Suggests,FALSE -REddyProc,*,modules/data.atmosphere,Imports,FALSE -redland,*,modules/data.land,Suggests,FALSE -reshape,*,modules/data.remote,Suggests,FALSE -reshape2,*,base/visualization,Imports,FALSE -reshape2,*,modules/benchmark,Imports,FALSE -reshape2,*,modules/data.atmosphere,Imports,FALSE -reshape2,>= 1.4.2,modules/assim.sequential,Suggests,FALSE -reticulate,*,modules/data.atmosphere,Suggests,FALSE -reticulate,*,modules/data.land,Suggests,FALSE -reticulate,*,modules/data.remote,Imports,FALSE -rjags,*,base/utils,Suggests,FALSE -rjags,*,modules/assim.batch,Imports,FALSE -rjags,*,modules/data.land,Imports,FALSE -rjags,*,modules/meta.analysis,Imports,FALSE -rjags,*,modules/photosynthesis,Depends,FALSE -rjson,*,models/dvmdostem,Imports,FALSE -rlang,*,base/db,Imports,FALSE -rlang,*,base/qaqc,Imports,FALSE -rlang,*,base/utils,Imports,FALSE -rlang,*,base/visualization,Imports,FALSE -rlang,*,models/biocro,Imports,FALSE -rlang,*,models/ed,Imports,FALSE -rlang,*,models/ldndc,Imports,FALSE -rlang,*,modules/assim.sequential,Imports,FALSE -rlang,*,modules/benchmark,Imports,FALSE -rlang,*,modules/data.land,Imports,FALSE -rlang,*,modules/data.remote,Imports,FALSE -rlang,*,modules/uncertainty,Imports,FALSE -rlang,>= 0.2.0,modules/data.atmosphere,Imports,FALSE -rlist,*,modules/assim.sequential,Suggests,FALSE -rmarkdown,>= 2.19,base/db,Suggests,FALSE -rmarkdown,>= 2.19,base/qaqc,Suggests,FALSE -rmarkdown,>= 2.19,modules/allometry,Suggests,FALSE -rmarkdown,>= 2.19,modules/assim.batch,Suggests,FALSE -rmarkdown,>= 2.19,modules/meta.analysis,Suggests,FALSE -rmarkdown,>= 2.19,modules/photosynthesis,Suggests,FALSE -roxygen2,== 7.3.2,base/all,Roxygen,FALSE -roxygen2,== 7.3.2,base/db,Roxygen,FALSE -roxygen2,== 7.3.2,base/logger,Roxygen,FALSE -roxygen2,== 7.3.2,base/qaqc,Roxygen,FALSE -roxygen2,== 7.3.2,base/remote,Roxygen,FALSE -roxygen2,== 7.3.2,base/settings,Roxygen,FALSE -roxygen2,== 7.3.2,base/utils,Roxygen,FALSE -roxygen2,== 7.3.2,base/visualization,Roxygen,FALSE -roxygen2,== 7.3.2,base/workflow,Roxygen,FALSE -roxygen2,== 7.3.2,models/basgra,Roxygen,FALSE -roxygen2,== 7.3.2,models/biocro,Roxygen,FALSE -roxygen2,== 7.3.2,models/cable,Roxygen,FALSE -roxygen2,== 7.3.2,models/clm45,Roxygen,FALSE -roxygen2,== 7.3.2,models/dalec,Roxygen,FALSE -roxygen2,== 7.3.2,models/dvmdostem,Roxygen,FALSE -roxygen2,== 7.3.2,models/ed,Roxygen,FALSE -roxygen2,== 7.3.2,models/fates,Roxygen,FALSE -roxygen2,== 7.3.2,models/gday,Roxygen,FALSE -roxygen2,== 7.3.2,models/jules,Roxygen,FALSE -roxygen2,== 7.3.2,models/ldndc,Roxygen,FALSE -roxygen2,== 7.3.2,models/linkages,Roxygen,FALSE -roxygen2,== 7.3.2,models/lpjguess,Roxygen,FALSE -roxygen2,== 7.3.2,models/maat,Roxygen,FALSE -roxygen2,== 7.3.2,models/maespa,Roxygen,FALSE -roxygen2,== 7.3.2,models/preles,Roxygen,FALSE -roxygen2,== 7.3.2,models/sibcasa,Roxygen,FALSE -roxygen2,== 7.3.2,models/sipnet,Roxygen,FALSE -roxygen2,== 7.3.2,models/stics,Roxygen,FALSE -roxygen2,== 7.3.2,models/template,Roxygen,FALSE -roxygen2,== 7.3.2,modules/allometry,Roxygen,FALSE -roxygen2,== 7.3.2,modules/assim.batch,Roxygen,FALSE -roxygen2,== 7.3.2,modules/assim.sequential,Roxygen,FALSE -roxygen2,== 7.3.2,modules/benchmark,Roxygen,FALSE -roxygen2,== 7.3.2,modules/data.atmosphere,Roxygen,FALSE -roxygen2,== 7.3.2,modules/data.land,Roxygen,FALSE -roxygen2,== 7.3.2,modules/data.remote,Roxygen,FALSE -roxygen2,== 7.3.2,modules/emulator,Roxygen,FALSE -roxygen2,== 7.3.2,modules/meta.analysis,Roxygen,FALSE -roxygen2,== 7.3.2,modules/photosynthesis,Roxygen,FALSE -roxygen2,== 7.3.2,modules/priors,Roxygen,FALSE -roxygen2,== 7.3.2,modules/rtm,Roxygen,FALSE -roxygen2,== 7.3.2,modules/uncertainty,Roxygen,FALSE -RPostgres,*,base/db,Suggests,FALSE -RPostgreSQL,*,base/db,Suggests,FALSE -RPostgreSQL,*,models/biocro,Suggests,FALSE -Rpreles,*,models/preles,Suggests,FALSE -RSQLite,*,base/db,Suggests,FALSE -sessioninfo,*,base/all,Suggests,FALSE -sf,*,modules/assim.sequential,Suggests,FALSE -sf,*,modules/data.atmosphere,Imports,FALSE -sf,*,modules/data.land,Imports,FALSE -sf,*,modules/data.remote,Suggests,FALSE -SimilarityMeasures,*,modules/benchmark,Imports,FALSE -sirt,*,modules/data.land,Imports,FALSE -sp,*,base/visualization,Suggests,FALSE -sp,*,modules/assim.sequential,Suggests,FALSE -sp,*,modules/data.atmosphere,Imports,FALSE -sp,*,modules/data.land,Imports,FALSE -sp,*,modules/data.remote,Imports,FALSE -stats,*,base/qaqc,Imports,FALSE -stats,*,modules/allometry,Imports,FALSE -stats,*,modules/assim.batch,Imports,FALSE -stats,*,modules/assim.sequential,Suggests,FALSE -stats,*,modules/photosynthesis,Imports,FALSE -SticsRFiles,*,models/stics,Suggests,FALSE -stringi,*,base/logger,Imports,FALSE -stringi,*,base/utils,Imports,FALSE -stringr,*,models/fates,Imports,FALSE -stringr,*,modules/assim.sequential,Imports,FALSE -stringr,*,modules/benchmark,Imports,FALSE -stringr,*,modules/data.land,Imports,FALSE -stringr,>= 1.1.0,base/visualization,Imports,FALSE -stringr,>= 1.1.0,models/ed,Imports,FALSE -stringr,>= 1.1.0,modules/data.atmosphere,Imports,FALSE -suntools,*,modules/data.atmosphere,Imports,FALSE -swfscMisc,*,modules/data.land,Imports,FALSE -terra,*,modules/assim.sequential,Suggests,FALSE -terra,*,modules/data.atmosphere,Imports,FALSE -terra,*,modules/data.land,Imports,FALSE -terra,*,modules/data.remote,Imports,FALSE -testthat,*,base/all,Suggests,FALSE -testthat,*,base/logger,Suggests,FALSE -testthat,*,base/remote,Suggests,FALSE -testthat,*,base/workflow,Suggests,FALSE -testthat,*,modules/assim.sequential,Suggests,FALSE -testthat,*,modules/priors,Suggests,FALSE -testthat,>= 1.0.2,base/visualization,Suggests,FALSE -testthat,>= 1.0.2,models/basgra,Suggests,FALSE -testthat,>= 1.0.2,models/cable,Suggests,FALSE -testthat,>= 1.0.2,models/clm45,Suggests,FALSE -testthat,>= 1.0.2,models/dalec,Suggests,FALSE -testthat,>= 1.0.2,models/dvmdostem,Suggests,FALSE -testthat,>= 1.0.2,models/ed,Suggests,FALSE -testthat,>= 1.0.2,models/fates,Suggests,FALSE -testthat,>= 1.0.2,models/gday,Suggests,FALSE -testthat,>= 1.0.2,models/jules,Suggests,FALSE -testthat,>= 1.0.2,models/ldndc,Suggests,FALSE -testthat,>= 1.0.2,models/linkages,Suggests,FALSE -testthat,>= 1.0.2,models/lpjguess,Suggests,FALSE -testthat,>= 1.0.2,models/maat,Suggests,FALSE -testthat,>= 1.0.2,models/maespa,Suggests,FALSE -testthat,>= 1.0.2,models/preles,Suggests,FALSE -testthat,>= 1.0.2,models/sipnet,Suggests,FALSE -testthat,>= 1.0.2,models/stics,Suggests,FALSE -testthat,>= 1.0.2,models/template,Suggests,FALSE -testthat,>= 1.0.2,modules/allometry,Suggests,FALSE -testthat,>= 1.0.2,modules/assim.batch,Suggests,FALSE -testthat,>= 1.0.2,modules/data.land,Suggests,FALSE -testthat,>= 1.0.2,modules/data.remote,Suggests,FALSE -testthat,>= 1.0.2,modules/meta.analysis,Suggests,FALSE -testthat,>= 1.0.2,modules/rtm,Suggests,FALSE -testthat,>= 1.0.2,modules/uncertainty,Suggests,FALSE -testthat,>= 2.0.0,base/db,Suggests,FALSE -testthat,>= 2.0.0,base/settings,Suggests,FALSE -testthat,>= 2.0.0,base/utils,Suggests,FALSE -testthat,>= 2.0.0,models/biocro,Suggests,FALSE -testthat,>= 2.0.0,modules/benchmark,Suggests,FALSE -testthat,>= 2.0.0,modules/data.atmosphere,Suggests,FALSE -testthat,>= 3.0.0,models/sibcasa,Suggests,FALSE -testthat,>= 3.0.4,base/qaqc,Suggests,FALSE -tibble,*,base/db,Imports,FALSE -tibble,*,models/ed,Imports,FALSE -tibble,*,models/fates,Imports,FALSE -tibble,*,models/lpjguess,Imports,FALSE -tibble,*,modules/data.atmosphere,Imports,FALSE -tibble,*,modules/data.remote,Suggests,FALSE -tictoc,*,modules/assim.sequential,Suggests,FALSE -tidyr,*,base/db,Imports,FALSE -tidyr,*,models/ed,Imports,FALSE -tidyr,*,modules/assim.sequential,Suggests,FALSE -tidyr,*,modules/data.atmosphere,Imports,FALSE -tidyr,*,modules/data.land,Imports,FALSE -tidyselect,*,modules/benchmark,Imports,FALSE -tidyselect,*,modules/data.atmosphere,Imports,FALSE -tidyselect,*,modules/data.land,Imports,FALSE -tidyverse,*,base/db,Suggests,FALSE -tools,*,base/remote,Suggests,FALSE -tools,*,modules/allometry,Imports,FALSE -traits,*,modules/data.land,Imports,FALSE -TruncatedNormal,>= 2.2,modules/assim.batch,Imports,FALSE -truncnorm,*,modules/data.atmosphere,Imports,FALSE -units,*,base/db,Imports,FALSE -units,*,base/utils,Imports,FALSE -units,*,modules/benchmark,Imports,FALSE -units,*,modules/data.atmosphere,Imports,FALSE -urltools,*,base/remote,Imports,FALSE -utils,*,base/all,Imports,FALSE -utils,*,base/logger,Imports,FALSE -utils,*,models/ed,Imports,FALSE -utils,*,modules/allometry,Imports,FALSE -utils,*,modules/assim.batch,Imports,FALSE -utils,*,modules/assim.sequential,Suggests,FALSE -utils,*,modules/benchmark,Imports,FALSE -utils,*,modules/data.remote,Suggests,FALSE -utils,*,modules/photosynthesis,Imports,FALSE -vdiffr,>= 1.0.2,base/qaqc,Suggests,FALSE -withr,*,base/db,Suggests,FALSE -withr,*,base/logger,Suggests,FALSE -withr,*,base/qaqc,Suggests,FALSE -withr,*,base/remote,Suggests,FALSE -withr,*,base/settings,Suggests,FALSE -withr,*,base/utils,Suggests,FALSE -withr,*,base/visualization,Suggests,FALSE -withr,*,base/workflow,Suggests,FALSE -withr,*,models/basgra,Suggests,FALSE -withr,*,models/ed,Suggests,FALSE -withr,*,models/sibcasa,Suggests,FALSE -withr,*,modules/allometry,Suggests,FALSE -withr,*,modules/data.atmosphere,Suggests,FALSE -XML,*,base/db,Imports,FALSE -XML,*,base/workflow,Imports,FALSE -XML,*,models/biocro,Imports,FALSE -XML,*,models/maat,Imports,FALSE -XML,*,models/stics,Imports,FALSE -XML,*,modules/assim.batch,Imports,FALSE -XML,*,modules/assim.sequential,Suggests,FALSE -XML,*,modules/data.remote,Imports,FALSE -XML,*,modules/rtm,Suggests,FALSE -XML,>= 3.98-1.3,base/settings,Imports,FALSE -XML,>= 3.98-1.4,models/ed,Imports,FALSE -XML,>= 3.98-1.4,modules/benchmark,Imports,FALSE -XML,>= 3.98-1.4,modules/data.atmosphere,Imports,FALSE -XML,>= 3.98-1.4,modules/data.land,Imports,FALSE -xtable,*,base/utils,Suggests,FALSE -xts,*,modules/data.atmosphere,Imports,FALSE -zoo,*,modules/benchmark,Imports,FALSE -zoo,*,modules/data.atmosphere,Imports,FALSE \ No newline at end of file +"package","version","needed_by_dir","type","is_pecan" +"abind","*","modules/assim.batch","Imports",FALSE +"abind",">= 1.4.5","base/utils","Imports",FALSE +"abind",">= 1.4.5","models/ed","Imports",FALSE +"abind",">= 1.4.5","modules/data.atmosphere","Imports",FALSE +"amerifluxr","*","modules/data.atmosphere","Imports",FALSE +"arrow","*","modules/data.atmosphere","Imports",FALSE +"assertthat","*","models/ed","Imports",FALSE +"assertthat","*","modules/data.atmosphere","Imports",FALSE +"BayesianTools","*","modules/assim.batch","Imports",FALSE +"BayesianTools","*","modules/rtm","Imports",FALSE +"BioCro","*","models/biocro","Suggests",FALSE +"bit64","*","base/db","Suggests",FALSE +"BrownDog","*","modules/benchmark","Suggests",FALSE +"coda","*","models/maespa","Suggests",FALSE +"coda","*","models/sipnet","Suggests",FALSE +"coda","*","modules/assim.sequential","Imports",FALSE +"coda","*","modules/data.land","Imports",FALSE +"coda","*","modules/rtm","Imports",FALSE +"coda",">= 0.18","base/utils","Suggests",FALSE +"coda",">= 0.18","modules/allometry","Imports",FALSE +"coda",">= 0.18","modules/assim.batch","Imports",FALSE +"coda",">= 0.18","modules/emulator","Imports",FALSE +"coda",">= 0.18","modules/meta.analysis","Imports",FALSE +"coda",">= 0.18","modules/photosynthesis","Imports",FALSE +"corrplot","*","modules/assim.sequential","Suggests",FALSE +"curl","*","base/db","Imports",FALSE +"curl","*","base/utils","Imports",FALSE +"curl","*","modules/data.atmosphere","Imports",FALSE +"curl","*","modules/data.land","Imports",FALSE +"curl","*","modules/data.remote","Imports",FALSE +"data.table","*","base/db","Suggests",FALSE +"data.table","*","base/utils","Suggests",FALSE +"data.table","*","base/visualization","Imports",FALSE +"data.table","*","models/biocro","Imports",FALSE +"data.table","*","modules/data.remote","Suggests",FALSE +"dataone","*","modules/data.land","Suggests",FALSE +"datapack","*","modules/data.land","Imports",FALSE +"DBI","*","base/db","Imports",FALSE +"DBI","*","modules/data.remote","Imports",FALSE +"dbplyr",">= 2.4.0","base/db","Imports",FALSE +"devtools","*","models/ed","Suggests",FALSE +"doParallel","*","modules/data.atmosphere","Suggests",FALSE +"doParallel","*","modules/data.remote","Imports",FALSE +"doSNOW","*","base/remote","Suggests",FALSE +"dplR","*","modules/data.land","Imports",FALSE +"dplyr","*","base/qaqc","Imports",FALSE +"dplyr","*","base/remote","Imports",FALSE +"dplyr","*","base/utils","Imports",FALSE +"dplyr","*","base/workflow","Imports",FALSE +"dplyr","*","models/biocro","Imports",FALSE +"dplyr","*","models/ed","Imports",FALSE +"dplyr","*","models/ldndc","Imports",FALSE +"dplyr","*","models/stics","Imports",FALSE +"dplyr","*","modules/assim.sequential","Imports",FALSE +"dplyr","*","modules/benchmark","Imports",FALSE +"dplyr","*","modules/data.land","Imports",FALSE +"dplyr","*","modules/data.remote","Suggests",FALSE +"dplyr","*","modules/uncertainty","Imports",FALSE +"dplyr",">= 0.8.1","modules/data.atmosphere","Imports",FALSE +"dplyr",">= 1.1.2","base/db","Imports",FALSE +"ellipse","*","modules/assim.batch","Imports",FALSE +"emdbook","*","modules/assim.sequential","Suggests",FALSE +"foreach","*","base/remote","Imports",FALSE +"foreach","*","modules/data.atmosphere","Suggests",FALSE +"foreach","*","modules/data.remote","Imports",FALSE +"fs","*","base/db","Imports",FALSE +"fs","*","modules/data.land","Imports",FALSE +"furrr","*","base/remote","Imports",FALSE +"furrr","*","modules/assim.sequential","Imports",FALSE +"furrr","*","modules/data.atmosphere","Suggests",FALSE +"furrr","*","modules/data.land","Imports",FALSE +"furrr","*","modules/data.remote","Imports",FALSE +"future","*","modules/assim.sequential","Imports",FALSE +"future","*","modules/data.atmosphere","Suggests",FALSE +"future","*","modules/data.land","Imports",FALSE +"future","*","modules/data.remote","Imports",FALSE +"GEDI4R","*","modules/data.remote","Suggests",FALSE +"geonames","> 0.998","modules/data.atmosphere","Imports",FALSE +"getPass","*","base/remote","Suggests",FALSE +"getPass","*","modules/data.land","Suggests",FALSE +"getPass","*","modules/data.remote","Suggests",FALSE +"ggmcmc","*","modules/meta.analysis","Suggests",FALSE +"ggplot2","*","base/utils","Suggests",FALSE +"ggplot2","*","base/visualization","Imports",FALSE +"ggplot2","*","modules/assim.sequential","Imports",FALSE +"ggplot2","*","modules/benchmark","Imports",FALSE +"ggplot2","*","modules/data.atmosphere","Imports",FALSE +"ggplot2","*","modules/data.remote","Suggests",FALSE +"ggplot2","*","modules/meta.analysis","Suggests",FALSE +"ggplot2","*","modules/priors","Imports",FALSE +"ggplot2","*","modules/uncertainty","Imports",FALSE +"ggpubr","*","modules/assim.sequential","Suggests",FALSE +"ggrepel","*","modules/assim.sequential","Suggests",FALSE +"glue","*","base/db","Imports",FALSE +"glue","*","models/ed","Imports",FALSE +"glue","*","modules/assim.sequential","Suggests",FALSE +"glue","*","modules/data.atmosphere","Imports",FALSE +"glue","*","modules/data.land","Suggests",FALSE +"glue","*","modules/data.remote","Imports",FALSE +"graphics","*","base/qaqc","Imports",FALSE +"graphics","*","modules/allometry","Imports",FALSE +"graphics","*","modules/assim.batch","Imports",FALSE +"graphics","*","modules/photosynthesis","Imports",FALSE +"grDevices","*","modules/allometry","Imports",FALSE +"grDevices","*","modules/assim.batch","Imports",FALSE +"grDevices","*","modules/benchmark","Imports",FALSE +"grDevices","*","modules/data.remote","Suggests",FALSE +"grid","*","base/visualization","Suggests",FALSE +"gridExtra","*","modules/assim.sequential","Suggests",FALSE +"gridExtra","*","modules/benchmark","Imports",FALSE +"gridExtra","*","modules/uncertainty","Imports",FALSE +"hdf5r","*","models/ed","Imports",FALSE +"here","*","base/db","Suggests",FALSE +"httr","*","base/remote","Imports",FALSE +"httr","*","modules/data.atmosphere","Imports",FALSE +"httr","*","modules/data.land","Imports",FALSE +"httr","*","modules/data.remote","Suggests",FALSE +"IDPmisc","*","modules/assim.batch","Imports",FALSE +"jsonlite","*","base/remote","Imports",FALSE +"jsonlite","*","models/stics","Imports",FALSE +"jsonlite","*","modules/data.atmosphere","Imports",FALSE +"jsonlite","*","modules/data.remote","Suggests",FALSE +"knitr",">= 1.42","base/db","Suggests",FALSE +"knitr",">= 1.42","base/qaqc","Suggests",FALSE +"knitr",">= 1.42","modules/allometry","Suggests",FALSE +"knitr",">= 1.42","modules/assim.batch","Suggests",FALSE +"knitr",">= 1.42","modules/meta.analysis","Suggests",FALSE +"knitr",">= 1.42","modules/photosynthesis","Suggests",FALSE +"knitr",">= 1.42","modules/rtm","Suggests",FALSE +"lattice","*","modules/meta.analysis","Imports",FALSE +"linkages","*","models/linkages","Suggests",FALSE +"lqmm","*","modules/assim.batch","Imports",FALSE +"lubridate","*","base/db","Imports",FALSE +"lubridate","*","models/basgra","Imports",FALSE +"lubridate","*","models/dvmdostem","Imports",FALSE +"lubridate","*","models/ed","Imports",FALSE +"lubridate","*","models/ldndc","Imports",FALSE +"lubridate","*","models/stics","Imports",FALSE +"lubridate","*","modules/data.land","Imports",FALSE +"lubridate","*","modules/data.remote","Suggests",FALSE +"lubridate",">= 1.6.0","base/settings","Imports",FALSE +"lubridate",">= 1.6.0","base/utils","Imports",FALSE +"lubridate",">= 1.6.0","models/dalec","Imports",FALSE +"lubridate",">= 1.6.0","models/fates","Imports",FALSE +"lubridate",">= 1.6.0","models/gday","Imports",FALSE +"lubridate",">= 1.6.0","models/jules","Imports",FALSE +"lubridate",">= 1.6.0","models/linkages","Imports",FALSE +"lubridate",">= 1.6.0","models/lpjguess","Imports",FALSE +"lubridate",">= 1.6.0","models/maat","Imports",FALSE +"lubridate",">= 1.6.0","models/maespa","Imports",FALSE +"lubridate",">= 1.6.0","models/preles","Imports",FALSE +"lubridate",">= 1.6.0","models/sipnet","Imports",FALSE +"lubridate",">= 1.6.0","modules/assim.batch","Imports",FALSE +"lubridate",">= 1.6.0","modules/assim.sequential","Imports",FALSE +"lubridate",">= 1.6.0","modules/benchmark","Imports",FALSE +"lubridate",">= 1.6.0","modules/data.atmosphere","Imports",FALSE +"lubridate",">= 1.6.0","modules/rtm","Imports",FALSE +"lubridate",">= 1.7.0","models/biocro","Imports",FALSE +"Maeswrap","*","models/maespa","Suggests",FALSE +"magic",">= 1.5.0","modules/assim.sequential","Suggests",FALSE +"magrittr","*","base/db","Imports",FALSE +"magrittr","*","base/utils","Imports",FALSE +"magrittr","*","models/ed","Imports",FALSE +"magrittr","*","modules/assim.sequential","Imports",FALSE +"magrittr","*","modules/benchmark","Imports",FALSE +"magrittr","*","modules/data.land","Imports",FALSE +"magrittr","*","modules/data.remote","Imports",FALSE +"markdown","*","modules/allometry","Suggests",FALSE +"markdown","*","modules/photosynthesis","Suggests",FALSE +"MASS","*","base/utils","Suggests",FALSE +"MASS","*","modules/assim.batch","Imports",FALSE +"MASS","*","modules/data.atmosphere","Imports",FALSE +"MASS","*","modules/meta.analysis","Imports",FALSE +"MASS","*","modules/priors","Imports",FALSE +"MASS","*","modules/rtm","Imports",FALSE +"Matrix","*","modules/assim.sequential","Imports",FALSE +"mclust","*","modules/rtm","Suggests",FALSE +"MCMCpack","*","modules/allometry","Imports",FALSE +"MCMCpack","*","modules/assim.batch","Imports",FALSE +"MCMCpack","*","modules/emulator","Imports",FALSE +"methods","*","base/db","Imports",FALSE +"methods","*","base/settings","Depends",FALSE +"methods","*","modules/allometry","Imports",FALSE +"methods","*","modules/assim.batch","Imports",FALSE +"methods","*","modules/assim.sequential","Suggests",FALSE +"methods","*","modules/emulator","Imports",FALSE +"mgcv","*","modules/data.atmosphere","Imports",FALSE +"minpack.lm","*","modules/rtm","Suggests",FALSE +"mlegp","*","modules/assim.batch","Imports",FALSE +"mockery","*","base/all","Suggests",FALSE +"mockery","*","base/qaqc","Suggests",FALSE +"mockery","*","base/remote","Suggests",FALSE +"mockery","*","base/settings","Suggests",FALSE +"mockery","*","base/utils","Suggests",FALSE +"mockery","*","base/visualization","Suggests",FALSE +"mockery","*","base/workflow","Suggests",FALSE +"mockery","*","modules/data.atmosphere","Suggests",FALSE +"mockery",">= 0.3.0","models/biocro","Suggests",FALSE +"mockery",">= 0.4.3","base/db","Suggests",FALSE +"MODISTools",">= 1.1.0","modules/data.remote","Imports",FALSE +"mvbutils","*","base/qaqc","Suggests",FALSE +"mvtnorm","*","modules/allometry","Imports",FALSE +"mvtnorm","*","modules/assim.batch","Imports",FALSE +"mvtnorm","*","modules/assim.sequential","Imports",FALSE +"mvtnorm","*","modules/data.land","Imports",FALSE +"mvtnorm","*","modules/emulator","Imports",FALSE +"ncdf4","*","base/db","Imports",FALSE +"ncdf4","*","models/basgra","Imports",FALSE +"ncdf4","*","models/dvmdostem","Imports",FALSE +"ncdf4","*","models/ldndc","Imports",FALSE +"ncdf4","*","models/sibcasa","Imports",FALSE +"ncdf4","*","models/stics","Imports",FALSE +"ncdf4","*","modules/assim.sequential","Imports",FALSE +"ncdf4","*","modules/data.remote","Imports",FALSE +"ncdf4",">= 1.15","base/utils","Imports",FALSE +"ncdf4",">= 1.15","base/visualization","Imports",FALSE +"ncdf4",">= 1.15","models/biocro","Imports",FALSE +"ncdf4",">= 1.15","models/clm45","Imports",FALSE +"ncdf4",">= 1.15","models/dalec","Imports",FALSE +"ncdf4",">= 1.15","models/ed","Imports",FALSE +"ncdf4",">= 1.15","models/fates","Imports",FALSE +"ncdf4",">= 1.15","models/gday","Imports",FALSE +"ncdf4",">= 1.15","models/jules","Imports",FALSE +"ncdf4",">= 1.15","models/linkages","Imports",FALSE +"ncdf4",">= 1.15","models/lpjguess","Imports",FALSE +"ncdf4",">= 1.15","models/maat","Imports",FALSE +"ncdf4",">= 1.15","models/maespa","Imports",FALSE +"ncdf4",">= 1.15","models/preles","Imports",FALSE +"ncdf4",">= 1.15","models/sipnet","Imports",FALSE +"ncdf4",">= 1.15","modules/assim.batch","Imports",FALSE +"ncdf4",">= 1.15","modules/benchmark","Imports",FALSE +"ncdf4",">= 1.15","modules/data.atmosphere","Imports",FALSE +"ncdf4",">= 1.15","modules/data.land","Imports",FALSE +"neonstore","*","modules/data.land","Imports",FALSE +"neonUtilities","*","modules/data.land","Imports",FALSE +"nimble","*","modules/assim.sequential","Imports",FALSE +"nneo","*","modules/data.atmosphere","Imports",FALSE +"optparse","*","base/settings","Imports",FALSE +"parallel","*","modules/assim.batch","Imports",FALSE +"parallel","*","modules/data.atmosphere","Suggests",FALSE +"parallel","*","modules/data.remote","Imports",FALSE +"PEcAn.allometry","*","base/all","Suggests",TRUE +"PEcAn.assim.batch","*","base/all","Depends",TRUE +"PEcAn.assim.batch","*","modules/rtm","Imports",TRUE +"PEcAn.benchmark","*","base/all","Depends",TRUE +"PEcAn.benchmark","*","modules/assim.batch","Imports",TRUE +"PEcAn.benchmark","*","modules/assim.sequential","Suggests",TRUE +"PEcAn.benchmark","*","modules/data.land","Imports",TRUE +"PEcAn.BIOCRO","*","base/all","Suggests",TRUE +"PEcAn.BIOCRO","*","base/qaqc","Suggests",TRUE +"PEcAn.DALEC","*","base/all","Suggests",TRUE +"PEcAn.data.atmosphere","*","base/all","Depends",TRUE +"PEcAn.data.atmosphere","*","base/workflow","Imports",TRUE +"PEcAn.data.atmosphere","*","models/basgra","Imports",TRUE +"PEcAn.data.atmosphere","*","models/biocro","Imports",TRUE +"PEcAn.data.atmosphere","*","models/ed","Imports",TRUE +"PEcAn.data.atmosphere","*","models/jules","Imports",TRUE +"PEcAn.data.atmosphere","*","models/ldndc","Imports",TRUE +"PEcAn.data.atmosphere","*","models/linkages","Imports",TRUE +"PEcAn.data.atmosphere","*","models/maat","Imports",TRUE +"PEcAn.data.atmosphere","*","models/maespa","Imports",TRUE +"PEcAn.data.atmosphere","*","models/preles","Imports",TRUE +"PEcAn.data.atmosphere","*","models/sipnet","Depends",TRUE +"PEcAn.data.land","*","base/all","Depends",TRUE +"PEcAn.data.land","*","base/workflow","Imports",TRUE +"PEcAn.data.land","*","models/biocro","Imports",TRUE +"PEcAn.data.land","*","models/ed","Imports",TRUE +"PEcAn.data.land","*","models/ldndc","Imports",TRUE +"PEcAn.data.land","*","modules/assim.sequential","Suggests",TRUE +"PEcAn.data.land","*","modules/benchmark","Suggests",TRUE +"PEcAn.data.remote","*","base/all","Depends",TRUE +"PEcAn.data.remote","*","modules/assim.sequential","Suggests",TRUE +"PEcAn.DB","*","base/all","Depends",TRUE +"PEcAn.DB","*","base/qaqc","Imports",TRUE +"PEcAn.DB","*","base/settings","Imports",TRUE +"PEcAn.DB","*","base/workflow","Imports",TRUE +"PEcAn.DB","*","models/biocro","Suggests",TRUE +"PEcAn.DB","*","models/template","Imports",TRUE +"PEcAn.DB","*","modules/allometry","Imports",TRUE +"PEcAn.DB","*","modules/assim.batch","Imports",TRUE +"PEcAn.DB","*","modules/assim.sequential","Imports",TRUE +"PEcAn.DB","*","modules/benchmark","Imports",TRUE +"PEcAn.DB","*","modules/data.atmosphere","Imports",TRUE +"PEcAn.DB","*","modules/data.land","Imports",TRUE +"PEcAn.DB","*","modules/data.remote","Imports",TRUE +"PEcAn.DB","*","modules/meta.analysis","Imports",TRUE +"PEcAn.DB","*","modules/uncertainty","Imports",TRUE +"PEcAn.ED2","*","base/all","Suggests",TRUE +"PEcAn.ED2","*","base/qaqc","Suggests",TRUE +"PEcAn.ED2","*","modules/rtm","Suggests",TRUE +"PEcAn.emulator","*","base/all","Depends",TRUE +"PEcAn.emulator","*","modules/assim.batch","Imports",TRUE +"PEcAn.emulator","*","modules/uncertainty","Imports",TRUE +"PEcAn.LINKAGES","*","base/all","Suggests",TRUE +"PEcAn.logger","*","base/all","Depends",TRUE +"PEcAn.logger","*","base/db","Imports",TRUE +"PEcAn.logger","*","base/qaqc","Imports",TRUE +"PEcAn.logger","*","base/remote","Imports",TRUE +"PEcAn.logger","*","base/settings","Imports",TRUE +"PEcAn.logger","*","base/utils","Imports",TRUE +"PEcAn.logger","*","base/visualization","Imports",TRUE +"PEcAn.logger","*","base/workflow","Imports",TRUE +"PEcAn.logger","*","models/basgra","Imports",TRUE +"PEcAn.logger","*","models/biocro","Imports",TRUE +"PEcAn.logger","*","models/cable","Imports",TRUE +"PEcAn.logger","*","models/clm45","Depends",TRUE +"PEcAn.logger","*","models/dalec","Imports",TRUE +"PEcAn.logger","*","models/dvmdostem","Imports",TRUE +"PEcAn.logger","*","models/ed","Imports",TRUE +"PEcAn.logger","*","models/fates","Imports",TRUE +"PEcAn.logger","*","models/gday","Imports",TRUE +"PEcAn.logger","*","models/jules","Imports",TRUE +"PEcAn.logger","*","models/ldndc","Imports",TRUE +"PEcAn.logger","*","models/linkages","Imports",TRUE +"PEcAn.logger","*","models/lpjguess","Imports",TRUE +"PEcAn.logger","*","models/maat","Imports",TRUE +"PEcAn.logger","*","models/maespa","Imports",TRUE +"PEcAn.logger","*","models/preles","Imports",TRUE +"PEcAn.logger","*","models/sibcasa","Imports",TRUE +"PEcAn.logger","*","models/sipnet","Imports",TRUE +"PEcAn.logger","*","models/stics","Imports",TRUE +"PEcAn.logger","*","models/template","Imports",TRUE +"PEcAn.logger","*","modules/assim.batch","Imports",TRUE +"PEcAn.logger","*","modules/assim.sequential","Imports",TRUE +"PEcAn.logger","*","modules/benchmark","Imports",TRUE +"PEcAn.logger","*","modules/data.atmosphere","Imports",TRUE +"PEcAn.logger","*","modules/data.land","Imports",TRUE +"PEcAn.logger","*","modules/data.remote","Imports",TRUE +"PEcAn.logger","*","modules/meta.analysis","Imports",TRUE +"PEcAn.logger","*","modules/priors","Imports",TRUE +"PEcAn.logger","*","modules/rtm","Imports",TRUE +"PEcAn.logger","*","modules/uncertainty","Imports",TRUE +"PEcAn.MA","*","base/all","Depends",TRUE +"PEcAn.MA","*","modules/assim.batch","Imports",TRUE +"PEcAn.MA","*","modules/priors","Imports",TRUE +"PEcAn.photosynthesis","*","base/all","Suggests",TRUE +"PEcAn.priors","*","base/all","Depends",TRUE +"PEcAn.priors","*","modules/uncertainty","Imports",TRUE +"PEcAn.remote","*","base/all","Depends",TRUE +"PEcAn.remote","*","base/db","Imports",TRUE +"PEcAn.remote","*","base/settings","Imports",TRUE +"PEcAn.remote","*","base/workflow","Imports",TRUE +"PEcAn.remote","*","models/biocro","Imports",TRUE +"PEcAn.remote","*","models/dalec","Imports",TRUE +"PEcAn.remote","*","models/ed","Imports",TRUE +"PEcAn.remote","*","models/fates","Imports",TRUE +"PEcAn.remote","*","models/gday","Imports",TRUE +"PEcAn.remote","*","models/jules","Imports",TRUE +"PEcAn.remote","*","models/ldndc","Imports",TRUE +"PEcAn.remote","*","models/linkages","Imports",TRUE +"PEcAn.remote","*","models/lpjguess","Imports",TRUE +"PEcAn.remote","*","models/maat","Imports",TRUE +"PEcAn.remote","*","models/maespa","Imports",TRUE +"PEcAn.remote","*","models/sipnet","Imports",TRUE +"PEcAn.remote","*","models/stics","Imports",TRUE +"PEcAn.remote","*","modules/assim.batch","Imports",TRUE +"PEcAn.remote","*","modules/assim.sequential","Imports",TRUE +"PEcAn.remote","*","modules/data.atmosphere","Imports",TRUE +"PEcAn.remote","*","modules/data.land","Imports",TRUE +"PEcAn.remote","*","modules/data.remote","Imports",TRUE +"PEcAn.settings","*","base/all","Depends",TRUE +"PEcAn.settings","*","base/workflow","Imports",TRUE +"PEcAn.settings","*","models/biocro","Imports",TRUE +"PEcAn.settings","*","models/ed","Imports",TRUE +"PEcAn.settings","*","models/maat","Imports",TRUE +"PEcAn.settings","*","models/stics","Imports",TRUE +"PEcAn.settings","*","modules/assim.batch","Imports",TRUE +"PEcAn.settings","*","modules/assim.sequential","Imports",TRUE +"PEcAn.settings","*","modules/benchmark","Imports",TRUE +"PEcAn.settings","*","modules/data.atmosphere","Suggests",TRUE +"PEcAn.settings","*","modules/data.land","Suggests",TRUE +"PEcAn.settings","*","modules/meta.analysis","Imports",TRUE +"PEcAn.settings","*","modules/uncertainty","Imports",TRUE +"PEcAn.SIPNET","*","base/all","Suggests",TRUE +"PEcAn.SIPNET","*","base/qaqc","Suggests",TRUE +"PEcAn.uncertainty","*","base/all","Depends",TRUE +"PEcAn.uncertainty","*","base/workflow","Imports",TRUE +"PEcAn.uncertainty","*","modules/assim.batch","Imports",TRUE +"PEcAn.uncertainty","*","modules/assim.sequential","Imports",TRUE +"PEcAn.utils","*","base/all","Depends",TRUE +"PEcAn.utils","*","base/db","Imports",TRUE +"PEcAn.utils","*","base/qaqc","Suggests",TRUE +"PEcAn.utils","*","base/settings","Imports",TRUE +"PEcAn.utils","*","base/workflow","Imports",TRUE +"PEcAn.utils","*","models/biocro","Imports",TRUE +"PEcAn.utils","*","models/clm45","Depends",TRUE +"PEcAn.utils","*","models/dalec","Imports",TRUE +"PEcAn.utils","*","models/ed","Imports",TRUE +"PEcAn.utils","*","models/fates","Imports",TRUE +"PEcAn.utils","*","models/gday","Depends",TRUE +"PEcAn.utils","*","models/jules","Imports",TRUE +"PEcAn.utils","*","models/linkages","Depends",TRUE +"PEcAn.utils","*","models/lpjguess","Imports",TRUE +"PEcAn.utils","*","models/maat","Imports",TRUE +"PEcAn.utils","*","models/maespa","Imports",TRUE +"PEcAn.utils","*","models/preles","Depends",TRUE +"PEcAn.utils","*","models/preles","Imports",TRUE +"PEcAn.utils","*","models/sipnet","Imports",TRUE +"PEcAn.utils","*","modules/assim.batch","Imports",TRUE +"PEcAn.utils","*","modules/assim.sequential","Suggests",TRUE +"PEcAn.utils","*","modules/benchmark","Imports",TRUE +"PEcAn.utils","*","modules/data.atmosphere","Imports",TRUE +"PEcAn.utils","*","modules/data.land","Imports",TRUE +"PEcAn.utils","*","modules/data.remote","Imports",TRUE +"PEcAn.utils","*","modules/meta.analysis","Imports",TRUE +"PEcAn.utils","*","modules/rtm","Suggests",TRUE +"PEcAn.utils","*","modules/uncertainty","Imports",TRUE +"PEcAn.utils",">= 1.4.8","models/basgra","Imports",TRUE +"PEcAn.utils",">= 1.4.8","models/cable","Imports",TRUE +"PEcAn.utils",">= 1.4.8","models/dvmdostem","Imports",TRUE +"PEcAn.utils",">= 1.4.8","models/ldndc","Imports",TRUE +"PEcAn.utils",">= 1.4.8","models/sibcasa","Imports",TRUE +"PEcAn.utils",">= 1.4.8","models/stics","Imports",TRUE +"PEcAn.utils",">= 1.4.8","models/template","Imports",TRUE +"PEcAn.visualization","*","modules/assim.sequential","Suggests",TRUE +"PEcAn.visualization","*","modules/data.land","Imports",TRUE +"PEcAn.visualization","*","modules/priors","Suggests",TRUE +"PEcAn.workflow","*","base/all","Depends",TRUE +"PEcAn.workflow","*","modules/assim.batch","Imports",TRUE +"PEcAn.workflow","*","modules/assim.sequential","Imports",TRUE +"plotrix","*","base/qaqc","Imports",FALSE +"plotrix","*","modules/assim.sequential","Suggests",FALSE +"plyr",">= 1.8.4","base/visualization","Imports",FALSE +"plyr",">= 1.8.4","modules/assim.sequential","Suggests",FALSE +"plyr",">= 1.8.4","modules/uncertainty","Imports",FALSE +"png","*","base/visualization","Suggests",FALSE +"prodlim","*","modules/assim.batch","Imports",FALSE +"progress","*","modules/data.atmosphere","Suggests",FALSE +"purrr","*","base/db","Imports",FALSE +"purrr","*","base/settings","Imports",FALSE +"purrr","*","base/utils","Imports",FALSE +"purrr","*","models/ed","Imports",FALSE +"purrr","*","modules/assim.sequential","Imports",FALSE +"purrr","*","modules/data.land","Imports",FALSE +"purrr","*","modules/data.remote","Imports",FALSE +"purrr","*","modules/uncertainty","Imports",FALSE +"purrr",">= 0.2.3","base/workflow","Imports",FALSE +"purrr",">= 0.2.3","modules/data.atmosphere","Imports",FALSE +"pwr","*","modules/rtm","Suggests",FALSE +"R.utils","*","base/db","Imports",FALSE +"randomForest","*","modules/assim.sequential","Suggests",FALSE +"randtoolbox","*","base/utils","Suggests",FALSE +"randtoolbox","*","modules/uncertainty","Imports",FALSE +"raster","*","base/visualization","Suggests",FALSE +"raster","*","modules/assim.sequential","Suggests",FALSE +"raster","*","modules/data.atmosphere","Imports",FALSE +"raster","*","modules/data.land","Suggests",FALSE +"raster","*","modules/data.remote","Suggests",FALSE +"rcrossref","*","base/db","Suggests",FALSE +"readr","*","models/ldndc","Imports",FALSE +"readr","*","modules/assim.sequential","Suggests",FALSE +"REddyProc","*","modules/data.atmosphere","Imports",FALSE +"redland","*","modules/data.land","Suggests",FALSE +"reshape","*","modules/data.remote","Suggests",FALSE +"reshape2","*","base/visualization","Imports",FALSE +"reshape2","*","modules/benchmark","Imports",FALSE +"reshape2","*","modules/data.atmosphere","Imports",FALSE +"reshape2",">= 1.4.2","modules/assim.sequential","Suggests",FALSE +"reticulate","*","modules/data.atmosphere","Suggests",FALSE +"reticulate","*","modules/data.land","Suggests",FALSE +"reticulate","*","modules/data.remote","Imports",FALSE +"rjags","*","base/utils","Suggests",FALSE +"rjags","*","modules/assim.batch","Imports",FALSE +"rjags","*","modules/data.land","Imports",FALSE +"rjags","*","modules/meta.analysis","Imports",FALSE +"rjags","*","modules/photosynthesis","Depends",FALSE +"rjson","*","models/dvmdostem","Imports",FALSE +"rlang","*","base/db","Imports",FALSE +"rlang","*","base/qaqc","Imports",FALSE +"rlang","*","base/utils","Imports",FALSE +"rlang","*","base/visualization","Imports",FALSE +"rlang","*","models/biocro","Imports",FALSE +"rlang","*","models/ed","Imports",FALSE +"rlang","*","models/ldndc","Imports",FALSE +"rlang","*","modules/assim.sequential","Imports",FALSE +"rlang","*","modules/benchmark","Imports",FALSE +"rlang","*","modules/data.land","Imports",FALSE +"rlang","*","modules/data.remote","Imports",FALSE +"rlang","*","modules/uncertainty","Imports",FALSE +"rlang",">= 0.2.0","modules/data.atmosphere","Imports",FALSE +"rlist","*","modules/assim.sequential","Suggests",FALSE +"rmarkdown",">= 2.19","base/db","Suggests",FALSE +"rmarkdown",">= 2.19","base/qaqc","Suggests",FALSE +"rmarkdown",">= 2.19","modules/allometry","Suggests",FALSE +"rmarkdown",">= 2.19","modules/assim.batch","Suggests",FALSE +"rmarkdown",">= 2.19","modules/meta.analysis","Suggests",FALSE +"rmarkdown",">= 2.19","modules/photosynthesis","Suggests",FALSE +"roxygen2","== 7.3.2","base/all","Roxygen",FALSE +"roxygen2","== 7.3.2","base/db","Roxygen",FALSE +"roxygen2","== 7.3.2","base/logger","Roxygen",FALSE +"roxygen2","== 7.3.2","base/qaqc","Roxygen",FALSE +"roxygen2","== 7.3.2","base/remote","Roxygen",FALSE +"roxygen2","== 7.3.2","base/settings","Roxygen",FALSE +"roxygen2","== 7.3.2","base/utils","Roxygen",FALSE +"roxygen2","== 7.3.2","base/visualization","Roxygen",FALSE +"roxygen2","== 7.3.2","base/workflow","Roxygen",FALSE +"roxygen2","== 7.3.2","models/basgra","Roxygen",FALSE +"roxygen2","== 7.3.2","models/biocro","Roxygen",FALSE +"roxygen2","== 7.3.2","models/cable","Roxygen",FALSE +"roxygen2","== 7.3.2","models/clm45","Roxygen",FALSE +"roxygen2","== 7.3.2","models/dalec","Roxygen",FALSE +"roxygen2","== 7.3.2","models/dvmdostem","Roxygen",FALSE +"roxygen2","== 7.3.2","models/ed","Roxygen",FALSE +"roxygen2","== 7.3.2","models/fates","Roxygen",FALSE +"roxygen2","== 7.3.2","models/gday","Roxygen",FALSE +"roxygen2","== 7.3.2","models/jules","Roxygen",FALSE +"roxygen2","== 7.3.2","models/ldndc","Roxygen",FALSE +"roxygen2","== 7.3.2","models/linkages","Roxygen",FALSE +"roxygen2","== 7.3.2","models/lpjguess","Roxygen",FALSE +"roxygen2","== 7.3.2","models/maat","Roxygen",FALSE +"roxygen2","== 7.3.2","models/maespa","Roxygen",FALSE +"roxygen2","== 7.3.2","models/preles","Roxygen",FALSE +"roxygen2","== 7.3.2","models/sibcasa","Roxygen",FALSE +"roxygen2","== 7.3.2","models/sipnet","Roxygen",FALSE +"roxygen2","== 7.3.2","models/stics","Roxygen",FALSE +"roxygen2","== 7.3.2","models/template","Roxygen",FALSE +"roxygen2","== 7.3.2","modules/allometry","Roxygen",FALSE +"roxygen2","== 7.3.2","modules/assim.batch","Roxygen",FALSE +"roxygen2","== 7.3.2","modules/assim.sequential","Roxygen",FALSE +"roxygen2","== 7.3.2","modules/benchmark","Roxygen",FALSE +"roxygen2","== 7.3.2","modules/data.atmosphere","Roxygen",FALSE +"roxygen2","== 7.3.2","modules/data.land","Roxygen",FALSE +"roxygen2","== 7.3.2","modules/data.remote","Roxygen",FALSE +"roxygen2","== 7.3.2","modules/emulator","Roxygen",FALSE +"roxygen2","== 7.3.2","modules/meta.analysis","Roxygen",FALSE +"roxygen2","== 7.3.2","modules/photosynthesis","Roxygen",FALSE +"roxygen2","== 7.3.2","modules/priors","Roxygen",FALSE +"roxygen2","== 7.3.2","modules/rtm","Roxygen",FALSE +"roxygen2","== 7.3.2","modules/uncertainty","Roxygen",FALSE +"RPostgres","*","base/db","Suggests",FALSE +"RPostgreSQL","*","base/db","Suggests",FALSE +"RPostgreSQL","*","models/biocro","Suggests",FALSE +"Rpreles","*","models/preles","Suggests",FALSE +"RSQLite","*","base/db","Suggests",FALSE +"sessioninfo","*","base/all","Suggests",FALSE +"sf","*","modules/assim.sequential","Suggests",FALSE +"sf","*","modules/data.atmosphere","Imports",FALSE +"sf","*","modules/data.land","Imports",FALSE +"sf","*","modules/data.remote","Suggests",FALSE +"SimilarityMeasures","*","modules/benchmark","Imports",FALSE +"sirt","*","modules/data.land","Imports",FALSE +"sp","*","base/visualization","Suggests",FALSE +"sp","*","modules/assim.sequential","Suggests",FALSE +"sp","*","modules/data.atmosphere","Imports",FALSE +"sp","*","modules/data.land","Imports",FALSE +"sp","*","modules/data.remote","Imports",FALSE +"stats","*","base/qaqc","Imports",FALSE +"stats","*","modules/allometry","Imports",FALSE +"stats","*","modules/assim.batch","Imports",FALSE +"stats","*","modules/assim.sequential","Suggests",FALSE +"stats","*","modules/photosynthesis","Imports",FALSE +"SticsRFiles","*","models/stics","Suggests",FALSE +"stringi","*","base/logger","Imports",FALSE +"stringi","*","base/utils","Imports",FALSE +"stringr","*","models/fates","Imports",FALSE +"stringr","*","modules/assim.sequential","Imports",FALSE +"stringr","*","modules/benchmark","Imports",FALSE +"stringr","*","modules/data.land","Imports",FALSE +"stringr",">= 1.1.0","base/visualization","Imports",FALSE +"stringr",">= 1.1.0","models/ed","Imports",FALSE +"stringr",">= 1.1.0","modules/data.atmosphere","Imports",FALSE +"suntools","*","modules/data.atmosphere","Imports",FALSE +"swfscMisc","*","modules/data.land","Imports",FALSE +"terra","*","modules/assim.sequential","Suggests",FALSE +"terra","*","modules/data.atmosphere","Imports",FALSE +"terra","*","modules/data.land","Imports",FALSE +"terra","*","modules/data.remote","Imports",FALSE +"testthat","*","base/all","Suggests",FALSE +"testthat","*","base/logger","Suggests",FALSE +"testthat","*","base/remote","Suggests",FALSE +"testthat","*","base/workflow","Suggests",FALSE +"testthat","*","modules/assim.sequential","Suggests",FALSE +"testthat","*","modules/priors","Suggests",FALSE +"testthat",">= 1.0.2","base/visualization","Suggests",FALSE +"testthat",">= 1.0.2","models/basgra","Suggests",FALSE +"testthat",">= 1.0.2","models/cable","Suggests",FALSE +"testthat",">= 1.0.2","models/clm45","Suggests",FALSE +"testthat",">= 1.0.2","models/dalec","Suggests",FALSE +"testthat",">= 1.0.2","models/dvmdostem","Suggests",FALSE +"testthat",">= 1.0.2","models/ed","Suggests",FALSE +"testthat",">= 1.0.2","models/fates","Suggests",FALSE +"testthat",">= 1.0.2","models/gday","Suggests",FALSE +"testthat",">= 1.0.2","models/jules","Suggests",FALSE +"testthat",">= 1.0.2","models/ldndc","Suggests",FALSE +"testthat",">= 1.0.2","models/linkages","Suggests",FALSE +"testthat",">= 1.0.2","models/lpjguess","Suggests",FALSE +"testthat",">= 1.0.2","models/maat","Suggests",FALSE +"testthat",">= 1.0.2","models/maespa","Suggests",FALSE +"testthat",">= 1.0.2","models/preles","Suggests",FALSE +"testthat",">= 1.0.2","models/sipnet","Suggests",FALSE +"testthat",">= 1.0.2","models/stics","Suggests",FALSE +"testthat",">= 1.0.2","models/template","Suggests",FALSE +"testthat",">= 1.0.2","modules/allometry","Suggests",FALSE +"testthat",">= 1.0.2","modules/assim.batch","Suggests",FALSE +"testthat",">= 1.0.2","modules/data.land","Suggests",FALSE +"testthat",">= 1.0.2","modules/data.remote","Suggests",FALSE +"testthat",">= 1.0.2","modules/meta.analysis","Suggests",FALSE +"testthat",">= 1.0.2","modules/rtm","Suggests",FALSE +"testthat",">= 1.0.2","modules/uncertainty","Suggests",FALSE +"testthat",">= 2.0.0","base/db","Suggests",FALSE +"testthat",">= 2.0.0","base/settings","Suggests",FALSE +"testthat",">= 2.0.0","base/utils","Suggests",FALSE +"testthat",">= 2.0.0","models/biocro","Suggests",FALSE +"testthat",">= 2.0.0","modules/benchmark","Suggests",FALSE +"testthat",">= 2.0.0","modules/data.atmosphere","Suggests",FALSE +"testthat",">= 3.0.0","models/sibcasa","Suggests",FALSE +"testthat",">= 3.0.4","base/qaqc","Suggests",FALSE +"tibble","*","base/db","Imports",FALSE +"tibble","*","models/ed","Imports",FALSE +"tibble","*","models/fates","Imports",FALSE +"tibble","*","models/lpjguess","Imports",FALSE +"tibble","*","modules/data.atmosphere","Imports",FALSE +"tibble","*","modules/data.remote","Suggests",FALSE +"tictoc","*","modules/assim.sequential","Suggests",FALSE +"tidyr","*","base/db","Imports",FALSE +"tidyr","*","models/ed","Imports",FALSE +"tidyr","*","modules/assim.sequential","Suggests",FALSE +"tidyr","*","modules/data.atmosphere","Imports",FALSE +"tidyr","*","modules/data.land","Imports",FALSE +"tidyselect","*","modules/benchmark","Imports",FALSE +"tidyselect","*","modules/data.atmosphere","Imports",FALSE +"tidyselect","*","modules/data.land","Imports",FALSE +"tidyverse","*","base/db","Suggests",FALSE +"tools","*","base/remote","Suggests",FALSE +"tools","*","modules/allometry","Imports",FALSE +"traits","*","modules/data.land","Imports",FALSE +"TruncatedNormal",">= 2.2","modules/assim.batch","Imports",FALSE +"truncnorm","*","modules/data.atmosphere","Imports",FALSE +"units","*","base/db","Imports",FALSE +"units","*","base/utils","Imports",FALSE +"units","*","modules/benchmark","Imports",FALSE +"units","*","modules/data.atmosphere","Imports",FALSE +"urltools","*","base/remote","Imports",FALSE +"utils","*","base/all","Imports",FALSE +"utils","*","base/logger","Imports",FALSE +"utils","*","models/ed","Imports",FALSE +"utils","*","modules/allometry","Imports",FALSE +"utils","*","modules/assim.batch","Imports",FALSE +"utils","*","modules/assim.sequential","Suggests",FALSE +"utils","*","modules/benchmark","Imports",FALSE +"utils","*","modules/data.remote","Suggests",FALSE +"utils","*","modules/photosynthesis","Imports",FALSE +"vdiffr",">= 1.0.2","base/qaqc","Suggests",FALSE +"withr","*","base/db","Suggests",FALSE +"withr","*","base/logger","Suggests",FALSE +"withr","*","base/qaqc","Suggests",FALSE +"withr","*","base/remote","Suggests",FALSE +"withr","*","base/settings","Suggests",FALSE +"withr","*","base/utils","Suggests",FALSE +"withr","*","base/visualization","Suggests",FALSE +"withr","*","base/workflow","Suggests",FALSE +"withr","*","models/basgra","Suggests",FALSE +"withr","*","models/ed","Suggests",FALSE +"withr","*","models/sibcasa","Suggests",FALSE +"withr","*","modules/allometry","Suggests",FALSE +"withr","*","modules/data.atmosphere","Suggests",FALSE +"XML","*","base/db","Imports",FALSE +"XML","*","base/workflow","Imports",FALSE +"XML","*","models/biocro","Imports",FALSE +"XML","*","models/maat","Imports",FALSE +"XML","*","models/stics","Imports",FALSE +"XML","*","modules/assim.batch","Imports",FALSE +"XML","*","modules/assim.sequential","Suggests",FALSE +"XML","*","modules/data.remote","Imports",FALSE +"XML","*","modules/rtm","Suggests",FALSE +"XML",">= 3.98-1.3","base/settings","Imports",FALSE +"XML",">= 3.98-1.4","models/ed","Imports",FALSE +"XML",">= 3.98-1.4","modules/benchmark","Imports",FALSE +"XML",">= 3.98-1.4","modules/data.atmosphere","Imports",FALSE +"XML",">= 3.98-1.4","modules/data.land","Imports",FALSE +"xtable","*","base/utils","Suggests",FALSE +"xts","*","modules/data.atmosphere","Imports",FALSE +"zoo","*","modules/benchmark","Imports",FALSE +"zoo","*","modules/data.atmosphere","Imports",FALSE