R/vpc.r

Defines functions RunVpcSimulation .check_numericText vpcmodel simmodel

Documented in simmodel vpcmodel

#' Executes an NLME simulation
#'
#' Executes an NLME simulation
#'
#' @inheritParams fitmodel
#' @param  simParams Simulation parameters. See \code{\link{NlmeSimulationParams}}.
#' If \code{missing}, default parameters generated by NlmeSimulationParams() are used.
#' @param  params Engine parameters. See \code{\link{engineParams}}. The common
#' parameters include: sort, ODE, rtolODE, atolODE, maxStepsODE.
#' If \code{missing}, default parameters generated by engineParams(model) are used.
#' @param  hostPlatform Host definition for model execution. See \code{\link{hostParams}}.
#' If \code{missing}, simple local host is used.
#' @param ... Additional class initializer arguments for \code{\link{NlmeSimulationParams}}, or
#' arguments available inside \code{\link{hostParams}} or \code{\link{engineParams}} functions.
#' If \code{\link{engineParams}} arguments are supplied through both \code{params} argument
#' and additional argument (i.e., ellipsis), then the arguments in \code{params} will be ignored
#' and only the additional arguments will be used with warning.
#' If \code{\link{hostParams}} arguments are supplied through both \code{hostPlatform}
#'  argument and additional argument, then its slots will be overridden by additional arguments.
#'  In addition, if \code{\link{NlmeSimulationParams}} arguments are supplied through both
#'  \code{simParams} argument and additional argument,
#'  then its slots will be overridden by additional arguments.
#'
#' @return returns job properties if runInBackground is \code{TRUE};
#' if runInBackground is \code{FALSE} and the function is called in interactive mode,
#' the resulted simulated tables wil be loaded and presented as a list;
#' if runInBackground is \code{FALSE} and the function is called in non-interactive mode,
#' the list returned will have just the full paths of the tables generated.
#'
#' @examples
#' \donttest{
#' SimTableObs <- tableParams(
#'   name = "SimTableObs.csv",
#'   timesList = "0,1,2,4,4.9,55.1,56,57,59,60",
#'   variablesList = "C, CObs",
#'   timeAfterDose = FALSE,
#'   forSimulation = TRUE
#' )
#'
#' simParams <- NlmeSimulationParams(
#'   numReplicates = 2,
#'   simulationTables = SimTableObs
#' )
#' # Define the model
#' model <- pkmodel(
#'   numComp = 2,
#'   absorption = "Extravascular",
#'   ID = "Subject",
#'   Time = "Act_Time",
#'   CObs = "Conc",
#'   Aa = "Amount",
#'   data = pkData,
#'   modelName = "PkModel"
#' )
#' results <- simmodel(model, simParams)
#' # with seed given additionally:
#' results <- simmodel(model, simParams, seed = 3527)
#' }
#' @export
simmodel <- function(model,
                     simParams,
                     params,
                     hostPlatform = NULL,
                     runInBackground = FALSE,
                     ...) {
  if (missing(model)) {
    stop("model argument is required for run.")
  } else {
    stopifnot(inherits(model, "NlmePmlModel"))
  }

  ellipsisArgs <- list(...)
  if ("simpleTables" %in% names(ellipsisArgs)) {
    warning("simpleTables argument is not supported by simmodel.",
            " Please use simulationTables")
  }

  hostPlatform <-
    .load_hostPlatform(hostPlatform,
                       ellipsisArgs,
                       model = model,
                       mode = "vpc")

  if (missing(simParams)) {
    simParams <- NlmeSimulationParams()
  } else {
    if (!inherits(simParams, "NlmeSimulationParams")) {
      stop("Please check the simParams argument;",
           " NlmeSimulationParams class instance expected.")
    }
  }

  simParams <- .modify_s4class(simParams, ellipsisArgs)
  params <- .load_engineParams(model, params, ellipsisArgs)

  model@modelInfo@workingDir <-
    .prepare_wd(model@modelInfo@workingDir)
  Certara.RsNLME::writeDefaultFiles(model = model,
                                    dataset = model@dataset,
                                    simParams = simParams)

  return(
    RunVpcSimulation(
      hostPlatform = hostPlatform,
      params = params,
      dataset = model@dataset,
      vpcParams = NULL,
      simParams = simParams,
      runInBackground = runInBackground,
      workingDir = model@modelInfo@workingDir
    )
  )
}

#' Perform visual predictive check for NLME models
#'
#' Perform visual predictive check for NLME models
#'
#' @inheritParams fitmodel
#' @param  vpcParams VPC argument setup. See \code{\link{NlmeVpcParams}}.
#' If \code{missing}, default values generated by NlmeVpcParams() are used.
#' @param  params Engine argument setup. See \code{\link{engineParams}}. The following
#' arguments are the subject of interest: sort, ODE, rtolODE, atolODE, maxStepsODE.
#' If \code{missing}, default values generated by engineParams(model) are used.
#' @param  hostPlatform Host definition for model execution. See \code{\link{hostParams}}.
#' If \code{missing}, simple local host is used.
#' @param ... Additional class initializer arguments for \code{\link{NlmeVpcParams}} or
#' \code{\link{hostParams}}, or arguments available inside \code{\link{engineParams}} functions.
#' If \code{\link{engineParams}} arguments are supplied through both \code{params} argument
#' and additional argument (i.e., ellipsis), then the arguments in \code{params} will be ignored
#' and only the additional arguments will be used with warning.
#' If \code{\link{hostParams}} arguments are supplied through both \code{hostPlatform}
#'  argument and additional argument, then its values will be overridden by additional arguments.
#'  In addition, if \code{\link{NlmeVpcParams}} arguments are supplied through both
#'  \code{vpcParams} argument and additional argument,
#'  then its slots will be overridden by additional arguments.
#'
#' @return if runInBackground is \code{TRUE}, it returns job properties.
#' Otherwise, \itemize{
#' \item {If the function is called in an interactive mode,
#' the resulting  simulated tables and summary statistics tables will be loaded
#' and presented as a list;}
#' \item {If the function is called in a non-interactive mode,
#' it returns the full paths of the tables generated}}
#'
#' @examples
#' \donttest{
#'
#' job <- fitmodel(model)
#'
#' # View estimation results
#' print(job)
#'
#' finalModelVPC <- copyModel(model, acceptAllEffects = TRUE, modelName = "model_VPC")
#'
#' # View the model
#' print(finalModelVPC)
#'
#' # Set up VPC arguments to have PRED outputted to simulation output dataset "predout.csv"
#' vpcSetup <- NlmeVpcParams(outputPRED = TRUE)
#'
#' # Run VPC using the default host, default values for the relevant NLME engine arguments
#' finalVPCJob <- vpcmodel(model = finalModelVPC, vpcParams = vpcSetup)
#' # the same as:
#' finalVPCJob <- vpcmodel(model = finalModelVPC, outputPRED = TRUE)
#'
#' # Observed dataset predcheck0.csv
#' dt_ObsData <- finalVPCJob$predcheck0
#'
#' # Simulation output dataset predout.csv
#' dt_SimData <- finalVPCJob$predout
#'
#' # Add PRED from REPLICATE = 0 of simulation output dataset to observed input dataset
#' dt_ObsData$PRED <- dt_SimData[REPLICATE == 0]$PRED
#'
#' # tidyvpc package VPC example:
#' # library(tidyvpc)
#' library(magrittr)
#' # Create a regular VPC plot with binning method set to be "jenks"
#' binned_VPC <- observed(dt_ObsData, x = IVAR, yobs = DV) %>%
#'   simulated(dt_SimData, ysim = DV) %>%
#'   binning(bin = "jenks") %>%
#'   vpcstats()
#'
#' plot_binned_VPC <- plot(binned_VPC)
#'
#' # Create a pcVPC plot with binning method set to be "jenks"
#' binned_pcVPC <- observed(dt_ObsData, x = IVAR, yobs = DV) %>%
#'   simulated(dt_SimData, ysim = DV) %>%
#'   binning(bin = "jenks") %>%
#'   predcorrect(pred = PRED) %>%
#'   vpcstats()
#'
#' plot_binned_pcVPC <- plot(binned_pcVPC)
#' }
#'
#' @export
vpcmodel <- function(model,
                     vpcParams,
                     params,
                     hostPlatform = NULL,
                     runInBackground = FALSE,
                     ...) {
  if (missing(model)) {
    stop("model argument is required for run.")
  } else {
    stopifnot(inherits(model, "NlmePmlModel"))
  }

  ellipsisArgs <- list(...)

  hostPlatform <-
    .load_hostPlatform(hostPlatform,
                       ellipsisArgs,
                       model = model,
                       mode = "vpc")

  if (missing(vpcParams)) {
    vpcParams <- NlmeVpcParams()
  } else {
    stopifnot(inherits(vpcParams, "NlmeVpcParams"))
  }

  if ("simpleTables" %in% names(ellipsisArgs)) {
    warning("simpleTables argument is not supported by vpcmodel.",
            " Please use simulationTables")
  }

  vpcParams <- .modify_s4class(vpcParams, ellipsisArgs)

  if (model@isTextual) {
    # some responses could be here
    ObsTypes <- sapply(model@columnMapping@mapping,
                       function(x) {
                         name <- x@variableType$type
                         name
                       })
    ObsTypes <- ObsTypes[!is.null(ObsTypes) & ObsTypes != ""]
    on <- names(ObsTypes[ObsTypes == "observation"])
  } else {
    on <- Certara.RsNLME::observationNames(model)
  }

  if (length(vpcParams@observationVars) == 0) {
    # will provide VPC for all variables found if nothing is specified
    observationVars <- c()
    for (Obs in on) {
      observationVars <-
        c(observationVars, NlmeObservationVar(name = Obs))
    }
    vpcParams@observationVars <- observationVars
  } else {
    vpcObs <- sapply(vpcParams@observationVars, function(x) {
      x@name
    })
    stopExecution <- FALSE
    for (VPCname in vpcObs) {
      if (!VPCname %in% on) {
        warning(VPCname, " not found in the list of observables.")
        stopExecution <- TRUE
      }
    }
    if (stopExecution) {
      stop(
        "Cannot proceed with VPC since one or more specified observable variables were not found."
      )
    }
  }

  params <- .load_engineParams(model, params, ellipsisArgs)

  if (hostPlatform@hostType == "Windows" && runInBackground) {
    warning("`runInBackground = TRUE` is not available on Windows. Setting argument to `FALSE`.")
    runInBackground <- FALSE
  } else {
    stopifnot(is.logical(runInBackground))
  }

  model@modelInfo@workingDir <-
    .prepare_wd(model@modelInfo@workingDir)
  workingDir <- model@modelInfo@workingDir
  writeDefaultFiles(model = model,
                    dataset = model@dataset,
                    simParams = vpcParams)

  return(
    RunVpcSimulation(
      hostPlatform = hostPlatform,
      params = params,
      dataset = model@dataset,
      vpcParams = vpcParams,
      simParams = NULL,
      runInBackground = runInBackground,
      workingDir = workingDir
    )
  )
}

#' Class initializer for NlmeObservationVar-class
#'
#' Describes an observation(observe,multi,...)
#'
#' @param  name Name of observation variable
#' @param  xaxis One of: T, TAD, PRED. If nothing is specified,
#' the user-specified name of axis is used.
#' @param  binningMethod Method of binning: \code{"none"} (default),
#' \code{"KMEANS"}, \code{"CENTERS"}, \code{"BOUNDARIES"}
#' @param  binningOption Centers or boundary values specified as numeric vector
#' @param  stratifyColumns Categorical covariates (up to 3)
#' for simulation stratification (overrides stratifyColumns given
#' in NlmeVpcParams)
#' @param ygroup Values specifying the category right
#' boundaries (used for categorical observations only; useful for count)
#' @param  quantilesValues Quantiles to be estimate for each x value (bin value) in each strata for the current
#' observable (internal quantiles)
#' @param  quantilesSecondaryValues Quantiles to estimate for each internal quantile
#' (quantiles for quantile)
#' @param BQLasLLOQ Flag to replace BLQ values with the LLOQ value
#'
#' @export NlmeObservationVar
#'
#' @examples
#'
#' var <- NlmeObservationVar(
#'   name = "Cobs",
#'   xaxis = "t",
#'   binningMethod = "none",
#'   quantilesValues = c(5, 50, 95)
#' )
#' @keywords internal
NlmeObservationVar <- setClass(
  "NlmeObservationVar",
  representation(
    name = "character",
    xaxis = "character",
    binningMethod = "character",
    binningOption = "numeric.character",
    stratifyColumns = "character",
    ygroup = "numeric.character",
    quantilesValues = "numeric.character",
    quantilesSecondaryValues = "numeric.character",
    BQLasLLOQ = "logical"
  )
)

setMethod("initialize", "NlmeObservationVar",
          function(.Object,
                   name,
                   xaxis = "t",
                   binningMethod = "none",
                   binningOption = numeric(0),
                   stratifyColumns = "",
                   ygroup = numeric(0),
                   quantilesValues = c(5, 50, 95),
                   quantilesSecondaryValues = numeric(0),
                   BQLasLLOQ = FALSE) {
            .Object@name <- name

            xaxis <- trimws(xaxis)
            if (grepl("(^T$)", xaxis, ignore.case = TRUE)) {
              .Object@xaxis <- "t"
            } else if (grepl("(^TAD$)|(^PRED$)", xaxis, ignore.case = TRUE)) {
              .Object@xaxis <- toupper(xaxis)
            } else {
              .Object@xaxis <- xaxis
            }

            if (grepl("^KMEANS", binningMethod, ignore.case = TRUE)) {
              .Object@binningMethod <- "kmeans"
            } else if (grepl("^center", binningMethod, ignore.case = TRUE)) {
              .Object@binningMethod <- "centers"
            } else if (grepl("^bound", binningMethod, ignore.case = TRUE)) {
              .Object@binningMethod <- "boundaries"
            } else {
              if (!grepl("^none$", binningMethod, ignore.case = TRUE)) {
                warning(
                  "binning method given: '",
                  binningMethod,
                  "' is not kmeans, centers or boundaries; resetting to none.",
                  call. = FALSE
                )
              }
              .Object@binningMethod <- "none"
              binningMethod <- "none"
            }

            if (length(binningOption) > 0 &&
                !binningMethod %in% c("centers", "boundaries")) {
              warning(
                "binning option is given: '",
                binningOption,
                "' but binningMethod is not 'centers' or 'boundaries' and will be ignored.",
                call. = FALSE
              )
            } else if (missing(binningOption) &&
                       binningMethod %in% c("centers", "boundaries")) {
              stop(
                "With binning method given: '",
                binningMethod,
                "' the binningMethod argument should be specified (set of numeric values)"
              )
            }

            .Object@binningOption <-
              .check_numericText("binningOption", binningOption)

            stratifyColumns <-
              stratifyColumns[stratifyColumns != ""]
            if (length(stratifyColumns) == 0) {
              stratifyColumns <- ""
            } else if (length(stratifyColumns) > 1) {
              stratifyColumns <- paste(stratifyColumns)
            }
            .Object@stratifyColumns <- stratifyColumns

            .Object@ygroup <- .check_numericText("ygroup", ygroup)

            .Object@quantilesValues <-
              .check_numericText("quantiles Values", quantilesValues)

            .Object@quantilesSecondaryValues <-
              .check_numericText("External quantiles Values", quantilesSecondaryValues)
            .Object@BQLasLLOQ <- BQLasLLOQ
            .Object
          })

.check_numericText <- function(name, value) {
  if (!missing(value) && is.character(value)) {
    tryCatch(
      value <- eval(parse(text = paste0("c(", value, ")"))),
      error = function(e) {
        stop("current numeric series for a ",
             name,
             ":\n",
             value,
             "\nis not valid",
             call. = FALSE)
      }
    )
  }

  value
}

#' Arguments for VPC runs
#'
#' Class initializer for arguments of visual predictive check (VPC) runs
#'
#' @param  numReplicates Integer; Number of replicates to simulate the model
#' @param  seed Integer; Random number generator seed
#' @param  predCorrection Character; Type of correction to use when calculating a prediction-corrected observation.
#' Options are \code{"none", "proportional", "additive"}.
#' This option is ignored for discontinuous observed variables (categorical, count, and time-to-event).
#' @param  predVarCorr Logical; Set to \code{TRUE} to use Prediction Variance Correction.
#' Only applicable to the case where \code{predCorrection} is set to either
#' \code{"proportional"} or \code{"additive"}.
#' @param  outputPRED Logical; Set to \code{TRUE} to include population prediction (PRED) results
#' for continuous observed variables in output.
#' @param  stratifyColumns Character or character vector; Names of categorical covariates (up to 3)
#' used to stratify modeling simulation results.
#' @param  observationVars NlmeObservationVar class instance or list of these
#' instances
#' @param  simulationTables Optional list of simulation tables.
#' \code{NlmeSimTableDef} class instance or a list of such instances. Could be
#' generated by \code{tableParams} wrapper function or by \code{NlmeSimTableDef} class instance
#' initializing directly.
#'
#' @seealso \code{\link{tableParams}, \link{NlmeSimTableDef}, \link{NlmeObservationVar}}
#'
#' @export NlmeVpcParams
#'
#' @examples
#' \donttest{
#'
#' job <- fitmodel(model)
#'
#' # View estimation results
#' print(job)
#'
#' finalModelVPC <- copyModel(model, acceptAllEffects = TRUE, modelName = "model_VPC")
#'
#' # View the model
#' print(finalModelVPC)
#'
#' # Set up VPC arguments to have PRED outputted to simulation output dataset "predout.csv"
#' vpcSetup <- NlmeVpcParams(outputPRED = TRUE)
#'
#' # Run VPC using the default host, default values for the relevant NLME engine arguments
#' finalVPCJob <- vpcmodel(model = finalModelVPC, vpcParams = vpcSetup)
#'
#' }
#' @keywords internal
NlmeVpcParams <- setClass(
  "NlmeVpcParams",
  representation(
    numReplicates = "numeric",
    seed = "numeric",
    predCorrection = "character",
    predVarCorr = "logical",
    outputPRED = "logical",
    stratifyColumns = "character",
    observationVars = "list",
    simulationTables = "list"
  )
)

setMethod("initialize", "NlmeVpcParams",
          function(.Object,
                   numReplicates = 100,
                   seed = 1234,
                   predCorrection = "none",
                   predVarCorr = FALSE,
                   outputPRED = FALSE,
                   stratifyColumns = "",
                   observationVars = list(),
                   simulationTables = list()) {
            stopifnot(
              length(numReplicates) == 1,
              length(seed) == 1,
              length(predCorrection) == 1,
              length(predVarCorr) == 1
            )
            .Object@numReplicates <- numReplicates
            .Object@seed <- seed
            if (grepl("^prop", predCorrection, ignore.case = TRUE)) {
              .Object@predCorrection <- "proportional"
            } else if (grepl("^add", predCorrection, ignore.case = TRUE)) {
              .Object@predCorrection <- "additive"
            } else {
              if (!grepl("^none$", predCorrection, ignore.case = TRUE)) {
                warning(
                  "prediction correction given: '",
                  predCorrection,
                  "' is not additive or proportional; resetting to none.",
                  call. = FALSE
                )
              }
              .Object@predCorrection <- "none"
              predCorrection <- "none"
            }

            if (predCorrection == "none" && predVarCorr) {
              warning(
                "prediction correction is not requested, but predVarCorr = TRUE.",
                "\nPlease check NlmeVpcParams data.",
                call. = FALSE
              )
            }

            if (!is.list(observationVars)) {
              if (inherits(observationVars, "NlmeObservationVar")) {
                observationVars <- list(observationVars)
              } else {
                stop("observationVars argument is not a list or NlmeObservationVar",
                     " class instance.")
              }
            }

            if (!is.list(simulationTables)) {
              if (inherits(simulationTables, "NlmeSimTableDef")) {
                simulationTables <- list(simulationTables)
              } else {
                stop("simulationTables argument is not a list or NlmeSimTableDef",
                     " class instance.")
              }
            }

            .Object@predVarCorr <- predVarCorr
            .Object@outputPRED <- outputPRED

            stratifyColumns <-
              stratifyColumns[stratifyColumns != ""]
            if (length(stratifyColumns) == 0) {
              stratifyColumns <- ""
            } else if (length(stratifyColumns) > 1) {
              stratifyColumns <- paste(stratifyColumns)
            }

            .Object@stratifyColumns <- stratifyColumns
            .Object@observationVars <- observationVars
            .Object@simulationTables <- simulationTables
            .Object
          })

#' Class initializer for NlmeSimulationParams
#'
#' Use to create set of parameters for simulation runs. Parameters \code{numPoints, maxXRange, yVariables, simAtObs}
#' are related to the model in individual mode. They will be outputted to
#' the file specified in \code{model@dataset@simoutFilename}, simout.csv by default
#'
#' @param  numReplicates Number of replicates to simulate
#' @param  seed Random number generator seed
#' @param  numPoints  Number of points in simulation for the models in individual mode
#' @param  maxXRange  Maximum value of independent variable for the models in individual mode
#' @param  yVariables Comma separated character string of Y variables for the models in individual mode
#' @param  simAtObs   Simulate values at observed values of ivar for the models in individual mode
#' @param  simulationTables Optional list of simulation tables.
#' \code{NlmeSimTableDef} class instance or a list of such instances. Could be
#' generated by \code{tableParams} wrapper function or by \code{NlmeSimTableDef} class instance
#' initializing directly.
#'
#' @seealso \code{\link{tableParams}, \link{NlmeSimTableDef}}
#'
#' @export NlmeSimulationParams
#' @keywords internal
#' @examples
#'
#' table1 <- tableParams(
#'   name = "simulate.csv",
#'   timesList = "0,2,4,12,24",
#'   variablesList = "V,Cl",
#'   timeAfterDose = TRUE,
#'   forSimulation = TRUE
#' )
#'
#' simParam <- NlmeSimulationParams(
#'   numReplicates = 10,
#'   seed = 29423,
#'   simulationTables = c(table1)
#' )
#'
#' simParam <- NlmeSimulationParams(
#'   numPoints = 100,
#'   maxXRange = 50,
#'   yVariables = "C,A1",
#'   simulationTables = table1
#' )
#'
NlmeSimulationParams <-
  setClass(
    "NlmeSimulationParams",
    representation(
      numReplicates = "numeric",
      seed = "numeric",
      numPoints = "numeric",
      maxXRange = "numeric",
      yVariables = "character",
      simAtObs = "logical",
      simulationTables = "list"
    )
  )

setMethod("initialize", "NlmeSimulationParams",
          function(.Object,
                   numReplicates = 100,
                   seed = 1234,
                   numPoints = 100,
                   maxXRange = 50,
                   yVariables = "",
                   simAtObs = FALSE,
                   simulationTables = list()) {
            .Object@numReplicates <- numReplicates
            .Object@seed <- seed
            .Object@numPoints <- numPoints
            .Object@maxXRange <- maxXRange
            yVariables <- yVariables[yVariables != ""]
            if (length(yVariables) == 0) {
              yVariables <- ""
            } else if (length(yVariables) > 1) {
              yVariables <- paste0(yVariables, collapse = ", ")
            }

            if (missing(yVariables) &&
                (!missing(numPoints) ||
                 !missing(maxXRange) || simAtObs)) {
              warning(
                "To generate individual simulation output please provide the variables for simulation"
              )
            }
            .Object@yVariables <- yVariables
            .Object@simAtObs <- simAtObs

            if (!is.list(simulationTables)) {
              if (inherits(simulationTables, "NlmeSimTableDef")) {
                simulationTables <- list(simulationTables)
              } else {
                stop("simulationTables argument is not a list or NlmeSimTableDef",
                     " class instance.")
              }
            }
            .Object@simulationTables <- simulationTables
            .Object
          })

RunVpcSimulation <- function(hostPlatform,
                             dataset,
                             params,
                             vpcParams,
                             simParams,
                             runInBackground = FALSE,
                             workingDir) {
  workFlow <- "WorkFlow"
  argsFile <-
    GenerateControlfile(
      dataset,
      params,
      workFlow = workFlow,
      vpcOption = vpcParams,
      simOption = simParams,
      workingDir = workingDir
    )

  argsList <- list(
    jobType = "GENERIC",
    parallelMethod = hostPlatform@parallelMethod@method,
    install_dir = hostPlatform@installationDirectory,
    shared_directory = hostPlatform@sharedDirectory,
    localWorkingDir = workingDir,
    controlFile = names(argsFile),
    NumProc = hostPlatform@numCores,
    workflow_name = workFlow
  )

  if (is.null(vpcParams)) {
    jobName <- "Simulation"
  } else {
    jobName <- "VPC"
  }

  job <- SimpleNlmeJob(
    jobType = jobName,
    localDir = workingDir,
    remoteDir = workingDir,
    host = hostPlatform,
    argsList = argsList,
    argsFile = names(argsFile),
    workflow = workFlow,
    runInBackground = runInBackground
  )

  .log_Execution(Model = model,
                 EngineParams = params,
                 RunMode = ifelse(jobName == "VPC", "Pred Check", "Simulation"),
                 Host = hostPlatform)

  status <- executeJob(job)

  message("\nVPC/Simulation results are ready in ", workingDir)

  if (!runInBackground) {
    results <- list()
    if (jobName == "VPC") {
      predcheckFiles <- c(
        "predcheck_bql.csv",
        "predcheck0.csv",
        "predcheck0_cat.csv",
        "predcheck1.csv",
        "predcheck1_cat.csv",
        "predcheck2.csv",
        "predcheck2_cat.csv"
      )

      predcheckExist <-
        file.exists(file.path(workingDir, predcheckFiles))
      names(predcheckExist) <- predcheckFiles
      results <- c(results, predcheckExist)
      simtablesFiles <-
        sapply(c(vpcParams@simulationTables), function(x) {
          x@name
        })
    } else {
      simtablesFiles <-
        sapply(c(simParams@simulationTables), function(x) {
          x@name
        })
    }

    if (length(simtablesFiles) > 0) {
      simtablesExist <- file.exists(file.path(workingDir, simtablesFiles))
      names(simtablesExist) <- simtablesFiles
      results <- c(results, simtablesExist)
    }

    if (params@isPopulation) {
      predoutFile <- dataset@predoutFilename
      predoutExist <-
        file.exists(file.path(workingDir, predoutFile))
      names(predoutExist) <- predoutFile
      results <- c(results, predoutExist)
    } else {
      simoutFile <- dataset@simoutFilename
      simoutExist <- file.exists(file.path(workingDir, simoutFile))
      names(simoutExist) <- simoutFile
      results <- c(results, simoutExist)
    }

    message("Loading the results")

    for (TableName in unique(names(results))) {
      message("Loading ", TableName, "\n")
      FullTableName <- file.path(workingDir, TableName)
      if (results[[TableName]]) {
        if (file.info(FullTableName)["size"] > 0) {
          # before assigning the list elements are just the flags to see
          # whether the file exists
          results[[tools::file_path_sans_ext(TableName)]] <-
            data.table::fread(FullTableName, fill = TRUE)
        } else {
          # if file is empty, just put empty data frame
          results[[tools::file_path_sans_ext(TableName)]] <-
            data.table::data.table()
        }
      }
    }
    # removing empty/logical elements
    results <- results[!sapply(results, is.logical)]

    results
  } else {
    .report_BackgroundJob(hostPlatform@isLocal,
                          LocalWorkingDir = workingDir,
                          RemoteDir = hostPlatform@sharedDirectory)

    status
  }
}

Try the Certara.RsNLME package in your browser

Any scripts or data that you put into this service are public.

Certara.RsNLME documentation built on April 3, 2025, 11:04 p.m.