#' @title Extracting simulated values
#'
#' @return
#'
#' Returns the simulated values for the selected outputs (e.g molecules or
#' parameters).
#'
#' @description
#'
#' The function receives an object of simulation results generated by running
#' the simulation and returns time-values profiles for the chosen quantities.
#' Results of a simulation of a single individual is treated as a population
#' simulation with only one individual.
#'
#' @template simulation_results
#' @param stopIfNotFound If `TRUE` (default) an error is thrown if no results
#' exist for any `path`. If `FALSE`, a list of `NA` values is returned for the
#' respective path.
#' @param addMetaData If `TRUE` (default), the output is a list two sublists
#' `data`and `metaData`, with latter storing information about units and
#' dimensions of the outputs. If `FALSE`, `metaData` is `NULL`. Setting this
#' option to `FALSE` might improve the performance of the function.
#'
#' @examples
#' library(ospsuite)
#'
#' simPath <- system.file("extdata", "simple.pkml", package = "ospsuite")
#' sim <- loadSimulation(simPath)
#'
#' # Running an individual simulation
#' # results is an instance of `SimulationResults`
#' results <- runSimulations(sim)[[1]]
#'
#' getOutputValues(results)
#' @export
getOutputValues <- function(simulationResults,
quantitiesOrPaths = NULL,
population = NULL,
individualIds = NULL,
stopIfNotFound = TRUE,
addMetaData = TRUE) {
validateIsOfType(simulationResults, "SimulationResults")
validateIsOfType(population, "Population", nullAllowed = TRUE)
validateIsNumeric(individualIds, nullAllowed = TRUE)
validateIsOfType(quantitiesOrPaths, c("Quantity", "character"), nullAllowed = TRUE)
quantitiesOrPaths <- quantitiesOrPaths %||% simulationResults$allQuantityPaths
quantitiesOrPaths <- c(quantitiesOrPaths)
if (length(quantitiesOrPaths) == 0) {
return(list(data = NULL, metaData = NULL))
}
# If quantities are provided, get their paths
paths <- vector("character", length(quantitiesOrPaths))
if (isOfType(quantitiesOrPaths, "Quantity")) {
for (idx in seq_along(quantitiesOrPaths)) {
paths[[idx]] <- quantitiesOrPaths[[idx]]$path
}
} else {
paths <- quantitiesOrPaths
}
paths <- unique(paths)
# If no specific individual ids are passed, iterate through all individuals
individualIds <- ifNotNull(individualIds, unique(individualIds), simulationResults$allIndividualIds)
# All time values are equal
timeValues <- simulationResults$timeValues
valueLength <- length(timeValues)
covariateNames <- ifNotNull(population, population$allCovariateNames, NULL)
individualPropertiesCache <- vector("list", length(individualIds))
# create a cache of all individual values that are constant independent from the path
for (individualIndex in seq_along(individualIds)) {
individualId <- individualIds[individualIndex]
individualProperties <- list(IndividualId = rep(individualId, valueLength))
for (covariateName in covariateNames) {
covariateValue <- population$getCovariateValue(covariateName, individualId)
individualProperties[[covariateName]] <- rep(covariateValue, valueLength)
}
individualProperties$Time <- timeValues
# Save one data frame with all individual properties per individual so that we can easily concatenate them
individualPropertiesCache[[individualIndex]] <- individualProperties
}
# Cache of all individual properties over all individual that will be duplicated in all resulting data.frame
allIndividualProperties <- do.call(rbind.data.frame, c(individualPropertiesCache, stringsAsFactors = FALSE))
values <- lapply(paths, function(path) {
simulationResults$getValuesByPath(path, individualIds, stopIfNotFound)
})
names(values) <- paths
# Use low-level methods to get unit and dimension
task <- .getNetTaskFromCache("ContainerTask")
metaData <- NULL
if (addMetaData) {
metaData <- lapply(paths, function(path) {
unit <- NULL
dimension <- NULL
# Get the dimension and unit from path if the results are obtained. If the results
# are NA, the entity with such path does not exist
if (!all(is.na(values[[path]]))) {
unit <- task$call("BaseUnitNameByPath", simulationResults$simulation, path, stopIfNotFound)
dimension <- task$call("DimensionNameByPath", simulationResults$simulation, path, stopIfNotFound)
}
list(unit = unit, dimension = dimension)
})
names(metaData) <- paths
metaData[["Time"]] <- list(unit = "min", dimension = "Time")
}
data <- data.frame(allIndividualProperties, values, stringsAsFactors = FALSE, check.names = FALSE)
return(list(data = data, metaData = metaData))
}
#' Saves the simulation results to csv file
#'
#' @param results Results to export (typically calculated using `runSimulations`
#' or imported from file).
#' @param filePath Full path where the results will be saved.
#'
#' @examples
#' simPath <- system.file("extdata", "simple.pkml", package = "ospsuite")
#'
#' # Load the simulation
#' sim <- loadSimulation(simPath)
#'
#' # Add some outputs to the simulation
#' addOutputs("Organism|**|*", sim)
#'
#' # Run the simulation
#' results <- runSimulations(sim)[[1]]
#'
#' # Export the results to csv file
#' exportResultsToCSV(results, tempfile())
#' @export
exportResultsToCSV <- function(results, filePath) {
validateIsOfType(results, "SimulationResults")
validateIsString(filePath)
filePath <- .expandPath(filePath)
simulationResultsTask <- .getNetTask("SimulationResultsTask")
simulationResultsTask$call("ExportResultsToCSV", results, results$simulation, filePath)
invisible()
}
#' @inherit exportResultsToCSV
.saveResultsToCSV <- function(results, filePath) {
exportResultsToCSV(results, filePath)
}
#' Imports the simulation results from one or more csv files
#'
#' @param simulation Instance of a simulation used to calculate the results
#' @param filePaths Full path of result files to import. Typically only one
#' file is provided but a list of files is sometimes available when the simulation
#' was parallelized and computed on different machines
#'
#' @examples
#' simPath <- system.file("extdata", "simple.pkml", package = "ospsuite")
#' resultPath <- system.file("extdata", "res.csv", package = "ospsuite")
#'
#' # Load the simulation
#' sim <- loadSimulation(simPath)
#'
#' # Run the simulation
#' results <- importResultsFromCSV(sim, resultPath)
#' @export
importResultsFromCSV <- function(simulation, filePaths) {
validateIsOfType(simulation, "Simulation")
validateIsString(filePaths)
simulationResultsTask <- .getNetTask("SimulationResultsTask")
filePaths <- unlist(lapply(filePaths, function(filePath) .expandPath(filePath)), use.names = FALSE)
results <- simulationResultsTask$call("ImportResultsFromCSV", simulation, filePaths)
SimulationResults$new(results, simulation)
}
#' Converts a `SimulationResults` objects to a data.frame
#'
#' @inheritParams getOutputValues
#'
#' @examples
#' library(ospsuite)
#'
#' simPath <- system.file("extdata", "simple.pkml", package = "ospsuite")
#' sim <- loadSimulation(simPath)
#'
#' # Running an individual simulation
#' # results is an instance of `SimulationResults`
#' results <- runSimulations(sim)[[1]]
#'
#' # convert to a dataframe
#' simulationResultsToDataFrame(results)
#' @return
#'
#' SimulationResults object as data.frame with columns IndividualId, Time, paths,
#' simulationValues, unit, dimension, TimeUnit.
#'
#' @export
simulationResultsToDataFrame <- function(simulationResults,
quantitiesOrPaths = NULL,
population = NULL,
individualIds = NULL) {
# no need to validating the input because this will be done by
# getOutputValues() anyways
simList <- getOutputValues(
simulationResults = simulationResults,
quantitiesOrPaths = quantitiesOrPaths,
population = population,
individualIds = individualIds
)
# use data.table to pivot simList$data to long format, all columns except
# "IndividualId" and "Time" to "paths" column and their value to
# "simulationValues"
simData <-
data.table::melt(as.data.table(simList$data),
id.vars = c("IndividualId", "Time"),
variable.name = "paths",
value.name = "simulationValues",
variable.factor = FALSE
)
# set order of simData by Time
simData <- data.table::setorder(simData, Time)
# add columns to simData
simData <- simData[, `:=`(
TimeDimension = simList$metaData$Time$dimension,
TimeUnit = simList$metaData$Time$unit,
dimension = simList$metaData[[paths]]$dimension,
unit = simList$metaData[[paths]]$unit,
molWeight = ospsuite::toUnit(
quantityOrDimension = ospDimensions$`Molecular weight`,
values = simulationResults$simulation$molWeightFor(paths),
targetUnit = ospUnits$`Molecular weight`$`g/mol`
)
),
by = paths
]
# # consistently return a (classical) data frame
return(as.data.frame(simData, stringsAsFactors = FALSE))
}
#' @rdname simulationResultsToDataFrame
#'
#' @export
simulationResultsToTibble <- function(simulationResults,
quantitiesOrPaths = NULL,
population = NULL,
individualIds = NULL) {
simData <- simulationResultsToDataFrame(
simulationResults = simulationResults,
quantitiesOrPaths = quantitiesOrPaths,
population = population,
individualIds = individualIds
)
# consistently return a tibble data frame
return(dplyr::as_tibble(simData))
}
Add the following code to your website.
For more information on customizing the embed code, read Embedding Snippets.