diff --git a/DESCRIPTION b/DESCRIPTION index dbb23c5..3ca1772 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -10,10 +10,6 @@ License: GPL (>= 3) URL: https://archaeostat.github.io/archaeocal/ BugReports: https://github.com/ArchaeoStat/ArchaeoCal/issues Imports: - arkhe (>= 1.9.0), - graphics, - grDevices, - methods, utils, V8 Suggests: @@ -25,19 +21,3 @@ VignetteBuilder: Encoding: UTF-8 Roxygen: list(markdown = TRUE) RoxygenNote: 7.3.2 -Collate: - 'AllClasses.R' - 'AllGenerics.R' - 'ArchaeoCal-internal.R' - 'ArchaeoCal-package.R' - 'coerce.R' - 'mutators.R' - 'oxcal_calibrate.R' - 'oxcal_configure.R' - 'oxcal_execute.R' - 'oxcal_install.R' - 'oxcal_parse.R' - 'plot.R' - 'show.R' - 'validate.R' - 'zzz.R' diff --git a/NAMESPACE b/NAMESPACE index dd9d1a4..14b7785 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -1,16 +1,10 @@ # Generated by roxygen2: do not edit by hand -S3method(as.data.frame,OxCalOutput) -S3method(plot,OxCalOutput) +S3method(as.data.frame,OxCalResults) +S3method(oxcal_parse,OxCalOutput) +S3method(oxcal_parse,character) export(oxcal_calibrate) export(oxcal_configure) export(oxcal_execute) export(oxcal_install) -exportMethods(oxcal_parse) -exportMethods(plot) -import(arkhe) -importFrom(methods,.valueClassTest) -importFrom(methods,new) -importFrom(methods,setGeneric) -importFrom(methods,setMethod) -importFrom(methods,setValidity) +export(oxcal_parse) diff --git a/R/AllClasses.R b/R/AllClasses.R deleted file mode 100644 index 16c8a4c..0000000 --- a/R/AllClasses.R +++ /dev/null @@ -1,28 +0,0 @@ -# CLASSES DEFINITION AND INITIALIZATION -NULL - -#' OxCal Output -#' -#' An S4 class to represent OxCal output. -#' @param ocd A [`list`] of OxCal data which holds the ranges, probability -#' distributions, etc. for each parameter. -#' @param model A [`list`] of information about the model. -#' @param calib A [`list`] of information about the calibration curve. -#' @section Coerce: -#' In the code snippets below, `x` is an `OxCalOutput` object. -#' \describe{ -#' \item{`as.data.frame(x)`}{Coerces to a [`data.frame`].} -#' } -#' @author N. Frerebeau -#' @family classes -#' @docType class -#' @aliases OxCalOutput-class -#' @keywords internal -.OxCalOutput <- setClass( - Class = "OxCalOutput", - slots = c( - ocd = "list", - model = "list", - calib = "list" - ) -) diff --git a/R/AllGenerics.R b/R/AllGenerics.R deleted file mode 100644 index 881699d..0000000 --- a/R/AllGenerics.R +++ /dev/null @@ -1,57 +0,0 @@ -# GENERIC METHODS -#' @include AllClasses.R -NULL - -#' Read and Parse OxCal Output -#' -#' @param object A [`character`] string naming a JavaScript file which the data -#' are to be read from (or a `list` returned by [oxcal_execute()]). -#' @return An [`OxCalOutput-class`] object. -#' @example inst/examples/ex-oxcal-execute.R -#' @references -#' \url{https://c14.arch.ox.ac.uk/oxcalhelp/hlp_analysis_file.html} -#' @author N. Frerebeau -#' @docType methods -#' @family OxCal tools -#' @aliases oxcal_parse-method -setGeneric( - name = "oxcal_parse", - def = function(object) standardGeneric("oxcal_parse"), - valueClass = "OxCalOutput" -) - -#' Plot OxCal Output -#' -#' @param x An [`OxCalOutput-class`] object. -#' @param likelihood A [`logical`] scalar: should likelihood be drawn? -#' @param posterior A [`logical`] scalar: should posterior distribution be -#' drawn? -#' @param warnings A [`logical`] scalar: should warnings be plotted? -#' @param col.likelihood,col.posterior A [`character`] string specifying the -#' color of the density. -#' @param lty.likelihood,lty.posterior A [`character`] string or [`numeric`] -#' value specifying the line type of the lines. -#' @param main A [`character`] string giving a main title for the plot. -#' @param sub A [`character`] string giving a subtitle for the plot. -#' @param ann A [`logical`] scalar: should the default annotation (title and x, -#' y and z axis labels) appear on the plot? -#' @param axes A [`logical`] scalar: should axes be drawn on the plot? -#' @param frame.plot A [`logical`] scalar: should a box be drawn around the -#' plot? -#' @param panel.first An an `expression` to be evaluated after the plot axes are -#' set up but before any plotting takes place. This can be useful for drawing -#' background grids. -#' @param panel.last An `expression` to be evaluated after plotting has taken -#' place but before the axes, title and box are added. -#' @param ... Other [graphical parameters][graphics::par] may also be passed as -#' arguments to this function. -#' @return -#' `plot()` is called it for its side-effects: it results in a graphic -#' being displayed. Invisibly returns `x`. -#' @example inst/examples/ex-oxcal-calibrate.R -#' @author N. Frerebeau -#' @docType methods -#' @family OxCal tools -#' @name plot -#' @rdname plot -NULL diff --git a/R/ArchaeoCal-internal.R b/R/ArchaeoCal-internal.R index f29c2ce..55dde9a 100644 --- a/R/ArchaeoCal-internal.R +++ b/R/ArchaeoCal-internal.R @@ -1 +1,24 @@ # HELPERS + +#' Default value for NULL +#' +#' Replaces `NULL` with a default value. +#' @param x,y An object. +#' @return If `x` is `NULL`, returns `y`; otherwise returns `x`. +#' @keywords internal +#' @noRd +`%||%` <- function(x, y) { + if (is.null(x)) y else x +} + +# Reexport from base on newer versions of R to avoid conflict messages +if (exists("%||%", envir = baseenv())) { + `%||%` <- get("%||%", envir = baseenv()) +} + +assert_exists <- function(x) { + if (length(x) == 1 && !file.exists(x)) { + stop(sprintf("Could not find %s.", x), call. = FALSE) + } + invisible(x) +} diff --git a/R/ArchaeoCal-package.R b/R/ArchaeoCal-package.R index afba820..b8e9799 100644 --- a/R/ArchaeoCal-package.R +++ b/R/ArchaeoCal-package.R @@ -28,7 +28,3 @@ #' @docType package #' @keywords internal "_PACKAGE" - -#' @import arkhe -#' @importFrom methods new setGeneric setMethod setValidity .valueClassTest -NULL diff --git a/R/coerce.R b/R/coerce.R index d8f3d11..c4a803f 100644 --- a/R/coerce.R +++ b/R/coerce.R @@ -1,22 +1,29 @@ # COERCE -#' @include AllGenerics.R -NULL -# @return A [`data.frame`] with the following columns: -# \describe{ -# \item{`name`}{} -# \item{`operation`}{} -# \item{`type`}{} -# \item{`date`}{} -# \item{`error`}{} -# \item{`agreement`}{} -# \item{`convergence`}{} -# \item{`likelihood`}{} -# \item{`posterior`}{} -# } +#' Coerce to a Data Frame +#' +#' @param x A [`list`] returned by [`oxcal_parse()`]. +#' @param row.names A [`character`] vector giving the row names for the data +#' frame description, or `NULL`. +#' @param optional A [`logical`] scalar. If `FALSE` then the names of the +#' variables in the data frame are checked to ensure that they are +#' syntactically valid variable names and are not duplicated. +#' @param ... Currently not used. +#' @return A [`data.frame`] with the following columns: +#' \describe{ +#' \item{`name`}{} +#' \item{`operation`}{} +#' \item{`type`}{} +#' \item{`date`}{} +#' \item{`error`}{} +#' \item{`agreement`}{} +#' \item{`convergence`}{} +#' \item{`likelihood`}{} +#' \item{`posterior`}{} +#' } #' @export -#' @method as.data.frame OxCalOutput -as.data.frame.OxCalOutput <- function(x, ...) { +as.data.frame.OxCalResults <- function(x, row.names = NULL, + optional = FALSE, ...) { data.frame( name = oxcal_get_names(x), operation = oxcal_get_operation(x), @@ -26,6 +33,8 @@ as.data.frame.OxCalOutput <- function(x, ...) { agreement = oxcal_get_agreement(x), convergence = oxcal_get_convergence(x), likelihood = I(oxcal_density(x, prob = "likelihood")), - posterior = I(oxcal_density(x, prob = "posterior")) + posterior = I(oxcal_density(x, prob = "posterior")), + row.names = row.names, + check.names = !optional ) } diff --git a/R/mutators.R b/R/mutators.R index 1c79b4f..c5c300c 100644 --- a/R/mutators.R +++ b/R/mutators.R @@ -1,11 +1,9 @@ # MUTATORS -#' @include AllGenerics.R -NULL # Helpers ====================================================================== oxcal_range <- function(x, na.rm = TRUE) { r <- vapply( - X = x@ocd, + X = x$ocd, FUN = function(x) { start_like <- x$likelihood$start start_post <- x$posterior$start @@ -27,7 +25,7 @@ oxcal_range <- function(x, na.rm = TRUE) { oxcal_density <- function(x, prob = c("likelihood", "posterior")) { prob <- match.arg(prob, several.ok = FALSE) lapply( - X = x@ocd[-1], + X = x$ocd[-1], FUN = function(x, prob) { years <- seq.int( from = x[[prob]]$start, @@ -43,41 +41,41 @@ oxcal_density <- function(x, prob = c("likelihood", "posterior")) { oxcal_get_names <- function(x) { vapply( - X = x@ocd[-1], + X = x$ocd[-1], FUN = function(x) x$name %||% NA_character_, FUN.VALUE = character(1) ) } oxcal_get_operation <- function(x) { - vapply(X = x@ocd[-1], FUN = `[[`, FUN.VALUE = character(1), i = "op") + vapply(X = x$ocd[-1], FUN = `[[`, FUN.VALUE = character(1), i = "op") } oxcal_get_type <- function(x) { - vapply(X = x@ocd[-1], FUN = `[[`, FUN.VALUE = character(1), i = "type") + vapply(X = x$ocd[-1], FUN = `[[`, FUN.VALUE = character(1), i = "type") } oxcal_get_bp_date <- function(x) { vapply( - X = x@ocd[-1], + X = x$ocd[-1], FUN = function(x) x[["date"]] %||% NA_real_, FUN.VALUE = numeric(1) ) } oxcal_get_bp_error <- function(x) { vapply( - X = x@ocd[-1], + X = x$ocd[-1], FUN = function(x) x[["error"]] %||% NA_real_, FUN.VALUE = numeric(1) ) } oxcal_get_agreement <- function(x) { vapply( - X = x@ocd[-1], + X = x$ocd[-1], FUN = function(x) x$posterior$agreement %||% NA_real_, FUN.VALUE = numeric(1) ) } oxcal_get_convergence <- function(x) { vapply( - X = x@ocd[-1], + X = x$ocd[-1], FUN = function(x) x$posterior$convergence %||% NA_real_, FUN.VALUE = numeric(1) ) diff --git a/R/oxcal_calibrate.R b/R/oxcal_calibrate.R index 3b1ec6f..1cbed40 100644 --- a/R/oxcal_calibrate.R +++ b/R/oxcal_calibrate.R @@ -7,7 +7,7 @@ #' to be calibrated. #' @param curve A [`character`] string specifying the calibration curve to be #' used. -#' @return An [`OxCalOutput-class`] object. +#' @return A [`list`] with class `OxCalResults` (see [oxcal_parse()]). #' @example inst/examples/ex-oxcal-calibrate.R #' @author N. Frerebeau #' @family OxCal tools diff --git a/R/oxcal_execute.R b/R/oxcal_execute.R index e0fee45..8b3ee76 100644 --- a/R/oxcal_execute.R +++ b/R/oxcal_execute.R @@ -4,10 +4,14 @@ #' @param file A [`character`] string naming a file (without extension) to #' write `script` to. Output files will be named after `file` and written to #' the same directory. +#' @param mcmc A [`character`] string giving the name of the output file for +#' the MCMC samples (without extension). It must match the `Name` argument of +#' OxCal's [`MCMC_Sample()`](https://intchron.org/tools/oxcalhelp/hlp_commands.html) +#' function. Only used if `script` contains the `MCMC_Sample()` command. #' @param verbose A [`logical`] scalar: should status updates be displayed? #' @param ... Further parameters to be passed to [system2()]. #' @return -#' A list with the following elements: +#' A [`list`] with class `OxCalOutput` containing the following elements: #' \describe{ #' \item{`oxcal`}{A [`character`] string giving the path to the .oxcal file.} #' \item{`js`}{A [`character`] string giving the path to the .js file.} @@ -21,7 +25,7 @@ #' @author N. Frerebeau #' @family OxCal tools #' @export -oxcal_execute <- function(script, file = NULL, +oxcal_execute <- function(script, file = NULL, mcmc = "MCMC_Sample", verbose = getOption("ArchaeoCal.verbose"), ...) { ## Construct output path if (is.null(file)) { @@ -43,24 +47,20 @@ oxcal_execute <- function(script, file = NULL, out <- oxcal_call(oxcal, ...) if (verbose) cat(out) - output <- list( - oxcal = oxcal, - js = sprintf("%s.js", file), - log = sprintf("%s.log", file), - txt = sprintf("%s.txt", file) - ) - - ## MCMC ? - csv <- sprintf("%s.csv", file) + ## MCMC? + csv <- sprintf("%s.csv", mcmc) csv <- if (file.exists(csv)) csv else character(0) ## Output files - list( - oxcal = oxcal, - js = sprintf("%s.js", file), - log = sprintf("%s.log", file), - txt = sprintf("%s.txt", file), - csv = csv + structure( + list( + oxcal = oxcal, + js = assert_exists(sprintf("%s.js", file)), + log = assert_exists(sprintf("%s.log", file)), + txt = assert_exists(sprintf("%s.txt", file)), + csv = csv + ), + class = "OxCalOutput" ) } diff --git a/R/oxcal_parse.R b/R/oxcal_parse.R index 76b465d..130d483 100644 --- a/R/oxcal_parse.R +++ b/R/oxcal_parse.R @@ -1,43 +1,52 @@ # PARSE OXCAL OUTPUT -#' @include AllGenerics.R -NULL + +#' Read and Parse OxCal Output +#' +#' @param path A [`character`] string naming a JavaScript file which the data +#' are to be read from (or a `list` returned by [oxcal_execute()]). +#' @return +#' A [`list`] with class `OxCalResults` containing the following elements: +#' \describe{ +#' \item{`ocd`}{A [`list`] of OxCal data which holds the ranges, probability +#' distributions, etc. for each parameter.} +#' \item{`model`}{A [`list`] of information about the model.} +#' \item{`calib`}{A [`list`] of information about the calibration curve.} +#' } +#' @example inst/examples/ex-oxcal-execute.R +#' @references +#' \url{https://c14.arch.ox.ac.uk/oxcalhelp/hlp_analysis_file.html} +#' @author N. Frerebeau +#' @family OxCal tools +#' @export +oxcal_parse <- function(path) { + UseMethod("oxcal_parse", path) +} #' @export #' @rdname oxcal_parse -#' @aliases oxcal_parse,list-method -setMethod( - f = "oxcal_parse", - signature = c(object = "list"), - definition = function(object) { - js <- object$js - if (is.null(js)) stop("Could not find the path.", call. = FALSE) - methods::callGeneric(js) +oxcal_parse.OxCalOutput <- function(path) { + js <- path$js + if (is.null(js) || !file.exists(js)) { + stop("Could not find the path.", call. = FALSE) } -) + oxcal_parse(js) +} #' @export #' @rdname oxcal_parse -#' @aliases oxcal_parse,character-method -setMethod( - f = "oxcal_parse", - signature = c(object = "character"), - definition = function(object) { - ox <- V8::v8() - ox$eval("ocd={};") - ox$eval("calib={};") - ox$eval("model={};") - ox$source(object) +oxcal_parse.character <- function(path) { + ox <- V8::v8() + ox$eval("ocd={};") + ox$eval("calib={};") + ox$eval("model={};") + ox$source(path) - ocd <- ox$get("ocd") - model <- ox$get("model") - calib <- ox$get("calib") - - .OxCalOutput( - ocd = ocd, - model = model, - calib = calib - # oxcal = ocd[[1]]$ref, - # curve = calib[[1]]$ref - ) - } -) + structure( + list( + ocd = ox$get("ocd"), + model = ox$get("model"), + calib = ox$get("calib") + ), + class = "OxCalResults" + ) +} diff --git a/R/plot.R b/R/plot.R deleted file mode 100644 index 3d4f9bc..0000000 --- a/R/plot.R +++ /dev/null @@ -1,105 +0,0 @@ -# PLOT -#' @include AllGenerics.R -NULL - -#' @export -#' @method plot OxCalOutput -plot.OxCalOutput <- function(x, likelihood = TRUE, posterior = TRUE, - warnings = TRUE, - col.likelihood = "grey", col.posterior = "blue", - lty.likelihood = "solid", lty.posterior = "dashed", - main = NULL, sub = NULL, ann = graphics::par("ann"), - axes = TRUE, frame.plot = FALSE, - panel.first = NULL, panel.last = NULL, ...) { - ## Drop first element (general information) - ocd <- as.data.frame(x) - ocd <- ocd[ocd$type == "date" | ocd$type == "model", , drop = FALSE] - n <- nrow(ocd) - - ## Graphical parameters - if (length(col.likelihood) != n) - col.likelihood <- rep(col.likelihood, length.out = n) - if (length(col.posterior) != n) - col.posterior <- rep(col.posterior, length.out = n) - fill.likelihood <- grDevices::adjustcolor(col.likelihood, alpha.f = 0.5) - fill.posterior <- grDevices::adjustcolor(col.posterior, alpha.f = 0.5) - - ## Open new window - grDevices::dev.hold() - on.exit(grDevices::dev.flush(), add = TRUE) - graphics::plot.new() - - ## Set plotting coordinates - xlim <- oxcal_range(x, na.rm = TRUE) - ylim <- c(n, -0.5) - graphics::plot.window(xlim = xlim, ylim = ylim) - - ## Evaluate pre-plot expressions - panel.first - - ## Plot - ages <- seq_len(n) - # graphics::abline(h = ages, col = "grey") - for (i in ages) { - if (likelihood) { - d <- ocd$likelihood[[i]] - if (!is.null(d$x)) { - yi <- (d$y - min(d$y)) / max(d$y - min(d$y)) * -1.5 + i - graphics::polygon(d$x, yi, border = NA, col = fill.likelihood[i]) - graphics::lines(d$x, yi, lty = lty.likelihood, col = "black") - } - if (warnings && !is.null(d$warning)) { - graphics::text(x = xlim[1L], y = i, adj = c(0, 0), - labels = d$warning, col = "red") - } - } - if (posterior) { - d <- ocd$posterior[[i]] - if (!is.null(d$x)) { - yi <- (d$y - min(d$y)) / max(d$y - min(d$y)) * -1.5 + i - graphics::polygon(d$x, yi, border = NA, col = fill.posterior[i]) - graphics::lines(d$x, yi, lty = lty.posterior, col = "black") - } - if (warnings && !is.null(d$warning)) { - graphics::text(x = xlim[1L], y = i + 0.5, adj = c(0, 0), - labels = d$warning, col = "red") - } - } - } - if (warnings) { - w <- x@ocd[[1]]$posterior$warning - if (!is.null(w)) { - graphics::mtext(w, side = 3, line = c(1, 0), adj = 0, col = "red") - } - } - - ## Evaluate post-plot and pre-axis expressions - panel.last - - ## Construct Axis - if (axes) { - graphics::axis(side = 1) - graphics::mtext(ocd$name, side = 2, at = ages, las = 2, padj = 0) - } - - ## Plot frame - if (frame.plot) { - graphics::box() - } - - ## Add annotation - if (ann) { - xlab <- "Year CE" - ylab <- NULL - graphics::title(main = main, sub = sub, xlab = xlab, ylab = ylab, ...) - graphics::mtext(text = x@ocd[[1]]$ref, side = 1, line = 3, adj = 1, cex = 0.7) - graphics::mtext(text = x@calib[[1]]$ref, side = 1, line = 4, adj = 1, cex = 0.7) - } - - invisible(x) -} - -#' @export -#' @rdname plot -#' @aliases plot,OxCalOutput,missing-method -setMethod("plot", c(x = "OxCalOutput", y = "missing"), plot.OxCalOutput) diff --git a/R/show.R b/R/show.R deleted file mode 100644 index 588bf9b..0000000 --- a/R/show.R +++ /dev/null @@ -1,25 +0,0 @@ -# SHOW -#' @include AllGenerics.R -NULL - -setMethod( - f = "show", - signature = "OxCalOutput", - definition = function(object) { - com <- vapply( - X = object@ocd[-1], - FUN = function(x) { - like <- paste0(x$likelihood$comment, collapse = "\n") - post <- paste0(x$posterior$comment, collapse = "\n") - c(like, post) - }, - FUN.VALUE = character(2) - ) - sep <- paste0(rep("-", length.out = getOption("width")), collapse = "") - - k <- paste(com, sep, sep = "\n") - cat(k, sep = "\n") - - invisible(object) - } -) diff --git a/R/validate.R b/R/validate.R deleted file mode 100644 index a99f2de..0000000 --- a/R/validate.R +++ /dev/null @@ -1,30 +0,0 @@ -# CLASSES VALIDATION -#' @include AllClasses.R -NULL - -setValidity( - Class = "OxCalOutput", - method = function(object) { - # Get data - ocd <- object@ocd - - for (i in ocd) { - name_warn <- if (is.null(i$name)) i$name else sprintf("%s - ", i$name) - - like_warn <- i$likelihood$warning - if (!is.null(like_warn)) - warning(paste0(name_warn, like_warn), call. = FALSE) - - post_warn <- i$posterior$warning - if (!is.null(post_warn)) - warning(paste0(name_warn, post_warn), call. = FALSE) - } - } -) - -assert_exists <- function(x) { - if (length(x) == 1 && !file.exists(x)) { - stop(sprintf("%s does not exist.", x), call. = FALSE) - } - invisible(x) -} diff --git a/R/zzz.R b/R/zzz.R index 910725a..b554858 100644 --- a/R/zzz.R +++ b/R/zzz.R @@ -2,7 +2,7 @@ ## Set package options op <- options() op.ArchaeoCal <- list( - ArchaeoCal.verbose = TRUE, + ArchaeoCal.verbose = interactive(), ArchaeoCal.oxcal = "" ) toset <- !(names(op.ArchaeoCal) %in% names(op)) diff --git a/inst/examples/ex-oxcal-calibrate.R b/inst/examples/ex-oxcal-calibrate.R index 33e95ea..69d4aa1 100644 --- a/inst/examples/ex-oxcal-calibrate.R +++ b/inst/examples/ex-oxcal-calibrate.R @@ -9,5 +9,5 @@ cal <- oxcal_calibrate( errors = c(45, 35) ) -plot(cal) +as.data.frame(cal) } diff --git a/inst/examples/ex-oxcal-execute.R b/inst/examples/ex-oxcal-execute.R index c131d89..836067e 100644 --- a/inst/examples/ex-oxcal-execute.R +++ b/inst/examples/ex-oxcal-execute.R @@ -24,7 +24,5 @@ scr <- 'Plot() out <- oxcal_execute(scr) res <- oxcal_parse(out) -plot(res) -plot(res, likelihood = TRUE, posterior = FALSE) -plot(res, likelihood = FALSE, posterior = TRUE) +as.data.frame(res) } diff --git a/inst/tinytest/test-oxcal_configure.R b/inst/tinytest/test-oxcal_configure.R index 116979e..f80f379 100644 --- a/inst/tinytest/test-oxcal_configure.R +++ b/inst/tinytest/test-oxcal_configure.R @@ -1,4 +1,4 @@ if (at_home()) { ## Check that OxCal configure works properly - expect_error(oxcal_configure(ask = TRUE), "Could not find OxCal") + expect_error(oxcal_configure(install = FALSE), "OxCal was not installed.") } diff --git a/man/OxCalOutput-class.Rd b/man/OxCalOutput-class.Rd deleted file mode 100644 index f195c37..0000000 --- a/man/OxCalOutput-class.Rd +++ /dev/null @@ -1,31 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/AllClasses.R -\docType{class} -\name{OxCalOutput-class} -\alias{OxCalOutput-class} -\alias{.OxCalOutput} -\title{OxCal Output} -\arguments{ -\item{ocd}{A \code{\link{list}} of OxCal data which holds the ranges, probability -distributions, etc. for each parameter.} - -\item{model}{A \code{\link{list}} of information about the model.} - -\item{calib}{A \code{\link{list}} of information about the calibration curve.} -} -\description{ -An S4 class to represent OxCal output. -} -\section{Coerce}{ - -In the code snippets below, \code{x} is an \code{OxCalOutput} object. -\describe{ -\item{\code{as.data.frame(x)}}{Coerces to a \code{\link{data.frame}}.} -} -} - -\author{ -N. Frerebeau -} -\concept{classes} -\keyword{internal} diff --git a/man/as.data.frame.OxCalResults.Rd b/man/as.data.frame.OxCalResults.Rd new file mode 100644 index 0000000..efcdd47 --- /dev/null +++ b/man/as.data.frame.OxCalResults.Rd @@ -0,0 +1,37 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/coerce.R +\name{as.data.frame.OxCalResults} +\alias{as.data.frame.OxCalResults} +\title{Coerce to a Data Frame} +\usage{ +\method{as.data.frame}{OxCalResults}(x, row.names = NULL, optional = FALSE, ...) +} +\arguments{ +\item{x}{A \code{\link{list}} returned by \code{\link[=oxcal_parse]{oxcal_parse()}}.} + +\item{row.names}{A \code{\link{character}} vector giving the row names for the data +frame description, or \code{NULL}.} + +\item{optional}{A \code{\link{logical}} scalar. If \code{FALSE} then the names of the +variables in the data frame are checked to ensure that they are +syntactically valid variable names and are not duplicated.} + +\item{...}{Currently not used.} +} +\value{ +A \code{\link{data.frame}} with the following columns: +\describe{ +\item{\code{name}}{} +\item{\code{operation}}{} +\item{\code{type}}{} +\item{\code{date}}{} +\item{\code{error}}{} +\item{\code{agreement}}{} +\item{\code{convergence}}{} +\item{\code{likelihood}}{} +\item{\code{posterior}}{} +} +} +\description{ +Coerce to a Data Frame +} diff --git a/man/oxcal_calibrate.Rd b/man/oxcal_calibrate.Rd index 8f15e5d..3dd7bbb 100644 --- a/man/oxcal_calibrate.Rd +++ b/man/oxcal_calibrate.Rd @@ -19,7 +19,7 @@ to be calibrated.} used.} } \value{ -An \code{\linkS4class{OxCalOutput}} object. +A \code{\link{list}} with class \code{OxCalResults} (see \code{\link[=oxcal_parse]{oxcal_parse()}}). } \description{ 14C Calibration with OxCal @@ -36,7 +36,7 @@ cal <- oxcal_calibrate( errors = c(45, 35) ) -plot(cal) +as.data.frame(cal) } } \seealso{ @@ -44,8 +44,7 @@ Other OxCal tools: \code{\link{oxcal_configure}()}, \code{\link{oxcal_execute}()}, \code{\link{oxcal_install}()}, -\code{\link{oxcal_parse}()}, -\code{\link{plot}()} +\code{\link{oxcal_parse}()} } \author{ N. Frerebeau diff --git a/man/oxcal_execute.Rd b/man/oxcal_execute.Rd index 3df7212..f29bc0e 100644 --- a/man/oxcal_execute.Rd +++ b/man/oxcal_execute.Rd @@ -7,6 +7,7 @@ oxcal_execute( script, file = NULL, + mcmc = "MCMC_Sample", verbose = getOption("ArchaeoCal.verbose"), ... ) @@ -18,12 +19,17 @@ oxcal_execute( write \code{script} to. Output files will be named after \code{file} and written to the same directory.} +\item{mcmc}{A \code{\link{character}} string giving the name of the output file for +the MCMC samples (without extension). It must match the \code{Name} argument of +OxCal's \href{https://intchron.org/tools/oxcalhelp/hlp_commands.html}{\code{MCMC_Sample()}} +function. Only used if \code{script} contains the \code{MCMC_Sample()} command.} + \item{verbose}{A \code{\link{logical}} scalar: should status updates be displayed?} \item{...}{Further parameters to be passed to \code{\link[=system2]{system2()}}.} } \value{ -A list with the following elements: +A \code{\link{list}} with class \code{OxCalOutput} containing the following elements: \describe{ \item{\code{oxcal}}{A \code{\link{character}} string giving the path to the .oxcal file.} \item{\code{js}}{A \code{\link{character}} string giving the path to the .js file.} @@ -62,9 +68,7 @@ scr <- 'Plot() out <- oxcal_execute(scr) res <- oxcal_parse(out) -plot(res) -plot(res, likelihood = TRUE, posterior = FALSE) -plot(res, likelihood = FALSE, posterior = TRUE) +as.data.frame(res) } } \references{ @@ -75,8 +79,7 @@ Other OxCal tools: \code{\link{oxcal_calibrate}()}, \code{\link{oxcal_configure}()}, \code{\link{oxcal_install}()}, -\code{\link{oxcal_parse}()}, -\code{\link{plot}()} +\code{\link{oxcal_parse}()} } \author{ N. Frerebeau diff --git a/man/oxcal_install.Rd b/man/oxcal_install.Rd index 54fe428..a1104c9 100644 --- a/man/oxcal_install.Rd +++ b/man/oxcal_install.Rd @@ -53,9 +53,7 @@ scr <- 'Plot() out <- oxcal_execute(scr) res <- oxcal_parse(out) -plot(res) -plot(res, likelihood = TRUE, posterior = FALSE) -plot(res, likelihood = FALSE, posterior = TRUE) +as.data.frame(res) } } \seealso{ @@ -63,8 +61,7 @@ Other OxCal tools: \code{\link{oxcal_calibrate}()}, \code{\link{oxcal_configure}()}, \code{\link{oxcal_execute}()}, -\code{\link{oxcal_parse}()}, -\code{\link{plot}()} +\code{\link{oxcal_parse}()} } \author{ N. Frerebeau diff --git a/man/oxcal_parse.Rd b/man/oxcal_parse.Rd index 3790d30..2b699d3 100644 --- a/man/oxcal_parse.Rd +++ b/man/oxcal_parse.Rd @@ -1,25 +1,29 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/AllGenerics.R, R/oxcal_parse.R -\docType{methods} +% Please edit documentation in R/oxcal_parse.R \name{oxcal_parse} \alias{oxcal_parse} -\alias{oxcal_parse-method} -\alias{oxcal_parse,list-method} -\alias{oxcal_parse,character-method} +\alias{oxcal_parse.OxCalOutput} +\alias{oxcal_parse.character} \title{Read and Parse OxCal Output} \usage{ -oxcal_parse(object) +oxcal_parse(path) -\S4method{oxcal_parse}{list}(object) +\method{oxcal_parse}{OxCalOutput}(path) -\S4method{oxcal_parse}{character}(object) +\method{oxcal_parse}{character}(path) } \arguments{ -\item{object}{A \code{\link{character}} string naming a JavaScript file which the data +\item{path}{A \code{\link{character}} string naming a JavaScript file which the data are to be read from (or a \code{list} returned by \code{\link[=oxcal_execute]{oxcal_execute()}}).} } \value{ -An \code{\linkS4class{OxCalOutput}} object. +A \code{\link{list}} with class \code{OxCalResults} containing the following elements: +\describe{ +\item{\code{ocd}}{A \code{\link{list}} of OxCal data which holds the ranges, probability +distributions, etc. for each parameter.} +\item{\code{model}}{A \code{\link{list}} of information about the model.} +\item{\code{calib}}{A \code{\link{list}} of information about the calibration curve.} +} } \description{ Read and Parse OxCal Output @@ -51,9 +55,7 @@ scr <- 'Plot() out <- oxcal_execute(scr) res <- oxcal_parse(out) -plot(res) -plot(res, likelihood = TRUE, posterior = FALSE) -plot(res, likelihood = FALSE, posterior = TRUE) +as.data.frame(res) } } \references{ @@ -64,8 +66,7 @@ Other OxCal tools: \code{\link{oxcal_calibrate}()}, \code{\link{oxcal_configure}()}, \code{\link{oxcal_execute}()}, -\code{\link{oxcal_install}()}, -\code{\link{plot}()} +\code{\link{oxcal_install}()} } \author{ N. Frerebeau diff --git a/man/plot.Rd b/man/plot.Rd deleted file mode 100644 index 5cd9d53..0000000 --- a/man/plot.Rd +++ /dev/null @@ -1,99 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/AllGenerics.R, R/plot.R -\docType{methods} -\name{plot} -\alias{plot} -\alias{plot,OxCalOutput,missing-method} -\title{Plot OxCal Output} -\usage{ -\S4method{plot}{OxCalOutput,missing}( - x, - likelihood = TRUE, - posterior = TRUE, - warnings = TRUE, - col.likelihood = "grey", - col.posterior = "blue", - lty.likelihood = "solid", - lty.posterior = "dashed", - main = NULL, - sub = NULL, - ann = graphics::par("ann"), - axes = TRUE, - frame.plot = FALSE, - panel.first = NULL, - panel.last = NULL, - ... -) -} -\arguments{ -\item{x}{An \code{\linkS4class{OxCalOutput}} object.} - -\item{likelihood}{A \code{\link{logical}} scalar: should likelihood be drawn?} - -\item{posterior}{A \code{\link{logical}} scalar: should posterior distribution be -drawn?} - -\item{warnings}{A \code{\link{logical}} scalar: should warnings be plotted?} - -\item{col.likelihood, col.posterior}{A \code{\link{character}} string specifying the -color of the density.} - -\item{lty.likelihood, lty.posterior}{A \code{\link{character}} string or \code{\link{numeric}} -value specifying the line type of the lines.} - -\item{main}{A \code{\link{character}} string giving a main title for the plot.} - -\item{sub}{A \code{\link{character}} string giving a subtitle for the plot.} - -\item{ann}{A \code{\link{logical}} scalar: should the default annotation (title and x, -y and z axis labels) appear on the plot?} - -\item{axes}{A \code{\link{logical}} scalar: should axes be drawn on the plot?} - -\item{frame.plot}{A \code{\link{logical}} scalar: should a box be drawn around the -plot?} - -\item{panel.first}{An an \code{expression} to be evaluated after the plot axes are -set up but before any plotting takes place. This can be useful for drawing -background grids.} - -\item{panel.last}{An \code{expression} to be evaluated after plotting has taken -place but before the axes, title and box are added.} - -\item{...}{Other \link[graphics:par]{graphical parameters} may also be passed as -arguments to this function.} -} -\value{ -\code{plot()} is called it for its side-effects: it results in a graphic -being displayed. Invisibly returns \code{x}. -} -\description{ -Plot OxCal Output -} -\examples{ -\dontrun{ -## Download OxCal -oxcal_configure() - -## Calibrate 14C dates -cal <- oxcal_calibrate( - names = c("X","Y"), - dates = c(5000, 4500), - errors = c(45, 35) -) - -plot(cal) -} -} -\seealso{ -Other OxCal tools: -\code{\link{oxcal_calibrate}()}, -\code{\link{oxcal_configure}()}, -\code{\link{oxcal_execute}()}, -\code{\link{oxcal_install}()}, -\code{\link{oxcal_parse}()} -} -\author{ -N. Frerebeau -} -\concept{OxCal tools} diff --git a/vignettes/ArchaeoCal.Rmd b/vignettes/ArchaeoCal.Rmd index 4ca3a7a..978a790 100644 --- a/vignettes/ArchaeoCal.Rmd +++ b/vignettes/ArchaeoCal.Rmd @@ -1,7 +1,7 @@ --- title: "Introduction to ArchaeoCal" author: "N. Frerebeau" -date: "2023-12-04" +date: "2025-01-17" output: markdown::html_format: options: @@ -16,29 +16,37 @@ vignette: > -This vignette uses data available through the [**ArchaeoData**](https://github.com/ArchaeoStat/ArchaeoData) package which is available in a [separate repository](https://archaeostat.r-universe.dev). **ArchaeoData** provides OxCal [@bronkramsey2009] input models. +This vignette uses data available through the [**ArchaeoData**](https://github.com/ArchaeoStat/ArchaeoData) package which is available in a [separate repository](https://archaeostat.r-universe.dev). +**ArchaeoData** provides OxCal (Bronk Ramsey, 2009) input models. -```r +``` r ## Install the latest version install.packages("ArchaeoData", repos = "https://archaeostat.r-universe.dev") ``` -```r +``` r ## Load package library(ArchaeoCal) ## Download OxCal -oxcal_configure() -#> OxCal binary found at /tmp/RtmpDY8HDa/OxCal/bin/OxCalLinux +oxcal_configure(ask = FALSE) +#> Could not find OxCal binary at /tmp/RtmpCaliqV/OxCal/bin/OxCalLinux +#> Could not find OxCal binary at OxCal +#> Attempting to download OxCal from https://c14.arch.ox.ac.uk/OxCalDistribution.zip. +#> OxCal successfully downloaded and extracted to /tmp/RtmphxBObr/OxCal. +#> OxCal binary found at /tmp/RtmphxBObr/OxCal/bin/OxCalLinux ``` -```r +``` r +## Construct path to file +path <- file.path("oxcal", "ksarakil", "ksarakil.oxcal") +file <- system.file(path, package = "ArchaeoData") + ## Read OxCal script from Bosch et al. 2015 -path <- system.file("oxcal/ksarakil/ksarakil.oxcal", package = "ArchaeoData") -scr <- readLines(path) +scr <- readLines(file) ## Print script # cat(scr, sep = "\n") @@ -50,37 +58,28 @@ out <- oxcal_execute(scr) #> MCMC analysis #> Sort Burn Trial Save Shrink kPasses Done Ok Convergence #> [.] [.] [.] [.] 3.0 10.0 100.0 100.0 -#> [.] [.] [.] [.] 6.0 20.0 100.0 6.8 -#> [.] [.] [.] [.] 12.0 22.2 100.0 14.4 -#> [.] [.] [.] [.] 24.0 22.2 100.0 6.2 -#> [.] [.] [.] [.] 48.0 22.2 100.0 43.2 -#> [.] [.] [.] [.] [.] 96.0 22.2 100.0 64.5 -#> [.] [.] [.] [.] 192.0 22.2 100.0 80.3 -#> [.] [.] [.] [.] 384.0 22.2 100.0 83.2 -#> [.] [.] [.] [.] 768.0 22.2 100.0 70.5 -#> [.] [.] [.] [.] 1152.0 30.0 100.0 95.8 -#> [.] [.] [.] [.] 1536.0 40.0 100.0 85.1 -#> [.] [.] [.] [.] 1920.0 50.0 100.0 85.1 -#> [.] [.] [.] [.] 2304.0 60.0 100.0 85.1 -#> [.] [.] [.] [.] 2688.0 70.0 100.0 85.1 -#> [.] [.] [.] [.] 3072.0 80.0 100.0 85.1 -#> [.] [.] [.] [.] 3456.0 90.0 100.0 85.1 -#> [.] [.] [.] [.] 3840.0 100.0 100.0 82.4 -#> [.] [.] [.] [.] 4224.0 110.0 100.0 82.4 +#> [.] [.] [.] [.] 6.0 20.0 100.0 0.0 +#> [.] [.] [.] [.] 12.0 22.2 100.0 4.7 +#> [.] [.] [.] [.] 24.0 22.2 100.0 25.5 +#> [.] [.] [.] [.] 48.0 22.2 100.0 42.5 +#> [.] [.] [.] [.] [.] 96.0 22.2 100.0 59.4 +#> [.] [.] [.] [.] 192.0 22.2 100.0 5.8 +#> [.] [.] [.] [.] 384.0 22.2 100.0 50.7 +#> [.] [.] [.] [.] 768.0 22.2 100.0 93.6 +#> [.] [.] [.] [.] 1152.0 30.0 100.0 94.4 +#> [.] [.] [.] [.] 1536.0 40.0 100.0 94.4 +#> [.] [.] [.] [.] 1920.0 50.0 100.0 90.0 +#> [.] [.] [.] [.] 2304.0 60.0 100.0 90.0 +#> [.] [.] [.] [.] 2688.0 70.0 100.0 90.0 +#> [.] [.] [.] [.] 3072.0 80.0 100.0 90.0 +#> [.] [.] [.] [.] 3456.0 90.0 100.0 90.0 +#> [.] [.] [.] [.] 3840.0 100.0 100.0 90.0 +#> [.] [.] [.] [.] 4224.0 110.0 100.0 90.0 ## Parse OxCal output res <- oxcal_parse(out) ``` - -```r -par(mar = c(5, 6, 1, 1) + 0.1) -plot(res) -``` - -
plot of chunk plot
-