From noreply at r-forge.r-project.org Tue Apr 25 13:19:56 2017 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Tue, 25 Apr 2017 13:19:56 +0200 (CEST) Subject: [CHNOSZ-commits] r187 - in pkg/CHNOSZ: . R data inst Message-ID: <20170425111956.B2E4E188B24@r-forge.r-project.org> Author: jedick Date: 2017-04-25 13:19:56 +0200 (Tue, 25 Apr 2017) New Revision: 187 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/R/diagram.R pkg/CHNOSZ/data/refs.csv pkg/CHNOSZ/inst/NEWS Log: diagram(): draw blank areas for NaN values from equilibrate() Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2017-03-20 12:46:58 UTC (rev 186) +++ pkg/CHNOSZ/DESCRIPTION 2017-04-25 11:19:56 UTC (rev 187) @@ -1,6 +1,6 @@ -Date: 2017-03-20 +Date: 2017-04-25 Package: CHNOSZ -Version: 1.0.8-75 +Version: 1.0.8-76 Title: Chemical Thermodynamics and Activity Diagrams Author: Jeffrey Dick Maintainer: Jeffrey Dick Modified: pkg/CHNOSZ/R/diagram.R =================================================================== --- pkg/CHNOSZ/R/diagram.R 2017-03-20 12:46:58 UTC (rev 186) +++ pkg/CHNOSZ/R/diagram.R 2017-04-25 11:19:56 UTC (rev 187) @@ -142,14 +142,18 @@ predominant <- NA if(plotvar %in% c("loga.equil", "alpha", "A/2.303RT")) { pv <- plotvals - for(i in 1:length(pv)) { - # change any NAs in the plotvals to -Inf, so that - # they don't get on the plot, but permit others to - pv[[i]][is.na(pv[[i]])] <- -Inf - # TODO: see vignette for an explanation for how this is normalizing - # the formulas in a predominance calculation - if(normalize & eout.is.aout) pv[[i]] <- (pv[[i]] + eout$species$logact[i] / n.balance[i]) - log10(n.balance[i]) - else if(as.residue & eout.is.aout) pv[[i]] <- pv[[i]] + eout$species$logact[i] / n.balance[i] + # some additional steps for affinity values, but not for equilibrated activities + if(eout.is.aout) { + for(i in 1:length(pv)) { + # change any NAs in the plotvals to -Inf, so that + # they don't get on the plot, but permit others to + # (useful for making mineral stability diagrams beyond transition temperatures of one or more minerals) + pv[[i]][is.na(pv[[i]])] <- -Inf + # TODO: see vignette for an explanation for how this is normalizing + # the formulas in a predominance calculation + if(normalize) pv[[i]] <- (pv[[i]] + eout$species$logact[i] / n.balance[i]) - log10(n.balance[i]) + else if(as.residue) pv[[i]] <- pv[[i]] + eout$species$logact[i] / n.balance[i] + } } predominant <- which.pmax(pv) } Modified: pkg/CHNOSZ/data/refs.csv =================================================================== --- pkg/CHNOSZ/data/refs.csv 2017-03-20 12:46:58 UTC (rev 186) +++ pkg/CHNOSZ/data/refs.csv 2017-04-25 11:19:56 UTC (rev 187) @@ -105,7 +105,7 @@ SLOP15.4,"E. L. Shock et al.",2015,"slop15.dat computer data file","adipic acid and n-dodecanoate: "Gibbs free energy corrected to be compatible with the equation ΔG=ΔH-TΔS for the formation reaction from elements. See footnote y in table 4 of @Sho95."",http://geopig.asu.edu/?q=tools SLOP15.5,"E. L. Shock et al.",2015,"slop15.dat computer data file","n-octanoate: "Enthalpy corrected to be compatible with the equation ΔG=ΔH-TΔS for the formation reaction from elements. See footnote ab in table 4 of @Sho95."",http://geopig.asu.edu/?q=tools SLOP15.6,"E. L. Shock et al.",2015,"slop15.dat computer data file",""Enthalpy corrected to be compatible with the equation ΔG=ΔH-TΔS for the formation reaction from elements."",http://geopig.asu.edu/?q=tools -SLOP15.7,"E. L. Shock et al.",2015,"slop15.dat computer data file","heptanol, hexanol, and octanol: "Minor differences in Gibbs energy, entropy, omega, a1, a2, a3, a4 and c1 values compared to @SH90."",http://geopig.asu.edu/?q=tools +SLOP15.7,"E. L. Shock et al.",2015,"slop15.dat computer data file","hexanol, heptanol, and octanol: "Minor differences in Gibbs energy, entropy, omega, a1, a2, a3, a4 and c1 values compared to @SH90."",http://geopig.asu.edu/?q=tools CS16,"P. A. Canovas III and E. L. Shock",2016,"Geochim. Cosmochim. Acta 195, 293-322","citric acid cycle metabolites",http://dx.doi.org/10.1016/j.gca.2016.08.028 CS16.1,"P. A. Canovas III and E. L. Shock",2016,"Geochim. Cosmochim. Acta 195, 293-322","citric acid species HKF a1--a4 parameters",http://dx.doi.org/10.1016/j.gca.2016.08.028 CHNOSZ.1,"J. M. Dick",2017,"CHNOSZ package documentation","GHS (Tr) of the phase that is stable at 298.15 K was combined with Htr and the Cp coefficients to calculate the metastable GHS (Tr) of the phases that are stable at higher temperatures.",http://chnosz.net Modified: pkg/CHNOSZ/inst/NEWS =================================================================== --- pkg/CHNOSZ/inst/NEWS 2017-03-20 12:46:58 UTC (rev 186) +++ pkg/CHNOSZ/inst/NEWS 2017-04-25 11:19:56 UTC (rev 187) @@ -1,4 +1,4 @@ -CHANGES IN CHNOSZ 1.0.8-75 (2017-03-20) +CHANGES IN CHNOSZ 1.0.8-76 (2017-04-25) --------------------------------------- DOCUMENTATION: @@ -109,13 +109,13 @@ were first present in sprons92.dat from SUPCRT, slop98.dat, or later versions of the slop data files (http://geopig.asu.edu/?q=tools). -- Canovas_aq.csv: Add data for citric acid cycle metabolites from +- biotic_aq.csv: Add data for citric acid cycle metabolites from Canovas and Shock, 2016. - CHNOSZ_aq.csv: Add H4SiO4 pseudospecies (pseudo-H4SiO4); see calculations in eos-regress.Rmd. -- Dick_aq.csv: Add data for aqueous phenanthrene and methylphenanthrene +- organic_aq.csv: Add data for aqueous phenanthrene and methylphenanthrene from Dick et al., 2013. - Remove superseded data previously in OBIGT-2.csv: citric acid cycle @@ -149,7 +149,7 @@ BUG FIXES: -- Correct charge (-2) of NAD(red)-2 in LaRowe_aq.csv. Thanks to Peter +- Correct charge (-2) of NAD(red)-2 in biotic_aq.csv. Thanks to Peter Canovas. - Also correct charge (-2) of MgATP-2. @@ -160,6 +160,10 @@ noted for the first example in ?nonideal. Thanks to David T. Wang for the bug report and test. +- NaN values from equilibrate() are now preserved by diagram(), + producing unlabeled blank (white) fields rather than being + mistakenly labeled with the first species. + OTHER CHANGES: - Remove msgout(), and replace previous calls to that function with From noreply at r-forge.r-project.org Thu Apr 27 04:30:52 2017 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Thu, 27 Apr 2017 04:30:52 +0200 (CEST) Subject: [CHNOSZ-commits] r188 - in pkg/CHNOSZ: . R inst man tests/testthat Message-ID: <20170427023052.BAD95188A0A@r-forge.r-project.org> Author: jedick Date: 2017-04-27 04:30:51 +0200 (Thu, 27 Apr 2017) New Revision: 188 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/R/diagram.R pkg/CHNOSZ/inst/NEWS pkg/CHNOSZ/man/diagram.Rd pkg/CHNOSZ/tests/testthat/test-diagram.R Log: diagram(): add 'col.NA' argument Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2017-04-25 11:19:56 UTC (rev 187) +++ pkg/CHNOSZ/DESCRIPTION 2017-04-27 02:30:51 UTC (rev 188) @@ -1,6 +1,6 @@ -Date: 2017-04-25 +Date: 2017-04-27 Package: CHNOSZ -Version: 1.0.8-76 +Version: 1.0.8-77 Title: Chemical Thermodynamics and Activity Diagrams Author: Jeffrey Dick Maintainer: Jeffrey Dick Modified: pkg/CHNOSZ/R/diagram.R =================================================================== --- pkg/CHNOSZ/R/diagram.R 2017-04-25 11:19:56 UTC (rev 187) +++ pkg/CHNOSZ/R/diagram.R 2017-04-27 02:30:51 UTC (rev 188) @@ -20,7 +20,7 @@ # line styles lty=NULL, lwd=par("lwd"), dotted=NULL, # colors - col=par("col"), col.names=par("col"), fill=NULL, + col=par("col"), col.names=par("col"), fill=NULL, col.NA="black", # labels names=NULL, main=NULL, legend.x=NA, format.names=TRUE, adj=0.5, dy=0, # plotting controls @@ -315,8 +315,10 @@ zs <- out for(i in 1:nrow(zs)) zs[i,] <- out[nrow(zs)+1-i,] zs <- t(zs) - breaks <- c(0,1:nspecies) + 0.5 - image(x=xs, y=ys, z=zs, col=fill, add=TRUE, breaks=breaks, useRaster=TRUE) + breaks <- c(-1, 0, 1:nspecies) + 0.5 + # use col.NA for NA values + zs[is.na(zs)] <- 0 + image(x=xs, y=ys, z=zs, col=c(col.NA, fill), add=TRUE, breaks=breaks, useRaster=TRUE) } ## curve plot function # 20091116 replaced plot.curve with plot.line; different Modified: pkg/CHNOSZ/inst/NEWS =================================================================== --- pkg/CHNOSZ/inst/NEWS 2017-04-25 11:19:56 UTC (rev 187) +++ pkg/CHNOSZ/inst/NEWS 2017-04-27 02:30:51 UTC (rev 188) @@ -1,4 +1,4 @@ -CHANGES IN CHNOSZ 1.0.8-76 (2017-04-25) +CHANGES IN CHNOSZ 1.0.8-77 (2017-04-27) --------------------------------------- DOCUMENTATION: @@ -161,8 +161,8 @@ the bug report and test. - NaN values from equilibrate() are now preserved by diagram(), - producing unlabeled blank (white) fields rather than being - mistakenly labeled with the first species. + producing unlabeled fields rather than being mistakenly labeled with + the first species. Thanks to Grayson Boyer for the bug report. OTHER CHANGES: Modified: pkg/CHNOSZ/man/diagram.Rd =================================================================== --- pkg/CHNOSZ/man/diagram.Rd 2017-04-25 11:19:56 UTC (rev 187) +++ pkg/CHNOSZ/man/diagram.Rd 2017-04-27 02:30:51 UTC (rev 188) @@ -14,7 +14,7 @@ ylog=TRUE, xlim=NULL, ylim=NULL, xlab=NULL, ylab=NULL, cex=par("cex"), cex.names=1, cex.axis=par("cex"), lty=NULL, lwd=par("lwd"), dotted=NULL, - col=par("col"), col.names=par("col"), fill=NULL, + col=par("col"), col.names=par("col"), fill=NULL, col.NA="black", names=NULL, main=NULL, legend.x=NA, format.names=TRUE, adj=0.5, dy=0, add=FALSE, plot.it=TRUE, tplot=TRUE, ...) strip(affinity, ispecies = NULL, col = NULL, ns = NULL, @@ -48,6 +48,7 @@ \item{col}{character, color of activity lines (1D diagram) or predominance field boundaries (2D diagram), or colors of bars in a strip diagram (\code{strip})} \item{col.names}{character, colors for labels of species} \item{fill}{character, colors used to fill predominance fields} + \item{col.NA}{character, color for grid points with NA values} \item{names}{character, names of species for activity lines or predominance fields} \item{main}{character, a main \code{\link{title}} for the plot; \code{NULL} means to plot no title} \item{legend.x}{character, description of legend placement passed to \code{\link{legend}}} Modified: pkg/CHNOSZ/tests/testthat/test-diagram.R =================================================================== --- pkg/CHNOSZ/tests/testthat/test-diagram.R 2017-04-25 11:19:56 UTC (rev 187) +++ pkg/CHNOSZ/tests/testthat/test-diagram.R 2017-04-27 02:30:51 UTC (rev 188) @@ -85,3 +85,16 @@ #expect_equal(diagram(a), diagram(a, plot.it=FALSE)) expect_warning(diagram(a, what="CO2", plot.it=FALSE), "showing only first species in 2-D property diagram") }) + +test_that("NaN values from equilibrate() are preserved (as NA in predominance calculation)", { + # example provided by Grayson Boyer 20170411 + basis(c("H2", "O2", "CO2"), c(-7.19, -60, -2.65)) + species(c("n-hexadecanol", "n-hexadecanoic acid", "n-octadecanol", "n-octadecanoic acid"), c("liq", "liq", "liq", "liq")) + a <- affinity("H2" = c(-12, 0), "O2" = c(-90, -50), T=30) + e <- equilibrate(a, balance = 1) + d <- diagram(e, plot.it = FALSE) + # equilibrate() here with default "boltzmann" method produces + # NaN at very high O2 + low H2 or very low O2 + high H2 + expect_equal(d$predominant[1, 128], as.numeric(NA)) + expect_equal(d$predominant[128, 1], as.numeric(NA)) +}) From noreply at r-forge.r-project.org Thu Apr 27 07:24:50 2017 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Thu, 27 Apr 2017 07:24:50 +0200 (CEST) Subject: [CHNOSZ-commits] r189 - in pkg/CHNOSZ: . R inst Message-ID: <20170427052450.804C5188A1B@r-forge.r-project.org> Author: jedick Date: 2017-04-27 07:24:50 +0200 (Thu, 27 Apr 2017) New Revision: 189 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/R/read.expr.R pkg/CHNOSZ/R/util.character.R pkg/CHNOSZ/R/util.formula.R pkg/CHNOSZ/inst/NEWS Log: avoid suppressWarnings (they still appear using testthat) Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2017-04-27 02:30:51 UTC (rev 188) +++ pkg/CHNOSZ/DESCRIPTION 2017-04-27 05:24:50 UTC (rev 189) @@ -1,6 +1,6 @@ Date: 2017-04-27 Package: CHNOSZ -Version: 1.0.8-77 +Version: 1.0.8-78 Title: Chemical Thermodynamics and Activity Diagrams Author: Jeffrey Dick Maintainer: Jeffrey Dick Modified: pkg/CHNOSZ/R/read.expr.R =================================================================== --- pkg/CHNOSZ/R/read.expr.R 2017-04-27 02:30:51 UTC (rev 188) +++ pkg/CHNOSZ/R/read.expr.R 2017-04-27 05:24:50 UTC (rev 189) @@ -12,9 +12,7 @@ # yeastgfp preprocessing ygfp <- read.csv(yfile) # convert factors to numeric w/o NA coercion warnings - warn <- options(warn=-1) - ygfp$abundance <- as.numeric(as.character(ygfp$abundance)) - options(warn) + ygfp$abundance <- as.numeric.nowarn(as.character(ygfp$abundance)) # if location is NULL, just report on the content of the file # and return the names of the locations if(is.null(location)) { Modified: pkg/CHNOSZ/R/util.character.R =================================================================== --- pkg/CHNOSZ/R/util.character.R 2017-04-27 02:30:51 UTC (rev 188) +++ pkg/CHNOSZ/R/util.character.R 2017-04-27 05:24:50 UTC (rev 189) @@ -55,14 +55,26 @@ # return a value of TRUE or FALSE for each element of x can.be.numeric <- function(x) { # return FALSE if length of argument is zero - if(length(x)==0) return(FALSE) - if(length(x)>1) return(as.logical(sapply(x,can.be.numeric))) - # don't warn about NAs in as.numeric - oldopt <- options(warn=-1) - cb <- FALSE - if(!is.na(as.numeric(x))) cb <- TRUE - if(x %in% c('.','+','-')) cb <- TRUE - # let the user have their way - options(oldopt) - return(cb) + if(length(x) == 0) FALSE else + if(length(x) > 1) as.logical(sapply(x, can.be.numeric)) else { + if(is.numeric(x)) TRUE else + if(!is.na(as.numeric.nowarn(x))) TRUE else + if(x %in% c('.','+','-')) TRUE else FALSE + } } + +# something like R's as.numeric(), but without the "NAs introduced by coercion" warnings +# (needed because testthat somehow detects the warnings suppressed by suppressWarnings) 20170427 +as.numeric.nowarn <- function(x) { + if(length(x) == 0) numeric() else + if(length(x) > 1) sapply(x, as.numeric.nowarn) else + # http://stackoverflow.com/questions/12643009/regular-expression-for-floating-point-numbers + if(grepl("^[+-]?([0-9]*[.])?[0-9]+$", x)) as.numeric(x) else NA_real_ +} + +# convert to integer without NA coercion warnings +as.integer.nowarn <- function(x) { + if(length(x) == 0) integer() else + if(length(x) > 1) sapply(x, as.integer.nowarn) else + if(grepl("[^0-9]", x)) NA_integer_ else as.integer(x) +} Modified: pkg/CHNOSZ/R/util.formula.R =================================================================== --- pkg/CHNOSZ/R/util.formula.R 2017-04-27 02:30:51 UTC (rev 188) +++ pkg/CHNOSZ/R/util.formula.R 2017-04-27 05:24:50 UTC (rev 189) @@ -156,7 +156,7 @@ # return the values in the argument, or chemical formula(s) # for values that are species indices # for numeric values, get the formulas from those rownumbers of thermo$obigt - i <- suppressWarnings(as.numeric(formula)) + i <- as.integer.nowarn(formula) # we can't have more than the number of rows in thermo$obigt thermo <- get("thermo") iover <- i > nrow(thermo$obigt) Modified: pkg/CHNOSZ/inst/NEWS =================================================================== --- pkg/CHNOSZ/inst/NEWS 2017-04-27 02:30:51 UTC (rev 188) +++ pkg/CHNOSZ/inst/NEWS 2017-04-27 05:24:50 UTC (rev 189) @@ -1,4 +1,4 @@ -CHANGES IN CHNOSZ 1.0.8-77 (2017-04-27) +CHANGES IN CHNOSZ 1.0.8-78 (2017-04-27) --------------------------------------- DOCUMENTATION: From noreply at r-forge.r-project.org Fri Apr 28 10:30:52 2017 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Fri, 28 Apr 2017 10:30:52 +0200 (CEST) Subject: [CHNOSZ-commits] r190 - in pkg/CHNOSZ: . R demo inst man vignettes Message-ID: <20170428083052.6F050188D23@r-forge.r-project.org> Author: jedick Date: 2017-04-28 10:30:51 +0200 (Fri, 28 Apr 2017) New Revision: 190 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/R/diagram.R pkg/CHNOSZ/R/mosaic.R pkg/CHNOSZ/R/util.plot.R pkg/CHNOSZ/demo/copper.R pkg/CHNOSZ/demo/mosaic.R pkg/CHNOSZ/demo/sources.R pkg/CHNOSZ/inst/NEWS pkg/CHNOSZ/man/diagram.Rd pkg/CHNOSZ/man/util.plot.Rd pkg/CHNOSZ/vignettes/anintro.Rmd Log: diagram(): gray areas beyond water stability limits Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2017-04-27 05:24:50 UTC (rev 189) +++ pkg/CHNOSZ/DESCRIPTION 2017-04-28 08:30:51 UTC (rev 190) @@ -1,6 +1,6 @@ -Date: 2017-04-27 +Date: 2017-04-28 Package: CHNOSZ -Version: 1.0.8-78 +Version: 1.0.8-79 Title: Chemical Thermodynamics and Activity Diagrams Author: Jeffrey Dick Maintainer: Jeffrey Dick Modified: pkg/CHNOSZ/R/diagram.R =================================================================== --- pkg/CHNOSZ/R/diagram.R 2017-04-27 05:24:50 UTC (rev 189) +++ pkg/CHNOSZ/R/diagram.R 2017-04-28 08:30:51 UTC (rev 190) @@ -20,7 +20,8 @@ # line styles lty=NULL, lwd=par("lwd"), dotted=NULL, # colors - col=par("col"), col.names=par("col"), fill=NULL, col.NA="black", + col=par("col"), col.names=par("col"), fill=NULL, + fill.NA="slategray1", limit.water=TRUE, # labels names=NULL, main=NULL, legend.x=NA, format.names=TRUE, adj=0.5, dy=0, # plotting controls @@ -33,7 +34,7 @@ if(!"sout" %in% names(eout)) stop("'eout' does not look like output from equil() or affinity()") ## 'what' can be: - # loga.equil - equilibrium activities of species of interest (eout) + # loga.equil - equilibrium activities of species of interest (eout) # basis species - equilibrium activity of a basis species (aout) # missing - property from affinity() or predominances of species (aout) eout.is.aout <- FALSE @@ -156,6 +157,19 @@ } } predominant <- which.pmax(pv) + # for an Eh-pH or pe-pH diagram, clip plot to water stability region + if(limit.water & eout$vars[1] == "pH" & eout$vars[2] %in% c("Eh", "pe")) { + wl <- water.lines(xaxis=eout$vars[1], yaxis=eout$vars[2], T=eout$T, P=eout$P, xpoints=eout$vals[[1]], plot.it=FALSE) + # for each x-point, find the y-values that are outside the water stability limits + for(i in seq_along(wl$xpoints)) { + ymin <- min(c(wl$y.oxidation[i], wl$y.reduction[i])) + ymax <- max(c(wl$y.oxidation[i], wl$y.reduction[i])) + # the actual calculation + iNA <- eout$vals[[2]] < ymin | eout$vals[[2]] > ymax + # assign NA to the predominance matrix + predominant[i, iNA] <- NA + } + } } # a warning about that we can only show properties of the first species on a 2-D diagram @@ -316,9 +330,9 @@ for(i in 1:nrow(zs)) zs[i,] <- out[nrow(zs)+1-i,] zs <- t(zs) breaks <- c(-1, 0, 1:nspecies) + 0.5 - # use col.NA for NA values + # use fill.NA for NA values zs[is.na(zs)] <- 0 - image(x=xs, y=ys, z=zs, col=c(col.NA, fill), add=TRUE, breaks=breaks, useRaster=TRUE) + image(x=xs, y=ys, z=zs, col=c(fill.NA, fill), add=TRUE, breaks=breaks, useRaster=TRUE) } ## curve plot function # 20091116 replaced plot.curve with plot.line; different @@ -405,7 +419,7 @@ ys <- rev(ys) } # the categories (species/groups/etc) on the plot - zvals <- unique(as.vector(predominant)) + zvals <- na.omit(unique(as.vector(predominant))) # take each possible pair for(i in 1:(length(zvals)-1)) { for(j in (i+1):length(zvals)) { @@ -460,6 +474,8 @@ else if(isTRUE(fill[1]=="rainbow")) fill <- rainbow(ngroups) else if(isTRUE(fill[1] %in% c("heat", "terrain", "topo", "cm"))) fill <- get(paste0(fill[1], ".colors"))(ngroups) fill <- rep(fill, length.out=ngroups) + # modify the default for fill.NA + if(add & missing(fill.NA)) fill.NA <- "transparent" # the x and y values xs <- eout$vals[[1]] ys <- eout$vals[[2]] Modified: pkg/CHNOSZ/R/mosaic.R =================================================================== --- pkg/CHNOSZ/R/mosaic.R 2017-04-27 05:24:50 UTC (rev 189) +++ pkg/CHNOSZ/R/mosaic.R 2017-04-28 08:30:51 UTC (rev 190) @@ -77,6 +77,8 @@ # merge affinities using the second, third, ... basis species for(j in tail(seq_along(affs), -1)) { is.predominant <- d$predominant==j + # diagram() produces NA beyond water limits on Eh-pH diagrams (but we can't use NA for indexing, below) + is.predominant[is.na(is.predominant)] <- FALSE for(i in seq_along(A.species$values)) { A.species$values[[i]][is.predominant] <- affs[[j]]$values[[i]][is.predominant] } Modified: pkg/CHNOSZ/R/util.plot.R =================================================================== --- pkg/CHNOSZ/R/util.plot.R 2017-04-27 05:24:50 UTC (rev 189) +++ pkg/CHNOSZ/R/util.plot.R 2017-04-28 08:30:51 UTC (rev 190) @@ -66,67 +66,66 @@ } water.lines <- function(xaxis='pH', yaxis='Eh', T=298.15, P='Psat', which=c('oxidation','reduction'), - logaH2O=0, lty=2, lwd=1, col=par('fg'), xpoints=NULL, O2state="gas") { + logaH2O=0, lty=2, lwd=1, col=par('fg'), xpoints=NULL, O2state="gas", plot.it=TRUE) { # draw water stability limits - # if we're on an Eh-pH diagram, or logfO2-pH diagram, - # or logfO2-T or Eh-T - # calculate them exactly (nicer looking lines), otherwise - # (TODO) add them using affinity() and diagram() - - # get the x and y limits from the current plot - pu <- par('usr') - xlim <- pu[1:2] - ylim <- pu[3:4] - # exact lines - # warning: Eh calculations are reliable only at a single T + # for Eh-pH, logfO2-pH, logfO2-T or Eh-T diagrams + # (i.e. redox variable is on the y axis) + y.oxidation <- y.reduction <- NULL + # if they are not provided, get the x points from the plot limits + if(is.null(xpoints)) { + pu <- par('usr') + xlim <- pu[1:2] + xpoints <- seq(xlim[1], xlim[2], length.out=100) + } + # note: Eh calculations are valid at a single T only if(xaxis=="O2" | (xaxis=='pH' & (yaxis=='Eh' | yaxis=='O2' | yaxis=="pe"))) { if('reduction' %in% which) { logfH2 <- 0 logK <- subcrt(c("H2O", "O2", "H2"), c(-1, 0.5, 1), c("liq", O2state, "gas"), T=T, P=P, convert=FALSE)$out$logK # this is logfO2 if O2state=="gas", or logaO2 if O2state=="aq" logfO2 <- 2 * logK - logfH2 + 2 * logaH2O - if(xaxis=='O2') abline(v=logfO2,lty=lty,lwd=lwd,col=col) - else if(yaxis=='O2') abline(h=logfO2,lty=lty,lwd=lwd,col=col) - else if(yaxis=="Eh") lines(xlim,convert(logfO2,'E0',T=T,P=P,pH=xlim),lty=lty,lwd=lwd,col=col) - else if(yaxis=="pe") lines(xlim,convert(convert(logfO2,'E0',T=T,P=P,pH=xlim),"pe",T=T),lty=lty,lwd=lwd,col=col) + #if(xaxis=='O2') abline(v=logfO2,lty=lty,lwd=lwd,col=col) + #if(yaxis=='O2') abline(h=logfO2,lty=lty,lwd=lwd,col=col) + if(yaxis=="Eh") y.reduction <- convert(logfO2, 'E0', T=T, P=P, pH=xpoints) + else if(yaxis=="pe") y.reduction <- convert(convert(logfO2, 'E0', T=T, P=P, pH=xpoints), "pe", T=T) } if('oxidation' %in% which) { logfO2 <- 0 logK <- subcrt(c("O2", "O2"), c(-1, 1), c("gas", O2state), T=T, P=P, convert=FALSE)$out$logK # this is logfO2 if O2state=="gas", or logaO2 if O2state=="aq" logfO2 <- logfO2 + logK - if(xaxis=='O2') abline(v=logfO2,lty=lty,lwd=lwd,col=col) - if(yaxis=='O2') abline(h=logfO2,lty=lty,lwd=lwd,col=col) - else if(yaxis=="Eh") lines(xlim,convert(logfO2,'E0',T=T,P=P,pH=xlim),lty=lty,lwd=lwd,col=col) - else if(yaxis=="pe") lines(xlim,convert(convert(logfO2,'E0',T=T,P=P,pH=xlim),"pe",T=T),lty=lty,lwd=lwd,col=col) + #if(xaxis=='O2') abline(v=logfO2,lty=lty,lwd=lwd,col=col) + #if(yaxis=='O2') abline(h=logfO2,lty=lty,lwd=lwd,col=col) + if(yaxis=="Eh") y.oxidation <- convert(logfO2, 'E0', T=T, P=P, pH=xpoints) + else if(yaxis=="pe") y.oxidation <- convert(convert(logfO2, 'E0', T=T, P=P, pH=xpoints), "pe", T=T) } } else if(xaxis %in% c('T','P') & yaxis %in% c('Eh','O2') ) { #if(xaxis=='T') if(is.null(xpoints)) xpoints <- T # 20090212 get T values from plot limits # TODO: make this work for T on y-axis too - if(xaxis=='T') { - if(missing(T)) { - xpoints <- seq(xlim[1],xlim[2],length.out=100) - T <- envert(xpoints,"K") - } - } - if(xaxis=='P') if(is.null(xpoints)) xpoints <- P + if(xaxis=='T' & missing(T)) T <- envert(xpoints, "K") + if(xaxis=='P') if(missing(xpoints)) xpoints <- P if('oxidation' %in% which) { logfO2 <- rep(0,length(xpoints)) - if(yaxis=='Eh') lines(xpoints,convert(logfO2,'E0',T=T,P=P,pH=xlim),lty=lty,lwd=lwd,col=col) - else lines(xpoints,logfO2,lty=lty,lwd=lwd,col=col) + if(yaxis=='Eh') y.oxidation <- convert(logfO2, 'E0', T=T, P=P, pH=xpoints) + else y.oxidation <- logfO2 } if('reduction' %in% which) { logfH2 <- 0 logK <- subcrt(c('H2O','oxygen','hydrogen'),c(-1,0.5,1),T=T,P=P,convert=FALSE)$out$logK logfO2 <- 2 * logK - logfH2 + 2 * logaH2O - if(yaxis=='Eh') lines(xpoints,convert(logfO2,'E0',T=T,P=P,pH=xlim),lty=lty,lwd=lwd,col=col) - else lines(xpoints,logfO2,lty=lty,lwd=lwd,col=col) + if(yaxis=='Eh') y.reduction <- convert(logfO2, 'E0', T=T, P=P, pH=xpoints) + else y.reduction <- logfO2 } - } else { - # inexact lines - # } + if(yaxis=="Eh") y.oxidation <- convert(logfO2, 'E0', T=T, P=P, pH=xpoints) + # now plot the lines + if(plot.it) { + lines(xpoints, y.oxidation, lty=lty, lwd=lwd, col=col) + lines(xpoints, y.reduction, lty=lty, lwd=lwd, col=col) + } + # return the values + return(invisible(list(xpoints=xpoints, y.oxidation=y.oxidation, y.reduction=y.reduction))) } mtitle <- function(main, line=0, ...) { Modified: pkg/CHNOSZ/demo/copper.R =================================================================== --- pkg/CHNOSZ/demo/copper.R 2017-04-27 05:24:50 UTC (rev 189) +++ pkg/CHNOSZ/demo/copper.R 2017-04-28 08:30:51 UTC (rev 190) @@ -38,7 +38,7 @@ # mosaic diagram with to speciate glycine as a function of pH m <- mosaic(bases=Gly, pH=c(0, 16, 300), Eh=c(-0.6, 1.0, 300)) fill <- c(rep("lightgrey", 3), rep("white", 4), rep("lightblue", 4)) -d <- diagram(m$A.species, fill=fill, names=NULL, xaxs="i", yaxs="i") +d <- diagram(m$A.species, fill=fill, names=NULL, xaxs="i", yaxs="i", fill.NA="pink2") # to make the labels look nicer names <- names[sort(unique(as.numeric(d$predominant)))] for(i in 1:length(names)) { @@ -54,7 +54,7 @@ } # add glycine ionization lines -d <- diagram(m$A.bases, add=TRUE, col="darkblue", lty=3, names=NULL) +d <- diagram(m$A.bases, add=TRUE, col="darkblue", lty=3, names=NULL, limit.water=FALSE) text(d$lx, -0.5, Gly, col="darkblue") # add water lines and title Modified: pkg/CHNOSZ/demo/mosaic.R =================================================================== --- pkg/CHNOSZ/demo/mosaic.R 2017-04-27 05:24:50 UTC (rev 189) +++ pkg/CHNOSZ/demo/mosaic.R 2017-04-28 08:30:51 UTC (rev 190) @@ -33,6 +33,7 @@ title(main=paste("Iron oxides, sulfides and carbonate in water, log(total S) = -6,", "log(total C)=0, after Garrels and Christ, 1965", sep="\n")) # overlay the carbonate basis species predominance fields -diagram(m1$A.bases2, add=TRUE, col="blue", col.names="blue", lty=3) +d <- diagram(m1$A.bases2, add=TRUE, col="blue", names=NULL, lty=3, limit.water=FALSE) +text(d$lx, -0.8, as.expression(sapply(m1$A.bases2$species$name, expr.species)), col="blue") # reset the database, as it was changed in this example data(thermo) Modified: pkg/CHNOSZ/demo/sources.R =================================================================== --- pkg/CHNOSZ/demo/sources.R 2017-04-27 05:24:50 UTC (rev 189) +++ pkg/CHNOSZ/demo/sources.R 2017-04-28 08:30:51 UTC (rev 190) @@ -9,7 +9,7 @@ obigt.source <- unique(c(os1,os2)) obigt.source <- obigt.source[!is.na(obigt.source)] # these all produce character(0) if the sources are all accounted for -print("missing these sources (1) for thermodynamic properties:") +print("missing these sources for thermodynamic properties:") print(unique(obigt.source[!(obigt.source %in% ref.source)])) # determine if all the reference sources are cited # this should produce character(0) Modified: pkg/CHNOSZ/inst/NEWS =================================================================== --- pkg/CHNOSZ/inst/NEWS 2017-04-27 05:24:50 UTC (rev 189) +++ pkg/CHNOSZ/inst/NEWS 2017-04-28 08:30:51 UTC (rev 190) @@ -1,4 +1,4 @@ -CHANGES IN CHNOSZ 1.0.8-78 (2017-04-27) +CHANGES IN CHNOSZ 1.0.8-79 (2017-04-28) --------------------------------------- DOCUMENTATION: @@ -58,6 +58,10 @@ - Add arguments `adj` and `dy` for x-alignment and y-offset of line labels. +- Add arguments `fill.NA` (color of empty areas) and `limit.water` + (assign NA to areas beyond water stability limits on Eh-pH and pe-pH + diagrams). + NEW FEATURES: - Add ZC.col() for generating a red-grey-blue color scale from @@ -161,7 +165,7 @@ the bug report and test. - NaN values from equilibrate() are now preserved by diagram(), - producing unlabeled fields rather than being mistakenly labeled with + producing empty (NA) fields rather than being mistakenly labeled with the first species. Thanks to Grayson Boyer for the bug report. OTHER CHANGES: Modified: pkg/CHNOSZ/man/diagram.Rd =================================================================== --- pkg/CHNOSZ/man/diagram.Rd 2017-04-27 05:24:50 UTC (rev 189) +++ pkg/CHNOSZ/man/diagram.Rd 2017-04-28 08:30:51 UTC (rev 190) @@ -14,7 +14,8 @@ ylog=TRUE, xlim=NULL, ylim=NULL, xlab=NULL, ylab=NULL, cex=par("cex"), cex.names=1, cex.axis=par("cex"), lty=NULL, lwd=par("lwd"), dotted=NULL, - col=par("col"), col.names=par("col"), fill=NULL, col.NA="black", + col=par("col"), col.names=par("col"), fill=NULL, + fill.NA="slategray1", limit.water=TRUE, names=NULL, main=NULL, legend.x=NA, format.names=TRUE, adj=0.5, dy=0, add=FALSE, plot.it=TRUE, tplot=TRUE, ...) strip(affinity, ispecies = NULL, col = NULL, ns = NULL, @@ -48,7 +49,8 @@ \item{col}{character, color of activity lines (1D diagram) or predominance field boundaries (2D diagram), or colors of bars in a strip diagram (\code{strip})} \item{col.names}{character, colors for labels of species} \item{fill}{character, colors used to fill predominance fields} - \item{col.NA}{character, color for grid points with NA values} + \item{fill.NA}{character, color for grid points with NA values} + \item{limit.water}{logical, set NA values beyond water stability limits?} \item{names}{character, names of species for activity lines or predominance fields} \item{main}{character, a main \code{\link{title}} for the plot; \code{NULL} means to plot no title} \item{legend.x}{character, description of legend placement passed to \code{\link{legend}}} @@ -89,6 +91,9 @@ \code{fill} determines the color of the predominance fields, \code{col} that of the boundary lines. By default, \code{\link{heat.colors}} are used to fill the predominance fields in diagrams on the screen plot device. \code{fill} can be any color specification, or the word \samp{rainbow}, \samp{heat}, \samp{terrain}, \samp{topo}, or \samp{cm}, indicating a palette from \pkg{grDevices}. +\code{fill.NA} gives the color for empty fields, i.e. points for which NA values are present, possibly by using \code{\link{equilibrate}} at extreme conditions (see \code{test-diagram.Rd}). +\code{fill.NA} is also used to specify the color outside the water stability limits on Eh-pH or pe-pH diagrams, when \code{limit.water} is TRUE. +Note that the default for \code{fill.NA} is automatically changed to \samp{transparent} when \code{add} is TRUE. As of CHNOSZ 1.0.8-11, a new default line-drawing procedure has been implemented. This uses \code{\link{contour}} to draw smooth-looking diagonal and curved lines, at the expense of not coinciding exactly with the rectangular grid (which is still used for drawing colors). @@ -210,9 +215,9 @@ "goethite", "melanterite", "pyrite")) a <- affinity(pH=c(-1, 4, 256), pe=c(-5, 23, 256)) d <- diagram(a, main="Fe-S-O-H, after Majzlan et al., 2006") -# the first four species show up along the top of the diagram -stopifnot(all.equal(unique(t(d$predominant)[256,]), 1:4)) -water.lines(yaxis="pe") +# the first four species show up in order near pe=15 +stopifnot(all.equal(unique(d$predominant[, 183]), 1:4)) +water.lines(yaxis="pe", lwd=2) text(3, 22, describe.basis(thermo$basis[2:3,], digits=2, oneline=TRUE)) text(3, 21, describe.property(c("T", "P"), c(25, 1), oneline=TRUE)) Modified: pkg/CHNOSZ/man/util.plot.Rd =================================================================== --- pkg/CHNOSZ/man/util.plot.Rd 2017-04-27 05:24:50 UTC (rev 189) +++ pkg/CHNOSZ/man/util.plot.Rd 2017-04-28 08:30:51 UTC (rev 190) @@ -27,7 +27,7 @@ italic = FALSE, ...) water.lines(xaxis = "pH", yaxis = "Eh", T = 298.15, P = "Psat", which = c("oxidation","reduction"), logaH2O = 0, lty = 2, lwd=1, - col = par("fg"), xpoints = NULL, O2state="gas") + col = par("fg"), xpoints = NULL, O2state="gas", plot.it = TRUE) mtitle(main, line=0, ...) ZC.col(z) } @@ -64,6 +64,7 @@ \item{lty}{numeric, line type} \item{xpoints}{numeric, points to plot on \eqn{x}{x} axis} \item{O2state}{character, state of O2} + \item{plot.it}{logical, plot the lines?} \item{main}{character, text for plot title} \item{line}{numeric, margin line to place title} \item{z}{numeric, set of values} Modified: pkg/CHNOSZ/vignettes/anintro.Rmd =================================================================== --- pkg/CHNOSZ/vignettes/anintro.Rmd 2017-04-27 05:24:50 UTC (rev 189) +++ pkg/CHNOSZ/vignettes/anintro.Rmd 2017-04-28 08:30:51 UTC (rev 190) @@ -244,7 +244,7 @@ as.chemical.formula(makeup(910)) ``` -For organic species, a simple calculation of the average oxidation state of carbon (`r zc`) is possible given the species index, chemical formula, or elemental count: +For organic species, a calculation of the average oxidation state of carbon (`r zc`) is possible given the species index, chemical formula, or elemental count: ```{r ZC_910, message=FALSE} ZC(910) ZC(info(910)$formula) @@ -281,7 +281,7 @@ subcrt("water", T = c(400, 500, 600), P = c(200, 400, 600), grid = "P")$out$water ``` -```{r subcrt_water_plot, fig.margin=TRUE, fig.width=4, fig.height=4, small.mar=TRUE, dpi=dpi, out.width="100%", echo=FALSE, message=FALSE, fig.cap="Isothermal contours of density (g cm-3) and pressure (bar) of H2O.", cache=TRUE, pngquant=pngquant, timeit=timeit} +```{r subcrt_water_plot, fig.margin=TRUE, fig.width=4, fig.height=4, small.mar=TRUE, dpi=dpi, out.width="100%", echo=FALSE, message=FALSE, fig.cap="Isothermal contours of density (g cm-3) and pressure (bar) of water.", cache=TRUE, pngquant=pngquant, timeit=timeit} substuff <- subcrt("water", T=seq(0,1000,100), P=c(NA, seq(1,500,1)), grid="T") water <- substuff$out$water plot(water$P, water$rho, type = "l") @@ -545,8 +545,9 @@ ``` ```{r EhpH_plot, fig.margin=TRUE, fig.width=4, fig.height=4, small.mar=TRUE, dpi=dpi, out.width="100%", echo=FALSE, message=FALSE, cache=TRUE, fig.cap="Aqueous sulfur species at 25 ?C.", pngquant=pngquant, timeit=timeit} -a <- affinity(pH = c(0, 12), Eh = c(-1, 1)) +a <- affinity(pH = c(0, 12), Eh = c(-0.5, 1)) diagram(a, fill = "heat") +water.lines() ``` Now we can calculate the affinities on an Eh-pH grid: @@ -555,8 +556,10 @@ ## Potential diagrams -Given values of affinity, the `diagram()` function uses the maximum affinity method to make a potential diagram (i.e. a Pourbaix diagram): -```{r EhpH_plot, echo=2, eval=FALSE} +Given values of affinity, the `diagram()` function uses the maximum affinity method to make a potential diagram (i.e. a Pourbaix diagram). +Areas corresponding to Eh-pH conditions beyond the stability limits of water are colored slate gray. +A second function, `water.lines()`, is used to draw lines at the water stability limits: +```{r EhpH_plot, echo=-1, eval=FALSE} ``` Note that the calculation of affinity implies a non-equilibrium reference state of equal activities of species ([see above](#species-of-interest)). @@ -572,7 +575,7 @@ The default colors for diagrams shown on the screen use R's `heat.colors()` palette. Some arguments in `diagram()` can be used to control the color, labels, and lines, and title. The `tplot` argument turns off plot customizations used in CHNOSZ. -Additional arguments are passed to R's plotting functions; here, we use `bty` to remove the box around the plot: +Additional arguments are passed to R's plotting functions; here, we use `bty` to remove the box around the plot. ```{r EhpH_plot_color, echo=TRUE, eval=FALSE} ``` @@ -618,15 +621,16 @@ The key argument is `bases`, which identifies the candidate basis species, starting with the one in the current basis. The other arguments, like those of `affinity()`, specify the ranges of the variables; `res` indicates the grid resolution to use for each variable (the default is 128). The first call to `diagram()` plots the species of interest; the second adds the predominance fields of the basis species. -Finally, `water.lines()` is used to add the stability limits of water at the given temperature. +We turn off the gray coloring beyond the water stability limits (`limit.water`) but plot the lines using `water.lines()`: -```{r copper_mosaic, fig.margin=TRUE, fig.width=4, fig.height=4, small.mar=TRUE, dpi=dpi, out.width="100%", message=FALSE, cache=TRUE, fig.cap="Copper minerals and aqueous complexes with chloride, 25 ?C.", pngquant=pngquant, timeit=timeit} +```{r copper_mosaic, fig.margin=TRUE, fig.width=4, fig.height=4, small.mar=TRUE, dpi=dpi, out.width="100%", message=FALSE, cache=TRUE, fig.cap="Copper minerals and aqueous complexes with chloride, 200 ?C.", pngquant=pngquant, timeit=timeit} T <- 200 res <- 200 bases <- c("H2S", "HS-", "HSO4-", "SO4-2") m1 <- mosaic(bases, blend = TRUE, pH = c(0, 12, res), Eh=c(-1.2, 0.75, res), T=T) -diagram(m1$A.species, lwd = 2, fill = NA) -diagram(m1$A.bases, add = TRUE, col = "blue", col.names = "blue", lty = 2) +diagram(m1$A.species, lwd = 2, fill = NA, limit.water = FALSE) +diagram(m1$A.bases, add = TRUE, col = "blue", col.names = "blue", lty = 2, + limit.water = FALSE) water.lines("pH", "Eh", T = convert(T, "K"), col = "red", lwd = 2, lty = 2) ``` @@ -646,8 +650,10 @@ if (names(newvar) == "O2") basis("O2", "gas") mosaicargs <- c(list(bases), blend=TRUE, pH=list(c(-2, 12, res)), newvar, T=T) m1 <- do.call(mosaic, mosaicargs) - diagram(m1$A.species, lwd = 2, fill = rev(topo.colors(10))) - diagram(m1$A.bases, add = TRUE, col = "blue", col.names = "blue", lty = 3) + diagram(m1$A.species, lwd = 2, fill = rev(topo.colors(10)), + limit.water = FALSE) + diagram(m1$A.bases, add = TRUE, col = "blue", col.names = "blue", lty = 3, + limit.water = FALSE) swap.basis(names(newvar), "e-") } par(mfrow = c(1, 3)) From noreply at r-forge.r-project.org Sat Apr 29 07:40:55 2017 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Sat, 29 Apr 2017 07:40:55 +0200 (CEST) Subject: [CHNOSZ-commits] r191 - in pkg/CHNOSZ: . inst vignettes Message-ID: <20170429054055.5624F1886FF@r-forge.r-project.org> Author: jedick Date: 2017-04-29 07:40:54 +0200 (Sat, 29 Apr 2017) New Revision: 191 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/inst/NEWS pkg/CHNOSZ/vignettes/anintro.Rmd pkg/CHNOSZ/vignettes/vig.bib Log: anintro.Rmd: add Sabatini et al., 2012 reference Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2017-04-28 08:30:51 UTC (rev 190) +++ pkg/CHNOSZ/DESCRIPTION 2017-04-29 05:40:54 UTC (rev 191) @@ -1,6 +1,6 @@ -Date: 2017-04-28 +Date: 2017-04-29 Package: CHNOSZ -Version: 1.0.8-79 +Version: 1.0.8-80 Title: Chemical Thermodynamics and Activity Diagrams Author: Jeffrey Dick Maintainer: Jeffrey Dick Modified: pkg/CHNOSZ/inst/NEWS =================================================================== --- pkg/CHNOSZ/inst/NEWS 2017-04-28 08:30:51 UTC (rev 190) +++ pkg/CHNOSZ/inst/NEWS 2017-04-29 05:40:54 UTC (rev 191) @@ -1,4 +1,4 @@ -CHANGES IN CHNOSZ 1.0.8-79 (2017-04-28) +CHANGES IN CHNOSZ 1.0.8-80 (2017-04-29) --------------------------------------- DOCUMENTATION: Modified: pkg/CHNOSZ/vignettes/anintro.Rmd =================================================================== --- pkg/CHNOSZ/vignettes/anintro.Rmd 2017-04-28 08:30:51 UTC (rev 190) +++ pkg/CHNOSZ/vignettes/anintro.Rmd 2017-04-29 05:40:54 UTC (rev 191) @@ -558,7 +558,7 @@ Given values of affinity, the `diagram()` function uses the maximum affinity method to make a potential diagram (i.e. a Pourbaix diagram). Areas corresponding to Eh-pH conditions beyond the stability limits of water are colored slate gray. -A second function, `water.lines()`, is used to draw lines at the water stability limits: +Another function, `water.lines()`, is used to draw lines at the water stability limits: ```{r EhpH_plot, echo=-1, eval=FALSE} ``` @@ -1642,8 +1642,12 @@

We have calculated the distribution of ATP species and average binding number of H+ and Mg+2 for given pH, pMg, ionic strength, and temperature. -Apparent equilibrium constants tabulated for specified ionic strength make an algebraic solution of the equilibrium distribution of species feasible, as demonstrated by the Mathematica code in Alberty (2003). -The required calculations can be performed "on the fly" in CHNOSZ by using the `IS` argument in `subcrt()` or `affinity()` to invoke the nonideality model on top of the standard Gibbs energies of species. +Accounting for the distribution of chemical species lends itself to thermodynamic models for reactions between reactants that have multiple possibly ionized and bound states. +In contrast, Alberty (2003) and others propose models for biochemical reactions where the ionized and complexed species are combined into a single representation. +Those models invoke Legendre-transformed thermodynamic properties, such as transformed Gibbs energies that are tabulated for specified pH, pMg, and ionic strength. +Although the conceptual pathways are different, the two approaches lead to equivalent results concerning the energetics of the overall reactions and the conditions for equilibrium [@SVI12]. +The example here shows how the required calculations can be performed at the species level using conventional standard Gibbs energies for species referenced to infinite dilution (zero ionic strength). +The effects of ionic strength are modeled "on the fly" in CHNOSZ by setting the `IS` argument in `subcrt()` or `affinity()` to invoke the nonideality model on top of the standard Gibbs energies of species. ## Optimization of chemical activities Modified: pkg/CHNOSZ/vignettes/vig.bib =================================================================== --- pkg/CHNOSZ/vignettes/vig.bib 2017-04-28 08:30:51 UTC (rev 190) +++ pkg/CHNOSZ/vignettes/vig.bib 2017-04-29 05:40:54 UTC (rev 191) @@ -237,14 +237,14 @@ } @Article{MSS13, - author = {Manning, Craig E. and Shock, Everett L. and Sverjensky, Dimitri A.}, - journal = {Reviews in Mineralogy and Geochemistry}, - title = {The chemistry of carbon in aqueous fluids at crustal and upper-mantle conditions: {E}xperimental and theoretical constraints}, - year = {2013}, - volume = {75}, - number = {1}, - pages = {109--148}, - doi = {10.2138/rmg.2013.75.5}, + author = {Manning, Craig E. and Shock, Everett L. and Sverjensky, Dimitri A.}, + journal = {Reviews in Mineralogy and Geochemistry}, + title = {{T}he chemistry of carbon in aqueous fluids at crustal and upper-mantle conditions: {E}xperimental and theoretical constraints}, + year = {2013}, + volume = {75}, + number = {1}, + pages = {109--148}, + doi = {10.2138/rmg.2013.75.5}, } @InProceedings{NPW_79, @@ -530,12 +530,12 @@ url = {http://www.worldcat.org/oclc/18559968}, } - at Article{Dic17, - author = {Dick, Jeffrey M.}, - journal = {bioRxiv}, - title = {{C}hemical composition and the potential for proteomic transformation in cancer, hypoxia, and hyperosmotic stress}, - year = {2017}, - doi = {10.1101/097667}, + at Article{Dic17a, + author = {Dick, Jeffrey M.}, + journal = {bioRxiv}, + title = {{C}hemical composition and the potential for proteomic transformation in cancer, hypoxia, and hyperosmotic stress}, + year = {2017}, + doi = {10.1101/097667}, } @Article{HW97, @@ -638,3 +638,26 @@ number = {UCRL-MA-110662 PT I}, } + at Article{Dic17, + author = {Dick, Jeffrey M.}, + journal = {PeerJ}, + title = {{C}hemical composition and the potential for proteomic transformation in cancer, hypoxia, and hyperosmotic stress}, + year = {2017}, +} + + at Article{SVI12, + author = {Sabatini, Antonio and Vacca, Alberto and Iotti, Stefano}, + journal = {PLoS ONE}, + title = {{B}alanced biochemical reactions: {A} new approach to unify chemical and biochemical thermodynamics}, + year = {2012}, + volume = {7}, + number = {1}, + pages = {e29529}, + doi = {10.1371/journal.pone.0029529}, + sn = {1932-6203}, + z8 = {0}, + z9 = {0}, + zb = {0}, + zs = {0}, +} + From noreply at r-forge.r-project.org Sun Apr 30 08:50:03 2017 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Sun, 30 Apr 2017 08:50:03 +0200 (CEST) Subject: [CHNOSZ-commits] r192 - in pkg/CHNOSZ: . R data inst inst/extdata/OBIGT man vignettes Message-ID: <20170430065003.28E3018867D@r-forge.r-project.org> Author: jedick Date: 2017-04-30 08:50:01 +0200 (Sun, 30 Apr 2017) New Revision: 192 Added: pkg/CHNOSZ/inst/extdata/OBIGT/CHNOSZ_aq.csv.xz pkg/CHNOSZ/inst/extdata/OBIGT/H2O_aq.csv.xz pkg/CHNOSZ/inst/extdata/OBIGT/biotic_aq.csv.xz pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_aq.csv.xz pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_cr.csv.xz pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_gas.csv.xz pkg/CHNOSZ/inst/extdata/OBIGT/organic_aq.csv.xz pkg/CHNOSZ/inst/extdata/OBIGT/organic_cr.csv.xz pkg/CHNOSZ/inst/extdata/OBIGT/organic_gas.csv.xz pkg/CHNOSZ/inst/extdata/OBIGT/organic_liq.csv.xz Removed: pkg/CHNOSZ/inst/extdata/OBIGT/CHNOSZ_aq.csv pkg/CHNOSZ/inst/extdata/OBIGT/H2O_aq.csv pkg/CHNOSZ/inst/extdata/OBIGT/biotic_aq.csv pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_aq.csv pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_cr.csv pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_gas.csv pkg/CHNOSZ/inst/extdata/OBIGT/organic_aq.csv pkg/CHNOSZ/inst/extdata/OBIGT/organic_cr.csv pkg/CHNOSZ/inst/extdata/OBIGT/organic_gas.csv pkg/CHNOSZ/inst/extdata/OBIGT/organic_liq.csv pkg/CHNOSZ/man/sideeffects.Rd Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/R/examples.R pkg/CHNOSZ/data/thermo.R pkg/CHNOSZ/inst/NEWS pkg/CHNOSZ/man/data.Rd pkg/CHNOSZ/vignettes/obigt.Rmd Log: convert files to *.xz in extdata/OBIGT/ Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2017-04-29 05:40:54 UTC (rev 191) +++ pkg/CHNOSZ/DESCRIPTION 2017-04-30 06:50:01 UTC (rev 192) @@ -1,6 +1,6 @@ -Date: 2017-04-29 +Date: 2017-04-30 Package: CHNOSZ -Version: 1.0.8-80 +Version: 1.0.8-81 Title: Chemical Thermodynamics and Activity Diagrams Author: Jeffrey Dick Maintainer: Jeffrey Dick Modified: pkg/CHNOSZ/R/examples.R =================================================================== --- pkg/CHNOSZ/R/examples.R 2017-04-29 05:40:54 UTC (rev 191) +++ pkg/CHNOSZ/R/examples.R 2017-04-30 06:50:01 UTC (rev 192) @@ -5,7 +5,7 @@ examples <- function(do.png=FALSE) { # run all the examples in CHNOSZ documentation .ptime <- proc.time() - topics <- c("thermo", "sideeffects", "examples", + topics <- c("thermo", "examples", "util.array", "util.blast", "util.data", "util.expression", "util.fasta", "util.formula", "util.matrix", "util.misc", "util.seq", "util.units", "util.water", "taxonomy", "info", "protein.info", "hkf", "water", "IAPWS95", "subcrt", Modified: pkg/CHNOSZ/data/thermo.R =================================================================== --- pkg/CHNOSZ/data/thermo.R 2017-04-29 05:40:54 UTC (rev 191) +++ pkg/CHNOSZ/data/thermo.R 2017-04-30 06:50:01 UTC (rev 192) @@ -15,7 +15,7 @@ sources_gas <- paste0(c("inorganic", "organic"), "_gas") OBIGTdir <- system.file("extdata/OBIGT/", package="CHNOSZ") # need explicit "/" for Windows - sourcefiles <- paste0(OBIGTdir, "/", c(sources_aq, sources_cr, sources_liq, sources_gas), ".csv") + sourcefiles <- paste0(OBIGTdir, "/", c(sources_aq, sources_cr, sources_liq, sources_gas), ".csv.xz") datalist <- lapply(sourcefiles, read.csv, as.is=TRUE) obigt <- do.call(rbind, datalist) # create thermo list Modified: pkg/CHNOSZ/inst/NEWS =================================================================== --- pkg/CHNOSZ/inst/NEWS 2017-04-29 05:40:54 UTC (rev 191) +++ pkg/CHNOSZ/inst/NEWS 2017-04-30 06:50:01 UTC (rev 192) @@ -1,4 +1,4 @@ -CHANGES IN CHNOSZ 1.0.8-80 (2017-04-29) +CHANGES IN CHNOSZ 1.0.8-81 (2017-04-30) --------------------------------------- DOCUMENTATION: @@ -197,6 +197,9 @@ - Remove grep.file(). +- Remove sideeffects.Rd (functions with side effects are now identified + with red color in anintro.Rmd). + CHANGES IN CHNOSZ 1.0.8 (2016-05-28) ------------------------------------ Deleted: pkg/CHNOSZ/inst/extdata/OBIGT/CHNOSZ_aq.csv =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/CHNOSZ_aq.csv 2017-04-29 05:40:54 UTC (rev 191) +++ pkg/CHNOSZ/inst/extdata/OBIGT/CHNOSZ_aq.csv 2017-04-30 06:50:01 UTC (rev 192) @@ -1,2 +0,0 @@ -name,abbrv,formula,state,ref1,ref2,date,G,H,S,Cp,V,a1.a,a2.b,a3.c,a4.d,c1.e,c2.f,omega.lambda,z.T -pseudo-H4SiO4,NA,H4SiO4,aq,CHNOSZ.4,NA,18.Feb.17,-312565,-346409,51.4246,-40.0964,52.1998,89.2031,-176.5071,-452.1431,101.36051,67.0854,-52.0776,0.1215745,0 Copied: pkg/CHNOSZ/inst/extdata/OBIGT/CHNOSZ_aq.csv.xz (from rev 191, pkg/CHNOSZ/inst/extdata/OBIGT/CHNOSZ_aq.csv) =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/CHNOSZ_aq.csv.xz (rev 0) +++ pkg/CHNOSZ/inst/extdata/OBIGT/CHNOSZ_aq.csv.xz 2017-04-30 06:50:01 UTC (rev 192) @@ -0,0 +1 @@ +?7zXZ???F!t/?????]7I??b???9??????TB;q?"?q???cL;?"????)~)??Ma=~??+ ?@??,??\???Z?"????ed????????C ?C??4?????????!?-???T?C%?:?????UP?U?????????g?YZ \ No newline at end of file Deleted: pkg/CHNOSZ/inst/extdata/OBIGT/H2O_aq.csv =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/H2O_aq.csv 2017-04-29 05:40:54 UTC (rev 191) +++ pkg/CHNOSZ/inst/extdata/OBIGT/H2O_aq.csv 2017-04-30 06:50:01 UTC (rev 192) @@ -1,4 +0,0 @@ -name,abbrv,formula,state,ref1,ref2,date,G,H,S,Cp,V,a1.a,a2.b,a3.c,a4.d,c1.e,c2.f,omega.lambda,z.T -water,NA,H2O,liq,NA,NA,25.Oct.06,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA -e-,NA,Z0-1,aq,NA,NA,28.Oct.06,0,0,15.6166,0,0,0,0,0,0,0,0,0,0 -H+,H+,H+,aq,NA,NA,06.Nov.97,0,0,0,0,0,0,0,0,0,0,0,0,0 Copied: pkg/CHNOSZ/inst/extdata/OBIGT/H2O_aq.csv.xz (from rev 191, pkg/CHNOSZ/inst/extdata/OBIGT/H2O_aq.csv) =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/H2O_aq.csv.xz (rev 0) +++ pkg/CHNOSZ/inst/extdata/OBIGT/H2O_aq.csv.xz 2017-04-30 06:50:01 UTC (rev 192) @@ -0,0 +1 @@ +?7zXZ???F!t/????]7I??b???9??????TB;q?"?q???cL;?"?? Author: jedick Date: 2017-04-30 09:06:16 +0200 (Sun, 30 Apr 2017) New Revision: 193 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/inst/NEWS pkg/CHNOSZ/tests/testthat/test-protein.info.R pkg/CHNOSZ/vignettes/anintro.Rmd Log: comment broken test under development version of testthat Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2017-04-30 06:50:01 UTC (rev 192) +++ pkg/CHNOSZ/DESCRIPTION 2017-04-30 07:06:16 UTC (rev 193) @@ -1,6 +1,6 @@ Date: 2017-04-30 Package: CHNOSZ -Version: 1.0.8-81 +Version: 1.0.8-82 Title: Chemical Thermodynamics and Activity Diagrams Author: Jeffrey Dick Maintainer: Jeffrey Dick Modified: pkg/CHNOSZ/inst/NEWS =================================================================== --- pkg/CHNOSZ/inst/NEWS 2017-04-30 06:50:01 UTC (rev 192) +++ pkg/CHNOSZ/inst/NEWS 2017-04-30 07:06:16 UTC (rev 193) @@ -1,4 +1,4 @@ -CHANGES IN CHNOSZ 1.0.8-81 (2017-04-30) +CHANGES IN CHNOSZ 1.0.8-82 (2017-04-30) --------------------------------------- DOCUMENTATION: Modified: pkg/CHNOSZ/tests/testthat/test-protein.info.R =================================================================== --- pkg/CHNOSZ/tests/testthat/test-protein.info.R 2017-04-30 06:50:01 UTC (rev 192) +++ pkg/CHNOSZ/tests/testthat/test-protein.info.R 2017-04-30 07:06:16 UTC (rev 193) @@ -13,21 +13,23 @@ expect_equal(pinfo(c("LYSC_CHICK", "MYGPHYCA")), c(6, NA)) }) -# test_that somehow affects capture.output so we set up the problem here -protein <- pinfo(c("CSG_METVO", "CSG_METJA")) -suppressMessages(mod.obigt("[Met]", G=-35245, H=-59310)) -basis("CHNOS+") -suppressMessages(swap.basis("O2", "H2")) -pequil <- capture.output(protein.equil(protein, loga.protein=-3), type="message") +# 20170430 comment this section becuase `pequil` somehow is just empty +# using the current development version of testthat (on Github) +## test_that somehow affects capture.output so we set up the problem here +#protein <- pinfo(c("CSG_METVO", "CSG_METJA")) +#suppressMessages(mod.obigt("[Met]", G=-35245, H=-59310)) +#basis("CHNOS+") +#suppressMessages(swap.basis("O2", "H2")) +#pequil <- capture.output(protein.equil(protein, loga.protein=-3), type="message") +# +#test_that("protein.equil() reports values consistent with Dick and Shock (2011)", { +# # the Astar/RT in the paragraph following Eq. 23, p. 6 of DS11 +# # (truncated because of rounding) +# expect_true(any(grepl(c("0\\.435.*1\\.36"), pequil))) +# # the log10 activities of the proteins in the left-hand column of the same page +# expect_true(any(grepl(c("-3\\.256.*-2\\.834"), pequil))) +#}) -test_that("protein.equil() reports values consistent with Dick and Shock (2011)", { - # the Astar/RT in the paragraph following Eq. 23, p. 6 of DS11 - # (truncated because of rounding) - expect_true(any(grepl(c("0\\.435.*1\\.36"), pequil))) - # the log10 activities of the proteins in the left-hand column of the same page - expect_true(any(grepl(c("-3\\.256.*-2\\.834"), pequil))) -}) - # references # Dick, J. M. and Shock, E. L. (2011) Calculation of the relative chemical stabilities of proteins # as a function of temperature and redox chemistry in a hot spring. Modified: pkg/CHNOSZ/vignettes/anintro.Rmd =================================================================== --- pkg/CHNOSZ/vignettes/anintro.Rmd 2017-04-30 06:50:01 UTC (rev 192) +++ pkg/CHNOSZ/vignettes/anintro.Rmd 2017-04-30 07:06:16 UTC (rev 193) @@ -1642,7 +1642,7 @@

We have calculated the distribution of ATP species and average binding number of H+ and Mg+2 for given pH, pMg, ionic strength, and temperature. -Accounting for the distribution of chemical species lends itself to thermodynamic models for reactions between reactants that have multiple possibly ionized and bound states. +Accounting for the distribution of chemical species lends itself to thermodynamic models for reactions between reactants that have multiple ionized and bound states. In contrast, Alberty (2003) and others propose models for biochemical reactions where the ionized and complexed species are combined into a single representation. Those models invoke Legendre-transformed thermodynamic properties, such as transformed Gibbs energies that are tabulated for specified pH, pMg, and ionic strength. Although the conceptual pathways are different, the two approaches lead to equivalent results concerning the energetics of the overall reactions and the conditions for equilibrium [@SVI12].