R/sonifyclass.R

##' print, summary and addition methods for \code{sonify} objects
##' 
##' Methods to print and alter sonify objects. Printing a sonify
##' object renders it to sound (analogously to how printing
##' \code{ggplot} objects renders them to screen in the
##' \href{http://had.co.nz/ggplot2}{ggplot2} package).
##' 
##' The \code{print} method for \code{sonify} objects not only renders
##' them to sound, it also creates an \code{audioSample} object (from
##' the \code{audio} package), \code{.LastRendering}, in the user's
##' workspace.  \code{.LastRendering} is the output of the
##' sonification and can be replayed or saved to a \code{.wav} file
##' without regenerating the sonification from scratch with the
##' convenience functions \code{\link{playLastRendering}} and
##' \code{\link{saveLastRendering}}.
##'
##' @rdname sonifyclass
##' @name sonifyclass
##' @aliases print.sonify summary.sonify +.sonify
##' @param x,object A \code{sonify} object
##' @param y  A \code{sonscaling} object generated by \code{scaling()}
##' or a \code{sonaes} object generated by \code{sonaes()} to add to
##' \code{x}.
##' 
##' @param \dots Ignored.
##' @return \code{+} and \code{\%+\%} both return a sonify object with
##' the relevant \code{y} value added into the object.
##' 
##' \code{print.sonify} is called for its side-effect, which is to
##' actually render the object to a sound.
##' 
##' \code{summary.sonify} prints a brief summary of the name of the
##' dataset to be sonified, and the specified mappings and scalings of
##' sonic values to data parameters.
##' @seealso \code{\link{sonify}} for the creation of these objects;
##' \code{\link{\%+\%}} for adding or replacing a default
##' \code{data.frame}.
##' @method print sonify
##' @export
print.sonify <- function(x, ...) {
  create_audioSample(x, play=TRUE)
  return(NULL)
}

##' @rdname sonifyclass
##' @method summary sonify
##' @export
summary.sonify <- function(object, ...) {
  mins <- as.vector(lapply(object$scales, function(y) y$min), "character")
  maxs <- as.vector(lapply(object$scales, function(y) y$max), "character")
  firstspaces <- sapply(names(object$scales), function(y) paste(rep(" ",17 - nchar(y)), collapse=""))
  secondspaces <- sapply(mins, function(y) paste(rep(" ",8 - nchar(y)), collapse=""))

  cat((paste("Summary of sonify object '", deparse(substitute(object)), "':\n\n", sep="")))

  cat("The data to be sonified:\n", paste("$dataname \n",
                                          object$dataname, "\n\n"))
  cat("Matchup of sonic values to data columns or constants:\n",
      "      $mapping")
  cat("           Column or Value\n"  )
  cat("--------------------------------------------\n")
  cat(paste("        $", names(object$mapping), " ",
            firstspaces,
            as.vector(object$mapping, "character"),
            sep="", collapse="\n"), "\n\n")

  cat("Desired min/max for sonic parameters:\n",
      "      $scales")
  cat("           Min      Max\n")
  cat("--------------------------------------------\n")
  cat(paste("        $", names(object$scales),
            firstspaces, mins, secondspaces, maxs,
            collapse="\n", sep=""))
  cat("\n")

}

##' @rdname sonifyclass
##' @method + sonify
##' @export
`+.sonify` <- function(x, y) {
  if("sonlayer" %in% class(y)) {
    ## adds sonlayer
    if(is.null(x$sonlayers)) {
      x$sonlayers[[1]] <- y
    } else {x$sonlayers <- c(x$sonlayers, list(y))}
  } else if("sonscaling" %in% class(y)) {
    ## adds to or overrides scale
    for(i in names(y)) {
      x$scales[[i]] <- y[[i]]
    }
  } else if("sonaes" %in% class(y)) {
    for(i in names(y)) {
      x$mapping[[i]] <- y[[i]]
    }
    if(is.null(y$time) && !is.null(x$mapping$tempo))
      x$mapping["time"] <- list(NULL)
    if(is.null(y$tempo) & !is.null(x$mapping$time))
      x$mapping["tempo"] <- list(NULL)
  } else if("sonrendering" %in% class(y)) {
    x$rendering <- y
    class(x) <- c(y, "sonify")
  } else {stop("'+' operator not supported for this operation.")}
  x
}         

Try the playitbyr package in your browser

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

playitbyr documentation built on May 2, 2019, 6:08 p.m.