From noreply at r-forge.r-project.org Fri Feb 1 02:45:02 2019 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Fri, 1 Feb 2019 02:45:02 +0100 (CET) Subject: [CHNOSZ-commits] r377 - in pkg/CHNOSZ: . R inst man tests/testthat vignettes Message-ID: <20190201014502.3683618AB49@r-forge.r-project.org> Author: jedick Date: 2019-02-01 02:45:00 +0100 (Fri, 01 Feb 2019) New Revision: 377 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/R/affinity.R pkg/CHNOSZ/R/util.affinity.R pkg/CHNOSZ/inst/NEWS pkg/CHNOSZ/man/affinity.Rd pkg/CHNOSZ/tests/testthat/test-affinity.R pkg/CHNOSZ/vignettes/obigt.Rmd pkg/CHNOSZ/vignettes/obigt.bib Log: affinity(): add 'return.sout' argument Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-01-28 08:53:03 UTC (rev 376) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-01 01:45:00 UTC (rev 377) @@ -1,6 +1,6 @@ -Date: 2019-01-28 +Date: 2019-02-01 Package: CHNOSZ -Version: 1.1.3-84 +Version: 1.1.3-85 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/R/affinity.R =================================================================== --- pkg/CHNOSZ/R/affinity.R 2019-01-28 08:53:03 UTC (rev 376) +++ pkg/CHNOSZ/R/affinity.R 2019-02-01 01:45:00 UTC (rev 377) @@ -13,7 +13,7 @@ #source("species.R") affinity <- function(..., property=NULL, sout=NULL, exceed.Ttr=FALSE, exceed.rhomin=FALSE, - return.buffer=FALSE, balance="PBB", iprotein=NULL, loga.protein=-3) { + return.buffer=FALSE, return.sout=FALSE, balance="PBB", iprotein=NULL, loga.protein=-3) { # ...: variables over which to calculate # property: what type of energy # (G.basis,G.species,logact.basis,logK,logQ,A) @@ -111,6 +111,8 @@ a <- aa$a sout <- aa$sout + if(return.sout) return(sout) + # more buffer stuff if(buffer) { args$what <- "logact.basis" Modified: pkg/CHNOSZ/R/util.affinity.R =================================================================== --- pkg/CHNOSZ/R/util.affinity.R 2019-01-28 08:53:03 UTC (rev 376) +++ pkg/CHNOSZ/R/util.affinity.R 2019-02-01 01:45:00 UTC (rev 377) @@ -133,9 +133,16 @@ ### function for calling subcrt sout.fun <- function(property="logK") { - if(!is.null(sout)) return(sout) else { + species <- c(mybasis$ispecies,myspecies$ispecies) + if(!is.null(sout)) { + # extract the needed species from a provided sout 20190131 + isout <- match(species, sout$species$ispecies) + this.sout <- sout + this.sout$species <- this.sout$species[isout, ] + this.sout$out <- this.sout$out[isout] + return(this.sout) + } else { ## subcrt arguments - species <- c(mybasis$ispecies,myspecies$ispecies) if("T" %in% vars) T <- vals[[which(vars=="T")]] if("P" %in% vars) P <- vals[[which(vars=="P")]] if("IS" %in% vars) IS <- vals[[which(vars=="IS")]] Modified: pkg/CHNOSZ/inst/NEWS =================================================================== --- pkg/CHNOSZ/inst/NEWS 2019-01-28 08:53:03 UTC (rev 376) +++ pkg/CHNOSZ/inst/NEWS 2019-02-01 01:45:00 UTC (rev 377) @@ -1,4 +1,4 @@ -CHANGES IN CHNOSZ 1.1.3-84 (2019-01-28) +CHANGES IN CHNOSZ 1.1.3-85 (2019-02-01) --------------------------------------- BUG FIXES @@ -240,6 +240,9 @@ - In affinity(), make invalid variable names an error. +- Add 'return.sout' argument to affinity(), to return just the values + calculated with subcrt(). + CHANGES IN CHNOSZ 1.1.3 (2017-11-13) ------------------------------------ Modified: pkg/CHNOSZ/man/affinity.Rd =================================================================== --- pkg/CHNOSZ/man/affinity.Rd 2019-01-28 08:53:03 UTC (rev 376) +++ pkg/CHNOSZ/man/affinity.Rd 2019-02-01 01:45:00 UTC (rev 377) @@ -8,7 +8,7 @@ \usage{ affinity(..., property=NULL, sout=NULL, exceed.Ttr=FALSE, exceed.rhomin = FALSE, - return.buffer=FALSE, balance="PBB", iprotein=NULL, loga.protein=-3) + return.buffer=FALSE, return.sout=FALSE, balance="PBB", iprotein=NULL, loga.protein=-3) } \arguments{ @@ -18,6 +18,7 @@ \item{exceed.Ttr}{logical, allow \code{\link{subcrt}} to compute properties for phases beyond their transition temperature?} \item{exceed.rhomin}{logical, allow \code{\link{subcrt}} to compute properties of species in the HKF model below 0.35 g cm\S{-3}?} \item{return.buffer}{logical. If \code{TRUE}, and a \code{\link{buffer}} has been associated with one or more basis species in the system, return the values of the activities of the basis species calculated using the buffer. Default is \code{FALSE}.} + \item{return.sout}{logical, return only the values calculated with \code{\link{subcrt}}?} \item{balance}{character. This argument is used to identify a conserved basis species (or \samp{PBB}) in a chemical activity buffer. Default is \samp{PBB}.} \item{iprotein}{numeric, indices of proteins in \code{\link{thermo}$protein} for which to calculate properties} \item{loga.protein}{numeric, logarithms of activities of proteins identified in \code{iprotein}} Modified: pkg/CHNOSZ/tests/testthat/test-affinity.R =================================================================== --- pkg/CHNOSZ/tests/testthat/test-affinity.R 2019-01-28 08:53:03 UTC (rev 376) +++ pkg/CHNOSZ/tests/testthat/test-affinity.R 2019-02-01 01:45:00 UTC (rev 377) @@ -174,6 +174,7 @@ }) test_that("argument recall is usable", { + # 20190127 basis("CHNOS") species(c("CO2", "CH4")) a0 <- affinity(O2=c(-80, -60)) @@ -184,3 +185,18 @@ # we don't test entire output here becuase a0 doesn't have a "T" argument expect_identical(a0$values, a3$values) }) + +test_that("sout is processed correctly", { + # 20190201 + basis("CHNOS+") + # previously, this test would fail when sout has + # more species than are used in the calculation + species(c("H2S", "CO2", "CH4")) + a0 <- affinity(T = c(0, 100)) + sout <- a0$sout + # test the calculation with just CH4 + species(1:2, delete = TRUE) + a1 <- affinity(T = c(0, 100)) + a2 <- affinity(T = c(0, 100), sout = a0$sout) + expect_equal(a1$values, a2$values) +}) Modified: pkg/CHNOSZ/vignettes/obigt.Rmd =================================================================== --- pkg/CHNOSZ/vignettes/obigt.Rmd 2019-01-28 08:53:03 UTC (rev 376) +++ pkg/CHNOSZ/vignettes/obigt.Rmd 2019-02-01 01:45:00 UTC (rev 377) @@ -119,7 +119,7 @@ * Data from SUPCRT92 which have been superseded by the Berman data are listed under **Optional Data** / **SUPCRT92**. -* Superseded data from SLOP98 (aqueous Au species) are listed under **Optional Data** / **SLOP98**. +* Superseded data from SLOP98 (aqueous SiO2 and Al, As, and Au species) are listed under **Optional Data** / **SLOP98**. # Sources of data {.tabset .tabset-fade} @@ -227,7 +227,7 @@ ### `r setfile("SLOP98.csv")` ```{r SLOP98, results="asis", echo=FALSE} -cat('These species, taken from the slop98 data file, were present in earlier versions of CHNOSZ but have been replaced by or are inconsistent with later updates. The data are kept here for comparative purposes. Use e.g. `add.obigt("SLOP98")` to load the data.\n\n') +cat('These species, taken from the slop98 data file, were present in earlier versions of CHNOSZ but have been replaced by or are inconsistent with later updates. The data are kept here for comparative purposes. Use `add.obigt("SLOP98")` to load the data.\n\n') ``` ```{r optreflist, results="asis", echo=FALSE} @@ -235,7 +235,7 @@ ### `r setfile("SUPCRT92.csv")` ```{r SUPCRT92, results="asis", echo=FALSE} -cat("These minerals, taken from the SUPCRT92 database, were used by default in earlier versions of CHNOSZ but have since been superseded by the Berman dataset. They are kept as optional data for testing and comparison purposes. The minerals here include all of the silicates and Al-bearing minerals from [Helgeson et al., 1978](http://www.worldcat.org/oclc/13594862), as well as calcite, dolomite, hematite, and magnetite. Note that other minerals from SUPCRT92 (including native elements, sulfides, halides, sulfates, and selected carbonates and oxides that do not duplicate those in the Berman dataset) are still present in the default database (**inorganic_cr.csv**).\n\n") +cat('These minerals, taken from the SUPCRT92 database, were present in earlier versions of CHNOSZ but have since been superseded by the Berman dataset. They are kept as optional data for testing and comparison purposes. The minerals here include all of the silicates and Al-bearing minerals from [Helgeson et al., 1978](http://www.worldcat.org/oclc/13594862), as well as calcite, dolomite, hematite, and magnetite. Use `add.obigt("SUPCRT92")` to load the data. Note that other minerals from SUPCRT92, including native elements, sulfides, halides, sulfates, and selected carbonates and oxides that do not duplicate those in the Berman dataset, are still present in the default database (**inorganic_cr.csv**).\n\n') ``` ```{r optreflist, results="asis", echo=FALSE} Modified: pkg/CHNOSZ/vignettes/obigt.bib =================================================================== --- pkg/CHNOSZ/vignettes/obigt.bib 2019-01-28 08:53:03 UTC (rev 376) +++ pkg/CHNOSZ/vignettes/obigt.bib 2019-02-01 01:45:00 UTC (rev 377) @@ -1177,16 +1177,16 @@ } @Article{HP11, - author = {Holland, T. J. B. and Powell, R.}, - journal = {Journal of Metamorphic Geology}, - title = {{A}n improved and extended internally consistent thermodynamic dataset for phases of petrological interest, involving a new equation of state for solids}, - year = {2011}, - volume = {29}, - number = {3}, - pages = {333--383}, - doi = {10.1111/j.1525-1314.2010.00923.x}, - sn = {0263-4929}, - z9 = {2}, + author = {Holland, T. J. B. and Powell, R.}, + journal = {Journal of Metamorphic Geology}, + title = {{A}n improved and extended internally consistent thermodynamic dataset for phases of petrological interest, involving a new equation of state for solids}, + year = {2011}, + volume = {29}, + number = {3}, + pages = {333--383}, + doi = {10.1111/j.1525-1314.2010.00923.x}, + sn = {0263-4929}, + z9 = {2}, } @Article{HRA91, @@ -1260,13 +1260,12 @@ pages = {9--70}, doi = {10.1144/SP402.4}, issn = {0305-8719}, - publisher = {Geological Society of London}, } @Article{WS00, author = {Wood, Scott A. and Samson, Iain M.}, journal = {Economic Geology}, - title = {{T}he hydrothermal geochemistry of tungsten in granitoid environments: {I}. {R}elative solubilities of ferberite and scheelite as a function of {T}, {P}, p{H}, and m{N}a{C}l}, + title = {{T}he hydrothermal geochemistry of tungsten in granitoid environments: {I}. {R}elative solubilities of ferberite and scheelite as a function of {T}, {P}, p{H}, and $m_\text{NaCl}$}, year = {2000}, volume = {95}, number = {1}, From noreply at r-forge.r-project.org Fri Feb 1 06:42:25 2019 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Fri, 1 Feb 2019 06:42:25 +0100 (CET) Subject: [CHNOSZ-commits] r378 - in pkg/CHNOSZ: . R demo inst man tests/testthat Message-ID: <20190201054225.2107F18B828@r-forge.r-project.org> Author: jedick Date: 2019-02-01 06:42:24 +0100 (Fri, 01 Feb 2019) New Revision: 378 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/R/mosaic.R pkg/CHNOSZ/demo/mosaic.R pkg/CHNOSZ/inst/NEWS pkg/CHNOSZ/man/mosaic.Rd pkg/CHNOSZ/man/solubility.Rd pkg/CHNOSZ/tests/testthat/test-mosaic.R Log: mosaic(): rewrite for performance and to handle more than two sets of changing basis species Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-01 01:45:00 UTC (rev 377) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-01 05:42:24 UTC (rev 378) @@ -1,6 +1,6 @@ Date: 2019-02-01 Package: CHNOSZ -Version: 1.1.3-85 +Version: 1.1.3-86 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/R/mosaic.R =================================================================== --- pkg/CHNOSZ/R/mosaic.R 2019-02-01 01:45:00 UTC (rev 377) +++ pkg/CHNOSZ/R/mosaic.R 2019-02-01 05:42:24 UTC (rev 378) @@ -1,15 +1,22 @@ # CHNOSZ/mosaic.R # calculate affinities with changing basis species -# 20141220 jmd +# 20141220 jmd initial version +# 20190129 complete rewrite to use any number of groups of changing basis species +# and improve speed by pre-calculating subcrt values (sout) +## if this file is interactively sourced, the following are also needed to provide unexported functions: +#source("basis.R") +#source("util.character.R") +#source("util.args.R") + # function to calculate affinities with mosaic of basis species -mosaic <- function(bases, bases2=NULL, blend=FALSE, ...) { +mosaic <- function(bases, bases2 = NULL, blend = FALSE, mixing = FALSE, ...) { # argument recall 20190120 # if the first argument is the result from a previous mosaic() calculation, # just update the remaining arguments if(is.list(bases)) { - if(identical(bases[1], list(fun="mosaic"))) { + if(identical(bases[1], list(fun = "mosaic"))) { aargs <- bases$args # we can only update arguments given in ... ddd <- list(...) @@ -23,100 +30,131 @@ } } - if(is.null(bases2)) { - # the arguments for affinity() - myargs <- list(...) - } else { - # the arguments for affinity (first set of basis species; outer loop) - myargs1 <- list(...) - # the arguments for mosaic() (second set of basis species; inner loop) - myargs <- list(bases=bases2, blend=blend, ...) + # backward compatibility 20190131: + # bases can be a vector instead of a list + # bases2 can be present + if(!is.list(bases)) { + bases <- list(bases) + hasbases2 <- FALSE + if(!is.null(bases2)) { + bases <- c(bases, list(bases2)) + hasbases2 <- TRUE + } + otherargs <- list(...) + allargs <- c(list(bases = bases, blend = blend, mixing = mixing), otherargs) + out <- do.call(mosaic, allargs) + # replace A.bases (affinity calculations for all groups of basis species) with backwards-compatbile A.bases and A.bases2 + if(hasbases2) A.bases2 <- out$A.bases[[2]] + A.bases <- out$A.bases[[1]] + out$A.bases <- A.bases + if(hasbases2) out <- c(out, list(A.bases2 = A.bases2)) + return(out) } - # are the swapped basis species on the plot? - # (the first one should be present in the starting basis set) - iswap <- match(bases[1], names(myargs)) - # the log activity of the starting basis species - logact.swap <- basis()$logact[ibasis(bases[1])] + # save starting basis and species definition + basis0 <- get("thermo")$basis + species0 <- get("thermo")$species + # get species indices of requested basis species + ispecies <- lapply(bases, info) + if(any(is.na(unlist(ispecies)))) stop("one or more of the requested basis species is unavailable") + # identify starting basis species + ispecies0 <- sapply(ispecies, "[", 1) + ibasis0 <- match(ispecies0, basis0$ispecies) + # quit if starting basis species are not present + ina <- is.na(ibasis0) + if(any(ina)) stop("the starting basis does not have ", paste(bases[ina], collapse = ", ")) - # a list where we'll keep the affinity calculations - affs <- list() - for(i in seq_along(bases)) { - message(paste("mosaic: current basis species is", bases[i], sep=" ")) - # set up argument list: name of swapped-in basis species - if(!is.na(iswap)) names(myargs)[iswap] <- bases[i] - # calculate affinities - if(is.null(bases2)) { - affs[[i]] <- do.call(affinity, myargs) - } else { - mcall <- do.call(mosaic, myargs) - affs[[i]] <- mcall$A.species - A.bases2 <- mcall$A.bases - } - # change the basis species; restore the original at the end of the loop - if(can.be.numeric(logact.swap)) logact.swap <- as.numeric(logact.swap) - if(i < length(bases)) { - swap.basis(bases[i], bases[i+1]) - # TODO: basis() requires the formula to identify the basis species, - # would be nicer to just use the ibasis here - bformula <- rownames(basis())[ibasis(bases[i+1])] - basis(bformula, logact.swap) - } else { - swap.basis(bases[i], bases[1]) - bformula <- rownames(basis())[ibasis(bases[1])] - basis(bformula, logact.swap) - } + # run subcrt() calculations for all basis species and formed species 20190131 + # this avoids repeating the calculations in different calls to affinity() + # add all the basis species here - the formed species are already present + lapply(bases, species) + sout <- affinity(..., return.sout = TRUE) + + # calculate affinities of the basis species themselves + A.bases <- list() + for(i in 1:length(bases)) { + message("mosaic: calculating affinities of basis species group ", i, ": ", paste(bases[[i]], collapse=" ")) + species(delete = TRUE) + species(bases[[i]]) + A.bases[[i]] <- suppressMessages(affinity(..., sout = sout)) } - # calculate affinities of formation of basis species - message(paste("mosaic: combining diagrams for", paste(bases, collapse=" "), sep=" ")) - ispecies <- species()$ispecies - species.logact <- species()$logact - species(delete=TRUE) - species(bases) - if(is.null(bases2)) A.bases <- do.call(affinity, myargs) - else A.bases <- do.call(affinity, myargs1) - # restore original species with original activities - species(delete=TRUE) - species(ispecies, species.logact) + # get all combinations of basis species + newbases <- as.matrix(expand.grid(ispecies)) + allbases <- matrix(basis0$ispecies, nrow = 1)[rep(1, nrow(newbases)), , drop = FALSE] + allbases[, ibasis0] <- newbases - # affinities calculated using the first basis species - A.species <- affs[[1]] + # calculate affinities of species for all combinations of basis species + aff.species <- list() + message("mosaic: calculating affinities of species for all ", nrow(allbases), " combinations of the basis species") + # run backwards so that we put the starting basis species back at the end + for(i in nrow(allbases):1) { + put.basis(allbases[i, ], basis0$logact) + # we have to define the species using the current basis + species(species0$ispecies, species0$logact) + aff.species[[i]] <- suppressMessages(affinity(..., sout = sout)) + } + + # calculate equilibrium mole fractions for each group of basis species + group.fraction <- list() if(blend) { - # calculate affinities using relative abundances of basis species - # this isn't needed (and doesn't work) if all the affinities are NA 20180925 - if(any(!sapply(A.species$values, is.na))) { - e <- equilibrate(A.bases) - # what is the total activity of the basis species? - a.tot <- Reduce("+", lapply(e$loga.equil, function(x) 10^x)) - for(j in seq_along(affs)) { - for(i in seq_along(A.species$values)) { - # start with zero affinity - if(j==1) A.species$values[[i]][] <- 0 - # add affinity scaled by relative abundance of this basis species - # and include mixing term (-x*log10(x)) 20190121 - x <- 10^e$loga.equil[[j]]/a.tot - A.species$values[[i]] <- A.species$values[[i]] + affs[[j]]$values[[i]] * x - x * log10(x) - } + for(i in 1:length(A.bases)) { + # this isn't needed (and doesn't work) if all the affinities are NA 20180925 + if(any(!sapply(A.bases[[1]]$values, is.na))) { + e <- equilibrate(A.bases[[i]]) + # exponentiate to get activities then divide by total activity + a.equil <- lapply(e$loga.equil, function(x) 10^x) + a.tot <- Reduce("+", a.equil) + group.fraction[[i]] <- lapply(a.equil, function(x) x / a.tot) + } else { + group.fraction[[i]] <- A.bases[[i]]$values } } } else { - # use affinities from the single predominant basis species - d <- diagram(A.bases, plot.it=FALSE) - # 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] + # for blend = FALSE, we just look at whether + # a basis species predominates within its group + for(i in 1:length(A.bases)) { + d <- diagram(A.bases[[i]], plot.it = FALSE, limit.water = FALSE) + group.fraction[[i]] <- list() + for(j in 1:length(bases[[i]])) { + # if a basis species predominates, it has a mole fraction of 1, or 0 otherwise + yesno <- d$predominant + yesno[yesno != j] <- 0 + yesno[yesno == j] <- 1 + group.fraction[[i]][[j]] <- yesno } } } + # make an indexing matrix for all combinations of basis species + ind.mat <- list() + for(i in 1:length(ispecies)) ind.mat[[i]] <- 1:length(ispecies[[i]]) + ind.mat <- as.matrix(expand.grid(ind.mat)) + + # calculate mole fractions for each combination of basis species + for(i in 1:nrow(ind.mat)) { + # multiply fractions from each group + for(j in 1:ncol(ind.mat)) { + if(j==1) x <- group.fraction[[j]][[ind.mat[i, j]]] + else x <- x * group.fraction[[j]][[ind.mat[i, j]]] + } + # multiply affinities by the mole fractions of basis species + # include mixing term (-x*log10(x)) 20190121 + if(blend & mixing) aff.species[[i]]$values <- lapply(aff.species[[i]]$values, function(values) values * x - x * log10(x)) + else aff.species[[i]]$values <- lapply(aff.species[[i]]$values, function(values) values * x) + } + + # get total affinities for the species + A.species <- aff.species[[1]] + for(i in 1:length(A.species$values)) { + # extract the affinity contributions from each basis species + A.values <- lapply(lapply(aff.species, "[[", "values"), "[[", i) + # sum them to get total affinities for this species + A.species$values[[i]] <- Reduce("+", A.values) + } + # for argument recall, include all arguments in output 20190120 - allargs <- c(list(bases=bases, bases2=bases2, blend=blend), list(...)) + allargs <- c(list(bases = bases, blend = blend, mixing = mixing), list(...)) # return the affinities for the species and basis species - if(is.null(bases2)) return(list(fun="mosaic", args=allargs, A.species=A.species, A.bases=A.bases)) - else return(list(fun="mosaic", args=allargs, A.species=A.species, A.bases=A.bases, A.bases2=A.bases2)) + return(list(fun = "mosaic", args = allargs, A.species = A.species, A.bases = A.bases)) } Modified: pkg/CHNOSZ/demo/mosaic.R =================================================================== --- pkg/CHNOSZ/demo/mosaic.R 2019-02-01 01:45:00 UTC (rev 377) +++ pkg/CHNOSZ/demo/mosaic.R 2019-02-01 05:42:24 UTC (rev 378) @@ -1,10 +1,13 @@ +# CHNOSZ/demo/mosaic.R +# 20141221 first version + # Fe-minerals and aqueous species in Fe-S-O-H-C system # after Garrels and Christ, 1965 Figure 7.21 # to reproduce their diagram as closely as posssible, use their thermodynamic data (from Appendix 2) -mod.obigt(c("Fe+2", "Fe+3"), G=c(-20300, -2520)) -mod.obigt(c("hematite", "magnetite", "pyrrhotite", "pyrite", "siderite"), G=c(-177100, -242400, -23320, -36000, -161060)) -mod.obigt(c("SO4-2", "HS-", "H2S", "HSO4-"), G=c(-177340, 3010, -6540, -179940)) -mod.obigt(c("CO2", "HCO3-", "CO3-2"), G=c(-92310, -140310, -126220)) +mod.obigt(c("Fe+2", "Fe+3"), G = c(-20300, -2520)) +mod.obigt(c("hematite", "magnetite", "pyrrhotite", "pyrite", "siderite"), G = c(-177100, -242400, -23320, -36000, -161060)) +mod.obigt(c("SO4-2", "HS-", "H2S", "HSO4-"), G = c(-177340, 3010, -6540, -179940)) +mod.obigt(c("CO2", "HCO3-", "CO3-2"), G = c(-92310, -140310, -126220)) # conditions and system definition pH <- c(0, 14, 400) Eh <- c(-1, 1, 400) @@ -22,18 +25,18 @@ # calculate affinities using the predominant basis species # using blend=TRUE we get curvy lines, particularly at the boundaries with siderite # compare with the plot in Garrels and Christ, 1965 -m1 <- mosaic(bases, bases2, blend=TRUE, pH=pH, Eh=Eh, T=T) +m1 <- mosaic(bases, bases2, blend = TRUE, pH = pH, Eh = Eh, T = T) # make a diagram and add water stability lines -diagram(m1$A.species, lwd=2) -water.lines(m1$A.species, col="seagreen", lwd=1.5) +diagram(m1$A.species, lwd = 2) +water.lines(m1$A.species, col = "seagreen", lwd = 1.5) # show lines for Fe(aq) = 10^-4 M species(c("Fe+2", "Fe+3"), -4) -m2 <- mosaic(bases, bases2, blend=TRUE, pH=pH, Eh=Eh, T=T) -diagram(m2$A.species, add=TRUE, names=NULL) +m2 <- mosaic(bases, bases2, blend = TRUE, pH = pH, Eh = Eh, T = T) +diagram(m2$A.species, add = TRUE, names = NULL) 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")) + "log(total C)=0, after Garrels and Christ, 1965", sep = "\n")) # overlay the carbonate basis species predominance fields -d <- diagram(m1$A.bases2, add=TRUE, col="blue", names=NULL, lty=3, limit.water=FALSE) -text(d$namesx, -0.8, as.expression(sapply(m1$A.bases2$species$name, expr.species)), col="blue") +d <- diagram(m1$A.bases2, add = TRUE, col = "blue", names = NULL, lty = 3, limit.water = FALSE) +text(d$namesx, -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/inst/NEWS =================================================================== --- pkg/CHNOSZ/inst/NEWS 2019-02-01 01:45:00 UTC (rev 377) +++ pkg/CHNOSZ/inst/NEWS 2019-02-01 05:42:24 UTC (rev 378) @@ -1,4 +1,4 @@ -CHANGES IN CHNOSZ 1.1.3-85 (2019-02-01) +CHANGES IN CHNOSZ 1.1.3-86 (2019-02-01) --------------------------------------- BUG FIXES @@ -69,6 +69,15 @@ of NaCl in water, taking account of activity coefficients and the reaction Na+ + Cl- = NaCl(aq). +OTHER NEW FEATURES + +- Add dumpdata() for returning/writing all packaged thermodynamic data + (including default database and optional data files). The file is + also available on the website (chnosz.net/download/alldata.csv). + +- mosaic() has been rewritten to handle more than two changing groups + of basis species. + DOCUMENTATION - Add demo/gold.R for calculations of Au solubility in hydrothermal @@ -92,10 +101,6 @@ THERMODYNAMIC DATA -- Add dumpdata() for returning/writing all packaged thermodynamic data - (including default database and optional data files). The file is - also available on the website (chnosz.net/download/alldata.csv). - - The Berman data (Berman, 1988 and later additions) have replaced the SUPCRT92 data (based on Helgeson et al., 1978) for most minerals in the default database (i.e. the one loaded by data(thermo)). Only Modified: pkg/CHNOSZ/man/mosaic.Rd =================================================================== --- pkg/CHNOSZ/man/mosaic.Rd 2019-02-01 01:45:00 UTC (rev 377) +++ pkg/CHNOSZ/man/mosaic.Rd 2019-02-01 05:42:24 UTC (rev 378) @@ -7,13 +7,14 @@ } \usage{ - mosaic(bases, bases2=NULL, blend=FALSE, ...) + mosaic(bases, bases2 = NULL, blend = FALSE, mixing = FALSE, ...) } \arguments{ - \item{bases}{character, basis species to be changed in the calculation} + \item{bases}{character, basis species to be changed in the calculation, or list, containing vectors for each group of changing basis species} \item{bases2}{character, second set of changing basis species} \item{blend}{logical, use relative abundances of basis species?} + \item{mixing}{logical, include a term for the Gibbs energy of mixing?} \item{...}{additional arguments to be passed to \code{\link{affinity}}} } @@ -28,14 +29,21 @@ The first species listed in \code{bases} should be in the current basis definition. The arguments in \code{...} are passed to \code{affinity} to specify the conditions. If \code{blend} is FALSE (the default), the function returns the affinities calculated using the single predominant basis species in \code{bases} at each condition. -If \code{blend} is TRUE, the function combines the affinities of the formation reactions in proportion to the relative abundances of the basis species at each condition, including a term to account for the Gibbs energy of mixing. -See the second example in \code{\link{solubility}} for a numerical test of the calculations using \code{blend}. +If \code{blend} is TRUE, the function combines the affinities of the formation reactions in proportion to the relative abundances of the basis species at each condition. +Additionally, if \code{mixing} is TRUE, a term is included to account for the Gibbs energy of mixing. +See the second example in \code{\link{solubility}} for a numerical test of the calculations using \code{blend} and \code{mixing}. The basis species listed in \code{bases} should all be related to the first basis species there (i.e. all share the same element). A second, independent set of basis species can be provided in \code{bases2} (for example \samp{CO3-2}, \samp{HCO3-}, \samp{CO2}, if the first set of basis species are the sulfur-bearing ones listed above). The function then works recursively, by calling itself instead of \code{affinity}, so that the inner loop changes the basis species in \code{bases2}. In this way, all possible combinations of the two sets of basis species are used in the calculation. +A more flexible method of specifying multiple sets of basis species is now available. +Instead of using \code{bases} and \code{bases2}, supply a list for just the \code{bases} argument. +The list should contain any number of vectors specifying the groups of basis species. +All combinations of basis species in these groups are used for the calculations. +This overcomes the prior limitation of only having two changing groups of basis species. + } \value{ Modified: pkg/CHNOSZ/man/solubility.Rd =================================================================== --- pkg/CHNOSZ/man/solubility.Rd 2019-02-01 01:45:00 UTC (rev 377) +++ pkg/CHNOSZ/man/solubility.Rd 2019-02-01 05:42:24 UTC (rev 378) @@ -121,7 +121,7 @@ ## method 2: CO2 and carbonate species as basis species basis(c("calcite", "CO2", "H2O", "O2", "H+")) species(c("Ca+2")) -m <- mosaic(c("CO2", "HCO3-", "CO3-2"), pH = c(3, 14), blend = TRUE) +m <- mosaic(c("CO2", "HCO3-", "CO3-2"), pH = c(3, 14), blend = TRUE, mixing = TRUE) sm0 <- solubility(m) smI <- solubility(m, find.IS = TRUE) ## plot the results Modified: pkg/CHNOSZ/tests/testthat/test-mosaic.R =================================================================== --- pkg/CHNOSZ/tests/testthat/test-mosaic.R 2019-02-01 01:45:00 UTC (rev 377) +++ pkg/CHNOSZ/tests/testthat/test-mosaic.R 2019-02-01 05:42:24 UTC (rev 378) @@ -34,8 +34,9 @@ bases <- c("SO4-2", "HSO4-", "HS-", "H2S") # calculate affinities using the predominant basis species pH <- c(0, 14, 29) - m1 <- mosaic(bases, pH=pH) - m2 <- mosaic(bases, pH=pH, blend=TRUE) + m1 <- mosaic(bases, pH = pH) + # calculate affinities with smooth transitions between basis species, including a mixing energy + m2 <- mosaic(bases, pH = pH, blend = TRUE, mixing = TRUE) # these species have no S so the results should be similar, # 20190121 except for a negative free energy of mixing (positive affinity) expect_true(all(m2$A.species$values[[1]] - m1$A.species$values[[1]] > 0)) From noreply at r-forge.r-project.org Sat Feb 2 12:54:47 2019 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Sat, 2 Feb 2019 12:54:47 +0100 (CET) Subject: [CHNOSZ-commits] r379 - in pkg/CHNOSZ: . R demo inst man tests/testthat vignettes Message-ID: <20190202115447.12BEE18C2F2@r-forge.r-project.org> Author: jedick Date: 2019-02-02 12:54:46 +0100 (Sat, 02 Feb 2019) New Revision: 379 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/R/mosaic.R pkg/CHNOSZ/demo/go-IU.R pkg/CHNOSZ/demo/mosaic.R pkg/CHNOSZ/inst/NEWS pkg/CHNOSZ/man/mosaic.Rd pkg/CHNOSZ/man/solubility.Rd pkg/CHNOSZ/tests/testthat/test-mosaic.R pkg/CHNOSZ/vignettes/mklinks.sh Log: mosaic(): change defaults to blend = TRUE and mixing = TRUE Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-01 05:42:24 UTC (rev 378) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-02 11:54:46 UTC (rev 379) @@ -1,6 +1,6 @@ -Date: 2019-02-01 +Date: 2019-02-02 Package: CHNOSZ -Version: 1.1.3-86 +Version: 1.1.3-87 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/R/mosaic.R =================================================================== --- pkg/CHNOSZ/R/mosaic.R 2019-02-01 05:42:24 UTC (rev 378) +++ pkg/CHNOSZ/R/mosaic.R 2019-02-02 11:54:46 UTC (rev 379) @@ -10,7 +10,7 @@ #source("util.args.R") # function to calculate affinities with mosaic of basis species -mosaic <- function(bases, bases2 = NULL, blend = FALSE, mixing = FALSE, ...) { +mosaic <- function(bases, bases2 = NULL, blend = TRUE, mixing = TRUE, ...) { # argument recall 20190120 # if the first argument is the result from a previous mosaic() calculation, Modified: pkg/CHNOSZ/demo/go-IU.R =================================================================== --- pkg/CHNOSZ/demo/go-IU.R 2019-02-01 05:42:24 UTC (rev 378) +++ pkg/CHNOSZ/demo/go-IU.R 2019-02-02 11:54:46 UTC (rev 379) @@ -98,9 +98,9 @@ bases <- c("H2S", "HS-", "HSO4-", "SO4-2") # calculate affinties of formation reactions using the speciated S basis species res <- 300 -# we "blend" the transitions with pH, unlike LZ11's diagram where +# the default has blend = TRUE, unlike LZ11's diagram where # it appears the S-basis species are switched in an on/off fashion -m <- mosaic(bases, pH=c(0, 14, res), Eh=c(-0.8, 0.8, res), blend=TRUE) +m <- mosaic(bases, pH=c(0, 14, res), Eh=c(-0.8, 0.8, res)) # adjust colors and names fill <- rev(heat.colors(nrow(species()))) fill[11:15] <- "darkgrey" Modified: pkg/CHNOSZ/demo/mosaic.R =================================================================== --- pkg/CHNOSZ/demo/mosaic.R 2019-02-01 05:42:24 UTC (rev 378) +++ pkg/CHNOSZ/demo/mosaic.R 2019-02-02 11:54:46 UTC (rev 379) @@ -9,8 +9,8 @@ mod.obigt(c("SO4-2", "HS-", "H2S", "HSO4-"), G = c(-177340, 3010, -6540, -179940)) mod.obigt(c("CO2", "HCO3-", "CO3-2"), G = c(-92310, -140310, -126220)) # conditions and system definition -pH <- c(0, 14, 400) -Eh <- c(-1, 1, 400) +pH <- c(0, 14, 500) +Eh <- c(-1, 1, 500) T <- 25 basis(c("FeO", "SO4-2", "H2O", "H+", "e-", "CO3-2")) basis("SO4-2", -6) @@ -22,16 +22,16 @@ # speciate CO3-2, HCO3-, CO2 as a function of pH bases <- c("SO4-2", "HSO4-", "HS-", "H2S") bases2 <- c("CO3-2", "HCO3-", "CO2") -# calculate affinities using the predominant basis species -# using blend=TRUE we get curvy lines, particularly at the boundaries with siderite -# compare with the plot in Garrels and Christ, 1965 -m1 <- mosaic(bases, bases2, blend = TRUE, pH = pH, Eh = Eh, T = T) +# calculate affinities using the relative abundances of different basis species +# (using default blend = TRUE) +# note curved lines, particularly at the boundaries with siderite +m1 <- mosaic(bases, bases2, pH = pH, Eh = Eh, T = T) # make a diagram and add water stability lines diagram(m1$A.species, lwd = 2) water.lines(m1$A.species, col = "seagreen", lwd = 1.5) # show lines for Fe(aq) = 10^-4 M species(c("Fe+2", "Fe+3"), -4) -m2 <- mosaic(bases, bases2, blend = TRUE, pH = pH, Eh = Eh, T = T) +m2 <- mosaic(bases, bases2, pH = pH, Eh = Eh, T = T) diagram(m2$A.species, add = TRUE, names = NULL) 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")) Modified: pkg/CHNOSZ/inst/NEWS =================================================================== --- pkg/CHNOSZ/inst/NEWS 2019-02-01 05:42:24 UTC (rev 378) +++ pkg/CHNOSZ/inst/NEWS 2019-02-02 11:54:46 UTC (rev 379) @@ -1,4 +1,4 @@ -CHANGES IN CHNOSZ 1.1.3-86 (2019-02-01) +CHANGES IN CHNOSZ 1.1.3-87 (2019-02-02) --------------------------------------- BUG FIXES @@ -15,10 +15,6 @@ NA where the density of H2O is less than 0.35 g/cm3, avoiding the output of bogus values in this region. Thanks to Evgeniy Bastrakov. -- In mosaic() with blend = TRUE, add a previously missing term for - Gibbs energy of mixing. An example using mosaic() to calculate the - pH-dependent solubility of calcite has been added to solubility.Rd. - - For systems where no basis species is present in all formation reactions, and the user hasn't provided balance coefficients, stop with an error instead of setting the balance cofficients to 1. @@ -78,6 +74,12 @@ - mosaic() has been rewritten to handle more than two changing groups of basis species. +- mosaic() gets a new argument 'mixing' (default TRUE), indicating + whether the Gibbs energy of ideal mixing should be included in the + calculations with blend = TRUE. As a test of this change, an example + using mosaic() to calculate the pH-dependent solubility of calcite + has been added to solubility.Rd. + DOCUMENTATION - Add demo/gold.R for calculations of Au solubility in hydrothermal Modified: pkg/CHNOSZ/man/mosaic.Rd =================================================================== --- pkg/CHNOSZ/man/mosaic.Rd 2019-02-01 05:42:24 UTC (rev 378) +++ pkg/CHNOSZ/man/mosaic.Rd 2019-02-02 11:54:46 UTC (rev 379) @@ -7,7 +7,7 @@ } \usage{ - mosaic(bases, bases2 = NULL, blend = FALSE, mixing = FALSE, ...) + mosaic(bases, bases2 = NULL, blend = TRUE, mixing = TRUE, ...) } \arguments{ @@ -20,24 +20,21 @@ \details{ -\code{mosaic} can be used to calculate the reaction affinities when the basis species listed in \code{bases} change in relative abundance over the range of conditions, due to e.g. ionization, complexation or redox reactions. -Chemical activity or predominance diagrams constructed by assembling sub-diagrams corresponding to the predominant basis species have sometimes been described as \dQuote{mosaic diagrams} in the literature. +\code{mosaic} can be used to calculate the affinities of formation of species when the relative abundances of basis species listed in \code{bases} changes over the range of conditions, due to e.g. ionization, complexation or redox reactions. This is a way to \dQuote{speciate the basis species}. For example, the speciation of sulfur (\samp{SO4-2}, \samp{HSO4-}, \samp{HS-} and \samp{H2S}) as a function of Eh and pH affects the formation affinities, and therefore relative stabilities of iron oxide and sulfide minerals. +Chemical activity diagrams constructed by assembling sub-diagrams corresponding to the predominant basis species can described as \dQuote{mosaic diagrams}. -The function calculates the affinities using each basis species listed in \code{bases} in turn, changing them via \code{\link{swap.basis}}. -The first species listed in \code{bases} should be in the current basis definition. +The function calculates the affinities using all combination of basis species given as vector arguments to \code{bases} and \code{bases2}. +The first species listed in each group should be in the current basis definition, and all the basis species in each group should be related to the first basis species there (i.e. all share the same element). +A second, independent set of basis species can be provided in \code{bases2} (for example \samp{CO3-2}, \samp{HCO3-}, \samp{CO2}, if the first set of basis species are the sulfur-bearing ones listed above). The arguments in \code{...} are passed to \code{affinity} to specify the conditions. -If \code{blend} is FALSE (the default), the function returns the affinities calculated using the single predominant basis species in \code{bases} at each condition. -If \code{blend} is TRUE, the function combines the affinities of the formation reactions in proportion to the relative abundances of the basis species at each condition. -Additionally, if \code{mixing} is TRUE, a term is included to account for the Gibbs energy of mixing. + +If \code{blend} is TRUE (the default), the function combines the affinities of the formation reactions in proportion to the relative abundances of the basis species at each condition. +Additionally, if \code{mixing} is TRUE (the default), a term is included to account for the Gibbs energy of ideal mixing. See the second example in \code{\link{solubility}} for a numerical test of the calculations using \code{blend} and \code{mixing}. +If \code{blend} is FALSE, the function returns the affinities calculated using the single predominant basis species in \code{bases} at each condition (in this case, the \code{mixing} argument has no effect). -The basis species listed in \code{bases} should all be related to the first basis species there (i.e. all share the same element). -A second, independent set of basis species can be provided in \code{bases2} (for example \samp{CO3-2}, \samp{HCO3-}, \samp{CO2}, if the first set of basis species are the sulfur-bearing ones listed above). -The function then works recursively, by calling itself instead of \code{affinity}, so that the inner loop changes the basis species in \code{bases2}. -In this way, all possible combinations of the two sets of basis species are used in the calculation. - A more flexible method of specifying multiple sets of basis species is now available. Instead of using \code{bases} and \code{bases2}, supply a list for just the \code{bases} argument. The list should contain any number of vectors specifying the groups of basis species. @@ -48,19 +45,19 @@ \value{ A list containing \code{A.species} (affinities of formation of the species with changing basis species) and \code{A.bases} (affinities of formation of the basis species in terms of the first basis species), each having same structure as the list returned by \code{\link{affinity}}. -If \code{bases2} is provided, the list also contains \code{A.bases2} (affinities of formation of the second set of basis species, in terms of the first one in that set). +If \code{bases2} is provided, the list also contains \code{A.bases2} (affinities of formation of the second set of basis species). } \seealso{ -\code{demo("mosaic")}, extending the example below by addition of carbonate species in \code{bases2}, with \code{blend} set to TRUE, and using thermodynamic data from Garrels and Christ, 1965. +\code{demo("mosaic")}, extending the example below by addition of carbonate species in \code{bases2}, and using thermodynamic data from Garrels and Christ, 1965. } \examples{ \dontshow{data(thermo)}# Fe-minerals and aqueous species in Fe-S-O-H system # speciate SO4-2, HSO4-, HS-, H2S as a function of Eh and pH # after Garrels and Christ, 1965 Figure 7.20 -pH <- c(0, 14, 200) -Eh <- c(-1, 1, 200) +pH <- c(0, 14, 500) +Eh <- c(-1, 1, 500) T <- 25 basis(c("FeO", "SO4-2", "H2O", "H+", "e-")) basis("SO4-2", -6) @@ -68,15 +65,17 @@ species(c("pyrrhotite", "pyrite", "hematite", "magnetite")) # the basis species we'll swap through bases <- c("SO4-2", "HSO4-", "HS-", "H2S") -# calculate affinities using the predominant basis species -m1 <- mosaic(bases, pH=pH, Eh=Eh, T=T) +# calculate affinities using the relative abundances of the basis species +# NOTE: set blend = FALSE for sharp transitions between the basis species +# (looks more like the diagram in GC65) +m1 <- mosaic(bases, pH = pH, Eh = Eh, T = T) # make a diagram and add water stability lines -d <- diagram(m1$A.species, lwd=2) -water.lines(d, col="seagreen", lwd=1.5) +d <- diagram(m1$A.species, lwd = 2) +water.lines(d, col = "seagreen", lwd = 1.5) # show lines for Fe(aq) = 10^-4 M species(c("Fe+2", "Fe+3"), -4) -m2 <- mosaic(bases, pH=pH, Eh=Eh, T=T) -diagram(m2$A.species, add=TRUE, names=NULL) +m2 <- mosaic(bases, pH = pH, Eh = Eh, T = T) +diagram(m2$A.species, add = TRUE, names = NULL) title(main=paste("Iron oxides and sulfides in water, log(total S) = -6", "After Garrels and Christ, 1965", sep="\n")) # we could overlay the basis species predominance fields Modified: pkg/CHNOSZ/man/solubility.Rd =================================================================== --- pkg/CHNOSZ/man/solubility.Rd 2019-02-01 05:42:24 UTC (rev 378) +++ pkg/CHNOSZ/man/solubility.Rd 2019-02-02 11:54:46 UTC (rev 379) @@ -121,7 +121,7 @@ ## method 2: CO2 and carbonate species as basis species basis(c("calcite", "CO2", "H2O", "O2", "H+")) species(c("Ca+2")) -m <- mosaic(c("CO2", "HCO3-", "CO3-2"), pH = c(3, 14), blend = TRUE, mixing = TRUE) +m <- mosaic(c("CO2", "HCO3-", "CO3-2"), pH = c(3, 14)) sm0 <- solubility(m) smI <- solubility(m, find.IS = TRUE) ## plot the results Modified: pkg/CHNOSZ/tests/testthat/test-mosaic.R =================================================================== --- pkg/CHNOSZ/tests/testthat/test-mosaic.R 2019-02-01 05:42:24 UTC (rev 378) +++ pkg/CHNOSZ/tests/testthat/test-mosaic.R 2019-02-02 11:54:46 UTC (rev 379) @@ -6,18 +6,18 @@ a25 <- affinity() # this is a degenerate case because we only allow NH3 to swap for NH3, and CO2 for CO2; # however it still exercises the affinity scaling and summing code - m1_25 <- mosaic("NH3", "CO2", blend=TRUE) + m1_25 <- mosaic("NH3", "CO2") # this failed before we divided by loga.tot to get _relative_ abundances of basis species in mosaic.R expect_equal(a25$values, m1_25$A.species$values) # the next call failed when which.pmax(), called by diagram(), choked on a list of length one - m2_25 <- mosaic("NH3", "CO2") + m2_25 <- mosaic("NH3", "CO2", blend = FALSE) expect_equal(a25$values, m2_25$A.species$values) # make sure the function works when all affinities are NA a500 <- affinity(T=500) # using blend=TRUE was failing prior to version 1.1.3-37 - m1_500 <- mosaic("NH3", "CO2", blend=TRUE, T=500) + m1_500 <- mosaic("NH3", "CO2", T=500) expect_equal(a500$values, m1_500$A.species$values) - m2_500 <- mosaic("NH3", "CO2", T=500) + m2_500 <- mosaic("NH3", "CO2", blend = FALSE, T=500) expect_equal(a500$values, m2_500$A.species$values) }) @@ -34,9 +34,9 @@ bases <- c("SO4-2", "HSO4-", "HS-", "H2S") # calculate affinities using the predominant basis species pH <- c(0, 14, 29) - m1 <- mosaic(bases, pH = pH) + m1 <- mosaic(bases, pH = pH, blend = FALSE) # calculate affinities with smooth transitions between basis species, including a mixing energy - m2 <- mosaic(bases, pH = pH, blend = TRUE, mixing = TRUE) + m2 <- mosaic(bases, pH = pH) # these species have no S so the results should be similar, # 20190121 except for a negative free energy of mixing (positive affinity) expect_true(all(m2$A.species$values[[1]] - m1$A.species$values[[1]] > 0)) @@ -44,8 +44,8 @@ expect_equal(unique(sign(diff(as.numeric(m2$A.species$values[[1]] - m1$A.species$values[[1]])))), c(1, -1)) # now with S-bearing species ... species(c("pyrrhotite", "pyrite")) - m3 <- mosaic(bases, pH=pH) - m4 <- mosaic(bases, pH=pH, blend=TRUE) + m3 <- mosaic(bases, pH = pH, blend = FALSE) + m4 <- mosaic(bases, pH = pH) # the results are different ... expect_equal(sapply(m3$A.species$values, "[", 13), sapply(m4$A.species$values, "[", 13), tol=1e-1) # but more similar at extreme pH values Modified: pkg/CHNOSZ/vignettes/mklinks.sh =================================================================== --- pkg/CHNOSZ/vignettes/mklinks.sh 2019-02-01 05:42:24 UTC (rev 378) +++ pkg/CHNOSZ/vignettes/mklinks.sh 2019-02-02 11:54:46 UTC (rev 379) @@ -6,7 +6,7 @@ # set background-image:none to remove underlines (from bootstrap theme) sed -i 's/?`CHNOSZ-package`<\/code>/?`CHNOSZ-package`<\/a><\/code>/g' anintro.html sed -i 's/?basis<\/code>/?basis<\/a><\/code>/g' anintro.html -sed -i 's/?mosaic<\/code>/?mosaic<\/a><\/code>/g' anintro.html +sed -i 's/?mosaic<\/code>/?mosaic<\/a><\/code>/g' anintro.html sed -i 's/?buffer<\/code>/?buffer<\/a><\/code>/g' anintro.html sed -i 's/?solubility<\/code>/?solubility<\/a><\/code>/g' anintro.html sed -i 's/?ionize.aa<\/code>/?ionize.aa<\/a><\/code>/g' anintro.html From noreply at r-forge.r-project.org Sun Feb 3 04:23:57 2019 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Sun, 3 Feb 2019 04:23:57 +0100 (CET) Subject: [CHNOSZ-commits] r380 - in pkg/CHNOSZ: . R vignettes Message-ID: <20190203032357.EDAE118C1C0@r-forge.r-project.org> Author: jedick Date: 2019-02-03 04:23:56 +0100 (Sun, 03 Feb 2019) New Revision: 380 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/R/util.affinity.R pkg/CHNOSZ/vignettes/anintro.Rmd Log: anintro.Rmd: fix to energy() for mosaic diagram with chalcocite (phase transitions) Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-02 11:54:46 UTC (rev 379) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-03 03:23:56 UTC (rev 380) @@ -1,6 +1,6 @@ -Date: 2019-02-02 +Date: 2019-02-03 Package: CHNOSZ -Version: 1.1.3-87 +Version: 1.1.3-88 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/R/util.affinity.R =================================================================== --- pkg/CHNOSZ/R/util.affinity.R 2019-02-02 11:54:46 UTC (rev 379) +++ pkg/CHNOSZ/R/util.affinity.R 2019-02-03 03:23:56 UTC (rev 380) @@ -147,7 +147,13 @@ if("P" %in% vars) P <- vals[[which(vars=="P")]] if("IS" %in% vars) IS <- vals[[which(vars=="IS")]] s.args <- list(species=species,property=property,T=T,P=P,IS=IS,grid=grid,convert=FALSE,exceed.Ttr=exceed.Ttr,exceed.rhomin=exceed.rhomin) - return(do.call("subcrt",s.args)) + sout <- do.call("subcrt",s.args) + # species indices are updated by subcrt() for minerals with phase transitions + # e.g. i <- info("chalcocite"); subcrt(i, T=200)$species$ispecies == i + 1 + # so we should keep the original species index to be able to find the species in a provided 'sout' + # (noted for Mosaic diagram section of anintro.Rmd 20190203) + sout$species$ispecies <- species + return(sout) } } Modified: pkg/CHNOSZ/vignettes/anintro.Rmd =================================================================== --- pkg/CHNOSZ/vignettes/anintro.Rmd 2019-02-02 11:54:46 UTC (rev 379) +++ pkg/CHNOSZ/vignettes/anintro.Rmd 2019-02-03 03:23:56 UTC (rev 380) @@ -687,22 +687,22 @@ 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. -We turn off the gray coloring beyond the water stability limits (`limit.water`) but plot the red dotted lines using `water.lines()`: +We turn off the gray coloring beyond the water stability limits (`limit.water`) but plot dashed blue lines using `water.lines()`: ```{r copper_mosaic, fig.margin=TRUE, fig.width=4, fig.height=4, 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 <- 300 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) +m1 <- mosaic(bases, pH = c(0, 12, res), Eh=c(-1.2, 0.75, res), T=T) diagram(m1$A.species, lwd = 2, fill = NA, limit.water = FALSE) diagram(m1$A.bases, add = TRUE, col = "red1", col.names = "red1", lty = 3, limit.water = FALSE, italic = TRUE) water.lines(m1$A.species, col = "blue1") ``` -The argument `blend = TRUE` is used to combine the diagrams according to the relative abundances of the basis species along with a mixing term (see `?mosaic`). +The diagrams are combined according to the relative abundances of the different possible basis species listed in `bases` along with a term for the Gibbs energy of mixing (see `?mosaic`). The smooth transitions between basis species can result in curved field boundaries, in this case around the chalcocite field. -Without that argument, the diagrams would be combined using the dominant basis species, and all of the line segments would be straight. +If we added the argument `blend = FALSE`, the diagrams would instead be assembled using the single predominant basis species at any point on the Eh-pH grid, and all of the line segments would be straight. The reactions used to make this diagram are balanced on Cu, so that no Cu appears in reactions between any two other species (minerals or aqueous species). If `diagram()` is run with `balance = 1`, then the reactions are written for one mole of the mineral formulas on each side of the reaction, with the possibility of Cu appearing as an additional species to conserve the elements. @@ -720,7 +720,7 @@ mosaicfun <- function(newvar, T = 200) { swap.basis("e-", names(newvar)) if (names(newvar) == "O2") basis("O2", "gas") - mosaicargs <- c(list(bases), blend=TRUE, pH=list(c(-2, 12, res)), newvar, T=T) + mosaicargs <- c(list(bases), pH = list(c(-2, 12, res)), newvar, T = T) m1 <- do.call(mosaic, mosaicargs) diagram(m1$A.species, lwd = 2, fill = "terrain", limit.water = FALSE) From noreply at r-forge.r-project.org Wed Feb 6 07:35:10 2019 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Wed, 6 Feb 2019 07:35:10 +0100 (CET) Subject: [CHNOSZ-commits] r381 - in pkg/CHNOSZ: . data inst inst/extdata/OBIGT inst/extdata/thermo man man/macros tests/testthat Message-ID: <20190206063510.70D8418BD6B@r-forge.r-project.org> Author: jedick Date: 2019-02-06 07:35:06 +0100 (Wed, 06 Feb 2019) New Revision: 381 Added: pkg/CHNOSZ/inst/extdata/thermo/SK95.csv pkg/CHNOSZ/tests/testthat/test-recalculate.R Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/data/refs.csv pkg/CHNOSZ/inst/NEWS pkg/CHNOSZ/inst/extdata/OBIGT/organic_aq.csv.xz pkg/CHNOSZ/man/extdata.Rd pkg/CHNOSZ/man/macros/macros.Rd Log: add test of recalculated GHS of alanate and glycinate complexes Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-03 03:23:56 UTC (rev 380) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-06 06:35:06 UTC (rev 381) @@ -1,6 +1,6 @@ -Date: 2019-02-03 +Date: 2019-02-06 Package: CHNOSZ -Version: 1.1.3-88 +Version: 1.1.3-89 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/data/refs.csv =================================================================== --- pkg/CHNOSZ/data/refs.csv 2019-02-03 03:23:56 UTC (rev 380) +++ pkg/CHNOSZ/data/refs.csv 2019-02-06 06:35:06 UTC (rev 381) @@ -56,10 +56,11 @@ PK95,"V. B. Parker and I. L. Khodakovskii",1995,"J. Phys. Chem. Ref. Data 24, 1699-1745",melanterite,https://doi.org/10.1063/1.555964 RH95,"R. A. Robie and B. S. Hemingway",1995,"U. S. Geological Survey Bull. 2131","gypsum GHS",http://pubs.er.usgs.gov/publication/b2131 SK95,"E. L. Shock and C. M. Koretsky",1995,"Geochim. Cosmochim. Acta 59, 1497-1532","metal-organic acid complexes",https://doi.org/10.1016/0016-7037(95)00058-8 -SK95.1,"E. L. Shock and C. M. Koretsky",1995,"Geochim. Cosmochim. Acta 59, 1497-1532","alanate, glycinate and their complexes not included in later slop files.",https://doi.org/10.1016/0016-7037(95)00058-8 +SK95.1,"E. L. Shock and C. M. Koretsky",1995,"Geochim. Cosmochim. Acta 59, 1497-1532","alanate, glycinate and their complexes with metals. Values are taken from slop98.dat, which notes corrected values for some species.",https://doi.org/10.1016/0016-7037(95)00058-8 Sho95,"E. L. Shock",1995,"Am. J. Sci. 295, 496-580","carboxylic acids",https://doi.org/10.2475/ajs.295.5.496 DPS+96,"I. Diakonov, G. Pokrovski et al.",1996,"Geochim. Cosmochim. Acta 60, 197-211",NaAl(OH)4,http://dx.doi.org/10.1016/0016-7037(95)00403-3 AH97b,"J. P. Amend and H. C. Helgeson",1997,"J. Chem. Soc., Faraday Trans. 93, 1927-1941","amino acids GHS",https://doi.org/10.1039/A608126F +AH97b.1,"J. P. Amend and H. C. Helgeson",1997,"J. Chem. Soc., Faraday Trans. 93, 1927-1941","alanate and glycinate GHS",https://doi.org/10.1039/A608126F DSM+97,"J. D. Dale, E. L. Shock et al.",1997,"Geochim. Cosmochim. Acta 61, 4017-4024",alkylphenols,https://doi.org/10.1016/S0016-7037(97)00212-3 DSM+97.1,"J. D. Dale, E. L. Shock et al.",1997,"Geochim. Cosmochim. Acta 61, 4017-4024","phenol, and cresol isomers",https://doi.org/10.1016/S0016-7037(97)00212-3 DSM+97.2,"J. D. Dale, E. L. Shock et al.",1997,"Geochim. Cosmochim. Acta 61, 4017-4024","dimethylphenol isomers",https://doi.org/10.1016/S0016-7037(97)00212-3 @@ -162,8 +163,7 @@ ZZL+16.2,"K. Zimmer et al.",2016,"Comp. Geosci. 90, 97-111","Cp parameters listed in spronsbl.dat",https://doi.org/10.1016/j.cageo.2016.02.013 ZZL+16.3,"K. Zimmer et al.",2016,"Comp. Geosci. 90, 97-111","dawsonite GHS",https://doi.org/10.1016/j.cageo.2016.02.013 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 -CHNOSZ.2,"J. M. Dick",2017,"CHNOSZ package documentation","alanate and glycinate: GHS as used by @DLH06",http://chnosz.net -CHNOSZ.3,"J. M. Dick",2017,"CHNOSZ package documentation","metal-amino acid complexes: GHS were recalculated by adding the differences between values from @AH97b and @DLH06 for alanate or glycinate to the properties of the complexes reported by @SK95.",http://chnosz.net +CHNOSZ.3,"J. M. Dick",2017,"CHNOSZ package documentation","metal-amino acid complexes: GHS were recalculated by adding the differences between values from @SK95 and @AH97b for alanate or glycinate to the properties of the complexes reported by @SK95.",http://chnosz.net CHNOSZ.5,"J. M. Dick",2017,"CHNOSZ package documentation","AuCl4- renamed to AuCl4-3",http://chnosz.net CHNOSZ.6,"J. M. Dick",2017,"CHNOSZ package documentation","dipeptides not included in slop files after slop98.dat",http://chnosz.net CHNOSZ.7,"J. M. Dick",2017,"CHNOSZ package documentation","charge of NpO2(Oxal), La(Succ)+, NH4(Succ)-, and NpO2(Succ) as listed by @PSK99",http://chnosz.net Modified: pkg/CHNOSZ/inst/NEWS =================================================================== --- pkg/CHNOSZ/inst/NEWS 2019-02-03 03:23:56 UTC (rev 380) +++ pkg/CHNOSZ/inst/NEWS 2019-02-06 06:35:06 UTC (rev 381) @@ -1,4 +1,4 @@ -CHANGES IN CHNOSZ 1.1.3-87 (2019-02-02) +CHANGES IN CHNOSZ 1.1.3-89 (2019-02-06) --------------------------------------- BUG FIXES @@ -163,6 +163,9 @@ - Move SUPCRTBL updates into default database. +- Add test-recalculate.R to check that some recalculated values are + correctly entered in OBIGT. + DIAGRAMS - Lines in 1-D diagram()s can optionally be drawn as splines using the Modified: pkg/CHNOSZ/inst/extdata/OBIGT/organic_aq.csv.xz =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/organic_aq.csv.xz 2019-02-03 03:23:56 UTC (rev 380) +++ pkg/CHNOSZ/inst/extdata/OBIGT/organic_aq.csv.xz 2019-02-06 06:35:06 UTC (rev 381) @@ -1,4 +1,4 @@ -?7zXZ???F!t/????Pq?]7I??b???9??????TB;q?"?q???cL;?"??? x!#???0N???????? ?V?q??P?@o?*?~ ??!?~?&??????x?{;??Q(T?{????~W??U?@?? r?&?3??f1(\F?^??=WOL_?????6d? 7a -?#?M?????.'$l?I?P?_?0?l??2?$K?j?j??>??=2?pr?K?8{?Vy?HWD%??.hL????????xc?~????????]?????NK?????5g?Z`?)?W?QCv?7/????`?@????B??n8???c??<0V????????????????x???m???j??h -??<,?h?fK?[??E?>??2F??yU?]Y??W-??WR??q?uEy?;q????+??z?%W?Ht?*?????F{??tlK??L??e?a?)v?F`dvq(??W?l7E??h?J[+?E???v??9?? -?;7?4??TX?Q??*?_A8?x??????w?A???Y?x9????)?4????nM?????F?;?O????C?I?x\=E?/R{/?,?????W?Q?'F=??210B?g? ??h?;?%???Sl?E???}?(?F]V? -??j???>??? ?nf????sY??v?3????*?:? ??L???]?r6XC?z???*?b9-BH[????;?O ????&d?2??~-w?J"??6????(?Q??vs/D???{$?%??????][?????Y???b??Lt+??C??Kj9?]d?O????va'E??z???#!^????????mv? ??y??T_???????R?}M|?Jz?Y?????d??Bi??A?fy q????.?J?nMu??L?L?"?????4?G??k??t?c&???b?5?F??g?.HB?????x6N??wn?x????"????LO???M?6??Jux+?b?-??/-??_???U?5$'???4???|??XU??6?YN????G ? -Afuv?#x??x??32?)X@?io?^???A????P??d??????? -?1??AoB?vEf[ax???? -?%?????|?|RhT??_?&?y?y?Yy?'?)>?E]M?W? -A??K??ku(i7 ???5?bp?????] -?r??pQ0??`k????z ??????Z`ZV??? ->b??&T-???K? ??Z?H`??(-u??Ckb3???? P&?L???"f?4??d&6?&?7=?Z??]??s?l%??Y?X8 ?Au)?Q???8?N#:?????#?qe????????/O?G???{=? >6z~l?9?^???????L????????y?????N0?[??m;K??Rf0?8#=3^n????????+?eW#?-CYb?{\k?-?S??pT?V?g??!?i??Y-?&nm??????? ?*>j^???u?2R{??{^B5@?,(j????? ? b????%???????R????[?#?p9G@?????L??Jq4k??T??a??9K????H\?m?I?)L!?j?>{??M,+??,?'?%$??E`/?aW??w??????'k?":???(??w?9????W??Y;?7?;|$l??C????(?_?3?[%??y]???\8J??nA?R?p9 ? -W?;?i -{@?x/??[???L?5??v?HT????yPa????m?%e??V????d$_N????a;?M0?[$???P+<-?????A9g} C?n?"???'??1C????/Z?{/?)????3??Y?n?.r?C??y?_h"??%h?|???lk?Y???"?8?R *??????~r$?K????t0l?^???Z??k?xb???PuF?t?????ZU?+b?w?(??HB4?ASO????[???G???.??????%??5????%B?Pq???K)??7??Ey?b? v???m??j??m???E???;W??*q????A?I?"?ir?????E?Y???????N??Z???|o????B]t?~E[?? m? -?Z{????l?i2 I????;SyAi}2??n??k~???~'??8'*?)??H? ?X?2?. -6?Gz??%{??{????u?#?U???GB?L???/)?J???w??,?????/8E\??]`?-???Q#??k=x?g;????/?$??q????????#v???A&?I2?g?u????{??V;???O?}P????Y???6??Pp`?J???T+?????U?}??O ?Nsh?Z??????(?H9i?'?ed|??Q(?a at k?SD??eB???P6[Y? ?x^Q?F??Pe???????w????n?p??;vR??@?????J.)?????/?9R?~?P???s????#??P>~-=? -????????T?p?`?q?????,???&3?M?r{>???. ,?N?N$? :?q??@?y??pu?FJ=(?#M??J4C??F??????3??m??d??Jh??wky???.?e?????X3u???7???? -?$\?AE?0<??1??????6???%??Y???????C?B??R????M?%?Dx,?>??^??%?u??6w?n???i????? ?,?????J?@aB(~??*.?bA?+?N?????????m?iJ?U????????W[?o????b0?d??b??b??A5?;?Soh??l?????z??d?C?????? h?^?>?p??????`?dU?>??4???|???%-??r?i??K???Q?=?O -?????m2?o??n??,5??1 -???[+??O??)??????t??,?/?{p??n??\???xH????#?(wO??Z?????V[|????Q?E?1??l(r?v?-??6"????w?????C -??Pr6d?I???RF?OdU?Fj??????&;???jp9?,???\mz???F\;?? U{???N?????er?rK?Fp?????S??zM?U5Ct?\???}?-??_?'~D?< -| ?9B?a?H??%o ?b????B???y??MFo?a??????x}?|q?(w???:H"X???,G??*?&??7D??T???Se???? ?*%Ae??~*?W??????On??? -V"???a??5??:??? _?o?????J^?lw?eT??D|??,??? -?;?a??|Cx???M????w"???B??B??&?-W?36o??:G/h?&?OR?lS??????O?????.?1?|?RmF`????????b???+F??X???b????B???????x???c??Q?>W??+?Q??|/???55 -|$YT?1.yM????Z= g??8????l???????????&??ZD-????I???g??+???hd???v??t?>??G???NJ -?O??"?Rc{??w=???v?F?V??? ?i??cFC?? -?d?SKm??VH?eJB -??????????K????U??'2??P ?Cyb???t????rC4?? >22??h;?????B?&?F??y?(h`?X >??????9m?!?????I.??P}{d??D`:?ji? -????!?@??J)?8_,?%? ???w??7I\M(Y????e?e??? -s?j?s |?????)n??# $??~??6,?Fw3A??5??=???Y?#e??j?q??@ ?y? ?^y?H?? ?G9^V??s?????"H|v??????=1|x/???zY5u[??V?????9':?_:???A??`W?????Z18r?Dd/b?`????J??? -????(>Z?????>#d?????(}?d???T?6w???$???=??\???e????b?lP"???X?L?!?. ???? ?y?hQ?E???????H??? -#f8%"M??4??(????_?u???4Z?J?????????sMb?????q=??'??1K$???z1?!???1>?+o? -???r -c O?????A? ^v??C^[???5?c??ZP.@??=?%12+wmfT????kI????'??I//????4?l.)?Y1NFl?-S'???;/=?g???(?5??W??$77K+?5??+X_??y?L??y???s)??w???????'AL"D??????\:??????G?m???;?]?/???0F?f??vvT???vd?<`??x??$?????\? ?7??l?x?U ?t??!??l{x?@?HZ? ??? Lq?"??VF?? ??dC???????i??o??}bB?8fs??(d??i??s ?Ch{r>??3H??R???G?%????J???qm??qMy?y??????;??=+'r?/??}lxq?P? Q?!A???&???"n?\o?G\??[(??gU?V??o?????? -?*???U?59???:?B???@??nm????+rI?c???? -??3???v??ni&9Qv???;?z1??M'XG?? %?3?5????6?-????i?h?F~???1^?B?@{???? (???3].I'A???g?]{>?pD?Z??7??)J.@???;?V?Z~t6Vw(X??.1????$z????u-?????I;tQ>????????????Xv???`?3is??@?.-`%8?.Nn???O???Lk???[/`i?????FG??????????@?????"*Y|??.???\X????%??N?Mw??????{Y!???"? -? -?`???{Q"'g?P)??f?>?J^?\?]?*QoI?y?l$?| -?S??eE?!?ow?z ??p"iu+?c???5cC?@??,E6???c$????r?-0v?A6?"b?-IG?.??@???R3???Z?^??c?z??&??j????OT?r??iNz ZD?#????5????4? p?u??"???Y??N}????i??'8?@????Y-#+I??K?n ???i?u?"????????????b??iKe?>?ywrBy?Mq??b???6??T????????St>}?(??P'??$?;X?Z,xd?z?[? ??1??iM?-??%??2?W????o??Q?Nu?H????R? n????c?N???q=&=??a??k$)E ??????r??r?Z???I?X`L ???Z??"e?q???u?&?y??2???=???u?X?6???n?g?+?????82???`P@?????Q4b0* ?????????????4??2?4i?C????:?????-?Z~??9 ? -z??RH????_?????uFA&??N??1???)*d??: U???Yg????[?????$k/e)0?????6M*????~'??P?????z?g]Z?1??0? -(o???-???k??h}?a?[4jh????(1ltv ?e+[ -???2 ?g??.??9????l?B??S?????????:8N?A -?v?,F3V???|W?????Y?fT??p????za`?(??0???????7"???~?????^?l ?L???"{??6???????34[?"?E`???b ?z?0???? ???27Y?-qi???}??????lCVl??b?B?+T????{1F??-??g?fTvkE}I4????P?\4Y???? ?l ?Pf`&?y?G??? ??N??2%'LxM????D,???{/???9$??z2w?{2??$?????q?a?J???6?v??-2???.'??3?s[??????Q??}l???G??ON??Ut:??&HKk?F qy????????H?R??D??? K,??? ?!???F????l_???????:3??m????y??F?^??$4?p???n5L?????F??@xR?I????? -?@????h?IM??N?3f???!-?/??????}S????Jj?(??O?b??|??@?cs????J?1? -???jy@??G???Z??????.r?? ???wl?j??Fl?v???i???o -??v??$Yg?P??L?Pj???Req~?I??2??????g??1?&?aW"P -(?c????TH? ^??e?t?aW???Y??X???G??? ??8?e{l?=@???d??? ????b?M+#?s9! ??7*/{???{H?>1?-???-??&F ?u?K?p???r?3?F`?????????* -Y??o#?R?%HH?D?ut???E?????9???5?F??+c?NN|)?V???????g??????????$?t?>? ????)?.?y???M?D_???g??$?6?&????Guo???2?? ?:]% ??G?_I??Z2???'?bv??????f??|^z?=?[9?"???? 4???B??&]0 -??]??????5???D?H??Q0[?L????bV???-??_?????????+o??hN 4@??w?#???Ph,?h?@? ? ?????y]/??s?m?J?????H???g?t?U?5? -????U;O{??????1\?? -???v=?9???6??=?H??+?????\??*?;4[?=??????y?????v?+?K??CsV7&??@???~??2\????O?,h?cB?Y?U??BY????;?l??v:xYoM?x{??`' -;??{p{??w?V????\?eo??QE5??????tc???Tt6y??e?D?F?????a??p?]?$?r???????f??>,A????X/F%?s?????L????n???"^??i??Lr???9??Q??????/?s?/?t?^g[??K??{F?J???y??k????m????&??g?M^q -?+,a??IB???A??JoH??q???J?r??;1?])d+c???I?V14%*?3 -?D?;m+???????????oHVfW%??z????U?u????1??????Eo????Y?p?wK(???H?????? -7 -/?D?fh? |^?#E???D?F??$??Xp?$2?6???@?[?>?O? ?"?~*??@?S?1?J?8?H -??6 ?&|?6 -??i?Z??m??:T(????7?h??[|??x0Gb?t????7?(2b?4g??????9?????"???2?t#D?%??t ?^?n -?2v???{?O ???????d]?V??L{?5F8}????"?%?????:?,??i%?jIJ??@????@$?v7?nj??????????VkwiO.??????4%???|8?&a???^@?w?yu^%??? -> ?Y0 -?{K???p?o???u?7,B?:??=?a4??/??s.??I?Y=????q?tG?^CYN??? -?C?=??vJ???5_E?Z?????@?.??G84i?ah?ce?]???D^?-?b??EZs??????R'??=?????'?????kP>K?N?QG?????X??(??(??V????e<???omqs?6;? ??`?n??Jp}??? -=saA4i -`2 8;*??3V]P????|?E?5[????]MZa???L? wB???G+???????G?_n??????k??/? h8????MtT??? ??????+????e??k?z?h>????d pg?S?X?L?}??k?R???O????x??sq*?o?h1Gc??{Ortp?%????w??t??O?s??????M???????j>?2???7???? ??C?? sM?5?yH??\???QA#T??_x???: -p?? -aL?@????(e????^u??+?l???a?:?O$4???Y?F3\B??}?z?^v?;?6?4???u~lm?a??8??P???)??7e$?Lq?L??X?"??5?+??@h?j???[?U??Q?jAGpM?.??aR9?W?l??&l?302i ?W?????1??y????o??g???? -?a??n?,??r&Los?)?5???0s????0? -p? -t?4????c????????'/? ?.?B$r?&??? -0 }?Eb?3??z$lyg?c?nCl??1=??#[Y?j???)? -?6?PQ?????o??O ???|e??>?b?7?[a??q?.????????m?slw??????[`Mn.6???ZE(?Q2???J#?~?????!t???? ?4y?e/D??Q?ta????;,?X??=2?pr?K?8{?Vy?HWD%??.a???;-V? ???0???}??]<{?I)x?8?l?B*?L?`?5?????`???Kq????6esz?? ??ZW????G(?Y?nL?7?Pno? +i O????v;????0??y~?q?Pm?2?? ?)???!?r??:iO????$??(-\?!??3]?C?{??`?Pl^???y?$??(S??M?? ??????L +????4?sxb?} $????Y?a?????^???^L~????fLp?S??Qp?u??>?????"\?t?4?E???5? 4=|?e??$?+????? +*?????O0??P? k{S?`9?U?.??YOE?^?3?F?D?'???%a??Pk8pO?+D?K????m??~*???~&Y??:z{2L}Il?*???vq??"n +?zT????:*2N?"4??R???7p???i??]c?I?GK,(Hr???????[?z?????????L??r?????{:?h?????? ?h>p?K?p.e??,?/%?????????.m???4???12PU~????????l?C?-n, N?????N????AU???U????"???????9?S"???R>?^J+6?tdr??I??V??Q????(j1f?A??j??A?????????r???5?}v??zi[}Ti??????%?s??T?3?Ep?DDW r???????*????Jq??$??}??@?y at i?Z?kG?bgm|??OV{X?{? ??????`c91??/) +?/ +?]?$??N??q? +??oE????e!Z?x{?:*?#9?|? 3?? +?}?{T?34?R?">??nb ??S??????'u`/0?{2????? ??~?K A +????ext???R5??l?LLV???E|??.?^]{?C%???r]?????~???X?44m?W*??S?d?dk/Ir?5????= +fW??(?u?????OK??d+? I?2K??w?|????????$ +???l@??X?@???>"?NrO?y2?e+??\<^} ?l9gd??@??z??? +??Eo?? ?? +?????9?C??u???[?"x??O?PZ????}S"?/????Y???b??BKZhK????[????*_e????#??{f?z??N??~9?? ??}[?>??[??]????????B~????P?j"c??0SRPg???o????~?p???#??)[???&??J+ +X???lt???b ??Y ?ZPV?p??+??l???=#V?WIrVa????/???{y ??X]??+??Ezc?T??e??????? +?&s?GG?V&1?p??p?i?{%???~?H??='?AalE????4??CEd7???????????4k/``}.U?pT???_k?w?Z????!??z*$?+x?.!?*???/?]?:??!???,??? ???)V??????????jq?|]???oi?u?O:K??qXl?\"Hl???t??v1???Ha???UJ4M?MDm????m?N!?N +p??wo%4 +F?K?GUH%?q?R???xi???4????????(i" +?R\?????4i?N.??"?\?????:?g????}?N??v?A???=?j`?5?}?/o?O?1U_??."???dCF????&??:z?/?? ? +??X???F??3i +???????sG??O??&=?K{?r ,RX?v?8Z?&L1???%.S?U?*6?F?]Jn?R{??J.?*??m???N??/???H??8 .???81?,4T???f?:??j???"??JZ?G?X??hm?|?X!:??&?}I??V???(6U???>*??,?w??gJ??'I +???????]?(| ?V??C??j19???[???;,?Q???Y8?? ????????1&X[Q?4???????????N???^?K=?? ??drS?ur`??????????_??qm?? s2 ???!G?2?Z?cU ????)?:,???Y?????1??C??k|??hlS???????S?_??\?{Dq??v????K2?s?H|?????0????^mj??"??N?2}??(?q???|??p??4v_A?]A?'?r^DX???s?l????G???$g?? +?????? ??Di?."??I?k?_??`???,?!^\Q?r?V????&8r???r??A?#?????5??F]??z?+ ?S3?C???)?(h8?(s(?Fu??$??B?????gc5??V??N?1: ]??1!?gi???W?x?w?I?}U?7????CdW?k8?}?$?>?????,?`??[??j(?]?.??j???5?9z??{?????&H??x?acu?:?????t?}?&O)??h??x?;G?Mo???c??Q?2I?%? ?pE~?????1?$??OF?O????Oc??gs?F?*??9???.?2?????? ?`1?G.?&??E??d?@( +o@??*-???????1v!?dz?w??a??m???D9??n?%x??PB?????$T?%a3?? ?)ZL?xp>????l?q[????k????? ?O>????o???\?LA???r{aw?5$H??,?n)???Fk?S?_??Fm?t??1?n?????_?F?*E?{\?IU?M 3? ?U? ?Y;??g???l/?>U??(_P6i??Y ??7Y??M~??a?P?'??Bo? ?p4???8???lNIfy?@??Y?j?t= +/#6w???????r8T?%X?????c??]?W?A?t?wE?bVU)???????~s??bu??5?"7!????0?????p]???B??F?5>T??b"?j??7? +H??O??7??z= n?&?E????????\E???! +Y:h?p?#e??8??= p?p??R?&w?MY??)??K98x??J??s?O?HP??Ya???@?9?B??M?+??9?h?=??k?e????Bn}??????O8??+?dU?-d???O??a'zvN-??? ????g8??? ???T?}4^?|?Q?/??r??.g?+F???!#%{W8?b???RS?q????y??X????v6T????lD?\???{??~3?y???v? +_?!tR?x??????/CI?%?c(s???H???r??G??%0j??????o??&B?????H?D?hW?O??L???8W-?{??]?W????bHCO?%?J? ?B?(?Rb???9/!???[?7???W?p??????T?vK?$?W?m??3??_??m?????????'@V?3??J?oF ,???????q??@?B2.??V,0?|!?k?A?????n?4?ToE???u^?K?h?0?/?????$ ?P? v??h??Jd?`??u%??r?}Jn??] + ?Z????????(; +? GS????s???MM?C?.????????VN??&-?q?????\????lf????????H?i-rG ??v1)??S +??? V.[.C$Hi?A?G\?S???4P???SR?{|???T??S??? 5???-^QP??^>l??/?$??Q?<:??,?c?q-??LY[???JY*? ????d??=#?????????3???d ????????r????? ??TrI?????????*]KvC?i????u?mN??M?~_;[cT??t`?^?'?4M:YF????1????W???=N?xC??'"y?bCa???24?? +?h?]3?N9??+??VuA'Y?H=Ws?!B?f5?7??;?7????u????803e??4??$??]??????% +????d8???????$Y?????mg +\?x???C!|{??K???Y?/?????@S???kJ???g(??M?6?w? +.??g+*?q?SR?v8 +M?i {????g??N???Y???K?~x???miK-?? ??\?[i-???s???????L????????5???(,?_ ?????vB???)???v??n2M???7?P??)?2+&??v??? ? ?F?4?$?(????n ???w ? +hzDb.1?`?C)?s?????T?h???Qz???{???? +e?w??????????^8??V? ??N???$?:r???Aa????^???:/aL???V??UK??wy?5?[?=x?????TY9.m"N???????Nc????/X???`??Z?2V2~?b?u5????????????s?E??3??? +t@ d???f?2???S????|*[??I???.?y??DU?S/?????q ?H???Y?k^K"R??? T??E!?s???J? V?R????h???o??+????d?x"???@F??]:E??????>?GN??"????,????6???????{&&?+??XF??J)?dcm???N2=,*+?v?? .07??ue?????jqA?N??6?=?/?}????'???)?Q?-i??? ?? ????H????{???W???????#??uZ?BJMy??0?? ??5?n?Hw??:R?? ????k]0h????????7??z?8?????? +?+?O-E~?o at o +? iP? [TRUNCATED] To get the complete diff run: svnlook diff /svnroot/chnosz -r 381 From noreply at r-forge.r-project.org Wed Feb 6 18:29:10 2019 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Wed, 6 Feb 2019 18:29:10 +0100 (CET) Subject: [CHNOSZ-commits] r382 - in pkg/CHNOSZ: . data demo inst inst/extdata/OBIGT man tests/testthat vignettes Message-ID: <20190206172910.3E03918BE86@r-forge.r-project.org> Author: jedick Date: 2019-02-06 18:29:09 +0100 (Wed, 06 Feb 2019) New Revision: 382 Added: pkg/CHNOSZ/inst/extdata/OBIGT/OldAA.csv Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/data/refs.csv pkg/CHNOSZ/demo/Shh.R pkg/CHNOSZ/demo/bugstab.R pkg/CHNOSZ/demo/copper.R pkg/CHNOSZ/demo/protein.equil.R pkg/CHNOSZ/demo/sources.R pkg/CHNOSZ/demo/yeastgfp.R pkg/CHNOSZ/inst/NEWS pkg/CHNOSZ/inst/extdata/OBIGT/biotic_aq.csv.xz pkg/CHNOSZ/inst/extdata/OBIGT/organic_aq.csv.xz pkg/CHNOSZ/man/add.obigt.Rd pkg/CHNOSZ/tests/testthat/test-add.protein.R pkg/CHNOSZ/tests/testthat/test-affinity.R pkg/CHNOSZ/tests/testthat/test-ionize.aa.R pkg/CHNOSZ/tests/testthat/test-recalculate.R pkg/CHNOSZ/tests/testthat/test-wjd.R pkg/CHNOSZ/vignettes/anintro.Rmd pkg/CHNOSZ/vignettes/equilibrium.Rnw pkg/CHNOSZ/vignettes/equilibrium.lyx pkg/CHNOSZ/vignettes/hotspring.Rnw pkg/CHNOSZ/vignettes/hotspring.lyx pkg/CHNOSZ/vignettes/obigt.Rmd pkg/CHNOSZ/vignettes/obigt.bib Log: add/update data for glycine and related species from Kitadai (2014) Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-06 06:35:06 UTC (rev 381) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-06 17:29:09 UTC (rev 382) @@ -1,6 +1,6 @@ Date: 2019-02-06 Package: CHNOSZ -Version: 1.1.3-89 +Version: 1.1.3-90 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/data/refs.csv =================================================================== --- pkg/CHNOSZ/data/refs.csv 2019-02-06 06:35:06 UTC (rev 381) +++ pkg/CHNOSZ/data/refs.csv 2019-02-06 17:29:09 UTC (rev 382) @@ -61,6 +61,7 @@ DPS+96,"I. Diakonov, G. Pokrovski et al.",1996,"Geochim. Cosmochim. Acta 60, 197-211",NaAl(OH)4,http://dx.doi.org/10.1016/0016-7037(95)00403-3 AH97b,"J. P. Amend and H. C. Helgeson",1997,"J. Chem. Soc., Faraday Trans. 93, 1927-1941","amino acids GHS",https://doi.org/10.1039/A608126F AH97b.1,"J. P. Amend and H. C. Helgeson",1997,"J. Chem. Soc., Faraday Trans. 93, 1927-1941","alanate and glycinate GHS",https://doi.org/10.1039/A608126F +AH97b.2,"J. P. Amend and H. C. Helgeson",1997,"J. Chem. Soc., Faraday Trans. 93, 1927-1941","glycine and glycinium GHS",https://doi.org/10.1039/A608126F DSM+97,"J. D. Dale, E. L. Shock et al.",1997,"Geochim. Cosmochim. Acta 61, 4017-4024",alkylphenols,https://doi.org/10.1016/S0016-7037(97)00212-3 DSM+97.1,"J. D. Dale, E. L. Shock et al.",1997,"Geochim. Cosmochim. Acta 61, 4017-4024","phenol, and cresol isomers",https://doi.org/10.1016/S0016-7037(97)00212-3 DSM+97.2,"J. D. Dale, E. L. Shock et al.",1997,"Geochim. Cosmochim. Acta 61, 4017-4024","dimethylphenol isomers",https://doi.org/10.1016/S0016-7037(97)00212-3 @@ -105,6 +106,7 @@ Ste01,"A. Stefansson",2001,"Chem. Geol. 172, 225-250","aqueous H4SiO4",http://dx.doi.org/10.1016/S0009-2541(00)00263-1 SSW01,"M. D. Schulte, E. L. Shock and R. H. Wood",2001,"Geochim. Cosmochim. Acta 65, 3919-3930","AsH3, CF4, CH3F, Cl2, ClO2, N2O, NF3, NO, PH3, and SF6",https://doi.org/10.1016/S0016-7037(01)00717-7 TS01,"B. Tagirov and J. Schott",2001,"Geochim. Cosmochim. Acta 65, 3965-3992","aqueous Al species",http://dx.doi.org/10.1016/S0016-7037(01)00705-0 +GKL02,"R. N. Goldberg et al.",2002,"J. Phys. Chem. Ref. Data 31, 231-370","glycine, diglycine, and triglycine (+1 and -1 ions) GHS",http://dx.doi.org/10.1063/1.1416902 MGN03,"J. Majzlan, K.-D. Grevel and A. Navrotsky",2003,"Am. Mineral. 88, 855-859","goethite, lepidocrocite, and maghemite GHS",https://doi.org/10.2138/am-2003-5-614 NA03,"D. K. Nordstrom and D. G. Archer",2003,"Arsenic thermodynamic data and environmental geochemistry. In Arsenic in Groundwater, eds. Welch and Stollenwerk, Kluwer","As oxide and sulfide minerals", NA03.1,"D. K. Nordstrom and D. G. Archer",2003,"Arsenic thermodynamic data and environmental geochemistry. In Arsenic in Groundwater, eds. Welch and Stollenwerk, Kluwer","aqueous As oxides and sulfides", @@ -120,7 +122,10 @@ LH06b.1,"D. E. LaRowe and H. C. Helgeson",2006,"Thermochim. Acta 448, 82-106","pyridine and piperidine",https://doi.org/10.1016/j.tca.2006.06.008 DLH06,"J. M. Dick, D. E. LaRowe and H. C. Helgeson",2006,"Biogeosciences 3, 311-336","amino acid, protein, and organic groups",https://doi.org/10.5194/bg-3-311-2006 DLH06.1,"J. M. Dick, D. E. LaRowe and H. C. Helgeson",2006,"Biogeosciences 3, 311-336","amino acids HKF parameters",https://doi.org/10.5194/bg-3-311-2006 -DLH06.2,"J. M. Dick, D. E. LaRowe and H. C. Helgeson",2006,"Biogeosciences 3, 311-336","Gly-X-Gly tripeptides",https://doi.org/10.5194/bg-3-311-2006 +DLH06.2,"J. M. Dick, D. E. LaRowe and H. C. Helgeson",2006,"Biogeosciences 3, 311-336","Gly-X-Gly tripeptides Cp, V, and HKF c1, c2, omega parameters",https://doi.org/10.5194/bg-3-311-2006 +DLH06.3,"J. M. Dick, D. E. LaRowe and H. C. Helgeson",2006,"Biogeosciences 3, 311-336","glycine, [Gly], and [UPBB] HKF parameters",https://doi.org/10.5194/bg-3-311-2006 +DLH06.4,"J. M. Dick, D. E. LaRowe and H. C. Helgeson",2006,"Biogeosciences 3, 311-336","methionine HKF parameters",https://doi.org/10.5194/bg-3-311-2006 +DLH06.5,"J. M. Dick, D. E. LaRowe and H. C. Helgeson",2006,"Biogeosciences 3, 311-336","triglycine Cp, V, and HKF c1, c2, omega parameters",https://doi.org/10.5194/bg-3-311-2006 LMR06,"D. Langmuir et al.",2006,"Geochim. Cosmochim. Acta 70, 2942-2956","scorodite and amorphous ferric arsenate: G",https://doi.org/10.1016/j.gca.2006.03.006 MNM+06,"J. Majzlan, A. Navrotsky et al.",2006,"Eur. J. Mineral. 18, 175-186","coquimbite, ferricopiapite, and rhomboclase",https://doi.org/10.1127/0935-1221/2006/0018-0175 Dic07,"J. M. Dick",2007,"Ph.D. Dissertation, Univ. of California","glutathione, cystine, and cystine sidechain", @@ -143,6 +148,7 @@ DEH+13,"J. M. Dick, K. A. Evans et al.",2013,"Geochim. Cosmochim. Acta 122, 247-266","phenanthrene and methylphenanthrene isomers",https://doi.org/10.1016/j.gca.2013.08.020 FDM+14,"S. Facq et al.",2014,"Geochim. Cosmochim. Acta 132, 375-390","CO2, CO3-2, and HCO3-",https://doi.org/10.1016/j.gca.2014.01.030 FDM+14.1,"S. Facq et al.",2014,"Geochim. Cosmochim. Acta 132, 375-390","aragonite; source of data: `berman.dat`",https://doi.org/10.1016/j.gca.2014.01.030 +Kit14,"N. Kitadai",2014,"J. Mol. Evol. 78, 171-187","glycine, diglycine, and triglycine (zwitterions and ions); diketopiperazine, [Gly] and [UPBB] groups",https://doi.org/10.1007/s00239-014-9616-1 PAB+14,"G. S. Pokrovski, N. N. Akinfiev et al., 2014",2014,"Geol. Soc. Spec. Publ. 402, 9-70","Au+, Au(OH)2-, AuCl, and AuOH",https://doi.org/10.1144/SP402.4 PAB+14.1,"G. S. Pokrovski, N. N. Akinfiev et al., 2014",2014,"Geol. Soc. Spec. Publ. 402, 9-70","corrected H of AuHS",https://doi.org/10.1144/SP402.4 SHA14,"D. A. Sverjensky et al.",2014,"Geochim. Cosmochim. Acta 129, 125-145","SiO2 and Si2O4",https://doi.org/10.1016/j.gca.2013.12.019 Modified: pkg/CHNOSZ/demo/Shh.R =================================================================== --- pkg/CHNOSZ/demo/Shh.R 2019-02-06 06:35:06 UTC (rev 381) +++ pkg/CHNOSZ/demo/Shh.R 2019-02-06 17:29:09 UTC (rev 382) @@ -1,6 +1,9 @@ # Compare affinities of Sonic hedgehog and transcription factors involved in dorsal-ventral patterning # (Dick, 2015. Chemical integration of proteins in signaling and development. https://doi.org/10.1101/015826) +# to reproduce the calculations in the paper, use superseded data for [Gly] 20190206 +add.obigt("OldAA") + # UniProt names of the proteins pname <- c("SHH", "OLIG2", "NKX22", "FOXA2", "IRX3", "PAX6", "NKX62", "DBX1", "DBX2", "NKX61", "PAX7", "GLI1", "GLI2", "GLI3", "PTC1", "SMO", "GLI3R")[1:11] @@ -197,3 +200,4 @@ # all done! par(opar) if(pdf) dev.off() +data(thermo) Modified: pkg/CHNOSZ/demo/bugstab.R =================================================================== --- pkg/CHNOSZ/demo/bugstab.R 2019-02-06 06:35:06 UTC (rev 381) +++ pkg/CHNOSZ/demo/bugstab.R 2019-02-06 17:29:09 UTC (rev 382) @@ -2,6 +2,8 @@ # based on "bugstab" function in Supporting Information of Dick, 2016 # (https://doi.org/10.7717/peerj.2238) +# to reproduce the calculations in the paper, use superseded data for [Gly] 20190206 +add.obigt("OldAA") # set up graphics device layout(cbind(matrix(sapply(list(c(1, 2), c(3, 4)), function(x) rep(rep(x, each=3), 3)), nrow=6, byrow=TRUE), matrix(rep(c(0, 5, 5, 5, 5, 0), each=4), nrow=6, byrow=TRUE))) @@ -70,3 +72,5 @@ # reset graphics device to default par(opar) layout(1) +# reset thermodynamic database +data(thermo) Modified: pkg/CHNOSZ/demo/copper.R =================================================================== --- pkg/CHNOSZ/demo/copper.R 2019-02-06 06:35:06 UTC (rev 381) +++ pkg/CHNOSZ/demo/copper.R 2019-02-06 17:29:09 UTC (rev 382) @@ -3,6 +3,8 @@ ## (Aksu, S. and Doyle, F. M., 2001. Electrochemistry of copper in aqueous glycine ## solutions. J. Electrochem. Soc., 148, B51-B57. doi:10.1149/1.1344532) +# we need some superseded Cu-Gly complexes 20190206 +add.obigt("OldAA") # add some new species to thermo$obigt m1 <- makeup(info(c("Cu+", "glycinate", "glycinate")), sum=TRUE) mod.obigt(name="Cu(Gly)2-", formula=as.chemical.formula(m1)) @@ -35,8 +37,8 @@ species(Cu_s) species(c(Cu_aq, CuGly), -4) names <- c(Cu_s, Cu_aq, CuGly) -# 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)) +# mosaic diagram with speciate glycine as a function of pH +m <- mosaic(bases=Gly, pH=c(0, 16, 500), Eh=c(-0.6, 1.0, 500)) fill <- c(rep("lightgrey", 3), rep("white", 4), rep("lightblue", 4)) d <- diagram(m$A.species, fill=fill, names=NULL, xaxs="i", yaxs="i", fill.NA="pink2") # to make the labels look nicer Modified: pkg/CHNOSZ/demo/protein.equil.R =================================================================== --- pkg/CHNOSZ/demo/protein.equil.R 2019-02-06 06:35:06 UTC (rev 381) +++ pkg/CHNOSZ/demo/protein.equil.R 2019-02-06 17:29:09 UTC (rev 382) @@ -6,6 +6,8 @@ data(thermo) # use properties of the "old" [Met] sidechain group (Dick et al., 2006) mod.obigt("[Met]", G=-35245, H=-59310) +# also use parameters for [Gly] from DLH06 20190206 +add.obigt("OldAA") # set up the basis species to those used in DS11 basis("CHNOS+") # note this yields logaH2 = -4.657486 Modified: pkg/CHNOSZ/demo/sources.R =================================================================== --- pkg/CHNOSZ/demo/sources.R 2019-02-06 06:35:06 UTC (rev 381) +++ pkg/CHNOSZ/demo/sources.R 2019-02-06 17:29:09 UTC (rev 382) @@ -16,8 +16,11 @@ tdata <- read.csv(system.file("extdata/OBIGT/SUPCRT92.csv", package="CHNOSZ"), as.is=TRUE) os5 <- gsub("\ .*", "", tdata$ref1) os6 <- gsub("\ .*", "", tdata$ref2) +tdata <- read.csv(system.file("extdata/OBIGT/OldAA.csv", package="CHNOSZ"), as.is=TRUE) +os7 <- gsub("\ .*", "", tdata$ref1) +os8 <- gsub("\ .*", "", tdata$ref2) # all of the thermodynamic data sources - some of them might be NA -obigt.source <- unique(c(ps1, ps2, os1, os2, os3, os4, os5, os6)) +obigt.source <- unique(c(ps1, ps2, os1, os2, os3, os4, os5, os6, os7, os8)) obigt.source <- obigt.source[!is.na(obigt.source)] # these all produce character(0) if the sources are all accounted for print("missing these sources for thermodynamic properties:") Modified: pkg/CHNOSZ/demo/yeastgfp.R =================================================================== --- pkg/CHNOSZ/demo/yeastgfp.R 2019-02-06 06:35:06 UTC (rev 381) +++ pkg/CHNOSZ/demo/yeastgfp.R 2019-02-06 17:29:09 UTC (rev 382) @@ -3,6 +3,8 @@ # use old properties of [Met] (Dick et al., 2006) to reproduce this example data(thermo) mod.obigt("[Met]", G=-35245, H=-59310) +# also use parameters for [Gly] from DLH06 20190206 +add.obigt("OldAA") # arranged by decreasing metastability: # order of this list of locations is based on the # (dis)appearance of species on the current set of diagrams Modified: pkg/CHNOSZ/inst/NEWS =================================================================== --- pkg/CHNOSZ/inst/NEWS 2019-02-06 06:35:06 UTC (rev 381) +++ pkg/CHNOSZ/inst/NEWS 2019-02-06 17:29:09 UTC (rev 382) @@ -1,4 +1,4 @@ -CHANGES IN CHNOSZ 1.1.3-89 (2019-02-06) +CHANGES IN CHNOSZ 1.1.3-90 (2019-02-06) --------------------------------------- BUG FIXES @@ -166,6 +166,10 @@ - Add test-recalculate.R to check that some recalculated values are correctly entered in OBIGT. +- Add or update glycine, diglycine, and triglycine (zwitterions and + ions), and diketopiperazine, [Gly] and [UPBB] groups from Kitadai, + 2014. Superseded data have been moved to OBIGT/OldAA.csv. + DIAGRAMS - Lines in 1-D diagram()s can optionally be drawn as splines using the Added: pkg/CHNOSZ/inst/extdata/OBIGT/OldAA.csv =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/OldAA.csv (rev 0) +++ pkg/CHNOSZ/inst/extdata/OBIGT/OldAA.csv 2019-02-06 17:29:09 UTC (rev 382) @@ -0,0 +1,63 @@ +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 +alanylglycine,NA,C5H10N2O3,aq,Sho92,CHNOSZ.6,28.Feb.92,-116730,-186110,50.7,60.3,95.22,14.6503,21.164,12.0751,-3.6538,54.7374,0.7979,-0.4278,0 +leucylglycine,NA,C8H16N2O3,aq,Sho92,CHNOSZ.6,27.Aug.06,-110620,-202660,72.6,118.8,145.34,21.3967,34.6501,13.1805,-4.2113,98.6389,6.4783,-0.7594,0 +diglycine,NA,C4H8N2O3,aq,Sho92,CHNOSZ.6,28.Feb.92,-117020,-175640,54.2,38,76.27,12.0393,15.9447,11.6466,-3.4381,36.349,-1.3673,-0.4808,0 +diketopiperazine,NA,C4H6N2O2,aq,Sho92,CHNOSZ.6,28.Feb.92,-57440,-99300,53.5,17,76.73,12.1058,16.0764,11.6608,-3.4435,19.5904,-3.4064,-0.4702,0 +glycine,Gly,C2H5NO2,aq,"AH97b.2 [S07]","DLH06.1 [S07]",25.Aug.06,-90950,-124780,39.29,9.3,43.2,11.3,0.71,3.99,-3.04,28.5,-8.4,0.23,0 +glycinium,Gly+,C2H6NO2+,aq,"AH97b.2 [S07]","DLH06.1 [S07]",25.Aug.06,-94160,-125720,46.91,40,56.4,19.57,-7.58,-40.35,5.41,49,-1.8,0.59,0 +[Gly],NA,H,aq,"DLH06 [S15]",NA,25.Aug.06,-6075,-5570,17.31,11.371,9.606,1.83,2.57,1.22,-1.27,6.9,2.2,0,0 +[UPBB],NA,C2H2NO,aq,"DLH06 [S15]",NA,25.Aug.06,-21436,-45220,1.62,-4.496,26.296,8.1,-3.75,-6.73,1.13,11.2,-7.5,0.05,0 +alanate,NA,C3H6NO2-,aq,"SK95.1 [S98]",AH97b.1,3.Sep.06,-75360,-121470,30.71,17.8,61.88,10.6281,17.3648,0.6505,-3.4968,12.685,-4.1859,1.17,-1 +glycinate,NA,C2H4NO2-,aq,"SK95.1 [S98]",AH97b.1,3.Sep.06,-77610,-114190,30.07,-6.6,43.77,8.1592,11.7696,1.921,-3.2655,12.9389,-4.1859,1.1975,-1 +Ca(Gly)+,NA,Ca(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-211570,-240519,34.375,59.3,32.6,6.2431,7.4595,2.8241,-3.0873,41.4246,9.0464,0.0543,1 +Ca(Gly)2,NA,Ca(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-290215,-351722,77.929,131,89,13.9371,26.2517,-4.5733,-3.8641,82.6597,23.6485,-0.03,0 +Mg(Gly)+,NA,Mg(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-190820,-227064,7.788,64.2,28.7,5.8466,6.4953,3.1944,-3.0474,48.0086,10.0502,0.4555,1 +Mg(Gly)2,NA,Mg(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-272534,-343783,43.136,140.6,84.7,13.3443,24.8034,-4.0028,-3.8043,88.2942,25.6069,-0.03,0 +Sr(Gly)+,NA,Sr(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-213664,-241197,42.515,53.6,33.3,6.3007,7.6019,2.7652,-3.0932,36.9719,7.8914,-0.0684,1 +Sr(Gly)2,NA,Sr(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-291859,-351200,88.581,119.9,89.8,14.0476,26.5176,-4.6704,-3.8751,76.1763,21.395,-0.03,0 +Ba(Gly)+,NA,Ba(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-213671,-237698,55.917,48.6,38.7,6.9656,9.2295,2.1164,-3.1604,32.1389,6.8602,-0.2709,1 +Ba(Gly)2,NA,Ba(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-292479,-347082,106.12,110.1,95.8,14.8647,28.514,-5.4575,-3.9577,70.3874,19.383,-0.03,0 +Mn(Gly)+,NA,Mn(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-137101,-167693,26.59,67,33.7,6.4299,7.9186,2.6372,-3.1063,47.0493,10.6185,0.1739,1 +Mn(Gly)2,NA,Mn(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-218761,-282627,67.741,146.1,90.2,14.1002,26.6481,-4.7253,-3.8805,91.4846,26.7157,-0.03,0 +Fe(Gly)+,NA,Fe(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-105368,-137141,21.59,58,28,5.6774,6.0837,3.3533,-3.0304,42.4593,8.7852,0.2482,1 +Fe(Gly)2,NA,Fe(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-187369,-252307,61.198,128.5,83.9,13.2339,24.5311,-3.8903,-3.793,81.1932,23.1388,-0.03,0 +Ni(Gly)+,NA,Ni(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-96871,-131179,13.59,49.9,20.4,4.6813,3.6515,4.3097,-2.9299,38.8214,7.1352,0.3686,1 +Ni(Gly)2,NA,Ni(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-181191,-249835,51.18,112.7,75.4,12.0787,21.7107,-2.7819,-3.6764,71.9311,19.9195,-0.03,0 +Cu(Gly)+,NA,Cu(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-73625,-104298,26.59,63.4,25.3,5.2864,5.1238,3.7413,-2.9907,44.9395,9.8852,0.1739,1 +Cu(Gly)2,NA,Cu(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-161137,-225550,66.18,139,80.9,12.8262,23.5338,-3.4944,-3.7518,87.3679,25.285,-0.03,0 +Zn(Gly)+,NA,Zn(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-120148,-153499,19.59,62.1,25.6,5.3677,5.3226,3.6628,-2.9989,45.1185,9.6102,0.2792,1 +Zn(Gly)2,NA,Zn(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-203799,-271188,58.18,136.4,81.3,12.8771,23.6625,-3.5537,-3.7571,85.8243,24.7484,-0.03,0 +Pb(Gly)+,NA,Pb(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-90780,-114202,58.508,47.7,35.3,6.4949,8.079,2.5712,-3.1129,31.2483,6.6769,-0.3103,1 +Pb(Gly)2,NA,Pb(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-173013,-226772,109.51,108.3,92.1,14.355,27.2722,-4.9746,-3.9063,69.3582,19.0253,-0.03,0 +Co(Gly)+,NA,Co(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-97525,-130972,16.59,58.7,25.5,5.3683,5.3273,3.6539,-2.9991,43.5722,8.9227,0.326,1 +Co(Gly)2,NA,Co(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-180617,-247207,58.18,129.8,81.2,12.8601,23.6197,-3.5341,-3.7553,81.9652,23.407,-0.03,0 +Cd(Gly)+,NA,Cd(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-102566,-133978,28.59,68.4,35.3,6.6477,8.4525,2.4231,-3.1283,47.5446,10.8935,0.1417,1 +Cd(Gly)2,NA,Cd(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-185236,-250387,68.18,148.7,92.1,14.355,27.2722,-4.9746,-3.9063,93.0282,27.2523,-0.03,0 +Eu(Gly)+,NA,Eu(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-208959,-236026,49.509,89.8,50.3,8.5841,13.176,0.5767,-3.3236,57.1645,15.2476,-0.1738,1 +Eu(Gly)2,NA,Eu(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-288477,-346709,97.734,190.4,108.7,16.6314,32.8272,-7.1514,-4.136,117.4699,35.7476,-0.03,0 +Ca(Alan)+,NA,Ca(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-209172,-247643,35.015,104.6,50.7,8.7124,13.4888,0.454,-3.3365,67.7227,18.2713,0.0279,1 +Ca(Alan)2,NA,Ca(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-285446,-365834,79.755,239.1,127.3,19.1765,39.0448,-9.6021,-4.393,146.0369,45.6768,-0.03,0 +Mg(Alan)+,NA,Mg(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-186539,-232305,8.428,109.5,46.8,8.3169,12.5282,0.821,-3.2968,74.3351,19.275,0.4322,1 +Mg(Alan)2,NA,Mg(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-263631,-353761,44.962,248.8,123,18.5836,37.5967,-9.0318,-4.3331,151.6713,47.6352,-0.03,0 +Sr(Alan)+,NA,Sr(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-211130,-248184,43.155,98.9,51.4,8.77,13.6312,0.3947,-3.3424,63.2691,17.1163,-0.0948,1 +Sr(Alan)2,NA,Sr(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-286831,-365053,90.407,228.1,128.1,19.2869,39.3109,-9.699,-4.404,139.5534,43.4233,-0.03,0 +Ba(Alan)+,NA,Ba(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-210713,-244263,56.557,93.7,56.8,9.4348,15.2528,-0.2391,-3.4095,58.4325,16.085,-0.2977,1 +Ba(Alan)2,NA,Ba(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-286687,-360171,107.946,218.2,134.1,20.104,41.3073,-10.4865,-4.4865,133.7647,41.4112,-0.03,0 +Mn(Alan)+,NA,Mn(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-134280,-173740,29.425,112.3,51.8,8.8873,13.9167,0.2842,-3.3542,73.0237,19.8433,0.1124,1 +Mn(Alan)2,NA,Mn(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-213474,-295365,72.44,254.2,128.5,19.3395,39.4414,-9.7539,-4.4094,154.8617,48.744,-0.03,0 +Fe(Alan)+,NA,Fe(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-103952,-146326,18.518,103.3,46.1,8.1661,12.1558,0.976,-3.2814,69.2856,18.01,0.2792,1 +Fe(Alan)2,NA,Fe(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-184387,-269655,58.166,236.6,122.2,18.4732,37.3244,-8.9189,-4.3219,144.5703,45.1671,-0.03,0 +Ni(Alan)+,NA,Ni(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-94227,-137691,15.46,95.2,38.5,7.1451,9.664,1.9536,-3.1784,64.9703,16.36,0.326,1 +Ni(Alan)2,NA,Ni(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-175945,-264092,50.92,220.8,113.8,17.318,34.504,-7.8105,-4.2053,135.3083,41.9478,-0.03,0 +Cu(Alan)+,NA,Cu(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,06.Feb.19,-71295,-110530,25.46,108.7,43.4,7.7387,11.1165,1.3762,-3.2385,70.7759,19.11,0.0974,1 +Cu(Alan)2,NA,Cu(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,06.Feb.19,-156054,-238480,65.92,247.2,119.2,18.0655,36.3271,-8.523,-4.2807,150.7452,47.3132,-0.03,0 +Zn(Alan)+,NA,Zn(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-117313,-161024,17.46,107.4,43.8,7.8514,11.3891,1.2746,-3.2497,71.8106,18.835,0.2956,1 +Zn(Alan)2,NA,Zn(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-198512,-284509,60.92,244.5,119.6,18.1164,36.4558,-8.5823,-4.286,149.2015,46.7767,-0.03,0 +Pb(Alan)+,NA,Pb(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-87891,-120835,59.148,93,53.4,8.964,14.1088,0.1992,-3.3622,57.5413,15.9017,-0.3372,1 +Pb(Alan)2,NA,Pb(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-167671,-240311,111.336,216.4,130.4,19.5944,40.0653,-10.0034,-4.4352,132.7356,41.0535,-0.03,0 +Co(Alan)+,NA,Co(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-94799,-136805,20.46,104,43.6,7.8202,11.3148,1.299,-3.2467,69.3955,18.1475,0.2482,1 +Co(Alan)2,NA,Co(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-175193,-260392,60.92,238,119.4,18.0995,36.4127,-8.5626,-4.2842,145.3423,45.4353,-0.03,0 +Cd(Alan)+,NA,Cd(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-100782,-141576,29.698,113.7,53.4,9.1151,14.4742,0.063,-3.3773,73.7914,20.1183,0.1098,1 +Cd(Alan)2,NA,Cd(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-181340,-264540,72.797,256.8,130.4,19.5944,40.0653,-10.0034,-4.4352,156.4053,49.2806,-0.03,0 +Eu(Alan)+,NA,Eu(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-206029,-242617,50.149,135,68.4,11.0532,19.2058,-1.7947,-3.5729,83.4588,24.4724,-0.2006,1 +Eu(Alan)2,NA,Eu(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-282521,-359634,99.56,298.5,147,21.8707,45.6205,-12.1799,-4.6649,180.847,57.7759,-0.03,0 Modified: pkg/CHNOSZ/inst/extdata/OBIGT/biotic_aq.csv.xz =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/biotic_aq.csv.xz 2019-02-06 06:35:06 UTC (rev 381) +++ pkg/CHNOSZ/inst/extdata/OBIGT/biotic_aq.csv.xz 2019-02-06 17:29:09 UTC (rev 382) @@ -1,104 +1,91 @@ -?7zXZ???F!t/?????.?]7I??b???9??????TB;q?"?q???cL;?"??I?,t?b?PK??7?t(?em?A-P?Q?]?? ??8?.f?|?????V[?????=??K????VTm??~vw? ?2/ ??Wa???s?-?????p?lVs????H???u???? ?%?XF??k#??????????+??(??m5?St5?Fa?a??jN??8????>z???3MwS?%??????+?3x??`cw`?; $? (???????P?>????>?1b???QA??????>6o?=?-?((??pN???i????VOL?A???9 c?E3??XP?? ??kj?s?????Y!&o??w(??3?+?"???????; ??R6eW????![?????r?O>O?*?h\t????ty??)B????n<?9l?N!3???z '???}???nV?,0uVe??????? j?????|B??d^7&KK?- -f("?9s??[?S>?W?;!6???2_?????s??3}/????hAa]x^|??j???`????????D3v??zq??F???W??#?U?!??23???1?^Fn??L ??????i??GwrG?u}????1?7?0??s?????:?C??L?????xyd?+?m????i#??;??????+}?j??$?!?1?????Go? ?|?)|?H??a????y??{??o??p????)i??uc??E?ni??8??????? 8H??3?q}??i??s??)???6 ??j???Y?V?-?)??q?^?????,u???#v???8??B?/???6x?7?4??U?~????? y??/mg9??M/?|??Z??????}M X?6????*?o???s???C7jy -?r?N??P*? -????f?d??H??f??T?D;??FN???s?W??2????$=?o??GBNg???6???#R??>??8?(_? --???=?QhZ???z??9??p???d::?/??#???-???T? S???~4?[X%?????????=?8_?%?n6!??z??\????x?S??#???U?y?-??R?zwS?E???>/??@??_?q?)?[?t? -??S?vR?Np??????P"Y???.???\:???R?????_/?????D?6j??V?? sb??p???????f?y??K?h??/1???|?1????p?nf????p???B -?# ???p8????? ?KC??}^?jkW??XLO??N? `??????S?m5>8????? '?~?U?hS???2???t@a?r?{?[?mV???t??J???F????????3@??p????*?/p ,?}??U???k?VjCL??:qeM"?s]????/$??? ??'??8?<??_oCw??S???0?q??W????|?Xb -` ?=n<^?"?g????6oyH?yB&(??xbI???F?V4???'???"???wW?a?G??W|?Z!??????6????#??6?x???I ??{?3???z? Z?%Y:???4??RR???????dUWKy -?D?]??G?!^h?X^?+W ?????'x? ????? -?N?3????[??Wo???????gFp???#?? -??z?L??p'N?G 1CuN$H?{????1?h????.???r{=J^\???g????  -?$?]???k??j??R???J??)?`?? -??/? ?????y??0Qx?????r??j=??????w??h?? -5??x?+?? -??8H?&?Hs?GQ???#Y?&???THCQ;?&?E9gvv]~r -?^[??????R????????;?"D??Go???:\m???vcTH?=?a0g????|-?qvr?'??ZB?=D???~$A??q??B??R?? Oe??|o??}???E:?` ??????4]O?c%A_\?;:?m?????!???$#G????%??j????????Q?)?F????/R?2??,??#T\5??<?}E([@(??? ???A??R5??:G?[U??w?cYkZR???????????u??N?tGf?i=??I???Vz;?(?????Ds???????????????v @??????s?z?G????????:??M??d??" -???|'????!h?m+ at 9?.`Y?}_???^~(AF??Y?????M?!???N??6????$????n?w??7?}??Sws?E??r??K??e???` J?H??*????B???N?E at Q??%?0M???&??ig6)??R?C??/?rQ????7?6 F?q~?c??????{?N???_?E?? -??<-??#?8 ??swh?G`???9?j??3,Q??????y??4?a???P?f?$?e????????pN?? -???Y?q??[f?4K?????????3;=??,B;%mB???]??9{??? -}?z&n??? ???|?e+???Y???@A;8q?;????]K?T?C? -f????h_??4V?P?7`??F6?p??.?w??A???????ZS?N???K???????23?=?|g?N???,T?Q??1??R??M8dl1/??????b?YK???bE??|Z??i????`3?? -?E?Y?K???????-???!'E(fUH^?Q????JC???? -f?hO????.??-??v=J???s????vtk?d?h?7??h(?^?Qd?FQ?\P?qm???\. ?uo.(7?g?0?uB VY?3??w???????P?2?q??'?&W%?f -7?w??5?_?c?6?8?G??em????G?E -T2?~S??Sj?L+????8???A??? z??R??b???B?G ?m??????/?8*^D??7v?)?qi+S??% ?Ed????:n0?RQ??[TjF????H=??%????1{p??A???t?Ih~f???{?????6m????S?P??X????b?o?\???UT??N?CH?J{e???L ??f?CU???26?b??1 -'?i?^?N<{=?)?O?X Og?+;|Y"?u???w??:????|?d?b??? ?3?W?~U?g-?QFb???;D?!?U??rE?0?h}?7Z{??????TF??j??????L=y???'p?T~????d+5?3Q?????}?^???w:>z`?? -uy_j@ -?I????d[?xk ?u??W????.V??)??l l?S?1?2?=?$??^ ??o ???`NH6??{??%;??O?,???l???i?a???*,Xl??Z?m8q?0v;uI?;???PC?+?-x??~???.M=?'t?d?????GC????)??D????/?z??'?)J?N?x3??M.v!*4???05???QJ,???K?$????UU?V?N,??T??3v? ;7??o???f???V?A??j??|?,?P?????????F V????I??T???t????GE???t?u ?H??S$m?)?/?{?m???V????????b????~ -????????s-???????[.d?!?z??Z?????"?:+`^_I???dl`??k?g???Z?s?f? ???7ML??u?w= -???y4???z??O????Z@?um/???l???R??G?@T??????vf?H?^-??TF??????????4&???!????Tl?/t?z;??3E??Z???bTDH?k???sg?$Ws:?P???????[???g???O????????1(?W????? ?=??X?gI83?#???? -J??Q.??????e at 5h?$?e0?M??I??c6$?????!T%?r??w?0 }w?v????8?????`!y L5??lS?3???^?a/????Db??!?`Aa?1W?1??lGI)h??0SO???G?%????~/l??*??????0%?wL????|???????????h0DF????1???N0?)z{Ol-?+??????X?5????:????g??8??????x??BH???\??,?I?u?????t?CKo?????????h??x?wQ?????? -???AQ?a?N???C,?2????.Y1A?^l?????P?)?6???????h3?dJ???J8??W?;!6???2_?????s??3}/????hAa]x^|??j???`????wt??\i??V>?eL8?^???QG,h????O???.?????J? +??@4??????b4p?J?u?3??#????o??0???????????????v??0?$`?^??:/??? +???3??)]g?1v*?n????{???;Q????+?????????m?g?Z8p+???^??????.rE??j??6[??k0?jh?\m??e?s???????????t(i$??$??T????;$?:??W?v5G????0 ???$Wg?q9s???$r????? ?YT?Tz.+'??#?R?d????/v??}%???????f???C'T???F?y???{?\4???_??CU?$$?u??5?ujH? ????#(??????u??-;??&?9?njm???h?DQ??A6xT/??f???????????????????v??T???s?_?A*?E~??? +?l?-?5????&?@??? +?????)?!d?9???.?????????eh???r ?y????I???Gg?;?u??N?:????@y???c???[D6?o?+??? +{?`??%?B??,P??%EZ?F?k????w!?9~0????`???X????????F?????? ??eWX@????M???j??S?D????m?(`$???Q????I6??9??$An9?K????{.%??s??8H?Y}yZ?? "i?t??a??D2U'?? ^?????u?p?4e?(? ??1????`j????4G?KM??#????????t??2?.vU?? ?P?/????*g %]:h?B????????y?QYh??d4?"???????? x ?, :i???!???g?C__?"?????? +???@?+?????,?'p??J???h????=n??[?`? +?L"???M???7?MPS????a?D????,??b?( ??Iz"2?a?p?F???>:j?T???D??=H??' ?8" ??M???g??J?o$?"???zc???G?h?},1{??=?x????|?n??jh??d??m?_[???`?\?xOr??A???I2? ]J???'?i?;???r?!5??eb??`??S?Ex?t-(????Z?L?2?a?tA +?|????????T?#H?2?s3{*/?.??~2?B??(?[???@??? +b??????.??? la??C0 ?c?Ud?+?S??q>t??v{N|{??l?????(A\?????s??????eN???'?*???E>P?????S?7P?tD9 ?ri??#w?/w?c2?G??????3E?Ms??b?i?????p??5f?*;z?})??h???_d???b??~?:???]???,?)?OU??bqG?j?t?G>?[?/???}?F??v??wJS?wPvE[?Qy????V?YT?\????U??J?????x?93?x????DU?????T??u3?y$??(?n??]s"?M?????7V!^o ??L??*??S?HTb???=???E>?3t?}9z@?G?????J????? Q?>B????pY???V?P??H3????4,?c????X?j +y??"?Q7~?@L1???(??R?d??p/`93?*?A??9?:Fk?([?3h?HW?c?|?g?2???G?=?B?4?B`A?)fO?]????_ 0m?[?W??1??Jt???C???S\???(?A6??O???8cHV!|??.?????@??h?X??`??c:??w??2S?? Wp??????j??C????+?!??|FfD???y?BS?;8F???0??,??~???mA +?????n????0?'gm?n[O^g??!xwnm???u??????k4??????!N3????]??4?q????=? +??????VO?46b??>;?D +WJU?????)??>??^q2Y({?????>???gS!v?????&????????"N????4?e*y?}G?T?K?X 7z????L???u?3?&n??V?????_8???V=??q??M???bpYJ{??`????TYcx??O?g????4?j????m3;?>??????\?u?????????9x0.'????&A??g????fB4??0???(??`?K9?????m?(n???????g??r? e@???C???4?????l.?h?.?????HD??M-F?? ?^?0?)?Z??`?4Hn;m?GH?Y?<'?]?;??4?IA}G??>0???zT??????$?M?;?Z??rbig!?J??N??I?2???d??w????w? +z??-$?;weyFc???A?0a? ????^i??u?I0???U??.?:?Y?3[; W?Y??? ?)?>;?Z??K?????M???)?H+??l?????q???N?Q?8T? ???$>??EqwZ?+q?I??? ??9?`????>/??W???p???)?[?%d16p?? ?y????_.?s?hveo?cy?5Hv&BT^<w??j ??1?5b?.?(%Q??Q??pq????????0A?d?I??e?s???D????t???O??j ??)?[a2??????] +??Fi? ?9[???^/WR?~`-?*p?&!??N?%r"?S ????K:%ir??????A?*???? ?jRa +??+???? +%?4%??U???n??????O??mq?xZ?M?Q??V??????3?n?;???????? ???v??G??C??T??-????r?,??p ?=u?A??DIk:??|@??J??xv? +|h?a?-??c?2|???K?m???? ?.?T??m????R???#?)l?Y8)1 g?5lC?? ??%;{v$?qn??OC????&: ????? ????? ??m~?v?(?L??????S???I?y???a? +????r.???p?G$A?L&dilE]RP?g#? +(.?U?@ +} +?r??+?6?D)??LW?O?}?????c?????A??y?v?w??????g?5??:??/??A~??*??????b??`.????U/??)6???????Q??r?{U?9?y+????,k??4?NQ7?Z??~?CK??w?D?gD?e?qc*????9?Gd??6?0??/??K +?.?k?^4??G??_p?o???,??X?.????V???e????????9g??~??=????n?H?.??} ? +~??#?)??>????x/????>?m???`???? ???%??????????%]Ys?????nw??=?_0??u???q+?XC?!??'jm0???-??LJ???U +?+f8?;???Ii??W??????q?@?????@?z6?gD?vM??V??Z?3c??? Author: jedick Date: 2019-02-07 02:19:55 +0100 (Thu, 07 Feb 2019) New Revision: 383 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/R/protein.info.R pkg/CHNOSZ/demo/Shh.R pkg/CHNOSZ/demo/bugstab.R pkg/CHNOSZ/demo/copper.R pkg/CHNOSZ/demo/protein.equil.R pkg/CHNOSZ/demo/yeastgfp.R pkg/CHNOSZ/inst/NEWS pkg/CHNOSZ/inst/extdata/OBIGT/OldAA.csv pkg/CHNOSZ/man/protein.Rd pkg/CHNOSZ/tests/testthat/test-add.protein.R pkg/CHNOSZ/tests/testthat/test-affinity.R pkg/CHNOSZ/tests/testthat/test-ionize.aa.R pkg/CHNOSZ/tests/testthat/test-protein.info.R pkg/CHNOSZ/vignettes/anintro.Rmd pkg/CHNOSZ/vignettes/equilibrium.Rnw pkg/CHNOSZ/vignettes/equilibrium.lyx pkg/CHNOSZ/vignettes/hotspring.Rnw pkg/CHNOSZ/vignettes/hotspring.lyx pkg/CHNOSZ/vignettes/vig.bib Log: add methionine and [Met] to OBIGT/OldAA.csv Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-06 17:29:09 UTC (rev 382) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-07 01:19:55 UTC (rev 383) @@ -1,6 +1,6 @@ -Date: 2019-02-06 +Date: 2019-02-07 Package: CHNOSZ -Version: 1.1.3-90 +Version: 1.1.3-91 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/R/protein.info.R =================================================================== --- pkg/CHNOSZ/R/protein.info.R 2019-02-06 17:29:09 UTC (rev 382) +++ pkg/CHNOSZ/R/protein.info.R 2019-02-07 01:19:55 UTC (rev 383) @@ -148,8 +148,14 @@ } protein.equil <- function(protein, T=25, loga.protein=0, digits=4) { + out <- character() + mymessage <- function(...) { + message(...) + text <- paste(list(...), collapse = " ") + out <<- c(out, text) + } # show the individual steps in calculating metastable equilibrium among proteins - message("protein.equil: temperature from argument is ", T, " degrees C") + mymessage("protein.equil: temperature from argument is ", T, " degrees C") TK <- convert(T, "K") # get the amino acid compositions of the proteins aa <- pinfo(pinfo(protein)) @@ -165,13 +171,13 @@ ionize.it <- TRUE iword <- "ionized" pH <- -thermo$basis$logact[match("H+", rownames(bmat))] - message("protein.equil: pH from thermo$basis is ", pH) + mymessage("protein.equil: pH from thermo$basis is ", pH) } # tell the user whose [Met] is in thermo$obigt info.Met <- info(info('[Met]', "aq")) - message("protein.equil: [Met] is from reference ", info.Met$ref1) + mymessage("protein.equil: [Met] is from reference ", info.Met$ref1) ## first set of output: show results of calculations for a single protein - message("protein.equil [1]: first protein is ", pname[1], " with length ", plength[1]) + mymessage("protein.equil [1]: first protein is ", pname[1], " with length ", plength[1]) # standard Gibbs energies of basis species G0basis <- unlist(suppressMessages(subcrt(thermo$basis$ispecies, T=T, property="G")$out)) # coefficients of basis species in formation reactions of proteins @@ -182,71 +188,72 @@ G0prot <- unlist(suppressMessages(subcrt(pname, T=T, property="G")$out)) # standard Gibbs energy of formation reaction of nonionized protein, cal/mol G0protform <- G0prot - G0basissum - message("protein.equil [1]: reaction to form nonionized protein from basis species has G0(cal/mol) of ", signif(G0protform[1], digits)) + mymessage("protein.equil [1]: reaction to form nonionized protein from basis species has G0(cal/mol) of ", signif(G0protform[1], digits)) if(ionize.it) { # standard Gibbs energy of ionization of protein, cal/mol G0ionization <- suppressMessages(ionize.aa(aa, property="G", T=T, pH=pH))[1, ] - message("protein.equil [1]: ionization reaction of protein has G0(cal/mol) of ", signif(G0ionization[1], digits)) + mymessage("protein.equil [1]: ionization reaction of protein has G0(cal/mol) of ", signif(G0ionization[1], digits)) # standard Gibbs energy of formation reaction of ionized protein, cal/mol G0protform <- G0protform + G0ionization } # standard Gibbs energy of formation reaction of non/ionized residue equivalents, dimensionless R <- 1.9872 # gas constant, cal K^-1 mol^-1 G0res.RT <- G0protform/R/TK/plength - message("protein.equil [1]: per residue, reaction to form ", iword, " protein from basis species has G0/RT of ", signif(G0res.RT[1], digits)) + mymessage("protein.equil [1]: per residue, reaction to form ", iword, " protein from basis species has G0/RT of ", signif(G0res.RT[1], digits)) # coefficients of basis species in formation reactions of residues resbasis <- suppressMessages(protein.basis(aa, T=T, normalize=TRUE)) # logQstar and Astar/RT logQstar <- colSums(t(resbasis) * - thermo$basis$logact) - message("protein.equil [1]: per residue, logQstar is ", signif(logQstar[1], digits)) + mymessage("protein.equil [1]: per residue, logQstar is ", signif(logQstar[1], digits)) Astar.RT <- -G0res.RT - log(10)*logQstar - message("protein.equil [1]: per residue, Astar/RT = -G0/RT - 2.303logQstar is ", signif(Astar.RT[1], digits)) - if(!is.numeric(protein)) message("protein.equil [1]: not comparing calculations with affinity() because 'protein' is not numeric") + mymessage("protein.equil [1]: per residue, Astar/RT = -G0/RT - 2.303logQstar is ", signif(Astar.RT[1], digits)) + if(!is.numeric(protein)) mymessage("protein.equil [1]: not comparing calculations with affinity() because 'protein' is not numeric") else { # for **Astar** we have to set the activities of the proteins to zero, not loga.protein! a <- suppressMessages(affinity(iprotein=protein, T=T, loga.protein=0)) aAstar.RT <- log(10) * as.numeric(a$values) / plength - message("check it! per residue, Astar/RT calculated using affinity() is ", signif(aAstar.RT[1], digits)) + mymessage("check it! per residue, Astar/RT calculated using affinity() is ", signif(aAstar.RT[1], digits)) if(!isTRUE(all.equal(Astar.RT, aAstar.RT, check.attributes=FALSE))) stop("Bug alert! The same value for Astar/RT cannot be calculated manually as by using affinity()") } - if(length(pname)==1) message("protein.equil [all]: all done... give me more than one protein for equilibrium calculations") + if(length(pname)==1) mymessage("protein.equil [all]: all done... give me more than one protein for equilibrium calculations") else { ## next set of output: equilibrium calculations - message("protein.equil [all]: lengths of all proteins are ", paste(plength, collapse=" ")) - message("protein.equil [all]: Astar/RT of all residue equivalents are ", paste(signif(Astar.RT, digits), collapse=" ")) + mymessage("protein.equil [all]: lengths of all proteins are ", paste(plength, collapse=" ")) + mymessage("protein.equil [all]: Astar/RT of all residue equivalents are ", paste(signif(Astar.RT, digits), collapse=" ")) expAstar.RT <- exp(Astar.RT) sumexpAstar.RT <- sum(expAstar.RT) - message("protein.equil [all]: sum of exp(Astar/RT) of all residue equivalents is ", signif(sumexpAstar.RT, digits)) + mymessage("protein.equil [all]: sum of exp(Astar/RT) of all residue equivalents is ", signif(sumexpAstar.RT, digits)) # boltzmann distribution alpha <- expAstar.RT / sumexpAstar.RT - message("protein.equil [all]: equilibrium degrees of formation (alphas) of residue equivalents are ", paste(signif(alpha, digits), collapse=" ")) + mymessage("protein.equil [all]: equilibrium degrees of formation (alphas) of residue equivalents are ", paste(signif(alpha, digits), collapse=" ")) # check with equilibrate() if(is.numeric(protein)) { loga.equil.protein <- unlist(suppressMessages(equilibrate(a, normalize=TRUE))$loga.equil) # here we do have to convert from logarithms of activities of proteins to degrees of formation of residue equivalents a.equil.residue <- plength*10^loga.equil.protein ealpha <- a.equil.residue/sum(a.equil.residue) - message("check it! alphas of residue equivalents from equilibrate() are ", paste(signif(ealpha, digits), collapse=" ")) + mymessage("check it! alphas of residue equivalents from equilibrate() are ", paste(signif(ealpha, digits), collapse=" ")) if(!isTRUE(all.equal(alpha, ealpha, check.attributes=FALSE))) stop("Bug alert! The same value for alpha cannot be calculated manually as by using equilibrate()") } # total activity of residues loga.residue <- log10(sum(plength * 10^loga.protein)) - message("protein.equil [all]: for activity of proteins equal to 10^", signif(loga.protein, digits), ", total activity of residues is 10^", signif(loga.residue, digits)) + mymessage("protein.equil [all]: for activity of proteins equal to 10^", signif(loga.protein, digits), ", total activity of residues is 10^", signif(loga.residue, digits)) # equilibrium activities of residues loga.residue.equil <- log10(alpha*10^loga.residue) - message("protein.equil [all]: log10 equilibrium activities of residue equivalents are ", paste(signif(loga.residue.equil, digits), collapse=" ")) + mymessage("protein.equil [all]: log10 equilibrium activities of residue equivalents are ", paste(signif(loga.residue.equil, digits), collapse=" ")) # equilibrium activities of proteins loga.protein.equil <- log10(10^loga.residue.equil/plength) - message("protein.equil [all]: log10 equilibrium activities of proteins are ", paste(signif(loga.protein.equil, digits), collapse=" ")) + mymessage("protein.equil [all]: log10 equilibrium activities of proteins are ", paste(signif(loga.protein.equil, digits), collapse=" ")) # check with equilibrate() if(is.numeric(protein)) { eloga.protein.equil <- unlist(suppressMessages(equilibrate(a, loga.balance=loga.residue, normalize=TRUE))$loga.equil) - message("check it! log10 eq'm activities of proteins from equilibrate() are ", paste(signif(eloga.protein.equil, digits), collapse=" ")) + mymessage("check it! log10 eq'm activities of proteins from equilibrate() are ", paste(signif(eloga.protein.equil, digits), collapse=" ")) if(!isTRUE(all.equal(loga.protein.equil, eloga.protein.equil, check.attributes=FALSE))) stop("Bug alert! The same value for log10 equilibrium activities of proteins cannot be calculated manually as by using equilibrate()") } } + return(out) } Modified: pkg/CHNOSZ/demo/Shh.R =================================================================== --- pkg/CHNOSZ/demo/Shh.R 2019-02-06 17:29:09 UTC (rev 382) +++ pkg/CHNOSZ/demo/Shh.R 2019-02-07 01:19:55 UTC (rev 383) @@ -1,8 +1,8 @@ # Compare affinities of Sonic hedgehog and transcription factors involved in dorsal-ventral patterning # (Dick, 2015. Chemical integration of proteins in signaling and development. https://doi.org/10.1101/015826) -# to reproduce the calculations in the paper, use superseded data for [Gly] 20190206 -add.obigt("OldAA") +# to reproduce the calculations in the paper, use superseded data for [Gly] and [UPBB] 20190206 +add.obigt("OldAA", c("[Gly]", "[UPBB]")) # UniProt names of the proteins pname <- c("SHH", "OLIG2", "NKX22", "FOXA2", "IRX3", "PAX6", "NKX62", "DBX1", Modified: pkg/CHNOSZ/demo/bugstab.R =================================================================== --- pkg/CHNOSZ/demo/bugstab.R 2019-02-06 17:29:09 UTC (rev 382) +++ pkg/CHNOSZ/demo/bugstab.R 2019-02-07 01:19:55 UTC (rev 383) @@ -2,8 +2,8 @@ # based on "bugstab" function in Supporting Information of Dick, 2016 # (https://doi.org/10.7717/peerj.2238) -# to reproduce the calculations in the paper, use superseded data for [Gly] 20190206 -add.obigt("OldAA") +# to reproduce the calculations in the paper, use superseded data for [Gly] and [UPBB] 20190206 +add.obigt("OldAA", c("[Gly]", "[UPBB]")) # set up graphics device layout(cbind(matrix(sapply(list(c(1, 2), c(3, 4)), function(x) rep(rep(x, each=3), 3)), nrow=6, byrow=TRUE), matrix(rep(c(0, 5, 5, 5, 5, 0), each=4), nrow=6, byrow=TRUE))) Modified: pkg/CHNOSZ/demo/copper.R =================================================================== --- pkg/CHNOSZ/demo/copper.R 2019-02-06 17:29:09 UTC (rev 382) +++ pkg/CHNOSZ/demo/copper.R 2019-02-07 01:19:55 UTC (rev 383) @@ -3,7 +3,7 @@ ## (Aksu, S. and Doyle, F. M., 2001. Electrochemistry of copper in aqueous glycine ## solutions. J. Electrochem. Soc., 148, B51-B57. doi:10.1149/1.1344532) -# we need some superseded Cu-Gly complexes 20190206 +# we need superseded data for Cu-Gly complexes 20190206 add.obigt("OldAA") # add some new species to thermo$obigt m1 <- makeup(info(c("Cu+", "glycinate", "glycinate")), sum=TRUE) Modified: pkg/CHNOSZ/demo/protein.equil.R =================================================================== --- pkg/CHNOSZ/demo/protein.equil.R 2019-02-06 17:29:09 UTC (rev 382) +++ pkg/CHNOSZ/demo/protein.equil.R 2019-02-07 01:19:55 UTC (rev 383) @@ -4,9 +4,7 @@ # clear out amino acid residues loaded by the example above # ( in affinity(iprotein=ip) ) data(thermo) -# use properties of the "old" [Met] sidechain group (Dick et al., 2006) -mod.obigt("[Met]", G=-35245, H=-59310) -# also use parameters for [Gly] from DLH06 20190206 +# use superseded properties of [Met], [Gly], and [UPBB] (Dick et al., 2006) add.obigt("OldAA") # set up the basis species to those used in DS11 basis("CHNOS+") @@ -27,5 +25,5 @@ Aref.residue <- Astar.residue - loga.residue # 0.446, after Eq. 16 # A-star of the residue in natural log units (A/RT) log(10) * Astar.residue # 0.4359, after Eq. 23 -# forget about the old [Met] group for whatever comes next +# forget about the superseded group properties for whatever comes next data(thermo) Modified: pkg/CHNOSZ/demo/yeastgfp.R =================================================================== --- pkg/CHNOSZ/demo/yeastgfp.R 2019-02-06 17:29:09 UTC (rev 382) +++ pkg/CHNOSZ/demo/yeastgfp.R 2019-02-07 01:19:55 UTC (rev 383) @@ -1,9 +1,7 @@ ## Oxygen fugacity - activity of H2O predominance ## diagrams for proteologs for 23 YeastGFP localizations -# use old properties of [Met] (Dick et al., 2006) to reproduce this example +# use superseded properties of [Met], [Gly], and [UPBB] (Dick et al., 2006) data(thermo) -mod.obigt("[Met]", G=-35245, H=-59310) -# also use parameters for [Gly] from DLH06 20190206 add.obigt("OldAA") # arranged by decreasing metastability: # order of this list of locations is based on the Modified: pkg/CHNOSZ/inst/NEWS =================================================================== --- pkg/CHNOSZ/inst/NEWS 2019-02-06 17:29:09 UTC (rev 382) +++ pkg/CHNOSZ/inst/NEWS 2019-02-07 01:19:55 UTC (rev 383) @@ -1,4 +1,4 @@ -CHANGES IN CHNOSZ 1.1.3-90 (2019-02-06) +CHANGES IN CHNOSZ 1.1.3-91 (2019-02-07) --------------------------------------- BUG FIXES @@ -168,8 +168,12 @@ - Add or update glycine, diglycine, and triglycine (zwitterions and ions), and diketopiperazine, [Gly] and [UPBB] groups from Kitadai, - 2014. Superseded data have been moved to OBIGT/OldAA.csv. + 2014. +- For reproducing previous calculations, superseded data for [Gly] and + [UPBB], as well as [Met] (earlier superseded by LaRowe and Dick, + 2012), have been moved to OBIGT/OldAA.csv. + DIAGRAMS - Lines in 1-D diagram()s can optionally be drawn as splines using the Modified: pkg/CHNOSZ/inst/extdata/OBIGT/OldAA.csv =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/OldAA.csv 2019-02-06 17:29:09 UTC (rev 382) +++ pkg/CHNOSZ/inst/extdata/OBIGT/OldAA.csv 2019-02-07 01:19:55 UTC (rev 383) @@ -5,7 +5,9 @@ diketopiperazine,NA,C4H6N2O2,aq,Sho92,CHNOSZ.6,28.Feb.92,-57440,-99300,53.5,17,76.73,12.1058,16.0764,11.6608,-3.4435,19.5904,-3.4064,-0.4702,0 glycine,Gly,C2H5NO2,aq,"AH97b.2 [S07]","DLH06.1 [S07]",25.Aug.06,-90950,-124780,39.29,9.3,43.2,11.3,0.71,3.99,-3.04,28.5,-8.4,0.23,0 glycinium,Gly+,C2H6NO2+,aq,"AH97b.2 [S07]","DLH06.1 [S07]",25.Aug.06,-94160,-125720,46.91,40,56.4,19.57,-7.58,-40.35,5.41,49,-1.8,0.59,0 +methionine,Met,C5H11NO2S,aq,AH97b,DLH06,25.Aug.06,-120120,-178520,62.36,70.7,105.4,24.95,6.9,13.59,-7.77,85.3,-6.6,0.13,0 [Gly],NA,H,aq,"DLH06 [S15]",NA,25.Aug.06,-6075,-5570,17.31,11.371,9.606,1.83,2.57,1.22,-1.27,6.9,2.2,0,0 +[Met],NA,C3H7S,aq,DLH06,NA,25.Aug.06,-35245,-59310,40.38,72.739,71.832,15.48,8.76,10.82,-6,63.7,4,-0.1,0 [UPBB],NA,C2H2NO,aq,"DLH06 [S15]",NA,25.Aug.06,-21436,-45220,1.62,-4.496,26.296,8.1,-3.75,-6.73,1.13,11.2,-7.5,0.05,0 alanate,NA,C3H6NO2-,aq,"SK95.1 [S98]",AH97b.1,3.Sep.06,-75360,-121470,30.71,17.8,61.88,10.6281,17.3648,0.6505,-3.4968,12.685,-4.1859,1.17,-1 glycinate,NA,C2H4NO2-,aq,"SK95.1 [S98]",AH97b.1,3.Sep.06,-77610,-114190,30.07,-6.6,43.77,8.1592,11.7696,1.921,-3.2655,12.9389,-4.1859,1.1975,-1 Modified: pkg/CHNOSZ/man/protein.Rd =================================================================== --- pkg/CHNOSZ/man/protein.Rd 2019-02-06 17:29:09 UTC (rev 382) +++ pkg/CHNOSZ/man/protein.Rd 2019-02-07 01:19:55 UTC (rev 383) @@ -29,9 +29,10 @@ ## surface-layer proteins from Methanococcus and others ## as a function of oxygen fugacity, after Dick, 2008, Fig. 5b -# use old properties of [Met] (Dick et al., 2006) to reproduce this example +# to reproduce the calculations in the paper, +# use superseded data for [Met], [Gly] and [UPBB] data(thermo) -mod.obigt("[Met]", G=-35245, H=-59310) +add.obigt("OldAA") # make our protein list organisms <- c("METSC", "METJA", "METFE", "HALJP", "METVO", "METBU", "ACEKI", "GEOSE", "BACLI", "AERSA") Modified: pkg/CHNOSZ/tests/testthat/test-add.protein.R =================================================================== --- pkg/CHNOSZ/tests/testthat/test-add.protein.R 2019-02-06 17:29:09 UTC (rev 382) +++ pkg/CHNOSZ/tests/testthat/test-add.protein.R 2019-02-07 01:19:55 UTC (rev 383) @@ -27,10 +27,7 @@ Cp <- 6415.5 V <- 10421 formula <- "C613H959N193O185S10" - # use parameters for [Met] sidechain group from DLH06 - # (OBIGT.csv uses updated values from LaRowe and Dick, 2012 (Geochim Cosmochim Acta 80, 70-91)) - mod.obigt("[Met]", G=-35245, H=-59310) - # also use parameters for [Gly] from DLH06 20190206 + # to reproduce, use superseded properties of [Met], [Gly], and [UPBB] (Dick et al., 2006) add.obigt("OldAA") lprop <- info(info("LYSC_CHICK")) expect_equal(G, lprop$G) Modified: pkg/CHNOSZ/tests/testthat/test-affinity.R =================================================================== --- pkg/CHNOSZ/tests/testthat/test-affinity.R 2019-02-06 17:29:09 UTC (rev 382) +++ pkg/CHNOSZ/tests/testthat/test-affinity.R 2019-02-07 01:19:55 UTC (rev 383) @@ -111,9 +111,7 @@ file <- system.file("extdata/protein/DS11.csv", package="CHNOSZ") aa <- read.csv(file, as.is=TRUE) ip <- add.protein(aa[1:5, ]) - # to reproduce, we need use the "old" parameters for [Met] from Dick et al., 2006 - mod.obigt("[Met]", G=-35245, H=-59310) - # also use parameters for [Gly] from DLH06 20190206 + # to reproduce, use superseded properties of [Met], [Gly], and [UPBB] (Dick et al., 2006) add.obigt("OldAA") a <- affinity(T=T, pH=pH, H2=H2, iprotein=ip) # divide A/2.303RT by protein length Modified: pkg/CHNOSZ/tests/testthat/test-ionize.aa.R =================================================================== --- pkg/CHNOSZ/tests/testthat/test-ionize.aa.R 2019-02-06 17:29:09 UTC (rev 382) +++ pkg/CHNOSZ/tests/testthat/test-ionize.aa.R 2019-02-07 01:19:55 UTC (rev 383) @@ -64,9 +64,7 @@ # digitized from Fig. 12 of Dick et al., 2006 G.AMY_BACSU.25 <- c(-24.9, -24.9, -24.7, -24.5, -24.4, -23.9, -23.5, -23.2) G.AMY_BACSU.100 <- c(-26.7, -26.7, -26.4, -26.1, -25.7, -25.1, -24.9, -24.9) - # calculate the Gibbs energies of the nonionized proteins using the same [Met] parameters as in the paper - mod.obigt("[Met]", G=-35245, H=-59310) - # also use parameters for [Gly] from DLH06 20190206 + # to reproduce the calculations in the paper, use superseded properties of [Met], [Gly], and [UPBB] add.obigt("OldAA") G.nonionized <- subcrt("AMY_BACSU", T=c(25, 100))$out[[1]]$G aa <- pinfo(pinfo("AMY_BACSU")) Modified: pkg/CHNOSZ/tests/testthat/test-protein.info.R =================================================================== --- pkg/CHNOSZ/tests/testthat/test-protein.info.R 2019-02-06 17:29:09 UTC (rev 382) +++ pkg/CHNOSZ/tests/testthat/test-protein.info.R 2019-02-07 01:19:55 UTC (rev 383) @@ -13,22 +13,18 @@ expect_equal(pinfo(c("LYSC_CHICK", "MYGPHYCA")), c(6, NA)) }) -# 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)", { + protein <- pinfo(c("CSG_METVO", "CSG_METJA")) + suppressMessages(add.obigt("OldAA")) + basis("CHNOS+") + suppressMessages(swap.basis("O2", "H2")) + pequil <- protein.equil(protein, loga.protein=-3) + # 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 Modified: pkg/CHNOSZ/vignettes/anintro.Rmd =================================================================== --- pkg/CHNOSZ/vignettes/anintro.Rmd 2019-02-06 17:29:09 UTC (rev 382) +++ pkg/CHNOSZ/vignettes/anintro.Rmd 2019-02-07 01:19:55 UTC (rev 383) @@ -1522,15 +1522,13 @@ logabundance <- unitize(log10(y$abundance[!ina]), pl) ``` -Now we can load the proteins and calculate their activities in metastable equilibrium as a function of `r logfO2`: -```{marginfigure} -The commented line uses `mod.obigt()` and `add.obigt()` to revert the parameters of the methionine and glycine sidechain groups to those present in older versions of CHNOSZ (Dick et al., 2006). -The current database, with parameters set by `data(thermo)` and used here, contains updated group additivity parameters for methionine (LaRowe and Dick, 2012). -``` +Now we can load the proteins and calculate their activities in metastable equilibrium as a function of `r logfO2`. +The commented line uses `add.obigt()` to revert the group additivity parameters to those present in older versions of CHNOSZ (Dick et al., 2006). +The current database, with parameters set by `data(thermo)` and used here, contains updated group additivity parameters for the sidechain groups of methionine (LaRowe and Dick, 2012) and glycine and the protein backbone [@Kit14]. + ```{r yeastplot, eval=FALSE, echo=1:6} par(mfrow = c(1, 3)) basis("CHNOS+") -#mod.obigt("[Met]", G = -35245, H = -59310) #add.obigt("OldAA") a <- affinity(O2 = c(-80, -73), iprotein = ip, loga.protein = logact) e <- equilibrate(a) @@ -1559,7 +1557,7 @@ ``` The minimum free energy difference occurs near `r logfO2` = -78. -This agrees with the assessment shown in Figure 4 of @Dic09 (note that the old parameters for the methionine sidechain group were used in that study). +This agrees with the assessment shown in Figure 4 of @Dic09 (but the updated group additivity parameters make the results slightly different). ## An affinity baseline Modified: pkg/CHNOSZ/vignettes/equilibrium.Rnw =================================================================== --- pkg/CHNOSZ/vignettes/equilibrium.Rnw 2019-02-06 17:29:09 UTC (rev 382) +++ pkg/CHNOSZ/vignettes/equilibrium.Rnw 2019-02-07 01:19:55 UTC (rev 383) @@ -714,13 +714,12 @@ For the CSG examples below, we would like to reproduce exactly the values appearing in publications. Because recent versions of CHNOSZ -incorporate data updates for the methionine and glycine sidechain -groups, we should therefore revert to the previous values \citep{DLH06} -before proceeding. +incorporate data updates for the protein backbone and methionine and +glycine sidechain groups, we should therefore revert to the previous +values \citep{DLH06} before proceeding. <>= data(thermo) -mod.obigt("[Met]", G=-35245, H=-59310) add.obigt("OldAA") @ Modified: pkg/CHNOSZ/vignettes/equilibrium.lyx =================================================================== --- pkg/CHNOSZ/vignettes/equilibrium.lyx 2019-02-06 17:29:09 UTC (rev 382) +++ pkg/CHNOSZ/vignettes/equilibrium.lyx 2019-02-07 01:19:55 UTC (rev 383) @@ -3112,9 +3112,9 @@ \begin_layout Standard For the CSG examples below, we would like to reproduce exactly the values appearing in publications. - Because recent versions of CHNOSZ incorporate data updates for the methionine - and glycine sidechain groups, we should therefore revert to the previous - values + Because recent versions of CHNOSZ incorporate data updates for the protein + backbone and methionine and glycine sidechain groups, we should therefore + revert to the previous values \begin_inset CommandInset citation LatexCommand citep key "DLH06" @@ -3141,11 +3141,6 @@ \begin_layout Plain Layout -mod.obigt("[Met]", G=-35245, H=-59310) -\end_layout - -\begin_layout Plain Layout - add.obigt( \begin_inset Quotes eld \end_inset Modified: pkg/CHNOSZ/vignettes/hotspring.Rnw =================================================================== --- pkg/CHNOSZ/vignettes/hotspring.Rnw 2019-02-06 17:29:09 UTC (rev 382) +++ pkg/CHNOSZ/vignettes/hotspring.Rnw 2019-02-07 01:19:55 UTC (rev 383) @@ -73,17 +73,16 @@ the code. Load CHNOSZ and the thermodynamic database. In order to reproduce -the calculations from the 2011 paper, we modify the methionine sidechain -group using old values of standard Gibbs energy and enthalpy from -\citep{DLH06}; these are inaccurate values that were updated by \citep{LD12} -and are available starting in CHNOSZ\_0.9-9 (the current values are -used further below). In addition, we load values for the glycine group -that were superseded in 2019. +the calculations from the 2011 paper, we load old values of standard +Gibbs energy and enthalpy of the methionine sidechain group from \citep{DLH06}; +these are inaccurate values that were updated by \citep{LD12} and +are available starting in CHNOSZ\_0.9-9 (the current values are used +further below). This step also loads values for the glycine group +and the protein backone {[}UPBB{]} that were superseded in 2019. <>= library(CHNOSZ) data(thermo) -mod.obigt("[Met]", G=-35245, H=-59310) add.obigt("OldAA") @ @@ -414,7 +413,7 @@ # use old [Met] for first row and new [Met] for second row if(j==2) { data(thermo) - add.obigt("OldAA") + add.obigt("OldAA", c("[Gly]", "[UPBB]")) ip.annot <- add.protein(aa.annot) } # setup basis species and proteins Modified: pkg/CHNOSZ/vignettes/hotspring.lyx =================================================================== --- pkg/CHNOSZ/vignettes/hotspring.lyx 2019-02-06 17:29:09 UTC (rev 382) +++ pkg/CHNOSZ/vignettes/hotspring.lyx 2019-02-07 01:19:55 UTC (rev 383) @@ -245,9 +245,9 @@ \begin_layout Standard Load CHNOSZ and the thermodynamic database. - In order to reproduce the calculations from the 2011 paper, we modify the - methionine sidechain group using old values of standard Gibbs energy and - enthalpy from + In order to reproduce the calculations from the 2011 paper, we load old + values of standard Gibbs energy and enthalpy of the methionine sidechain + group from \begin_inset CommandInset citation LatexCommand citep key "DLH06" @@ -265,8 +265,8 @@ and are available starting in CHNOSZ_0.9-9 (the current values are used further below). - In addition, we load values for the glycine group that were superseded - in 2019. + This step also loads values for the glycine group and the protein backone + [UPBB] that were superseded in 2019. \end_layout \begin_layout Standard @@ -290,11 +290,6 @@ \begin_layout Plain Layout -mod.obigt("[Met]", G=-35245, H=-59310) -\end_layout - -\begin_layout Plain Layout - add.obigt( \begin_inset Quotes eld \end_inset @@ -1820,7 +1815,23 @@ \begin_inset Quotes erd \end_inset -) +, c( +\begin_inset Quotes eld +\end_inset + +[Gly] +\begin_inset Quotes erd +\end_inset + +, +\begin_inset Quotes eld +\end_inset + +[UPBB] +\begin_inset Quotes erd +\end_inset + +)) \end_layout \begin_layout Plain Layout Modified: pkg/CHNOSZ/vignettes/vig.bib =================================================================== --- pkg/CHNOSZ/vignettes/vig.bib 2019-02-06 17:29:09 UTC (rev 382) +++ pkg/CHNOSZ/vignettes/vig.bib 2019-02-07 01:19:55 UTC (rev 383) @@ -223,6 +223,19 @@ doi = {10.1016/0098-3004(92)90029-Q}, } + at Article{Kit14, + author = {Kitadai, Norio}, + journal = {Journal of Molecular Evolution}, + title = {{T}hermodynamic prediction of glycine polymerization as a function of temperature and p{H} consistent with experimentally obtained results}, + year = {2014}, + volume = {78}, + number = {3-4}, + pages = {171--187}, + doi = {10.1007/s00239-014-9616-1}, + issn = {0022-2844}, + language = {English}, +} + @Article{LD12, author = {LaRowe, Douglas E. and Dick, Jeffrey M.}, journal = {Geochimica et Cosmochimica Acta}, From noreply at r-forge.r-project.org Thu Feb 7 07:43:10 2019 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Thu, 7 Feb 2019 07:43:10 +0100 (CET) Subject: [CHNOSZ-commits] r384 - in pkg/CHNOSZ: . R data demo inst inst/extdata/OBIGT man vignettes Message-ID: <20190207064311.0294F18BA88@r-forge.r-project.org> Author: jedick Date: 2019-02-07 07:43:08 +0100 (Thu, 07 Feb 2019) New Revision: 384 Added: pkg/CHNOSZ/demo/glycinate.R Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/R/examples.R pkg/CHNOSZ/data/refs.csv pkg/CHNOSZ/demo/00Index pkg/CHNOSZ/inst/NEWS pkg/CHNOSZ/inst/extdata/OBIGT/OldAA.csv pkg/CHNOSZ/inst/extdata/OBIGT/biotic_aq.csv.xz pkg/CHNOSZ/man/examples.Rd pkg/CHNOSZ/vignettes/obigt.Rmd pkg/CHNOSZ/vignettes/obigt.bib Log: add metal-glycinate complexes from Azadi et al., 2019 and demo/glycinate.R Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-07 01:19:55 UTC (rev 383) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-07 06:43:08 UTC (rev 384) @@ -1,6 +1,6 @@ Date: 2019-02-07 Package: CHNOSZ -Version: 1.1.3-91 +Version: 1.1.3-92 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/R/examples.R =================================================================== --- pkg/CHNOSZ/R/examples.R 2019-02-07 01:19:55 UTC (rev 383) +++ pkg/CHNOSZ/R/examples.R 2019-02-07 06:43:08 UTC (rev 384) @@ -27,8 +27,8 @@ } demos <- function(which=c("sources", "protein.equil", "affinity", "NaCl", "density", - "ORP", "revisit", "findit", "ionize", "buffer", "protbuff", "yeastgfp", "mosaic", - "copper", "solubility", "gold", "wjd", "bugstab", "Shh", "saturation", + "ORP", "revisit", "findit", "ionize", "buffer", "protbuff", "yeastgfp", "glycinate", + "mosaic", "copper", "solubility", "gold", "wjd", "bugstab", "Shh", "saturation", "adenine", "DEW", "lambda", "TCA", "go-IU", "bison"), save.png=FALSE) { # run one or more demos from CHNOSZ with ask=FALSE, and return the value of the last one for(i in 1:length(which)) { Modified: pkg/CHNOSZ/data/refs.csv =================================================================== --- pkg/CHNOSZ/data/refs.csv 2019-02-07 01:19:55 UTC (rev 383) +++ pkg/CHNOSZ/data/refs.csv 2019-02-07 06:43:08 UTC (rev 384) @@ -42,7 +42,7 @@ JUN92,"C. de Capitani",1992,"JUN92.bs database supplied with Theriak/Domino software","data as listed in `JUN92.bs` data file",http://titan.minpet.unibas.ch/minpet/theriak/theruser.html SPRONS92.1,"H. C. Helgeson et al.",1992,"sprons92.dat computer data file","titanite: @BH83 + "Gibbs free energies and enthalpies were corrected to be consistent with updated values of Gibbs free energies of Ca2+ and CO32- [@SH88] together with the solubilities of calcite and aragonite reported by @PB82 "", SPRONS92.2,"H. C. Helgeson et al.",1992,"sprons92.dat computer data file","Ca-bearing minerals; "Gibbs free energies and enthalpies were corrected to be consistent with updated values of Gibbs free energies of Ca2+ and CO32- [@SH88] together with the solubilities of calcite and aragonite reported by @PB82 "", -Sho92,"E. L. Shock",1992,"Geochim. Cosmochim. Acta 56, 3481-3491","diglycine, alanylglycine, leucylglycine, and diketopiperazine",https://doi.org/10.1016/0016-7037(92)90392-V +Sho92,"E. L. Shock",1992,"Geochim. Cosmochim. Acta 56, 3481-3491","diglycine, alanylglycine, leucylglycine, and diketopiperazine; not present in slop files after slop98.dat",https://doi.org/10.1016/0016-7037(92)90392-V ZS92,"C. Zhu and D. A. Sverjensky",1982,"Geochim. Cosmochim. Acta 56, 3435-3467","F,Cl,OH biotite and apatite endmembers. GHS and V were taken from Table 6 of @ZS92; heat capacity and volume parameters from `berman.dat`.",https://doi.org/10.1016/0016-7037(92)90390-5 Sho93,"E. L. Shock",1993,"Geochim. Cosmochim. Acta 57, 3341-3349","ethylacetate and acetamide",https://doi.org/10.1016/0016-7037(93)90542-5 Sho93.1,"E. L. Shock",1993,"Geochim. Cosmochim. Acta 57, 3341-3349","carbon monoxide and ethylene",https://doi.org/10.1016/0016-7037(93)90542-5 @@ -61,7 +61,7 @@ DPS+96,"I. Diakonov, G. Pokrovski et al.",1996,"Geochim. Cosmochim. Acta 60, 197-211",NaAl(OH)4,http://dx.doi.org/10.1016/0016-7037(95)00403-3 AH97b,"J. P. Amend and H. C. Helgeson",1997,"J. Chem. Soc., Faraday Trans. 93, 1927-1941","amino acids GHS",https://doi.org/10.1039/A608126F AH97b.1,"J. P. Amend and H. C. Helgeson",1997,"J. Chem. Soc., Faraday Trans. 93, 1927-1941","alanate and glycinate GHS",https://doi.org/10.1039/A608126F -AH97b.2,"J. P. Amend and H. C. Helgeson",1997,"J. Chem. Soc., Faraday Trans. 93, 1927-1941","glycine and glycinium GHS",https://doi.org/10.1039/A608126F +AH97b.2,"J. P. Amend and H. C. Helgeson",1997,"J. Chem. Soc., Faraday Trans. 93, 1927-1941","glycine, glycinium, and methionine GHS",https://doi.org/10.1039/A608126F DSM+97,"J. D. Dale, E. L. Shock et al.",1997,"Geochim. Cosmochim. Acta 61, 4017-4024",alkylphenols,https://doi.org/10.1016/S0016-7037(97)00212-3 DSM+97.1,"J. D. Dale, E. L. Shock et al.",1997,"Geochim. Cosmochim. Acta 61, 4017-4024","phenol, and cresol isomers",https://doi.org/10.1016/S0016-7037(97)00212-3 DSM+97.2,"J. D. Dale, E. L. Shock et al.",1997,"Geochim. Cosmochim. Acta 61, 4017-4024","dimethylphenol isomers",https://doi.org/10.1016/S0016-7037(97)00212-3 @@ -126,6 +126,7 @@ DLH06.3,"J. M. Dick, D. E. LaRowe and H. C. Helgeson",2006,"Biogeosciences 3, 311-336","glycine, [Gly], and [UPBB] HKF parameters",https://doi.org/10.5194/bg-3-311-2006 DLH06.4,"J. M. Dick, D. E. LaRowe and H. C. Helgeson",2006,"Biogeosciences 3, 311-336","methionine HKF parameters",https://doi.org/10.5194/bg-3-311-2006 DLH06.5,"J. M. Dick, D. E. LaRowe and H. C. Helgeson",2006,"Biogeosciences 3, 311-336","triglycine Cp, V, and HKF c1, c2, omega parameters",https://doi.org/10.5194/bg-3-311-2006 +DLH06.6,"J. M. Dick, D. E. LaRowe and H. C. Helgeson",2006,"Biogeosciences 3, 311-336","[Gly], [Met], and [UPBB]",https://doi.org/10.5194/bg-3-311-2006 LMR06,"D. Langmuir et al.",2006,"Geochim. Cosmochim. Acta 70, 2942-2956","scorodite and amorphous ferric arsenate: G",https://doi.org/10.1016/j.gca.2006.03.006 MNM+06,"J. Majzlan, A. Navrotsky et al.",2006,"Eur. J. Mineral. 18, 175-186","coquimbite, ferricopiapite, and rhomboclase",https://doi.org/10.1127/0935-1221/2006/0018-0175 Dic07,"J. M. Dick",2007,"Ph.D. Dissertation, Univ. of California","glutathione, cystine, and cystine sidechain", @@ -171,9 +172,10 @@ 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 CHNOSZ.3,"J. M. Dick",2017,"CHNOSZ package documentation","metal-amino acid complexes: GHS were recalculated by adding the differences between values from @SK95 and @AH97b for alanate or glycinate to the properties of the complexes reported by @SK95.",http://chnosz.net CHNOSZ.5,"J. M. Dick",2017,"CHNOSZ package documentation","AuCl4- renamed to AuCl4-3",http://chnosz.net -CHNOSZ.6,"J. M. Dick",2017,"CHNOSZ package documentation","dipeptides not included in slop files after slop98.dat",http://chnosz.net CHNOSZ.7,"J. M. Dick",2017,"CHNOSZ package documentation","charge of NpO2(Oxal), La(Succ)+, NH4(Succ)-, and NpO2(Succ) as listed by @PSK99",http://chnosz.net CHNOSZ.8,"J. M. Dick",2017,"CHNOSZ package documentation","Incorrect values of HKF a1--a4 parameters for [-CH2NH2] were printed in Table 6 of @DLH06; corrected values are used here.",http://chnosz.net +CHNOSZ.9,"J. M. Dick",2019,"CHNOSZ package documentation","recalculated values of Cp (those in @AKAE19 appear to be calculated using wrong sign on ω) and enthalpy (using ΔG=ΔH-TΔS and the entropies of the elements)",http://chnosz.net +CHNOSZ.10,"J. M. Dick",2019,"CHNOSZ package documentation","Tl(Gly) and Tl(Gly)2-: replace Ti with Tl",http://chnosz.net LCT17,"A. R. Lowe, J. S. Cox and P. R. Tremaine",2017,"J. Chem. Thermodynamics 112, 129-145","adenine HKF parameters",https://doi.org/10.1016/j.jct.2017.04.005 DEW17,"D. A. Sverjensky et al.",2017,"Deep Earth Water (DEW) spreadsheet","other data from Aqueous Species Table in spreadsheet (see detailed references there)",http://www.dewcommunity.org DEW17.1,"D. A. Sverjensky et al.",2017,"Deep Earth Water (DEW) spreadsheet","revised with new predicted a1 for ions",http://www.dewcommunity.org @@ -184,3 +186,4 @@ DEW17.103,"D. A. Sverjensky et al.",2017,"Deep Earth Water (DEW) spreadsheet","NaCl: revised with new predicted a1 for complex species",http://www.dewcommunity.org DEW17.104,"D. A. Sverjensky et al.",2017,"Deep Earth Water (DEW) spreadsheet","propanoate: Revised a1 from new delVn correlation for -1 ions",http://www.dewcommunity.org BDat17.1,"D. A. Sverjensky et al.",2017,"berman.dat file in SUPCRT92b.zip on the DEW website","antigorite: "Oct. 21, 2016: Revised volume coefficients consistent with @HDR06 and @YIY+14 "",http://www.dewcommunity.org/resources.html +AKAE19,"M. R. Azadi et al.",2019,"Fluid Phase Equilib. 480, 25-40","metal-glycinate complexes",https://doi.org/10.1016/j.fluid.2018.10.002 Modified: pkg/CHNOSZ/demo/00Index =================================================================== --- pkg/CHNOSZ/demo/00Index 2019-02-07 01:19:55 UTC (rev 383) +++ pkg/CHNOSZ/demo/00Index 2019-02-07 06:43:08 UTC (rev 384) @@ -10,6 +10,7 @@ buffer Minerals and aqueous species as buffers of hydrogen fugacity protbuff Chemical activities buffered by thiol peroxidases or sigma factors yeastgfp Subcellular locations: log fO2 - log aH2O and log a - log fO2 diagrams +glycinate Divalent and monovalent metal-glycinate complexes mosaic Eh-pH diagram for iron oxides, sulfides and carbonate with two sets of changing basis species copper Another example of mosaic(): complexation of copper with glycine species solubility Solubility of calcite and CO2(gas) as a function of pH Added: pkg/CHNOSZ/demo/glycinate.R =================================================================== --- pkg/CHNOSZ/demo/glycinate.R (rev 0) +++ pkg/CHNOSZ/demo/glycinate.R 2019-02-07 06:43:08 UTC (rev 384) @@ -0,0 +1,67 @@ +# CHNOSZ/demo/glycinate.R +# plot logK of metal-glycinate complexes +# 20190207 + +# divalent metals +di <- c("Cu+2", "Ni+2", "Co+2", "Mn+2", "Zn+2", "Cd+2") +# divalent metals with one glycinate +di1 <- c("Cu(Gly)+", "Ni(Gly)+", "Co(Gly)+", "Mn(Gly)+", "Zn(Gly)+", "Cd(Gly)+") +# divalent metals with two glycinates +di2 <- c("Cu(Gly)2", "Ni(Gly)2", "Co(Gly)2", "Mn(Gly)2", "Zn(Gly)2", "Cd(Gly)2") +# monovalent metals +mo <- c("Au+", "Ag+", "Na+", "Tl+", "Cu+") +# monovalent metals with one glycinate +mo1 <- c("Au(Gly)", "Ag(Gly)", "Na(Gly)", "Tl(Gly)", "Cu(Gly)") +# monovalent metals with two glycinates +mo2 <- c("Au(Gly)2-", "Ag(Gly)2-", "Na(Gly)2-", "Tl(Gly)2-", "Cu(Gly)2-") + +# set the temperature values +T <- seq(0, 150, 10) +# calculate the logKs using data from Azadi et al., 2019 +# doi:10.1016/j.fluid.2018.10.002 +logK_di1 <- logK_di2 <- logK_mo1 <- logK_mo2 <- list() +for(i in 1:length(di1)) logK_di1[[i]] <- subcrt(c(di[i], "glycinate", di1[i]), c(-1, -1, 1), T = T)$out$logK +for(i in 1:length(di2)) logK_di2[[i]] <- subcrt(c(di[i], "glycinate", di2[i]), c(-1, -2, 1), T = T)$out$logK +for(i in 1:length(mo1)) logK_mo1[[i]] <- subcrt(c(mo[i], "glycinate", mo1[i]), c(-1, -1, 1), T = T)$out$logK +for(i in 1:length(mo2)) logK_mo2[[i]] <- subcrt(c(mo[i], "glycinate", mo2[i]), c(-1, -2, 1), T = T)$out$logK + +# calculate the logKs for divalent metals using data from Shock and Koretsky, 1995 +# doi:10.1016/0016-7037(95)00058-8 +add.obigt("OldAA") +logK_di1_SK95 <- logK_di2_SK95 <- list() +for(i in 1:length(di1)) logK_di1_SK95[[i]] <- subcrt(c(di[i], "glycinate", di1[i]), c(-1, -1, 1), T = T)$out$logK +for(i in 1:length(di2)) logK_di2_SK95[[i]] <- subcrt(c(di[i], "glycinate", di2[i]), c(-1, -2, 1), T = T)$out$logK +data(thermo) + +# set up the plots +layout(matrix(1:6, byrow = TRUE, nrow = 2), widths = c(2, 2, 1)) +par(mar = c(4, 3.2, 2.5, 0.5), mgp = c(2, 1, 0), las = 1, cex = 0.8) +xlab <- axis.label("T") +ylab <- axis.label("logK") + +# first row: divalent metals +matplot(T, sapply(logK_di1, c), type = "l", lwd = 2, lty = 1, xlab = xlab, ylab = ylab) +matplot(T, sapply(logK_di1_SK95, c), type = "l", lwd = 2, lty = 2, add = TRUE) +legend(-5, 7.7, c("Azadi et al., 2019", "Shock and Koretsky, 1995"), lty = c(1, 2), bty = "n", cex = 1) +mtext(expression(M^"+2" + Gly^"-" == M*(Gly)^"+"), line = 0.5) +matplot(T, sapply(logK_di2, c), type = "l", lwd = 2, lty = 1, xlab = xlab, ylab = ylab) +matplot(T, sapply(logK_di2_SK95, c), type = "l", lwd = 2, lty = 2, add = TRUE) +legend(-5, 14, c("Azadi et al., 2019", "Shock and Koretsky, 1995"), lty = c(1, 2), bty = "n", cex = 1) +mtext(expression(M^"+2" + 2*Gly^"-" == M*(Gly)[2]), line = 0.5) +plot.new() +par(xpd = NA) +legend("right", as.expression(lapply(di, expr.species)), lty = 1, col = 1:6, bty = "n", cex = 1.2, lwd = 2) + +# add overall title +text(0, 1, "metal-\nglycinate\ncomplexes", cex = 1.3, font = 2) +par(xpd = FALSE) + +# second row: monovalent metals +matplot(T, sapply(logK_mo1, c), type = "l", lwd = 2, lty = 1, xlab = xlab, ylab = ylab) +mtext(expression(M^"+" + Gly^"-" == M*(Gly)), line = 0.5) +matplot(T, sapply(logK_mo2, c), type = "l", lwd = 2, lty = 1, xlab = xlab, ylab = ylab) +mtext(expression(M^"+" + 2*Gly^"-" == M*(Gly)[2]^"-"), line = 0.5) +plot.new() +par(xpd = NA) +legend("right", as.expression(lapply(mo, expr.species)), lty = 1, col = 1:5, bty = "n", cex = 1.2, lwd = 2) +par(xpd = FALSE) Modified: pkg/CHNOSZ/inst/NEWS =================================================================== --- pkg/CHNOSZ/inst/NEWS 2019-02-07 01:19:55 UTC (rev 383) +++ pkg/CHNOSZ/inst/NEWS 2019-02-07 06:43:08 UTC (rev 384) @@ -1,4 +1,4 @@ -CHANGES IN CHNOSZ 1.1.3-91 (2019-02-07) +CHANGES IN CHNOSZ 1.1.3-92 (2019-02-07) --------------------------------------- BUG FIXES @@ -101,6 +101,9 @@ limits for calcite, dolomite, magnesite, and brucite in the H2O-CO2-CaO-MgO-SiO2 system. +- Add demo/glycinate.R showing logK of complexation of glycinate with + divalent and monovalent metals. + THERMODYNAMIC DATA - The Berman data (Berman, 1988 and later additions) have replaced the @@ -170,9 +173,13 @@ ions), and diketopiperazine, [Gly] and [UPBB] groups from Kitadai, 2014. +- Add data for metal-glycinate complexes from Azadi et al., 2019, + superseding Shock and Koretsky, 1995. + - For reproducing previous calculations, superseded data for [Gly] and [UPBB], as well as [Met] (earlier superseded by LaRowe and Dick, - 2012), have been moved to OBIGT/OldAA.csv. + 2012), and metal-glycinate complexes have been moved to + OBIGT/OldAA.csv. DIAGRAMS Modified: pkg/CHNOSZ/inst/extdata/OBIGT/OldAA.csv =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/OldAA.csv 2019-02-07 01:19:55 UTC (rev 383) +++ pkg/CHNOSZ/inst/extdata/OBIGT/OldAA.csv 2019-02-07 06:43:08 UTC (rev 384) @@ -1,14 +1,14 @@ 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 -alanylglycine,NA,C5H10N2O3,aq,Sho92,CHNOSZ.6,28.Feb.92,-116730,-186110,50.7,60.3,95.22,14.6503,21.164,12.0751,-3.6538,54.7374,0.7979,-0.4278,0 -leucylglycine,NA,C8H16N2O3,aq,Sho92,CHNOSZ.6,27.Aug.06,-110620,-202660,72.6,118.8,145.34,21.3967,34.6501,13.1805,-4.2113,98.6389,6.4783,-0.7594,0 -diglycine,NA,C4H8N2O3,aq,Sho92,CHNOSZ.6,28.Feb.92,-117020,-175640,54.2,38,76.27,12.0393,15.9447,11.6466,-3.4381,36.349,-1.3673,-0.4808,0 -diketopiperazine,NA,C4H6N2O2,aq,Sho92,CHNOSZ.6,28.Feb.92,-57440,-99300,53.5,17,76.73,12.1058,16.0764,11.6608,-3.4435,19.5904,-3.4064,-0.4702,0 -glycine,Gly,C2H5NO2,aq,"AH97b.2 [S07]","DLH06.1 [S07]",25.Aug.06,-90950,-124780,39.29,9.3,43.2,11.3,0.71,3.99,-3.04,28.5,-8.4,0.23,0 -glycinium,Gly+,C2H6NO2+,aq,"AH97b.2 [S07]","DLH06.1 [S07]",25.Aug.06,-94160,-125720,46.91,40,56.4,19.57,-7.58,-40.35,5.41,49,-1.8,0.59,0 -methionine,Met,C5H11NO2S,aq,AH97b,DLH06,25.Aug.06,-120120,-178520,62.36,70.7,105.4,24.95,6.9,13.59,-7.77,85.3,-6.6,0.13,0 -[Gly],NA,H,aq,"DLH06 [S15]",NA,25.Aug.06,-6075,-5570,17.31,11.371,9.606,1.83,2.57,1.22,-1.27,6.9,2.2,0,0 -[Met],NA,C3H7S,aq,DLH06,NA,25.Aug.06,-35245,-59310,40.38,72.739,71.832,15.48,8.76,10.82,-6,63.7,4,-0.1,0 -[UPBB],NA,C2H2NO,aq,"DLH06 [S15]",NA,25.Aug.06,-21436,-45220,1.62,-4.496,26.296,8.1,-3.75,-6.73,1.13,11.2,-7.5,0.05,0 +alanylglycine,NA,C5H10N2O3,aq,Sho92 [S98],NA,28.Feb.92,-116730,-186110,50.7,60.3,95.22,14.6503,21.164,12.0751,-3.6538,54.7374,0.7979,-0.4278,0 +leucylglycine,NA,C8H16N2O3,aq,Sho92 [S98],NA,27.Aug.06,-110620,-202660,72.6,118.8,145.34,21.3967,34.6501,13.1805,-4.2113,98.6389,6.4783,-0.7594,0 +diglycine,NA,C4H8N2O3,aq,Sho92 [S98],NA,28.Feb.92,-117020,-175640,54.2,38,76.27,12.0393,15.9447,11.6466,-3.4381,36.349,-1.3673,-0.4808,0 +diketopiperazine,NA,C4H6N2O2,aq,Sho92 [S98],NA,28.Feb.92,-57440,-99300,53.5,17,76.73,12.1058,16.0764,11.6608,-3.4435,19.5904,-3.4064,-0.4702,0 +glycine,Gly,C2H5NO2,aq,AH97b.2,DLH06.1,25.Aug.06,-90950,-124780,39.29,9.3,43.2,11.3,0.71,3.99,-3.04,28.5,-8.4,0.23,0 +glycinium,Gly+,C2H6NO2+,aq,AH97b.2,DLH06.1,25.Aug.06,-94160,-125720,46.91,40,56.4,19.57,-7.58,-40.35,5.41,49,-1.8,0.59,0 +methionine,Met,C5H11NO2S,aq,AH97b.2,DLH06.1,25.Aug.06,-120120,-178520,62.36,70.7,105.4,24.95,6.9,13.59,-7.77,85.3,-6.6,0.13,0 +[Gly],NA,H,aq,DLH06.6,NA,25.Aug.06,-6075,-5570,17.31,11.371,9.606,1.83,2.57,1.22,-1.27,6.9,2.2,0,0 +[Met],NA,C3H7S,aq,DLH06.6,NA,25.Aug.06,-35245,-59310,40.38,72.739,71.832,15.48,8.76,10.82,-6,63.7,4,-0.1,0 +[UPBB],NA,C2H2NO,aq,DLH06.6,NA,25.Aug.06,-21436,-45220,1.62,-4.496,26.296,8.1,-3.75,-6.73,1.13,11.2,-7.5,0.05,0 alanate,NA,C3H6NO2-,aq,"SK95.1 [S98]",AH97b.1,3.Sep.06,-75360,-121470,30.71,17.8,61.88,10.6281,17.3648,0.6505,-3.4968,12.685,-4.1859,1.17,-1 glycinate,NA,C2H4NO2-,aq,"SK95.1 [S98]",AH97b.1,3.Sep.06,-77610,-114190,30.07,-6.6,43.77,8.1592,11.7696,1.921,-3.2655,12.9389,-4.1859,1.1975,-1 Ca(Gly)+,NA,Ca(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-211570,-240519,34.375,59.3,32.6,6.2431,7.4595,2.8241,-3.0873,41.4246,9.0464,0.0543,1 Modified: pkg/CHNOSZ/inst/extdata/OBIGT/biotic_aq.csv.xz =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/biotic_aq.csv.xz 2019-02-07 01:19:55 UTC (rev 383) +++ pkg/CHNOSZ/inst/extdata/OBIGT/biotic_aq.csv.xz 2019-02-07 06:43:08 UTC (rev 384) @@ -1,4 +1,4 @@ -?7zXZ???F!t/?????0]7I??b???9??????TB;q?"?q???cL;?"??I?,t?b?PK??7?t(?em?A-P?Q?]?? ??8?.f?|?????V[?????=??K????VTm??~vw? ?2/ ??Wa???s?-?????p?lVs????H???u???? ?%?XF??k#??????????+??(??m5?St5?Fa?a??jN??8????>z???3MwS?%??????+?3x??`cw`?; $? (???????P?>????>?1b???QA??????>6o?=?-?((??pN???i????VOL?A???9 c?E3??XP?? ??kj?s?????Y!&o??w(??3?+?"???????; ??R6eW????![?????r?O>O?*?h\t????ty??)B????n<?9l?N!3???z '???}???nV?,0uVe??????? j?????|B??d^7&KK?- @@ -88,4 +88,11 @@ ???^V??4?-o???K{??????1<7? c?O_??2??? &r.w ??????#F5?V?v}8??@??t????a??? ??'@??;???e3????F?@m}?+/??u*?|0?]?M?=???;? eu+??]???%?????!d"??????.? ????8?????n????)???D??M?? -D???E??;y9???.?????? ??o;[???5K??V???4Y(?^|???`????`?????3?{I????,?:??w?W?Op???-1??b^?????=? ???O?*?YmEUu??????????\?E?`??Zt8g??5n????1????Mg#??l??.???n?????+ pOYE?v??f??u4uV?}J?i???E?w?y`?m???9ma?i??????o??R?>?&f?7??;??????=l??H????&E??&L?(?????L?4????(?d???I??N-/E??b?9??:???d??6Dl?????"_;o???s??wq??v?0?_???_%?W??????`??+M????g?YZ \ No newline at end of file +D???E??;y9???.?????? ??o;[???5K??V???4Y(?^|???`????`?????3?{I????,?:??w?W?Op???-1??b^?????=? ???O?*?YmEUu??????????\?E?`??Zt8g??5n????1????Mg#??l??.???n?????+ pOYE?v??f??u4uV?}J?i???E?w?y`?m???9ma?i??????o??R?>?&f?7??;??????=l??H????&E??&L?(?????L?4????(?d???I??N-/E??b?9??:???d??6Dl?????"_;o???s??wq??v?0?_??Cm{???)PiT? +U???-?*??]??d]=??WP +?#????5}x$?????b?Ak???9????4?????s??GbAi?????? Im??to??sQ?3~$??????tO?+?u#Fk??:????<0jX?????P(???2f????!F??????!????????????????????l???tE???\????%???]??[fa??w??s?}]t??5zw?t?V???N?-???8?T;E?o/R? ?|Iy??O??????6Y??f???g???%Jj?y???????I??{(1F?????p_p?8iyE?g?&?u_??2???}???????.??/]? ?V??`DFj?n?[?P?6!?Y?????,?}C?=??&:?:???}B?x?$????F???f??qwY??!??^??P?a?? +2?? ??J???H??p?????}?l?}?p?4P????????h,???V?Pn?i.??sy?M?????@*??~?????????qe'?G???/]?viZ?`q???aC,???t?[?Bg{a??-?????B*?_^i???=E???.?L Tf?V9?Q??'e??[O??????kx?y???3?<$???f_?????D??>k`add.obigt("SLOP98")` to load the data.\n\n') +cat('These species, taken from the slop98 data file, were present in earlier versions of CHNOSZ but have been replaced by or are incompatible with later updates. The data are kept here for comparative purposes. Use `add.obigt("SLOP98")` to load the data.\n\n') ``` ```{r optreflist, results="asis", echo=FALSE} @@ -243,7 +243,7 @@ ### `r setfile("OldAA.csv")` ```{r OldAA, results="asis", echo=FALSE} -cat('Data for these amino acids and related species were present in earlier versions of CHNOSZ but have been replaced by or are inconsistent with later updates [@Kit14]. The data are kept here to reproduce published calculations and for comparison with newer data. Use `add.obigt("OldAA")` to load the data.\n\n') +cat('Data for these amino acids and related species were present in earlier versions of CHNOSZ but have been replaced by or are incompatible with later updates [@LD12; @Kit14; @AKAE19]. The data are kept here to reproduce published calculations and for comparison with newer data. Use `add.obigt("OldAA")` to load the data.\n\n') ``` ```{r optreflist, results="asis", echo=FALSE} Modified: pkg/CHNOSZ/vignettes/obigt.bib =================================================================== --- pkg/CHNOSZ/vignettes/obigt.bib 2019-02-07 01:19:55 UTC (rev 383) +++ pkg/CHNOSZ/vignettes/obigt.bib 2019-02-07 06:43:08 UTC (rev 384) @@ -272,7 +272,6 @@ doi = {10.1007/s00239-014-9616-1}, issn = {0022-2844}, language = {English}, - publisher = {Springer US}, } @Article{LD12, @@ -1260,6 +1259,17 @@ url = {http://www.ingentaconnect.com/content/10.1127/0935-1221/2010/0022-2021}, } + at Article{AKAE19, + author = {M.R. Azadi and A. Karrech and M. Attar and M. Elchalakani}, + journal = {Fluid Phase Equilibria}, + title = {{D}ata analysis and estimation of thermodynamic properties of aqueous monovalent metal-glycinate complexes}, + year = {2019}, + volume = {480}, + pages = {25--40}, + doi = {10.1016/j.fluid.2018.10.002}, + issn = {0378-3812}, +} + @Article{AZ10, author = {Akinfiev, N. N. and Zotov, A. V.}, journal = {Geochemistry International}, From noreply at r-forge.r-project.org Fri Feb 8 04:57:39 2019 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Fri, 8 Feb 2019 04:57:39 +0100 (CET) Subject: [CHNOSZ-commits] r385 - in pkg/CHNOSZ: . data inst inst/extdata/OBIGT tests/testthat vignettes Message-ID: <20190208035739.8156A18CA2F@r-forge.r-project.org> Author: jedick Date: 2019-02-08 04:57:38 +0100 (Fri, 08 Feb 2019) New Revision: 385 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/data/refs.csv pkg/CHNOSZ/inst/CHECKLIST pkg/CHNOSZ/inst/NEWS pkg/CHNOSZ/inst/extdata/OBIGT/SLOP98.csv pkg/CHNOSZ/inst/extdata/OBIGT/biotic_aq.csv.xz pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_aq.csv.xz pkg/CHNOSZ/tests/testthat/test-recalculate.R pkg/CHNOSZ/tests/testthat/test-revisit.R pkg/CHNOSZ/vignettes/obigt.bib Log: OBIGT: recalculate GHS of HSiO3- Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-07 06:43:08 UTC (rev 384) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-08 03:57:38 UTC (rev 385) @@ -1,6 +1,6 @@ -Date: 2019-02-07 +Date: 2019-02-08 Package: CHNOSZ -Version: 1.1.3-92 +Version: 1.1.3-93 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/data/refs.csv =================================================================== --- pkg/CHNOSZ/data/refs.csv 2019-02-07 06:43:08 UTC (rev 384) +++ pkg/CHNOSZ/data/refs.csv 2019-02-08 03:57:38 UTC (rev 385) @@ -43,6 +43,7 @@ SPRONS92.1,"H. C. Helgeson et al.",1992,"sprons92.dat computer data file","titanite: @BH83 + "Gibbs free energies and enthalpies were corrected to be consistent with updated values of Gibbs free energies of Ca2+ and CO32- [@SH88] together with the solubilities of calcite and aragonite reported by @PB82 "", SPRONS92.2,"H. C. Helgeson et al.",1992,"sprons92.dat computer data file","Ca-bearing minerals; "Gibbs free energies and enthalpies were corrected to be consistent with updated values of Gibbs free energies of Ca2+ and CO32- [@SH88] together with the solubilities of calcite and aragonite reported by @PB82 "", Sho92,"E. L. Shock",1992,"Geochim. Cosmochim. Acta 56, 3481-3491","diglycine, alanylglycine, leucylglycine, and diketopiperazine; not present in slop files after slop98.dat",https://doi.org/10.1016/0016-7037(92)90392-V +Sho92.1,"E. L. Shock",1992,"Geochim. Cosmochim. Acta 56, 3481-3491","diketopiperazine GHS",https://doi.org/10.1016/0016-7037(92)90392-V ZS92,"C. Zhu and D. A. Sverjensky",1982,"Geochim. Cosmochim. Acta 56, 3435-3467","F,Cl,OH biotite and apatite endmembers. GHS and V were taken from Table 6 of @ZS92; heat capacity and volume parameters from `berman.dat`.",https://doi.org/10.1016/0016-7037(92)90390-5 Sho93,"E. L. Shock",1993,"Geochim. Cosmochim. Acta 57, 3341-3349","ethylacetate and acetamide",https://doi.org/10.1016/0016-7037(93)90542-5 Sho93.1,"E. L. Shock",1993,"Geochim. Cosmochim. Acta 57, 3341-3349","carbon monoxide and ethylene",https://doi.org/10.1016/0016-7037(93)90542-5 @@ -122,10 +123,10 @@ LH06b.1,"D. E. LaRowe and H. C. Helgeson",2006,"Thermochim. Acta 448, 82-106","pyridine and piperidine",https://doi.org/10.1016/j.tca.2006.06.008 DLH06,"J. M. Dick, D. E. LaRowe and H. C. Helgeson",2006,"Biogeosciences 3, 311-336","amino acid, protein, and organic groups",https://doi.org/10.5194/bg-3-311-2006 DLH06.1,"J. M. Dick, D. E. LaRowe and H. C. Helgeson",2006,"Biogeosciences 3, 311-336","amino acids HKF parameters",https://doi.org/10.5194/bg-3-311-2006 -DLH06.2,"J. M. Dick, D. E. LaRowe and H. C. Helgeson",2006,"Biogeosciences 3, 311-336","Gly-X-Gly tripeptides Cp, V, and HKF c1, c2, omega parameters",https://doi.org/10.5194/bg-3-311-2006 +DLH06.2,"J. M. Dick, D. E. LaRowe and H. C. Helgeson",2006,"Biogeosciences 3, 311-336","Gly-X-Gly tripeptides Cp, V, and HKF c1, c2, ω parameters",https://doi.org/10.5194/bg-3-311-2006 DLH06.3,"J. M. Dick, D. E. LaRowe and H. C. Helgeson",2006,"Biogeosciences 3, 311-336","glycine, [Gly], and [UPBB] HKF parameters",https://doi.org/10.5194/bg-3-311-2006 DLH06.4,"J. M. Dick, D. E. LaRowe and H. C. Helgeson",2006,"Biogeosciences 3, 311-336","methionine HKF parameters",https://doi.org/10.5194/bg-3-311-2006 -DLH06.5,"J. M. Dick, D. E. LaRowe and H. C. Helgeson",2006,"Biogeosciences 3, 311-336","triglycine Cp, V, and HKF c1, c2, omega parameters",https://doi.org/10.5194/bg-3-311-2006 +DLH06.5,"J. M. Dick, D. E. LaRowe and H. C. Helgeson",2006,"Biogeosciences 3, 311-336","triglycine Cp, V, and HKF c1, c2, ω parameters",https://doi.org/10.5194/bg-3-311-2006 DLH06.6,"J. M. Dick, D. E. LaRowe and H. C. Helgeson",2006,"Biogeosciences 3, 311-336","[Gly], [Met], and [UPBB]",https://doi.org/10.5194/bg-3-311-2006 LMR06,"D. Langmuir et al.",2006,"Geochim. Cosmochim. Acta 70, 2942-2956","scorodite and amorphous ferric arsenate: G",https://doi.org/10.1016/j.gca.2006.03.006 MNM+06,"J. Majzlan, A. Navrotsky et al.",2006,"Eur. J. Mineral. 18, 175-186","coquimbite, ferricopiapite, and rhomboclase",https://doi.org/10.1127/0935-1221/2006/0018-0175 @@ -162,7 +163,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","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 +SLOP15.7,"E. L. Shock et al.",2015,"slop15.dat computer data file","hexanol, heptanol, and octanol: "Minor differences in Gibbs energy, entropy, ω, 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",https://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",https://doi.org/10.1016/j.gca.2016.08.028 ZZL+16,"K. Zimmer et al.",2016,"Comp. Geosci. 90, 97-111","data listed in spronsbl.dat",https://doi.org/10.1016/j.cageo.2016.02.013 @@ -176,6 +177,7 @@ CHNOSZ.8,"J. M. Dick",2017,"CHNOSZ package documentation","Incorrect values of HKF a1--a4 parameters for [-CH2NH2] were printed in Table 6 of @DLH06; corrected values are used here.",http://chnosz.net CHNOSZ.9,"J. M. Dick",2019,"CHNOSZ package documentation","recalculated values of Cp (those in @AKAE19 appear to be calculated using wrong sign on ω) and enthalpy (using ΔG=ΔH-TΔS and the entropies of the elements)",http://chnosz.net CHNOSZ.10,"J. M. Dick",2019,"CHNOSZ package documentation","Tl(Gly) and Tl(Gly)2-: replace Ti with Tl",http://chnosz.net +CHNOSZ.11,"J. M. Dick",2019,"CHNOSZ package documentation","HSiO3-: GHS recalculated by adding difference from SiO2 [@SSH97] to updated values for SiO2 [@AS04]",http://chnosz.net LCT17,"A. R. Lowe, J. S. Cox and P. R. Tremaine",2017,"J. Chem. Thermodynamics 112, 129-145","adenine HKF parameters",https://doi.org/10.1016/j.jct.2017.04.005 DEW17,"D. A. Sverjensky et al.",2017,"Deep Earth Water (DEW) spreadsheet","other data from Aqueous Species Table in spreadsheet (see detailed references there)",http://www.dewcommunity.org DEW17.1,"D. A. Sverjensky et al.",2017,"Deep Earth Water (DEW) spreadsheet","revised with new predicted a1 for ions",http://www.dewcommunity.org Modified: pkg/CHNOSZ/inst/CHECKLIST =================================================================== --- pkg/CHNOSZ/inst/CHECKLIST 2019-02-07 06:43:08 UTC (rev 384) +++ pkg/CHNOSZ/inst/CHECKLIST 2019-02-08 03:57:38 UTC (rev 385) @@ -26,6 +26,8 @@ - check reverse dependencies: ecipex and canprot packages +- vignettes/obigt.bib: check correct year for CHNOSZ reference + - documentation links: after installation, run doc/mklinks.sh and insert the modified anintro.html in the package Modified: pkg/CHNOSZ/inst/NEWS =================================================================== --- pkg/CHNOSZ/inst/NEWS 2019-02-07 06:43:08 UTC (rev 384) +++ pkg/CHNOSZ/inst/NEWS 2019-02-08 03:57:38 UTC (rev 385) @@ -1,4 +1,4 @@ -CHANGES IN CHNOSZ 1.1.3-92 (2019-02-07) +CHANGES IN CHNOSZ 1.1.3-93 (2019-02-08) --------------------------------------- BUG FIXES @@ -162,13 +162,21 @@ - Update aqueous Au species with data from Akinfiev and Zotov, 2001 and 2010, and Pokrovski et al., 2014. -- Move superseded data for aqueous Au species to SLOP98.csv. +- Move SUPCRTBL updates (As and Al minerals and aqueous species and + SiO2(aq)) into default database. -- Move SUPCRTBL updates into default database. +- Values for SiO2(aq) are taken from Apps and Spycher, 2004. Thanks + to John Apps for providing the document. -- Add test-recalculate.R to check that some recalculated values are - correctly entered in OBIGT. +- Recalculate GHS for HSiO3- by adding difference from SiO2(aq) + (Sverjensky et al., 1997) to updated values for SiO2(aq). +- Add test-recalculate.R to check that recalculated values are correctly + entered in OBIGT. + +- Move superseded data for aqueous Au, As, and Al species, SiO2 and + HSiO3- to OBIGT/SLOP98.csv. + - Add or update glycine, diglycine, and triglycine (zwitterions and ions), and diketopiperazine, [Gly] and [UPBB] groups from Kitadai, 2014. Modified: pkg/CHNOSZ/inst/extdata/OBIGT/SLOP98.csv =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/SLOP98.csv 2019-02-07 06:43:08 UTC (rev 384) +++ pkg/CHNOSZ/inst/extdata/OBIGT/SLOP98.csv 2019-02-08 03:57:38 UTC (rev 385) @@ -16,6 +16,7 @@ AsO2-,AsO2-,AsO2-,aq,"SSWS97.3 [S98]",NA,11.Nov.97,-83650,-102540,9.7,-28,6.9,3.2101,0.0554,5.7305,-2.7812,3.4104,-8.7381,1.482,-1 HAsO2,HAsO2,HAsO2,aq,"SSWS97.3 [S98]",NA,11.Nov.97,-96240,-109110,30.1,2.9,28.3,5.5984,5.8913,3.428,-3.0224,6.799,-2.4438,-0.1158,0 SiO2,NA,SiO2,aq,"SHS89.1 [S92]",NA,13.Jan.89,-199190,-209775,18,-76.1,16.1,1.9,1.7,20,-2.7,29.1,-51.2,0.1291,0 +HSiO3-,HSiO3-,HSiO3-,aq,"SSH97 [S98]",NA,18.Sep.97,-242801,-273872,5,-21,5,2.9735,-0.5158,5.9467,-2.7575,8.1489,-7.3123,1.5511,-1 AlO2-,AlO2-,AlO2-1,aq,"SSWS97.4 [S98]",NA,07.Nov.97,-198693,-222125,-7.22,-11.9,10,3.7221,3.9954,-1.5879,-2.9441,15.2391,-5.4585,1.7418,-1 Al+3,Al+3,Al+3,aq,"SSWS97.4 [S98]",NA,07.Nov.97,-115609,-126834,-77.7,-32.5,-44.4,-3.3802,-17.0071,14.5185,-2.0758,10.7,-8.06,2.753,3 AlOH+2,AlOH+2,AlOH+2,aq,"SSWS97.4 [S98]",NA,13.Nov.97,-165475,-183300,-44.2,13.2,-2.2,2.0469,-2.7813,6.8376,-2.6639,29.7923,-0.3457,1.7247,2 Modified: pkg/CHNOSZ/inst/extdata/OBIGT/biotic_aq.csv.xz =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/biotic_aq.csv.xz 2019-02-07 06:43:08 UTC (rev 384) +++ pkg/CHNOSZ/inst/extdata/OBIGT/biotic_aq.csv.xz 2019-02-08 03:57:38 UTC (rev 385) @@ -1,4 +1,4 @@ -?7zXZ???F!t/????u4]7I??b???9??????TB;q?"?q???cL;?"??I?,t?b?PK??7?t(?em?A-P?Q?]?? ??8?.f?|?????V[?????=??K????VTm??~vw? ?2/ ??Wa???s?-?????p?lVs????H???u???? ?%?XF??k#??????????+??(??m5?St5?Fa?a??jN??8????>z???3MwS?%??????+?3x??`cw`?; $? (???????P?>????>?1b???QA??????>6o?=?-?((??pN???i????VOL?A???9 c?E3??XP?? ??kj?s?????Y!&o??w(??3?+?"???????; ??R6eW????![?????r?O>O?*?h\t????ty??)B????n<?9l?N!3???z '???}???nV?,0uVe??????? j?????|B??d^7&KK?- @@ -88,11 +88,9 @@ ???^V??4?-o???K{??????1<7? c?O_??2??? &r.w ??????#F5?V?v}8??@??t????a??? ??'@??;???e3????F?@m}?+/??u*?|0?]?M?=???;? eu+??]???%?????!d"??????.? ????8?????n????)???D??M?? -D???E??;y9???.?????? ??o;[???5K??V???4Y(?^|???`????`?????3?{I????,?:??w?W?Op???-1??b^?????=? ???O?*?YmEUu??????????\?E?`??Zt8g??5n????1????Mg#??l??.???n?????+ pOYE?v??f??u4uV?}J?i???E?w?y`?m???9ma?i??????o??R?>?&f?7??;??????=l??H????&E??&L?(?????L?4????(?d???I??N-/E??b?9??:???d??6Dl?????"_;o???s??wq??v?0?_??Cm{???)PiT? -U???-?*??]??d]=??WP -?#????5}x$?????b?Ak???9????4?????s??GbAi?????? Im??to??sQ?3~$??????tO?+?u#Fk??:????<0jX?????P(???2f????!F??????!????????????????????l???tE???\????%???]??[fa??w??s?}]t??5zw?t?V???N?-???8?T;E?o/R? ?|Iy??O??????6Y??f???g???%Jj?y???????I??{(1F?????p_p?8iyE?g?&?u_??2???}???????.??/]? ?V??`DFj?n?[?P?6!?Y?????,?}C?=??&:?:???}B?x?$????F???f??qwY??!??^??P?a?? -2?? ??J???H??p?????}?l?}?p?4P????????h,???V?Pn?i.??sy?M?????@*??~?????????qe'?G???/]?viZ?`q???aC,???t?[?Bg{a??-?????B*?_^i???=E???.?L Tf?V9?Q??'e??[O??????kx?y???3?<$???f_?????D??>k?&f?7??;??????=l??H????&E??&L?(?????L?4????(?d???I??N-/E??b?9??:???e??-????U?5\??.????5?:]?a?&??As??y'g[??%ay????Q??2?B/?7?????"?L& ???]Jj?>^?0???^Z??_?n?????B??g2Vw???s?$:??K*??[?#????b?7'= +Mrv?d^???%cc!2???2?_r???=yJ??? ?WH????!D?5??`?8?D?H????^yJ?????Xs???Qv-G???\??V!K??R????G????U?Q??;9~h???N?k?zhj??H?-^???iZ???/???J@?T?;? ???7?2????EU???????????4??P{?>????co#??gU????d?A0D[???????0????@_?z0??3?N??j[( +??????3k????}r?&j1Vg?qz??? $????????|c?%|M>-Y???f?$??? ?4?~^:?(?Bu2?I???W{?e????z?????R?Z????????????T?????/G)6???!?]t??$;??36 ?T?6??>&u????? 3??????|??=?p?x?^?y;u????=???????B???}?T????u?V??q 4?C?LfZ?/?I???:???toT???g???i.??????????4?????x?A?A??c??[t?p?g????,???YZ?R-?%T(?p?^?w???+?)BFD?>+?Qa??i??3????h7????~4?r+?\1?b????p?? ?;7?J??H???????R -?T?I?7???4??e????[.?V?????~G?Y??tA?e?G2?:`?J?W?5.??jK?*?x????7????}???^???[ ?0???a? w???&?????/l:? ?}J?4??|?f???b?o????????A?????.??pwRq?Y????XW@???>?j???? ::jZ_?_4%H|??0/_????%c?,:???5?s???$??&???QE2 -? -?D?k?g?Hg=7:5?\?!v?$S??????Ins????Z?9WB???`??c??rk??7?????????Dt)QU)?k?EW@?OeOVW?WS?H?!?\?????????????z?uU?Z?=?oE?4Z;,????1??,????? ???tR?Yyz??eUQg???wi?Ce?8[?u%??????%????)??? ?\=s???O?Z#?8,?(}?&??W,????? ?????G??[?q?Xb???????-???x?D?? t??J?S?b??:???T??N9???D[?SA?3?D-?????????H??7{b??E9???\???????SRj??y??+??U???_eb?????????L???????\?M??Pf_??h^R?l?I2?kj?>142?8?I y???#$?D? -????!?k?yi??O? ???:^?2`d?aY'?????n?`???jL5?]?vZ??K???????h?8:???8?m?'????7 -j7q?????????~??U[??|=L~-l?k?.y??Sh6?0?R?????F????Q????Dck{ -??2N??b?V8?T_R"?EBj??EE=fk_??nv??"K@?9?Q???u`???U?~RG????;+?'?????{?W'?Cg ?3(?_j?(^L1z?D3?? -?????n?? !;?D?R???DjhV??!??V_??^?wpD??W?H?|3???7b?]??R?7j^c?;??q?w?8n????F^??4?(?B`???? -?7?(?-)}????Y??Z????S????Q?f?tJ??p?[',^???J?;?u??7???s?CY???-. ??_???????5?I??l[???n{g????:/?D??!?c?Y? -??????????#?????q?x??(E?ZVL/=?*/>?U7?l -??P??(?`,I??7cW??????1?uIOjb????cx???gM_? ??????0?a?/zE&gK?a\?M`Y?1?o??l?n?k?=??H??W??-?U6?hS?FN?W? ??4??????n??W=_???l???f?+Any?c??d?? -??Z?SS?r?N?3?`c??a?'?c??o(?.Rt?l?D-?? V?@????zt??|/?m?B???f*????n ??+S:L??????v??/v??[?6???/%2??v?l N?w?:?rk???1??K?=?c[!?g??rBH???C???Pv???o{????wM???Ou]?k???w? -ko???W?g4??Z?!?*w?K?^?#IT?}?E??o?b?f? -????????3;?"?e6Vy????dw?h?d??5??\?&*%8z??P0???%?!????r?Mb?????43?p}?????L???"?? ? ???1??t??~<3??%a,u?^??u???S*0?9?#!2B?8A????3????r?K?D?? -???n?LJ?u??jW?X???+??\????j?T$??#qt?Mf???+?? -U?j8B$??6>??L?W?? ??; e5w?4:?#F??&??.???6b?0?6??&??????????????9L?9Vi???????? F?y??~?,??_??nlh?8:$??qxV???]?0???8W???"d??BCV???QUQ? -?\&?p?????^??????f????????G?gLHC??dP?gzC??k?/u???/2;oE?j?bS?T? -bYL}?2?&?????v?:??Z~1b"?A??Ah at i??!??ju??2?gL??%a'????????Y??4'??a???y?6S???????P]?4?S'??U???A?0??H_?????Ui????q)Y????O??;4~???T????Y????l??w&m?{?A??G? t6???*l?n???b??O&'?R?? ?h??i??????N?C??t???'?[????+???l????L$:=?;??????9]\???H??K??1?C???k' ???L*?????=`4????_?????g??7???p???/?? mw"zrO?p?? -?tb??.1 ???WlSb??wZL uv?i?n??S???V?r???jn???? ??u??)?????4?Q??C|?? -??|?q?????w/JS???D?gmW -????U????????????0?DU[G??~&?C1???B??Z -??u, M?R?&~a??W?&? ??P?a??qK -?]??FV5???V?6???q??]A??@p???Q??-???=Vo??P? -???-{??$P?z??? %???n;O???iF~C??z? ?E?????g? -? ?dI?_????c??4?T??`?!wp B?{V>???????@?J???1?fq_??i??????.=?);9 ?W?P??b ??7OnM.?????~PI??m?Z??pXR?.?D? :z`^??`Nl??n?????#????Y@??????R?I?????X??????u???9????D??\?NR;????n?z? ??????J?????a5jp??}??G? p?=e?#????KC???% ??????? ??I?-L????????U?)w?C?L?,5KZ?5??:u4?????R4?9?2?SG?V?td?am?&}??;??m7"??????Y??.?s3#?????}?\6&s??fF?{}\??#BC?O?T????R??U?l? ???P?g??-???;? ?t?????C????5 /I???p??5o????.?????>?FN& -??.????????? ??.???(??T?'Pw?n -:?O@$ ot-?CA???;&bD???????9?v!??B%?Ol??0?x?L?\N_5??f41?k5N?\vz??0 c??p8?3~???????D?gA???\J?n?X??s?oD?e??k?P?ot?j\x?H????lo [???????PQ??T"/?Z??\???r? ???F?5?=??/??t_`I????a????/?????y??????????l????7Nb?O??8??(Mm?0? ??um???a???{??Yj??dw???????.???"???SO,???????Ng|??B&Z???kD??G???.M???%???`????+(??hi??U???:?*b?t$ -??????_9????`????f? -s??_?t??? ?9~?X`e??Mf?@"+?? -H?ff??XM4?|~G?v?dh???????????)?t??????????B???U?\?+??B????????? -???????_?M0=j?U?$}?@^e'l??+??+[I????2?Z???v??f???e?\?\???:h????n??ry[7??????/Md??A?O}?R?,?;YQ?#a?; e<<0 ????#!m??`?_,????+2G?(??9O^?????e/B????;??65Fu??e????88???.?????P???{??<???_0o???m9'4 -0R1 ????X? -]#4}??0?????????? /dU?2?Y???SxV|???9)*V??F?s???? -?~??? ?D{C?l ??6??u?}_??s?????_???j?>|??5?????o?3?/?|[g???=}??5??? ??i??? -???JH? -" -?03Xp?y?[?vBf?S"???I?p????yUUp?5??c?}gi1??Po??T????????w???%?9?C9?(??R?????M-?????#??HE?????w?????B??|/?l????L7!E???;?%?X?????b?f????[?????3 KA 1????K??????Z??\2}k*Y?D?I??25i?f?????????? ????i.????Zq??W??T?l???e?nb??????@?.?N??#??l??x?qi??r???1o???[?;e??G???ck?]?uy?v#K/Xd??75 T?9.??g????Ae?_?s?I7??=+??z\Q????iAo??9?9?U??? -??f?iXG???? ?????V?e????$'!??? ?n????-?p=?h?@?z?e)c"B???F????????mm?\5????)c? -.?=?M??1y??G?T???????G?U,?Q? [g??$???=?I!???,? ???{9??*?X??k???9?z??:1 :???e?i'???a?* ??kBB -??f?????9?m|??!d}S?????oN%???????mO??s??_????}?m?_??`???D???c?OG?@P{????????3????.?G???kV_?q?6??p]P?a\{$'???k}`?Bw4|??????f???;N??kP???d?)?9t?d9????? ??WJ?;wF?Q?qF?? jn?I@??=d??????_????]?% -m)a?I????%???B?w8-8?C?R???o 8?????c??^???~?R6wj??mp?>???7V/??a.??-???_??i?8???j???%???!??(+k'??+??#??Q??C??H?I=???n?i?v?U?,??b??m?H?4?{?-4P?(???m?,?i?A??????KJ1 ???lr?? -??%/j??%?`??? -??x?????1Je -?z?????g0?o?9??????D?#i????:8hS????? O????G[?%5 ????WT??_-??????c?~&???XEL?M????cXe''0b??,?,???[s1b?5???9???x -??Z?}I??P????????ygF?@??}?R??n???????"?Kn&E?A?o???V\1$%I?b?? ? ?UC?j?9*'?3?~gI????:???r??????o?T????BD??v-?!G??3??WAB?I?!]"@t:3 -?a??] G???P???}???yI????: ??J[????r?????._O:%2?????????u????D??%?????f?????3??4????#???(b?{15!??`???I???\?! -Z??&?g/?u?am?? -m?x?pH??;p?`?????$rxd???Dl?T???46g?V????????<2??b????:?????oY??gd????K??jxh7 -?\ N?kFB;???~?????0???????????k?G?;?GR????" n???!?6?N^???n???n]I???????m??"U????&?0?????h?????n,i?t????q?h?????_c???%??5 -!?5?%?) 7?#;??x?I}?????E???????????D\k?????d8 ????????U?#?????,???7M??z ?-???.??A)?Y???????Q?? ,??Vk??m?W[?]$??h?*?mU??????uw??gOO8?8???j????=6??w???r???(??F???E???????????1?9J????=k?0??(???? K*?]}p??-??ft:?,????0???????F?J?"??(??&11??J?"Ae??s ??Y2J? 8??"?pt????????:?1????#??f ????\???,0????jc?#??.?0+???D????????y?? ??[@?/????"I+? ?K????'?2i?G??8@?:??f??hui?b????????q??????R??!q&.???????VxSbfC? -B? -??~v?? `Q(?/8G?_????U??E?w?+#?Q???jXPF??!?????@ywc?pTs??+3???}?F????6y}?Eq**?r?????%???_?????\???z???????h??AS44??88?????"??pj?W6??Z?d???r???R?:&? ???I???????|?yT??????j????e??????k0&?c?\^??Z;?,?N???>|??a???A?X?e????b??K?????>?N??y?????y??q?)?G,?`#??a?????BO ????wJ?5?WB?4B^?B?:???5????? -?5?](?@ -??ES??z?[???<\Q???R#B???wS??U??P? -?????H%hO? \?f???,?{r]?????l???N?F ??"?5?w?7<5f?Z?????_??.$2Uv?0?????u?k.?;n?&`???x??b]???????#??X?v??c?? -????T???5?C?.???;??rR5fC|??=?=~p?????8????1???7^???%9]??9??tP??A????/?V -?0?????\?:?0?Chp@9 ????k?N??N?'????)9?LC??5?;????B??v_?kc,$???\R?,4?_????N?f;???9????`OZv?F??????v?2?6?Z5(7??p?_/?l??M??Y6@JW?'}?\?Y{??+?Dt?h2?d?}?h??{??/?(G?NrU????yU??5???-???d?#?~*???E??(?S???C??l?u??}??????P????rH??:?Y?6 ?????????H?W? ??81P?5?WA??[x?0%s?h???P??V^?&????V?(76?Q???? ??0?"?1?H?Q?r,G??.??e?????g??|??? -??e?25{?jza?????C&?H?I?| ??.?[~k??`9?:?u????E????k}????#???)B??S?9???(?i????)?>I&a?'????G?????T???H_?6ft??????M?TE?[?p?p?t?=?_?? ???? -??b?&qx?Z?v??{~?-E?kV?$???o^?;y??HL???O?s8??????o?"o?+C???6~?E???d?D!)?ZJrP?nJ?8????#???T?Q?1p??/y?????????W?+2??c?(?a?{:??(K?????n -???U???RSz?"wI:\?CkxQ??3|R??/b5g???b?PB9?W~??@d??po??=i -??\?S?????x1?Cj??F?u0?k?R???????????"????j(?b|z#,/??n?l??#???hCLwM?$??????%@IwBpm?????w@!??F?8?!C??G7??xX????9?$?->G?????,?$??n?`?@"????U?#?{???,(b? -?<~?x@???=??p??D?=8c??G?i@??[??a`?Hp????????[?4*Zy??(U??C?? -? ? ??-+?%????k?T!w? ???????j???P?t??????????m_z?O?u?{v?<m9{m???N3m???i????????P????? #??U?Pkst????u?-V/(??????n/:Ak_?Y??=?VV?(?F????? ????8????? p?q?e?Lb??-4$?/2m?.?w?T??" ?L??K?0???hF??Z|(@????]???9?????g?j?????cT_b?@ ? ??9??????%[??=??j??????F??b9?????? -??)???j?sq? -?t??9??zv1J?????\^?f?` ,H?????s?o???\Xh??R&????`???5b?7??(V??\??2???R? ????????{???????\?U?ye???#????@???8 h??%"???i??????0?Xc?C??t??? ??g??????&?6|?????I??p??I(wd@?q?????#^??U3??f??[%?K E?h?@??5????????^?l??K?M?`?$?2KQ??Y?w??l=?#??\????)????o??X \????lJ=????????@t E????EYU?g1? -n???????N??D???U?haK?? ?z?????0??a??M?W?N?x????o?T?????;4 ???GM?????ji?!KK6P??????????k)???????F.R1??4? ?s??????x~???N??????????????0l??'???y? ??. ???rP?????)?????.??.|??L'?BI^B?Z+h?y??H?????E?{?~?Q??$?3??|?H????M+???"????????A?|Q????HF.???F???k*?{la?p9?+BC?d?????H??j??????>z?m??p?M???c,~*??W5??cP???bAL??z?qr>?^|??h~???0????????B8???Q&?z?[?7???6'C??????>??/? -44?/??????n?? ???;B?????.????H!??m????'?Rx ?] -??wri?0}???O?'???:1??V?1?-?d?o????.???.?gV????Z-?s? -?????u??q-???V+,N4?Vp?iz.y?f*?? [TRUNCATED] To get the complete diff run: svnlook diff /svnroot/chnosz -r 385 From noreply at r-forge.r-project.org Fri Feb 8 09:07:59 2019 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Fri, 8 Feb 2019 09:07:59 +0100 (CET) Subject: [CHNOSZ-commits] r386 - in pkg/CHNOSZ: . data demo inst/extdata/OBIGT Message-ID: <20190208080759.F19911801BC@r-forge.r-project.org> Author: jedick Date: 2019-02-08 09:07:59 +0100 (Fri, 08 Feb 2019) New Revision: 386 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/data/refs.csv pkg/CHNOSZ/demo/glycinate.R pkg/CHNOSZ/inst/extdata/OBIGT/OldAA.csv pkg/CHNOSZ/inst/extdata/OBIGT/SLOP98.csv pkg/CHNOSZ/inst/extdata/OBIGT/biotic_aq.csv.xz pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_aq.csv.xz pkg/CHNOSZ/inst/extdata/OBIGT/organic_aq.csv.xz Log: OBIGT: clean up CHNOSZ references Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-08 03:57:38 UTC (rev 385) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-08 08:07:59 UTC (rev 386) @@ -1,6 +1,6 @@ Date: 2019-02-08 Package: CHNOSZ -Version: 1.1.3-93 +Version: 1.1.3-94 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/data/refs.csv =================================================================== --- pkg/CHNOSZ/data/refs.csv 2019-02-08 03:57:38 UTC (rev 385) +++ pkg/CHNOSZ/data/refs.csv 2019-02-08 08:07:59 UTC (rev 386) @@ -26,7 +26,8 @@ RA87,"E. J. Reardon and D. K. Armstrong",1987,"Geochim. Cosmochim. Acta 51, 63-72","celestite GHS",https://doi.org/10.1016/0016-7037(87)90007-X Ber88,"R. G. Berman",1988,"J. Petrol. 29, 445-522",minerals,https://doi.org/10.1093/petrology/29.2.445 SH88,"E. L. Shock and H. C. Helgeson",1988,"Geochim. Cosmochim. Acta 52, 2009-2036","ionic species",https://doi.org/10.1016/0016-7037(88)90181-0 -SH88.1,"E. L. Shock and H. C. Helgeson",1988,"Geochim. Cosmochim. Acta 52, 2009-2036","H2AsO3-",https://doi.org/10.1016/0016-7037(88)90181-0 +SH88.1,"E. L. Shock and H. C. Helgeson",1988,"Geochim. Cosmochim. Acta 52, 2009-2036","values of GHS",https://doi.org/10.1016/0016-7037(88)90181-0 +SH88.2,"E. L. Shock and H. C. Helgeson",1988,"Geochim. Cosmochim. Acta 52, 2009-2036","H2AsO3-",https://doi.org/10.1016/0016-7037(88)90181-0 SHS89,"E. L. Shock, H. C. Helgeson and D. A. Sverjensky",1989,"Geochim. Cosmochim. Acta 53, 2157-2183","inorganic neutral species",https://doi.org/10.1016/0016-7037(89)90341-4 SHS89.1,"E. L. Shock, H. C. Helgeson and D. A. Sverjensky",1989,"Geochim. Cosmochim. Acta 53, 2157-2183","aqueous SiO2",https://doi.org/10.1016/0016-7037(89)90341-4 Ber90,"R. G. Berman",1990,"Am. Mineral. 75, 328-344",annite,http://ammin.geoscienceworld.org/content/75/3-4/328 @@ -171,13 +172,13 @@ ZZL+16.2,"K. Zimmer et al.",2016,"Comp. Geosci. 90, 97-111","Cp parameters listed in spronsbl.dat",https://doi.org/10.1016/j.cageo.2016.02.013 ZZL+16.3,"K. Zimmer et al.",2016,"Comp. Geosci. 90, 97-111","dawsonite GHS",https://doi.org/10.1016/j.cageo.2016.02.013 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 -CHNOSZ.3,"J. M. Dick",2017,"CHNOSZ package documentation","metal-amino acid complexes: GHS were recalculated by adding the differences between values from @SK95 and @AH97b for alanate or glycinate to the properties of the complexes reported by @SK95.",http://chnosz.net -CHNOSZ.5,"J. M. Dick",2017,"CHNOSZ package documentation","AuCl4- renamed to AuCl4-3",http://chnosz.net -CHNOSZ.7,"J. M. Dick",2017,"CHNOSZ package documentation","charge of NpO2(Oxal), La(Succ)+, NH4(Succ)-, and NpO2(Succ) as listed by @PSK99",http://chnosz.net -CHNOSZ.8,"J. M. Dick",2017,"CHNOSZ package documentation","Incorrect values of HKF a1--a4 parameters for [-CH2NH2] were printed in Table 6 of @DLH06; corrected values are used here.",http://chnosz.net -CHNOSZ.9,"J. M. Dick",2019,"CHNOSZ package documentation","recalculated values of Cp (those in @AKAE19 appear to be calculated using wrong sign on ω) and enthalpy (using ΔG=ΔH-TΔS and the entropies of the elements)",http://chnosz.net -CHNOSZ.10,"J. M. Dick",2019,"CHNOSZ package documentation","Tl(Gly) and Tl(Gly)2-: replace Ti with Tl",http://chnosz.net -CHNOSZ.11,"J. M. Dick",2019,"CHNOSZ package documentation","HSiO3-: GHS recalculated by adding difference from SiO2 [@SSH97] to updated values for SiO2 [@AS04]",http://chnosz.net +CHNOSZ.2,"J. M. Dick",2017,"CHNOSZ package documentation","metal-amino acid complexes: GHS were recalculated by adding the differences between values from @SK95 and @AH97b for alanate or glycinate to the properties of the complexes reported by @SK95.",http://chnosz.net +CHNOSZ.3,"J. M. Dick",2017,"CHNOSZ package documentation","AuCl4- renamed to AuCl4-3",http://chnosz.net +CHNOSZ.4,"J. M. Dick",2017,"CHNOSZ package documentation","charge of NpO2(Oxal), La(Succ)+, NH4(Succ)-, and NpO2(Succ) as listed by @PSK99",http://chnosz.net +CHNOSZ.5,"J. M. Dick",2017,"CHNOSZ package documentation","Incorrect values of HKF a1--a4 parameters for [-CH2NH2] were printed in Table 6 of @DLH06; corrected values are used here.",http://chnosz.net +CHNOSZ.6,"J. M. Dick",2019,"CHNOSZ package documentation","recalculated values of Cp (those in @AKAE19 appear to be calculated using wrong sign on ω) and enthalpy (using ΔG=ΔH-TΔS and the entropies of the elements)",http://chnosz.net +CHNOSZ.7,"J. M. Dick",2019,"CHNOSZ package documentation","Tl(Gly) and Tl(Gly)2-: change Ti to Tl",http://chnosz.net +CHNOSZ.8,"J. M. Dick",2019,"CHNOSZ package documentation","HSiO3-: GHS recalculated by adding difference from SiO2 [@SSH97] to updated values for SiO2 [@AS04]",http://chnosz.net LCT17,"A. R. Lowe, J. S. Cox and P. R. Tremaine",2017,"J. Chem. Thermodynamics 112, 129-145","adenine HKF parameters",https://doi.org/10.1016/j.jct.2017.04.005 DEW17,"D. A. Sverjensky et al.",2017,"Deep Earth Water (DEW) spreadsheet","other data from Aqueous Species Table in spreadsheet (see detailed references there)",http://www.dewcommunity.org DEW17.1,"D. A. Sverjensky et al.",2017,"Deep Earth Water (DEW) spreadsheet","revised with new predicted a1 for ions",http://www.dewcommunity.org Modified: pkg/CHNOSZ/demo/glycinate.R =================================================================== --- pkg/CHNOSZ/demo/glycinate.R 2019-02-08 03:57:38 UTC (rev 385) +++ pkg/CHNOSZ/demo/glycinate.R 2019-02-08 08:07:59 UTC (rev 386) @@ -35,19 +35,20 @@ # set up the plots layout(matrix(1:6, byrow = TRUE, nrow = 2), widths = c(2, 2, 1)) -par(mar = c(4, 3.2, 2.5, 0.5), mgp = c(2, 1, 0), las = 1, cex = 0.8) +par(mar = c(4, 3.2, 2.5, 0.5), mgp = c(2.1, 1, 0), las = 1, cex = 0.8) xlab <- axis.label("T") ylab <- axis.label("logK") # first row: divalent metals matplot(T, sapply(logK_di1, c), type = "l", lwd = 2, lty = 1, xlab = xlab, ylab = ylab) matplot(T, sapply(logK_di1_SK95, c), type = "l", lwd = 2, lty = 2, add = TRUE) -legend(-5, 7.7, c("Azadi et al., 2019", "Shock and Koretsky, 1995"), lty = c(1, 2), bty = "n", cex = 1) -mtext(expression(M^"+2" + Gly^"-" == M*(Gly)^"+"), line = 0.5) +legend(-9, 7.7, c("Azadi et al., 2019", "Shock and Koretsky, 1995"), lty = c(1, 2), bty = "n", cex = 1) +# \u21cc is the double reaction arrow +mtext(expression(M^"+2" + Gly^"-"~"\u21cc"~M*(Gly)^"+"), line = 0.5) matplot(T, sapply(logK_di2, c), type = "l", lwd = 2, lty = 1, xlab = xlab, ylab = ylab) matplot(T, sapply(logK_di2_SK95, c), type = "l", lwd = 2, lty = 2, add = TRUE) -legend(-5, 14, c("Azadi et al., 2019", "Shock and Koretsky, 1995"), lty = c(1, 2), bty = "n", cex = 1) -mtext(expression(M^"+2" + 2*Gly^"-" == M*(Gly)[2]), line = 0.5) +legend(-9, 14, c("Azadi et al., 2019", "Shock and Koretsky, 1995"), lty = c(1, 2), bty = "n", cex = 1) +mtext(expression(M^"+2" + 2*Gly^"-"~"\u21cc"~M*(Gly)[2]), line = 0.5) plot.new() par(xpd = NA) legend("right", as.expression(lapply(di, expr.species)), lty = 1, col = 1:6, bty = "n", cex = 1.2, lwd = 2) @@ -58,9 +59,9 @@ # second row: monovalent metals matplot(T, sapply(logK_mo1, c), type = "l", lwd = 2, lty = 1, xlab = xlab, ylab = ylab) -mtext(expression(M^"+" + Gly^"-" == M*(Gly)), line = 0.5) +mtext(expression(M^"+" + Gly^"-"~"\u21cc"~M*(Gly)), line = 0.5) matplot(T, sapply(logK_mo2, c), type = "l", lwd = 2, lty = 1, xlab = xlab, ylab = ylab) -mtext(expression(M^"+" + 2*Gly^"-" == M*(Gly)[2]^"-"), line = 0.5) +mtext(expression(M^"+" + 2*Gly^"-"~"\u21cc"~M*(Gly)[2]^"-"), line = 0.5) plot.new() par(xpd = NA) legend("right", as.expression(lapply(mo, expr.species)), lty = 1, col = 1:5, bty = "n", cex = 1.2, lwd = 2) Modified: pkg/CHNOSZ/inst/extdata/OBIGT/OldAA.csv =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/OldAA.csv 2019-02-08 03:57:38 UTC (rev 385) +++ pkg/CHNOSZ/inst/extdata/OBIGT/OldAA.csv 2019-02-08 08:07:59 UTC (rev 386) @@ -11,55 +11,55 @@ [UPBB],NA,C2H2NO,aq,DLH06.6,NA,25.Aug.06,-21436,-45220,1.62,-4.496,26.296,8.1,-3.75,-6.73,1.13,11.2,-7.5,0.05,0 alanate,NA,C3H6NO2-,aq,"SK95.1 [S98]",AH97b.1,3.Sep.06,-75360,-121470,30.71,17.8,61.88,10.6281,17.3648,0.6505,-3.4968,12.685,-4.1859,1.17,-1 glycinate,NA,C2H4NO2-,aq,"SK95.1 [S98]",AH97b.1,3.Sep.06,-77610,-114190,30.07,-6.6,43.77,8.1592,11.7696,1.921,-3.2655,12.9389,-4.1859,1.1975,-1 -Ca(Gly)+,NA,Ca(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-211570,-240519,34.375,59.3,32.6,6.2431,7.4595,2.8241,-3.0873,41.4246,9.0464,0.0543,1 -Ca(Gly)2,NA,Ca(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-290215,-351722,77.929,131,89,13.9371,26.2517,-4.5733,-3.8641,82.6597,23.6485,-0.03,0 -Mg(Gly)+,NA,Mg(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-190820,-227064,7.788,64.2,28.7,5.8466,6.4953,3.1944,-3.0474,48.0086,10.0502,0.4555,1 -Mg(Gly)2,NA,Mg(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-272534,-343783,43.136,140.6,84.7,13.3443,24.8034,-4.0028,-3.8043,88.2942,25.6069,-0.03,0 -Sr(Gly)+,NA,Sr(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-213664,-241197,42.515,53.6,33.3,6.3007,7.6019,2.7652,-3.0932,36.9719,7.8914,-0.0684,1 -Sr(Gly)2,NA,Sr(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-291859,-351200,88.581,119.9,89.8,14.0476,26.5176,-4.6704,-3.8751,76.1763,21.395,-0.03,0 -Ba(Gly)+,NA,Ba(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-213671,-237698,55.917,48.6,38.7,6.9656,9.2295,2.1164,-3.1604,32.1389,6.8602,-0.2709,1 -Ba(Gly)2,NA,Ba(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-292479,-347082,106.12,110.1,95.8,14.8647,28.514,-5.4575,-3.9577,70.3874,19.383,-0.03,0 -Mn(Gly)+,NA,Mn(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-137101,-167693,26.59,67,33.7,6.4299,7.9186,2.6372,-3.1063,47.0493,10.6185,0.1739,1 -Mn(Gly)2,NA,Mn(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-218761,-282627,67.741,146.1,90.2,14.1002,26.6481,-4.7253,-3.8805,91.4846,26.7157,-0.03,0 -Fe(Gly)+,NA,Fe(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-105368,-137141,21.59,58,28,5.6774,6.0837,3.3533,-3.0304,42.4593,8.7852,0.2482,1 -Fe(Gly)2,NA,Fe(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-187369,-252307,61.198,128.5,83.9,13.2339,24.5311,-3.8903,-3.793,81.1932,23.1388,-0.03,0 -Ni(Gly)+,NA,Ni(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-96871,-131179,13.59,49.9,20.4,4.6813,3.6515,4.3097,-2.9299,38.8214,7.1352,0.3686,1 -Ni(Gly)2,NA,Ni(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-181191,-249835,51.18,112.7,75.4,12.0787,21.7107,-2.7819,-3.6764,71.9311,19.9195,-0.03,0 -Cu(Gly)+,NA,Cu(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-73625,-104298,26.59,63.4,25.3,5.2864,5.1238,3.7413,-2.9907,44.9395,9.8852,0.1739,1 -Cu(Gly)2,NA,Cu(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-161137,-225550,66.18,139,80.9,12.8262,23.5338,-3.4944,-3.7518,87.3679,25.285,-0.03,0 -Zn(Gly)+,NA,Zn(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-120148,-153499,19.59,62.1,25.6,5.3677,5.3226,3.6628,-2.9989,45.1185,9.6102,0.2792,1 -Zn(Gly)2,NA,Zn(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-203799,-271188,58.18,136.4,81.3,12.8771,23.6625,-3.5537,-3.7571,85.8243,24.7484,-0.03,0 -Pb(Gly)+,NA,Pb(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-90780,-114202,58.508,47.7,35.3,6.4949,8.079,2.5712,-3.1129,31.2483,6.6769,-0.3103,1 -Pb(Gly)2,NA,Pb(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-173013,-226772,109.51,108.3,92.1,14.355,27.2722,-4.9746,-3.9063,69.3582,19.0253,-0.03,0 -Co(Gly)+,NA,Co(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-97525,-130972,16.59,58.7,25.5,5.3683,5.3273,3.6539,-2.9991,43.5722,8.9227,0.326,1 -Co(Gly)2,NA,Co(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-180617,-247207,58.18,129.8,81.2,12.8601,23.6197,-3.5341,-3.7553,81.9652,23.407,-0.03,0 -Cd(Gly)+,NA,Cd(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-102566,-133978,28.59,68.4,35.3,6.6477,8.4525,2.4231,-3.1283,47.5446,10.8935,0.1417,1 -Cd(Gly)2,NA,Cd(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-185236,-250387,68.18,148.7,92.1,14.355,27.2722,-4.9746,-3.9063,93.0282,27.2523,-0.03,0 -Eu(Gly)+,NA,Eu(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-208959,-236026,49.509,89.8,50.3,8.5841,13.176,0.5767,-3.3236,57.1645,15.2476,-0.1738,1 -Eu(Gly)2,NA,Eu(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-288477,-346709,97.734,190.4,108.7,16.6314,32.8272,-7.1514,-4.136,117.4699,35.7476,-0.03,0 -Ca(Alan)+,NA,Ca(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-209172,-247643,35.015,104.6,50.7,8.7124,13.4888,0.454,-3.3365,67.7227,18.2713,0.0279,1 -Ca(Alan)2,NA,Ca(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-285446,-365834,79.755,239.1,127.3,19.1765,39.0448,-9.6021,-4.393,146.0369,45.6768,-0.03,0 -Mg(Alan)+,NA,Mg(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-186539,-232305,8.428,109.5,46.8,8.3169,12.5282,0.821,-3.2968,74.3351,19.275,0.4322,1 -Mg(Alan)2,NA,Mg(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-263631,-353761,44.962,248.8,123,18.5836,37.5967,-9.0318,-4.3331,151.6713,47.6352,-0.03,0 -Sr(Alan)+,NA,Sr(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-211130,-248184,43.155,98.9,51.4,8.77,13.6312,0.3947,-3.3424,63.2691,17.1163,-0.0948,1 -Sr(Alan)2,NA,Sr(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-286831,-365053,90.407,228.1,128.1,19.2869,39.3109,-9.699,-4.404,139.5534,43.4233,-0.03,0 -Ba(Alan)+,NA,Ba(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-210713,-244263,56.557,93.7,56.8,9.4348,15.2528,-0.2391,-3.4095,58.4325,16.085,-0.2977,1 -Ba(Alan)2,NA,Ba(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-286687,-360171,107.946,218.2,134.1,20.104,41.3073,-10.4865,-4.4865,133.7647,41.4112,-0.03,0 -Mn(Alan)+,NA,Mn(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-134280,-173740,29.425,112.3,51.8,8.8873,13.9167,0.2842,-3.3542,73.0237,19.8433,0.1124,1 -Mn(Alan)2,NA,Mn(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-213474,-295365,72.44,254.2,128.5,19.3395,39.4414,-9.7539,-4.4094,154.8617,48.744,-0.03,0 -Fe(Alan)+,NA,Fe(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-103952,-146326,18.518,103.3,46.1,8.1661,12.1558,0.976,-3.2814,69.2856,18.01,0.2792,1 -Fe(Alan)2,NA,Fe(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-184387,-269655,58.166,236.6,122.2,18.4732,37.3244,-8.9189,-4.3219,144.5703,45.1671,-0.03,0 -Ni(Alan)+,NA,Ni(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-94227,-137691,15.46,95.2,38.5,7.1451,9.664,1.9536,-3.1784,64.9703,16.36,0.326,1 -Ni(Alan)2,NA,Ni(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-175945,-264092,50.92,220.8,113.8,17.318,34.504,-7.8105,-4.2053,135.3083,41.9478,-0.03,0 -Cu(Alan)+,NA,Cu(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,06.Feb.19,-71295,-110530,25.46,108.7,43.4,7.7387,11.1165,1.3762,-3.2385,70.7759,19.11,0.0974,1 -Cu(Alan)2,NA,Cu(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,06.Feb.19,-156054,-238480,65.92,247.2,119.2,18.0655,36.3271,-8.523,-4.2807,150.7452,47.3132,-0.03,0 -Zn(Alan)+,NA,Zn(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-117313,-161024,17.46,107.4,43.8,7.8514,11.3891,1.2746,-3.2497,71.8106,18.835,0.2956,1 -Zn(Alan)2,NA,Zn(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-198512,-284509,60.92,244.5,119.6,18.1164,36.4558,-8.5823,-4.286,149.2015,46.7767,-0.03,0 -Pb(Alan)+,NA,Pb(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-87891,-120835,59.148,93,53.4,8.964,14.1088,0.1992,-3.3622,57.5413,15.9017,-0.3372,1 -Pb(Alan)2,NA,Pb(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-167671,-240311,111.336,216.4,130.4,19.5944,40.0653,-10.0034,-4.4352,132.7356,41.0535,-0.03,0 -Co(Alan)+,NA,Co(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-94799,-136805,20.46,104,43.6,7.8202,11.3148,1.299,-3.2467,69.3955,18.1475,0.2482,1 -Co(Alan)2,NA,Co(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-175193,-260392,60.92,238,119.4,18.0995,36.4127,-8.5626,-4.2842,145.3423,45.4353,-0.03,0 -Cd(Alan)+,NA,Cd(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-100782,-141576,29.698,113.7,53.4,9.1151,14.4742,0.063,-3.3773,73.7914,20.1183,0.1098,1 -Cd(Alan)2,NA,Cd(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-181340,-264540,72.797,256.8,130.4,19.5944,40.0653,-10.0034,-4.4352,156.4053,49.2806,-0.03,0 -Eu(Alan)+,NA,Eu(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-206029,-242617,50.149,135,68.4,11.0532,19.2058,-1.7947,-3.5729,83.4588,24.4724,-0.2006,1 -Eu(Alan)2,NA,Eu(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.3,3.Sep.06,-282521,-359634,99.56,298.5,147,21.8707,45.6205,-12.1799,-4.6649,180.847,57.7759,-0.03,0 +Ca(Gly)+,NA,Ca(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-211570,-240519,34.375,59.3,32.6,6.2431,7.4595,2.8241,-3.0873,41.4246,9.0464,0.0543,1 +Ca(Gly)2,NA,Ca(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-290215,-351722,77.929,131,89,13.9371,26.2517,-4.5733,-3.8641,82.6597,23.6485,-0.03,0 +Mg(Gly)+,NA,Mg(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-190820,-227064,7.788,64.2,28.7,5.8466,6.4953,3.1944,-3.0474,48.0086,10.0502,0.4555,1 +Mg(Gly)2,NA,Mg(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-272534,-343783,43.136,140.6,84.7,13.3443,24.8034,-4.0028,-3.8043,88.2942,25.6069,-0.03,0 +Sr(Gly)+,NA,Sr(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-213664,-241197,42.515,53.6,33.3,6.3007,7.6019,2.7652,-3.0932,36.9719,7.8914,-0.0684,1 +Sr(Gly)2,NA,Sr(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-291859,-351200,88.581,119.9,89.8,14.0476,26.5176,-4.6704,-3.8751,76.1763,21.395,-0.03,0 +Ba(Gly)+,NA,Ba(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-213671,-237698,55.917,48.6,38.7,6.9656,9.2295,2.1164,-3.1604,32.1389,6.8602,-0.2709,1 +Ba(Gly)2,NA,Ba(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-292479,-347082,106.12,110.1,95.8,14.8647,28.514,-5.4575,-3.9577,70.3874,19.383,-0.03,0 +Mn(Gly)+,NA,Mn(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-137101,-167693,26.59,67,33.7,6.4299,7.9186,2.6372,-3.1063,47.0493,10.6185,0.1739,1 +Mn(Gly)2,NA,Mn(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-218761,-282627,67.741,146.1,90.2,14.1002,26.6481,-4.7253,-3.8805,91.4846,26.7157,-0.03,0 +Fe(Gly)+,NA,Fe(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-105368,-137141,21.59,58,28,5.6774,6.0837,3.3533,-3.0304,42.4593,8.7852,0.2482,1 +Fe(Gly)2,NA,Fe(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-187369,-252307,61.198,128.5,83.9,13.2339,24.5311,-3.8903,-3.793,81.1932,23.1388,-0.03,0 +Ni(Gly)+,NA,Ni(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-96871,-131179,13.59,49.9,20.4,4.6813,3.6515,4.3097,-2.9299,38.8214,7.1352,0.3686,1 +Ni(Gly)2,NA,Ni(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-181191,-249835,51.18,112.7,75.4,12.0787,21.7107,-2.7819,-3.6764,71.9311,19.9195,-0.03,0 +Cu(Gly)+,NA,Cu(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-73625,-104298,26.59,63.4,25.3,5.2864,5.1238,3.7413,-2.9907,44.9395,9.8852,0.1739,1 +Cu(Gly)2,NA,Cu(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-161137,-225550,66.18,139,80.9,12.8262,23.5338,-3.4944,-3.7518,87.3679,25.285,-0.03,0 +Zn(Gly)+,NA,Zn(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-120148,-153499,19.59,62.1,25.6,5.3677,5.3226,3.6628,-2.9989,45.1185,9.6102,0.2792,1 +Zn(Gly)2,NA,Zn(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-203799,-271188,58.18,136.4,81.3,12.8771,23.6625,-3.5537,-3.7571,85.8243,24.7484,-0.03,0 +Pb(Gly)+,NA,Pb(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-90780,-114202,58.508,47.7,35.3,6.4949,8.079,2.5712,-3.1129,31.2483,6.6769,-0.3103,1 +Pb(Gly)2,NA,Pb(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-173013,-226772,109.51,108.3,92.1,14.355,27.2722,-4.9746,-3.9063,69.3582,19.0253,-0.03,0 +Co(Gly)+,NA,Co(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-97525,-130972,16.59,58.7,25.5,5.3683,5.3273,3.6539,-2.9991,43.5722,8.9227,0.326,1 +Co(Gly)2,NA,Co(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-180617,-247207,58.18,129.8,81.2,12.8601,23.6197,-3.5341,-3.7553,81.9652,23.407,-0.03,0 +Cd(Gly)+,NA,Cd(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-102566,-133978,28.59,68.4,35.3,6.6477,8.4525,2.4231,-3.1283,47.5446,10.8935,0.1417,1 +Cd(Gly)2,NA,Cd(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-185236,-250387,68.18,148.7,92.1,14.355,27.2722,-4.9746,-3.9063,93.0282,27.2523,-0.03,0 +Eu(Gly)+,NA,Eu(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-208959,-236026,49.509,89.8,50.3,8.5841,13.176,0.5767,-3.3236,57.1645,15.2476,-0.1738,1 +Eu(Gly)2,NA,Eu(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-288477,-346709,97.734,190.4,108.7,16.6314,32.8272,-7.1514,-4.136,117.4699,35.7476,-0.03,0 +Ca(Alan)+,NA,Ca(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-209172,-247643,35.015,104.6,50.7,8.7124,13.4888,0.454,-3.3365,67.7227,18.2713,0.0279,1 +Ca(Alan)2,NA,Ca(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-285446,-365834,79.755,239.1,127.3,19.1765,39.0448,-9.6021,-4.393,146.0369,45.6768,-0.03,0 +Mg(Alan)+,NA,Mg(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-186539,-232305,8.428,109.5,46.8,8.3169,12.5282,0.821,-3.2968,74.3351,19.275,0.4322,1 +Mg(Alan)2,NA,Mg(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-263631,-353761,44.962,248.8,123,18.5836,37.5967,-9.0318,-4.3331,151.6713,47.6352,-0.03,0 +Sr(Alan)+,NA,Sr(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-211130,-248184,43.155,98.9,51.4,8.77,13.6312,0.3947,-3.3424,63.2691,17.1163,-0.0948,1 +Sr(Alan)2,NA,Sr(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-286831,-365053,90.407,228.1,128.1,19.2869,39.3109,-9.699,-4.404,139.5534,43.4233,-0.03,0 +Ba(Alan)+,NA,Ba(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-210713,-244263,56.557,93.7,56.8,9.4348,15.2528,-0.2391,-3.4095,58.4325,16.085,-0.2977,1 +Ba(Alan)2,NA,Ba(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-286687,-360171,107.946,218.2,134.1,20.104,41.3073,-10.4865,-4.4865,133.7647,41.4112,-0.03,0 +Mn(Alan)+,NA,Mn(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-134280,-173740,29.425,112.3,51.8,8.8873,13.9167,0.2842,-3.3542,73.0237,19.8433,0.1124,1 +Mn(Alan)2,NA,Mn(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-213474,-295365,72.44,254.2,128.5,19.3395,39.4414,-9.7539,-4.4094,154.8617,48.744,-0.03,0 +Fe(Alan)+,NA,Fe(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-103952,-146326,18.518,103.3,46.1,8.1661,12.1558,0.976,-3.2814,69.2856,18.01,0.2792,1 +Fe(Alan)2,NA,Fe(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-184387,-269655,58.166,236.6,122.2,18.4732,37.3244,-8.9189,-4.3219,144.5703,45.1671,-0.03,0 +Ni(Alan)+,NA,Ni(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-94227,-137691,15.46,95.2,38.5,7.1451,9.664,1.9536,-3.1784,64.9703,16.36,0.326,1 +Ni(Alan)2,NA,Ni(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-175945,-264092,50.92,220.8,113.8,17.318,34.504,-7.8105,-4.2053,135.3083,41.9478,-0.03,0 +Cu(Alan)+,NA,Cu(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,06.Feb.19,-71295,-110530,25.46,108.7,43.4,7.7387,11.1165,1.3762,-3.2385,70.7759,19.11,0.0974,1 +Cu(Alan)2,NA,Cu(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,06.Feb.19,-156054,-238480,65.92,247.2,119.2,18.0655,36.3271,-8.523,-4.2807,150.7452,47.3132,-0.03,0 +Zn(Alan)+,NA,Zn(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-117313,-161024,17.46,107.4,43.8,7.8514,11.3891,1.2746,-3.2497,71.8106,18.835,0.2956,1 +Zn(Alan)2,NA,Zn(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-198512,-284509,60.92,244.5,119.6,18.1164,36.4558,-8.5823,-4.286,149.2015,46.7767,-0.03,0 +Pb(Alan)+,NA,Pb(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-87891,-120835,59.148,93,53.4,8.964,14.1088,0.1992,-3.3622,57.5413,15.9017,-0.3372,1 +Pb(Alan)2,NA,Pb(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-167671,-240311,111.336,216.4,130.4,19.5944,40.0653,-10.0034,-4.4352,132.7356,41.0535,-0.03,0 +Co(Alan)+,NA,Co(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-94799,-136805,20.46,104,43.6,7.8202,11.3148,1.299,-3.2467,69.3955,18.1475,0.2482,1 +Co(Alan)2,NA,Co(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-175193,-260392,60.92,238,119.4,18.0995,36.4127,-8.5626,-4.2842,145.3423,45.4353,-0.03,0 +Cd(Alan)+,NA,Cd(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-100782,-141576,29.698,113.7,53.4,9.1151,14.4742,0.063,-3.3773,73.7914,20.1183,0.1098,1 +Cd(Alan)2,NA,Cd(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-181340,-264540,72.797,256.8,130.4,19.5944,40.0653,-10.0034,-4.4352,156.4053,49.2806,-0.03,0 +Eu(Alan)+,NA,Eu(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-206029,-242617,50.149,135,68.4,11.0532,19.2058,-1.7947,-3.5729,83.4588,24.4724,-0.2006,1 +Eu(Alan)2,NA,Eu(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-282521,-359634,99.56,298.5,147,21.8707,45.6205,-12.1799,-4.6649,180.847,57.7759,-0.03,0 Modified: pkg/CHNOSZ/inst/extdata/OBIGT/SLOP98.csv =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/SLOP98.csv 2019-02-08 03:57:38 UTC (rev 385) +++ pkg/CHNOSZ/inst/extdata/OBIGT/SLOP98.csv 2019-02-08 08:07:59 UTC (rev 386) @@ -2,13 +2,13 @@ AuCl,AuCl,AuCl,aq,"SSH97.1 [S98]",NA,2.Oct.97,-3184,-2140,41.47,-9.83,38.61,7.0357,9.4008,2.0481,-3.1676,0.0551,-5.0371,-0.038,0 AuCl2-,AuCl2-,AuCl2-,aq,"SSH97.1 [S98]",NA,2.Oct.97,-36781,-44725,53.6,-24.52,69.26,11.5192,20.3482,-2.2547,-3.6201,-0.6764,-8.03,0.8173,-1 AuCl3-2,AuCl3-2,AuCl3-2,aq,"SSH97.1 [S98]",NA,2.Oct.97,-67811,-86023,61.39,-43.48,103.42,16.6878,32.9687,-7.2151,-4.1419,1.7155,-11.891,2.2827,-2 -AuCl4-3,AuCl4-3,AuCl4-3,aq,"SSH97.1 [S98]",CHNOSZ.5,2.Oct.97,-35332,23573,-32.72,-1.36,-20.66,-0.5361,-9.0876,9.3148,-2.4033,19.7251,-3.3107,1.5579,-3 +AuCl4-3,AuCl4-3,AuCl4-3,aq,"SSH97.1 [S98]",CHNOSZ.3,2.Oct.97,-35332,23573,-32.72,-1.36,-20.66,-0.5361,-9.0876,9.3148,-2.4033,19.7251,-3.3107,1.5579,-3 Au(HS)2-,Au(HS)2-,Au(HS)2-,aq,"SSH97.1 [S98]",NA,9.Oct.97,2429,-2509,56.77,6.06,75.39,12.342,22.3572,-3.0443,-3.7032,16.8038,-1.8007,0.7693,-1 -Au+,Au+,Au+,aq,"SSWS97.2 [S98]",NA,13.Nov.97,39000,47900,25.6,-0.3,12.5,3.5312,0.8428,5.4139,-2.8137,7.5089,-3.0956,0.1648,1 -Au+3,Au+3,Au+3,aq,"SSWS97.2 [S98]",NA,13.Nov.97,103600,97800,-54.8,-8.2,-31.4,-1.7167,-11.9654,10.4352,-2.2843,23.5775,-4.7048,2.4115,3 +Au+,Au+,Au+,aq,"SSWS97.2 [S98]",SH88.1,13.Nov.97,39000,47900,25.6,-0.3,12.5,3.5312,0.8428,5.4139,-2.8137,7.5089,-3.0956,0.1648,1 +Au+3,Au+3,Au+3,aq,"SSWS97.2 [S98]",SH88.1,13.Nov.97,103600,97800,-54.8,-8.2,-31.4,-1.7167,-11.9654,10.4352,-2.2843,23.5775,-4.7048,2.4115,3 Au(Ac),NA,AuCH3COO,aq,"SK93.1 [S98]",NA,10.Sep.92,-49870,-68310,48,56.1,61.8,10.213,17.1576,-0.9969,-3.4882,38.7432,8.3843,-0.03,0 Au(Ac)2-,NA,Au(CH3COO)2-,aq,"SK93.1 [S98]",NA,10.Sep.92,-138240,-186750,61.3,132.8,118.3,18.1917,36.6392,-8.6534,-4.2936,90.461,24.0193,0.701,-1 -H2AsO3-,H2AsO3-,H2AsO3-,aq,"SH88.1 [S92]",NA,3.Jul.87,-140330,-170840,26.4,-2.9,26.4,5.7934,6.3646,3.2485,-3.0421,15.8032,-3.6253,1.2305,-1 +H2AsO3-,H2AsO3-,H2AsO3-,aq,"SH88.2 [S92]",NA,3.Jul.87,-140330,-170840,26.4,-2.9,26.4,5.7934,6.3646,3.2485,-3.0421,15.8032,-3.6253,1.2305,-1 AsO4-3,AsO4-3,AsO4-3,aq,"SSWS97.3 [S98]",NA,11.Nov.97,-154970,-212270,-38.9,-116.1,-18.7,1.0308,-5.2609,7.8091,-2.5614,-12.1352,-26.6841,5.399,-3 HAsO4-2,HAsO4-2,HAsO4-2,aq,"SSWS97.3 [S98]",NA,11.Nov.97,-170790,-216620,-0.4,-47.5,11.3,4.3994,2.9611,4.5853,-2.9013,7.9908,-12.7102,3.2197,-2 H2AsO4-,H2AsO4-,H2AsO4-,aq,"SSWS97.3 [S98]",NA,11.Nov.97,-180010,-217390,28,-0.6,33.4,6.7429,8.6835,2.3351,-3.1379,16.9206,-3.1567,1.2055,-1 Modified: pkg/CHNOSZ/inst/extdata/OBIGT/biotic_aq.csv.xz =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/biotic_aq.csv.xz 2019-02-08 03:57:38 UTC (rev 385) +++ pkg/CHNOSZ/inst/extdata/OBIGT/biotic_aq.csv.xz 2019-02-08 08:07:59 UTC (rev 386) @@ -1,4 +1,4 @@ -?7zXZ???F!t/????z4]7I??b???9??????TB;q?"?q???cL;?"??I?,t?b?PK??7?t(?em?A-P?Q?]?? ??8?.f?|?????V[?????=??K????VTm??~vw? ?2/ ??Wa???s?-?????p?lVs????H???u???? ?%?XF??k#??????????+??(??m5?St5?Fa?a??jN??8????>z???3MwS?%??????+?3x??`cw`?; $? (???????P?>????>?1b???QA??????>6o?=?-?((??pN???i????VOL?A???9 c?E3??XP?? ??kj?s?????Y!&o??w(??3?+?"???????; ??R6eW????![?????r?O>O?*?h\t????ty??)B????n<?9l?N!3???z '???}???nV?,0uVe??????? j?????|B??d^7&KK?- @@ -83,14 +83,20 @@ ??e??m{P~ ?#?e?\?O??t?Y?1??j?L?3?R??????U8?&???4?????5-?]??I???????*??-??????R??B?D?M?\?? ?C??r?8'?? T?????F=??+ch??)J? |???~?Q{??????B??0?j??9??????s??~?k=??? ?(u??'q;X`?????C???r4??? dfS)N??D??H?6?V%1?O??6k?Z?K?%????y_z?2?`??Z?u?7????|????H5?? ??????q????]*?r?r?~??E*E??"?P??????_?o?>??@ ??n??Ip?M?5???;u? ???->|????jj?i>Z?????{?????]???;??? ???v"q???N)?}^ -?Rf ????????B????4????.:???Zc+?]??i?R?n-.??Q?i?9+&?U^??ufeu?????b???c7??/????Zml??p????l??????!j?x?g?yL?X?J??Cj?? ?)]??%????G0??J?j???-??Y)?)???"B??%t???????Av3?8?:?? ??????o?>??z?P??jcX?a?t'????p??H?6?B?* ?$???_?cHE???I?)?N?A?h??.X???v6n??yy????????i}(Ze`???&?9????d ?Bi-?K??? ?A?[????????????=?????8C?? T?kD&y)?vO=W?~ ??B|m??Dp?|?oR???5,/8??r?{?-D??C??mvc?`?>w??'???*[$B?G?="?_??? ???I~O?%g?Tn????U??? ((H?4&??4??aG?&?o?A??_??W3j???{(,?Q?:6GG??u?##J)???1?@???$&x??x?f???? ????&"?????M??6????1 =????*?+&(?3D????"Kf???Oc%?k??k?76S??B?? ???Y?sb??????w??Em?g??w?????P? ???? ,???????3 |?a?$u?f??.i5?x??I?_>l?????Sh??Z5I??k???nxI???t?b?n?6?? -???^V??4?-o???K{??????1<7? -c?O_??2??? &r.w -??????#F5?V?v}8??@??t????a??? ??'@??;???e3????F?@m}?+/??u*?|0?]?M?=???;? eu+??]???%?????!d"??????.? ????8?????n????)???D??M?? -D???E??;y9???.?????? ??o;[???5K??V???4Y(?^|???`????`?????3?{I????,?:??w?W?Op???-1??b^?????=? ???O?*?YmEUu??????????\?E?`??Zt8g??5n????1????Mg#??l??.???n?????+ pOYE?v??f??u4uV?}J?i???E?w?y`?m???9ma?i??????o??R?>?&f?7??;??????=l??H????&E??&L?(?????L?4????(?d???I??N-/E??b?9??:???e??-????U?5\??.????5?:]?a?&??As??y'g[??%ay????Q??2?B/?7?????"?L& ???]Jj?>^?0???^Z??_?n?????B??g2Vw???s?$:??K*??[?#????b?7'= -Mrv?d^???%cc!2???2?_r???=yJ??? ?WH????!D?5??`?8?D?H????^yJ?????Xs???Qv-G???\??V!K??R????G????U?Q??;9~h???N?k?zhj??H?-^???iZ???/???J@?T?;? ???7?2????EU???????????4??P{?>????co#??gU????d?A0D[???????0????@_?z0??3?N??j[( -??????3k????}r?&j1Vg?qz??? $????????|c?%|M>-Y???f?$??? ?4?~^:?(?Bu2?I???W{?e????z?????R?Z????????????T?????/G)6???!?]t??$;??36 ?T?6??>&u????? 3??????|??=?p?x?^?y;u????=???????B???}?T????u?Rf ????????B????4????.:???Zc+?]??i?R?n-.??Q?i?9+&?U^??ufeu?????b???c7??/????Zml??p????l??????!j?x?g?yL?X?I????XYZ?ZHs[C????p.?78T?bu:???*W?nT???'??g|#????gK?x4?????^????%b??)??%???~??'?N?$???*F/?Tg????82?x???? *u??1?&?????u?????.?j[e??E????????#?ix:I??l?4????Z?A?nb]X((?0??+?g.?p??v#?A +~??YC?s???V??I???B?N"}?S??l?q??}2????;?e +?J?????B?=j??-B?????_r???????L?jz??V%8??YTG?yq3%yc???C?`?e???????tQT?? S ??>H?2?9???m??H|Y????R?c?fz???? +V?! 'S???? ? U?q?U??e??v Author: jedick Date: 2019-02-08 10:15:07 +0100 (Fri, 08 Feb 2019) New Revision: 387 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/man/mosaic.Rd pkg/CHNOSZ/vignettes/anintro.Rmd Log: anintro.Rmd: revise section on Optional data Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-08 08:07:59 UTC (rev 386) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-08 09:15:07 UTC (rev 387) @@ -1,6 +1,6 @@ Date: 2019-02-08 Package: CHNOSZ -Version: 1.1.3-94 +Version: 1.1.3-95 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), @@ -14,23 +14,21 @@ Depends: R (>= 3.1.0) Suggests: limSolve, testthat, knitr, rmarkdown, tufte Imports: grDevices, graphics, stats, utils -Description: An integrated set of tools for thermodynamic calculations in geochemistry and compositional - biology. The thermodynamic properties of liquid water are calculated using Fortran code from - SUPCRT92 (Johnson et al., 1992 ) or an implementation - in R of the IAPWS-95 formulation (Wagner and Pru?, 2002 ). - Thermodynamic properties of other species are taken from a database for minerals and inorganic - and organic aqueous species including biomolecules, or from amino acid group additivity for - proteins (Dick et al., 2006 ). High-temperature properties are - calculated using the Berman-Brown (1985) equations for minerals - and the revised Helgeson-Kirkham-Flowers (1981) equations for - aqueous species. The HKF equations are augmented with the Deep Earth Water (DEW) model - (Sverjensky et al., 2014 ) and estimates of parameters in the - extended Debye-H?ckel equation (Manning et al., 2013 ) - to calculate standard-state properties and activity coefficients for given ionic strength at high - pressure (to 6 GPa). Functions are provided to calculate standard-state properties of species and - reactions, define the basis species of a chemical system, automatically balance reactions, calculate - the chemical affinities of formation reactions for selected species, calculate the equilibrium - activities of those species, and plot the results on chemical activity diagrams. +Description: An integrated set of tools for thermodynamic calculations in + aqueous geochemistry and geobiochemistry. Functions are provided for writing + balanced reactions to form species from user-selected basis species and for + calculating the standard molal properties of species and reactions, including + the standard Gibbs energy and equilibrium constant. Calculations of the + non-equilibrium chemical affinity and equilibrium chemical activity of species + can be portrayed on diagrams as a function of temperature, pressure, or + activity of basis species; in two dimensions, this gives a maximum affinity or + predominance diagram. The diagrams have formatted chemical formulas and axis + labels, and water stability limits can be added to Eh-pH, logfO2-T, and other + diagrams with a redox variable. The package has been developed to handle common + calculations in aqueous geochemistry, such as solubility due to complexation of + metal ions, mineral buffers of redox or pH, and changing the basis species + across a diagram ("mosaic diagrams"). CHNOSZ also has unique capabilities for + comparing the compositional and thermodynamic properties of different proteins. Encoding: UTF-8 License: GPL (>= 2) BuildResaveData: no Modified: pkg/CHNOSZ/man/mosaic.Rd =================================================================== --- pkg/CHNOSZ/man/mosaic.Rd 2019-02-08 08:07:59 UTC (rev 386) +++ pkg/CHNOSZ/man/mosaic.Rd 2019-02-08 09:15:07 UTC (rev 387) @@ -56,8 +56,8 @@ \dontshow{data(thermo)}# Fe-minerals and aqueous species in Fe-S-O-H system # speciate SO4-2, HSO4-, HS-, H2S as a function of Eh and pH # after Garrels and Christ, 1965 Figure 7.20 -pH <- c(0, 14, 500) -Eh <- c(-1, 1, 500) +pH <- c(0, 14, 250) +Eh <- c(-1, 1, 250) T <- 25 basis(c("FeO", "SO4-2", "H2O", "H+", "e-")) basis("SO4-2", -6) @@ -78,6 +78,7 @@ diagram(m2$A.species, add = TRUE, names = NULL) title(main=paste("Iron oxides and sulfides in water, log(total S) = -6", "After Garrels and Christ, 1965", sep="\n")) +legend("bottomleft", c("log(act_Fe) = -4", "log(act_Fe) = -6"), lwd = c(2, 1), bty = "n") # we could overlay the basis species predominance fields #diagram(m1$A.bases, add=TRUE, col="blue", col.names="blue", lty=3) } Modified: pkg/CHNOSZ/vignettes/anintro.Rmd =================================================================== --- pkg/CHNOSZ/vignettes/anintro.Rmd 2019-02-08 08:07:59 UTC (rev 386) +++ pkg/CHNOSZ/vignettes/anintro.Rmd 2019-02-08 09:15:07 UTC (rev 387) @@ -251,6 +251,9 @@ ``` Multiple entries exist for methane; the index of the `aq` (aqueous) species is returned by default. +```{marginfigure} +This convention applies to organic species, but for inorganic species, the English name refers to the gas (`info("oxygen")`) while the chemical formula is used to identify the aqueous species (`info("O2")`). +``` A second argument can be used to specify a different physical state: ```{r info_methane_gas} info("methane", "gas") @@ -1962,18 +1965,24 @@ Thermodynamic properties of minerals in the default database are mostly taken from @Ber88 (including silicates, aluminosilicates, calcite, dolomite, hematite, and magnetite) and @HDNB78 (native elements, sulfides, halides, sulfates, and selected carbonates and oxides that do not duplicate any in the Berman dataset). Minerals are identified by the state `cr`, and (for the Helgeson dataset) `cr2`, `cr3`, etc. for higher-temperature polymorphs. -Two optional datasets can be activated by using `add.obigt()`: +Some optional datasets can be activated by using `add.obigt()`. The first three of these contain data that have been replaced by or are incompatible with later updates; the superseded data are kept here to reproduce published calculations and for comparison with the newer data: +`add.obigt("SUPCRT92")` -- This file contains data for minerals from SUPCRT92 (mostly Helgeson et al., 1978) that have been replaced by the Berman data set. + +`add.obigt("SLOP98")` -- This file contains data from `slop98.dat` or later slop files, from Everett Shock's GEOPIG group at Arizona State University, that were previously used in CHNOSZ but have been replaced by newer data. +This includes updates for aqueous Au species as summarized by @PAB_14, and aqueous SiO2, aqueous aluminum species, and arsenic-bearing aqueous species and minerals, as compiled in the [SUPCRTBL package](http://www.indiana.edu/~hydrogeo/supcrtbl.html) [@ZZL_16]. +Some calculations using the older data are shown in [this vignette](#complete-equilibrium-solubility) and [`demo(go-IU)`](../demo); see [`demo(gold)`](../demo) for calculations that depend exclusively on the newer data that are now loaded by default in CHNOSZ. + +`add.obigt("OldAA")` -- This file contains superseded data for amino acids (methionine and glycine) and related species, particularly the [Met], [Gly], and protein backbone groups, as well as metal-glycinate complexes. +The updates for these data have been taken from various publications ([LaRowe and Dick, 2012](https://doi.org/10.1016/j.gca.2011.11.041); [Kitadai, 2014](https://doi.org/10.1007/s00239-014-9616-1); [Azadi et al., 2019](https://doi.org/10.1016/j.fluid.2018.10.002)) +A comparison of log*K* of metal-glycinate complexes using the updated data is in [`demo(glycinate)`](../demo). + `add.obigt("DEW")` -- These are aqueous species, with modified parameters, that are intended for use with the [Deep Earth Water](http://www.dewcommunity.org/) (DEW) model [@SHA14]. You should also run `water("DEW")` to activate the equations in the model; then, they will be used by `subcrt()` and `affinity()`. Examples are in [`demo(DEW)`](../demo). -`add.obigt("SLOP98")` -- This file contains data that have been replaced by or are incompatible with more recent data updates. -This includes updates for aqueous Au species as summarized by @PAB_14, and aqueous SiO2, aqueous aluminum species, and arsenic-bearing aqueous species and minerals, as compiled in the [SUPCRTBL package](http://www.indiana.edu/~hydrogeo/supcrtbl.html) [@ZZL_16]. -These updates have been applied to the default database in CHNOSZ; some calculations using the updated data are shown in [`demo(go-IU)`](../demo) and [`demo(gold)`](../demo). +Detailed references for these optional datasets are in the vignette [*Thermodynamic data in CHNOSZ*](obigt.html) (look under **Optional Data**). -Detailed references for these optional datasets are in the vignette [*Thermodynamic data in CHNOSZ*](obigt.html) (look under **Optional Data** / **DEW** and **Optional Data** / **SLOP98**). - ## Adding data You can also use `add.obigt()` to add data from a user-specified file to the database in the current session. From noreply at r-forge.r-project.org Sat Feb 9 05:54:48 2019 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Sat, 9 Feb 2019 05:54:48 +0100 (CET) Subject: [CHNOSZ-commits] r388 - in pkg/CHNOSZ: . R tests/testthat Message-ID: <20190209045448.196E818CA36@r-forge.r-project.org> Author: jedick Date: 2019-02-09 05:54:47 +0100 (Sat, 09 Feb 2019) New Revision: 388 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/R/info.R pkg/CHNOSZ/tests/testthat/test-info.R Log: info(): improve message for info("glycine") Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-08 09:15:07 UTC (rev 387) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-09 04:54:47 UTC (rev 388) @@ -1,6 +1,6 @@ -Date: 2019-02-08 +Date: 2019-02-09 Package: CHNOSZ -Version: 1.1.3-95 +Version: 1.1.3-96 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/R/info.R =================================================================== --- pkg/CHNOSZ/R/info.R 2019-02-08 09:15:07 UTC (rev 387) +++ pkg/CHNOSZ/R/info.R 2019-02-09 04:54:47 UTC (rev 388) @@ -136,8 +136,13 @@ mystate <- thermo$obigt$state[ispecies.out] ispecies.other <- ispecies[!ispecies %in% ispecies.out] otherstates <- thermo$obigt$state[ispecies.other] + # for minerals (cr), use the word "phase"; otherwise, use "state" 20190209 + word <- "state" # substitute the mineral name for "cr" 20190121 - otherstates[otherstates=="cr"] <- thermo$obigt$name[ispecies.other[otherstates=="cr"]] + if(mystate == "cr" | sum(otherstates=="cr") > 1) { + word <- "phase" + otherstates[otherstates=="cr"] <- thermo$obigt$name[ispecies.other[otherstates=="cr"]] + } transtext <- othertext <- "" # we count, but don't show the states for phase transitions (cr2, cr3, etc) istrans <- otherstates %in% c("cr2", "cr3", "cr4", "cr5", "cr6", "cr7", "cr8", "cr9") @@ -146,12 +151,12 @@ ntrans <- sum(istrans) if(ntrans == 1) transtext <- paste(" with", ntrans, "phase transition") else if(ntrans > 1) transtext <- paste(" with", ntrans, "phase transitions") - # substitute the mineral name for "cr" 20190121 - mystate <- thermo$obigt$name[ispecies.out] + # if it's not already in the species name, substitute the mineral name for "cr" 20190121 + if(species != thermo$obigt$name[ispecies.out]) mystate <- thermo$obigt$name[ispecies.out] } otherstates <- otherstates[!istrans] - if(length(otherstates) == 1) othertext <- paste0("; other available phase is ", otherstates) - if(length(otherstates) > 1) othertext <- paste0("; other available phases are ", paste(otherstates, collapse=", ")) + if(length(otherstates) == 1) othertext <- paste0("; other available ", word, " is ", otherstates) + if(length(otherstates) > 1) othertext <- paste0("; other available ", word, "s are ", paste(otherstates, collapse=", ")) if(transtext != "" | othertext != "") { starttext <- paste0("info.character: found ", species, "(", mystate, ")") message(starttext, transtext, othertext) @@ -253,4 +258,3 @@ message("info.approx: '", species, "' has no approximate matches") return(NA) } - Modified: pkg/CHNOSZ/tests/testthat/test-info.R =================================================================== --- pkg/CHNOSZ/tests/testthat/test-info.R 2019-02-08 09:15:07 UTC (rev 387) +++ pkg/CHNOSZ/tests/testthat/test-info.R 2019-02-09 04:54:47 UTC (rev 388) @@ -4,7 +4,9 @@ expect_equal(info.character("acetate", "cr"), NA) expect_message(info.character("acetate", "cr"), "only 'aq' is available") expect_message(info.character("methane", "cr"), "only 'aq' 'liq' 'gas' are available") - expect_message(info.character("methane"), "other available phases are liq, gas") + expect_message(info.character("methane"), "other available states are liq, gas") + expect_message(info.character("SiO2", "cr"), "other available phases are") + expect_message(info.character("chalcocite"), "found chalcocite\\(cr\\) with 2 phase transitions") # H2O is a special case expect_equal(info.character("H2O", "aq"), info.character("H2O", "liq")) }) From noreply at r-forge.r-project.org Sat Feb 9 06:15:08 2019 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Sat, 9 Feb 2019 06:15:08 +0100 (CET) Subject: [CHNOSZ-commits] r389 - in pkg/CHNOSZ: . R inst/extdata/OBIGT inst/extdata/thermo tests/testthat Message-ID: <20190209051508.9E10718C1A8@r-forge.r-project.org> Author: jedick Date: 2019-02-09 06:15:07 +0100 (Sat, 09 Feb 2019) New Revision: 389 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/R/info.R pkg/CHNOSZ/inst/extdata/OBIGT/OldAA.csv pkg/CHNOSZ/inst/extdata/thermo/SK95.csv pkg/CHNOSZ/tests/testthat/test-recalculate.R Log: info(): add OldAA.csv to list of optional data files for searching Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-09 04:54:47 UTC (rev 388) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-09 05:15:07 UTC (rev 389) @@ -1,6 +1,6 @@ Date: 2019-02-09 Package: CHNOSZ -Version: 1.1.3-96 +Version: 1.1.3-98 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/R/info.R =================================================================== --- pkg/CHNOSZ/R/info.R 2019-02-09 04:54:47 UTC (rev 388) +++ pkg/CHNOSZ/R/info.R 2019-02-09 05:15:07 UTC (rev 389) @@ -248,7 +248,7 @@ } # if we got here there were no approximate matches # 20190127 look for the species in optional data files - for(opt in c("SLOP98", "SUPCRT92")) { + for(opt in c("SLOP98", "SUPCRT92", "OldAA")) { optdat <- read.csv(system.file(paste0("extdata/OBIGT/", opt, ".csv"), package="CHNOSZ"), as.is=TRUE) if(species %in% optdat$name) { message('info.approx: ', species, ' is in an optional database; use add.obigt("', opt, '", "', species, '") to load it') Modified: pkg/CHNOSZ/inst/extdata/OBIGT/OldAA.csv =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/OldAA.csv 2019-02-09 04:54:47 UTC (rev 388) +++ pkg/CHNOSZ/inst/extdata/OBIGT/OldAA.csv 2019-02-09 05:15:07 UTC (rev 389) @@ -37,29 +37,29 @@ Cd(Gly)2,NA,Cd(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-185236,-250387,68.18,148.7,92.1,14.355,27.2722,-4.9746,-3.9063,93.0282,27.2523,-0.03,0 Eu(Gly)+,NA,Eu(C2H4NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-208959,-236026,49.509,89.8,50.3,8.5841,13.176,0.5767,-3.3236,57.1645,15.2476,-0.1738,1 Eu(Gly)2,NA,Eu(C2H4NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-288477,-346709,97.734,190.4,108.7,16.6314,32.8272,-7.1514,-4.136,117.4699,35.7476,-0.03,0 -Ca(Alan)+,NA,Ca(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-209172,-247643,35.015,104.6,50.7,8.7124,13.4888,0.454,-3.3365,67.7227,18.2713,0.0279,1 -Ca(Alan)2,NA,Ca(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-285446,-365834,79.755,239.1,127.3,19.1765,39.0448,-9.6021,-4.393,146.0369,45.6768,-0.03,0 -Mg(Alan)+,NA,Mg(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-186539,-232305,8.428,109.5,46.8,8.3169,12.5282,0.821,-3.2968,74.3351,19.275,0.4322,1 -Mg(Alan)2,NA,Mg(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-263631,-353761,44.962,248.8,123,18.5836,37.5967,-9.0318,-4.3331,151.6713,47.6352,-0.03,0 -Sr(Alan)+,NA,Sr(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-211130,-248184,43.155,98.9,51.4,8.77,13.6312,0.3947,-3.3424,63.2691,17.1163,-0.0948,1 -Sr(Alan)2,NA,Sr(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-286831,-365053,90.407,228.1,128.1,19.2869,39.3109,-9.699,-4.404,139.5534,43.4233,-0.03,0 -Ba(Alan)+,NA,Ba(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-210713,-244263,56.557,93.7,56.8,9.4348,15.2528,-0.2391,-3.4095,58.4325,16.085,-0.2977,1 -Ba(Alan)2,NA,Ba(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-286687,-360171,107.946,218.2,134.1,20.104,41.3073,-10.4865,-4.4865,133.7647,41.4112,-0.03,0 -Mn(Alan)+,NA,Mn(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-134280,-173740,29.425,112.3,51.8,8.8873,13.9167,0.2842,-3.3542,73.0237,19.8433,0.1124,1 -Mn(Alan)2,NA,Mn(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-213474,-295365,72.44,254.2,128.5,19.3395,39.4414,-9.7539,-4.4094,154.8617,48.744,-0.03,0 -Fe(Alan)+,NA,Fe(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-103952,-146326,18.518,103.3,46.1,8.1661,12.1558,0.976,-3.2814,69.2856,18.01,0.2792,1 -Fe(Alan)2,NA,Fe(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-184387,-269655,58.166,236.6,122.2,18.4732,37.3244,-8.9189,-4.3219,144.5703,45.1671,-0.03,0 -Ni(Alan)+,NA,Ni(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-94227,-137691,15.46,95.2,38.5,7.1451,9.664,1.9536,-3.1784,64.9703,16.36,0.326,1 -Ni(Alan)2,NA,Ni(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-175945,-264092,50.92,220.8,113.8,17.318,34.504,-7.8105,-4.2053,135.3083,41.9478,-0.03,0 -Cu(Alan)+,NA,Cu(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,06.Feb.19,-71295,-110530,25.46,108.7,43.4,7.7387,11.1165,1.3762,-3.2385,70.7759,19.11,0.0974,1 -Cu(Alan)2,NA,Cu(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,06.Feb.19,-156054,-238480,65.92,247.2,119.2,18.0655,36.3271,-8.523,-4.2807,150.7452,47.3132,-0.03,0 -Zn(Alan)+,NA,Zn(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-117313,-161024,17.46,107.4,43.8,7.8514,11.3891,1.2746,-3.2497,71.8106,18.835,0.2956,1 -Zn(Alan)2,NA,Zn(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-198512,-284509,60.92,244.5,119.6,18.1164,36.4558,-8.5823,-4.286,149.2015,46.7767,-0.03,0 -Pb(Alan)+,NA,Pb(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-87891,-120835,59.148,93,53.4,8.964,14.1088,0.1992,-3.3622,57.5413,15.9017,-0.3372,1 -Pb(Alan)2,NA,Pb(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-167671,-240311,111.336,216.4,130.4,19.5944,40.0653,-10.0034,-4.4352,132.7356,41.0535,-0.03,0 -Co(Alan)+,NA,Co(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-94799,-136805,20.46,104,43.6,7.8202,11.3148,1.299,-3.2467,69.3955,18.1475,0.2482,1 -Co(Alan)2,NA,Co(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-175193,-260392,60.92,238,119.4,18.0995,36.4127,-8.5626,-4.2842,145.3423,45.4353,-0.03,0 -Cd(Alan)+,NA,Cd(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-100782,-141576,29.698,113.7,53.4,9.1151,14.4742,0.063,-3.3773,73.7914,20.1183,0.1098,1 -Cd(Alan)2,NA,Cd(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-181340,-264540,72.797,256.8,130.4,19.5944,40.0653,-10.0034,-4.4352,156.4053,49.2806,-0.03,0 -Eu(Alan)+,NA,Eu(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-206029,-242617,50.149,135,68.4,11.0532,19.2058,-1.7947,-3.5729,83.4588,24.4724,-0.2006,1 -Eu(Alan)2,NA,Eu(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-282521,-359634,99.56,298.5,147,21.8707,45.6205,-12.1799,-4.6649,180.847,57.7759,-0.03,0 +Ca(Ala)+,NA,Ca(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-209172,-247643,35.015,104.6,50.7,8.7124,13.4888,0.454,-3.3365,67.7227,18.2713,0.0279,1 +Ca(Ala)2,NA,Ca(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-285446,-365834,79.755,239.1,127.3,19.1765,39.0448,-9.6021,-4.393,146.0369,45.6768,-0.03,0 +Mg(Ala)+,NA,Mg(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-186539,-232305,8.428,109.5,46.8,8.3169,12.5282,0.821,-3.2968,74.3351,19.275,0.4322,1 +Mg(Ala)2,NA,Mg(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-263631,-353761,44.962,248.8,123,18.5836,37.5967,-9.0318,-4.3331,151.6713,47.6352,-0.03,0 +Sr(Ala)+,NA,Sr(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-211130,-248184,43.155,98.9,51.4,8.77,13.6312,0.3947,-3.3424,63.2691,17.1163,-0.0948,1 +Sr(Ala)2,NA,Sr(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-286831,-365053,90.407,228.1,128.1,19.2869,39.3109,-9.699,-4.404,139.5534,43.4233,-0.03,0 +Ba(Ala)+,NA,Ba(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-210713,-244263,56.557,93.7,56.8,9.4348,15.2528,-0.2391,-3.4095,58.4325,16.085,-0.2977,1 +Ba(Ala)2,NA,Ba(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-286687,-360171,107.946,218.2,134.1,20.104,41.3073,-10.4865,-4.4865,133.7647,41.4112,-0.03,0 +Mn(Ala)+,NA,Mn(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-134280,-173740,29.425,112.3,51.8,8.8873,13.9167,0.2842,-3.3542,73.0237,19.8433,0.1124,1 +Mn(Ala)2,NA,Mn(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-213474,-295365,72.44,254.2,128.5,19.3395,39.4414,-9.7539,-4.4094,154.8617,48.744,-0.03,0 +Fe(Ala)+,NA,Fe(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-103952,-146326,18.518,103.3,46.1,8.1661,12.1558,0.976,-3.2814,69.2856,18.01,0.2792,1 +Fe(Ala)2,NA,Fe(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-184387,-269655,58.166,236.6,122.2,18.4732,37.3244,-8.9189,-4.3219,144.5703,45.1671,-0.03,0 +Ni(Ala)+,NA,Ni(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-94227,-137691,15.46,95.2,38.5,7.1451,9.664,1.9536,-3.1784,64.9703,16.36,0.326,1 +Ni(Ala)2,NA,Ni(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-175945,-264092,50.92,220.8,113.8,17.318,34.504,-7.8105,-4.2053,135.3083,41.9478,-0.03,0 +Cu(Ala)+,NA,Cu(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,06.Feb.19,-71295,-110530,25.46,108.7,43.4,7.7387,11.1165,1.3762,-3.2385,70.7759,19.11,0.0974,1 +Cu(Ala)2,NA,Cu(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,06.Feb.19,-156054,-238480,65.92,247.2,119.2,18.0655,36.3271,-8.523,-4.2807,150.7452,47.3132,-0.03,0 +Zn(Ala)+,NA,Zn(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-117313,-161024,17.46,107.4,43.8,7.8514,11.3891,1.2746,-3.2497,71.8106,18.835,0.2956,1 +Zn(Ala)2,NA,Zn(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-198512,-284509,60.92,244.5,119.6,18.1164,36.4558,-8.5823,-4.286,149.2015,46.7767,-0.03,0 +Pb(Ala)+,NA,Pb(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-87891,-120835,59.148,93,53.4,8.964,14.1088,0.1992,-3.3622,57.5413,15.9017,-0.3372,1 +Pb(Ala)2,NA,Pb(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-167671,-240311,111.336,216.4,130.4,19.5944,40.0653,-10.0034,-4.4352,132.7356,41.0535,-0.03,0 +Co(Ala)+,NA,Co(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-94799,-136805,20.46,104,43.6,7.8202,11.3148,1.299,-3.2467,69.3955,18.1475,0.2482,1 +Co(Ala)2,NA,Co(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-175193,-260392,60.92,238,119.4,18.0995,36.4127,-8.5626,-4.2842,145.3423,45.4353,-0.03,0 +Cd(Ala)+,NA,Cd(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-100782,-141576,29.698,113.7,53.4,9.1151,14.4742,0.063,-3.3773,73.7914,20.1183,0.1098,1 +Cd(Ala)2,NA,Cd(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-181340,-264540,72.797,256.8,130.4,19.5944,40.0653,-10.0034,-4.4352,156.4053,49.2806,-0.03,0 +Eu(Ala)+,NA,Eu(C3H6NO2)+,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-206029,-242617,50.149,135,68.4,11.0532,19.2058,-1.7947,-3.5729,83.4588,24.4724,-0.2006,1 +Eu(Ala)2,NA,Eu(C3H6NO2)2,aq,"SK95.1 [S98]",CHNOSZ.2,3.Sep.06,-282521,-359634,99.56,298.5,147,21.8707,45.6205,-12.1799,-4.6649,180.847,57.7759,-0.03,0 Modified: pkg/CHNOSZ/inst/extdata/thermo/SK95.csv =================================================================== --- pkg/CHNOSZ/inst/extdata/thermo/SK95.csv 2019-02-09 04:54:47 UTC (rev 388) +++ pkg/CHNOSZ/inst/extdata/thermo/SK95.csv 2019-02-09 05:15:07 UTC (rev 389) @@ -27,29 +27,29 @@ Cd(Gly)2,NA,Cd(C2H4NO2)2,aq,SK95,CHNOSZ,3.Sep.06,-180576,-246607,65,148.7,92.1,14.355,27.2722,-4.9746,-3.9063,93.0282,27.2523,-0.03,0 Eu(Gly)+,NA,Eu(C2H4NO2)+,aq,SK95,CHNOSZ,3.Sep.06,-206629,-234136,47.919,89.8,50.3,8.5841,13.176,0.5767,-3.3236,57.1645,15.2476,-0.1738,1 Eu(Gly)2,NA,Eu(C2H4NO2)2,aq,SK95,CHNOSZ,3.Sep.06,-283817,-342929,94.554,190.4,108.7,16.6314,32.8272,-7.1514,-4.136,117.4699,35.7476,-0.03,0 -Ca(Alan)+,NA,Ca(C3H6NO2)+,aq,SK95,CHNOSZ,3.Sep.06,-208472,-247083,34.555,104.6,50.7,8.7124,13.4888,0.454,-3.3365,67.7227,18.2713,0.0279,1 -Ca(Alan)2,NA,Ca(C3H6NO2)2,aq,SK95,CHNOSZ,3.Sep.06,-284046,-364714,78.835,239.1,127.3,19.1765,39.0448,-9.6021,-4.393,146.0369,45.6768,-0.03,0 -Mg(Alan)+,NA,Mg(C3H6NO2)+,aq,SK95,CHNOSZ,3.Sep.06,-185839,-231745,7.968,109.5,46.8,8.3169,12.5282,0.821,-3.2968,74.3351,19.275,0.4322,1 -Mg(Alan)2,NA,Mg(C3H6NO2)2,aq,SK95,CHNOSZ,3.Sep.06,-262231,-352641,44.042,248.8,123,18.5836,37.5967,-9.0318,-4.3331,151.6713,47.6352,-0.03,0 -Sr(Alan)+,NA,Sr(C3H6NO2)+,aq,SK95,CHNOSZ,3.Sep.06,-210430,-247624,42.695,98.9,51.4,8.77,13.6312,0.3947,-3.3424,63.2691,17.1163,-0.0948,1 -Sr(Alan)2,NA,Sr(C3H6NO2)2,aq,SK95,CHNOSZ,3.Sep.06,-285431,-363933,89.487,228.1,128.1,19.2869,39.3109,-9.699,-4.404,139.5534,43.4233,-0.03,0 -Ba(Alan)+,NA,Ba(C3H6NO2)+,aq,SK95,CHNOSZ,3.Sep.06,-210013,-243703,56.097,93.7,56.8,9.4348,15.2528,-0.2391,-3.4095,58.4325,16.085,-0.2977,1 -Ba(Alan)2,NA,Ba(C3H6NO2)2,aq,SK95,CHNOSZ,3.Sep.06,-285287,-359051,107.026,218.2,134.1,20.104,41.3073,-10.4865,-4.4865,133.7647,41.4112,-0.03,0 -Mn(Alan)+,NA,Mn(C3H6NO2)+,aq,SK95,CHNOSZ,3.Sep.06,-133580,-173180,28.965,112.3,51.8,8.8873,13.9167,0.2842,-3.3542,73.0237,19.8433,0.1124,1 -Mn(Alan)2,NA,Mn(C3H6NO2)2,aq,SK95,CHNOSZ,3.Sep.06,-212074,-294245,71.52,254.2,128.5,19.3395,39.4414,-9.7539,-4.4094,154.8617,48.744,-0.03,0 -Fe(Alan)+,NA,Fe(C3H6NO2)+,aq,SK95,CHNOSZ,3.Sep.06,-103252,-145766,18.058,103.3,46.1,8.1661,12.1558,0.976,-3.2814,69.2856,18.01,0.2792,1 -Fe(Alan)2,NA,Fe(C3H6NO2)2,aq,SK95,CHNOSZ,3.Sep.06,-182987,-268535,57.246,236.6,122.2,18.4732,37.3244,-8.9189,-4.3219,144.5703,45.1671,-0.03,0 -Ni(Alan)+,NA,Ni(C3H6NO2)+,aq,SK95,CHNOSZ,3.Sep.06,-93527,-137131,15,95.2,38.5,7.1451,9.664,1.9536,-3.1784,64.9703,16.36,0.326,1 -Ni(Alan)2,NA,Ni(C3H6NO2)2,aq,SK95,CHNOSZ,3.Sep.06,-174545,-262972,50,220.8,113.8,17.318,34.504,-7.8105,-4.2053,135.3083,41.9478,-0.03,0 -Cu(Alan)+,NA,Cu(C3H6NO2)+,aq,SK95,CHNOSZ,12.Oct.07,-70595,-109970,25,108.7,43.4,7.7387,11.1165,1.3762,-3.2385,70.7759,19.11,0.0974,1 -Cu(Alan)2,NA,Cu(C3H6NO2)2,aq,SK95,CHNOSZ,12.Oct.07,-154654,-237360,65,247.2,119.2,18.0655,36.3271,-8.523,-4.2807,150.7452,47.3132,-0.03,0 -Zn(Alan)+,NA,Zn(C3H6NO2)+,aq,SK95,CHNOSZ,3.Sep.06,-116613,-160464,17,107.4,43.8,7.8514,11.3891,1.2746,-3.2497,71.8106,18.835,0.2956,1 -Zn(Alan)2,NA,Zn(C3H6NO2)2,aq,SK95,CHNOSZ,3.Sep.06,-197112,-283389,60,244.5,119.6,18.1164,36.4558,-8.5823,-4.286,149.2015,46.7767,-0.03,0 -Pb(Alan)+,NA,Pb(C3H6NO2)+,aq,SK95,CHNOSZ,3.Sep.06,-87191,-120275,58.688,93,53.4,8.964,14.1088,0.1992,-3.3622,57.5413,15.9017,-0.3372,1 -Pb(Alan)2,NA,Pb(C3H6NO2)2,aq,SK95,CHNOSZ,3.Sep.06,-166271,-239191,110.416,216.4,130.4,19.5944,40.0653,-10.0034,-4.4352,132.7356,41.0535,-0.03,0 -Co(Alan)+,NA,Co(C3H6NO2)+,aq,SK95,CHNOSZ,3.Sep.06,-94099,-136245,20,104,43.6,7.8202,11.3148,1.299,-3.2467,69.3955,18.1475,0.2482,1 -Co(Alan)2,NA,Co(C3H6NO2)2,aq,SK95,CHNOSZ,3.Sep.06,-173793,-259272,60,238,119.4,18.0995,36.4127,-8.5626,-4.2842,145.3423,45.4353,-0.03,0 -Cd(Alan)+,NA,Cd(C3H6NO2)+,aq,SK95,CHNOSZ,3.Sep.06,-100082,-141016,29.238,113.7,53.4,9.1151,14.4742,0.063,-3.3773,73.7914,20.1183,0.1098,1 -Cd(Alan)2,NA,Cd(C3H6NO2)2,aq,SK95,CHNOSZ,3.Sep.06,-179940,-263420,71.877,256.8,130.4,19.5944,40.0653,-10.0034,-4.4352,156.4053,49.2806,-0.03,0 -Eu(Alan)+,NA,Eu(C3H6NO2)+,aq,SK95,CHNOSZ,3.Sep.06,-205329,-242057,49.689,135,68.4,11.0532,19.2058,-1.7947,-3.5729,83.4588,24.4724,-0.2006,1 -Eu(Alan)2,NA,Eu(C3H6NO2)2,aq,SK95,CHNOSZ,3.Sep.06,-281121,-358514,98.64,298.5,147,21.8707,45.6205,-12.1799,-4.6649,180.847,57.7759,-0.03,0 +Ca(Ala)+,NA,Ca(C3H6NO2)+,aq,SK95,CHNOSZ,3.Sep.06,-208472,-247083,34.555,104.6,50.7,8.7124,13.4888,0.454,-3.3365,67.7227,18.2713,0.0279,1 +Ca(Ala)2,NA,Ca(C3H6NO2)2,aq,SK95,CHNOSZ,3.Sep.06,-284046,-364714,78.835,239.1,127.3,19.1765,39.0448,-9.6021,-4.393,146.0369,45.6768,-0.03,0 +Mg(Ala)+,NA,Mg(C3H6NO2)+,aq,SK95,CHNOSZ,3.Sep.06,-185839,-231745,7.968,109.5,46.8,8.3169,12.5282,0.821,-3.2968,74.3351,19.275,0.4322,1 +Mg(Ala)2,NA,Mg(C3H6NO2)2,aq,SK95,CHNOSZ,3.Sep.06,-262231,-352641,44.042,248.8,123,18.5836,37.5967,-9.0318,-4.3331,151.6713,47.6352,-0.03,0 +Sr(Ala)+,NA,Sr(C3H6NO2)+,aq,SK95,CHNOSZ,3.Sep.06,-210430,-247624,42.695,98.9,51.4,8.77,13.6312,0.3947,-3.3424,63.2691,17.1163,-0.0948,1 +Sr(Ala)2,NA,Sr(C3H6NO2)2,aq,SK95,CHNOSZ,3.Sep.06,-285431,-363933,89.487,228.1,128.1,19.2869,39.3109,-9.699,-4.404,139.5534,43.4233,-0.03,0 +Ba(Ala)+,NA,Ba(C3H6NO2)+,aq,SK95,CHNOSZ,3.Sep.06,-210013,-243703,56.097,93.7,56.8,9.4348,15.2528,-0.2391,-3.4095,58.4325,16.085,-0.2977,1 +Ba(Ala)2,NA,Ba(C3H6NO2)2,aq,SK95,CHNOSZ,3.Sep.06,-285287,-359051,107.026,218.2,134.1,20.104,41.3073,-10.4865,-4.4865,133.7647,41.4112,-0.03,0 +Mn(Ala)+,NA,Mn(C3H6NO2)+,aq,SK95,CHNOSZ,3.Sep.06,-133580,-173180,28.965,112.3,51.8,8.8873,13.9167,0.2842,-3.3542,73.0237,19.8433,0.1124,1 +Mn(Ala)2,NA,Mn(C3H6NO2)2,aq,SK95,CHNOSZ,3.Sep.06,-212074,-294245,71.52,254.2,128.5,19.3395,39.4414,-9.7539,-4.4094,154.8617,48.744,-0.03,0 +Fe(Ala)+,NA,Fe(C3H6NO2)+,aq,SK95,CHNOSZ,3.Sep.06,-103252,-145766,18.058,103.3,46.1,8.1661,12.1558,0.976,-3.2814,69.2856,18.01,0.2792,1 +Fe(Ala)2,NA,Fe(C3H6NO2)2,aq,SK95,CHNOSZ,3.Sep.06,-182987,-268535,57.246,236.6,122.2,18.4732,37.3244,-8.9189,-4.3219,144.5703,45.1671,-0.03,0 +Ni(Ala)+,NA,Ni(C3H6NO2)+,aq,SK95,CHNOSZ,3.Sep.06,-93527,-137131,15,95.2,38.5,7.1451,9.664,1.9536,-3.1784,64.9703,16.36,0.326,1 +Ni(Ala)2,NA,Ni(C3H6NO2)2,aq,SK95,CHNOSZ,3.Sep.06,-174545,-262972,50,220.8,113.8,17.318,34.504,-7.8105,-4.2053,135.3083,41.9478,-0.03,0 +Cu(Ala)+,NA,Cu(C3H6NO2)+,aq,SK95,CHNOSZ,12.Oct.07,-70595,-109970,25,108.7,43.4,7.7387,11.1165,1.3762,-3.2385,70.7759,19.11,0.0974,1 +Cu(Ala)2,NA,Cu(C3H6NO2)2,aq,SK95,CHNOSZ,12.Oct.07,-154654,-237360,65,247.2,119.2,18.0655,36.3271,-8.523,-4.2807,150.7452,47.3132,-0.03,0 +Zn(Ala)+,NA,Zn(C3H6NO2)+,aq,SK95,CHNOSZ,3.Sep.06,-116613,-160464,17,107.4,43.8,7.8514,11.3891,1.2746,-3.2497,71.8106,18.835,0.2956,1 +Zn(Ala)2,NA,Zn(C3H6NO2)2,aq,SK95,CHNOSZ,3.Sep.06,-197112,-283389,60,244.5,119.6,18.1164,36.4558,-8.5823,-4.286,149.2015,46.7767,-0.03,0 +Pb(Ala)+,NA,Pb(C3H6NO2)+,aq,SK95,CHNOSZ,3.Sep.06,-87191,-120275,58.688,93,53.4,8.964,14.1088,0.1992,-3.3622,57.5413,15.9017,-0.3372,1 +Pb(Ala)2,NA,Pb(C3H6NO2)2,aq,SK95,CHNOSZ,3.Sep.06,-166271,-239191,110.416,216.4,130.4,19.5944,40.0653,-10.0034,-4.4352,132.7356,41.0535,-0.03,0 +Co(Ala)+,NA,Co(C3H6NO2)+,aq,SK95,CHNOSZ,3.Sep.06,-94099,-136245,20,104,43.6,7.8202,11.3148,1.299,-3.2467,69.3955,18.1475,0.2482,1 +Co(Ala)2,NA,Co(C3H6NO2)2,aq,SK95,CHNOSZ,3.Sep.06,-173793,-259272,60,238,119.4,18.0995,36.4127,-8.5626,-4.2842,145.3423,45.4353,-0.03,0 +Cd(Ala)+,NA,Cd(C3H6NO2)+,aq,SK95,CHNOSZ,3.Sep.06,-100082,-141016,29.238,113.7,53.4,9.1151,14.4742,0.063,-3.3773,73.7914,20.1183,0.1098,1 +Cd(Ala)2,NA,Cd(C3H6NO2)2,aq,SK95,CHNOSZ,3.Sep.06,-179940,-263420,71.877,256.8,130.4,19.5944,40.0653,-10.0034,-4.4352,156.4053,49.2806,-0.03,0 +Eu(Ala)+,NA,Eu(C3H6NO2)+,aq,SK95,CHNOSZ,3.Sep.06,-205329,-242057,49.689,135,68.4,11.0532,19.2058,-1.7947,-3.5729,83.4588,24.4724,-0.2006,1 +Eu(Ala)2,NA,Eu(C3H6NO2)2,aq,SK95,CHNOSZ,3.Sep.06,-281121,-358514,98.64,298.5,147,21.8707,45.6205,-12.1799,-4.6649,180.847,57.7759,-0.03,0 Modified: pkg/CHNOSZ/tests/testthat/test-recalculate.R =================================================================== --- pkg/CHNOSZ/tests/testthat/test-recalculate.R 2019-02-09 04:54:47 UTC (rev 388) +++ pkg/CHNOSZ/tests/testthat/test-recalculate.R 2019-02-09 05:15:07 UTC (rev 389) @@ -2,7 +2,7 @@ # SK95: Shock and Korestky, 1995 # doi:10.1016/0016-7037(95)00058-8 -test_that("recalculated values from SK95 are correctly enetered in OBIGT", { +test_that("recalculated values from SK95 are correctly entered in OBIGT", { # test added 20190206 # thermodynamic data entries for amino acid glycinate and alanate complexes # (no longer in default database) @@ -11,31 +11,31 @@ iaa <- info(c("alanate", "glycinate")) iGly <- grep("\\(Gly\\)\\+$", thermo$obigt$name) iGly2 <- grep("\\(Gly\\)2$", thermo$obigt$name) - iAlan <- grep("\\(Alan\\)\\+$", thermo$obigt$name) - iAlan2 <- grep("\\(Alan\\)2$", thermo$obigt$name) + iAla <- grep("\\(Ala\\)\\+$", thermo$obigt$name) + iAla2 <- grep("\\(Ala\\)2$", thermo$obigt$name) # get values used in OBIGT aa_GHS_OBIGT <- thermo$obigt[iaa, c("G", "H", "S")] Gly_GHS_OBIGT <- thermo$obigt[iGly, c("G", "H", "S")] Gly2_GHS_OBIGT <- thermo$obigt[iGly2, c("G", "H", "S")] - Alan_GHS_OBIGT <- thermo$obigt[iAlan, c("G", "H", "S")] - Alan2_GHS_OBIGT <- thermo$obigt[iAlan2, c("G", "H", "S")] + Ala_GHS_OBIGT <- thermo$obigt[iAla, c("G", "H", "S")] + Ala2_GHS_OBIGT <- thermo$obigt[iAla2, c("G", "H", "S")] # get values from SK95 SK95 <- system.file("extdata/thermo/SK95.csv", package="CHNOSZ") add.obigt(SK95) aa_GHS_SK95 <- thermo$obigt[iaa, c("G", "H", "S")] Gly_GHS_SK95 <- thermo$obigt[iGly, c("G", "H", "S")] Gly2_GHS_SK95 <- thermo$obigt[iGly2, c("G", "H", "S")] - Alan_GHS_SK95 <- thermo$obigt[iAlan, c("G", "H", "S")] - Alan2_GHS_SK95 <- thermo$obigt[iAlan2, c("G", "H", "S")] + Ala_GHS_SK95 <- thermo$obigt[iAla, c("G", "H", "S")] + Ala2_GHS_SK95 <- thermo$obigt[iAla2, c("G", "H", "S")] # calculate differences for alanate and glycinate # nb. round values to avoid floating-point difficulties with unique() etc. - Alan_GHS_Delta <- round(aa_GHS_SK95[1, ] - aa_GHS_OBIGT[1, ], 2) + Ala_GHS_Delta <- round(aa_GHS_SK95[1, ] - aa_GHS_OBIGT[1, ], 2) Gly_GHS_Delta <- round(aa_GHS_SK95[2, ] - aa_GHS_OBIGT[2, ], 2) # test that the differences are the same in the corresponding complexes expect_equivalent(Gly_GHS_Delta, unique(round(Gly_GHS_SK95 - Gly_GHS_OBIGT, 2))) expect_equivalent(Gly_GHS_Delta, unique(round((Gly2_GHS_SK95 - Gly2_GHS_OBIGT)/2, 2))) - expect_equivalent(Alan_GHS_Delta, unique(round(Alan_GHS_SK95 - Alan_GHS_OBIGT, 2))) - expect_equivalent(Alan_GHS_Delta, unique(round((Alan2_GHS_SK95 - Alan2_GHS_OBIGT)/2, 2))) + expect_equivalent(Ala_GHS_Delta, unique(round(Ala_GHS_SK95 - Ala_GHS_OBIGT, 2))) + expect_equivalent(Ala_GHS_Delta, unique(round((Ala2_GHS_SK95 - Ala2_GHS_OBIGT)/2, 2))) # clean up data(thermo) }) From noreply at r-forge.r-project.org Sat Feb 9 06:52:59 2019 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Sat, 9 Feb 2019 06:52:59 +0100 (CET) Subject: [CHNOSZ-commits] r390 - in pkg/CHNOSZ: . R inst/extdata/OBIGT inst/extdata/thermo Message-ID: <20190209055259.A24E418C7C3@r-forge.r-project.org> Author: jedick Date: 2019-02-09 06:52:58 +0100 (Sat, 09 Feb 2019) New Revision: 390 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/R/makeup.R pkg/CHNOSZ/R/util.data.R pkg/CHNOSZ/inst/extdata/OBIGT/biotic_aq.csv.xz pkg/CHNOSZ/inst/extdata/thermo/obigt_check.csv Log: update obigt_check.csv Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-09 05:15:07 UTC (rev 389) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-09 05:52:58 UTC (rev 390) @@ -1,6 +1,6 @@ Date: 2019-02-09 Package: CHNOSZ -Version: 1.1.3-98 +Version: 1.1.3-99 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/R/makeup.R =================================================================== --- pkg/CHNOSZ/R/makeup.R 2019-02-09 05:15:07 UTC (rev 389) +++ pkg/CHNOSZ/R/makeup.R 2019-02-09 05:52:58 UTC (rev 390) @@ -79,7 +79,7 @@ if("CHNOSZ" %in% search()) { are.elements <- names(out) %in% thermo$element$element if(!all(are.elements)) warning(paste("element(s) not in thermo$element:", - paste(rownames(out)[!are.elements], collapse=" ") )) + paste(names(out)[!are.elements], collapse=" ") )) } # done! return(out) Modified: pkg/CHNOSZ/R/util.data.R =================================================================== --- pkg/CHNOSZ/R/util.data.R 2019-02-09 05:15:07 UTC (rev 389) +++ pkg/CHNOSZ/R/util.data.R 2019-02-09 05:52:58 UTC (rev 390) @@ -263,20 +263,23 @@ else if(what=="DEW") tdata <- read.csv(system.file("extdata/OBIGT/DEW_aq.csv", package="CHNOSZ"), as.is=TRUE) else if(what=="SLOP98") tdata <- read.csv(system.file("extdata/OBIGT/SLOP98.csv", package="CHNOSZ"), as.is=TRUE) else if(what=="SUPCRT92") tdata <- read.csv(system.file("extdata/OBIGT/SUPCRT92.csv", package="CHNOSZ"), as.is=TRUE) + else if(what=="OldAA") tdata <- read.csv(system.file("extdata/OBIGT/OldAA.csv", package="CHNOSZ"), as.is=TRUE) ntot <- nrow(tdata) # where to keep the results DCp <- DV <- DG <- rep(NA,ntot) # first get the aqueous species isaq <- tdata$state=="aq" - eos.aq <- obigt2eos(tdata[isaq,],"aq") - DCp.aq <- checkEOS(eos.aq,"aq","Cp",ret.diff=TRUE) - DV.aq <- checkEOS(eos.aq,"aq","V",ret.diff=TRUE) - cat(paste("check.obigt: GHS for",sum(isaq),"aq species in",what,"\n")) - DG.aq <- checkGHS(eos.aq,ret.diff=TRUE) - # store the results - DCp[isaq] <- DCp.aq - DV[isaq] <- DV.aq - DG[isaq] <- DG.aq + if(any(isaq)) { + eos.aq <- obigt2eos(tdata[isaq,],"aq") + DCp.aq <- checkEOS(eos.aq,"aq","Cp",ret.diff=TRUE) + DV.aq <- checkEOS(eos.aq,"aq","V",ret.diff=TRUE) + cat(paste("check.obigt: GHS for",sum(isaq),"aq species in",what,"\n")) + DG.aq <- checkGHS(eos.aq,ret.diff=TRUE) + # store the results + DCp[isaq] <- DCp.aq + DV[isaq] <- DV.aq + DG[isaq] <- DG.aq + } # then other species, if they are present if(sum(!isaq) > 0) { eos.cgl <- obigt2eos(tdata[!isaq,],"cgl") @@ -296,6 +299,7 @@ out <- rbind(out, checkfun("DEW")) out <- rbind(out, checkfun("SLOP98")) out <- rbind(out, checkfun("SUPCRT92")) + out <- rbind(out, checkfun("OldAA")) # set differences within a tolerance to NA out$DCp[abs(out$DCp) < 1] <- NA out$DV[abs(out$DV) < 1] <- NA Modified: pkg/CHNOSZ/inst/extdata/OBIGT/biotic_aq.csv.xz =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/biotic_aq.csv.xz 2019-02-09 05:15:07 UTC (rev 389) +++ pkg/CHNOSZ/inst/extdata/OBIGT/biotic_aq.csv.xz 2019-02-09 05:52:58 UTC (rev 390) @@ -1,4 +1,4 @@ -?7zXZ???F!t/????x4]7I??b???9??????TB;q?"?q???cL;?"??I?,t?b?PK??7?t(?em?A-P?Q?]?? ??8?.f?|?????V[?????=??K????VTm??~vw? ?2/ ??Wa???s?-?????p?lVs????H???u???? ?%?XF??k#??????????+??(??m5?St5?Fa?a??jN??8????>z???3MwS?%??????+?3x??`cw`?; $? (???????P?>????>?1b???QA??????>6o?=?-?((??pN???i????VOL?A???9 c?E3??XP?? ??kj?s?????Y!&o??w(??3?+?"???????; ??R6eW????![?????r?O>O?*?h\t????ty??)B????n<?9l?N!3???z '???}???nV?,0uVe??????? j?????|B??d^7&KK?- @@ -86,17 +86,19 @@ ?Rf ????????B????4????.:???Zc+?]??i?R?n-.??Q?i?9+&?U^??ufeu?????b???c7??/????Zml??p????l??????!j?x?g?yL?X?I????XYZ?ZHs[C????p.?78T?bu:???*W?nT???'??g|#????gK?x4?????^????%b??)??%???~??'?N?$???*F/?Tg????82?x???? *u??1?&?????u?????.?j[e??E????????#?ix:I??l?4????Z?A?nb]X((?0??+?g.?p??v#?A -~??YC?s???V??I???B?N"}?S??l?q??}2????;?e -?J?????B?=j??-B?????_r???????L?jz??V%8??YTG?yq3%yc???C?`?e???????tQT?? S ??>H?2?9???m??H|Y????R?c?fz???? -V?! 'S???? ? U?q?U??e??v???K`??/?????5f?????? -???MOq?$?vs\->?"?.&???q???{????;?k?@e?v??\?*???"?????4?g?'?+?)&k!s?'Y?5?R{???n?H??8??? ????u?7`{zuN?????N/p??q??#??,-v_b?S?u???E?v7?Ds?.????? ?>)?ci??????B??k?nD3F?-?`?R?_ff?!?xF?f+???MD???oHS?w??0L?:Y?w?L?n?f?Un-??R?????"B4$?o -?z???=3????G??7??2u-4?As?_???O}J>f_?B???y}?<#?k?X??$??i?1????{%c?~?????P:??b???K[???????TM74???x???5????k????m&5?????}m -4A?8??r_??f?-?6C_)N?t??>p ?$???OF}h? ??01S???Q_q???? mS??a??? gW$???;u?Q5B???9?%??u?nlgQ?5?C???: b????????????????L??(~??I??t`I???_???? FA?????$??l86?}?'??x?$??:[E??;??f?o#????=kV????N???2?????6?????P#????@??XR?@+?4?e\?? ????-?^W?G?Rja??j????;[?*???@?.?m@???hW???s`?8??6?~???Q?h??Z?N??g?YZ \ No newline at end of file +}%z?R??mNE?? ??Zb?F????? +???G?`?P?QT?b?rL> '??3??n#4`Bg&ZH"/?BL??)??n????=#*v???????rIgI4 +6Za??r???Teo???a@?????E5H0?F?X????H?ym?OCZU????f?? ??n????o?????#?????~?? +d?r?/?Q?>??????k??7?>+????.??????%?2??6X??XCy?\?S?:$I???_?McC?K?d????{HNFB?x#??Q@?? t??? Te?n:???k???o??%???M}ye ?|?t9"1??{ X???igE?}y{?J??"7??[O?*??N?b?n??f?g?????QI?u??t???94yO??!8 + x?+?z?????????NI?Bn#h_9o?08??)?4b(|??;??E??p,8?,???i?M????s'Y?fL?????Kq]~M + +???? ?????NgU???`??@{?*?U?(?LiS?dn???D?????Fm??B??y?8???}?7???q?{?q?????C=??>/???1???????????X?1q?*G?>2rQ?b!?I-a?24M??{f`????:??$EZ!?w?????OF??h??'?????g?YZ \ No newline at end of file Modified: pkg/CHNOSZ/inst/extdata/thermo/obigt_check.csv =================================================================== --- pkg/CHNOSZ/inst/extdata/thermo/obigt_check.csv 2019-02-09 05:15:07 UTC (rev 389) +++ pkg/CHNOSZ/inst/extdata/thermo/obigt_check.csv 2019-02-09 05:52:58 UTC (rev 390) @@ -2,241 +2,216 @@ "OBIGT",14,"CO3-2","aq",,-1.04, "OBIGT",20,"HPO4-2","aq",,-1.02, "OBIGT",49,"BO2-","aq",,-19.31, -"OBIGT",62,"Cu+2","aq",3.62,, -"OBIGT",66,"NH3","aq",2.75,, -"OBIGT",75,"SO2","aq",11.1,, -"OBIGT",93,"LaSO4+","aq",-6.02,, -"OBIGT",136,"NdF2+","aq",16.64,6.19, -"OBIGT",182,"EuF+","aq",4.11,-19.19, -"OBIGT",183,"EuF2","aq",9.75,-40.4, -"OBIGT",184,"EuF3-","aq",17.18,-64.45, -"OBIGT",185,"EuF4-2","aq",26.07,-91.02, -"OBIGT",186,"EuCl+","aq",-4.11,19.2, -"OBIGT",187,"EuCl2","aq",-9.84,40.4, -"OBIGT",188,"EuCl3-","aq",-17.19,64.47, -"OBIGT",189,"EuCl4-2","aq",-26.15,91.04, -"OBIGT",343,"UO4-2","aq",,-1.11, -"OBIGT",380,"Ag(CO3)2-3","aq",,-1.56, -"OBIGT",398,"AgCl4-3","aq",,-1.31, -"OBIGT",451,"CuCl4-2","aq",,-1.07, -"OBIGT",453,"ReO4-","aq",-1.26,, -"OBIGT",462,"PO4-3","aq",,-1.72, -"OBIGT",464,"Al+3","aq",1.74,, -"OBIGT",472,"UO2+2","aq",-1.1,, -"OBIGT",473,"Th+4","aq",,-1.14, -"OBIGT",492,"P2O7-4","aq",,-2.11, -"OBIGT",493,"HP2O7-3","aq",,-1.42, -"OBIGT",502,"AsO4-3","aq",,-1.65, -"OBIGT",513,"SO3-2","aq",,-1.02, -"OBIGT",547,"VO4-3","aq",,-1.63, -"OBIGT",559,"Zr+4","aq",,-1.18, -"OBIGT",566,"Hf+4","aq",,-1.18, -"OBIGT",571,"U+4","aq",,-1.13, -"OBIGT",587,"Ce+4","aq",,-1.13, -"OBIGT",588,"Pr+4","aq",,-1.12, -"OBIGT",589,"Nd+4","aq",,-1.12, -"OBIGT",590,"Pm+4","aq",,-1.13, -"OBIGT",591,"Sm+4","aq",,-1.14, -"OBIGT",592,"Eu+4","aq",,-1.14, -"OBIGT",593,"Gd+4","aq",,-1.16, -"OBIGT",594,"Tb+4","aq",,-1.15, -"OBIGT",595,"Dy+4","aq",,-1.15, -"OBIGT",596,"Ho+4","aq",,-1.15, -"OBIGT",597,"Er+4","aq",,-1.15, -"OBIGT",598,"Tm+4","aq",,-1.16, -"OBIGT",599,"Yb+4","aq",,-1.16, -"OBIGT",600,"Lu+4","aq",,-1.17, -"OBIGT",609,"BeO2-2","aq",,-1.17, -"OBIGT",655,"MnO2-2","aq",,-1.05, -"OBIGT",666,"CoO2-2","aq",,-1.14, -"OBIGT",671,"NiO2-2","aq",,-1.16, -"OBIGT",675,"CuO2-2","aq",,-1.09, -"OBIGT",679,"ZnO2-2","aq",,-1.17, -"OBIGT",694,"CdO2-2","aq",,-1.08, -"OBIGT",712,"RuCl4-2","aq",,-1.09, -"OBIGT",715,"Ru(SO4)3-4","aq",,-1.8, -"OBIGT",722,"RuCl5-2","aq",,-1.49, -"OBIGT",723,"RuCl6-3","aq",,-2.39, -"OBIGT",726,"Ru(SO4)3-3","aq",,-1.3, -"OBIGT",732,"RhCl4-2","aq",,-1.14, -"OBIGT",735,"Rh(SO4)3-4","aq",,-1.82, -"OBIGT",739,"RhCl2+","aq",,4.67, -"OBIGT",744,"Rh(SO4)3-3","aq",,-1.33, -"OBIGT",750,"PdCl4-2","aq",,-1.05, -"OBIGT",753,"Pd(SO4)3-4","aq",,-1.8, -"OBIGT",756,"PtCl+","aq",-3.52,1.25, -"OBIGT",757,"PtCl2","aq",-7.11,2.29, -"OBIGT",758,"PtCl3-","aq",-10.48,1.78, -"OBIGT",759,"PtCl4-2","aq",-13.86,, -"OBIGT",762,"Pt(SO4)3-4","aq",,-1.79, -"OBIGT",765,"CF4","aq",5.9,, -"OBIGT",772,"AsH3","aq",-2.67,, -"OBIGT",859,"methane","aq",-2.61,, -"OBIGT",864,"hexane","aq",1.43,3.21, -"OBIGT",867,"ethylene","aq",6.12,-3.82, -"OBIGT",891,"propanol","aq",-1.89,, -"OBIGT",1033,"urea","aq",-23.26,23.32, -"OBIGT",1046,"propanoic acid","aq",1.42,, -"OBIGT",1069,"formate","aq",1.96,, -"OBIGT",1071,"propanoate","aq",1.68,, -"OBIGT",1078,"n-decanoate","aq",-1.93,, -"OBIGT",1094,"oxalate","aq",-3.19,, -"OBIGT",1121,"alanate","aq",-24.28,, -"OBIGT",1415,"Li(Mal)-","aq",,-3.22, -"OBIGT",1419,"Al(Mal)+","aq",,-2.19, -"OBIGT",1420,"Pb(Mal)","aq",,1.16, -"OBIGT",1424,"Pb(Succ)","aq",,1.49, -"OBIGT",1425,"Na(Oxal)-","aq",,-3.14, -"OBIGT",1426,"K(Oxal)-","aq",,-2.75, -"OBIGT",1427,"Fe(Oxal)+","aq",,-2.19, -"OBIGT",1429,"Na(Mal)-","aq",,-3.11, -"OBIGT",1430,"K(Mal)-","aq",,-2.63, -"OBIGT",1432,"La(Mal)+","aq",,-1.92, -"OBIGT",1433,"Gd(Mal)+","aq",,-1.73, -"OBIGT",1434,"Lu(Mal)+","aq",,-2.25, -"OBIGT",1435,"Yb(Mal)+","aq",,-2.05, -"OBIGT",1436,"Th(Mal)+2","aq",-1.29,-4.79, -"OBIGT",1438,"Ce(Mal)+","aq",,-1.75, -"OBIGT",1439,"Nd(Mal)+","aq",4.52,, -"OBIGT",1440,"Sm(Mal)+","aq",,-1.77, -"OBIGT",1441,"Pr(Mal)+","aq",,-1.75, -"OBIGT",1442,"Eu(Mal)+","aq",,-1.87, -"OBIGT",1443,"Tb(Mal)+","aq",,-1.92, -"OBIGT",1444,"Dy(Mal)+","aq",,-1.89, -"OBIGT",1445,"Tm(Mal)+","aq",,-2.08, -"OBIGT",1446,"Ho(Mal)+","aq",,-2.08, -"OBIGT",1447,"Er(Mal)+","aq",,-2.11, -"OBIGT",1448,"Sc(Mal)+","aq",,-1.97, -"OBIGT",1449,"Fe(Mal)+","aq",,-1.97, -"OBIGT",1450,"Na(Succ)-","aq",,-2.82, -"OBIGT",1451,"K(Succ)-","aq",,-2.39, -"OBIGT",1457,"Th(Succ)+2","aq",-1.21,-4.47, -"OBIGT",1462,"NH4(Oxal)-","aq",,-2.62, -"OBIGT",1467,"Al(Oxal)+","aq",,-2.62, -"OBIGT",1468,"Yb(Oxal)+","aq",,-2.02, -"OBIGT",1469,"Ce(Oxal)+","aq",,-1.8, -"OBIGT",1470,"Nd(Oxal)+","aq",,-1.8, -"OBIGT",1471,"Eu(Oxal)+","aq",,-1.89, -"OBIGT",1472,"Gd(Oxal)+","aq",,-1.8, -"OBIGT",1473,"Ru(Oxal)+","aq",,-2.41, -"OBIGT",1474,"Pa(Oxal)+2","aq",-1.25,-4.63, -"OBIGT",1475,"Th(Oxal)+2","aq",-1.27,-4.69, -"OBIGT",1476,"U(Oxal)+2","aq",-1.25,-4.63, -"OBIGT",1477,"Np(Oxal)+2","aq",-1.27,-4.69, -"OBIGT",1480,"Am(Oxal)+","aq",,-1.8, -"OBIGT",1481,"Cm(Oxal)+","aq",,-1.8, -"OBIGT",1482,"Y(Oxal)+","aq",,-2.11, -"OBIGT",1487,"La(Oxal)+","aq",,-1.87, -"OBIGT",1488,"Tb(Oxal)+","aq",,-1.92, -"OBIGT",1489,"Er(Oxal)+","aq",,-2.05, -"OBIGT",1490,"Lu(Oxal)+","aq",,-2.19, -"OBIGT",1491,"Cr(Oxal)+","aq",,-2.58, -"OBIGT",1492,"Ga(Oxal)+","aq",,-2.66, -"OBIGT",1493,"Sc(Oxal)+","aq",,-2.13, -"OBIGT",1494,"In(Oxal)+","aq",,-2.19, -"OBIGT",1495,"Pu(Oxal)+2","aq",-1.2,-4.44, -"OBIGT",1496,"NpO2(Oxal)","aq",,-1.94, -"OBIGT",1497,"Sm(Oxal)+","aq",,-1.84, -"OBIGT",1498,"Cs(Mal)-","aq",,-2.39, -"OBIGT",1499,"NH4(Mal)-","aq",,-2.54, -"OBIGT",1504,"In(Mal)+","aq",,-2.11, -"OBIGT",1505,"Y(Mal)+","aq",,-2.02, -"OBIGT",1513,"La(Succ)+","aq",,-1.52, -"OBIGT",1514,"NH4(Succ)-","aq",,-2.26, -"OBIGT",1516,"Fe(Succ)+","aq",,-1.92, -"OBIGT",1517,"Sc(Succ)+","aq",,-1.77, -"OBIGT",1520,"NpO2(Succ)","aq",,-3.16, -"OBIGT",1521,"Sm(Succ)+","aq",,-1.48, -"OBIGT",1522,"Er(Succ)+","aq",,-1.68, -"OBIGT",1523,"U(Succ)+2","aq",-1.15,-4.27, -"OBIGT",1527,"La(Glut)+","aq",,-1.23, -"OBIGT",1528,"Y(Glut)+","aq",,-1.46, -"OBIGT",1529,"Sc(Glut)+","aq",,-1.5, -"OBIGT",1530,"Th(Glut)+2","aq",-1.09,-4.05, -"OBIGT",1533,"Fe(Glut)+","aq",,-1.05, -"OBIGT",1534,"Sm(Glut)+","aq",,-1.2, -"OBIGT",1537,"Er(Glut)+","aq",,-1.4, -"OBIGT",1539,"Ba(Adip)","aq",,1.19, -"OBIGT",1546,"Pb(Adip)","aq",,1.25, -"OBIGT",1547,"Sc(Adip)+","aq",,-1.22, -"OBIGT",1549,"Th(Adip)+2","aq",-1.02,-3.76, -"OBIGT",1550,"U(Adip)+2","aq",-1,-3.71, -"OBIGT",1552,"Li(Oxal)-","aq",,-3.3, -"OBIGT",1556,"Li(Succ)-","aq",,-2.94, -"OBIGT",1558,"Na(Glut)-","aq",,-2.34, -"OBIGT",1559,"K(Glut)-","aq",,-2.05, -"OBIGT",1560,"Li(Glut)-","aq",,-2.66, -"OBIGT",1565,"Na(Adip)-","aq",,-2.05, -"OBIGT",1566,"K(Adip)-","aq",,-1.76, -"OBIGT",1567,"Li(Adip)-","aq",,-2.38, -"OBIGT",1573,"cyclohexane","aq",9.35,6.64, -"OBIGT",1574,"argon","aq",-1.24,-8.59, -"OBIGT",1575,"benzene","aq",,-1.14, -"OBIGT",1576,"CO2","aq",-4.94,, -"OBIGT",1577,"xenon","aq",2.8,, -"OBIGT",1587,"n-butanethiol","aq",2.19,, -"OBIGT",1609,"methyldiethanolamine","aq",1.61,, -"OBIGT",1619,"cysteinate","aq",-1,, -"OBIGT",1646,"glucose","aq",1.11,, -"OBIGT",1676,"guanine","aq",-4.26,, -"OBIGT",1720,"dHUMP-","aq",-3.13,, -"OBIGT",1817,"MgADP-","aq",-1.01,, -"OBIGT",1828,"HNicMP(ox)","aq",,9.4, -"OBIGT",1836,"ribose-5-phosphate","aq",,7.48, -"OBIGT",1838,"ribose-5-phosphate-2","aq",1.53,, -"OBIGT",1839,"H4NADP(red)","aq",1.73,, -"OBIGT",1840,"H3NADP(red)-","aq",2.41,, -"OBIGT",1841,"H2NADP(red)-2","aq",1.28,, -"OBIGT",1842,"HNADP(red)-3","aq",2.09,, -"OBIGT",1843,"NADP(red)-4","aq",1.09,, -"OBIGT",1845,"H3NADP(ox)","aq",1.05,, -"OBIGT",1893,"Gly-Ala-Gly","aq",,-126.09, -"OBIGT",1894,"Gly-Arg+-Gly","aq",,-182.01, -"OBIGT",1895,"Gly-Asn-Gly","aq",,-145.77, -"OBIGT",1896,"Gly-Asp-Gly","aq",,-139.16, -"OBIGT",1897,"Gly-Cys-Gly","aq",,-139.2, -"OBIGT",1898,"Gly-Gln-Gly","aq",,-158.09, -"OBIGT",1899,"Gly-Glu-Gly","aq",,-155.4, -"OBIGT",1900,"Gly-Gly-Gly","aq",,-107.83, -"OBIGT",1901,"Gly-His-Gly","aq",,-167.84, -"OBIGT",1902,"Gly-Ile-Gly","aq",,-172.24, -"OBIGT",1903,"Gly-Leu-Gly","aq",,-171.74, -"OBIGT",1904,"Gly-Lys+-Gly","aq",,-175.45, -"OBIGT",1905,"Gly-Met-Gly","aq",,-172.45, -"OBIGT",1906,"Gly-Phe-Gly","aq",,-188.52, -"OBIGT",1907,"Gly-Pro-Gly","aq",,-140.68, -"OBIGT",1908,"Gly-Ser-Gly","aq",,-125.79, -"OBIGT",1909,"Gly-Thr-Gly","aq",,-141.19, -"OBIGT",1910,"Gly-Tyr-Gly","aq",,-190.24, -"OBIGT",1911,"Gly-Val-Gly","aq",,-155.72, -"OBIGT",1912,"[GXGBB]","aq",,-98.93, -"OBIGT",1944,"antigorite","cr",,,812 -"OBIGT",1978,"clinochlore,7a","cr",,,666 -"OBIGT",1997,"daphnite,14a","cr",,,-836 -"OBIGT",2022,"ferrosilite","cr",,,694 -"OBIGT",2023,"ferrosilite","cr2",,,694 -"OBIGT",2038,"greenalite","cr",,,142507 -"OBIGT",2053,"hydromagnesite","cr",,,-2569 -"OBIGT",2204,"jarosite","cr",,,20697 -"OBIGT",2205,"natrojarosite","cr",,,17554 -"OBIGT",2227,"n-octadecane","cr",-2.63,, -"OBIGT",2228,"n-nonadecane","cr",-13.32,, -"OBIGT",2229,"n-eicosane","cr",-2.79,, -"OBIGT",2230,"n-heneicosane","cr",-8.61,, -"OBIGT",2231,"n-docosane","cr",-2.63,, -"OBIGT",2232,"n-tricosane","cr",-5.22,, -"OBIGT",2233,"n-tetracosane","cr",-2.02,, -"OBIGT",2234,"n-pentacosane","cr",-2.93,, -"OBIGT",2235,"n-hexacosane","cr",-1.29,, -"OBIGT",2236,"n-heptacosane","cr",-1.23,, -"OBIGT",2288,"carbazole","cr",-43.39,, -"OBIGT",2329,"triphenylene","cr",,,541 -"OBIGT",2642,"deoxyadenosine","cr",,,-2977 -"OBIGT",2829,"n-nonacontane","liq",,,635 -"OBIGT",2836,"2-methyloctane","liq",10,, -"OBIGT",3249,"5,6-dithiadecane","liq",2,, -"OBIGT",3324,"ethylene","gas",-4.59,, -"OBIGT",3334,"3,5-dimethylphenol","gas",,,628 +"OBIGT",61,"Cu+2","aq",3.62,, +"OBIGT",65,"NH3","aq",2.75,, +"OBIGT",73,"SO2","aq",11.1,, +"OBIGT",91,"LaSO4+","aq",-6.02,, +"OBIGT",134,"NdF2+","aq",16.64,6.19, +"OBIGT",180,"EuF+","aq",4.11,-19.19, +"OBIGT",181,"EuF2","aq",9.75,-40.4, +"OBIGT",182,"EuF3-","aq",17.18,-64.45, +"OBIGT",183,"EuF4-2","aq",26.07,-91.02, +"OBIGT",184,"EuCl+","aq",-4.11,19.2, +"OBIGT",185,"EuCl2","aq",-9.84,40.4, +"OBIGT",186,"EuCl3-","aq",-17.19,64.47, +"OBIGT",187,"EuCl4-2","aq",-26.15,91.04, +"OBIGT",341,"UO4-2","aq",,-1.11, +"OBIGT",378,"Ag(CO3)2-3","aq",,-1.56, +"OBIGT",396,"AgCl4-3","aq",,-1.31, +"OBIGT",444,"CuCl4-2","aq",,-1.07, +"OBIGT",446,"ReO4-","aq",-1.26,, +"OBIGT",455,"PO4-3","aq",,-1.72, +"OBIGT",463,"UO2+2","aq",-1.1,, +"OBIGT",464,"Th+4","aq",,-1.14, +"OBIGT",483,"P2O7-4","aq",,-2.11, +"OBIGT",484,"HP2O7-3","aq",,-1.42, +"OBIGT",498,"SO3-2","aq",,-1.02, +"OBIGT",532,"VO4-3","aq",,-1.63, +"OBIGT",544,"Zr+4","aq",,-1.18, +"OBIGT",551,"Hf+4","aq",,-1.18, +"OBIGT",554,"U+4","aq",,-1.13, +"OBIGT",570,"Ce+4","aq",,-1.13, +"OBIGT",571,"Pr+4","aq",,-1.12, +"OBIGT",572,"Nd+4","aq",,-1.12, +"OBIGT",573,"Pm+4","aq",,-1.13, +"OBIGT",574,"Sm+4","aq",,-1.14, +"OBIGT",575,"Eu+4","aq",,-1.14, +"OBIGT",576,"Gd+4","aq",,-1.16, +"OBIGT",577,"Tb+4","aq",,-1.15, +"OBIGT",578,"Dy+4","aq",,-1.15, +"OBIGT",579,"Ho+4","aq",,-1.15, +"OBIGT",580,"Er+4","aq",,-1.15, +"OBIGT",581,"Tm+4","aq",,-1.16, +"OBIGT",582,"Yb+4","aq",,-1.16, +"OBIGT",583,"Lu+4","aq",,-1.17, +"OBIGT",592,"BeO2-2","aq",,-1.17, +"OBIGT",635,"MnO2-2","aq",,-1.05, +"OBIGT",646,"CoO2-2","aq",,-1.14, +"OBIGT",651,"NiO2-2","aq",,-1.16, +"OBIGT",655,"CuO2-2","aq",,-1.09, +"OBIGT",659,"ZnO2-2","aq",,-1.17, +"OBIGT",674,"CdO2-2","aq",,-1.08, +"OBIGT",692,"RuCl4-2","aq",,-1.09, +"OBIGT",695,"Ru(SO4)3-4","aq",,-1.8, +"OBIGT",702,"RuCl5-2","aq",,-1.49, +"OBIGT",703,"RuCl6-3","aq",,-2.39, +"OBIGT",706,"Ru(SO4)3-3","aq",,-1.3, +"OBIGT",712,"RhCl4-2","aq",,-1.14, +"OBIGT",715,"Rh(SO4)3-4","aq",,-1.82, +"OBIGT",719,"RhCl2+","aq",,4.67, +"OBIGT",724,"Rh(SO4)3-3","aq",,-1.33, +"OBIGT",730,"PdCl4-2","aq",,-1.05, +"OBIGT",733,"Pd(SO4)3-4","aq",,-1.8, +"OBIGT",736,"PtCl+","aq",-3.52,1.25, +"OBIGT",737,"PtCl2","aq",-7.11,2.29, +"OBIGT",738,"PtCl3-","aq",-10.48,1.78, +"OBIGT",739,"PtCl4-2","aq",-13.86,, +"OBIGT",742,"Pt(SO4)3-4","aq",,-1.79, +"OBIGT",745,"CF4","aq",5.9,, +"OBIGT",752,"AsH3","aq",-2.67,, +"OBIGT",841,"MgAsO4-","aq",1.3,, +"OBIGT",844,"MnAsO4-","aq",-1.45,, +"OBIGT",926,"methane","aq",-2.61,, +"OBIGT",931,"hexane","aq",1.43,3.21, +"OBIGT",934,"ethylene","aq",6.12,-3.82, +"OBIGT",958,"propanol","aq",-1.89,, +"OBIGT",1091,"urea","aq",-23.26,23.32, +"OBIGT",1104,"propanoic acid","aq",1.42,, +"OBIGT",1127,"formate","aq",1.96,, +"OBIGT",1129,"propanoate","aq",1.68,, +"OBIGT",1136,"n-decanoate","aq",-1.93,, +"OBIGT",1152,"oxalate-2","aq",-3.19,, +"OBIGT",1419,"Li(Mal)-","aq",,-3.22, +"OBIGT",1423,"Pb(Mal)","aq",,1.16, +"OBIGT",1427,"Pb(Succ)","aq",,1.49, +"OBIGT",1428,"Na(Oxal)-","aq",,-3.14, +"OBIGT",1429,"K(Oxal)-","aq",,-2.75, +"OBIGT",1430,"Fe(Oxal)+","aq",,-2.19, +"OBIGT",1432,"Na(Mal)-","aq",,-3.11, +"OBIGT",1433,"K(Mal)-","aq",,-2.63, +"OBIGT",1435,"La(Mal)+","aq",,-1.92, +"OBIGT",1436,"Gd(Mal)+","aq",,-1.73, +"OBIGT",1437,"Lu(Mal)+","aq",,-2.25, +"OBIGT",1438,"Yb(Mal)+","aq",,-2.05, +"OBIGT",1439,"Th(Mal)+2","aq",-1.29,-4.79, +"OBIGT",1441,"Ce(Mal)+","aq",,-1.75, +"OBIGT",1442,"Nd(Mal)+","aq",4.52,, +"OBIGT",1443,"Sm(Mal)+","aq",,-1.77, +"OBIGT",1444,"Pr(Mal)+","aq",,-1.75, +"OBIGT",1445,"Eu(Mal)+","aq",,-1.87, +"OBIGT",1446,"Tb(Mal)+","aq",,-1.92, +"OBIGT",1447,"Dy(Mal)+","aq",,-1.89, +"OBIGT",1448,"Tm(Mal)+","aq",,-2.08, +"OBIGT",1449,"Ho(Mal)+","aq",,-2.08, +"OBIGT",1450,"Er(Mal)+","aq",,-2.11, +"OBIGT",1451,"Sc(Mal)+","aq",,-1.97, +"OBIGT",1452,"Fe(Mal)+","aq",,-1.97, +"OBIGT",1453,"Na(Succ)-","aq",,-2.82, +"OBIGT",1454,"K(Succ)-","aq",,-2.39, +"OBIGT",1460,"Th(Succ)+2","aq",-1.21,-4.47, +"OBIGT",1465,"NH4(Oxal)-","aq",,-2.62, +"OBIGT",1470,"Yb(Oxal)+","aq",,-2.02, +"OBIGT",1471,"Ce(Oxal)+","aq",,-1.8, +"OBIGT",1472,"Nd(Oxal)+","aq",,-1.8, +"OBIGT",1473,"Eu(Oxal)+","aq",,-1.89, +"OBIGT",1474,"Gd(Oxal)+","aq",,-1.8, +"OBIGT",1475,"Ru(Oxal)+","aq",,-2.41, +"OBIGT",1476,"Pa(Oxal)+2","aq",-1.25,-4.63, +"OBIGT",1477,"Th(Oxal)+2","aq",-1.27,-4.69, +"OBIGT",1478,"U(Oxal)+2","aq",-1.25,-4.63, +"OBIGT",1479,"Np(Oxal)+2","aq",-1.27,-4.69, +"OBIGT",1482,"Am(Oxal)+","aq",,-1.8, +"OBIGT",1483,"Cm(Oxal)+","aq",,-1.8, +"OBIGT",1484,"Y(Oxal)+","aq",,-2.11, +"OBIGT",1489,"La(Oxal)+","aq",,-1.87, +"OBIGT",1490,"Tb(Oxal)+","aq",,-1.92, +"OBIGT",1491,"Er(Oxal)+","aq",,-2.05, +"OBIGT",1492,"Lu(Oxal)+","aq",,-2.19, +"OBIGT",1493,"Cr(Oxal)+","aq",,-2.58, +"OBIGT",1494,"Ga(Oxal)+","aq",,-2.66, +"OBIGT",1495,"Sc(Oxal)+","aq",,-2.13, +"OBIGT",1496,"In(Oxal)+","aq",,-2.19, +"OBIGT",1497,"Pu(Oxal)+2","aq",-1.2,-4.44, +"OBIGT",1498,"NpO2(Oxal)","aq",,-1.94, +"OBIGT",1499,"Sm(Oxal)+","aq",,-1.84, +"OBIGT",1500,"Cs(Mal)-","aq",,-2.39, +"OBIGT",1501,"NH4(Mal)-","aq",,-2.54, +"OBIGT",1506,"In(Mal)+","aq",,-2.11, +"OBIGT",1507,"Y(Mal)+","aq",,-2.02, +"OBIGT",1515,"La(Succ)+","aq",,-1.52, +"OBIGT",1516,"NH4(Succ)-","aq",,-2.26, +"OBIGT",1518,"Fe(Succ)+","aq",,-1.92, +"OBIGT",1519,"Sc(Succ)+","aq",,-1.77, +"OBIGT",1522,"NpO2(Succ)","aq",,-3.16, +"OBIGT",1523,"Sm(Succ)+","aq",,-1.48, +"OBIGT",1524,"Er(Succ)+","aq",,-1.68, +"OBIGT",1525,"U(Succ)+2","aq",-1.15,-4.27, +"OBIGT",1529,"La(Glut)+","aq",,-1.23, +"OBIGT",1530,"Y(Glut)+","aq",,-1.46, +"OBIGT",1531,"Sc(Glut)+","aq",,-1.5, +"OBIGT",1532,"Th(Glut)+2","aq",-1.09,-4.05, +"OBIGT",1535,"Fe(Glut)+","aq",,-1.05, +"OBIGT",1536,"Sm(Glut)+","aq",,-1.2, +"OBIGT",1539,"Er(Glut)+","aq",,-1.4, +"OBIGT",1541,"Ba(Adip)","aq",,1.19, +"OBIGT",1548,"Pb(Adip)","aq",,1.25, +"OBIGT",1549,"Sc(Adip)+","aq",,-1.22, +"OBIGT",1551,"Th(Adip)+2","aq",-1.02,-3.76, +"OBIGT",1552,"U(Adip)+2","aq",-1,-3.71, +"OBIGT",1554,"Li(Oxal)-","aq",,-3.3, +"OBIGT",1558,"Li(Succ)-","aq",,-2.94, +"OBIGT",1560,"Na(Glut)-","aq",,-2.34, +"OBIGT",1561,"K(Glut)-","aq",,-2.05, +"OBIGT",1562,"Li(Glut)-","aq",,-2.66, +"OBIGT",1567,"Na(Adip)-","aq",,-2.05, +"OBIGT",1568,"K(Adip)-","aq",,-1.76, +"OBIGT",1569,"Li(Adip)-","aq",,-2.38, +"OBIGT",1575,"cyclohexane","aq",9.35,6.64, +"OBIGT",1576,"argon","aq",-1.24,-8.59, +"OBIGT",1577,"benzene","aq",,-1.14, +"OBIGT",1578,"CO2","aq",-4.94,, +"OBIGT",1579,"xenon","aq",2.8,, +"OBIGT",1589,"n-butanethiol","aq",2.19,, +"OBIGT",1611,"methyldiethanolamine","aq",1.61,, +"OBIGT",1621,"cysteinate","aq",-1,, +"OBIGT",1647,"glucose","aq",1.11,, +"OBIGT",1675,"guanine","aq",-4.26,, +"OBIGT",1719,"dHUMP-","aq",-3.13,, +"OBIGT",1816,"MgADP-","aq",-1.01,, +"OBIGT",1827,"HNicMP(ox)","aq",,9.4, +"OBIGT",1835,"ribose-5-phosphate","aq",,7.48, +"OBIGT",1837,"ribose-5-phosphate-2","aq",1.53,, +"OBIGT",1838,"H4NADP(red)","aq",1.73,, +"OBIGT",1839,"H3NADP(red)-","aq",2.41,, +"OBIGT",1840,"H2NADP(red)-2","aq",1.28,, +"OBIGT",1841,"HNADP(red)-3","aq",2.09,, +"OBIGT",1842,"NADP(red)-4","aq",1.09,, +"OBIGT",1844,"H3NADP(ox)","aq",1.05,, +"OBIGT",1915,"diglycine+","aq",-177.69,, +"OBIGT",1916,"diglycine-","aq",-49.22,, +"OBIGT",1917,"triglycine+","aq",,1.75, +"OBIGT",1918,"triglycine-","aq",,1.78, +"OBIGT",2048,"jarosite","cr",,,20697 +"OBIGT",2049,"natrojarosite","cr",,,17554 +"OBIGT",2068,"dawsonite","cr",,,4653 +"OBIGT",2089,"n-octadecane","cr",-2.63,, +"OBIGT",2090,"n-nonadecane","cr",-13.32,, +"OBIGT",2091,"n-eicosane","cr",-2.79,, +"OBIGT",2092,"n-heneicosane","cr",-8.61,, +"OBIGT",2093,"n-docosane","cr",-2.63,, +"OBIGT",2094,"n-tricosane","cr",-5.22,, +"OBIGT",2095,"n-tetracosane","cr",-2.02,, +"OBIGT",2096,"n-pentacosane","cr",-2.93,, +"OBIGT",2097,"n-hexacosane","cr",-1.29,, +"OBIGT",2098,"n-heptacosane","cr",-1.23,, +"OBIGT",2150,"carbazole","cr",-43.39,, +"OBIGT",2191,"triphenylene","cr",,,541 +"OBIGT",2504,"deoxyadenosine","cr",,,-2977 +"OBIGT",2691,"n-nonacontane","liq",,,635 +"OBIGT",2698,"2-methyloctane","liq",10,, +"OBIGT",3111,"5,6-dithiadecane","liq",2,, +"OBIGT",3186,"ethylene","gas",-4.59,, +"OBIGT",3196,"3,5-dimethylphenol","gas",,,628 "DEW",15,"BO(OH)","aq",,,-1111 "DEW",19,"CaCl+","aq",,,-593 "DEW",20,"CaCl2","aq",,,-7937 @@ -271,6 +246,20 @@ "DEW",177,"SO3-2","aq",,-1.02, "DEW",186,"U+4","aq",,-1.13, "DEW",199,"ZnCl3-","aq",,,2264 -"SUPCRTBL",16,"dawsonite","cr",,,4653 -"SUPCRTBL",76,"MgAsO4-","aq",1.3,, -"SUPCRTBL",79,"MnAsO4-","aq",-1.45,, +"SLOP98",4,"AuCl4-3","aq",,,117800 +"SLOP98",11,"AsO4-3","aq",,-1.65, +"SLOP98",20,"Al+3","aq",1.74,, +"SLOP98",27,"Al(Mal)+","aq",,-2.19, +"SLOP98",28,"Al(Oxal)+","aq",,-2.62, +"SUPCRT92",26,"antigorite","cr",,,812 +"SUPCRT92",43,"clinochlore,7a","cr",,,666 +"SUPCRT92",59,"daphnite,14a","cr",,,-836 +"SUPCRT92",84,"ferrosilite","cr",,,694 +"SUPCRT92",85,"ferrosilite","cr2",,,694 +"SUPCRT92",96,"greenalite","cr",,,142507 +"SUPCRT92",110,"hydromagnesite","cr",,,-2569 +"OldAA",11,"alanate","aq",-24.28,, +"OldAA",24,"Fe(Gly)2","aq",,,537 +"OldAA",50,"Fe(Ala)2","aq",,,553 +"OldAA",53,"Cu(Ala)+","aq",,,1490 +"OldAA",54,"Cu(Ala)2","aq",,,1502 From noreply at r-forge.r-project.org Sat Feb 9 09:19:06 2019 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Sat, 9 Feb 2019 09:19:06 +0100 (CET) Subject: [CHNOSZ-commits] r391 - in pkg/CHNOSZ: . demo inst man vignettes Message-ID: <20190209081906.538A218BD00@r-forge.r-project.org> Author: jedick Date: 2019-02-09 09:18:42 +0100 (Sat, 09 Feb 2019) New Revision: 391 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/demo/00Index pkg/CHNOSZ/inst/CHECKLIST pkg/CHNOSZ/inst/NEWS pkg/CHNOSZ/man/add.obigt.Rd pkg/CHNOSZ/man/affinity.Rd pkg/CHNOSZ/man/basis.Rd pkg/CHNOSZ/man/berman.Rd pkg/CHNOSZ/man/diagram.Rd pkg/CHNOSZ/man/examples.Rd pkg/CHNOSZ/vignettes/anintro.Rmd Log: Rd files: fix truncated lines in PDF Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-09 05:52:58 UTC (rev 390) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-09 08:18:42 UTC (rev 391) @@ -1,6 +1,6 @@ Date: 2019-02-09 Package: CHNOSZ -Version: 1.1.3-99 +Version: 1.1.3-100 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/demo/00Index =================================================================== --- pkg/CHNOSZ/demo/00Index 2019-02-09 05:52:58 UTC (rev 390) +++ pkg/CHNOSZ/demo/00Index 2019-02-09 08:18:42 UTC (rev 391) @@ -10,7 +10,7 @@ buffer Minerals and aqueous species as buffers of hydrogen fugacity protbuff Chemical activities buffered by thiol peroxidases or sigma factors yeastgfp Subcellular locations: log fO2 - log aH2O and log a - log fO2 diagrams -glycinate Divalent and monovalent metal-glycinate complexes +glycinate Metal-glycinate complexes mosaic Eh-pH diagram for iron oxides, sulfides and carbonate with two sets of changing basis species copper Another example of mosaic(): complexation of copper with glycine species solubility Solubility of calcite and CO2(gas) as a function of pH Modified: pkg/CHNOSZ/inst/CHECKLIST =================================================================== --- pkg/CHNOSZ/inst/CHECKLIST 2019-02-09 05:52:58 UTC (rev 390) +++ pkg/CHNOSZ/inst/CHECKLIST 2019-02-09 08:18:42 UTC (rev 391) @@ -24,7 +24,7 @@ try both qpdf and ghostscript to compact vignettes: R CMD build --compact-vignettes=both chnosz/ -- check reverse dependencies: ecipex and canprot packages +- check reverse dependencies on CRAN: LipidMS, canprot, ecipex, iemisc as of 2019-02-09 - vignettes/obigt.bib: check correct year for CHNOSZ reference Modified: pkg/CHNOSZ/inst/NEWS =================================================================== --- pkg/CHNOSZ/inst/NEWS 2019-02-09 05:52:58 UTC (rev 390) +++ pkg/CHNOSZ/inst/NEWS 2019-02-09 08:18:42 UTC (rev 391) @@ -1,5 +1,5 @@ -CHANGES IN CHNOSZ 1.1.3-93 (2019-02-08) ---------------------------------------- +CHANGES IN CHNOSZ 1.1.3-100 (2019-02-09) +---------------------------------------- BUG FIXES @@ -19,8 +19,8 @@ reactions, and the user hasn't provided balance coefficients, stop with an error instead of setting the balance cofficients to 1. Thanks to Shuang Kong for an example calculation and Tucker Ely for - a previous request to produce an error here. The affected code is in - balance(), an unexported function used in equilibrate() and + a previous suggestion to produce an error here. The affected code is + in balance(), an unexported function used in equilibrate() and diagram() (and now also solubility()). NEW FEATURE: SOLUBILITY CALCULATIONS Modified: pkg/CHNOSZ/man/add.obigt.Rd =================================================================== --- pkg/CHNOSZ/man/add.obigt.Rd 2019-02-09 05:52:58 UTC (rev 390) +++ pkg/CHNOSZ/man/add.obigt.Rd 2019-02-09 08:18:42 UTC (rev 391) @@ -118,7 +118,8 @@ add.obigt("OldAA") DLH06 <- subcrt(c("[AABB]", "[UPBB]", "H2O"), c(-1, 1, 1), T = seq(0, 300, 10)) xlab <- axis.label("T"); ylab <- axis.label("DG", prefix="k") -plot(Kit14$out$T, Kit14$out$G/1000, type = "l", ylim = c(10, 35), xlab = xlab, ylab = ylab) +plot(Kit14$out$T, Kit14$out$G/1000, type = "l", ylim = c(10, 35), + xlab = xlab, ylab = ylab) lines(DLH06$out$T, DLH06$out$G/1000, lty = 2) legend("topleft", c("Dick et al., 2006", "Kitadai, 2014"), lty = c(2, 1)) title(main = "AABB = UPBB + H2O; after Figure 9 of Kitadai, 2014") Modified: pkg/CHNOSZ/man/affinity.Rd =================================================================== --- pkg/CHNOSZ/man/affinity.Rd 2019-02-09 05:52:58 UTC (rev 390) +++ pkg/CHNOSZ/man/affinity.Rd 2019-02-09 08:18:42 UTC (rev 391) @@ -7,8 +7,9 @@ } \usage{ - affinity(..., property=NULL, sout=NULL, exceed.Ttr=FALSE, exceed.rhomin = FALSE, - return.buffer=FALSE, return.sout=FALSE, balance="PBB", iprotein=NULL, loga.protein=-3) + affinity(..., property = NULL, sout = NULL, exceed.Ttr = FALSE, + exceed.rhomin = FALSE, return.buffer = FALSE, return.sout = FALSE, + balance = "PBB", iprotein = NULL, loga.protein = -3) } \arguments{ Modified: pkg/CHNOSZ/man/basis.Rd =================================================================== --- pkg/CHNOSZ/man/basis.Rd 2019-02-09 05:52:58 UTC (rev 390) +++ pkg/CHNOSZ/man/basis.Rd 2019-02-09 08:18:42 UTC (rev 391) @@ -33,11 +33,9 @@ Whenever \code{basis} is called with NULL values of both \code{state} and \code{logact}, the new set of species, if they are a valid basis set, completely replaces any existing basis definition. If this occurs, any existing species definition (created by the \code{species} function) is deleted. -Call \code{basis} with \code{delete} set to TRUE or \code{species} set to \samp{""} to clear the basis definition. -This also deletes the \code{\link{species}} list, if any. +Call \code{basis} with \code{delete} set to TRUE or \code{species} set to \samp{""} to clear the basis definition and that of the \code{\link{species}}, if present. If the value of \code{basis} is one of the keywords in the following table, the corresponding set of basis species is loaded, and their activities are given preset values. -This approach is used by many of the examples in the package. The basis species identified by these keywords are aqueous except for \H2O (liq), \O2 (gas) and \Fe2O3 (hematite). \tabular{ll}{ Modified: pkg/CHNOSZ/man/berman.Rd =================================================================== --- pkg/CHNOSZ/man/berman.Rd 2019-02-09 05:52:58 UTC (rev 390) +++ pkg/CHNOSZ/man/berman.Rd 2019-02-09 08:18:42 UTC (rev 391) @@ -126,7 +126,8 @@ # and not coesite or some other phase of SiO2 iSiO2 <- rownames(basis()) == "SiO2" stopifnot(info(basis()$ispecies[iSiO2])$name == "quartz") -# Berman's dataset doesn't have the upper temperature limits, so we don't need exceed.Ttr here +# Berman's dataset doesn't have the upper temperature limits, +# so we don't need exceed.Ttr here a <- affinity(`K+` = c(0, 5, res), T = c(200, 650, res), P = 1000, exceed.rhomin = TRUE) diagram(a, add = TRUE, names = NULL, col = "blue", lwd = 1.5) # the list of references: Modified: pkg/CHNOSZ/man/diagram.Rd =================================================================== --- pkg/CHNOSZ/man/diagram.Rd 2019-02-09 05:52:58 UTC (rev 390) +++ pkg/CHNOSZ/man/diagram.Rd 2019-02-09 08:18:42 UTC (rev 391) @@ -14,25 +14,26 @@ eout, # type plot type = "auto", alpha = FALSE, normalize = FALSE, - as.residue = FALSE, balance=NULL, groups=as.list(1:length(eout$values)), + as.residue = FALSE, balance = NULL, groups = as.list(1:length(eout$values)), # figure size and sides for axis tick marks - xrange=NULL, mar=NULL, yline=par("mgp")[1]+0.3, side=1:4, + xrange = NULL, mar = NULL, yline = par("mgp")[1]+0.3, side = 1:4, # axis limits and labels - ylog=TRUE, xlim=NULL, ylim=NULL, xlab=NULL, ylab=NULL, + ylog = TRUE, xlim = NULL, ylim = NULL, xlab = NULL, ylab = NULL, # character sizes - cex=par("cex"), cex.names=1, cex.axis=par("cex"), + cex = par("cex"), cex.names = 1, cex.axis = par("cex"), # line styles - lty=NULL, lwd=par("lwd"), dotted=NULL, spline.method = NULL, contour.method = "edge", + lty = NULL, lwd = par("lwd"), dotted = NULL, spline.method = NULL, + contour.method = "edge", # colors - col=par("col"), col.names=par("col"), fill=NULL, - fill.NA="slategray1", limit.water=TRUE, + col = par("col"), col.names = par("col"), fill = NULL, + fill.NA = "slategray1", limit.water = TRUE, # field and line labels - names=NULL, format.names=TRUE, bold = FALSE, italic = FALSE, - font = par("font"), family = par("family"), adj=0.5, dy=0, srt=0, + names = NULL, format.names = TRUE, bold = FALSE, italic = FALSE, + font = par("font"), family = par("family"), adj = 0.5, dy = 0, srt = 0, # title and legend - main=NULL, legend.x=NA, + main = NULL, legend.x = NA, # plotting controls - add=FALSE, plot.it=TRUE, tplot=TRUE, ...) + add = FALSE, plot.it = TRUE, tplot = TRUE, ...) strip(affinity, ispecies = NULL, col = NULL, ns = NULL, xticks = NULL, ymin = -0.2, xpad = 1, cex.names = 0.7) find.tp(x) Modified: pkg/CHNOSZ/man/examples.Rd =================================================================== --- pkg/CHNOSZ/man/examples.Rd 2019-02-09 05:52:58 UTC (rev 390) +++ pkg/CHNOSZ/man/examples.Rd 2019-02-09 08:18:42 UTC (rev 391) @@ -28,37 +28,36 @@ \code{demos} runs all the \code{\link{demo}s} in the package. The demo(s) to run is/are specified by \code{which}; the default is to run them in the order of the list below. -(Demos that are displayed on the CHNOSZ website (\url{http://chnosz.net/demos}) are indicated with an asterisk.) \tabular{ll}{ \code{sources} \tab Cross-check the reference list with the thermodynamic database \cr \code{protein.equil} \tab Chemical activities of two proteins in metastable equilibrium (Dick and Shock, 2011) \cr \code{affinity} \tab Affinities of metabolic reactions and amino acid synthesis (Amend and Shock, 1998, 2001) \cr - \code{NaCl} \tab * Equilibrium constant for aqueous NaCl dissociation (Shock et al., 1992) \cr - \code{density} \tab * Density of \H2O, inverted from IAPWS-95 equations (\code{\link{rho.IAPWS95}}) \cr - \code{ORP} \tab * Temperature dependence of oxidation-reduction potential for redox standards \cr + \code{NaCl} \tab Equilibrium constant for aqueous NaCl dissociation (Shock et al., 1992) \cr + \code{density} \tab Density of \H2O, inverted from IAPWS-95 equations (\code{\link{rho.IAPWS95}}) \cr + \code{ORP} \tab Temperature dependence of oxidation-reduction potential for redox standards \cr \code{revisit} \tab Coefficient of variation of metastable equilibrium activities of proteins \cr \code{findit} \tab Minimize the standard deviation of logarithms of activities of sulfur species \cr \code{ionize} \tab ionize.aa(): contour plots of net charge and ionization properties of LYSC_CHICK \cr - \code{buffer} \tab * Minerals and aqueous species as buffers of hydrogen fugacity (Schulte and Shock, 1995) \cr + \code{buffer} \tab Minerals and aqueous species as buffers of hydrogen fugacity (Schulte and Shock, 1995) \cr \code{protbuff} \tab Chemical activities buffered by thiol peroxidases or sigma factors \cr - \code{yeastgfp} \tab * Subcellular locations: \logfO2 - \logaH2O and \loga - \logfO2 diagrams (Dick, 2009) \cr - \code{glycinate} \tab * Divalent and monovalent metal-glycinate complexes (Azadi et al., 2019) \cr - \code{mosaic} \tab * Eh-pH diagram with two sets of changing basis species (Garrels and Christ, 1965) \cr - \code{copper} \tab * Another example of \code{\link{mosaic}}: complexation of Cu with glycine (Aksu and Doyle, 2001) \cr - \code{solubility} \tab * Solubility of calcite (cf. Manning et al., 2013) and \CO2 (cf. Stumm and Morgan, 1996) \cr - \code{gold} \tab * Solubility of gold (Akinfiev and Zotov; 2001; Stef{\aacute}nsson and Seward, 2004; Williams-Jones et al., 2009) \cr - \code{wjd} \tab * \eqn{G}{G} minimization: prebiological atmospheres (Dayhoff et al., 1964) and cell periphery of yeast \cr - \code{dehydration} \tab * \logK of dehydration reactions; SVG file contains tooltips and links \cr - \code{bugstab} \tab * Formation potential of microbial proteins in colorectal cancer (Dick, 2016) \cr - \code{Shh} \tab * Affinities of transcription factors relative to Sonic hedgehog (Dick, 2015) \cr - \code{saturation} \tab * Equilibrium activity diagram showing activity ratios and mineral saturation limits (Bowers et al., 1984) \cr - \code{adenine} \tab * HKF regression of heat capacity and volume of aqueous adenine (Lowe et al., 2017) \cr - \code{DEW} \tab * Deep Earth Water (DEW) model for high pressures (Sverjensky et al., 2014a and 2014b) \cr - \code{lambda} \tab * Effects of lambda transition on thermodynamic properties of quartz (Berman, 1988) \cr - \code{TCA} \tab * Standard Gibbs energies of the tricarboxylic (citric) acid cycle (Canovas and Shock, 2016) \cr - \code{go-IU} \tab * Diagrams using thermodynamic data in the SUPCRTBL compilation (Zimmer et al., 2016) \cr - \code{carboxylase} \tab * Rank abundance distribution for RuBisCO and acetyl-CoA carboxylase \cr + \code{yeastgfp} \tab Subcellular locations: \logfO2 - \logaH2O and \loga - \logfO2 diagrams (Dick, 2009) \cr + \code{glycinate} \tab Metal-glycinate complexes (Shock and Koretsky, 1995; Azadi et al., 2019) \cr + \code{mosaic} \tab Eh-pH diagram with two sets of changing basis species (Garrels and Christ, 1965) \cr + \code{copper} \tab Another example of \code{\link{mosaic}}: complexation of Cu with glycine (Aksu and Doyle, 2001) \cr + \code{solubility} \tab Solubility of calcite (cf. Manning et al., 2013) and \CO2 (cf. Stumm and Morgan, 1996) \cr + \code{gold} \tab Solubility of gold (Akinfiev and Zotov; 2001; Stef{\aacute}nsson and Seward, 2004; Williams-Jones et al., 2009) \cr + \code{wjd} \tab \eqn{G}{G} minimization: prebiological atmospheres (Dayhoff et al., 1964) and cell periphery of yeast \cr + \code{dehydration} \tab \logK of dehydration reactions; SVG file contains tooltips and links \cr + \code{bugstab} \tab Formation potential of microbial proteins in colorectal cancer (Dick, 2016) \cr + \code{Shh} \tab Affinities of transcription factors relative to Sonic hedgehog (Dick, 2015) \cr + \code{saturation} \tab Equilibrium activity diagram showing activity ratios and mineral saturation limits (Bowers et al., 1984) \cr + \code{adenine} \tab HKF regression of heat capacity and volume of aqueous adenine (Lowe et al., 2017) \cr + \code{DEW} \tab Deep Earth Water (DEW) model for high pressures (Sverjensky et al., 2014a and 2014b) \cr + \code{lambda} \tab Effects of lambda transition on thermodynamic properties of quartz (Berman, 1988) \cr + \code{TCA} \tab Standard Gibbs energies of the tricarboxylic (citric) acid cycle (Canovas and Shock, 2016) \cr + \code{go-IU} \tab Diagrams using thermodynamic data in the SUPCRTBL compilation (Zimmer et al., 2016) \cr + \code{carboxylase} \tab Rank abundance distribution for RuBisCO and acetyl-CoA carboxylase \cr \code{bison} \tab Average oxidation state of carbon in proteins for phyla at Bison Pool (Dick and Shock, 2013) \cr } @@ -119,6 +118,8 @@ Schulte, M. D. and Shock, E. L. (1995) Thermodynamics of Strecker synthesis in hydrothermal systems. \emph{Orig. Life Evol. Biosph.} \bold{25}, 161--173. \url{https://doi.org/10.1007/BF01581580} +Shock, E. L. and Koretsky, C. M. (1995) Metal-organic complexes in geochemical processes: Estimation of standard partial molal thermodynamic properties of aqueous complexes between metal cations and monovalent organic acid ligands at high pressures and temperatures. \emph{Geochim. Cosmochim. Acta} \bold{59}, 1497--1532. \url{https://doi.org/10.1016/0016-7037(95)00058-8} + Shock, E. L., Oelkers, E. H., Johnson, J. W., Sverjensky, D. A. and Helgeson, H. C. (1992) Calculation of the thermodynamic properties of aqueous species at high pressures and temperatures: Effective electrostatic radii, dissociation constants and standard partial molal properties to 1000 \degC and 5 kbar. \emph{J. Chem. Soc. Faraday Trans.} \bold{88}, 803--826. \url{https://doi.org/10.1039/FT9928800803} Stef{\aacute}nsson, A. and Seward, T. M. (2004) Gold(I) complexing in aqueous sulphide solutions to 500\degC at 500 bar. \emph{Geochim. Cosmochim. Acta} \bold{68}, 4121--4143. \url{https://doi.org/10.1016/j.gca.2004.04.006} Modified: pkg/CHNOSZ/vignettes/anintro.Rmd =================================================================== --- pkg/CHNOSZ/vignettes/anintro.Rmd 2019-02-09 05:52:58 UTC (rev 390) +++ pkg/CHNOSZ/vignettes/anintro.Rmd 2019-02-09 08:18:42 UTC (rev 391) @@ -2197,7 +2197,7 @@ # Document history -* 2010-09-30 Initial version. +* 2010-09-30 Initial version (titled "Getting started with CHNOSZ"). invocation changes from data(thermo) to reset() +# --> invocation changes from data(OBIGT) to obigt() + +reset <- function() { + # create thermo list + thermodir <- system.file("extdata/thermo/", package="CHNOSZ") + thermo <- list( + # as.is: keep character values as character and not factor + opt = as.list(read.csv(file.path(thermodir, "opt.csv"), as.is=TRUE)), + element = read.csv(file.path(thermodir, "element.csv"), as.is=1:3), + obigt = NULL, + refs = NULL, + buffers = read.csv(file.path(thermodir, "buffer.csv"), as.is=1:3), + protein = read.csv(file.path(thermodir, "protein.csv"), as.is=1:4), + groups = read.csv(file.path(thermodir, "groups.csv"), row.names=1, check.names=FALSE), + basis = NULL, + species = NULL, + opar = NULL + ) + # give a summary of what we are doing + if(!"thermo" %in% ls(CHNOSZ)) message("reset: creating \"thermo\" object") + else message("reset: resetting \"thermo\" object") + # place thermo in CHNOSZ environment + assign("thermo", thermo, CHNOSZ) + # run obigt() to add the thermodynamic data + obigt() +} + +# load default thermodynamic data (OBIGT) in thermo +obigt <- function() { + # we only work if thermo is already in the CHNOSZ environment + if(!"thermo" %in% ls(CHNOSZ)) stop("The CHNOSZ environment doesn't have a \"thermo\" object. Try running reset()") + # create obigt data frame + sources_aq <- paste0(c("H2O", "inorganic", "organic", "biotic"), "_aq") + sources_cr <- paste0(c("inorganic", "organic", "Berman"), "_cr") + sources_liq <- paste0(c("organic"), "_liq") + sources_gas <- paste0(c("inorganic", "organic"), "_gas") + sources <- c(sources_aq, sources_cr, sources_liq, sources_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[!sources=="Berman_cr"] <- paste0(sourcefiles[!sources=="Berman_cr"], ".xz") + datalist <- lapply(sourcefiles, read.csv, as.is=TRUE) + obigt <- do.call(rbind, datalist) + # also read references file + refs <- read.csv(file.path(OBIGTdir, "refs.csv"), as.is=TRUE) + # get thermo from CHNOSZ environment + thermo <- get("thermo", CHNOSZ) + # set obigt and refs + thermo$obigt <- obigt + thermo$refs <- refs + # place modified thermo in CHNOSZ environment + assign("thermo", thermo, CHNOSZ) + # give a summary of some of the data + message(paste("obigt: loading default database with", + nrow(thermo$obigt[thermo$obigt$state=="aq",]), + "aqueous,", nrow(thermo$obigt), "total species")) + # warn if there are duplicated species + idup <- duplicated(paste(thermo$obigt$name, thermo$obigt$state)) + if(any(idup)) warning("obigt: duplicated species: ", + paste(thermo$obigt$name[idup], "(", thermo$obigt$state[idup], ")", sep="", collapse=" ")) +} + +# a function to access or modify the thermo object 20190214 +thermo <- function(...) { + args <- list(...) + # get the object + thermo <- get("thermo", CHNOSZ) + if(length(args) > 0) { + # assign into the object + slots <- names(args) + for(i in 1:length(slots)) { + # parse the name of the slot + names <- strsplit(slots[i], "$", fixed=TRUE)[[1]] + if(length(names) == 1) thermo[[names]] <- args[[i]] + if(length(names) == 2) thermo[[names[1]]][[names[2]]] <- args[[i]] + } + assign("thermo", thermo, CHNOSZ) + } else { + # return the object + thermo + } +} Modified: pkg/CHNOSZ/R/util.affinity.R =================================================================== --- pkg/CHNOSZ/R/util.affinity.R 2019-02-09 10:49:34 UTC (rev 393) +++ pkg/CHNOSZ/R/util.affinity.R 2019-02-13 14:47:58 UTC (rev 394) @@ -40,7 +40,7 @@ mybasis <- basis() nbasis <- nrow(mybasis) ## species definition / number of species - myspecies <- get("thermo")$species + myspecies <- get("thermo", CHNOSZ)$species if(is.character(what)) { if(is.null(myspecies)) stop('species properties requested, but species have not been defined') nspecies <- nrow(myspecies) @@ -244,7 +244,7 @@ # over which to calculate logQ, logK and affinity # the names should be T, P, IS and names of basis species # (or pH, pe, Eh) - thermo <- get("thermo") + thermo <- get("thermo", CHNOSZ) ## inputs are like c(T1,T2,res) # and outputs are like seq(T1,T2,length.out=res) # unless transect: do the variables specify a transect? 20090627 Modified: pkg/CHNOSZ/R/util.args.R =================================================================== --- pkg/CHNOSZ/R/util.args.R 2019-02-09 10:49:34 UTC (rev 393) [TRUNCATED] To get the complete diff run: svnlook diff /svnroot/chnosz -r 394 From noreply at r-forge.r-project.org Fri Feb 15 01:53:57 2019 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Fri, 15 Feb 2019 01:53:57 +0100 (CET) Subject: [CHNOSZ-commits] r395 - in pkg/CHNOSZ: . R inst man tests/testthat Message-ID: <20190215005357.88F3618C910@r-forge.r-project.org> Author: jedick Date: 2019-02-15 01:53:56 +0100 (Fri, 15 Feb 2019) New Revision: 395 Added: pkg/CHNOSZ/R/retrieve.R pkg/CHNOSZ/man/retrieve.Rd pkg/CHNOSZ/tests/testthat/test-retrieve.R Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/NAMESPACE pkg/CHNOSZ/inst/NEWS Log: retrieve(): new function Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-13 14:47:58 UTC (rev 394) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-15 00:53:56 UTC (rev 395) @@ -1,6 +1,6 @@ -Date: 2019-02-13 +Date: 2019-02-15 Package: CHNOSZ -Version: 1.2.0-1 +Version: 1.2.0-2 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/NAMESPACE =================================================================== --- pkg/CHNOSZ/NAMESPACE 2019-02-13 14:47:58 UTC (rev 394) +++ pkg/CHNOSZ/NAMESPACE 2019-02-15 00:53:56 UTC (rev 395) @@ -58,7 +58,7 @@ # added 20171121 or later "dumpdata", "thermo.axis", "solubility", "NaCl", # added 20190213 or later - "CHNOSZ", "thermo", "reset", "obigt" + "CHNOSZ", "thermo", "reset", "obigt", "retrieve" ) # Load shared objects Added: pkg/CHNOSZ/R/retrieve.R =================================================================== --- pkg/CHNOSZ/R/retrieve.R (rev 0) +++ pkg/CHNOSZ/R/retrieve.R 2019-02-15 00:53:56 UTC (rev 395) @@ -0,0 +1,33 @@ +# CHNOSZ/retrieve.R +# retrieve species with given elements +# 20190214 initial version + +retrieve <- function(elements) { + # what are the formulas of species in the current database? + formula <- thermo()$obigt$formula + # get a previously calculated stoichiometric matrix, if it matches the current database + stoich <- thermo()$stoich + if(!is.null(stoich)) { + # if it doesn't match the current database, don't use it + if(!identical(rownames(stoich), formula)) stoich <- NULL + } + if(is.null(stoich)) { + # Create the stoichiometric matrix for the current database + # and suppress warning messages about missing elements + message("retrieve: creating stoichiometric matrix") + # NOTE: row names are the formulas, so we can detect if the database changes + stoich <- suppressWarnings(i2A(formula)) + # store the stoichiometric matrix for later calculations + thermo("stoich" = stoich) + } + not.present <- ! elements %in% colnames(stoich) + if(any(not.present)) { + if(sum(not.present)==1) stop(elements[not.present], " is not an element that is present in any species") + else stop(paste(elements[not.present], collapse=", "), " are not elements that are present in any species") + } + # identify the species that have the elements + has.elements <- rowSums(stoich[, elements, drop = FALSE] != 0) == length(elements) + # which species are these (i.e. the species index) + which(has.elements) +} + Modified: pkg/CHNOSZ/inst/NEWS =================================================================== --- pkg/CHNOSZ/inst/NEWS 2019-02-13 14:47:58 UTC (rev 394) +++ pkg/CHNOSZ/inst/NEWS 2019-02-15 00:53:56 UTC (rev 395) @@ -1,4 +1,4 @@ -CHANGES IN CHNOSZ 1.2.0-1 (2019-02-13) +CHANGES IN CHNOSZ 1.2.0-2 (2019-02-15) -------------------------------------- CRAN COMPLIANCE @@ -10,11 +10,14 @@ that existing scripts beginning with data(thermo) still work (this command now has no effect other than producing a warning). -OTHER CHANGES +NEW FEATURES - Add thermo() as a convenience function to access or modify the package's data, especially various computational options. +- Add retrieve() to retrieve all the species with given elements. Thanks + to Evgeniy Bastrakov for the suggestion. + CHANGES IN CHNOSZ 1.2.0 (2019-02-09) ------------------------------------ Added: pkg/CHNOSZ/man/retrieve.Rd =================================================================== --- pkg/CHNOSZ/man/retrieve.Rd (rev 0) +++ pkg/CHNOSZ/man/retrieve.Rd 2019-02-15 00:53:56 UTC (rev 395) @@ -0,0 +1,37 @@ +\encoding{UTF-8} +\name{retrieve} +\alias{retrieve} +\title{Retrieve Species by Element} +\description{ +Retrieve species in the database containing one or more chemical elements. +} + +\usage{ + retrieve(elements) +} + +\arguments{ + \item{elements}{character, one or more chemical elements} +} + +\details{ +This function retrieves the species in the thermodynamic database (see \code{\link{thermo}}) that have all of the elements specified in \code{elements}. +The return value is a named numeric vector giving the species index (i.e. rownumber(s) of \code{thermo()$obigt}) with names corresponding to the chemical formulas of the species. + +The first time the function is run, it uses \code{\link{i2A}} to build the stoichiometric matrix for the current database. +Following runs use the previously calculated stoichiometric matrix, unless a change to the database is detected, which triggers a recalculation. +} + +\seealso{ +\code{\link{info}} +} + +\examples{ +# species index of Ti-bearing minerals +retrieve("Ti") + +# thermodynamic data for Au-Cl complexes +info(retrieve(c("Au", "Cl"))) +} + +\concept{Extended workflow} Added: pkg/CHNOSZ/tests/testthat/test-retrieve.R =================================================================== --- pkg/CHNOSZ/tests/testthat/test-retrieve.R (rev 0) +++ pkg/CHNOSZ/tests/testthat/test-retrieve.R 2019-02-15 00:53:56 UTC (rev 395) @@ -0,0 +1,12 @@ +context("retrieve") + +test_that("errors and recalculations produce expected messages", { + # this should give an error about one non-element + expect_error(retrieve(c("A", "B", "C")), "A is not an element") + # this should give an error about two non-elements + expect_error(retrieve(c("A", "B", "C", "D")), "A, D are not elements") + # this should recalculate the stoichiometric matrix + add.obigt("SUPCRT92") + expect_message(retrieve("Ti"), "creating stoichiometric matrix") + reset() +}) From noreply at r-forge.r-project.org Fri Feb 15 04:27:45 2019 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Fri, 15 Feb 2019 04:27:45 +0100 (CET) Subject: [CHNOSZ-commits] r396 - in pkg/CHNOSZ: . tests/testthat Message-ID: <20190215032745.6015F18C70A@r-forge.r-project.org> Author: jedick Date: 2019-02-15 04:27:44 +0100 (Fri, 15 Feb 2019) New Revision: 396 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/tests/testthat/test-wjd.R Log: test-wjd.R: workaround for "Additional issues" on CRAN (alternative BLAS implementations) Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-15 00:53:56 UTC (rev 395) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-15 03:27:44 UTC (rev 396) @@ -1,6 +1,6 @@ Date: 2019-02-15 Package: CHNOSZ -Version: 1.2.0-2 +Version: 1.2.0-3 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/tests/testthat/test-wjd.R =================================================================== --- pkg/CHNOSZ/tests/testthat/test-wjd.R 2019-02-15 00:53:56 UTC (rev 395) +++ pkg/CHNOSZ/tests/testthat/test-wjd.R 2019-02-15 03:27:44 UTC (rev 396) @@ -19,8 +19,10 @@ }) test_that("open-system equilibrium distributions reproduce the results of wjd()", { -# ### FIXME: equil.potentials(w) returns NULL unless we use parameters for [Gly] from DLH06 20190206 -# add.obigt("OldAA") + ### FIXME: equil.potentials(w) returns NULL unless we use group additivity parameters from DLH06 20190206 + ### (issue appears with MKL and OpenBLAS CRAN checks) + reset() + add.obigt("OldAA") ### set up system # use proteins in the lipid particle (n=19) y <- yeastgfp("lipid.particle") @@ -60,11 +62,9 @@ # the test: abundances calculated both ways are equal expect_equal(X.closed, X.open, tolerance=0.018) # seems that we could do better than that 1.8% mean difference! + reset() }) -# see also test-swap.basis.R for an example using run.wjd() and -# equil.potentials() to generate chemical potentials of elements - # references # White, W. B., Johnson, S. M. and Dantzig, G. B. (1958) From noreply at r-forge.r-project.org Sun Feb 17 22:43:50 2019 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Sun, 17 Feb 2019 22:43:50 +0100 (CET) Subject: [CHNOSZ-commits] r397 - in pkg/CHNOSZ: . R demo inst inst/extdata/OBIGT man vignettes Message-ID: <20190217214350.B6E891884FD@r-forge.r-project.org> Author: jedick Date: 2019-02-17 22:43:50 +0100 (Sun, 17 Feb 2019) New Revision: 397 Added: pkg/CHNOSZ/inst/extdata/OBIGT/AS04.csv Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/R/util.data.R pkg/CHNOSZ/demo/go-IU.R pkg/CHNOSZ/demo/sources.R pkg/CHNOSZ/inst/NEWS pkg/CHNOSZ/inst/extdata/OBIGT/SLOP98.csv pkg/CHNOSZ/inst/extdata/OBIGT/SUPCRT92.csv pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_aq.csv.xz pkg/CHNOSZ/inst/extdata/OBIGT/refs.csv pkg/CHNOSZ/man/diagram.Rd pkg/CHNOSZ/vignettes/anintro.Rmd pkg/CHNOSZ/vignettes/eos-regress.Rmd pkg/CHNOSZ/vignettes/obigt.Rmd pkg/CHNOSZ/vignettes/vig.bib Log: data: move SiO2(aq) to OBIGT/AS04.csv Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-15 03:27:44 UTC (rev 396) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-17 21:43:50 UTC (rev 397) @@ -1,6 +1,6 @@ -Date: 2019-02-15 +Date: 2019-02-18 Package: CHNOSZ -Version: 1.2.0-3 +Version: 1.2.0-4 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/R/util.data.R =================================================================== --- pkg/CHNOSZ/R/util.data.R 2019-02-15 03:27:44 UTC (rev 396) +++ pkg/CHNOSZ/R/util.data.R 2019-02-17 21:43:50 UTC (rev 397) @@ -264,6 +264,7 @@ else if(what=="SLOP98") tdata <- read.csv(system.file("extdata/OBIGT/SLOP98.csv", package="CHNOSZ"), as.is=TRUE) else if(what=="SUPCRT92") tdata <- read.csv(system.file("extdata/OBIGT/SUPCRT92.csv", package="CHNOSZ"), as.is=TRUE) else if(what=="OldAA") tdata <- read.csv(system.file("extdata/OBIGT/OldAA.csv", package="CHNOSZ"), as.is=TRUE) + else if(what=="AS04") tdata <- read.csv(system.file("extdata/OBIGT/AS04.csv", package="CHNOSZ"), as.is=TRUE) ntot <- nrow(tdata) # where to keep the results DCp <- DV <- DG <- rep(NA,ntot) Modified: pkg/CHNOSZ/demo/go-IU.R =================================================================== --- pkg/CHNOSZ/demo/go-IU.R 2019-02-15 03:27:44 UTC (rev 396) +++ pkg/CHNOSZ/demo/go-IU.R 2019-02-17 21:43:50 UTC (rev 397) @@ -10,17 +10,16 @@ ########### ## experimental data from Table 1 of Hemley et al., 1980 # doi:10.2113/gsecongeo.75.2.210 -xT <- c(200, 200, 200, 200, 250, 250, 300, 300, 300, 300) -xlogaSiO2 <- -c(2.54, 2.59, 2.65, 2.77, 2.21, 2.32, 1.90, 1.95, 1.94, 1.90) +xT <- c(200, 200, 200, 200, 250, 250, 265, 300, 300, 300, 300) +xlogaSiO2 <- -c(2.54, 2.59, 2.65, 2.77, 2.21, 2.32, 2.12, 1.90, 1.95, 1.94, 1.90) ## set up basis species so that axis.label shows activity of SiO2 basis(c("Al2O3","SiO2", "H2O", "O2")) T <- 125:350 thermo.plot.new(xlim=range(T), ylim=c(-3.5, -1.5), xlab = axis.label("T"), ylab=axis.label("SiO2")) points(xT, xlogaSiO2) basis(delete=TRUE) -## first calculation: after SUPCRT92 and SLOP98 +## first calculation: as in SUPCRT92 add.obigt("SUPCRT92") # gets kaolinite and boehmite from HDNB78 -add.obigt("SLOP98") # SiO2(aq) from SHS89 r1 <- subcrt(c("boehmite", "H2O", "SiO2", "kaolinite"), c(-1, -0.5, -1, 0.5), T=T, P=1000, exceed.Ttr = TRUE) # we need exceed.Ttr = TRUE because the T limit for boehmite is 500 K (Helgeson et al., 1978) ## second calculation: CHNOSZ default @@ -29,15 +28,19 @@ # SiO2 from Apps and Spycher, 2004 reset() r2 <- subcrt(c("boehmite", "H2O", "SiO2", "kaolinite"), c(-1, -0.5, -1, 0.5), T=T, P=1000, exceed.Ttr = TRUE) +## third calculation: get SiO2(aq) from SHS89 +add.obigt("AS04") +r3 <- subcrt(c("boehmite", "H2O", "SiO2", "kaolinite"), c(-1, -0.5, -1, 0.5), T=T, P=1000, exceed.Ttr = TRUE) ## log activity of SiO2 is -ve logK lines(T, -r1$out$logK) lines(T, -r2$out$logK, col="red") +lines(T, -r3$out$logK, col="red", lty = 2) ## add points calculated using the SUPCRTBL package points(seq(125, 350, 25), -c(3.489, 3.217, 2.967, 2.734, 2.517, 2.314, 2.124, 1.946, 1.781, 1.628), pch=4, col="red") ## add legend and title -legend("topleft", lty=c(0, 1, 0, 1), pch=c(1, NA, 4, NA), - col=c("black", "black", "red", "red"), bty="n", cex=0.9, - legend=c("Hemley et al., 1980", "SUPCRT92/SLOP98", "SUPCRTBL", "CHNOSZ")) +legend("bottomright", lty=c(0, 0, 1, 1, 2), pch=c(1, 4, NA, NA, NA), + col=c("black", "red", "black", "red", "red"), bty="n", cex=0.9, + legend=c("Hemley et al., 1980", "SUPCRTBL", "SUPCRT92", "CHNOSZ (default)", 'add.obigt("AS04")')) mtitle(c("Kaolinite - Boehmite", "After Zhu and Lu, 2009 Fig. A1"), cex=0.95) # Zhu and Lu, 2009: doi:10.1016/j.gca.2009.03.015 # Helgeson et al., 1978 (HDNB78): http://www.worldcat.org/oclc/13594862 @@ -70,8 +73,8 @@ ## add points calculated using the SUPCRTBL package points(seq(25, 250, 25), c(-17.829, -16.523, -15.402, -14.425, -13.568, -12.815, -12.154, -11.581, -11.094, -10.699), pch=4, col="red") ## add legend and title -legend("topleft", lty=c(0, 1, 0, 2), pch=c(1, NA, 4, NA), col=c("black", "red", "red", "red"), - bty="n", cex=0.9, legend=c("Ben\u00e9z\u00e9th et al., 2007", "CHNOSZ", "SUPCRTBL", "Cp(dawsonite) = 0")) +legend("bottomright", lty=c(0, 0, 1, 2), pch=c(1, 4, NA, NA), col=c("black", "red", "red", "red"), + bty="n", cex=0.9, legend=c("Ben\u00e9z\u00e9th et al., 2007", "SUPCRTBL", "CHNOSZ", 'mod.obigt("dawsonite", Cp = 0)')) mtitle(c("Dawsonite - aqueous species", "After Zimmer et al., 2016 Fig. 2"), cex=0.95) # doi:10.1016/j.cageo.2016.02.013 Modified: pkg/CHNOSZ/demo/sources.R =================================================================== --- pkg/CHNOSZ/demo/sources.R 2019-02-15 03:27:44 UTC (rev 396) +++ pkg/CHNOSZ/demo/sources.R 2019-02-17 21:43:50 UTC (rev 397) @@ -19,8 +19,11 @@ tdata <- read.csv(system.file("extdata/OBIGT/OldAA.csv", package="CHNOSZ"), as.is=TRUE) os7 <- gsub("\ .*", "", tdata$ref1) os8 <- gsub("\ .*", "", tdata$ref2) +tdata <- read.csv(system.file("extdata/OBIGT/AS04.csv", package="CHNOSZ"), as.is=TRUE) +os9 <- gsub("\ .*", "", tdata$ref1) +os10 <- gsub("\ .*", "", tdata$ref2) # all of the thermodynamic data sources - some of them might be NA -obigt.source <- unique(c(ps1, ps2, os1, os2, os3, os4, os5, os6, os7, os8)) +obigt.source <- unique(c(ps1, ps2, os1, os2, os3, os4, os5, os6, os7, os8, os9, os10)) obigt.source <- obigt.source[!is.na(obigt.source)] # these all produce character(0) if the sources are all accounted for print("missing these sources for thermodynamic properties:") Modified: pkg/CHNOSZ/inst/NEWS =================================================================== --- pkg/CHNOSZ/inst/NEWS 2019-02-15 03:27:44 UTC (rev 396) +++ pkg/CHNOSZ/inst/NEWS 2019-02-17 21:43:50 UTC (rev 397) @@ -1,4 +1,4 @@ -CHANGES IN CHNOSZ 1.2.0-2 (2019-02-15) +CHANGES IN CHNOSZ 1.2.0-4 (2019-02-18) -------------------------------------- CRAN COMPLIANCE @@ -18,6 +18,10 @@ - Add retrieve() to retrieve all the species with given elements. Thanks to Evgeniy Bastrakov for the suggestion. +THERMODYNAMIC DATA + +- Move SiO2(aq) and H2AsO3- from SLOP98.csv to SUPCRT92.csv. + CHANGES IN CHNOSZ 1.2.0 (2019-02-09) ------------------------------------ Added: pkg/CHNOSZ/inst/extdata/OBIGT/AS04.csv =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/AS04.csv (rev 0) +++ pkg/CHNOSZ/inst/extdata/OBIGT/AS04.csv 2019-02-17 21:43:50 UTC (rev 397) @@ -0,0 +1,3 @@ +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 +SiO2,NA,SiO2,aq,AS04,NA,08.Feb.19,-199540,-212179,11.128325,-22.324515,15.575422,1.9,1.7,20,-2.7,32.221331,-25.288582,0.342671,0 +HSiO3-,HSiO3-,HSiO3-,aq,"SSH97.2 [S98]",CHNOSZ.8,08.Feb.19,-243151,-276276,-1.871675,-21,5,2.9735,-0.5158,5.9467,-2.7575,8.1489,-7.3123,1.5511,-1 Modified: pkg/CHNOSZ/inst/extdata/OBIGT/SLOP98.csv =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/SLOP98.csv 2019-02-15 03:27:44 UTC (rev 396) +++ pkg/CHNOSZ/inst/extdata/OBIGT/SLOP98.csv 2019-02-17 21:43:50 UTC (rev 397) @@ -8,15 +8,12 @@ Au+3,Au+3,Au+3,aq,"SSWS97.2 [S98]",SH88.1,13.Nov.97,103600,97800,-54.8,-8.2,-31.4,-1.7167,-11.9654,10.4352,-2.2843,23.5775,-4.7048,2.4115,3 Au(Ac),NA,AuCH3COO,aq,"SK93.1 [S98]",NA,10.Sep.92,-49870,-68310,48,56.1,61.8,10.213,17.1576,-0.9969,-3.4882,38.7432,8.3843,-0.03,0 Au(Ac)2-,NA,Au(CH3COO)2-,aq,"SK93.1 [S98]",NA,10.Sep.92,-138240,-186750,61.3,132.8,118.3,18.1917,36.6392,-8.6534,-4.2936,90.461,24.0193,0.701,-1 -H2AsO3-,H2AsO3-,H2AsO3-,aq,"SH88.2 [S92]",NA,3.Jul.87,-140330,-170840,26.4,-2.9,26.4,5.7934,6.3646,3.2485,-3.0421,15.8032,-3.6253,1.2305,-1 AsO4-3,AsO4-3,AsO4-3,aq,"SSWS97.3 [S98]",NA,11.Nov.97,-154970,-212270,-38.9,-116.1,-18.7,1.0308,-5.2609,7.8091,-2.5614,-12.1352,-26.6841,5.399,-3 HAsO4-2,HAsO4-2,HAsO4-2,aq,"SSWS97.3 [S98]",NA,11.Nov.97,-170790,-216620,-0.4,-47.5,11.3,4.3994,2.9611,4.5853,-2.9013,7.9908,-12.7102,3.2197,-2 H2AsO4-,H2AsO4-,H2AsO4-,aq,"SSWS97.3 [S98]",NA,11.Nov.97,-180010,-217390,28,-0.6,33.4,6.7429,8.6835,2.3351,-3.1379,16.9206,-3.1567,1.2055,-1 H3AsO4,H3AsO4,H3AsO4,aq,"SSWS97.3 [S98]",NA,11.Nov.97,-183100,-215700,44,25.8,45.9,7.9357,11.5925,1.199,-3.2581,18.2805,2.2209,-0.3263,0 AsO2-,AsO2-,AsO2-,aq,"SSWS97.3 [S98]",NA,11.Nov.97,-83650,-102540,9.7,-28,6.9,3.2101,0.0554,5.7305,-2.7812,3.4104,-8.7381,1.482,-1 HAsO2,HAsO2,HAsO2,aq,"SSWS97.3 [S98]",NA,11.Nov.97,-96240,-109110,30.1,2.9,28.3,5.5984,5.8913,3.428,-3.0224,6.799,-2.4438,-0.1158,0 -SiO2,NA,SiO2,aq,"SHS89.1 [S92]",NA,13.Jan.89,-199190,-209775,18,-76.1,16.1,1.9,1.7,20,-2.7,29.1,-51.2,0.1291,0 -HSiO3-,HSiO3-,HSiO3-,aq,"SSH97 [S98]",NA,18.Sep.97,-242801,-273872,5,-21,5,2.9735,-0.5158,5.9467,-2.7575,8.1489,-7.3123,1.5511,-1 AlO2-,AlO2-,AlO2-1,aq,"SSWS97.4 [S98]",NA,07.Nov.97,-198693,-222125,-7.22,-11.9,10,3.7221,3.9954,-1.5879,-2.9441,15.2391,-5.4585,1.7418,-1 Al+3,Al+3,Al+3,aq,"SSWS97.4 [S98]",NA,07.Nov.97,-115609,-126834,-77.7,-32.5,-44.4,-3.3802,-17.0071,14.5185,-2.0758,10.7,-8.06,2.753,3 AlOH+2,AlOH+2,AlOH+2,aq,"SSWS97.4 [S98]",NA,13.Nov.97,-165475,-183300,-44.2,13.2,-2.2,2.0469,-2.7813,6.8376,-2.6639,29.7923,-0.3457,1.7247,2 Modified: pkg/CHNOSZ/inst/extdata/OBIGT/SUPCRT92.csv =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/SUPCRT92.csv 2019-02-15 03:27:44 UTC (rev 396) +++ pkg/CHNOSZ/inst/extdata/OBIGT/SUPCRT92.csv 2019-02-17 21:43:50 UTC (rev 397) @@ -178,6 +178,7 @@ stilbite,Stb,NaCa2(Al5Si13)O36*14H2O,cr,"HDNB78 [S92]",NA,5.May.78,NA,NA,399.3,NA,649.91,390.55,137.68,-49.84,0,0,0,0,848 stilbite,Stb,NaCa2(Al5Si13)O36*14H2O,cr2,"HDNB78 [S92]",CHNOSZ.1,5.May.78,-11.741,NA,395.63,NA,649.91,400.12,118.9,-41.74,0,0,0,0,1000 talc,Tcl,Mg3Si4O10(OH)2,cr,"HDNB78 [S92]",NA,5.May.78,-1320188,-1410920,62.34,NA,136.25,82.482,41.614,-13.342,0,0,0,0,800 +H2AsO3-,H2AsO3-,H2AsO3-,aq,"SH88.2 [S92]",NA,3.Jul.87,-140330,-170840,26.4,-2.9,26.4,5.7934,6.3646,3.2485,-3.0421,15.8032,-3.6253,1.2305,-1 tremolite,Tr,(Ca2Mg5)Si8O22(OH)2,cr,"HDNB78 [S92]",SPRONS92.2,15.Mar.90,-2770245,-2944038,131.19,NA,272.92,188.222,57.294,-44.822,0,0,0,0,800 wairakite,Wai,Ca(Al2Si4)O12*2H2O,cr,"HDNB78 [S92]",SPRONS92.2,15.Mar.90,-1477432,-1579333,105.1,NA,186.87,100.4,44.47,-16.43,0,0,0,0,1000 wollastonite,Wo,CaSiO3,cr,"HDNB78 [S92]",SPRONS92.2,15.Mar.90,-369225,-389590,19.6,NA,39.93,26.64,3.6,-6.52,0,0,0,0,1400 Modified: pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_aq.csv.xz =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_aq.csv.xz 2019-02-15 03:27:44 UTC (rev 396) +++ pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_aq.csv.xz 2019-02-17 21:43:50 UTC (rev 397) @@ -1,4 +1,4 @@ -?7zXZ???F!t/????C?4]7I??b???9??????TB;q?"?q???cL;?"??N?[?????=EU?0-g |??gz?0?6v0 -??c?F??\?^????????I??>E?K???&?SKB????/2??U?>,&?M?V?]???h'D8(?K?i??I??DYN??"???&??7????$=??[??s??????????U????C )??nso%|6 -f???D?-???v????.?Di???Ax???sq?s?{X i??M?x?a33lc}???G??ZQk v{s?*Xc]??? ????[a6?w}\?g??)??????S???;??u?g?R??w?$2??c?)?y?.?:~??!+Q'7?]H??~}?H?z *?u|?????J???PBte? W???o-q????a???Y7???7a??j?I??K:?_?R?? ?j??'WVJ????s??A WU?iX???? -?[e??;?E?^??MUx???;(???aXF?w?e -O?^|f??gj?3u|??????"?!j?Ks??u?V???S>?H?YI???+\??WY????N??! z?_i? y+?j??s]x?v???G??X??A?,?HK?n??g??P?????]????7Q???????? -~???s?-????O????~????>?Ki?T????%??~D&7?j????????0?????Y?????P??n?u????? ????P????.?>????????k?xY?>g??R??????q?Z.UJ?j2??ga???p?K{?VF?? -??J? -???$????? ?`F\ ????????o???a???df????4?}????|?O j3{]pk??7?*????3e?Y??y??`3??3B?|,???6t?0@nJ??1??f?v?m?R6l?!??V]?,?4pO??B??a???!?V?=? -T?,c?y?n[???c???fb?????@29?ue?NL?}H?`' ????????8o?????k|[?;???" ??????mN -u???}?s~?hR?rZ?^?t -??aI?tZ3P???ih??? ????&?? -?EF?sG4?Q???Y??,??]~\????s????a???>????{??\$L??cb(P& ?m?? -Q3?*G??????.h???X?2T?$GT??W???D?r?c???,????G?s?5}??2_Z?V?Ht????z???3?????? gX?gm?j????l???|h?|lD?????G??*???~?l?.?3|?A?i e>\??D????k??x?2+???G??#??I?,x??????????q%???"xR3[???????~v??ho?R? -7\?? ?????2I??1oZ???V?g1Y?%a??6????M?? ?b?O~????;??Z?? -O?w????n-&?4?H?oPy9w? -H??~#????NZ?hB=?g?w?_???&?r2 -???O????,Y??Q7="h????kuN?&???? -=r?j@??!??So??Qd/???C??q??{???? ?t??h)Z???d??N?????~Y????y??????lJ+??????c??h??u`d?-???1?;[5?t?_$???%?:???????f??=(??C]A? ??i at Fk??i??J???f?'? ??????G???S??J ?&z%b()?????#??p_????UV?V[nDO??^?O?z? ?fW^?RV??w ?S!b*?,4???y???5??9?`????>? -=P3t??UO??v?2?s`??B?j?_ ???K??^???wb=P?73?FHpBY?9]?8>????$?G???? -?)??n??r??6???#?a?u?? sm>b??^????%4Z?`?uM$mD?o?3?????8??w?+???3ZoD,x?| -eC?k?? -??V? 0M?G?**?s%93 ???Y?6m??D)??B9tC30??,???k??h?????f????8D?NI>?kwE??~"T?W??????XE?????p????4?!ojS?T Lx?C?U?????Y?7[????R???Y?nZ????E[?J ?H?/i?????\?h} k?b?jNE,8$? -?=?A???U$??Z????b^???g?;?)?.?.c??D`?????(/?} V??F7_????????? -Z?P??ln?N3m`??c_c?? ?13?O]??*????[??U8e?sF,?'=U`???_????i| R R?)?????S?IDk??B$??;)M0f??94+??????????*2?d?^?~|IaT_???kK ????Ss??pE??X??J?C???5??h+i?B=????`??D?+????F???q???????y4?????y??j\?????????k?cJ??L@?O????f^M?????W?r?H?? ?0o? -#?j$^?KS???@Pyf-?-????????S???B\?"_@?~3? ????P!?}i?]?K?PL???;???B ?|N??>oQ?RYtCh?A????? ?A?*?{"? ?96H?i?v?(N?\???q%?????)?az?0L??d:?DC??mV?:c?=t?!?&E????4Y>?? (??zC?x?????p?*???!mz?>???????+????['??-??o? -?D???k? ??X?????`f&?d????{?h??=eKj?~UT?;????????:0????X??L??=++M?9Q6???h??S????`??{~??W^???k6n??,s^???2l???rA)??p-?????v?[{?lt?K?-[???8ST??H?*ug]?"V?[6!+`?(?.X??4??a??/??8??FFZ??P?T??q?F???????0??ai -< -e?q???L?????7pr?2E??Y?A9x??K???I?j??t?3?K>??C??O???,????1 -jy8R??=?;6d% ?? ? ??(????[?k_???w?$Z?????????Z????U??~??-???????bp???=}??t?0\?????????An??r@?????k?\?????Z?8??9??-?????P??bN?{h??s?3ra?F%??h??n??????????|??$??-O?KL??;??7??? ???f????D???-[2?186???JpHh??G?C?y?????iD???q???-?t ?????????????V2???F?1??i???bybZ??n B\d?&???M????w??f??&[????>H.-?{???C ????`????K???????@????l,.??K???T?u?????/?^T?Q??U???F -????????rH(? -?m?]y????F??GA#?S??N ?]?ck -?}????n???dl????[~?V!?|d +i?.'????.?F?/????6?IH?3???? I????EW?$??1??}j??Q?r??6uH??, ???????o???~????~l?3?>??V?:?/ -??H??G??{??]9X?{?m?|T???_?????j?;??3Cv???t?????{??\?b?5H?Y'X??3??? )rd?l????r?Sm????1?r?O????T???????Jvis?&?3?[??O???$LL0a?p??????1+????C??9???????xV?i?x?L??al?%?Gy? )A)?:?R?SFw?sV???%/?-???+?:?G?`*T+&.????>?CL????? ?G?j? -??????1?{??7???Y=?d??x????;?9O????? -??c4#R%6Uh??????t???x[??D5]#?^???f?? ?,)?hXG?^????????;??L?)sP?9/&<Q???$??????>f?9jG?? -C'?????}????0?Q?????:??V?M?%o}bL"?5?u?????&ik???_rS?>??!???=?T???q??O9f???K??a?&9????oZ???:6s? ???v???p???~??/!?7???E?xg?????u?%?~????????-??XX?]?|Jg?*@X??7d?Q????Ot??x?QO???E?L???}????%ks???@??}?% ??!k???{?W?2??k\? -??2+i?{ ?0???????y????p???_?G??G??t???0?34E???V@?D?n???Lt?A?K?q?[??)zr@??+?c??hInz????)??a??f??? ??%??bua???? -??C?m?1??q??? -???????E\??hQ{H?u???Qa%`V?Z9???????X?0????h?b??u5H???z'??g???$8fK???(???z?iv^);y???~=, -?O??Rp ?B?a? ????R??T??E?;??=;c?z??????g???k? -?n?????f]????~???. ????XM?????!GY?ax???? ??uoFvu?w??q:?5??F??2tH??L?"KD??^?lc~??a?}?Hu????ZS?( c??Mm??? -2??Q$?}?/*???????? A??b? d??1???j????Cf@?Y???}A?+?<?#????-??s_X?(??E??>????? {H?q?=??F??Z??f[???lI?+|H????Z????6 ?zD???Y????? -??n?n -t????D?NhE???u1?`u???`\,-???^?d?O,?|?=~O???3>Tu?Y?6u?????v?????j+&?\???5??t????S+?s??8????g#\????fQ??L??????' ?????????????????wAe+TTK??R /?K?>???#?.??? wB>?s\?E?N??+iI0,c?];?u!?u??q??8we??2????C???0?#`3????o?U|??^?? \?^????v????~8???2g?{1Qjz?;? -W7?7???u????fz???(?c??P0m+??]]OB?4??I?_?&??LwN???P - -?t?0?fx[????s'????I1?? -L?"????<9???Q??? -[q0??????E?67?#?"?? B????-???|e?|$AZ???(??/?~eX?? ???}`???N? -?, ?d???m\???????K?`=????l?????`???|????w?????????.Xo"|????l?F?G"a?V?y??? ??*????;u??Cd7?? -WO?E???"4???? -?%3c?(???Ks??p -?????????G0K-????(?A????zW#?7?Qz?t?????????H??qV????? -????_??L??j^?????qg????5?W ??HQ????/}????8???PI???liw?0????n??a?????????B0?R??R???q??pR? ? ??-??i???pV? -????A5JH??q??Q???Ob wC?????M?rv>?M????&???? -1 o???? ?u??Ve???!?{x???M?V?6??S??I?????\?gD]??vw??D??c`? ?h?Jk+L???I8?>???HU?[??$!???[?6????A??V??3?????? ???7V`??{-???4?Y??????Et?Ry?G?#???\???|????P??!?R??#?e?@s0?RR?????u?[M\??(@???i???@/?S?0?Gs?n??????9?P.???+vd ?????oA6I??])Y!?n??%{??`?u?a -?^?_?qLz?????=???$?dn?????*j???J?5b?????P???$??_Xw#&??Z??C??"?%?`x?8Z|}\8VH??Uo??qS+?}h??*?*??b"T>???t?? ??f??$|???j?? -8C? -?????r?m? ??W????hH? (??iH??7??%"?e?b*X??????k??CS?;u?0aG???????Nga????:9?.? ??????A?f;?A^qv?&?V???????(6?x-??????u? -?^ffj=i?:?J?y?.ks?%?u????lnI?; -Q?Yt?v??X? ?I??+j~x?8???y?????j?????y????J?^??9?vR" ?m???h????tm?"???N??*?F`?g??Y"???p???f? -\?m?o98?2?#?,???9?.????4???????cL???o??e7S???-??Y4Wd?Uk#??Y?????%?}h&??-? \'?b?_Nh???g?1? -?l???{\???Lv?pF? ????@?Z?P/U?`???t?T&LX?t^pUO -?'B/d?E?@?vQ??!Y"??I?HC=IVu??0&??H?~?U^-n.{?C?9??5??????U\u];??U%:??bL?R????!???8?????%?????????0q0??????????? ??P?{2a??w|?u#Nc?@{c??< ????h{q?H?:1???????? -??h??O?q?6|?k??GS@??? D???~Awp???(????K???y????K?K(?$ ????9eu?D?dja???T -,N?? ?5?x3D?-?}Y?9?U?G'???? ??u???6zT???)???g}c=?x?R???mF*???V??{r??In?r? ??/??????C?????????\?fo??????=Q???K???T?1?~?1~???6? -1?Fpt?Q???z??%S?&??.?"S: ??`?????@m u$??????V+I???Z??.??????? -??????1v?b?X^a?????]?????h??U<'G ???????Yb?w???N?aNh?P?????S??m5???V>?{?2?|7? v????+????0?>U } e??@;$?H?????{??&??????M$??%:>??S????V]JV?? ??_1??|????j??;??fKo5?"?Cb?ne?m -"^?????NR^#?T>\iC~??z1R?5SV?tI??-??1rh?[t^?<3????R$?G?X????=??e???^?R?z?D??5e??$D?g?\a4????9>??j8???? I*?E0??????h??O?? -???????A?qs}?6??4?6>^??V??q -4?C?LfZ?/?I???:???toT???g???i.??????????4?????x?A?A??c??[t?p?g????,???YZ?R-?%T(?p?^?w???+?)BFD?>+?Qa??i??3????h7????~4?r+?\1?b????p?? ?;7?J??H???????R -?bC???\?r?N??????J?D%C?c?*?o??>?Fg?g?]?????5???w???z??r-M?k???????t?$j?}?Ykl???~?? -??{??%92???`d -???E???NC??. #?~??????2XM?:??C?FfB???OL????a?36?O??%????' -??;e???Y???3"~?? -????;??g???a?H$&V?Z!-?^????*??/?#???{?vX????>S??>?Z??X5H???m???m:)??\5i?x?g???M??h+???V?+?"??????(d????GbS'?R_A)5e0??h??? -???{P????????R?^?_3q?wo????A?Q? ?H?,QJL???O??G??e???Mt7Q?z??cg????R&%?#J`?Y?.+Q?????.[ ??x? ????6>?U?2'nA??:o?/.[@?p???q?; N??k?,??F???s??*e?A?Ou/[???3?S?Gc???????h?{????e?t?? ?\1:b?[?X(b?C`?V6?k??L???(?!Jr? -=bt?%?????}?q?Z??????-?7h9 ??O$???q?i?? q??9?=??????????3????????`V??????W?????C??C?0?U?????M?$??Nho?\ -"?????r?L?? !?????X??G?????O???zm?W?????`?Yz? -NZ???Lrip?>???=?????t?t???!L??[??:???w?G?F?\a?D?j?"?l?1??yu?,h??n?OV[????ro*?mr(m?S?f?*??9/??@Z?&??Lq??.?5?2f?p9?$W??? ??Ls??@?H?JeFZ???l#-??,@???8C???^dRF??%??dq?,??Fy9wL>; ??t)???4\?????n}??fV??}Y;2??K???;W2??d????+0??r?e??`??=`?d>??v6????????I??Y?U??[R??1jj?O=??&f?z??????????BpEeQ?d?????)?{?????\P???u![??e#?i\??qr?!K?o??eDaCm?E??t???w.`????_?????[??/$?Tu?z>???~??!|????7z?5?? -?n???l??U?n)???H????X??[5 ?*? -?ucz`??_??xr?????n?0??b????o??Gi????.hIol???6\W?Y???x?(X4(?4-z:??kU????r?F????????Se}A?f3:^?UHzd%??gY -Dr??C^??`U*???????&????????s??w ??f -d?????h?^7%??o???\XZ{?)?d^>v??B? -????P?^?0D?7???=?iI]?"?x???>9M??#??}$?PT????D]V?????{??-??jtU0-?Mr?fS?d???Z[?y???????m??A,;??T????.????|??*g?1Ba??1Q?_|1??\??6wz? -a??C*^E??~???6????b?) -????B at s??6X?Z?k*(F?]"?4??B3RG??s??D????4\?????k???8??o2?M????a?E???~&?]gO|X?/*?e???e???(?o:}?????v?g9??????/????????}?W?D?e????N??3?????Pv\?8?{ ?t?j"??g??????q?}??? ? ???D/????}??ls?~~??.4?KR=?I?@P*??p?iw?nX????= ?>??U?.??m`?7?V_??U???>????{E}??g??l|?O???R????W???'? ??m???L0????`_@???B???'??(6u[?S??H???f?o?z??A`OP?7???AKX?????"?}w?ZK?dS?6 ??!??????7???^?K??"?F???2? -?p?m?m(? -,0Z??~+ -o??cV?c??^q?I????r"1X|?-?9????????????1????6!t??R?/;?@??ivh2W??Sz???S??????????q,??DY???.??:{?e???DF?h????yl%:? ]+???;d??8\?#=GT?Xi?E????)A,??????2??Uvgx???????h???9????O?ye#?????[i?Sz?M????v?`?{?Q?u?X???VZ$?? ?GT?S?'???????N8?S40]k??Q??6?bGU? ?P?? ?E?%???ts?\P?94]DZL?5"?U??? ?0?K?e?4"????kP??L!^?uON????f??n?P|%????v-f?>???Mu??m??|>?rfm7$?>???]??3?4??a???a?h??????????????P???]U??l??v?Q?!?k{B?????? ???????=  ?B??O??m?n???+??D(C??? -LN?aE?????hE?v???F?V?fY?p?>???V#?S?MW:5?q??v?h@??w?^yR????'??s? ?|??2?_?/$u?}??@?????&N?6??n?,"???q????_??vtVZ?X??&?nEN? ????v??_g??n?o?F"?????Q????????;SFb:?[k?????????r?0?jn????;???4??????V??z?8??*? ?????\?)??????p.?Pg|]?LS?`F??5.??????*??????+??% -????????????????Ni~???. ?c??Y)?????Y?3???/?>?oJ,? T?]??????'???f???+3P???a??/?4@????K,??mx\?PT??`?d??L??? -?b?E?(9;I?'????E?????WG?5c-? -E??J??u?wy??????]???Jw???x???8?? -????]Pf?m?Y?S7???l??z?]rc?"????M??X?/?a5??Z\p?????R??%?????4????de? s?y?w(??E????????????`??^?,??6???O?q?Fr#?\??LB??v=??:??^???"Ffq?$sF?W?P?un?s?????C?3???ZW???&1?h???j?k zl???s?4?????????f? -?F???-w=X ?%m?1??Z?'yc???"M??#?AEw?????8Znh??s?V:"?4PM??? ???*&??#?)?@??,l?(??t?KP?:c?1?K?r????????:F.?r?"???????????m(????8|??}a???????N?7??????+DQ?L'?=?$?bu?1t?????P?k5????8???????_??u?if? -51?[E;?h?l??B??!?b?4K?D?W?)[n??1???]??? -wB?Y??I?e???eD??e??C??d??#??v?bv?V????_i?m6?H?Rm???D?D??n??<?? -;q|i+?????3?;i? ???& ?????N?~???????)5??`N?]??\ ??8O?x -????h??e?????ZV)????v?u?.????O??l???xNB????A?>?'Q4?E?k?z??????? u??|?J? x4???s ?'??T?>;?? ?????T?????????n??7??#??2.S?G05j?WC??:???w\R1???w ?G??W2????2??x??????:??%?m6f?????^G???%?g {?U?d? ????-v2???}??f????Y??????*??z??%?8?B??d?[Z@????`??~X????c($uA;??t??grTuwzt.0n??^?d? -??e?!?x?)'?????'R ?%??Cq???? n?{fH??2JL?mJ?-??w????rG,#?`??D<2?e7??v???|?7?UZ%??? ;??iL? -??B?K?)%q?? ?????~?O?R????(? ?T7??????X????T?*8?=?l???:8YA???#?"??7?n?=?U???ot?R?????t?*?'???Y???k? ?0hW??=?e???p[??'}??|?$?>??v??1??v??v??/?\2?o?3?S??4?? ???zkw2?u?x?? ?? -G??4?6??y??? -????2? ?)?z6j?&?bk?U????I?? ???V[???Js\k?.??@?ewz?8/P????T?PE`???o??7?????ZL0Z"??x1c?/U#Z?????)???\???????? -??jx?vby???0??YTNk?6??B ?P/????9f???0V??B??u?_3=???%9cc??xW?9A??{f^?"?e?8????w?-4 p??rD.????q??2?????'?d[??C?*??~?hl??????Y3???Q?9YI??vH?y? ??j?=??)?E|@?wA?^???q??????U&,?,?Y??? k??dl?e?????aW? -D9C?????5F????El???y??????DS?z?PYL??Y]?V??????????KZ?$??1?W`~D%W?E?XC???4e??mB.?????>?:?c??U??????????D?9??qv?|??Y&=?????X?#???? t??]a`??;??HH???U???@?-??1???4)#(?z????0^?E?I??v??u???? +;Gcl<3?"?8;UhN?#B??o? ?? -????0'??%??k??Y&????(I }??j????~G??Ur?????Lx?B(+pea?s_"I?yZ?0?o????6?|{?%?K???=z4??e?3????=?F??5????L?K??-??????? ???X????????????5?rp?L??l??-???{??"???{yl7p???P???MT?????5/:O??(?????w?.{?b??Uo???f&???V?_:?? :?????tT?B???gk*bo -??`?,;2??sU????????~??RY???\?vS?a?OD ??????????@ ???????? g????8"????????_?5?}?R??|5?e?/%??Sl%???7?Uk???bV??-??o? -N?p?T=???;?X?u??^???F????7????=f?)?_y?U5?{1????z??+iK??a;??b?#w??2?~???G?y?|??JZ??FT???3?7(??x?d)?fzL?.????? -??)???????:????)?H?gk???v???bP?h????8Tc?d?+?;?????D???[?|????????F*s_}L???r??2??????I?~?Sxtuh2o2?d3??????n?t??p????????"?%?N????????G??????? -??Ru??.???3?V2???F??7k??82^fX[????9NKE?R]???#?t$?fv??6,?SY`?kmzL?LD?y?1e??? ??? 7(???v??OD?????q?u????Cw?W>?"???4?ag:? -gx:4|??k???O?p??He\?)?????Uy?E??R Author: jedick Date: 2019-02-18 12:59:47 +0100 (Mon, 18 Feb 2019) New Revision: 398 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/R/util.expression.R pkg/CHNOSZ/demo/NaCl.R pkg/CHNOSZ/inst/NEWS pkg/CHNOSZ/man/examples.Rd pkg/CHNOSZ/man/util.expression.Rd Log: demo/NaCl.R: improve labels and documentation of discontinuities Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-17 21:43:50 UTC (rev 397) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-18 11:59:47 UTC (rev 398) @@ -1,6 +1,6 @@ Date: 2019-02-18 Package: CHNOSZ -Version: 1.2.0-4 +Version: 1.2.0-5 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/R/util.expression.R =================================================================== --- pkg/CHNOSZ/R/util.expression.R 2019-02-17 21:43:50 UTC (rev 397) +++ pkg/CHNOSZ/R/util.expression.R 2019-02-18 11:59:47 UTC (rev 398) @@ -255,7 +255,7 @@ if(i %in% iname) species <- reaction$name[i] else { # should the chemical formula have a state? - if(identical(states,"all")) species <- expr.species(reaction$formula[i], state=reaction$state[i], use.state=TRUE) + if(identical(states,"all") | i %in% states) species <- expr.species(reaction$formula[i], state=reaction$state[i], use.state=TRUE) else species <- expr.species(reaction$formula[i], state=reaction$state[i]) } # get the absolute value of the reaction coefficient @@ -278,7 +278,8 @@ } } # put an equals sign between reactants and products - desc <- substitute(a==b, list(a=reactexpr, b=prodexpr)) + # change this to unicode for the reaction double-arrow 20190218 \u21cc + desc <- substitute(a ~ "\u21cc" ~ b, list(a=reactexpr, b=prodexpr)) return(desc) } Modified: pkg/CHNOSZ/demo/NaCl.R =================================================================== --- pkg/CHNOSZ/demo/NaCl.R 2019-02-17 21:43:50 UTC (rev 397) +++ pkg/CHNOSZ/demo/NaCl.R 2019-02-18 11:59:47 UTC (rev 398) @@ -4,40 +4,59 @@ ## Calculation of the thermodynamic properties of aqueous species at high pressures and temperatures: ## Effective electrostatic radii, dissociation constants and standard partial molal properties to 1000 degrees C and 5 kbar. ## J. Chem. Soc. Faraday Trans. 88, 803-826. https://doi.org/10.1039/FT9928800803 ) -species <- c("NaCl", "Na+", "Cl-") -coeffs <- c(-1, 1, 1) + +## uncomment these lines to make the plot with the g-function disabled +#mod.obigt("Cl-", z=0) +#mod.obigt("Na+", z=0) + # start a new plot and show the experimental logK thermo.plot.new(xlim=c(0, 1000), ylim=c(-5.5, 1), xlab=axis.label("T"), ylab=axis.label("logK")) expt <- read.csv(system.file("extdata/cpetc/SOJSH.csv", package="CHNOSZ"), as.is=TRUE) points(expt$T,expt$logK, pch=expt$pch) + # we'll be at 9 distinct pressure conditions, including Psat -P <- c(list("Psat"), as.list(seq(500, 4000, by=500))) +# Psat is repeated to show "not considered" region +# (T >= 355 degC; Fig. 6 of Shock et al., 1992) +P <- c(list("Psat", "Psat"), as.list(seq(500, 4000, by=500))) # for each of those what's the range of temperature T <- list() -# T > 350 degC at Psat is possibly inappropriate; see "Warning" of subcrt.Rd -T[[1]] <- seq(0, 370, 5) -T[[2]] <- seq(265, 465, 5) -T[[3]] <- seq(285, 760, 5) -T[[4]] <- seq(395, 920, 5) -T[[5]] <- T[[6]] <- T[[7]] <- T[[8]] <- T[[9]] <- seq(400, 1000, 5) +T[[1]] <- seq(0, 354, 1) +T[[2]] <- seq(354, 370, 1) +T[[3]] <- seq(265, 465, 1) +T[[4]] <- seq(285, 760, 1) +T[[5]] <- seq(395, 920, 1) +T[[6]] <- T[[7]] <- T[[8]] <- T[[9]] <- T[[10]] <- seq(400, 1000, 1) + # calculate and plot the logK +species <- c("NaCl", "Na+", "Cl-") +coeffs <- c(-1, 1, 1) logK <- numeric() for(i in 1:length(T)) { s <- subcrt(species, coeffs, T=T[[i]], P=P[[i]]) - lines(s$out$T, s$out$logK) - # keep the calculated values for each experimental condition + if(i==2) lty <- 3 else lty <- 1 + lines(s$out$T, s$out$logK, lty=lty) + # keep the calculated values for each experimental condition (excluding Psat) iexpt <- which(P[[i]]==expt$P) Texpt <- expt$T[iexpt] - logK <- c(logK, splinefun(s$out$T, s$out$logK)(Texpt)) + if(i > 2) logK <- c(logK, splinefun(s$out$T, s$out$logK)(Texpt)) } + +# add title, labels, and legends +title(describe.reaction(s$reaction, states = 1)) +text(150, -0.1, quote(italic(P)[sat]), cex=1.2) +text(462, -4, "500 bar") +text(620, -4.3, "1000 bar") +text(796, -4.3, "1500 bar") +text(813, -1.4, "4000 bar") legend("bottomleft",pch=unique(expt$pch), - legend=c(unique(expt$source),tail(expt$source,1))) -mtitle(c(describe.reaction(s$reaction), expression(italic(P)[sat]~"or 500-4000 bar, after Shock et al., 1992"))) -# where do we diverge most from experiment? -imaxdiff <- which.max(abs(logK - expt$logK)) -stopifnot(all.equal(c("Psat", 347.7), - as.character(expt[imaxdiff,1:2]))) -# what's our average divergence? + legend=c(unique(expt$source),tail(expt$source,1)), bty="n") +#mtitle(c(describe.reaction(s$reaction), expression(italic(P)[sat]~"and 500-4000 bar"))) +l1 <- quote("Revised HKF model with " * italic(g) * " function (Shock et al., 1992)") +l2 <- "Non-recommended region (Shock et al., 1992, Fig. 6)" +legend("topright", as.expression(c(l1, l2)), lty=c(1, 3), bty="n") + +# test for average divergence (excluding Psat) +expt <- expt[!expt$P %in% "Psat", ] stopifnot(mean(abs(logK - expt$logK)) < 0.09) Modified: pkg/CHNOSZ/inst/NEWS =================================================================== --- pkg/CHNOSZ/inst/NEWS 2019-02-17 21:43:50 UTC (rev 397) +++ pkg/CHNOSZ/inst/NEWS 2019-02-18 11:59:47 UTC (rev 398) @@ -1,4 +1,4 @@ -CHANGES IN CHNOSZ 1.2.0-4 (2019-02-18) +CHANGES IN CHNOSZ 1.2.0-5 (2019-02-18) -------------------------------------- CRAN COMPLIANCE @@ -20,8 +20,24 @@ THERMODYNAMIC DATA -- Move SiO2(aq) and H2AsO3- from SLOP98.csv to SUPCRT92.csv. +- Revert to using SiO2(aq) from SUPCRT92 (i.e. Shock et al., 1989) in + the default database. +- Move SiO2(aq) from Apps and Spycher, 2004 and recalculated HSiO3- to + new optional data file, OBIGT/AS04.csv. + +- Move H2AsO3- from SLOP98.csv to SUPCRT92.csv. + +DOCUMENTATION + +- In demo/NaCl.R, indicate region not considered by Shock et al., 1992 + in developing the revised HKF model and presence of the associated + discontinuities in SUPCRT92. + +OTHER CHANGES + +- In describe.reaction(), change equals sign to reaction double arrow. + CHANGES IN CHNOSZ 1.2.0 (2019-02-09) ------------------------------------ Modified: pkg/CHNOSZ/man/examples.Rd =================================================================== --- pkg/CHNOSZ/man/examples.Rd 2019-02-17 21:43:50 UTC (rev 397) +++ pkg/CHNOSZ/man/examples.Rd 2019-02-18 11:59:47 UTC (rev 398) @@ -73,12 +73,14 @@ There are 12 ribulose phosphate carboxylase and 12 acetyl-coenzyme A carboxylase; 6 of each type are from nominally mesophilic organisms and 6 from nominally thermophilic organisms, shown as blue and red symbols on the diagrams. The activities of hydrogen at each temperature are calculated using \eqn{\log a_{\mathrm{H_{2}}_{\left(aq\right)}}=-11+3/\left(40\times T\left(^{\circ}C\right)\right)}{logaH2 = -11 + 3/40 * T(degC)}; this equation comes from a model of relative stabilities of proteins in a hot-spring environment (Dick and Shock, 2011). -In the \samp{NaCl} demo, the \logK lines calculated at \Psat and P=500 bar show discontinuities at 355 \degC. -Although not realistic, this behavior is consistent with the output of \acronym{SUPCRT92} (Johnson et al., 1992) at 500 bar. -This is probably due to a transition between different regimes for the properties of water as coded in SUPCRT's \code{H2O92D.F}, which is used by CHNOSZ. -(Note that SUPCRT does not output thermodynamic properties above 350 \degC at \Psat; see Warning in \code{\link{subcrt}}.) } +\section{Warning}{ +The discontinuities apparent in the plot made by the \code{NaCl} demo illustrate limitations of the "\emph{g} function" for charged species in the revised HKF model (the 355 \degC boundary of region II in Figure 6 of Shock et al., 1992). +Note that \acronym{SUPCRT92} (Johnson et al., 1992) gives similar output at 500 bar. +However, \acronym{SUPCRT} does not output thermodynamic properties above 350 \degC at \Psat; see Warning in \code{\link{subcrt}}. +} + \references{ Akinfiev, N. N. and Zotov, A. V. (2001) Thermodynamic description of chloride, hydrosulfide, and hydroxo complexes of Ag(I), Cu(I), and Au(I) at temperatures of 25-500\degC and pressures of 1-2000 bar. \emph{Geochem. Int.} \bold{39}, 990--1006. \url{http://pleiades.online/cgi-perl/search.pl/?type=abstract&name=geochem&number=10&year=1&page=990} Modified: pkg/CHNOSZ/man/util.expression.Rd =================================================================== --- pkg/CHNOSZ/man/util.expression.Rd 2019-02-17 21:43:50 UTC (rev 397) +++ pkg/CHNOSZ/man/util.expression.Rd 2019-02-18 11:59:47 UTC (rev 398) @@ -50,7 +50,7 @@ \item{ret.val}{logical, return only the value with the units?} \item{reaction}{data frame, definition of reaction} \item{iname}{numeric, show names instead of formulas for these species} - \item{states}{character, if \samp{all}, show states for all species} + \item{states}{character, if \samp{all}, show states for all species; numeric, which species to show states for} \item{system}{character, thermodynamic components} \item{dash}{character to use for dash between components} \item{ion}{character, an ion} @@ -112,7 +112,12 @@ \code{describe.property} makes an expression summarizing the properties supplied in \code{property}, along with their \code{value}s. The expressions returned by both functions consist of a property, an equals sign, and a value (with units where appropriate); the expressions have a length equal to the number of property/value pairs. If \code{oneline} is TRUE, the property/value pairs are combined into a single line, separated by commas. The number of digits shown after the decimal point in the values is controlled by \code{digits}. If \code{ret.val} is TRUE, only the values and their units are returned; this is useful for labeling plots with values of temperature. - \code{describe.reaction} makes an expression summarizing a chemical reaction. The \code{reaction} data frame can be generated using \code{\link{subcrt}}. Based on the sign of their reaction coefficients, species are placed on the reactant (left) or product (right) side of the reaction, where the species with their coefficients are separated by plus signs; the two sides of the reaction are separated by an equals sign. Coefficients equal to 1 are not shown. Chemical formulas of species include a designation of physical state if \code{states} is \samp{all}. Names of species (as provided in \code{reaction}) are shown instead of chemical formulas for the species identified by \code{iname}. +\code{describe.reaction} makes an expression summarizing a chemical reaction. +The \code{reaction} data frame can be generated using \code{\link{subcrt}}. +Based on the sign of their reaction coefficients, species are placed on the reactant (left) or product (right) side of the reaction, where the species with their coefficients are separated by plus signs; the two sides of the reaction are separated by a reaction double arrow (Unicode U+21CC). +Coefficients equal to 1 are not shown. +Chemical formulas of species include the physical state if \code{states} is \samp{all}, or a numeric value indicating which species to label with the state. +Names of species (as provided in \code{reaction}) are shown instead of chemical formulas for the species identified by \code{iname}. \code{syslab} formats the given thermodynamic components (using \code{expr.species}) and adds intervening en dashes. From noreply at r-forge.r-project.org Tue Feb 19 12:12:12 2019 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Tue, 19 Feb 2019 12:12:12 +0100 (CET) Subject: [CHNOSZ-commits] r399 - in pkg/CHNOSZ: . R inst man Message-ID: <20190219111212.B684F18C037@r-forge.r-project.org> Author: jedick Date: 2019-02-19 12:12:12 +0100 (Tue, 19 Feb 2019) New Revision: 399 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/R/water.R pkg/CHNOSZ/inst/NEWS pkg/CHNOSZ/man/water.Rd Log: water(): add 'P1' argument (set Psat to 1 bar below 100 degrees C) Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-18 11:59:47 UTC (rev 398) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-19 11:12:12 UTC (rev 399) @@ -1,6 +1,6 @@ -Date: 2019-02-18 +Date: 2019-02-19 Package: CHNOSZ -Version: 1.2.0-5 +Version: 1.2.0-6 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/R/water.R =================================================================== --- pkg/CHNOSZ/R/water.R 2019-02-18 11:59:47 UTC (rev 398) +++ pkg/CHNOSZ/R/water.R 2019-02-19 11:12:12 UTC (rev 399) @@ -2,7 +2,7 @@ # calculate thermodynamic and electrostatic properties of H2O # 20061016 jmd -water <- function(property = NULL, T = 298.15, P = "Psat") { +water <- function(property = NULL, T = 298.15, P = "Psat", P1 = TRUE) { # calculate the properties of liquid H2O as a function of T and P # T in Kelvin, P in bar if(is.null(property)) return(get("thermo", CHNOSZ)$opt$water) @@ -25,7 +25,7 @@ # change 273.15 K to 273.16 K (needed for water.SUPCRT92 at Psat) if(identical(P, "Psat")) T[T == 273.15] <- 273.16 # get properties using SUPCRT92 - w.out <- water.SUPCRT92(property, T, P) + w.out <- water.SUPCRT92(property, T, P, P1) } if(grepl("IAPWS", wopt)) { # get properties using IAPWS-95 @@ -38,7 +38,7 @@ w.out } -water.SUPCRT92 <- function(property=NULL, T=298.15, P=1) { +water.SUPCRT92 <- function(property=NULL, T=298.15, P=1, P1=TRUE) { ### interface to H2O92D.f : FORTRAN subroutine taken from ### SUPCRT92 for calculating the thermodynamic and ### electrostatic properties of H2O. @@ -105,7 +105,7 @@ w.P <- H2O[[2]][2] w.P[w.P==0] <- NA # Psat specifies P=1 below 100 degC - w.P[w.P < 1] <- 1 + if(P1) w.P[w.P < 1] <- 1 P.out[i] <- w.P } } Modified: pkg/CHNOSZ/inst/NEWS =================================================================== --- pkg/CHNOSZ/inst/NEWS 2019-02-18 11:59:47 UTC (rev 398) +++ pkg/CHNOSZ/inst/NEWS 2019-02-19 11:12:12 UTC (rev 399) @@ -1,4 +1,4 @@ -CHANGES IN CHNOSZ 1.2.0-5 (2019-02-18) +CHANGES IN CHNOSZ 1.2.0-6 (2019-02-19) -------------------------------------- CRAN COMPLIANCE @@ -18,6 +18,10 @@ - Add retrieve() to retrieve all the species with given elements. Thanks to Evgeniy Bastrakov for the suggestion. +- water() and water.SUPCRT92(): add 'P1' argument to choose whether to + output 1 bar for Psat at temperatures less than 100 degrees C + (default is TRUE). + THERMODYNAMIC DATA - Revert to using SiO2(aq) from SUPCRT92 (i.e. Shock et al., 1989) in Modified: pkg/CHNOSZ/man/water.Rd =================================================================== --- pkg/CHNOSZ/man/water.Rd 2019-02-18 11:59:47 UTC (rev 398) +++ pkg/CHNOSZ/man/water.Rd 2019-02-19 11:12:12 UTC (rev 399) @@ -10,8 +10,8 @@ } \usage{ - water(property = NULL, T = 298.15, P = "Psat") - water.SUPCRT92(property=NULL, T = 298.15, P = 1) + water(property = NULL, T = 298.15, P = "Psat", P1 = TRUE) + water.SUPCRT92(property=NULL, T = 298.15, P = 1, P1 = TRUE) water.IAPWS95(property=NULL, T = 298.15, P = 1) water.DEW(property=NULL, T = 373.15, P = 1000) } @@ -20,6 +20,7 @@ \item{property}{character, computational setting or property(s) to calculate} \item{T}{numeric, temperature (K)} \item{P}{numeric, pressure (bar), or \samp{Psat} for vapor-liquid saturation} + \item{P1}{logical, output pressure of 1 bar below 100 \degC instead of calculated values of \samp{Psat}?} } \details{ From noreply at r-forge.r-project.org Tue Feb 19 23:57:50 2019 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Tue, 19 Feb 2019 23:57:50 +0100 (CET) Subject: [CHNOSZ-commits] r400 - in pkg/CHNOSZ: . R inst man tests/testthat Message-ID: <20190219225750.D681318C1EF@r-forge.r-project.org> Author: jedick Date: 2019-02-19 23:57:50 +0100 (Tue, 19 Feb 2019) New Revision: 400 Added: pkg/CHNOSZ/R/AkDi.R Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/NAMESPACE pkg/CHNOSZ/R/hkf.R pkg/CHNOSZ/R/info.R pkg/CHNOSZ/R/subcrt.R pkg/CHNOSZ/R/util.data.R pkg/CHNOSZ/inst/NEWS pkg/CHNOSZ/man/eos.Rd pkg/CHNOSZ/man/thermo.Rd pkg/CHNOSZ/tests/testthat/test-eos.R pkg/CHNOSZ/tests/testthat/test-info.R pkg/CHNOSZ/tests/testthat/test-thermo.R Log: add AkDi(): new function implementing Akinfiev-Diamond model Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-19 11:12:12 UTC (rev 399) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-19 22:57:50 UTC (rev 400) @@ -1,6 +1,6 @@ -Date: 2019-02-19 +Date: 2019-02-20 Package: CHNOSZ -Version: 1.2.0-6 +Version: 1.2.0-8 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/NAMESPACE =================================================================== --- pkg/CHNOSZ/NAMESPACE 2019-02-19 11:12:12 UTC (rev 399) +++ pkg/CHNOSZ/NAMESPACE 2019-02-19 22:57:50 UTC (rev 400) @@ -58,7 +58,7 @@ # added 20171121 or later "dumpdata", "thermo.axis", "solubility", "NaCl", # added 20190213 or later - "CHNOSZ", "thermo", "reset", "obigt", "retrieve" + "CHNOSZ", "thermo", "reset", "obigt", "retrieve", "AkDi" ) # Load shared objects Added: pkg/CHNOSZ/R/AkDi.R =================================================================== --- pkg/CHNOSZ/R/AkDi.R (rev 0) +++ pkg/CHNOSZ/R/AkDi.R 2019-02-19 22:57:50 UTC (rev 400) @@ -0,0 +1,54 @@ +# CHNOSZ/AkDi.R +# Akinfiev-Diamond model for aqueous species +# 20190219 first version + +AkDi <- function(property = NULL, parameters = NULL, T = 298.15, P = 1, isPsat = TRUE) { + + # some constants (from Akinfiev and Diamond, 2004 doi:10.1016/j.fluid.2004.06.010) + MW <- 18.0153 # g mol-1 + NW <- 1000/MW # mol kg-1 + R <- 8.31441 # J K-1 mol-1 + + # a list for the output + out <- list() + # loop over species + nspecies <- nrow(parameters) + for(i in seq_len(nspecies)) { + PAR <- parameters[i, ] + # start with an NA-filled data frame + myprops <- as.data.frame(matrix(NA, ncol=length(property), nrow=length(T))) + colnames(myprops) <- property + # just calculate G for now + for(j in seq_along(property)) { + if(property[[j]]=="G") { + # send a message + message("AkDi(): Akinfiev-Diamond model for ", PAR$name, " gas to aq") + # get gas properties (J mol-1) + G_gas <- subcrt(PAR$name, "gas", T=T, P=P, convert=FALSE)$out[[1]]$G + # TODO: does this work if E.units is cal or J? + G_gas <- convert(G_gas, "J", T=T) + # get H2O fugacity (bar) + GH2O_P <- water("G", T=T, P=P)$G + GH2O_1 <- water("G", T=T, P=1)$G + f1 <- exp ( (GH2O_P - GH2O_1) / (1.9872 * T) ) + # for Psat, calculate the real liquid-vapor curve (not 1 bar below 100 degC) + if(isPsat) { + P <- water("Psat", T = T, P = "Psat", P1 = FALSE)$Psat + f1[P < 1] <- P[P < 1] + } + # density (g cm-3) + rho1 <- water("rho", T=T, P=P)$rho / 1000 + # calculate G_hyd (J mol-1) + G_hyd <- R*T * ( -log(NW) + (1 - PAR$xi) * log(f1) + PAR$xi * log(10 * R * T * rho1 / MW) + rho1 * (PAR$a + PAR$b * (1000/T)^0.5) ) + # calculate the chemical potential (J mol-1) + G <- G_gas + G_hyd + # convert J to cal + G <- convert(G, "cal", T=T) + # insert into data frame of properties + myprops$G <- G + } + } + out[[i]] <- myprops + } + out +} Modified: pkg/CHNOSZ/R/hkf.R =================================================================== --- pkg/CHNOSZ/R/hkf.R 2019-02-19 11:12:12 UTC (rev 399) +++ pkg/CHNOSZ/R/hkf.R 2019-02-19 22:57:50 UTC (rev 400) @@ -48,7 +48,7 @@ # a list to store the result aq.out <- list() nspecies <- nrow(parameters) - for(k in 1:nspecies) { + for(k in seq_len(nspecies)) { # loop over each species PAR <- parameters[k, ] # substitute Cp and V for missing EoS parameters @@ -71,7 +71,7 @@ dwdP <- dwdT <- d2wdT2 <- numeric(length(T)) Z <- PAR$Z omega.PT <- rep(PAR$omega, length(T)) - if(!identical(Z, 0) & !identical(PAR$name, "H+")) { + if(!identical(Z, 0) & !is.na(Z) & !identical(PAR$name, "H+")) { # compute derivatives of omega: g and f functions (Shock et al., 1992; Johnson et al., 1992) rhohat <- H2O.PT$rho/1000 # just converting kg/m3 to g/cm3 g <- gfun(rhohat, convert(T, "C"), P, H2O.PT$alpha, H2O.PT$daldT, H2O.PT$beta) Modified: pkg/CHNOSZ/R/info.R =================================================================== --- pkg/CHNOSZ/R/info.R 2019-02-19 11:12:12 UTC (rev 399) +++ pkg/CHNOSZ/R/info.R 2019-02-19 22:57:50 UTC (rev 400) @@ -194,7 +194,8 @@ this[, which(naGHS)+7] <- GHS[naGHS] } # now perform consistency checks for GHS and EOS parameters if check.it=TRUE - if(check.it) { + # don't do it for the AkDi species 20190219 + if(check.it & !"xi" %in% colnames(this)) { # check GHS if they were all present if(sum(naGHS)==0) calcG <- checkGHS(this) # check tabulated heat capacities against EOS parameters Modified: pkg/CHNOSZ/R/subcrt.R =================================================================== --- pkg/CHNOSZ/R/subcrt.R 2019-02-19 11:12:12 UTC (rev 399) +++ pkg/CHNOSZ/R/subcrt.R 2019-02-19 22:57:50 UTC (rev 400) @@ -9,6 +9,7 @@ #source("util.units.R") #source("util.data.R") #source("species.R") +#source("AkDi.R") subcrt <- function(species, coeff = 1, state = NULL, property = c("logK", "G", "H", "S", "V", "Cp"), T = seq(273.15, 623.15, 25), P = "Psat", grid = NULL, convert = TRUE, exceed.Ttr = FALSE, @@ -75,6 +76,7 @@ } # gridding? + isPsat <- FALSE do.grid <- FALSE if(!is.null(grid)) if(!is.logical(grid)) do.grid <- TRUE newIS <- IS @@ -101,6 +103,8 @@ P <- rep(tpargs$P,length.out=length(newIS)) } } else { + # for AkDi, remember if P = "Psat" 20190219 + if(identical(P, "Psat")) isPsat <- TRUE # expansion of Psat and equivalence of argument lengths tpargs <- TP.args(T=T,P=P) T <- tpargs$T; P <- tpargs$P @@ -277,17 +281,22 @@ if(TRUE %in% isaq) { # 20110808 get species parameters using obigt2eos() (faster than using info()) param <- obigt2eos(thermo$obigt[iphases[isaq],], "aq", fixGHS = TRUE) + # aqueous species with NA for Z use the AkDi model + isAkDi <- is.na(param$Z) # always get density H2O.props <- "rho" # calculate A_DH and B_DH if we're using the B-dot (Helgeson) equation if(any(IS != 0) & thermo$opt$nonideal %in% c("Bdot", "Bdot0", "bgamma", "bgamma0")) H2O.props <- c(H2O.props, "A_DH", "B_DH") # get other properties for H2O only if it's in the reaction if(any(isH2O)) H2O.props <- c(H2O.props, eosprop) - hkfstuff <- hkf(eosprop, parameters = param, T = T, P = P, H2O.props=H2O.props) + # in case everything is AkDi, run hkf (for water properties) but exclude all species + hkfpar <- param + if(all(isAkDi)) hkfpar <- param[0, ] + hkfstuff <- hkf(eosprop, parameters = hkfpar, T = T, P = P, H2O.props=H2O.props) p.aq <- hkfstuff$aq H2O.PT <- hkfstuff$H2O # set properties to NA for density below 0.35 g/cm3 (a little above the critical isochore, threshold used in SUPCRT92) 20180922 - if(!exceed.rhomin) { + if(!exceed.rhomin & !all(isAkDi)) { ilowrho <- H2O.PT$rho < 350 ilowrho[is.na(ilowrho)] <- FALSE if(any(ilowrho)) { @@ -296,6 +305,12 @@ warnings <- c(warnings, paste0("below minimum density for applicability of revised HKF equations (", sum(ilowrho), " T,P ", ptext, ")")) } } + # calculate properties using Akinfiev-Diamond model 20190219 + if(any(isAkDi)) { + # get the parameters with the right names + param <- obigt2eos(param[isAkDi, ], "aq") + p.aq[isAkDi] <- AkDi(eosprop, parameters = param, T = T, P = P, isPsat = isPsat) + } # calculate activity coefficients if ionic strength is not zero if(any(IS != 0)) { if(thermo$opt$nonideal %in% c("Bdot", "Bdot0", "bgamma", "bgamma0")) p.aq <- nonideal(iphases[isaq], p.aq, newIS, T, P, H2O.PT$A_DH, H2O.PT$B_DH) Modified: pkg/CHNOSZ/R/util.data.R =================================================================== --- pkg/CHNOSZ/R/util.data.R 2019-02-19 11:12:12 UTC (rev 399) +++ pkg/CHNOSZ/R/util.data.R 2019-02-19 22:57:50 UTC (rev 400) @@ -397,8 +397,15 @@ # remove scaling factors from EOS parameters # and apply column names depending on the EOS if(identical(state, "aq")) { - obigt[,13:20] <- t(t(obigt[,13:20]) * 10^c(-1,2,0,4,0,4,5,0)) - colnames(obigt)[13:20] <- c('a1','a2','a3','a4','c1','c2','omega','Z') + # species in the Akinfiev-Diamond model (AkDi) have NA for Z 20190219 + isAkDi <- is.na(obigt$z.T) + # remove scaling factors for the HKF species, but not for the AkDi species + obigt[!isAkDi, 13:20] <- t(t(obigt[!isAkDi, 13:20]) * 10^c(-1,2,0,4,0,4,5,0)) + # for AkDi specie, set NA values in remaining columns (for display only) + obigt[isAkDi, 16:19] <- NA + # if all of the species are AkDi, change the variable names + if(all(isAkDi)) colnames(obigt)[13:20] <- c('a','b','xi','XX1','XX2','XX3','XX4','Z') + else colnames(obigt)[13:20] <- c('a1','a2','a3','a4','c1','c2','omega','Z') } else { obigt[,13:20] <- t(t(obigt[,13:20]) * 10^c(0,-3,5,0,-5,0,0,0)) colnames(obigt)[13:20] <- c('a','b','c','d','e','f','lambda','T') Modified: pkg/CHNOSZ/inst/NEWS =================================================================== --- pkg/CHNOSZ/inst/NEWS 2019-02-19 11:12:12 UTC (rev 399) +++ pkg/CHNOSZ/inst/NEWS 2019-02-19 22:57:50 UTC (rev 400) @@ -1,4 +1,4 @@ -CHANGES IN CHNOSZ 1.2.0-6 (2019-02-19) +CHANGES IN CHNOSZ 1.2.0-8 (2019-02-20) -------------------------------------- CRAN COMPLIANCE @@ -18,9 +18,9 @@ - Add retrieve() to retrieve all the species with given elements. Thanks to Evgeniy Bastrakov for the suggestion. -- water() and water.SUPCRT92(): add 'P1' argument to choose whether to - output 1 bar for Psat at temperatures less than 100 degrees C - (default is TRUE). +- Add AkDi() to calculate thermodynamic properties of aqueous + nonelectrolytes using the Akinfiev-Diamond model. Thanks to Evgeniy + Bastrakov for guidance and advice. THERMODYNAMIC DATA @@ -30,18 +30,23 @@ - Move SiO2(aq) from Apps and Spycher, 2004 and recalculated HSiO3- to new optional data file, OBIGT/AS04.csv. -- Move H2AsO3- from SLOP98.csv to SUPCRT92.csv. +- Move H2AsO3- from OBIGT/SLOP98.csv to OBIGT/SUPCRT92.csv. DOCUMENTATION - In demo/NaCl.R, indicate region not considered by Shock et al., 1992 - in developing the revised HKF model and presence of the associated - discontinuities in SUPCRT92. + in developing the "g function" applicable to electrolytes in the + revised HKF model, and note presence of resulting discontinuities (see + man/examples.Rd). OTHER CHANGES - In describe.reaction(), change equals sign to reaction double arrow. +- water() and water.SUPCRT92(): add 'P1' argument to choose whether to + output 1 bar for Psat at temperatures less than 100 degrees C + (default is TRUE). + CHANGES IN CHNOSZ 1.2.0 (2019-02-09) ------------------------------------ Modified: pkg/CHNOSZ/man/eos.Rd =================================================================== --- pkg/CHNOSZ/man/eos.Rd 2019-02-19 11:12:12 UTC (rev 399) +++ pkg/CHNOSZ/man/eos.Rd 2019-02-19 22:57:50 UTC (rev 400) @@ -3,15 +3,17 @@ \alias{eos} \alias{hkf} \alias{cgl} +\alias{AkDi} \title{Equations of State} \description{ -Calculate thermodynamic properties using the revised Helgeson-Kirkham-Flowers (HKF) equations of state for aqueous species, or using a generic heat capacity equation for crystalline, gas, and liquid species. +Calculate thermodynamic properties using the revised Helgeson-Kirkham-Flowers (HKF) or Akinfiev-Diamond (AkDi) equations of state for aqueous species, or using a generic heat capacity equation for crystalline, gas, and liquid species. } \usage{ cgl(property = NULL, parameters = NULL, T = 298.15, P = 1) hkf(property = NULL, parameters = NULL, T = 298.15, P = 1, contrib = c("n", "s", "o"), H2O.props = "rho") + AkDi(property = NULL, parameters = NULL, T = 298.15, P = 1, isPsat = TRUE) } \arguments{ @@ -21,6 +23,7 @@ \item{P}{numeric, pressure(s) at which to calculate properties (bar)} \item{contrib}{character, which contributions to consider in the revised HKF equations equations of state: (\code{n})onsolvation, (\code{s})olvation (the \eqn{\omega}{omega} terms), or (o)rigination contributions (i.e., the property itself at 25 \degC and 1 bar). Default is \code{c("n","s","o")}, for all contributions} \item{H2O.props}{character, properties to calculate for water} + \item{isPsat}{logical, is this a calculation along the liquid-vapor saturation curve (Psat)?} } \details{ @@ -43,11 +46,16 @@ For both \code{hkf} and \code{cgl}, if at least one equations-of-state parameter for a species is provided, any NA values of the other parameters are reset to zero. If all equations-of-state parameters are NA, but values of \samp{Cp} and/or \samp{V} are available, those values are used in the integration of \samp{G}, \samp{H} and \samp{S} as a function of temperature. + +\code{AkDi} provides the Akinfiev-Diamond model for aqueous species (Akinfiev and Diamond, 2003). +To run this code, the database must also include the corresponding gasesous species (with the same name or chemical formula). + } \section{Warning}{ -The temperature and pressure range of validity of the revised HKF equations of state for aqueous species corresponds to the stability region of liquid water or the supercritical fluid at conditions between 0 to 1000 \degC and 1 to 5000 bar (Tanger and Helgeson, 1988; Shock and Helgeson, 1988). -The \code{hkf} function does not check these limits and will compute properties as long as the requisite electrostatic properties of water are available. There are conceptually no temperature limits (other than 0 Kelvin) for the validity of the \code{cgl} equations of state. +The range of applicability of the revised HKF equations of state for aqueous species corresponds to the stability region of liquid water or the supercritical fluid with density greater than 0.35 g/cm3, and between 0 to 1000 \degC and 1 to 5000 bar (Tanger and Helgeson, 1988; Shock and Helgeson, 1988). +The \code{hkf} function does not check these limits and will compute properties as long as the requisite electrostatic properties of water are available. +There are conceptually no temperature limits (other than 0 Kelvin) for the validity of the \code{cgl} equations of state. However, the actual working upper temperature limits correspond to the temperatures of phase transitions of minerals or to those temperatures beyond which extrapolations from experimental data become highly uncertain. These temperature limits are stored in the thermodynamic database for some minerals, but \code{cgl} ignores them; however, \code{\link{subcrt}} warns if they are exceeded. } @@ -86,6 +94,8 @@ \references{ + Akinfiev, N. N. and Diamond, L. W. (2003) Thermodynamic description of aqueous nonelectrolytes at infinite dilution over a wide range of state parameters. \emph{Geochim. Cosmochim. Acta} \bold{67}, 613--629. \url{https://doi.org/10.1016/S0016-7037(02)01141-9} + Helgeson, H. C., Kirkham, D. H. and Flowers, G. C. (1981) Theoretical prediction of the thermodynamic behavior of aqueous electrolytes at high pressures and temperatures. IV. Calculation of activity coefficients, osmotic coefficients, and apparent molal and standard and relative partial molal properties to 600\degC and 5 Kb. \emph{Am. J. Sci.} \bold{281}, 1249--1516. \url{https://doi.org/10.2475/ajs.281.10.1249} Helgeson, H. C., Owens, C. E., Knox, A. M. and Richard, L. (1998) Calculation of the standard molal thermodynamic properties of crystalline, liquid, and gas organic molecules at high temperatures and pressures. \emph{Geochim. Cosmochim. Acta} \bold{62}, 985--1081. \url{https://doi.org/10.1016/S0016-7037(97)00219-6} Modified: pkg/CHNOSZ/man/thermo.Rd =================================================================== --- pkg/CHNOSZ/man/thermo.Rd 2019-02-19 11:12:12 UTC (rev 399) +++ pkg/CHNOSZ/man/thermo.Rd 2019-02-19 22:57:50 UTC (rev 400) @@ -83,19 +83,21 @@ Note the following database conventions: \itemize{ \item The combination of \code{name} and \code{state} defines a species in \code{thermo$obigt}. A species can not be duplicated (this is checked when running \code{reset()}). - \item English names of gases are used only for the gas state. The dissolved species is named with the chemical formula. Therefore, \code{info("oxygen")} refers to the gas, and \code{info("O2")} refers to the aqueous species. + \item English names of inorganic gases are used only for the gas state. The dissolved species is named with the chemical formula. Therefore, \code{info("oxygen")} refers to the gas, and \code{info("O2")} refers to the aqueous species. + \item Properties of most aqueous species (\code{state} = \samp{aq}) are calculated using the revised Helgeson-Kirkham-Flowers (HKF) model (see \code{\link{hkf}}). + \item Properties of aqueous species with an NA value of \code{Z} (the final column of thermo$obigt) are calculated using the Akinfiev-Diamond model (see \code{\link{AkDi}}). + \item Properties of most non-aqueous species (liquids, gases, and minerals) are calculated using a heat capacity polynomial expression with up to six terms (see \code{\link{cgl}}). + \item Properties of minerals with NA values of all heat capacity parameters are calculated using the Berman model (see \code{\link{berman}}). } \samp{OrganoBioGeoTherm} is the name of a GUI program to use SUPCRT in Windows, produced in Harold C. Helgeson's Laboratory of Theoretical Geochemistry and Biogeochemistry at the University of California, Berkeley. - The \acronym{OBIGT} database was originally developed for that program, and has been ported to CHNOSZ, with additional modifications. + The \acronym{OBIGT} database was originally developed for that program, and was the original basis for the database in CHNOSZ. There may be an additional meaning for the acronym: \dQuote{One BIG Table} of thermodynamic data. Each entry is referenced to one or two literature sources listed in \code{thermo$refs}. Use \code{\link{thermo.refs}} to look up the citation information for the references. - \acronym{OBIGT} was initially built from the \acronym{SUPCRT92} (Johnson et al., 1992) and \acronym{slop98.dat} data files (Shock et al., 1998), and the references in those files are included here. - Some data in \acronym{slop98.dat} were corrected or modified as noted in that file; these modifications are indicated in OBIGT by having \samp{SLOP98} as one of the sources of data. - Other additions or modifications used in CHNOSZ are indicated by having \samp{CHNOSZ} as one of the sources of data. See the vignette \emph{Thermodynamic data in CHNOSZ} for a complete description of the sources of data. + The original \acronym{OBIGT} database was influenced by the \acronym{SUPCRT92} (Johnson et al., 1992) and \acronym{slop98.dat} data files (Shock et al., 1998), and the references in those files are included here. In order to represent thermodynamic data for minerals with phase transitions, the higher-temperature phases of these minerals are represented as phase species that have states denoted by \samp{cr2}, \samp{cr3}, etc. The standard molar thermodynamic properties at 25 \degC and 1 bar (\eqn{T_r}{Pr} and \eqn{P_r}{Pr}) of the \samp{cr2} phase species of minerals were generated by first calculating those of the \samp{cr} (lowest-T) phase species at the transition temperature (\eqn{T_{tr}}{Ttr}) and 1 bar then taking account of the volume and entropy of transition (the latter can be retrieved by combining the former with the Clausius-Clapeyron equation and values of \eqn{(dP/dT)} of transitions taken from the \acronym{SUPCRT92} data file) to calculate the standard molar entropy of the \samp{cr2} phase species at \eqn{T_{tr}}{Ttr}, and taking account of the enthalpy of transition (\eqn{{\Delta}H^{\circ}}{DeltaH0}, taken from the \acronym{SUPCRT92} data file) to calculate the standard molar enthalpy of the \samp{cr2} phase species at \eqn{T_{tr}}{Ttr}. @@ -124,9 +126,8 @@ } -The meanings of the remaining columns depend on the physical state of a particular species. -If it is aqueous, the values in these columns represent parameters in the revised HKF equations of state (see \code{\link{hkf}}), otherwise they denote parameters in a general equations for crystalline, gas and liquid species (see \code{\link{cgl}}). -The names of these columns are compounded from those of the parameters in each of the equations of state (for example, column 13 is named \code{a1.a}). +The meanings of the remaining columns depend on the model used for a particular species (see database conventions above). +The names of these columns are compounded from those of the parameters in the HKF equations of state and general heat capacity polynomial; for example, column 13 is named \code{a1.a}. Scaling of the values by orders of magnitude is adopted for some of the parameters, following common usage in the literature. Columns 13-20 for aqueous species (parameters in the revised HKF equations of state): @@ -156,6 +157,19 @@ \tab \tab temperature limit of validity of extrapolation (K) } +Columns 13-20 for aqueous species using the Akinfiev-Diamond model. Note that the \code{c} column is used to store the \eqn{\xi}{xi} parameter, and that \code{Z} must be NA to activate the code for this model. + + \tabular{lll}{ + \code{a} \tab numeric \tab \eqn{a} \cr + \code{b} \tab numeric \tab \eqn{b} \cr + \code{c} \tab numeric \tab \eqn{\xi}{xi} \cr + \code{d} \tab numeric \tab \eqn{XX1} NA \cr + \code{e} \tab numeric \tab \eqn{XX2} NA \cr + \code{f} \tab numeric \tab \eqn{XX3} NA \cr + \code{lambda} \tab numeric \tab \eqn{XX4} NA \cr + \code{Z} \tab numeric \tab \eqn{Z} NA \cr + } + \item \code{thermo$refs} Dataframe of references to sources of thermodynamic data. \tabular{lll}{ Modified: pkg/CHNOSZ/tests/testthat/test-eos.R =================================================================== --- pkg/CHNOSZ/tests/testthat/test-eos.R 2019-02-19 11:12:12 UTC (rev 399) +++ pkg/CHNOSZ/tests/testthat/test-eos.R 2019-02-19 22:57:50 UTC (rev 400) @@ -78,6 +78,30 @@ expect_equal(gfun.4000$dgdP * 1e6, dgdP.4000.ref, tolerance=1e-3) }) +test_that("AkDi produces expected results", { + # 20190220 + # add an aqueous species conforming to the AkDi model: it has NA for Z + iCO2 <- mod.obigt("CO2", a=-8.8321, b=11.2684, c=-0.0850, z=NA) + # do the properties we calculate match previously calculated values? + P <- "Psat" + T <- seq(50, 350, 100) + # J mol-1 + G_ref <- c(-389122.3, -405138.4, -425410.7, -450573.2) + G_calc <- subcrt(iCO2, T=T, P=P)$out[[1]]$G + # convert to J mol-1 + G_calc <- convert(G_calc, "J", T=convert(T, "K")) + expect_equal(round(G_calc, 1), G_ref) + + P <- 500 + T <- seq(200, 1000, 200) + G_ref <- c(-412767.4, -459654.1, -515231.6, -565736.3, -617927.9) + G_calc <- subcrt(iCO2, T=T, P=P)$out[[1]]$G + G_calc <- convert(G_calc, "J", T=convert(T, "K")) + expect_equal(round(G_calc, 1), G_ref) + + reset() +}) + # reference # Shock, E. L., Oelkers, E. H., Johnson, J. W., Sverjensky, D. A. and Helgeson, H. C. (1992) Modified: pkg/CHNOSZ/tests/testthat/test-info.R =================================================================== --- pkg/CHNOSZ/tests/testthat/test-info.R 2019-02-19 11:12:12 UTC (rev 399) +++ pkg/CHNOSZ/tests/testthat/test-info.R 2019-02-19 22:57:50 UTC (rev 400) @@ -33,3 +33,12 @@ expect_equal(thermo()$obigt$state[i2], c("cr", "aq")) expect_equal(info(i2)[1, ], info(i2[1]), check.attributes=FALSE) }) + +test_that("info() gives correct column names for species using the AkDi model", { + # add an aqueous species conforming to the AkDi model: it has NA for Z + iCO2 <- mod.obigt("CO2", a = -8.8321, b = 11.2684, c = -0.0850, z = NA) + params <- info(iCO2) + expect_equal(params$a, -8.8321) + expect_equal(params$b, 11.2684) + expect_equal(params$xi, -0.0850) +}) Modified: pkg/CHNOSZ/tests/testthat/test-thermo.R =================================================================== --- pkg/CHNOSZ/tests/testthat/test-thermo.R 2019-02-19 11:12:12 UTC (rev 399) +++ pkg/CHNOSZ/tests/testthat/test-thermo.R 2019-02-19 22:57:50 UTC (rev 400) @@ -30,6 +30,8 @@ "please supply a valid chemical formula") # the default state is aq expect_message(itest <- mod.obigt("test", formula="Z0", date=today()), "added test\\(aq\\)") + # set the charge so following test use hkf() rather than AkDi() + mod.obigt("test", z = 0) # we should get NA values of G for a species with NA properties expect_true(all(is.na(subcrt(itest)$out[[1]]$G))) # a single value of G comes through to subcrt From noreply at r-forge.r-project.org Wed Feb 20 05:29:45 2019 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Wed, 20 Feb 2019 05:29:45 +0100 (CET) Subject: [CHNOSZ-commits] r401 - in pkg/CHNOSZ: . R demo inst inst/extdata/OBIGT tests/testthat Message-ID: <20190220042946.07B1018CB15@r-forge.r-project.org> Author: jedick Date: 2019-02-20 05:29:44 +0100 (Wed, 20 Feb 2019) New Revision: 401 Added: pkg/CHNOSZ/inst/extdata/OBIGT/AkDi.csv Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/R/info.R pkg/CHNOSZ/R/util.data.R pkg/CHNOSZ/demo/sources.R pkg/CHNOSZ/inst/NEWS pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_gas.csv.xz pkg/CHNOSZ/inst/extdata/OBIGT/organic_aq.csv.xz pkg/CHNOSZ/inst/extdata/OBIGT/refs.csv pkg/CHNOSZ/tests/testthat/test-eos.R Log: add Akinfiev-Diamond model parameters to OBIGT/AkDi.csv Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-19 22:57:50 UTC (rev 400) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-20 04:29:44 UTC (rev 401) @@ -1,6 +1,6 @@ Date: 2019-02-20 Package: CHNOSZ -Version: 1.2.0-8 +Version: 1.2.0-9 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/R/info.R =================================================================== --- pkg/CHNOSZ/R/info.R 2019-02-19 22:57:50 UTC (rev 400) +++ pkg/CHNOSZ/R/info.R 2019-02-20 04:29:44 UTC (rev 401) @@ -249,7 +249,7 @@ } # if we got here there were no approximate matches # 20190127 look for the species in optional data files - for(opt in c("SLOP98", "SUPCRT92", "OldAA")) { + for(opt in c("SLOP98", "SUPCRT92", "OldAA", "AkDi")) { optdat <- read.csv(system.file(paste0("extdata/OBIGT/", opt, ".csv"), package="CHNOSZ"), as.is=TRUE) if(species %in% optdat$name) { message('info.approx: ', species, ' is in an optional database; use add.obigt("', opt, '", "', species, '") to load it') Modified: pkg/CHNOSZ/R/util.data.R =================================================================== --- pkg/CHNOSZ/R/util.data.R 2019-02-19 22:57:50 UTC (rev 400) +++ pkg/CHNOSZ/R/util.data.R 2019-02-20 04:29:44 UTC (rev 401) @@ -265,6 +265,7 @@ else if(what=="SUPCRT92") tdata <- read.csv(system.file("extdata/OBIGT/SUPCRT92.csv", package="CHNOSZ"), as.is=TRUE) else if(what=="OldAA") tdata <- read.csv(system.file("extdata/OBIGT/OldAA.csv", package="CHNOSZ"), as.is=TRUE) else if(what=="AS04") tdata <- read.csv(system.file("extdata/OBIGT/AS04.csv", package="CHNOSZ"), as.is=TRUE) + else if(what=="AkDi") tdata <- read.csv(system.file("extdata/OBIGT/AkDi.csv", package="CHNOSZ"), as.is=TRUE) ntot <- nrow(tdata) # where to keep the results DCp <- DV <- DG <- rep(NA,ntot) @@ -401,7 +402,7 @@ isAkDi <- is.na(obigt$z.T) # remove scaling factors for the HKF species, but not for the AkDi species obigt[!isAkDi, 13:20] <- t(t(obigt[!isAkDi, 13:20]) * 10^c(-1,2,0,4,0,4,5,0)) - # for AkDi specie, set NA values in remaining columns (for display only) + # for AkDi species, set NA values in remaining columns (for display only) obigt[isAkDi, 16:19] <- NA # if all of the species are AkDi, change the variable names if(all(isAkDi)) colnames(obigt)[13:20] <- c('a','b','xi','XX1','XX2','XX3','XX4','Z') Modified: pkg/CHNOSZ/demo/sources.R =================================================================== --- pkg/CHNOSZ/demo/sources.R 2019-02-19 22:57:50 UTC (rev 400) +++ pkg/CHNOSZ/demo/sources.R 2019-02-20 04:29:44 UTC (rev 401) @@ -22,8 +22,11 @@ tdata <- read.csv(system.file("extdata/OBIGT/AS04.csv", package="CHNOSZ"), as.is=TRUE) os9 <- gsub("\ .*", "", tdata$ref1) os10 <- gsub("\ .*", "", tdata$ref2) +tdata <- read.csv(system.file("extdata/OBIGT/AkDi.csv", package="CHNOSZ"), as.is=TRUE) +os11 <- gsub("\ .*", "", tdata$ref1) +os12 <- gsub("\ .*", "", tdata$ref2) # all of the thermodynamic data sources - some of them might be NA -obigt.source <- unique(c(ps1, ps2, os1, os2, os3, os4, os5, os6, os7, os8, os9, os10)) +obigt.source <- unique(c(ps1, ps2, os1, os2, os3, os4, os5, os6, os7, os8, os9, os10, os11, os12)) obigt.source <- obigt.source[!is.na(obigt.source)] # these all produce character(0) if the sources are all accounted for print("missing these sources for thermodynamic properties:") Modified: pkg/CHNOSZ/inst/NEWS =================================================================== --- pkg/CHNOSZ/inst/NEWS 2019-02-19 22:57:50 UTC (rev 400) +++ pkg/CHNOSZ/inst/NEWS 2019-02-20 04:29:44 UTC (rev 401) @@ -1,4 +1,4 @@ -CHANGES IN CHNOSZ 1.2.0-8 (2019-02-20) +CHANGES IN CHNOSZ 1.2.0-9 (2019-02-20) -------------------------------------- CRAN COMPLIANCE @@ -32,6 +32,9 @@ - Move H2AsO3- from OBIGT/SLOP98.csv to OBIGT/SUPCRT92.csv. +- Add OBIGT/AkDi.csv as optional data file for species using + Akinfiev-Diamond model. + DOCUMENTATION - In demo/NaCl.R, indicate region not considered by Shock et al., 1992 Added: pkg/CHNOSZ/inst/extdata/OBIGT/AkDi.csv =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/AkDi.csv (rev 0) +++ pkg/CHNOSZ/inst/extdata/OBIGT/AkDi.csv 2019-02-20 04:29:44 UTC (rev 401) @@ -0,0 +1,11 @@ +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 +Ar,NA,Ar,aq,AD03,NA,20.Feb.19,NA,NA,NA,NA,NA,-8.5139,11.921,0.0733,NA,NA,NA,NA,NA +H2S,NA,H2S,aq,AD03,NA,20.Feb.19,NA,NA,NA,NA,NA,-11.2303,12.6104,-0.2102,NA,NA,NA,NA,NA +O2,NA,O2,aq,AD03,NA,20.Feb.19,NA,NA,NA,NA,NA,-9.754,12.9411,0.026,NA,NA,NA,NA,NA +N2,NA,N2,aq,AD03,NA,20.Feb.19,NA,NA,NA,NA,NA,-11.538,14.6278,-0.032,NA,NA,NA,NA,NA +NH3,NA,NH3,aq,AD03,NA,20.Feb.19,NA,NA,NA,NA,NA,-4.7245,4.9782,-0.0955,NA,NA,NA,NA,NA +H2,NA,H2,aq,AD03,NA,20.Feb.19,NA,NA,NA,NA,NA,-8.4596,10.8301,0.309,NA,NA,NA,NA,NA +methane,NA,CH4,aq,AD03,NA,20.Feb.19,NA,NA,NA,NA,NA,-11.8462,14.8615,-0.1131,NA,NA,NA,NA,NA +CO2,NA,CO2,aq,AD03,NA,20.Feb.19,NA,NA,NA,NA,NA,-8.8321,11.2684,-0.085,NA,NA,NA,NA,NA +benzene,NA,C6H6,aq,AD03,NA,20.Feb.19,NA,NA,NA,NA,NA,-21.0084,22.934,-1.101,NA,NA,NA,NA,NA +HCl,NA,HCl,aq,AD03,NA,20.Feb.19,NA,NA,NA,NA,NA,11.642,-7.4244,-0.28,NA,NA,NA,NA,NA Modified: pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_gas.csv.xz =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_gas.csv.xz 2019-02-19 22:57:50 UTC (rev 400) +++ pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_gas.csv.xz 2019-02-20 04:29:44 UTC (rev 401) @@ -1,5 +1,5 @@ -?7zXZ???F!t/???.}]7I??b???9??????TB;q?"?q???cL;?"?????!???{??Q,?0?uY?????d?????? ?f???????Y?? f?bQ????*??vtP?t????????? ?7?A+??a0"c1? ???W?I???????uw(????k??n????f;? +?????}z? +y???`?Ix?}?i?????z?;v??}??X???q?QNI_y??S???????qLH?0??y ???? +Y?-?W_?4&}?_WV?]eF<? ??%H??E???[(3?????u??D??[?C +?D????7 r|\? ?Q?"???ku???(?&}????7????w???%U????E?1?[??TQ?}_J????$????}q??Dc`o?*&:fD??`7??=g?????VR??Hd?'??&???/??H_??????$?(pf??(??????????????z??g????gK??? m?;?e_ {&ge??y!?Lq??Kt.???dz??(Yh??SGq??? ???PU???M??r?~?????????(????g?YZ \ No newline at end of file Modified: pkg/CHNOSZ/inst/extdata/OBIGT/organic_aq.csv.xz =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/organic_aq.csv.xz 2019-02-19 22:57:50 UTC (rev 400) +++ pkg/CHNOSZ/inst/extdata/OBIGT/organic_aq.csv.xz 2019-02-20 04:29:44 UTC (rev 401) @@ -1,4 +1,4 @@ -?7zXZ???F!t/???j?h?]7I??b???9??????TB;q?"?q???cL;?"??? x!#???0N???????? ?V?q??P?@o?*?~ ??!?~?&??????x?{;??Q(T?{????~W??U?@?? r?&?3??f1(\F?^??=W?x??]?w?g??O?|X?G???fO?tO A????Y??|?N??tg!3|?? -<!N??$??????E7?^?_??????h? -SqR?z?\m??a?E??@L? -J???2?K?A??m{??]#?_??'uc@?!?N?'?^E#1'j???0(6^???s??+f?? ??vL????5??H??e???????`??l?a??)!)?b?????l??PD?z2???K?3?Sf/??????b??'?v?G????- ?????nvtS/J?P?+4a)(?l? ??3z[?????,?*??%bF?"?5W?????W?????%??J~~'???sH -????I??x??U <-j_M>?+?m??????y???'?c??Um?VV?????l -l???9??~??T??$??(e&???tJ??b?b???* ???m???????+&?k??v\W??84?yCd?H&??r? -???-;????Z?5??(???N????oA????5????rK r???A?=????o??a\??7???q? ???1????????????J??????v??J??# 2~??K?_TaYK???+??nf}?? -??vJ?#Z??>d?A???? |_?j?>w?@?????E?Q[?? Rm????????????L??d{???X[?t?????~????? 9.????[??]f????! -??;?T???????D????? ?^?? ? n$????E8?B"?????z??b?N?????????9>??T2?YYHB??? lU??????????? ??g?YZ \ No newline at end of file +???%_?lr????????P{:IYnc8???:K?????f?? ????T?.??yR*??O?????? M??:'4]????%????, at e?*Vj?sL{??}?????Z `??H?!6????? jR? ?L??!? jm]$?@W[?s???i?K???2?GK?!?@???6/K??r~?bSA?_mFhq?+{????@??m?G?R?????G??O?']? +_????.?????L?X?3z72>?b? +??u+?2TUL????qkK?????? )yU9l*_?DV.7u??????'?2"???_X?P?????? ??H?????&"??g?YZ \ No newline at end of file Modified: pkg/CHNOSZ/inst/extdata/OBIGT/refs.csv =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/refs.csv 2019-02-19 22:57:50 UTC (rev 400) +++ pkg/CHNOSZ/inst/extdata/OBIGT/refs.csv 2019-02-20 04:29:44 UTC (rev 401) @@ -57,10 +57,11 @@ PH95,"V. A. Pokrovskii and H. C. Helgeson",1995,"Am. J. Sci. 295, 1255-1342","aluminum species",https://doi.org/10.2475/ajs.295.10.1255 PK95,"V. B. Parker and I. L. Khodakovskii",1995,"J. Phys. Chem. Ref. Data 24, 1699-1745",melanterite,https://doi.org/10.1063/1.555964 RH95,"R. A. Robie and B. S. Hemingway",1995,"U. S. Geological Survey Bull. 2131","gypsum GHS",http://pubs.er.usgs.gov/publication/b2131 +RH95.1,"R. A. Robie and B. S. Hemingway",1995,"U. S. Geological Survey Bull. 2131","hydrogen chloride (HCl gas)",http://pubs.er.usgs.gov/publication/b2131 SK95,"E. L. Shock and C. M. Koretsky",1995,"Geochim. Cosmochim. Acta 59, 1497-1532","metal-organic acid complexes",https://doi.org/10.1016/0016-7037(95)00058-8 SK95.1,"E. L. Shock and C. M. Koretsky",1995,"Geochim. Cosmochim. Acta 59, 1497-1532","alanate, glycinate and their complexes with metals. Values are taken from slop98.dat, which notes corrected values for some species.",https://doi.org/10.1016/0016-7037(95)00058-8 Sho95,"E. L. Shock",1995,"Am. J. Sci. 295, 496-580","carboxylic acids",https://doi.org/10.2475/ajs.295.5.496 -DPS+96,"I. Diakonov, G. Pokrovski et al.",1996,"Geochim. Cosmochim. Acta 60, 197-211",NaAl(OH)4,http://dx.doi.org/10.1016/0016-7037(95)00403-3 +DPS+96,"I. Diakonov, G. Pokrovski et al.",1996,"Geochim. Cosmochim. Acta 60, 197-211",NaAl(OH)4,https://doi.org/10.1016/0016-7037(95)00403-3 AH97b,"J. P. Amend and H. C. Helgeson",1997,"J. Chem. Soc., Faraday Trans. 93, 1927-1941","amino acids GHS",https://doi.org/10.1039/A608126F AH97b.1,"J. P. Amend and H. C. Helgeson",1997,"J. Chem. Soc., Faraday Trans. 93, 1927-1941","alanate and glycinate GHS",https://doi.org/10.1039/A608126F AH97b.2,"J. P. Amend and H. C. Helgeson",1997,"J. Chem. Soc., Faraday Trans. 93, 1927-1941","glycine, glycinium, and methionine GHS",https://doi.org/10.1039/A608126F @@ -106,10 +107,11 @@ PS01,"A. V. Plyasunov and E. L. Shock",2001,"Geochim. Cosmochim. Acta 65, 3879-3900","aqueous nonelectrolytes",https://doi.org/10.1016/S0016-7037(01)00678-0 PS01.1,"A. V. Plyasunov and E. L. Shock",2001,"Geochim. Cosmochim. Acta 65, 3879-3900","acetic acid, propanoic acid, and methane",https://doi.org/10.1016/S0016-7037(01)00678-0 Ric01,"L. Richard",2001,"Geochim. Cosmochim. Acta 65, 3827-3877","organic sulfur compounds",https://doi.org/10.1016/S0016-7037(01)00761-X -Ste01,"A. Stefansson",2001,"Chem. Geol. 172, 225-250","aqueous H4SiO4",http://dx.doi.org/10.1016/S0009-2541(00)00263-1 +Ste01,"A. Stefansson",2001,"Chem. Geol. 172, 225-250","aqueous H4SiO4",https://doi.org/10.1016/S0009-2541(00)00263-1 SSW01,"M. D. Schulte, E. L. Shock and R. H. Wood",2001,"Geochim. Cosmochim. Acta 65, 3919-3930","AsH3, CF4, CH3F, Cl2, ClO2, N2O, NF3, NO, PH3, and SF6",https://doi.org/10.1016/S0016-7037(01)00717-7 -TS01,"B. Tagirov and J. Schott",2001,"Geochim. Cosmochim. Acta 65, 3965-3992","aqueous Al species",http://dx.doi.org/10.1016/S0016-7037(01)00705-0 -GKL02,"R. N. Goldberg et al.",2002,"J. Phys. Chem. Ref. Data 31, 231-370","glycine, diglycine, and triglycine (+1 and -1 ions) GHS",http://dx.doi.org/10.1063/1.1416902 +TS01,"B. Tagirov and J. Schott",2001,"Geochim. Cosmochim. Acta 65, 3965-3992","aqueous Al species",https://doi.org/10.1016/S0016-7037(01)00705-0 +GKL02,"R. N. Goldberg et al.",2002,"J. Phys. Chem. Ref. Data 31, 231-370","glycine, diglycine, and triglycine (+1 and -1 ions) GHS",https://doi.org/10.1063/1.1416902 +AD03,"N. N. Akinfiev and L. W. Diamond",2003,"Geochim. Cosmochim. Acta 67, 613-629","aqueous nonelectrolytes",https://doi.org/10.1016/S0016-7037(02)01141-9 MGN03,"J. Majzlan, K.-D. Grevel and A. Navrotsky",2003,"Am. Mineral. 88, 855-859","goethite, lepidocrocite, and maghemite GHS",https://doi.org/10.2138/am-2003-5-614 NA03,"D. K. Nordstrom and D. G. Archer",2003,"Arsenic thermodynamic data and environmental geochemistry. In Arsenic in Groundwater, eds. Welch and Stollenwerk, Kluwer","As oxide and sulfide minerals", NA03.1,"D. K. Nordstrom and D. G. Archer",2003,"Arsenic thermodynamic data and environmental geochemistry. In Arsenic in Groundwater, eds. Welch and Stollenwerk, Kluwer","aqueous As oxides and sulfides", Modified: pkg/CHNOSZ/tests/testthat/test-eos.R =================================================================== --- pkg/CHNOSZ/tests/testthat/test-eos.R 2019-02-19 22:57:50 UTC (rev 400) +++ pkg/CHNOSZ/tests/testthat/test-eos.R 2019-02-20 04:29:44 UTC (rev 401) @@ -80,7 +80,7 @@ test_that("AkDi produces expected results", { # 20190220 - # add an aqueous species conforming to the AkDi model: it has NA for Z + # modify aqueous CO2 to use the AkDi model: it has NA for Z iCO2 <- mod.obigt("CO2", a=-8.8321, b=11.2684, c=-0.0850, z=NA) # do the properties we calculate match previously calculated values? P <- "Psat" @@ -99,7 +99,19 @@ G_calc <- convert(G_calc, "J", T=convert(T, "K")) expect_equal(round(G_calc, 1), G_ref) + # compare Gibbs energies at 25 degrees calculatwith with AkDi model to database values + iAkDi <- add.obigt("AkDi") + # this would produce an error if any of the corresponding gases were unavailable + sAkDi <- subcrt(iAkDi, T = 25) + GAkDi <- do.call(rbind, sAkDi$out)$G + # now get the parameters from default OBIGT reset() + GOBIGT <- info(iAkDi)$G + # calculate the differences and add names + Gdiff <- GAkDi - GOBIGT + names(Gdiff) <- info(iAkDi)$name + # the differences are not that big, except for HCl(aq) + expect_lt(max(abs(Gdiff)), 300) }) # reference From noreply at r-forge.r-project.org Wed Feb 20 06:34:32 2019 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Wed, 20 Feb 2019 06:34:32 +0100 (CET) Subject: [CHNOSZ-commits] r402 - in pkg/CHNOSZ: . demo inst inst/extdata/OBIGT inst/extdata/cpetc man Message-ID: <20190220053432.1CC0118C0D4@r-forge.r-project.org> Author: jedick Date: 2019-02-20 06:34:30 +0100 (Wed, 20 Feb 2019) New Revision: 402 Added: pkg/CHNOSZ/demo/AkDi.R pkg/CHNOSZ/inst/extdata/cpetc/AD03_Fig1a.csv pkg/CHNOSZ/inst/extdata/cpetc/AD03_Fig1b.csv pkg/CHNOSZ/inst/extdata/cpetc/AD03_Fig1c.csv pkg/CHNOSZ/inst/extdata/cpetc/AD03_Fig1d.csv Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/demo/00Index pkg/CHNOSZ/inst/NEWS pkg/CHNOSZ/inst/extdata/OBIGT/AkDi.csv pkg/CHNOSZ/man/examples.Rd pkg/CHNOSZ/man/extdata.Rd Log: add demo/AkDi.R: Henry's constant of dissolved gases Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-20 04:29:44 UTC (rev 401) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-20 05:34:30 UTC (rev 402) @@ -1,6 +1,6 @@ Date: 2019-02-20 Package: CHNOSZ -Version: 1.2.0-9 +Version: 1.2.0-10 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/demo/00Index =================================================================== --- pkg/CHNOSZ/demo/00Index 2019-02-20 04:29:44 UTC (rev 401) +++ pkg/CHNOSZ/demo/00Index 2019-02-20 05:34:30 UTC (rev 402) @@ -27,3 +27,4 @@ go-IU Diagrams using thermodynamic data in the SUPCRTBL compilation carboxylase Rank abundance distribution for RuBisCO and acetyl-CoA carboxylase bison Average oxidation state of carbon in proteins for phyla at Bison Pool +AkDi Henry's constant of dissolved gases Added: pkg/CHNOSZ/demo/AkDi.R =================================================================== --- pkg/CHNOSZ/demo/AkDi.R (rev 0) +++ pkg/CHNOSZ/demo/AkDi.R 2019-02-20 05:34:30 UTC (rev 402) @@ -0,0 +1,80 @@ +# CHNOSZ/demo/AkDi.R +# calculations using the Akinfiev-Diamond model 20190220 +# after Fig. 1 of Akinfiev and Diamond, 2003 + +# function to plot natural logarithm of Henry's constant +lines.KH <- function(name = "CO2", T = 1:373, P = "Psat", HKF = FALSE, altH2S = FALSE) { + # use AkDi or HKF model? + if(!HKF) add.obigt("AkDi") + # use alternative parameters for H2S? (AD03 Table 1) + if(altH2S) mod.obigt("H2S", state="aq", a=-11.2303, b=12.6104, c=-0.2102) + # get properties of aq - gas reaction + sres <- subcrt(c(name, name), c("aq", "gas"), c(-1, 1), T = T, P = P) + # calculate natural logarithm of Henry's constant in mole-fraction units + ln_KH <- log(1000/18.0153) + log(10) * sres$out$logK + # plot with units of reciprocal temperature (1000/K) + TK <- convert(T, "K") + lty <- 1 + if(altH2S) lty <- 2 + if(HKF) lty <- 3 + if(HKF) col <- "red" else col <- "black" + lines(1000/TK, ln_KH, lty = lty, col = col) + reset() +} + +# set up plot +par(mfrow=c(2, 2)) +ylab <- quote(ln~italic(K[H])) +xlab <- quote(1000 / list(italic(T), K)) + +# CO2 (Fig. 1a of AD03) +plot(0, 0, xlim=c(1, 4), ylim=c(4, 10), xlab=xlab, ylab=ylab) +lines.KH("CO2", 1:373, "Psat") +lines.KH("CO2", seq(100, 650, 10), 500) +lines.KH("CO2", 1:373, "Psat", HKF = TRUE) +lines.KH("CO2", seq(100, 650, 10), 500, HKF = TRUE) +dat <- read.csv(system.file("extdata/cpetc/AD03_Fig1a.csv", package="CHNOSZ")) +points(dat$x, dat$y, pch=dat$pch) +text(3.5, 7.8, quote(italic(P)[sat])) +text(3.05, 9.2, "500 bar") +legend("bottom", c("Data (AD03, Fig. 1a)", "AkDi model", "HKF model"), lty=c(0, 1, 3), pch=c(1, NA, NA), col=c(1, 1, 2), bty="n") +title(main=syslab(c("CO2", "H2O"), dash = " - ")) + +# H2 (Fig. 1b of AD03) +plot(0, 0, xlim=c(1, 4), ylim=c(8, 12), xlab=xlab, ylab=ylab) +lines.KH("H2", 1:373, "Psat") +lines.KH("H2", seq(100, 650, 10), 1000) +lines.KH("H2", 1:373, "Psat", HKF = TRUE) +lines.KH("H2", seq(100, 650, 10), 1000, HKF = TRUE) +text(3.4, 11.4, quote(italic(P)[sat])) +text(1.5, 11, "1000 bar") +dat <- read.csv(system.file("extdata/cpetc/AD03_Fig1b.csv", package="CHNOSZ")) +points(dat$x, dat$y, pch=dat$pch) +legend("bottomright", c("Data (AD03, Fig. 1b)", "AkDi model", "HKF model"), lty=c(0, 1, 3), pch=c(1, NA, NA), col=c(1, 1, 2), bty="n") +title(main=syslab(c("H2", "H2O"), dash = " - ")) + +# H2S (Fig. 1c of AD03) +plot(0, 0, xlim=c(1, 4), ylim=c(4, 9), xlab=xlab, ylab=ylab) +lines.KH("H2S", 1:373, "Psat") +lines.KH("H2S", seq(100, 650, 10), 1000) +lines.KH("H2S", 1:373, "Psat", altH2S = TRUE) +lines.KH("H2S", seq(100, 650, 10), 1000, altH2S = TRUE) +lines.KH("H2S", 1:373, "Psat", HKF = TRUE) +lines.KH("H2S", seq(100, 650, 10), 1000, HKF = TRUE) +dat <- read.csv(system.file("extdata/cpetc/AD03_Fig1c.csv", package="CHNOSZ")) +points(dat$x, dat$y, pch=dat$pch) +text(3.4, 6.9, quote(italic(P)[sat])) +text(3.1, 8.6, "1000 bar") +legend("bottom", c("Data (AD03, Fig. 1c)", "AkDi model", "AkDi model (alt. H2S)", "HKF model"), lty=c(0, 1, 2, 3), pch=c(1, NA, NA, NA), col=c(1, 1, 1, 2), bty="n") +title(main=syslab(c("H2S", "H2O"), dash = " - ")) + +# CH4 (Fig. 1d of AD03) +plot(0, 0, xlim=c(1.5, 4), ylim=c(8, 12), xlab=xlab, ylab=ylab) +lines.KH("CH4", 1:350, "Psat") +lines.KH("CH4", 1:350, "Psat", HKF = TRUE) +dat <- read.csv(system.file("extdata/cpetc/AD03_Fig1d.csv", package="CHNOSZ")) +points(dat$x, dat$y, pch=dat$pch) +text(3.4, 11, quote(italic(P)[sat])) +legend("bottomright", c("Data (AD03, Fig. 1d)", "AkDi model", "HKF model"), lty=c(0, 1, 3), pch=c(1, NA, NA), col=c(1, 1, 2), bty="n") +title(main=syslab(c("CH4", "H2O"), dash = " - ")) + Modified: pkg/CHNOSZ/inst/NEWS =================================================================== --- pkg/CHNOSZ/inst/NEWS 2019-02-20 04:29:44 UTC (rev 401) +++ pkg/CHNOSZ/inst/NEWS 2019-02-20 05:34:30 UTC (rev 402) @@ -1,5 +1,5 @@ -CHANGES IN CHNOSZ 1.2.0-9 (2019-02-20) --------------------------------------- +CHANGES IN CHNOSZ 1.2.0-10 (2019-02-20) +--------------------------------------- CRAN COMPLIANCE @@ -20,7 +20,7 @@ - Add AkDi() to calculate thermodynamic properties of aqueous nonelectrolytes using the Akinfiev-Diamond model. Thanks to Evgeniy - Bastrakov for guidance and advice. + Bastrakov for guidance. THERMODYNAMIC DATA @@ -42,6 +42,9 @@ revised HKF model, and note presence of resulting discontinuities (see man/examples.Rd). +- Add demo/AkDi.R showing calculations of Henry's constant of dissolved + gases, after Figure 1 of Akinfiev and Diamond, 2003. + OTHER CHANGES - In describe.reaction(), change equals sign to reaction double arrow. Modified: pkg/CHNOSZ/inst/extdata/OBIGT/AkDi.csv =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/AkDi.csv 2019-02-20 04:29:44 UTC (rev 401) +++ pkg/CHNOSZ/inst/extdata/OBIGT/AkDi.csv 2019-02-20 05:34:30 UTC (rev 402) @@ -1,6 +1,6 @@ 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 Ar,NA,Ar,aq,AD03,NA,20.Feb.19,NA,NA,NA,NA,NA,-8.5139,11.921,0.0733,NA,NA,NA,NA,NA -H2S,NA,H2S,aq,AD03,NA,20.Feb.19,NA,NA,NA,NA,NA,-11.2303,12.6104,-0.2102,NA,NA,NA,NA,NA +H2S,NA,H2S,aq,AD03,NA,20.Feb.19,NA,NA,NA,NA,NA,-13.4046,13.8582,-0.2029,NA,NA,NA,NA,NA O2,NA,O2,aq,AD03,NA,20.Feb.19,NA,NA,NA,NA,NA,-9.754,12.9411,0.026,NA,NA,NA,NA,NA N2,NA,N2,aq,AD03,NA,20.Feb.19,NA,NA,NA,NA,NA,-11.538,14.6278,-0.032,NA,NA,NA,NA,NA NH3,NA,NH3,aq,AD03,NA,20.Feb.19,NA,NA,NA,NA,NA,-4.7245,4.9782,-0.0955,NA,NA,NA,NA,NA Added: pkg/CHNOSZ/inst/extdata/cpetc/AD03_Fig1a.csv =================================================================== --- pkg/CHNOSZ/inst/extdata/cpetc/AD03_Fig1a.csv (rev 0) +++ pkg/CHNOSZ/inst/extdata/cpetc/AD03_Fig1a.csv 2019-02-20 05:34:30 UTC (rev 402) @@ -0,0 +1,69 @@ +x,y,pch +1.67,7.577,24 +1.742,7.861,24 +1.909,8.341,24 +2.11,8.657,24 +2.361,8.744,24 +2.678,8.541,24 +1.567,7.348,1 +1.606,7.608,1 +1.642,7.789,1 +1.687,7.931,1 +1.726,8.057,1 +1.773,8.176,1 +1.823,8.27,1 +1.87,8.373,1 +1.929,8.452,1 +1.987,8.523,1 +2.043,8.586,1 +2.11,8.649,1 +2.177,8.681,1 +2.255,8.72,1 +2.333,8.729,1 +2.416,8.713,1 +2.508,8.698,1 +2.609,8.643,1 +2.712,8.549,1 +2.837,8.407,1 +2.871,8.337,1 +2.913,8.274,1 +2.955,8.203,1 +2.996,8.124,1 +3.044,8.054,1 +3.097,7.959,1 +3.139,7.873,1 +3.194,7.763,1 +3.242,7.653,1 +3.295,7.535,1 +3.351,7.401,1 +3.409,7.26,1 +3.465,7.126,1 +3.527,6.953,1 +3.588,6.772,1 +3.658,6.575,1 +2.291,8.673,5 +2.352,8.674,5 +2.411,8.689,5 +2.467,8.666,5 +2.528,8.643,5 +2.598,8.596,5 +2.667,8.556,5 +2.737,8.478,5 +2.818,8.376,5 +2.896,8.282,5 +2.985,8.132,5 +3.075,7.967,5 +3.169,7.771,5 +3.278,7.574,5 +3.387,7.307,5 +3.504,7.016,5 +3.63,6.693,5 +1.147,6.449,18 +1.219,6.505,18 +1.3,6.702,18 +1.386,7.237,18 +1.483,7.915,18 +1.544,8.506,18 +1.562,7.136,0 +1.584,7.372,0 +1.606,7.498,0 Added: pkg/CHNOSZ/inst/extdata/cpetc/AD03_Fig1b.csv =================================================================== --- pkg/CHNOSZ/inst/extdata/cpetc/AD03_Fig1b.csv (rev 0) +++ pkg/CHNOSZ/inst/extdata/cpetc/AD03_Fig1b.csv 2019-02-20 05:34:30 UTC (rev 402) @@ -0,0 +1,43 @@ +x,y,pch +1.313,8.754,2 +1.313,8.77,2 +1.371,9.011,2 +1.448,9.362,2 +1.591,9.713,2 +1.671,9.912,2 +1.759,10.153,2 +1.575,8.219,5 +1.623,8.806,5 +1.686,9.231,5 +1.714,9.314,5 +1.771,9.451,5 +1.838,9.733,5 +1.84,9.812,5 +1.904,9.995,5 +2.013,10.242,5 +2.107,10.467,5 +2.129,10.603,5 +2.175,10.582,5 +2.258,10.76,5 +2.335,10.86,5 +2.387,10.938,5 +2.406,10.938,5 +2.507,11.053,5 +2.554,11.106,5 +2.59,11.074,5 +2.656,11.221,5 +2.771,11.226,5 +2.864,11.236,5 +2.858,11.267,5 +2.949,11.267,5 +3.033,11.251,5 +3.138,11.262,5 +2.913,11.21,1 +3.006,11.22,1 +3.091,11.225,1 +3.192,11.204,1 +3.299,11.177,1 +3.359,11.141,1 +3.417,11.114,1 +3.537,11.046,1 +3.666,10.925,1 Added: pkg/CHNOSZ/inst/extdata/cpetc/AD03_Fig1c.csv =================================================================== --- pkg/CHNOSZ/inst/extdata/cpetc/AD03_Fig1c.csv (rev 0) +++ pkg/CHNOSZ/inst/extdata/cpetc/AD03_Fig1c.csv 2019-02-20 05:34:30 UTC (rev 402) @@ -0,0 +1,89 @@ +x,y,pch +1.282,7.566,25 +1.304,7.614,25 +1.393,7.906,25 +1.476,8.175,25 +1.479,8.112,25 +1.546,8.184,25 +1.654,8.548,25 +1.651,8.429,25 +1.732,8.627,25 +1.732,8.493,25 +1.599,7.222,0 +1.619,7.294,0 +1.646,7.404,0 +1.682,7.444,0 +1.716,7.492,0 +1.766,7.547,0 +1.785,7.603,0 +1.816,7.619,0 +1.835,7.619,0 +1.863,7.619,0 +1.885,7.619,0 +1.922,7.596,0 +1.961,7.596,0 +1.999,7.605,0 +2.038,7.597,0 +2.072,7.605,0 +2.105,7.606,0 +2.141,7.582,0 +2.166,7.575,0 +2.2,7.567,0 +2.239,7.552,0 +2.28,7.529,0 +2.303,7.466,0 +2.35,7.506,0 +2.392,7.506,0 +2.433,7.483,0 +2.458,7.42,0 +2.517,7.444,0 +2.567,7.421,0 +2.6,7.398,0 +2.634,7.414,0 +2.678,7.382,0 +2.695,7.32,0 +2.742,7.312,0 +2.745,7.241,0 +2.806,7.218,0 +2.851,7.195,0 +2.92,7.14,0 +2.912,7.038,0 +2.995,7.094,0 +3.048,7.023,0 +3.054,6.866,0 +3.101,6.795,0 +3.148,6.717,0 +1.663,7.184,23 +1.744,7.389,23 +1.688,7.018,1 +1.719,6.979,1 +1.752,7.098,1 +1.769,7.169,1 +1.816,7.311,1 +1.863,7.391,1 +1.902,7.493,1 +1.947,7.525,1 +1.988,7.565,1 +2.041,7.574,1 +2.041,7.708,1 +2.091,7.669,1 +2.133,7.638,1 +2.155,7.59,1 +2.272,7.584,1 +2.342,7.576,1 +2.419,7.554,1 +2.408,7.506,1 +2.675,7.312,1 +2.792,7.194,1 +3.001,6.936,1 +3.193,6.607,1 +3.246,6.528,1 +3.371,6.285,1 +3.396,6.199,1 +3.402,6.096,2 +3.301,6.395,2 +3.357,6.301,2 +3.468,6.034,2 +3.527,5.893,2 +3.594,5.728,2 +3.661,5.586,2 Added: pkg/CHNOSZ/inst/extdata/cpetc/AD03_Fig1d.csv =================================================================== --- pkg/CHNOSZ/inst/extdata/cpetc/AD03_Fig1d.csv (rev 0) +++ pkg/CHNOSZ/inst/extdata/cpetc/AD03_Fig1d.csv 2019-02-20 05:34:30 UTC (rev 402) @@ -0,0 +1,30 @@ +x,y,pch +2.253,10.668,2 +2.435,10.867,2 +2.649,11.051,2 +2.907,11.04,2 +3.219,10.76,2 +3.354,10.597,2 +1.931,10.164,5 +2.113,10.569,5 +2.323,10.826,5 +2.576,11.051,5 +2.597,11.062,5 +3.001,11.008,5 +3.363,10.623,5 +1.749,9.539,1 +1.81,9.723,1 +1.876,9.907,1 +1.949,10.091,1 +2.029,10.285,1 +2.113,10.479,1 +2.207,10.663,1 +2.31,10.831,1 +2.419,10.973,1 +2.544,11.083,1 +2.681,11.14,1 +2.834,11.145,1 +3.005,11.066,1 +3.197,10.886,1 +3.413,10.576,1 +3.66,10.102,1 Modified: pkg/CHNOSZ/man/examples.Rd =================================================================== --- pkg/CHNOSZ/man/examples.Rd 2019-02-20 04:29:44 UTC (rev 401) +++ pkg/CHNOSZ/man/examples.Rd 2019-02-20 05:34:30 UTC (rev 402) @@ -59,6 +59,7 @@ \code{go-IU} \tab Diagrams using thermodynamic data in the SUPCRTBL compilation (Zimmer et al., 2016) \cr \code{carboxylase} \tab Rank abundance distribution for RuBisCO and acetyl-CoA carboxylase \cr \code{bison} \tab Average oxidation state of carbon in proteins for phyla at Bison Pool (Dick and Shock, 2013) \cr + \code{AkDi} \tab Henry's constant of dissolved gases (Akinfiev and Diamond, 2003) \cr } For either function, if \code{save.png} is TRUE, the plots are saved in \code{\link{png}} files whose names begin with the names of the help topics or demos. @@ -82,6 +83,8 @@ } \references{ +Akinfiev, N. N. and Diamond, L. W. (2003) Thermodynamic description of aqueous nonelectrolytes at infinite dilution over a wide range of state parameters. \emph{Geochim. Cosmochim. Acta} \bold{67}, 613--629. \url{https://doi.org/10.1016/S0016-7037(02)01141-9} + Akinfiev, N. N. and Zotov, A. V. (2001) Thermodynamic description of chloride, hydrosulfide, and hydroxo complexes of Ag(I), Cu(I), and Au(I) at temperatures of 25-500\degC and pressures of 1-2000 bar. \emph{Geochem. Int.} \bold{39}, 990--1006. \url{http://pleiades.online/cgi-perl/search.pl/?type=abstract&name=geochem&number=10&year=1&page=990} Aksu, S. and Doyle, F. M. (2001) Electrochemistry of copper in aqueous glycine solutions. \emph{J. Electrochem. Soc.} \bold{148}, B51--B57. \url{https://doi.org/10.1149/1.1344532} Modified: pkg/CHNOSZ/man/extdata.Rd =================================================================== --- pkg/CHNOSZ/man/extdata.Rd 2019-02-20 04:29:44 UTC (rev 401) +++ pkg/CHNOSZ/man/extdata.Rd 2019-02-20 05:34:30 UTC (rev 402) @@ -45,6 +45,7 @@ \item \code{SS98_Fig5a.csv}, \code{SS98_Fig5b.csv} Values of logarithm of fugacity of \O2 and pH as a function of temperature for mixing of seawater and hydrothermal fluid, digitized from Figs. 5a and b of Shock and Schulte, 1998. See the vignette \code{anintro.Rmd} for an example that uses this file. \item \code{rubisco.csv} UniProt IDs for Rubisco, ranges of optimal growth temperature of organisms, domain and name of organisms, and URL of reference for growth temperature, from Dick, 2014. See the vignette \code{anintro.Rmd} for an example that uses this file. \item \code{bluered.txt} Blue - light grey - red color palette, computed using \CRANpkg{colorspace}\code{::diverge_hcl(1000,} \code{c = 100, l = c(50, 90), power = 1)}. This is used by \code{\link{ZC.col}}. + \item \code{AD03_Fig1?.csv} Experimental data points digitized from Figure 1 of Akinfiev and Diamond, 2003, used in \code{\link{demos}("AkDi")}. } Files in \code{fasta} contain protein sequences: @@ -112,6 +113,8 @@ } \references{ +Akinfiev, N. N. and Diamond, L. W. (2003) Thermodynamic description of aqueous nonelectrolytes at infinite dilution over a wide range of state parameters. \emph{Geochim. Cosmochim. Acta} \bold{67}, 613--629. \url{https://doi.org/10.1016/S0016-7037(02)01141-9} + Amend, J. P. and Helgeson, H. C. (1997) Calculation of the standard molal thermodynamic properties of aqueous biomolecules at elevated temperatures and pressures. Part 1. L-\alpha-amino acids. \emph{J. Chem. Soc., Faraday Trans.} \bold{93}, 1927--1941. \url{https://doi.org/10.1039/A608126F} Bazarkina, E. F., Zotov, A. V. and Akinfiev, N. N. (2010) Pressure-dependent stability of cadmium chloride complexes: Potentiometric measurements at 1?1000 bar and 25?C. \emph{Geol. Ore Deposits} \bold{52}, 167--178. \url{https://doi.org/10.1134/S1075701510020054} From noreply at r-forge.r-project.org Thu Feb 21 16:33:37 2019 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Thu, 21 Feb 2019 16:33:37 +0100 (CET) Subject: [CHNOSZ-commits] r403 - in pkg/CHNOSZ: . inst inst/extdata/OBIGT man tests/testthat vignettes Message-ID: <20190221153338.02F9118CB36@r-forge.r-project.org> Author: jedick Date: 2019-02-21 16:33:37 +0100 (Thu, 21 Feb 2019) New Revision: 403 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/inst/NEWS pkg/CHNOSZ/inst/extdata/OBIGT/AkDi.csv pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_gas.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 pkg/CHNOSZ/inst/extdata/OBIGT/refs.csv pkg/CHNOSZ/man/eos.Rd pkg/CHNOSZ/man/objective.Rd pkg/CHNOSZ/man/subcrt.Rd pkg/CHNOSZ/man/thermo.Rd pkg/CHNOSZ/tests/testthat/test-eos.R pkg/CHNOSZ/tests/testthat/test-equilibrate.R pkg/CHNOSZ/tests/testthat/test-revisit.R pkg/CHNOSZ/tests/testthat/test-wjd.R pkg/CHNOSZ/vignettes/obigt.Rmd pkg/CHNOSZ/vignettes/obigt.bib Log: OBIGT/AkDi.csv: add more species Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-20 05:34:30 UTC (rev 402) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-21 15:33:37 UTC (rev 403) @@ -1,6 +1,6 @@ -Date: 2019-02-20 +Date: 2019-02-21 Package: CHNOSZ -Version: 1.2.0-10 +Version: 1.2.0-11 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/inst/NEWS =================================================================== --- pkg/CHNOSZ/inst/NEWS 2019-02-20 05:34:30 UTC (rev 402) +++ pkg/CHNOSZ/inst/NEWS 2019-02-21 15:33:37 UTC (rev 403) @@ -1,4 +1,4 @@ -CHANGES IN CHNOSZ 1.2.0-10 (2019-02-20) +CHANGES IN CHNOSZ 1.2.0-11 (2019-02-21) --------------------------------------- CRAN COMPLIANCE @@ -32,9 +32,12 @@ - Move H2AsO3- from OBIGT/SLOP98.csv to OBIGT/SUPCRT92.csv. -- Add OBIGT/AkDi.csv as optional data file for species using - Akinfiev-Diamond model. +- Add OBIGT/AkDi.csv as optional data file for aqueous species from + Akinfiev and Diamond, 2003 and Akinfiev and Plyasunov, 2014. +- Add gaseous HF and HCl to as requirements for the Akinfiev-Diamond + model for dissolved gases. + DOCUMENTATION - In demo/NaCl.R, indicate region not considered by Shock et al., 1992 Modified: pkg/CHNOSZ/inst/extdata/OBIGT/AkDi.csv =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/AkDi.csv 2019-02-20 05:34:30 UTC (rev 402) +++ pkg/CHNOSZ/inst/extdata/OBIGT/AkDi.csv 2019-02-21 15:33:37 UTC (rev 403) @@ -1,11 +1,23 @@ 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 -Ar,NA,Ar,aq,AD03,NA,20.Feb.19,NA,NA,NA,NA,NA,-8.5139,11.921,0.0733,NA,NA,NA,NA,NA -H2S,NA,H2S,aq,AD03,NA,20.Feb.19,NA,NA,NA,NA,NA,-13.4046,13.8582,-0.2029,NA,NA,NA,NA,NA -O2,NA,O2,aq,AD03,NA,20.Feb.19,NA,NA,NA,NA,NA,-9.754,12.9411,0.026,NA,NA,NA,NA,NA -N2,NA,N2,aq,AD03,NA,20.Feb.19,NA,NA,NA,NA,NA,-11.538,14.6278,-0.032,NA,NA,NA,NA,NA -NH3,NA,NH3,aq,AD03,NA,20.Feb.19,NA,NA,NA,NA,NA,-4.7245,4.9782,-0.0955,NA,NA,NA,NA,NA -H2,NA,H2,aq,AD03,NA,20.Feb.19,NA,NA,NA,NA,NA,-8.4596,10.8301,0.309,NA,NA,NA,NA,NA -methane,NA,CH4,aq,AD03,NA,20.Feb.19,NA,NA,NA,NA,NA,-11.8462,14.8615,-0.1131,NA,NA,NA,NA,NA -CO2,NA,CO2,aq,AD03,NA,20.Feb.19,NA,NA,NA,NA,NA,-8.8321,11.2684,-0.085,NA,NA,NA,NA,NA -benzene,NA,C6H6,aq,AD03,NA,20.Feb.19,NA,NA,NA,NA,NA,-21.0084,22.934,-1.101,NA,NA,NA,NA,NA -HCl,NA,HCl,aq,AD03,NA,20.Feb.19,NA,NA,NA,NA,NA,11.642,-7.4244,-0.28,NA,NA,NA,NA,NA +Ar,NA,Ar,aq,AD03.1,NA,20.Feb.19,NA,NA,NA,NA,NA,-8.5139,11.921,0.0733,NA,NA,NA,NA,NA +H2S,NA,H2S,aq,AD03.1,NA,20.Feb.19,NA,NA,NA,NA,NA,-13.4046,13.8582,-0.2029,NA,NA,NA,NA,NA +O2,NA,O2,aq,AD03.1,NA,20.Feb.19,NA,NA,NA,NA,NA,-9.754,12.9411,0.026,NA,NA,NA,NA,NA +N2,NA,N2,aq,AD03.1,NA,20.Feb.19,NA,NA,NA,NA,NA,-11.538,14.6278,-0.032,NA,NA,NA,NA,NA +NH3,NA,NH3,aq,AD03.1,NA,20.Feb.19,NA,NA,NA,NA,NA,-4.7245,4.9782,-0.0955,NA,NA,NA,NA,NA +H2,NA,H2,aq,AD03.1,NA,20.Feb.19,NA,NA,NA,NA,NA,-8.4596,10.8301,0.309,NA,NA,NA,NA,NA +methane,NA,CH4,aq,AD03.1,NA,20.Feb.19,NA,NA,NA,NA,NA,-11.8462,14.8615,-0.1131,NA,NA,NA,NA,NA +CO2,NA,CO2,aq,AD03.1,NA,20.Feb.19,NA,NA,NA,NA,NA,-8.8321,11.2684,-0.085,NA,NA,NA,NA,NA +benzene,NA,C6H6,aq,AD03.1,NA,20.Feb.19,NA,NA,NA,NA,NA,-21.0084,22.934,-1.101,NA,NA,NA,NA,NA +HCl,NA,HCl,aq,AD03.1,NA,20.Feb.19,NA,NA,NA,NA,NA,11.642,-7.4244,-0.28,NA,NA,NA,NA,NA +Ne,NA,Ne,aq,AD03.2,NA,21.Feb.19,4565,NA,16.74,NA,20.4,1.0014,4.7976,0.5084,NA,NA,NA,NA,NA +ethylene,NA,C2H4,aq,AD03.2,NA,21.Feb.19,19450,NA,28.7,NA,45.5,-16.8037,18.846,-0.4499,NA,NA,NA,NA,NA +ethane,NA,C2H6,aq,AD03.2,NA,21.Feb.19,-4141,NA,26.75,NA,51.2,-16.3482,20.0628,-0.6091,NA,NA,NA,NA,NA +propane,NA,C3H8,aq,AD03.2,NA,21.Feb.19,-2021,NA,33.49,NA,67,-25.3879,28.2616,-1.1471,NA,NA,NA,NA,NA +butane,NA,C4H10,aq,AD03.2,NA,21.Feb.19,99,NA,39.66,NA,82.8,-33.8492,36.1457,-1.6849,NA,NA,NA,NA,NA +benzene,NA,C6H6,aq,AD03.2,NA,21.Feb.19,32000,NA,35.62,NA,83.5,-39.109,37.5421,-1.9046,NA,NA,NA,NA,NA +H3BO3,NA,H3BO3,aq,AD03.2,NA,21.Feb.19,-231540,NA,38.79,NA,39.6,-3.5423,3.4693,-1.085,NA,NA,NA,NA,NA +HF,NA,HF,aq,AD03.2,NA,21.Feb.19,-71662,NA,22.5,NA,12.5,3.0888,-3.5714,0.1008,NA,NA,NA,NA,NA +SO2,NA,SO2,aq,AD03.2,NA,21.Feb.19,-71980,NA,38.7,NA,38.5,-14.5223,14.3512,-0.4295,NA,NA,NA,NA,NA +B(OH)3,NA,B(OH)3,aq,AP14,NA,22.Feb.19,NA,NA,NA,NA,NA,-4.2561,4.0194,-1.057,NA,NA,NA,NA,NA +Si(OH)4,NA,Si(OH)4,aq,AP14,NA,22.Feb.19,NA,NA,NA,NA,NA,0.9285,-0.9409,-1.8933,NA,NA,NA,NA,NA +As(OH)3,NA,As(OH)3,aq,AP14,NA,22.Feb.19,NA,NA,NA,NA,NA,-9.903,7.6818,-1.23,NA,NA,NA,NA,NA Modified: pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_gas.csv.xz =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_gas.csv.xz 2019-02-20 05:34:30 UTC (rev 402) +++ pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_gas.csv.xz 2019-02-21 15:33:37 UTC (rev 403) @@ -1,5 +1,7 @@ -?7zXZ???F!t/?????]7I??b???9??????TB;q?"?q???cL;?"???W?I???????uw(????k??n????f;? +?7zXZ???F!t/??? ?v]7I??b???9??????TB;q?"?q???cL;?"???W?I???????uw(????k??n????f;? ?????}z? y???`?Ix?}?i?????z?;v??}??X???q?QNI_y??S???????qLH?0??y ???? Y?-?W_?4&}?_WV?]eF<? ??%H??E???[(3?????u??D??[?C -?D????7 r|\? ?Q?"???ku???(?&}????7????w???%U????E?1?[??TQ?}_J????$????}q??Dc`o?*&:fD??`7??=g?????VR??Hd?'??&???/??H_??????$?(pf??(??????????????z??g????gK??? m?;?e_ {&ge??y!?Lq??Kt.???dz??(Yh??SGq??? ???PU???M??r?~?????????(????g?YZ \ No newline at end of file +?D????7 r|\? ?Q?"???ku???(?&}????7????w???%U????E?1?[??TQ?}_J????$????}q??Dc`o?*&:fD??`7??=g?????VR??Hd?'??&???/??H_??????$?(pf??(??????????????z??g????gK??? m?;?e_ {&e???y?#?v?G6?_{????????#??#s8m?"!v?]?>?U?c???.?I at -?????*?#?/?z?P3cP???? ,o?SMw?!???p????u?y?.??4????-??????T?dL??B??_? ll2w????1?? ?????/eD??WWP??$?m?9gy& +??f?'?B??h?d???6??AO?G?????(?-???f3H???p=??N_>? +???o???b?????g?YZ \ No newline at end of file Modified: pkg/CHNOSZ/inst/extdata/OBIGT/organic_cr.csv.xz =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/organic_cr.csv.xz 2019-02-20 05:34:30 UTC (rev 402) +++ pkg/CHNOSZ/inst/extdata/OBIGT/organic_cr.csv.xz 2019-02-21 15:33:37 UTC (rev 403) @@ -1,116 +1,107 @@ -?7zXZ???F!t/????L41]7I??b???9??????TB;q?"?q???cL;?"???,?????|?U??m??. B??????Q?????[???m??O???Io????i(/xq?lK?(?l -?O7 at O~?g?,???????????7?T??a8pT??b???<2>r???:-?KT? -:u?z????u?f??Q??r??s??'??E???9??u??)?:W??7????tY????c|J-??]?q?Y?@?H??? ? [?9@?98?????;? ???MSAAK??q6???4??L????"?}>?$}???@$????7g7??$p,?y4x?5??? ?????.1 k?J?????g?6^?b?nol?7?EHt?"<$?F?N6?h??Bj?c?A?????K2????QF?M?vh??a????|?????TX???k????N?t?Qy??l?Y??6+? ?%Y|z?g???.??co??????G???4?PT??YD????+?????%:??^y????x??n??? -B??w??s????????9???V?w?) ??DJ?JE?I`)???????R?6????? ???d?Bv! @?/e? -?z5>???D?E????>d?m??w???? JW????L??T?e?????k??B?;???Q??d?????oC??????J?1???P?Z????.L-?5* - I?????S??+??????X/8?a?@??r0 k?V?5?MQ???J?????9??R????n?p^i?"?/?!??!?????aB??????]??O??HH?IT\??2??g?y{?7$??I????5+#C}Q^a??\?;???K?h?????X,?Y??????O??7j-1??d>J??Y??H?^?W???z??y?$??B? ??8???~*OV??X??>???`]????-?31? ?L???jY???S??G??xF?w*Q/?+?[????????M?{A?2???????~8)????`??w???l?9?????l???????g?df?s?XT?_?????-}??b?%????'?9O??v4?>?????Z?? ??qQ??v?/????5?????????X????z?m@.=T????8???j?@???8?. e??V%?(????>0? b??rT??!?P?78n?fQu???^?? 3?"B???????d?,??D3?H???^=?Y_?PK??Y?>^?uU??f???6????H?^2?s7?=?>???o??o?j???6o????G???%_F???q?u??????????v2?S?I?J???N V???Kbmkg??O4n7???CEe??????L??#??M???n?X?? -???o??ez?????z?t?5?????8???!%"YC9f%?W?]$??????????mH??x?!???=?& ??(? -5?{?5 ??0?J?????????2My? -%?2????jg$?n?en?????{?H ?07+?uu???D Q??J??W??A?~????D???? j???f?????M???9<`?E/?=O???"?*???_???????b[$}?)???Y?*???`,R?????B?2?[1?X?? -???]?*??Zq?u?n?<&??ZW?_ge%;??i??+???i???d???~?\f?? k???A-?l???[?)JD~j7,???????S??l? -f?6C?W???_???O`On?3Xa?.?OG]k\sH ?X? !????+?Y?_??s?????4????p?O????b?????"|??IM(??????v?yu(\@?b[?!=U?????????+?n?H?5?? -?1?oY?q?mF???j\?????y??9??;?b??????X???Y??S???=1? ^0|??!?_L.????? ????????Wr????|s????QE;0???????QJ?@9????#!L???B??{??_?0U?&v?h)5??d~$t)??o?)?PZ?7_s???C-???>????P???4???????????szk??5 -??????L??uI??9c?????(&q??h????g?,|?=$p?f[?????#???] -?k/K????n?+\ -N??'?*(\??D??>:?R?A?q???[??~$??x?y ????\?O?j??????El)0)?~n??S?!9??v? -??_L$j?,?~'S*OT????c>[????????De?Mz:?c?B{??????m1??@??=?R?????B?? -%??z?c?&???g??.?R?????db +??i?x?)???????9fS?; ?t.3??h2 0?k?]??s?j???U??????7"???H?%?1!Y????:e0???????y?Y??1N?G?j???a?_7??? ?P6 ?N?- -? h1[?b??)????O?N?]?#2?d|??]#?-????#?+@??a%?u??i?a??l?7E*o?????N???]?b???a?jO t?JG%?3e?3x?m???D`C?b??smp?[F?h?2}???F??????S ???Y$ER??3?OWv?E????KtO?4P?M ??Q?kU???z??,D?'??e?7????4k!?B???TFw??!???Z#???P??t??,??jOpp ???Tf?y `d?##h?a$??h?Q2j?^?F?r? ?????c?(????U?Q????! 7$???l"l?0y?\??G?v1 N\??????????6 -?U??6???[?a~??Y????S??u?? [t??W[??xJQ??<"??s?3 *?5?/?J?aa??j+?a??-?o?-H?Fi??XKw?2?n|]?J??T?R>?? -????,???????CP?k?Y?e???????Pz??7???"=V??Y???&???O^>???g??s8?????b???.??7????&Z|O+????\?g{?f??=C'?qKR?;(?M??lP5a??*?3??5????kU?.??? ????????'h?w?@7????????M?x???????`?s^?)HL|????????$???????<<?_??Pu??>?P??2?{?:???4??W???????r1C^??T2$????\?m?f??/[???(d2???6???m4q?~???'??8???QW?????Q???m?????Q?F?=???d+??"/PT??g?? ????????rk i+?i???l -???????????P???q?F??+?a?&Z??K?????????],6?^????g&?Vtt?\@ o?????????>?A??=`?????0v?v,?-]?D??&?q???????? ??,:e?H????Fs???w???e???c???XI?:? -i&/?1???]9?X;???`?5qw\]0Mv:h?h55??|s????1?A? ????D??T?;2????O#7??a?Y(?s4?????7??{B d??|??$p??H?m?????^?{?0??6??0?g6IC?a]?Y? ?S?fa??s??fa #??3FcV???^???????????D0???V?{??'o?Y?? -?GC?e??g!c??Y????oq?'????>?? ?9??>Rh??$ -?=~???? t??O????? +?O7 at O~?g?,???????????7?v????????mc?2FECD?A ?2@???RzDt"?????qJz?~"??l"gf???(????93?v???N????I?%??????y????y??x0a"-??`?!????????{?m-Jgho????_$????h^?'?????YWEV#????M??N(?%??N??m?CE????,?zC?~??R?????4?]Y??`v-?Y????:z?m}h???=q_??m?Ie? ?>? ???????+???????A?~?+~H?qvX6n+?g????0??Q??9W?Y?????n??R??4????=Q&??z???)H?A;{]????C???v?j%?$S?$?H?????y?n???{?:Q???tz2?:q?&??=?i?(?????}IX!?u=???qD??????8X}?C???~?s??dg?6????? +?U????? f?%U? +I&[d??$R>??V??c?v`??Z?U?UBq??.???mIKOA?e ?????L???#??M?'~??),?G??????_ L??D???ig+v?UM?'???????q??A#?jC?{???z?[o??3???hk??d????`???{???-??????b?z?r?B? ???`????&~?j@?.?SS??7 +tXFR?o?O 2/_?????= +?;t?_?,??9xN???@??>(?????4i7Z?:??e??nz?(I"Y?gk\HA.3T??}n????#?pC???d?K#??&?????D2$o????JN??gj:ff?I???wX1??c???f?rD???I?G?/2??!, o???w???'?E??nQr??/?D?p!X??????dT???t??????6?$N?*?????_F?s9Z???g?Gv?9???1Y? N?6DI????G????G?H?O??<]6h???n?.A;?0Z??k??F^??E?V???9d??????E?????<]i ?!??A??Wx?~??f??Jg=sJ??$c2w?????{?(3=}? O?.??i)???%??,1?????s?5?C????????ZR?+*??s-r?cM?|K ???r??u????v?`%??W?m? +0?I>QZ??`??Xz?m??????cC"???y6??:,???????' Szk?'?-? ? F _???? N??Ux??f??????? %????1?0???jI??????\???1???????????????\3?u?/??????q????:{?A?q?hs?????I5$??::??????J????M?y ?_?2+J + ?????????l??J?H????3Yshm/?&Dp6\?"?v_?????!-?d????????V???????'E]X?/???tH??C[???_?K?_j??,????o3?-m?L??6/f??U???????V+?6n???13?n +a?????I?`?|e??_?w???w?????C_?$3?T???Q\?W,?\?{hOF'?8?(q? +M??Ca????q,?9g????G??F???\G5?u???_tGZ?c??????aPC??????q???!?a 8????<KG Ldu???j?W?S?b? ?9?q??????$?iNOBaqF?U?????????l????? +/??aF?m)???5?-?????9???g?t$j?|?t}?,??! +??????B+??v?H?p??r>??M??L'??????J?R??o??}zF????r????@N??H?q???E?=?????/?_:?d(?g7m???YV???gT?????q +??????0??R?t.??$Kf???P?1}5?B=?^e???a|??^? ??}@bpl?r??&????g(%??o??Q??# M????[%?\z??????&??l??z????N??????F? ??'?q^0?????f^w>??w}coS????????S??q? @@J}??a?H?????????W0?^?o?V????-[??rt??@??F?(???^65?p???`?t??Ucwja?D +?Kr?=???:?&?|PK?? +?nH]?????????,MlL,??b???B'Kt??hAJ?????k? +?@q??b? +`? ? +$? +???????e???8???{I?A[?\+A\b)?$ +??s?O??;(#FN;????*"7Jp?H????n??Z????}v????1??E?w?@??????E????>?f????? ?????P?}???}a|??l.|{???@??I"l???Dh???G?]??f??X???RQ???T??Bj(??4z+-Q??O?(!o0???)?U?I?/??u????h? ?^?2??Y?x??ix|??~??f?a/}????????agO?B??????l??? +DvS2??3?????????W??-~{?x~?~7b???L>|{M2?k?i9?????????????w?9????PB0z?5?^+v?B\?????t?O?]#?9E??i?fx??<@?? +???{????t???dHH j?????c?[???h?????z&}iD?? *?9????B90?????^?%?~??m????????hw??r???y9;??^??K2????m9:Q??????a0* ???Q?x/j"]U?!????K?X;H?6G????c??< +?`F???8??&u.??F????-)>?????9e??Omu5>-?k??????#]v?T???'?? ??dQ?9????l`+???????J?w?iQ??s???@??Zu/??F?`6z9-??\=<1?~??????$??w?j?????Q??[l???[ +??G!???8?l8???{6&?Cf?????Qb???Y?h ? -??^?????,??**B?{???a?u1e?U??29"=s_ -?[?'???@kf?3??????????@c??}? - ?????????/yk%Lo??S?????K?1?X at S?\h??GR&???fp?????????x?+?0?=?Y???n??h?!-????+RD?&?t??h?s?"?.????(*jF?>?^????fp??ca?=??^????????;ra????Yu? --?n?Yw??@(???/?????;??#????v?M??H?P????_7??w=$?y??m????:?fW??o??79Mm"???8?VP???j??j5?z?L????????P?^?^i*????V??U??6??????? ?G^?7|C????Y\? NV??&? -?d????@???K???i?????zX???"L??L???s0d???c???lH???{?O?A??????g?L??;?:??[? }?.?Y?3??`?_?????? -k - *(=J??K????????!?vo?|????Y?? 4?????oC<????1F?? -Ye%?%??v8??0??D???$???oC?.?'???5P??????Jh;?^W?y????)? -]???TS??=???4???vr???)r&??R?? -@?=5?*Y?+?S??^?Eox???s?P|??,?q???? -?? 1???=9c??l?{4?z?!?AQ????:?ZD?b????P???~No?Q?? ??)S???u?}????o???-X?? -??ZG?????|j??2?$???S?????cf -????4)0 ????N,???q????G?????????????@??,??B?l?p? ???>d?W}]???????2<$V?7?#G??U???|??4??GF??-?7!sK?@??(ya^7XU?y?q?[J??v?v?????!B?F?????,?!lN?v5 <57??K??, -??Y~CIV?R??X,p?????GF?1?_}?#~?$N??'?J?I;??bA????6BCZ+)??Fg?#???LU?BF?9????gj???*^-T/?y?x5??u??f?????/|??L; }A???3?????H????g????y??k?[k. 5V?~?,>Xp???? -??f??8?1v?\??,?_~rq??j??????????+5i?Lv??>???.?,&Fr-?2t5;c???q? -??\????)??(?????*U??#?if-{??2#?.?Gn??T?&?` i #???B.v?P??yJ=, ??]|?4?x?u?31?D????U?2?9?????V ????I?r??????w(g??k???Og??q???B??<[vq5???M????U?9???/?D?0? -^-wf??)?Ap???u?W/j?*??V??????q!? ????????$?&????????4?V??c?r*?r?#????? ????????'eEN>X) ???Q?(?|?W?T???by8y?>jQ?K=??LI?\fsr?z>??s???????hPJ?VN+vT?#!Q?9???g??????&??q??d??\??v???????;???U_????KhJ???_k?S?~QD?_???X???wS???U??n@??VFE?.???+S?|?6?)?L????8K?<{yA?Z?mN??????3w?D E?[:?????*?O?~????x???,?~U?f?`???vs?"?!??g``hN?p???????????= -> ?? -??ll?cFp0,??% ]TD??e?r??nxL`z?k?'Z???5i/????oA%V??3??{??,@?$/???9m?{?: ???*:?&Aqwe? ??x????U7B?q89-C??^???X?/?*??5]??K??? J??9??E?g -?+/???l -f?? C? -?? ?b?????[???"h??z?Q?1%'??/`?/?;+?u?< "?Tzz??n???v???BeEdA??g?????????:???-????@??\b???????????,6?svt??e?`??f?~?]?????Ju??v? --???I??U?h?5?a??X?i???i??|?aYfz?J??Y?$?W?[X@@????%OE?3??????A??[???]???Q%0?2 - Sb*^3?I ?|m??????)?K??j?8??U??9Eg?\??????????d??+??:???????@?K???1??N?iD?~?? -???'???????3?Y#? x???7??+?q??=?a?*?w?(????Lg~ - ??y??p??[?????Z\??Q?/s?@bt???a??y??h$??)?w??????aM???D&?p???<6??&Y??R>??R?H0?????? %VV?g???_??lL?v??????&??S?? -v_l???J:??|>9?Q?????p?d}o??????E&N??/~?s??????P]??????2???0*u1?+:??N?A8??.?)???e???b??????dG???T???[8P?B[fE`2???{U?u>????H?1??K?{??#}????;??~|?ln?r???V??g c?8=?mx?V?? ?`??????1???+|?????&??E'Ln?g??4??GS????&? ,e?%-???b??????Cp? -% ??n Q??????? -???????>s?zI??1? -?U??q4??j?zvi???8??$???w)|D:O92 ????c??+k??".l??^?Z?m#?-?x&J???~????????g??+8U???????Om??*?=W????^B???Y${?NU@?Q}????Iz?%}-&L?n?-??4??? ?2?(??C?t???K(????5????r??X?????n?1??!?1?xV???_?z?b`?|T?y??8?,m^????/??K?!? -Rwq?g?3???*?W???#? g?DwI???\???y]j??5????e5E?6 r??????g?Z??S??_????CZD?E????E???.?gP8??????ud???????Fz??L?j9?????Lx???>?T:?m?;Oz??i??r?t?-????d?=??"??D)L??T?\?????h@??r??l??E[\??u?9?????? -kS%?)>????????w^??h???j?:I?????fW?????pf?H?????*??1???r???T?L???|?b????/????????&D?????\ -)/??b??x????"G?}?S?i?toI????????s???@?U5W?? g???????*$*??j??wm$??V?7|???C??&)?R??`b???G??! -? -???`???? >???9 at p?^$?g????z|??E;I?B??k?MZ??E:d?|?y9L?#+???Q?V?L??!?1?]l[HeS???T-?3??g@??#b?>%?9E -;?(???)?????????OD????gb??@???r ??w?7z*?`69DT?]]??%5JA?S)?t??/?M~F?? ??'J???PNu??"x?i?F;? ?,??K? -????o???#?`?2r4w5x?m;5@?????M?KG)???88Jd????\3lwyj?eB^??H?|??E^?f4?tu?Ua]??????Y??hp??????6???.??????9U-??W???L???????y??D?? -??H?????????+?R??????b@?{???'?#?u??????q?:u2_s}0?c???#M??"??m2s?2 yb????????8/????Y??.My8???P'mb?MYq?_? =???G?N?'?????m9_??Y?u?????cG?]?????N(???j?mq????0?jau?#???P?#y? -??5????2D??+??R???$]ZM~?p?t?(G???3b?D_?&?NK??MHV??*??h??0D??Q????#S*????????,P+??(??)]e?SmL?!p:??&?z,?I[?8??)`2j????Vq ???^w?O'U>zz?o%l?e)?:??b??.;wk??v\???r? ?d??? G?~5? -?@??n?~"?rD5??3z???? .<]8j?W -?%?t?o?X?/???????t>???M??Ue^?eQ?H??Q?I?(????xq?xvzz?[?4?JIT?`?7?+?Z?? ~????xC?~U??n~*lb*???Lr??ol|?f?1+?i???f_????G???u?S?}?'?2???+??C -+7??y??pR??"??v?zQ?????1 ??J???9?N?e@??kHl???J?H5?????X9`W?pd???o$5j?|????":O?f? -???VNJ??c?Z?Z????c?l_oC??? ??56??c?N?4?-o??}?o?l?/;???p-?//?Fn?%??,???#?? ???????;??vU???2????x?X??? A??????? ??A -???Z&??(???W???`????3P?n?C`^?V????}_0{k -}??\?????Y?@????????_g???rA_??E?I??1????? ?????;%??!??h??'$ ???g?YZ \ No newline at end of file +? ??????X??????E7?P???C????c?V????<?????N???????G;.R???????1V'?F?????z?ch?t???d????G??;?l???Qj??3??o>??Co???qo?UCx8.c G2?C?m?? ??)2???pW???w??????e????Pf??*???^HU&??+M{?U?????H????>???+8?K#]??????b}NX?bV?^JO6??mK?0^???*?r??c3?#?)?G?!Nzi??@?+?@k??????~?h`??uh?????V??{?|?}??>???N/?A?k????XI?}V??r?????N? ??H????????????!?9??.= +"???????vref?g?1C? V???O?y??H???j???!J?~?)???Irf?OE#3T?z?Tf?)???N?^IC??? ??8-???/qg????x?c? +?P???? I??S5X????f0?N}?0?X*h?V?Sh?A???!?]`?sw???"???f???????&c?????(??9?@K????z9???+B ????Ox9m?Ri??}E;^????M??+Q:=?????Ar??]???B>w?,?????????z???????;(?S&???\?{?4-l????`|??>?d??R??i??8ig???3q9??!???????8???PH|:}???n??S?,48???x?????EU??M???6"%4I(??????????A??u?8??L?9? ???3??????0?????_??~?.?\?'K !?_?I?' +?tj??2 at E^@O?^I?e?x???-??-+,???) ;??kv??AI?=K,(ce?K?;???k???(0?1??%?pG??8????@???)/?n?t9??6?R??f??? +?w??????????e???????[?t(;???o???.?)?U? +?4N?&?3???V??I5?f??EY???@?v???Z/?M?K5?)?)l??1??B??lo*M-??BV=??\?{?u?6~??J:??/???}07?g?^??DO???????-?l?y:?$Z?ky +???u??(?%?v??(S?U?i9?&[?y#r??v?a?>?'{????plU ?u:$s^?:p? _????????????/s +nZt??FL?I????>???2?????F?"&??/??m,?k\U????????????l? 9????%6P???G??,?8????cg?;?=MhE!m;??}39r"?\L?B??4??V?R??{jgPr??K02?l???$??9K +??}?m?u???Rv,I@]?*y?|?y??3TQ?`?6???a_6?>?)??s?c???? ??L?~??(?/D4:c???m??O?S????<':uxD??_1??%&_?????????i?wqY?J*^?????@????9`+?1h???P????????-M?y?j?YV?Y?8?D?????R?K??VQ? +??k?y7??K?/???g??\?/??*;?{/?????"?j??????A??;^???V?~???G??o?l?%)??s????}??r1sc?? 2?=h???E?+-?qB ?O?????Wp? +-????-??3 +?? ???L8!?O??g?XyPv~??2?d???ZyM"?????R?? ?wZm?Z?%?J?MtdY????????w??????Pi} +~\??n???U<?g???;r???"??n$?4 ]C?3?L%??:???7M??\8F$=??$??u|??????v???UeT??3g?)@?&?8p\??]7?w?n:8????????????c?g?g??????=(?vu???>1%? ?d????4??F??_(n??h?????LJ?X???? U?|?VP??1?? >??Y???????9????M?2???zq X?!?~? +,Y%1?X?S????KYi?E??d??F??????7?5 ?,:?%????wh G?i??L??~??]>??3??????(c???8&D`|\3?Pg{!??7?a;???"?t? }???P??m?K??? g^??}?????ea3h???h??)"?&?G?8V+P:?X?????rJJ?_?????*??]:?^P??????4}<+ ??+ ?_|"bD?o??m??M???]/????8?NF?>_?Rjt,??u?,??T??N?6d {???tqL??J??????d?(????Vn??R@???yAh?@??pb+#??T S<?N????????????BuD???? ??????W O??3??u!?A??#?????????N? Rw??zLM?v,>? n"?wg????]????E?????v?? v> +???,K?????6?q? ?jN???%ip?D???a?F??????!]? +Z#??? ?{??????? ??="?ks?s???????Q?g+????? Pe????????(??T??c??????r??cg???? +?z???? + ?^???-i?????6?u? zVQ)&%_?d??(???h???lBs'??y?m~?^??3??????D?mPO>k?uQ|?"???3?|????U??? +)??H????n:?O?1? ?P^?????????? +?$W4?|?-??!?jO?&?????p?????B????@?)?y4??NA,???H?\???W???oe ]X?????f??c?,K?W7??x?}????j`N\*??74??????j??fL???? +?m???s??o????Z?????????W?<??e?AX???M_tij?(C???/??? +?rrK6L*~$~??(????1_.~}??S)`T????%1y?0?a????|e?????3rV9?n%?? ????~6?????u*??n???????"G[2?w??yh?o??%j=J????j?^D?1?K\$A??EP?????C:E??b;???)e??}}s!????__R??i?P?t'M?F?~GY??C??R??"?nH?sz????+???A????8?Hp$?P??Wy??"2?.???C??/?;$?B.X????+ +/????){??x?|W????r?a?6! +Z???Z??VCz?Z/:???{?? +*?|?8ZZ?;N?(r.0???, ?o8?hP?c?}I??m? +b??5 +?P??6??Ob??*???pZ?A?NE??? ?;????a???s?nH??r?F????_Z????q^??xR??W??2{?????~???? ? 7?T?????e?@`??????IV.?%?D? +??v9ryyU???TNf??(o?:???e???/?P???B?*?? ??? +?????Z ??r?X5??"8???rg$EU2Z??oz????S????j? y?d??^??^:??h??????i?@U???5????%}?k|Z?????D?K??2?(h^5(?J?]|P]??Z??????R???s[<>?M ?b?L??]??z8??? ?>.??4????????K???O]F????Fj?/???x???$#7?f?P?RHd??Q?qa?Ai??A^??h^?#?@?>pJ??G?3??/???^??z???Y}???o(K +}6??? ?"??'?]?? +?Aej?G ????a??QG:??Wd?`???@(?X?}k????]e???[??Q_????x +b?`??J_?;&?0??-??4Z??c????wS??(?}?? + +?I48>A??lZ?????vm"/tA??????? +}Ye?}K??W????c??9?*?8??C?z??6??????\?P???a??? +8?AE??4??HB,????d??t?????lD?[????;?bo?F?l=??????? +??W?????]?g?? +l???????b0??\??f,?G3?w?,???ZS?p9?????????N$???m_a????H?? 5E]?$?#????6N)%x???{??B_;?????H?b?????#??ZD?1?F????N?(?,@??*??????X??\?????BI??k???r?"?????P??l?S~?W???J????(<4?H???`?????l???p?*B*??????H? ?4?????? +??5??.|7R????y?x*??? t?.oCAKM?4+D?E?ot???z.?Qey????2?U"}?q Author: jedick Date: 2019-02-22 02:18:45 +0100 (Fri, 22 Feb 2019) New Revision: 404 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/inst/NEWS pkg/CHNOSZ/inst/extdata/OBIGT/AkDi.csv pkg/CHNOSZ/inst/extdata/OBIGT/SLOP98.csv pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_aq.csv.xz pkg/CHNOSZ/inst/extdata/OBIGT/refs.csv pkg/CHNOSZ/tests/testthat/test-eos.R pkg/CHNOSZ/vignettes/anintro.Rmd pkg/CHNOSZ/vignettes/obigt.bib Log: OBIGT/inorganic_aq.csv: re-add Au+3, AuCl3-2, AuCl4-3 Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-21 15:33:37 UTC (rev 403) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-22 01:18:45 UTC (rev 404) @@ -1,6 +1,6 @@ -Date: 2019-02-21 +Date: 2019-02-22 Package: CHNOSZ -Version: 1.2.0-11 +Version: 1.2.0-12 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/inst/NEWS =================================================================== --- pkg/CHNOSZ/inst/NEWS 2019-02-21 15:33:37 UTC (rev 403) +++ pkg/CHNOSZ/inst/NEWS 2019-02-22 01:18:45 UTC (rev 404) @@ -1,4 +1,4 @@ -CHANGES IN CHNOSZ 1.2.0-11 (2019-02-21) +CHANGES IN CHNOSZ 1.2.0-12 (2019-02-22) --------------------------------------- CRAN COMPLIANCE @@ -38,6 +38,8 @@ - Add gaseous HF and HCl to as requirements for the Akinfiev-Diamond model for dissolved gases. +- Move Au+3, AuCl3-2, and AuCl4-3 back into default database. + DOCUMENTATION - In demo/NaCl.R, indicate region not considered by Shock et al., 1992 Modified: pkg/CHNOSZ/inst/extdata/OBIGT/AkDi.csv =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/AkDi.csv 2019-02-21 15:33:37 UTC (rev 403) +++ pkg/CHNOSZ/inst/extdata/OBIGT/AkDi.csv 2019-02-22 01:18:45 UTC (rev 404) @@ -15,7 +15,6 @@ propane,NA,C3H8,aq,AD03.2,NA,21.Feb.19,-2021,NA,33.49,NA,67,-25.3879,28.2616,-1.1471,NA,NA,NA,NA,NA butane,NA,C4H10,aq,AD03.2,NA,21.Feb.19,99,NA,39.66,NA,82.8,-33.8492,36.1457,-1.6849,NA,NA,NA,NA,NA benzene,NA,C6H6,aq,AD03.2,NA,21.Feb.19,32000,NA,35.62,NA,83.5,-39.109,37.5421,-1.9046,NA,NA,NA,NA,NA -H3BO3,NA,H3BO3,aq,AD03.2,NA,21.Feb.19,-231540,NA,38.79,NA,39.6,-3.5423,3.4693,-1.085,NA,NA,NA,NA,NA HF,NA,HF,aq,AD03.2,NA,21.Feb.19,-71662,NA,22.5,NA,12.5,3.0888,-3.5714,0.1008,NA,NA,NA,NA,NA SO2,NA,SO2,aq,AD03.2,NA,21.Feb.19,-71980,NA,38.7,NA,38.5,-14.5223,14.3512,-0.4295,NA,NA,NA,NA,NA B(OH)3,NA,B(OH)3,aq,AP14,NA,22.Feb.19,NA,NA,NA,NA,NA,-4.2561,4.0194,-1.057,NA,NA,NA,NA,NA Modified: pkg/CHNOSZ/inst/extdata/OBIGT/SLOP98.csv =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/SLOP98.csv 2019-02-21 15:33:37 UTC (rev 403) +++ pkg/CHNOSZ/inst/extdata/OBIGT/SLOP98.csv 2019-02-22 01:18:45 UTC (rev 404) @@ -1,11 +1,8 @@ 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 AuCl,AuCl,AuCl,aq,"SSH97.1 [S98]",NA,2.Oct.97,-3184,-2140,41.47,-9.83,38.61,7.0357,9.4008,2.0481,-3.1676,0.0551,-5.0371,-0.038,0 AuCl2-,AuCl2-,AuCl2-,aq,"SSH97.1 [S98]",NA,2.Oct.97,-36781,-44725,53.6,-24.52,69.26,11.5192,20.3482,-2.2547,-3.6201,-0.6764,-8.03,0.8173,-1 -AuCl3-2,AuCl3-2,AuCl3-2,aq,"SSH97.1 [S98]",NA,2.Oct.97,-67811,-86023,61.39,-43.48,103.42,16.6878,32.9687,-7.2151,-4.1419,1.7155,-11.891,2.2827,-2 -AuCl4-3,AuCl4-3,AuCl4-3,aq,"SSH97.1 [S98]",CHNOSZ.3,2.Oct.97,-35332,23573,-32.72,-1.36,-20.66,-0.5361,-9.0876,9.3148,-2.4033,19.7251,-3.3107,1.5579,-3 Au(HS)2-,Au(HS)2-,Au(HS)2-,aq,"SSH97.1 [S98]",NA,9.Oct.97,2429,-2509,56.77,6.06,75.39,12.342,22.3572,-3.0443,-3.7032,16.8038,-1.8007,0.7693,-1 Au+,Au+,Au+,aq,"SSWS97.2 [S98]",SH88.1,13.Nov.97,39000,47900,25.6,-0.3,12.5,3.5312,0.8428,5.4139,-2.8137,7.5089,-3.0956,0.1648,1 -Au+3,Au+3,Au+3,aq,"SSWS97.2 [S98]",SH88.1,13.Nov.97,103600,97800,-54.8,-8.2,-31.4,-1.7167,-11.9654,10.4352,-2.2843,23.5775,-4.7048,2.4115,3 Au(Ac),NA,AuCH3COO,aq,"SK93.1 [S98]",NA,10.Sep.92,-49870,-68310,48,56.1,61.8,10.213,17.1576,-0.9969,-3.4882,38.7432,8.3843,-0.03,0 Au(Ac)2-,NA,Au(CH3COO)2-,aq,"SK93.1 [S98]",NA,10.Sep.92,-138240,-186750,61.3,132.8,118.3,18.1917,36.6392,-8.6534,-4.2936,90.461,24.0193,0.701,-1 AsO4-3,AsO4-3,AsO4-3,aq,"SSWS97.3 [S98]",NA,11.Nov.97,-154970,-212270,-38.9,-116.1,-18.7,1.0308,-5.2609,7.8091,-2.5614,-12.1352,-26.6841,5.399,-3 Modified: pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_aq.csv.xz =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_aq.csv.xz 2019-02-21 15:33:37 UTC (rev 403) +++ pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_aq.csv.xz 2019-02-22 01:18:45 UTC (rev 404) @@ -1,4 +1,4 @@ -?7zXZ???F!t/????#?]7I??b???9??????TB;q?"?q???cL;?"??V????K?????h?????? dS80?>ev?mb?9?? =??f??W???{???C?i?????????mE+! 89?? ??[x??1?v3?k??l?M?>??G?m??z1??%?MhK"F??Z??O?Ed8/??+??X?4?N???yn?{2:a[?D?J???6Q?? ??Z?L^?|2????-???"??3?????m???@?:?????y? ?PH??T????????C????????wv??P?C??MPJ q?y??????j?~?h???S^??i??&?v?q??l?C??P?????[r?I>0?K??????f?{r#?j??????}?[?:^??6?,??R?????o? -?????%NUSE???????t??O?? -????V?4?-??L?J???v-?HU?o??????? N.G?K???X/??T?Z??~[#?l??Bx~????QK??E?.?R%N??P?1????????2E?/????1??(?n}?"U?v;5???H??~?p?qvC,?kM?? -K??Yn_?P??5?"???w?~x?????????????"?pP?????(V@?Y?C? ?P?x?e?? ????%E?W[???v?!?l}?[?>??(?? -H~`,M?????[?ss???`u?klE?2????-R?/Q??B'??c??lN.O7E??F_|???s+????q |*?.n?????>-????[C?? -??F??E??V??S???KnD?O??e&7????e?_9R??~ -q?t????0???u Ka?1?e????T??t?=???? ??q????i@)"???$w???????+U9\????????D??zH?E???u?Z@ ?r?X2??FD?PD???/,?t??x??#c?R?tB?5=???x?xO??5????t????L??$????0?????? -W?*T??uqxo)????&?Y?s~P?????6Fd8V+? ?5?5f|?X?LE??m???|??2??+D?Y$?a'?e????'D????????????)?W????? ?N?????uE?I?,m?l?????bL)/ ?#??$w?;US-??+??f?,`??:8?0???=??, ???}?s-?? Q 6??v? !]>^???:S*x???]?16*V\?? -c???S??mH??-t???f? J?{???udG?????????o?/ -AJ ?vN? ????ost???T?O???:??|?_9??Avl??????t[R?Kh7np0?E3??-??6???z -s K? ?W??_}sO???O??/?|? -2??.??&G?_?nU&:g>L?k??u??I??~A?i? d??#?x?D??+???}??????XU?N?c?`?.?? H]%???{???k??c??5?/????b?1E???9????V% -2l???>????????P????n|u?}q?L?]?C?h:???.w?^ p?d#???]??^??cA?? ::*?$!%?????L?B +b??)??u?0jg?6?a?(??{;?[m?K???r@???k??a?W)??????,(j??S?V?? ??w?)? zP?{?#d???IKe?o?A?`??iK?:??72yf?P?m??Sx?????f?~?!?}??4??????%??????????#6?Ys?x???]?l4??&??K?????g????X +`?????+????Y??????? )|???????HAT????i??? ?]???lNNF??Oo?*?,????????? +G?????c???u?+^a?bk??o"????????K????7??zkm(??hU??=}K?E9??_??sZ/f?5I???|?/?????U?u????U{??]9"r?M&???????H{?????Qy??s?i?4l?????p??v? 2'\|t?-9?O???w? ?]L*kr???2%[F?v%?Uuz?kRM?*!e +?s??a|?*???;d!????L^??{?!??P?SS?z?^w9?mPlJ??C?zCT?Vt +H|????????p1?` -?T??,RN?D?&????[7pC?6??? ?Z?cH?????+??$??)??yw#???????????oPrs?2???????W?Rq Lhl?j1?qg+?w??QMF!NT?Y3?m???.>?`??u??ra??L???2MB}??O???5a?z?b?Rf??"?????,???????q?.q?"?????{? ?w??????L????cVpu3???x????Z??????S???????????H?aHE????r?5??`??1?y^\?%vD??b?????i???3?e?,?H0??tH@?} +????/BO?i??V_ ???9J???? h2? +?$F?6?zka9*??^????g??m?F?szP:??y??y?N??(?r?6??????? w1?Ip???|?7@?q?7?zc.i?? +?m??1??(?[?>{@??U]3?G?w?l +>?x??????v?-???(?w?7;?u?_??6??????;o??r`8?F?J?f??<6NYu?IPdH??!???????o??B 4?A?D??`w???\Ra?p?98??"??Bo????6lT??????%??;???T2 at k??s??n[??W????????[?L???*L???at&v?fc?y?5W?;??Z????f??}?????k????l???n?? xHB1??/0?5???X\"TJ?_????4??f? +`o"?K?B*G?? G?? ?r??????K??????ES%?8?Z?Y???q&?`YE??/?i)8?5???????b?N?=?#?? ??j:?m?9WP???E@?Hv?+?E%??m??q?s??*%~p#???{?U?2?v?c???v??kB?I??? +4UZ??8??n~?Xp BB?f??b?,v?}A1.4????????DC??q?e4aLpI??3???6?x???k ??@1?????#M?Nv1?m?\5?R?il?A??q?J +?#?"???dG??j?'?a?\??Y???????IG??1 #&B?5????D6?F????a> ?4?N?c?h-????????JY +?]???$9????U?\,H?*?V??1=!E`R ?????Z?????,?|?a?n????????^8??N!????J?{v$D??"???i???????????3?1w??I??;@/???~9}46~?r??'R???????????KGu4'MFHSP?????${???r ?c? +???`+??xa???$??? ?*?? ?U?]??R???v? +.??#?:???????LEWT?:?o???_???)??^!???y???^?7,_p ???Oe]~????D31H?F1????W?????n?P??-#vOA?U?d??IMGx]????????d?k????? ???K?^?? ???%?L?v}k???v?qc?K?????"8?&?}?@??w[??A?????.t,e??????Q?~]??*Z?/?>???;*?+ ?8??_"n?{?}??UzVF?;s????????(?? ??)?@???????j\? +HqOxL d???A4J???- ?3??CA#wnF +Y??"????+ g??X?j??w? ?~?DXN?`??.???h%%?N'?XWn????cU????G:?(?B??y 4%N&??o] n&??K?^or?|?????9?kNO?n\ _??hd?!?[??E ??/?%?X??^?????d???B?pH-Cc?5?W?Md?? ?,?L??e?X???8????????m?7|? +?V????O??,U??m}? ?Te?????KZJ'D,?J??d9??B?{??D/??????? >*#? !r?c??????OZ7?\???"??/??EN????!??????'z 2?S~?X??????tn?$a???????p? ??k`?J,c??@G??a??^?????77Z +?P??4?pVC?i?~7~.??:v??^x7qNv.?i?,????/6?%?????Fb6h?G?|pCc??|V?~??v?t????2?:$oed??b???~?>????c?+???{??;C?{'~w???&&2a?#?A???? y??;?????qStd??'???w?f??{0???*?e??fZ????D]??q??2[???????C9??$??????T@?^????5 ?$G3??????#??N?3?H?,??????V??f?:????Y?&\=??D?????f$V',,E??c??7y?Q=?>????P?Hv???iv?A?@??(%I??X??*??0????gGc?YC ?c?}S^? +\?????%\???6?????????~???????U?2yl?/??O13?Z>?oI?r??X5]pm;????'m4???????i/_ ??I?7??#?? +??Nw????qu*^????$?t??u??-? +???,{?2b?3?0Th#L,?t???V?????V?ft ???F????#I?jj?2????\2-J2?jt4t??K??1?-;j??? +???l?8?sX]??j????J+>[?K/Or??jKt^?%?.m?o??N?v??0Bi??;??&P??muX at N3?????N?)?????9??hQRq?? +??[??R?????*?$?5?T0??D??a?_??mm8?}iP??y|m ????h??0+??0Y?m?????'??????;?3??&?????e7L?J???e?b0L?,uy\! ?YN??????H ?&M??_????x?0????_V\?|?4?=? ?#?????N?????d6n?#?k?*?K?????D8%???UQ:?KPc?3?@dc?6?v1Qs??H6WS ?f??g?db?6/???c?o?? w?L??5???^?C???A??kQ????#?Vj!t?????7;,^<.C?I???????*???]?S??P??d??" ???e1??+e6p(??p?????? +??K??]w??<-??DG*??v6dms??K?Pg????ef?W+m??;8hK?rX\???a*=lA.???K72??'??e8 ????sR?x?????8???F8?????? ?????*??@??9?5??g??B?F????????"??J?vcy?B???J*3??O?`=2????x?f?Z?-.?AO??4?????{?n?v[?q +????S???_?Q)?f?S????eN? ???X?~?I3d???E??&??\)@n64?J??jyS+JM??????+?8.?E?'?JQ?3[?)=?d&?t?/??b??7?#??9??1??R??+?KDn?tw??B?o??%[?-?????j???[i???T??&?l8Q????~???r???~??lz??s?-??[?%??#?A0?^?P*o??c-?j??$??/?{r??J4????????L?$?{8O??4????5?B??&??4????\?????l?9? ??p??s????????u???2o?yb"??=:E???c?%???#??????????;{???????xu???.#r?{N????????'????R?Dw??se?K????Yp??? ???S??l?Cgw??????1D??*?????S???s?????@?18??6h???e?oR?5???*??s(Rj???t'?+??4????? }?}?ukE ???? +???8???&?_O?PG?vN??uT?9??JbL??V???,??/??x +??Zi?? ?=?H?e{??P1??vx?7?????WUg?$??px???8)?N??????`?k!???????????{?n?bW??@?@?\??l/B????6?3G??2]?e^??5#?)???- ??v?g?G?e?M?@??41??q--???j???*?B??RH?e???zY???A???2?X{?e_?????????h??o??=?????5???+???*&?7?? m?'??a?#???hZ?56?}K???Y?k?????0?#|???!?#c}?&?7??S8?R???$?XE??X?? ?P????????GI?/d???q\n?????(???p??????$G[?D}?S|U?????MF~"H??(gL +?!??(??~??E~+M]0??Q?F????*??(????HE +L?!bOQ??c7G??^?O?????f W?X?DZ????I???(`??a???D?7?y??f?G?E?1[?Z 0b:???+g?!k?]??w ????O?{J1?%????-?!?"V???Q3~??|a??@h{r?j93???-)?*Fk;?MF??G&??W ?????t?t??o?=??E?WW?????3iXp??_?????w??7??r?g?y?>yU?????X??6n??~????Y??ZL?y?E??cz????E?6y?7 !? +v??a??'?????OG)3????p??sO"?D??KY+ +?-&???W??Z? +q???%?NS?.?m ?????r?r?0#??0?[N???????=kAa??S??1=????i???Z???>???]z?R?of +?x=u?t8??7#p<$??z +????/???$^fN??.s?f?K??????e??{?????';??rK??g??>j.??Ej?.kP?9???Y? ??????S?&????\?V???G'???y??????9?+ +?E??{S?|??4h1??]??H{?<?Y???,??/??????4?g7 ??sV~?u???yX??%???v?Y?P?5???C;???z?&??7?C??*? +? B%h?E? +???????DGi7?? 9???M??i?hau/-????????%???<(????"$?]}?k??+?./F??>.????(? \?vbX&???+ ?? ????w????#GI???6????)??sKk?2j ???????4?Fkre~?+S????n< ~gqVN$XV?Ww,?W?7?7?s?|??_?y??mk?r?|Ul?|X7^B???>3???}???N?O7?9# #A???*?Kr+P2?g?????3???tf ??qd ?of??>p??sC??L?&S?\??B??@?????;?u40L6??|?i:f|9)5?6'?? ??Q?A???Q?o"????X?$??o~???w??M?????%??C?/?w5[????????K?Y9????t7??W??x?\?G?-??^!?:D?wr?0???To?f?2~????2\?E6??RHQ,????p?N?@F]doxVp2?C?.+?}:%?/ ???t?=B??C???2p?????v???x??????(????N?6????%????nD??g?????Tm2?_????nN?ah????\???@??*?? +????k:Y?q??OWs +??<8??????^???W4???S b?Yj??=?????HcJ ??'??7d??i ???3J?ih?W? +??????Hi8q?%???pC??&= (bmRF??L???PJ?|OY???te?D????lX?*?L?L???? l??|3? ?Z?7???AM????????x?-??>Z?E|????E??_?$a?4?? ??V?$6?????k.???"?c?2k??'D?!'\??t?? +?>??~?K?a?_????ES?v49 "R??E??{ ?6??????Gg???\3?M\u???{??DBDb${?z?F?xg9?VG????V?KA?????)?*^??,???????,?+????)??????t?Q??of??1?@&??X?R???? .?)?p??? ?g??L8??????Pi??dv?B???D???=9=Iw????G ?UnL????K?8;n???^?????!" ??hO.,???Y^???[???????^L"???ps?????T)?WT? ???F????:????]q??to???n?g??U??'s*B?BB??@C at x?e?B`????x???j(?y?A?g +?w?? +}???-|s???=.??Y???(???6?,?????U??!?/?M?a?V?{? ??? +R??*u??.??3????????"??v??7????Q???!7g?????}??H?,M??/??|:0???0??92?Oy??[?????x9O/??e?M???????~w????q??qg?%{?H????3?N?/ ! ???C??N?t?5S?]?s?>???*E?p??R?e?@?l? +pj? ???-??e*%%E?L??/ +???c??z??2??u?FC7?2??~r??????6???????%???)?EDA +z????*???a +$???}Acm??+_??Q????K??? ??7,Q???T???R??:?Q/???~ ?A?7&??u07?????r?F???:?? ?D('?x???y"??P-Yc7?}??#)?>'?C? ?????j??J??P?)L??>??+?,^?|??=??????6^?T|! q:3?:D??e???a?????????r??A}z???s?>??r?Q?/?+]`?a9iV??????#\v??h?tgi?Z|&;3 ???ytY?x??[?? ???????????E_????,??&}y???1mtS????>1??????!6J???{?F$?ef???d?????n ???A??c|???/5???? ?8?Dn?c????p|?????.?un????Sv.?)??(?c\@???R?`m??q?"??@?|???b????4&?)*?????\z[N2?o??5A???G?|?j5'??-??tg?????e"??#??(???q4M??;????????d?K.?l??.???_>??}@???Y??V? o?QOm?k????o'f?Z?????B??b?p??1d??{t????Sy?5?~b1?????,Kn$???.??[???'?~??VF???Y?5Z*??^m??L?A?h??R??``*%?????UYW??S.?g???Y??p?njgO?6??Bh?`I?????0????????c???&?g?(?(????t ?m?sG?J??????$?M_w1?? -?EbC?&Z??r??=5"????C at V???)r??????fwU?'%?4 -????? $?v??b??y??6D?~?`?x?????:????D?cEW?>?M??P/???????*W???l.zJ_?t??? ????/?r??????????????m|???L?S?&c???o?L ?Y?`???2?9??S???Xd??q?:???v?5r??];[$W??? T?YS??3??6p?????Z??v???-??4d?????R j???.??v???N????;?1$???wl,4a???????-/??J?????????x?p???_ym]?i??Rm6p?>'??g????o???????86??*ZA,????q?????8?9w?QF??$??O??2???-??E?F?ay?C6+?????>????)??_?y$?x?3???B?*K[ ???1?(hw?h?????/`???]A?DV2????w1[????? ?R1????.?s?}??$?????C=P??????S?V?~?+?j5m'?&?!?????#3???gw??Os?%?|?t?????]c.&????p??X?>?x????{???????w??/?'@ -D????f?A[7?\??`???=? |?].6g?&??W???}????D&?g?Q?U?"???U?'W???I??-kf?}Y?????emq%??-?x?GXh?e??/J????3??U?g?BS??R???o?U????t????w:%?+(? -?f??Gms;T??f?????@X??X,???2+V ??D?j???vN?o?8J???F ?i?'i?R?K1A8?E??*q:????1 ? Ms1Z???M????????q??C -???C?5?%Sl??1?T? ???D??????????0;'??yh;?-????L????????wN?0?S ?F[|E?g~????~'H iS?s???U??"??U??up?e+?uU??dO????!???????0????????*?x!???S?v?s2?3?!? ?f??{????&??????3?O???Y?????w?}??O-?s?????8?-???B5nJ??@?x??L???8wN??R?????`?2DR??????m????d9;??6??|h??o??C??????k???EjcM?S?g ??8?h?+????f???T ???j??G?39??&U <????SB???H?? f%?2?B?$???1? -uC?,?I -?????m???????U? ?H8?6P2?z;???}???\??Y??\?X???Ukw2??R.`??#?k0???????Y????Gk7up???TW?7/g??A?r?/?H?Z5?c\h7qrw???M???)??oZ???w2?tP%?a?????(?N ????3w!q?????jOCf???7}?Jj.A`:Y?P????1![?2+H1 0]?H ???EI??>5k?B??5??-?ty??Sk?+? ?wV`?? z?????r"??[???U?{??^??s(z?V??g?????RE??f#?y?g[??1t?????:R???o???g?u_"?? -_?s9???k?Y??S18 at Q?0?zj?y9?h?o???S?.c?iK?(????vP{~MC?5???z??wo????,E!@?\Z???O??T??? ?????^g F??#??5??'? K?V???_???X\E?}fK?"?(?P?^:$????h?9???'+Q?frt????L??8Q?*??QF}!j??/?\qr???t???of8O)?"?)p;? ????f)\5?B^ ???c($?,?+??Re8?G!A??2O?x5???B??n[Fz??9?????9?a????h 9:?#?????;#6??????%cE????x????U?M7k??o????Kl??N??? ?5?????e8W?U???x?????*??????c? m? G??? -p -???Z??y?yp???@.????)V?\2 ???z?,????i?_???8??/tp?'??z?u_???n#K?m^??Ke??j|?D??v@?On,?o?]???????YZ?7j-????u?G???A?A?&?_??o??y?K_?F???????p?qI?N?X-?V?F??<#Q???T2cNe?2 W??)?AM? ?}?-?YA??^??? <#???'?r?| i'~??? -?{??1???3?boo?? ?Z?c?Z??=??$?a7??{??S/)?#??x6t??Gp*?B?(??G?wq?Xvq?]9??6 [?,???FgCAbeV\?S?$???:?? ???n??k??ucX???? -??????D???*??JJ????eV? -?5o?p??=0?} 1?????Wn@?oD??????h??oN???g}????'? -????KH???????g ?}?z"8%??#2??_q?2W??T;O -???R???Q?Bl&?:???wawV%?? )~M??*??=8IB?03l??LhD?{???/????y_? ?h?+??ex???@0?????+4??F}?yN?????"??????b?G.???x??&?t?r_?O?[?9\(N?v[?????),E'/?????????????????]?????z?_??Q?=??I?????V?w,? -?Z?XT?_ -??#?#K?????'???a?? -U??gG]????%%??gM7 7???????G9?(??x?}??-:?i ?)7??*?qb!?"t_????tL-?@Il?:???*UEZ?2^????t??'?r???? Bh?_???5m? -?z=u@)_2????l?z=RR?G?@?G??????Bn????e?C6??g?????WY_Z??X<$?D???i?? !?????????X???Jy ?x????C.?#XKH?????`??????BY???????^=????? ?? -?b??6?????;l?m????/?H??F W??5?g?]0W)5?h3????o?j@????? ?ME@?`yfa???N,?ao??G?[z????8?Tj?8%b\?#???6?W/???2,????7?Z?qG?;???@\?6?>+?Fa?(??r?7l?m?]?=?<{??O????z(7??51?(?7q??>????????F???L????d????N??m???,??#????????R?"1?e?W?K?n? ????????r? ???|?5????w ??+??`)?????'??"L??XRF?i"dv???&???4??q????G???xM??B??D???'? 3??n~?Kn??`??O2'?v?J[?P?et?a?S ?c??u???&?z???*??6?q?????6????zX9? -D/?????.A????C9??G??=*D"???-??S?? ?}/??o?l?Rn??,F0*???h7????{?f@??g??oj?}??????1?k??????????e?X??????????V\????o'?????mGA^??BZQ?2Q[$??Y??$?56?$0?p???=??F?e??w??? >l?h?C??????w3a??'??r?a????E??V?q???k#"&?]?D?f???c7m -?b?k9a?vQ??;WiG??0??7d?,hb-=?C"??G?/?.f?~???M??7????b2i?/???G:5???OQ1A??b??Uo????p?7?hZ???>K#"?Z?BD????I?7 &^ ?#??s> Pvx??[??c????N0qA??.r?3o???>? -?7?P?[ -?G?}[??????{?);.h???*#(R%1???e??[???}??lnJ`/??>[' 6??? d????<?-??????WIL??0XG?:B ?A=????2??Vi??+?w?al" -?ce6b????)?d??w-k e?Dz????Xg??,5?{:??X????"?ru???f???#?Mo?Y?Y>???U9+??S????sds?,P?X??YD??????Q??y?B????BX??z?R??,6A8?U`?Pj?) ????#?-W?9x??v??L??J5?)?5???>O?l??3o ?;??lL??????H?W@???e??4?"???T&??C??]?u?x???HCjj?]?K??f -\q\?9OX??*8}?????oZ?^?6A7??F??g?????t@?/.|?`?`???@L?z?k?af???uW?h?g4??p? -?$x?r}???zhs?SRWCu??}O?????????y??????.??~????????Uk??????*"k?m?y???SjF?:i???? -?t????g#??gM9?&???????[?a?8??WB?t??8:T??'?,?t -4?$????B??????]????x?q>oA???.g???G?c)?'y@?Vc????<|r]??> -90?!?q?X????xB??b?????>rV????9????)9?'?F?????Om[???Z?]5i????? ???????/?\?h??$No at l???????m???f?UT?A -?????Ot}G????t??P??'N?-H???::?k -?f -m???aG????j?q??????*?b ?t???7?dR`-???)??? ??"??L?????: 5l?????bNz????Dn?-c}y3??N?:?1?????(?jP[r??N?Y?bj?U??c?Eq???;,u??/??1?F -(???u????*???L????????zTP?c'(?? ..?S???2?B?qsV?e???Av)>?? ????` o:;?a?E???n2??? - s?+??=????? ? ??,:????????7???2???|?uhg?P??A?????e?z?ZL?q????TTJ?????x?????? g*?^[????~??? -0?6e`??[????(y??s?oBD????o?>b^? ?wP5?!?~?9?v????LZ??By?Q??????4S"??pL??H??????$????V???????????????KpM?D.??l -?kg?M?H????'?X???????ym\W'?}??X]q?o??;T?b;???\b?Ve&?i?>???q4?&?7?????+?RO?|pNxO???}{??f;)+G??L?? -w??sej;|)?????? ??????bqP??U?.???]?H?$??;T????Uv??????3$?d= +U+ ??1?Lf?+h^S??R_v? ?H??.?8?z????S??H?yf???!??S-??9????????6?p?8WB?9? qI?7"? ??????2u?]? ? c?s(?q????????(???????s2f???i??~??O???????Z????Ul???s?D???9e?y??*?(O.??`$???pPx*a??z?Ej????|A?B????sB|??G??>%?(?????u??2J????{O?K4? -?0?????1??S???i??([|?"?^???GOa???K?d?D???E?[????;7???'?????]?>?YV???????"?L?+m?v?jCF ??-?tIx???R???D?`GM? ???K??N=~?*?P,? s?u?E`?5Uv$??4:p??w????????,???!?c.???zK??H#???i??????=?????[?(gEc?mW??ZF%o=?J"-????M???'??x7? ^Zi?B?i?pA"j???"???!sd?S[!????%s9\?E7??@??mDi'N??~?-?????fN?x: ?/???J?j?????^A???3O???,?zm?b?K^'??????e=??J?E??D??Y??+?[?Y?????Tt?` ????s????`????g??B?=??0??'?????*????{????O0V?t\?D`?+ I?0?Ao???????kR(t???9j?k+h$Z?????W^??l?D??%n?\????????0?EPbN? [TRUNCATED] To get the complete diff run: svnlook diff /svnroot/chnosz -r 404 From noreply at r-forge.r-project.org Fri Feb 22 04:45:31 2019 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Fri, 22 Feb 2019 04:45:31 +0100 (CET) Subject: [CHNOSZ-commits] r405 - in pkg/CHNOSZ: . inst inst/extdata/OBIGT tests/testthat vignettes Message-ID: <20190222034531.80A2F18C0CF@r-forge.r-project.org> Author: jedick Date: 2019-02-22 04:45:29 +0100 (Fri, 22 Feb 2019) New Revision: 405 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/inst/NEWS pkg/CHNOSZ/inst/extdata/OBIGT/SLOP98.csv pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_aq.csv.xz pkg/CHNOSZ/inst/extdata/OBIGT/organic_aq.csv.xz pkg/CHNOSZ/inst/extdata/OBIGT/refs.csv pkg/CHNOSZ/tests/testthat/test-util.data.R pkg/CHNOSZ/vignettes/anintro.Rmd pkg/CHNOSZ/vignettes/obigt.bib Log: OBIGT/inorganic_aq.csv: Add/update Ag- and Cu-species Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-22 01:18:45 UTC (rev 404) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-22 03:45:29 UTC (rev 405) @@ -1,6 +1,6 @@ Date: 2019-02-22 Package: CHNOSZ -Version: 1.2.0-12 +Version: 1.2.0-13 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/inst/NEWS =================================================================== --- pkg/CHNOSZ/inst/NEWS 2019-02-22 01:18:45 UTC (rev 404) +++ pkg/CHNOSZ/inst/NEWS 2019-02-22 03:45:29 UTC (rev 405) @@ -40,6 +40,9 @@ - Move Au+3, AuCl3-2, and AuCl4-3 back into default database. +- Add/replace data for Ag+ and Cu+ and their complexes from Akinfiev + and Zotov, 2001 and 2010. + DOCUMENTATION - In demo/NaCl.R, indicate region not considered by Shock et al., 1992 Modified: pkg/CHNOSZ/inst/extdata/OBIGT/SLOP98.csv =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/SLOP98.csv 2019-02-22 01:18:45 UTC (rev 404) +++ pkg/CHNOSZ/inst/extdata/OBIGT/SLOP98.csv 2019-02-22 03:45:29 UTC (rev 405) @@ -1,10 +1,23 @@ 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 +Ag(Ac),NA,AgCH3COO,aq,"SK93.1 [S98]",NA,17.Aug.92,-70840,-91650,38.9,72.5,48.6,8.3987,12.7257,0.7485,-3.305,48.3694,11.73,-0.03,0 +Ag(Ac)2-,NA,Ag(CH3COO)2-,aq,"SK93.1 [S98]",NA,17.Aug.92,-158990,-210560,49.9,164.9,103.5,16.2287,31.8418,-6.7592,-4.0952,110.8373,30.5473,0.8741,-1 +Cu(Ac),NA,CuCH3COO,aq,"SK93.1 [S98]",NA,19.Aug.92,-76770,-99970,28.7,85.5,40.5,7.3009,10.0483,1.7946,-3.1943,56.0175,14.3883,-0.03,0 +Cu(Ac)2-,NA,Cu(CH3COO)2-,aq,"SK93.1 [S98]",NA,10.Sep.92,-165000,-219740,37,190.3,94.6,15.0715,29.0205,-5.6592,-3.9786,127.5564,35.7339,1.0691,-1 +Au(Ac),NA,AuCH3COO,aq,"SK93.1 [S98]",NA,10.Sep.92,-49870,-68310,48,56.1,61.8,10.213,17.1576,-0.9969,-3.4882,38.7432,8.3843,-0.03,0 +Au(Ac)2-,NA,Au(CH3COO)2-,aq,"SK93.1 [S98]",NA,10.Sep.92,-138240,-186750,61.3,132.8,118.3,18.1917,36.6392,-8.6534,-4.2936,90.461,24.0193,0.701,-1 +AgCl,AgCl,AgCl,aq,"SSH97.1 [S98]",NA,16.Sep.97,-17450,-18270,34.1,6.7,25.24,5.2088,4.9399,3.8015,-2.9832,9.8168,-1.6698,-0.03,0 +AgCl2-,AgCl2-,AgCl2-,aq,"SSH97.1 [S98]",NA,16.Sep.97,-51560,-61130,47,7.8,54.37,9.5149,15.4544,-0.3312,-3.4178,19.185,-1.4457,0.9169,-1 +AgCl3-2,AgCl3-2,AgCl3-2,aq,"SSH97.1 [S98]",NA,2.Oct.97,-82710,-105613,44.5,10.69,86.82,14.504,27.6363,-5.1192,-3.9214,35.8339,-0.857,2.5402,-2 AuCl,AuCl,AuCl,aq,"SSH97.1 [S98]",NA,2.Oct.97,-3184,-2140,41.47,-9.83,38.61,7.0357,9.4008,2.0481,-3.1676,0.0551,-5.0371,-0.038,0 AuCl2-,AuCl2-,AuCl2-,aq,"SSH97.1 [S98]",NA,2.Oct.97,-36781,-44725,53.6,-24.52,69.26,11.5192,20.3482,-2.2547,-3.6201,-0.6764,-8.03,0.8173,-1 +CuCl,CuCl,CuCl,aq,"SSH97.1 [S98]",NA,2.Oct.97,-22608,-26338,22.06,19.64,17.22,4.1084,2.253,4.8575,-2.8721,17.3292,0.967,-0.038,0 +CuCl2-,CuCl2-,CuCl2-,aq,"SSH97.1 [S98]",NA,2.Oct.97,-58038,-72903,26.96,32.99,45.43,8.3943,12.7182,0.7442,-3.3047,36.7555,3.6846,1.2219,-1 +Ag(HS)2-,Ag(HS)2-,Ag(HS)2-,aq,"SSH97.1 [S98]",NA,9.Oct.97,0,-8200,44.68,38.1,60.5,10.3654,17.5311,-1.1475,-3.5037,37.2753,4.7273,0.9527,-1 Au(HS)2-,Au(HS)2-,Au(HS)2-,aq,"SSH97.1 [S98]",NA,9.Oct.97,2429,-2509,56.77,6.06,75.39,12.342,22.3572,-3.0443,-3.7032,16.8038,-1.8007,0.7693,-1 +Ag+,Ag+,Ag+,aq,"SH88.3 [S92]",NA,07.Nov.97,18427,25275,17.54,7.9,-0.8,1.7285,-3.5608,7.1496,-2.6318,12.7862,-1.4254,0.216,1 Au+,Au+,Au+,aq,"SSWS97.2 [S98]",SH88.1,13.Nov.97,39000,47900,25.6,-0.3,12.5,3.5312,0.8428,5.4139,-2.8137,7.5089,-3.0956,0.1648,1 -Au(Ac),NA,AuCH3COO,aq,"SK93.1 [S98]",NA,10.Sep.92,-49870,-68310,48,56.1,61.8,10.213,17.1576,-0.9969,-3.4882,38.7432,8.3843,-0.03,0 -Au(Ac)2-,NA,Au(CH3COO)2-,aq,"SK93.1 [S98]",NA,10.Sep.92,-138240,-186750,61.3,132.8,118.3,18.1917,36.6392,-8.6534,-4.2936,90.461,24.0193,0.701,-1 +Cu+,Cu+,Cu+,aq,"SSWS97.2 [S98]",SH88.1,13.Nov.97,11950,17132,9.7,13.7,-8,0.807,-5.804,8.0165,-2.539,17.9233,-0.2438,0.4046,1 +AgOH,AgOH,AgOH,aq,"SSWS97 [S98]",NA,14.Nov.97,-21900,-31800,17.2,-10.6,3.9,2.2885,-2.1912,6.6063,-2.6883,-0.3221,-5.1937,-0.03,0 AsO4-3,AsO4-3,AsO4-3,aq,"SSWS97.3 [S98]",NA,11.Nov.97,-154970,-212270,-38.9,-116.1,-18.7,1.0308,-5.2609,7.8091,-2.5614,-12.1352,-26.6841,5.399,-3 HAsO4-2,HAsO4-2,HAsO4-2,aq,"SSWS97.3 [S98]",NA,11.Nov.97,-170790,-216620,-0.4,-47.5,11.3,4.3994,2.9611,4.5853,-2.9013,7.9908,-12.7102,3.2197,-2 H2AsO4-,H2AsO4-,H2AsO4-,aq,"SSWS97.3 [S98]",NA,11.Nov.97,-180010,-217390,28,-0.6,33.4,6.7429,8.6835,2.3351,-3.1379,16.9206,-3.1567,1.2055,-1 @@ -16,8 +29,8 @@ AlOH+2,AlOH+2,AlOH+2,aq,"SSWS97.4 [S98]",NA,13.Nov.97,-165475,-183300,-44.2,13.2,-2.2,2.0469,-2.7813,6.8376,-2.6639,29.7923,-0.3457,1.7247,2 AlO+,AlO+,AlO+1,aq,"SSWS97.4 [S98]",NA,13.Nov.97,-158188,-170900,-27,-30,0.6,2.1705,-2.4811,6.7241,-2.6763,-2.5983,-9.1455,0.957,1 HAlO2,HAlO2(AQ),HAlO2,aq,"SSWS97.4 [S98]",NA,13.Nov.97,-207700,-227500,5,-50,13,3.5338,0.8485,5.4132,-2.814,-23.4129,-13.2195,-0.03,0 -Al(Ac)+2,NA,AlCH3COO+2,aq,"SK93.2 [S98]",NA,5.Apr.93,-207630,-249130,-66.1,72.2,-0.03,2.4411,-1.8235,6.4722,-2.7035,67.0012,11.6689,2.0115,2 -Al(Ac)2+,NA,Al(CH3COO)2+,aq,"SK93.2 [S98]",NA,5.Apr.93,-298430,-372080,-59.8,168.7,49.4,8.9971,14.1844,0.1805,-3.3653,117.86,31.3303,1.3918,1 -Al(Ac)3,NA,Al(CH3COO)3,aq,"SK93.2 [S98]",NA,5.Apr.93,-391100,-498280,-57,NA,NA,16.0545,31.4184,-6.597,-4.0777,156.5453,49.3293,-0.03,0 +Al(Ac)+2,NA,AlCH3COO+2,aq,"SK93.1 [S98]",NA,5.Apr.93,-207630,-249130,-66.1,72.2,-0.03,2.4411,-1.8235,6.4722,-2.7035,67.0012,11.6689,2.0115,2 +Al(Ac)2+,NA,Al(CH3COO)2+,aq,"SK93.1 [S98]",NA,5.Apr.93,-298430,-372080,-59.8,168.7,49.4,8.9971,14.1844,0.1805,-3.3653,117.86,31.3303,1.3918,1 +Al(Ac)3,NA,Al(CH3COO)3,aq,"SK93.1 [S98]",NA,5.Apr.93,-391100,-498280,-57,NA,NA,16.0545,31.4184,-6.597,-4.0777,156.5453,49.3293,-0.03,0 Al(Mal)+,NA,AlC3H2O4+,aq,"PSK99.1 [S07]",NA,24.Aug.06,-289589,-331497,-16,-17.9,0,0,0,0,0,2.2763,-6.6807,0.7895,1 Al(Oxal)+,NA,AlC2O4+,aq,"PSK99.1 [S07]",NA,24.Aug.06,-286615,-321675,-25.6,-25.8,0,0,0,0,0,-1.0645,-8.29,0.9437,1 Modified: pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_aq.csv.xz =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_aq.csv.xz 2019-02-22 01:18:45 UTC (rev 404) +++ pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_aq.csv.xz 2019-02-22 03:45:29 UTC (rev 405) @@ -1,4 +1,4 @@ -?7zXZ???F!t/??????y]7I??b???9??????TB;q?"?q???cL;?"???#y*H?????3???)?G?Q?h/;;?;??S????? ??}_?i_???O|?? ?%1s??????EP~J? ????\??F? ????fK9bV???w"??o??{p?????s?????tdYN?03????Y??O?W.2?w??)Y0????z7??8?$??G#???2???4]?$???O??????Pr ?+ -(W???N?t???;???????????3??k??=?u???}Dk\4??????d[Y??????!?_6???????z6??Ng?)??R?V?m9?????2??+?%???????H??|@??.??????h??zf??yFb??~?wu????TR?-???k?Meh]p0lg?? 1????g]RL??w???????6>?(?.%9B?c*gK?8OJ7oew??? OT??C???U ??????8???nf?R??C>??Z??%T????? Q???x????q?\???K?X?????7^C3?E?????0???{2??S?????t?s???????????????Df ?:??????G?I??SU!? hr??;4?y&?O???t{?K?}?N?[?????=EU?0-g -|??gz?0?6v0 -??c?F??\?^????????I??>E?K???&?SKB????/2??U?>,&?M?V?]???h'D8(?K?i??I??DYN??"???&??7????$=??[??s??????????U????@(Q=?h_??#$i??y???N??r??J??\r???NR ?[ -??i/?=e/v??[??p???@h?=?h?! ?AgP???3?U 7k????8??,c|?,-_??O???????m?O"A'?{???????_???p?"?p?U=??O????hG?? ;?????????]??Cr?O.?q????u~??W -?gA]2x?_???Sg??X??.?Tb????/i?i>????l???W?r??K???9?????W?]??????jO? y????X?> ???R -z? ->e???????k??OA??-???,PW??e,???`??????Be3//?J??????mY>??m????f!??7#z?>t???'g?f???V?E??????T????JC?p?s?IK02N?.???a?E`??J?=????q?8?d?j??Y9&(?am?@???FDK?&kM@?L??+ U)?[r?vu?%?;?U??X?CM?????tWN?7?-#8nwk?.?=??d"??mI>h???]?K\?????D?V,??P?l??C????F?[??5???) ??]???M??]}?8??Fq..??[b???(\??1???WZy????$?_!.j~=W???M ??`?X?????`??VCGC0 ?.??`??M?D????? -??Ts5?u??,???eYxG????~{?4[ ?U3??tYM?lj?.^??ky?2?73|M????c?H??I???z??CiLK?9??< .????????j0;U???9?Gt??ne $?D1??w??[??????n?Kd??T??3FP??gZ?H?? -?s<@??bUbqgk????Y) -????????~??U)??Jy+U.?R='lC??e??H??^???_G??}?[U?D??z???^Q?????????l??(J??L?/!4?? -nY?r.r2?Z?[^G?t{cFv?[R?#"??}?|?cF?(wwT?J?7T?Ae???4??,_ ????w?W?q????^?1??i?????Er???hT at X??s:??O?@?= -KtA?V(?$+??Wx?????????C??18???????? hh??}M????????u??J?]c???l?FQ???'???9U???qK?&????????+????5_qAXs??K??v?M?b????w?hc9?????%?????X._>????????bsY$?Yy???????8???Gn??l+???s????fm???/? ????g"x???x9??5V?>??'v?"?^LM?3?,???^?????wz???3?M2???{??*??0????~??:?m??X-3???Wn??Y???m??/9??.q?M%P????x ?Xy.??"??V????Z??GV?? - -?L?W?aI:??????v?m??n?.????i^?z??g?d?x?R?r??^?P^#??!ayz???????U???p??9??r4??l?t?V?O@??????q$???y???\??]??>k?%???L?ci_??????_3nB ??????y??l?hhZ -???B?H?>7m??????0/???t??_53??=@!??_??. ?F???m???"?4? {??l??|=????B?+U -M* -=g????" ;?*$ ??=?m ?P ?;?s??m?h??"9?B]P????t%IB??2V?? -?N?K? ?W????vX0s??)???k???.??Y*????O? 2 =??A?2?=?)?#????1m???*i???q???? n???@Tx???I?^z?%CZ,?7?[??b:l]?Q??O1?????3?J?f" CX??,??????ytb?Y r?>????7B/?????f?? - 7=eW???E_g??*?????K?R?????c?Z6?[,?p?4????_I???.?????6??????A???????u?[??5?wke?k? ????]??? ???4? ??Nj0 A??B|??d?Z?{;?wh?L????a???z??5q??r3?? -?N???w??7????[????W:7L??}? ???~zH?f.?+D8???h?>( ?? Nz(??wL???@E)+$?[???g?f??;?:[z???3r?CX?1??5N???K?cN?&?????*x???q?????_(?(P??"gY????_v.](???? B?????RI`???4?o??RBK?Z%i?"?%&9?j???????2o?m??DO8?v??????$T?\M?v.8g???p???o?Cw????b?z?p?lZiq+D%f?_???z?5? C??Bt??L??{????Y?P?f?\n%9q??M -?fj?c+>??[ &?5vU??k???)o??p7???#???dvs?#B?sNM??j?r:??lz - ????A??|#??$??X#???Sm?n??^?z??S??k?$?wn3?? ??/?I?([????a?dYJ??!?*?' ?s??k.6r?3??yZYq%???J? -^?L?F?z[~O????w??D??? ?????f??*???P???[????>?????}??iE1|sF9?+?I???1{????KA?????c(??7_?a|??{?/?H1t????;o??W????C?j?{??,l?w???mdQp??? -??????s?Nc??;?s? ?????+????h?\OC??O??=?%???J?pLa Z?zl?F?? ?<??1?e??g?????\\m????i?$??_????o# -??? ? -N?A????t??S`Kn{A?k)???/????f??X???NM(?Z????@^?6??"?g??M}b? -?m??Z??Jp?O??p?-??cWw?.? -.???@???_8T??P?R?L?(?yV?,'B???}??rV?@"q?+??d">?l{bBMaQm1????_}:?j6?}? -?`???B?2Oq????# Ej?J)??????????:8=?[/Z???n?? KW;?l?i?0???.?????-$&??#????|E??bj1??;z???p??Ww!????q )??b?8N?aA=????x?G?E?S?????6Z???+=-?X??oK????eU??W???3d???r(????In?U???>)? ?????h?6c2?iy&??+??????E??d??(H???[19??y^??pP??? -=?%???7K+? '??????V!??3$???f}???\a??=F????Mrt??yJ??????d??u?????b?W????"????D?3??_riR?'?7g??/???T)??????Q?|?*f8??dD??_???M??$(H?"?Q??a%?????)?????q??E*?? {?? Bb??????L?L?{??QV????l?>";uXD?????L+??>? MDF?o?r?? D?0?R?-??0K????ly/?>?G?E?*??wc?]2?6??0F??F?@?0?I?? "??h??a??m???o??????????????E????P?????3/???O???, ????u:?1p?????:?|?u???,??J??ju%Ywl????q*'???eVL"?Q??CX2.???? -4???9???_U?????)E -?x?f?Z?????? ????Jk???{^q????y?r?GxX2v]?%u??C????QTD?? ???V?#p???q?&@?]?r?f?N?=*+??g???????& -bE????? - ??S<;???]^V?6?6?j??>?????i ??w?&?(?H? ?T??3VPP|?6??? 5?q???D?e/??? -e?\F?g??n?h(?;???=qG??D??Oe?$">??FG=?8L??:?2MO??b?z?XA*\????????u??}?%?LJ~?|;??%???*?V%0 -8??l(?C?? 8h?q??????????_v??A6vE????!??G???Y??h?]???9A~??E -|????.S ??Bu????? SvCf?7uR6?Z$y? -*:??;?S?t??Ms|?dx?@????a?vnEu??x?3?????r?????lT?E??8_???W?Y???Y?-?????e?J??????t+???x%KT'?kc?v??Z????eOP?_ ?02?????4?#5???.7M0???w????MX,???:6??E?z?^n???&?q??u???????????rqt 8no??+c??-?:??????Vn?6??p? ???nc?>y???"|?W??|??7??????,7?J??BI???????W???y?m)d???t?H?L??+ -A??7fL3???????-*????7???Cug?/????f?R4?|IX?z??<@???Z??%{1???? -?l!?4T? g?t?????"???}?`|? ???(T???.?L? nxDW??Y?j) -?Cq.??t?1+A?E]4????Q?? -?+??9o???????c?\??J???9?kPf?g??q?p7???8?YD6??+??)??;g?????d???%x'2?"??X?????aW??H?*??jr????mq????i??y???8}u?{b????m?[J????Ow?0i? -?????tY?o?u7??Mh??c?r?e?????????B?,??KH???????dI?`7rq9????tu?[)m??2?Q?5J??F??????-w6?N;??g????b=??-? -?i_2#-???????H?g?:? -.?P;??U???M??z?$????p??xH`R?pTvrCN?? ^????Rz^>?[?Rxni?Z???x -???4l2??H6??a?%?w?_ 0>? %??&????\????????S??v??b????b? ?G??? ??*?}A?~z????9^???l?p??I?%???[????????%???A?d???/Vl????? -?o ?????e7^/ -[???1?1?z???|??.{?? "w????7-t???v^????N^??'m???t?GQ????= @? -Ha??Y??WUb??3X;??f??)O?}C???xq???i?+?? ?#&?????nN?? ?T'?????9??r?A?i? R?u $+????=???/?ji/ ????/5i?&???-????,?(??N?F?XZ?[?\??$??&ws?\?~[k?5?`??t:?lJ -?Y???9???isT??????Y-??D(7?I??jT ?0(~?!??T6s -?-??;r??I??f@?%?D;yT????j4??k???> -??? T?D??ef??6q?\????0 B|\F???U=??,BSj? VM??dc3?v|??k?Cvr2?,???[???'?? 6q???f+??eU?V-:?p??????o?L???\?????#?Bc???f?9LB?"??j1???????????W?L?7 -Z????????i?7Z??P?@?7oAp?2!I???e\???M???g?r$??9r}?? -jYu?c???????44?M????????1??=s?S??Z??Vm????? ?????^??YZ?u??>???Pn?DP?B????$?;??n???2???? C???Z???B?6?D]{??.?????E ??????yM????????KW?I?nq?U???K?B~eaI,q???????_????]??5?"o? -?m=?????R?G ?n#t?CocL??8??|???Ed6U'???}[I[r?/GL???j??A???-~?s?t~T?i??x??Z?^?f=?C????MN?$4?????L3??K?8?G???M?P1?.~dg:a?t? L,???&????Z?2?[??_?Ok?A??o??jokd????c????W???nO??/}N?[?U????#???1?????M???J=??i??Q0/t|5???c??f????????x_??????P1???????{??_????CP?E?R?>????????*?u??J?4??7?yuLwT??_J>??U ??~?r???@>?SEb?????*????? 1?j?\??`??=?Z??0??"?????c?V???73zJ=a???? ?R?1&[? ??#?(?'?????a?1??>??UFU?%??@!?p?jw????SW?8??|??Pa?Zv?Q??"3?? -???d?a??6D2Q?t?C?????5Z?XC?W?u??C,n;??Y?2??>?G?@???O?yGk??j$X?&E?4 ?????mAV??B????e?????u6?>?`????]dbt)??fX????1??}w???1s?_???2??9]L"?B??C?n^?n???R4V????j ?t?/??6?+"??y.%?D??$?@??z&??z????^??!4Z -'-???_V8?gMA?????j?VS?!?M??9???-kqH`n???????A?Y?????|???;?Z`???g????B?H?????<cBMp????r??8-?????????O?9P`???~U?????HT?(5?8G??? k?/???|??????????D???9C????x ??!??zw4*???!(??K?A?!??* l??"/???????5?????????t?W??D?????M??c????8?z%?q? -?]?I??t??????t?h{I?????[??3?4%K?/.?? bg?>?8;4???d???6?1??????A???F??~?z?YH???:h???FUT?qy???I?+?????KW????8???[?.G??F??Hx??W~??-U????L??u??a?HO???V$a??????5?T??+?.A????H?????QGI?t??????? -k#??@>?'3??a b???????X3? %V?7???? yEgGD??|F?3??a????? ??? -??.k?}s75???d???w??q?UY?p?????YX5?m??^hU?|"???-Fg???9???# ??v???V????K?????h?????? -dS80?>ev?mb?9?? =??f??W???{???C?i?????????mE+! 89?? ??[x??1?v3?k??l?M?>??G?m??z1??%?MhK"F??Z??O?Ed8/??+??X?4?N???yn?{2:a[?D?J???6Q?? -??Z?L^?|2????-???"??3?????m???@?:?????y? ?PH??T????????C????????wv??P?C??MPJ q?y??????j?~?h???S^??i??&?v?q??l?C??P?????[r?I>0?K??????f?{r#?j??????}?[?:^??6?,w#???????????oPrs?2???????W?Rq Lhl?j1?qg+?w??QMF!NT?Y3?m???.>?`??u??ra??L???2MB}??O???5a?z?b?Rf??"?????,???????q?.q?"?????{? ?w??????L????cVpu3???x????Z??????S???????????H?aHE????r?5??`??1?y^\?%vD??b?????i???3?e?,?H0??tH@?} -????/BO?i??V_ ???9J???? h2? -?$F?6?zka9*??^????g??m?F?szP:??y??y?N??(?r?6??????? w1?Ip???|?7@?q?7?zc.i?? -?m??1??(?[?>{@??U]3?G?w?l ->?x??????v?-???(?w?7;?u?_??6??????;o??r`8?F?J?f??<6NYu?IPdH??!???????o??B 4?A?D??`w???\Ra?p?98??"??Bo????6lT??????%??;???T2 at k??s??n[??W????????[?L???*L???at&v?fc?y?5W?;??Z????f??}?????k????l???n?? xHB1??/0?5???X\"TJ?_????4??f? -`o"?K?B*G?? G?? ?r??????K??????ES%?8?Z?Y???q&?`YE??/?i)8?5???????b?N?=?#?? ??j:?m?9WP???E@?Hv?+?E%??m??q?s??*%~p#???{?U?2?v?c???v??kB?I??? -4UZ??8??n~?Xp BB?f??b?,v?}A1.4????????DC??q?e4aLpI??3???6?x???k ??@1?????#M?Nv1?m?\5?R?il?A??q?J -?#?"???dG??j?'?a?\??Y???????IG??1 #&B?5????D6?F????a> ?4?N?c?h-????????JY -?]???$9????U?\,H?*?V??1=!E`R ?????Z?????,?|?a?n????????^8??N!????J?{v$D??"???i???????????3?1w??I??;@/???~9}46~?r??'R???????????KGu4'MFHSP?????${???r ?c? -???`+??xa???$??? ?*?? ?U?]??R???v? -.??#?:???????LEWT?:?o???_???)??^!???y???^?7,_p ???Oe]~????D31H?F1????W?????n?P??-#vOA?U?d??IMGx]????????d?k????? ???K?^?? ???%?L?v}k???v?qc?K?????"8?&?}?@??w[??A?????.t,e??????Q?~]??*Z?/?>???;*?+ ?8??_"n?{?}??UzVF?;s????????(?? ??)?@???????j\? -HqOxL d???A4J???- ?3??CA#wnF -Y??"????+ g??X?j??w? ?~?DXN?`??.???h%%?N'?XWn????cU????G:?(?B??y 4%N&??o] n&??K?^or?|?????9?kNO?n\ _??hd?!?[??E ??/?%?X??^?????d???B?pH-Cc?5?W?Md?? ?,?L??e?X???8????????m?7|? -?V????O??,U??m}? ?Te?????KZJ'D,?J??d9??B?{??D/??????? >*#? !r?c??????OZ7?\???"??/??EN????!??????'z 2?S~?X??????tn?$a???????p? ??k`?J,c??@G??a??^?????77Z -?P??4?pVC?i?~7~.??:v??^x7qNv.?i?,????/6?%?????Fb6h?G?|pCc??|V?~??v?t????2?:$oed??b???~?>????c?+???{??;C?{'~w???&&2a?#?A???? y??;?????qStd??'???w?f??{0???*?e??fZ????D]??q??2[???????C9??$??????T@?^????5 ?$G3??????#??N?3?H?,??????V??f?:????Y?&\=??D?????f$V',,E??c??7y?Q=?>????P?Hv???iv?A?@??(%I??X??*??0????gGc?YC ?c?}S^? -\?????%\???6?????????~???????U?2yl?/??O13?Z>?oI?r??X5]pm;????'m4???????i/_ ??I?7??#?? -??Nw????qu*^????$?t??u??-? -???,{?2b?3?0Th#L,?t???V?????V?ft ???F????#I?jj?2????\2-J2?jt4t??K??1?-;j??? -???l?8?sX]??j????J+>[?K/Or??jKt^?%?.m?o??N?v??0Bi??;??&P??muX at N3?????N?)?????9??hQRq?? -??[??R?????*?$?5?T0??D??a?_??mm8?}iP??y|m ????h??0+??0Y?m?????'??????;?3??&?????e7L?J???e?b0L?,uy\! ?YN??????H ?&M??_????x?0????_V\?|?4?=? ?#?????N?????d6n?#?k?*?K?????D8%???UQ:?KPc?3?@dc?6?v1Qs??H6WS ?f??g?db?6/???c?o?? w?L??5???^?C???A??kQ????#?Vj!t?????7;,^<.C?I???????*???]?S??P??d??" ???e1??+e6p(??p?????? -??K??]w??<-??DG*??v6dms??K?Pg????ef?W+m??;8hK?rX\???a*=lA.???K72??'??e8 ????sR?x?????8???F8?????? ?????*??@??9?5??g??B?F????????"??J?vcy?B???J*3??O?`=2????x?f?Z?-.?AO??4?????{?n?v[?q -????S???_?Q)?f?S????eN? ???X?~?I3d???E??&??\)@n64?J??jyS+JM??????+?8.?E?'?JQ?3[?)=?d&?t?/??b??7?#??9??1??R??+?KDn?tw??B?o??%[?-?????j???[i???T??&?l8Q????~???r???~??lz??s?-??[?%??#?A0?^?P*o??c-?j??$??/?{r??J4????????L?$?{8O??4????5?B??&??4????\?????l?9? ??p??s????????u???2o?yb"??=:E???c?%???#??????????;{???????xu???.#r?{N????????'????R?Dw??se?K????Yp??? ???S??l?Cgw??????1D??*?????S???s?????@?18??6h???e?oR?5???*??s(Rj???t'?+??4????? }?}?ukE ???? -???8???&?_O?PG?vN??uT?9??JbL??V???,??/??x -??Zi?? ?=?H?e{??P1??vx?7?????WUg?$??px???8)?N??????`?k!???????????{?n?bW??@?@?\??l/B????6?3G??2]?e^??5#?)???- ??v?g?G?e?M?@??41??q--???j???*?B??RH?e???zY???A???2?X{?e_?????????h??o??=?????5???+???*&?7?? m?'??a?#???hZ?56?}K???Y?k?????0?#|???!?#c}?&?7??S8?R???$?XE??X?? ?P????????GI?/d???q\n?????(???p??????$G[?D}?S|U?????MF~"H??(gL -?!??(??~??E~+M]0??Q?F????*??(????HE -L?!bOQ??c7G??^?O?????f W?X?DZ????I???(`??a???D?7?y??f?G?E?1[?Z 0b:???+g?!k?]??w ????O?{J1?%????-?!?"V???Q3~??|a??@h{r?j93???-)?*Fk;?MF??G&??W ?????t?t??o?=??E?WW?????3iXp??_?????w??7??r?g?y?>yU?????X??6n??~????Y??ZL?y?E??cz????E?6y?7 !? -v??a??'?????OG)3????p??sO"?D??KY+ -?-&???W??Z? -q???%?NS?.?m ?????r?r?0#??0?[N???????=kAa??S??1=????i???Z???>???]z?R?of -?x=u?t8??7#p<$??z -????/???$^fN??.s?f?K??????e??{?????';??rK??g??>j.??Ej?.kP?9???Y? ??????S?&????\?V???G'???y??????9?+ -?E??{S?|??4h1??]??H{?<?Y???,??/??????4?g7 ??sV~?u???yX??%???v?Y?P?5???C;???z?&??7?C??*? -? B%h?E? -???????DGi7?? 9???M??i?hau/-????????%???<(????"$?]}?k??+?./F??>.????(? \?vbX&???+ ?? ????w????#GI???6????)??sKk?2j ???????4?Fkre~?+S????n< ~gqVN$XV?Ww,?W?7?7?s?|??_?y??mk?r?|Ul?|X7^B???>3???}???N?O7?9# #A???*?Kr+P2?g?????3???tf ??qd ?of??>p??sC??L?&S?\??B??@?????;?u40L6??|?i:f|9)5?6'?? ??Q?A???Q?o"????X?$??o~???w??M?????%??C?/?w5[????????K?Y9????t7??W??x?\?G?-??^!?:D?wr?0???To?f?2~????2\?E6??RHQ,????p?N?@F]doxVp2?C?.+?}:%?/ ???t?=B??C???2p?????v???x??????(????N?6????%????nD??g?????Tm2?_????nN?ah????\???@??*?? -????k:Y?q??OWs -??<8??????^???W4???S b?Yj??=?????HcJ ??'??7d??i ???3J?ih?W? -??????Hi8q?%???pC??&= (bmRF??L???PJ?|OY???te?D????lX?*?L?L???? l??|3? ?Z?7???AM????????x?-??>Z?E|????E??_?$a?4?? ??V?$6?????k.???"?c?2k??'D?!'\??t?? -?>??~?K?a?_????ES?v49 "R??E??{ ?6??????Gg???\3?M\u???{??DBDb${?z?F?xg9?VG????V?KA?????)?*^??,???????,?+????)??????t?Q??of??1?@&??X?R???? .?)?p??? ?g??L8??????Pi??dv?B???D???=9=Iw????G ?UnL????K?8;n???^?????!" ??hO.,???Y^???[???????^L"???ps?????T)?WT? ???F????:????]q??to???n?g??U??'s*B?BB??@C at x?e?B`????x???j(?y?A?g -?w?? -}???-|s???=.??Y???(???6?,?????U??!?/?M?a?V?{? ??? -R??*u??.??3????????"??v??7????Q???!7g?????}??H?,M??/??|:0???0??92?Oy??[?????x9O/??e?M???????~w????q??qg?%{?H????3?N?/ ! ???C??N?t?5S?]?s?>???*E?p??R?e?@?l? -pj? ???-??e*%%E?L??/ -???c??z??2??u?FC7?2??~r??????6???????%???)?EDA -z????*???a -$???}Acm??+_??Q????K??? ??7,Q???T???R??:?Q/???~ ?A?7&??u07? Author: jedick Date: 2019-02-22 07:12:52 +0100 (Fri, 22 Feb 2019) New Revision: 406 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/inst/NEWS pkg/CHNOSZ/inst/extdata/OBIGT/SLOP98.csv pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_aq.csv.xz pkg/CHNOSZ/inst/extdata/OBIGT/refs.csv pkg/CHNOSZ/vignettes/anintro.Rmd pkg/CHNOSZ/vignettes/obigt.Rmd pkg/CHNOSZ/vignettes/obigt.bib Log: OBIGT/inorganic_aq.csv: Update Pd and Pt species Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-22 03:45:29 UTC (rev 405) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-22 06:12:52 UTC (rev 406) @@ -1,6 +1,6 @@ Date: 2019-02-22 Package: CHNOSZ -Version: 1.2.0-13 +Version: 1.2.0-14 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/inst/NEWS =================================================================== --- pkg/CHNOSZ/inst/NEWS 2019-02-22 03:45:29 UTC (rev 405) +++ pkg/CHNOSZ/inst/NEWS 2019-02-22 06:12:52 UTC (rev 406) @@ -1,4 +1,4 @@ -CHANGES IN CHNOSZ 1.2.0-12 (2019-02-22) +CHANGES IN CHNOSZ 1.2.0-14 (2019-02-22) --------------------------------------- CRAN COMPLIANCE @@ -43,6 +43,12 @@ - Add/replace data for Ag+ and Cu+ and their complexes from Akinfiev and Zotov, 2001 and 2010. +- Update HCl(aq) with data from Tagirov et al., 1997. + +- Update Pd+2 and complexes with data from Tagirov et al., 2013. + +- Update Pt+2 and complexes with data from Tagirov et al., 2015. + DOCUMENTATION - In demo/NaCl.R, indicate region not considered by Shock et al., 1992 Modified: pkg/CHNOSZ/inst/extdata/OBIGT/SLOP98.csv =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/SLOP98.csv 2019-02-22 03:45:29 UTC (rev 405) +++ pkg/CHNOSZ/inst/extdata/OBIGT/SLOP98.csv 2019-02-22 06:12:52 UTC (rev 406) @@ -5,6 +5,23 @@ Cu(Ac)2-,NA,Cu(CH3COO)2-,aq,"SK93.1 [S98]",NA,10.Sep.92,-165000,-219740,37,190.3,94.6,15.0715,29.0205,-5.6592,-3.9786,127.5564,35.7339,1.0691,-1 Au(Ac),NA,AuCH3COO,aq,"SK93.1 [S98]",NA,10.Sep.92,-49870,-68310,48,56.1,61.8,10.213,17.1576,-0.9969,-3.4882,38.7432,8.3843,-0.03,0 Au(Ac)2-,NA,Au(CH3COO)2-,aq,"SK93.1 [S98]",NA,10.Sep.92,-138240,-186750,61.3,132.8,118.3,18.1917,36.6392,-8.6534,-4.2936,90.461,24.0193,0.701,-1 +Pd+2,Pd+2,Pd+2,aq,"SS98a.3 [S98]",NA,9.Apr.92,42200,42540,-21.1,-5.7,-19.4,-0.3631,-8.6602,9.1359,-2.4209,17.1907,-4.1915,1.5579,2 +Pt+2,Pt+2,Pt+2,aq,"SS98a.3 [S98]",NA,9.Apr.92,61600,60900,-23.6,-7,-21.7,-0.6648,-9.3985,9.4293,-2.3904,16.8028,-4.4624,1.6005,2 +PdSO4,Pd(SO4),Pd(SO4),aq,"SS98a.3 [S98]",NA,14.Apr.92,-139000,-173450,-0.9,-20.1,4,2.3022,-2.1585,6.5951,-2.6897,-5.8662,-7.1207,-0.03,0 +PdO,PdO,PdO,aq,"SS98a.3 [S98]",NA,14.Apr.92,-11500,-24320,-9.5,-4.7,-16.3,-0.4755,-8.9398,9.256,-2.4093,3.1356,-3.9919,-0.03,0 +Pd(SO4)2-2,Pd(SO4)2-2,Pd(SO4)2-2,aq,"SS98a.3 [S98]",NA,14.Apr.95,-319640,-388900,19.2,-34.4,27.4,6.502,8.0916,2.5759,-3.1134,12.9271,-10.0418,2.9221,-2 +PtCl+,PtCl+,PtCl+,aq,"SS98a.3 [S98]",NA,14.Apr.95,18380,10030,-7,21.7,1.1,2.3363,-2.0793,6.5718,-2.6929,22.821,0.6543,0.6557,1 +PtCl2,PtCl2,PtCl2,aq,"SS98a.3 [S98]",NA,14.Apr.95,-22290,-41110,0.1,39.2,27.3,5.8026,6.3859,3.2424,-3.0429,24.6982,3.5025,-0.03,0 +PtCl3-,PtCl3-,PtCl3-,aq,"SS98a.3 [S98]",NA,14.Apr.95,-57760,-90150,-3.1,45.6,57.4,10.4995,17.8547,-1.2658,-3.517,42.0877,4.0842,1.6759,-1 +PtCl4-2,PtCl4-2,PtCl4-2,aq,"SS98a.3 [S98]",NA,14.Apr.95,-91210,-141160,-19.8,40.9,91.8,15.7103,30.5792,-6.27,-4.043,54.1382,2.3994,3.51,-2 +PtSO4,Pt(SO4),Pt(SO4),aq,"SS98a.3 [S98]",NA,14.Apr.95,-120300,-155850,-3.6,-21.4,2,2.0253,-2.837,6.8659,-2.6616,-6.6457,-7.3916,-0.03,0 +Pt(SO4)2-2,Pt(SO4)2-2,Pt(SO4)2-2,aq,"SS98a.3 [S98]",NA,14.Apr.95,-300670,-371080,16.4,-35.8,25.7,6.277,7.5454,2.7833,-3.0908,12.5104,-10.3208,2.9641,-2 +Pt(SO4)3-4,Pt(SO4)3-4,Pt(SO4)3-4,aq,"SS98a.3 [S98]",NA,14.Apr.95,-480380,-588630,36.3,-50.2,49.3,10.5204,17.906,-1.2876,-3.5191,31.4399,-13.2501,5.9335,-4 +PtOH+,Pt(OH)+,Pt(OH)+,aq,"SS98a.3 [S98]",NA,14.Apr.92,1560,-10700,-6.7,16.6,-15,-0.0659,-7.935,8.8518,-2.4509,21.9365,0.3468,0.6557,1 +PtO,PtO,PtO,aq,"SS98a.3 [S98]",NA,14.Apr.92,-1130,-15300,-13,-0.7,-17.9,-0.6945,-9.4705,9.4567,-2.3874,5.4799,-3.1771,-0.03,0 +PdOH+,Pd(OH)+,Pd(OH)+,aq,"SS98a.3 [S98]",NA,13.Jul.95,-13130,-24120,-3.4,12.8,-13.5,0.1226,-7.4741,8.6697,-2.4699,19.2537,-0.4271,0.6063,1 +Pd(SO4)3-4,Pd(SO4)3-4,Pd(SO4)3-4,aq,"SS98a.3 [S98]",NA,28.Jul.94,-499900,-603950,39.4,-48.2,50.8,10.7074,18.3646,-1.4712,-3.5381,32.1909,-12.8528,5.891,-4 +HCl,HCl,HCl,aq,"MS97.2 [S98]",SLOP98.11,30.Jul.96,-30410,-42054,3.2,NA,NA,1.2547,-4.7177,7.6043,-2.584,16.7134,2.8727,-0.7,0 AgCl,AgCl,AgCl,aq,"SSH97.1 [S98]",NA,16.Sep.97,-17450,-18270,34.1,6.7,25.24,5.2088,4.9399,3.8015,-2.9832,9.8168,-1.6698,-0.03,0 AgCl2-,AgCl2-,AgCl2-,aq,"SSH97.1 [S98]",NA,16.Sep.97,-51560,-61130,47,7.8,54.37,9.5149,15.4544,-0.3312,-3.4178,19.185,-1.4457,0.9169,-1 AgCl3-2,AgCl3-2,AgCl3-2,aq,"SSH97.1 [S98]",NA,2.Oct.97,-82710,-105613,44.5,10.69,86.82,14.504,27.6363,-5.1192,-3.9214,35.8339,-0.857,2.5402,-2 @@ -34,3 +51,7 @@ Al(Ac)3,NA,Al(CH3COO)3,aq,"SK93.1 [S98]",NA,5.Apr.93,-391100,-498280,-57,NA,NA,16.0545,31.4184,-6.597,-4.0777,156.5453,49.3293,-0.03,0 Al(Mal)+,NA,AlC3H2O4+,aq,"PSK99.1 [S07]",NA,24.Aug.06,-289589,-331497,-16,-17.9,0,0,0,0,0,2.2763,-6.6807,0.7895,1 Al(Oxal)+,NA,AlC2O4+,aq,"PSK99.1 [S07]",NA,24.Aug.06,-286615,-321675,-25.6,-25.8,0,0,0,0,0,-1.0645,-8.29,0.9437,1 +PdCl+,PdCl+,PdCl+,aq,"SS98a.3 [S98]",NA,16.Aug.15,3310,-3820,-3.9,21,5.1,2.6729,-1.2577,6.2503,-2.7269,24.1532,1.2501,0.6143,1 +PdCl2,PdCl2,PdCl2,aq,"SS98a.3 [S98]",NA,16.Aug.15,-34080,-51390,4.2,37.8,32.4,6.1933,7.3404,2.8664,-3.0824,28.0429,4.665,-0.03,0 +PdCl3-,PdCl3-,PdCl3-,aq,"SS98a.3 [S98]",NA,16.Aug.15,-68390,-98890,2.5,44.6,62.9,10.9057,18.8497,-1.6645,-3.5581,46.9452,6.0491,1.5895,-1 +PdCl4-2,PdCl4-2,PdCl4-2,aq,"SS98a.3 [S98]",NA,16.Aug.15,-102130,-149470,-11.7,41.4,96.8,16.1552,31.6662,-6.698,-4.088,61.6845,5.4024,3.3914,-2 Modified: pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_aq.csv.xz =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_aq.csv.xz 2019-02-22 03:45:29 UTC (rev 405) +++ pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_aq.csv.xz 2019-02-22 06:12:52 UTC (rev 406) @@ -1,4 +1,4 @@ -?7zXZ???F!t/????b??]7I??b???9??????TB;q?"?q???cL;?"??c?J?\??~???Y?%???q??l}?Re??.5?B?o?Z????[*H}v?J?a*?F?/???e&???<????Q???h\4?>h;?h@)??fKGB!^?uuT??????????J?nM_?,U?%B??.E/?C?M8~?KDHq?U???E?V???M??j?u???B??*YX{%#t ?8oUp??nw@???8?u??WN?k?1??c? s^u1???iV????:?M8e?3??]?mB????B?9+????&?E????v9????l{)????`????=C??E?? =??\???[4w)??,??5#?H?p[ 2?L at W?H????B???)??DJJ??-?b ??><?g?????M!R??????eM????"|?4|??T?\\h???]Q? >m8I??E`??? 0???0?????O??=O????Y(L???"?? M?U?EJ$(? U2??7B???0? -?????????????m_?j????6_?>??? -???&??&1`?" ????g?r???? ??z|-??n?H??j????*???$?y????`t?/?0?[?$?.???T?h???? a?:?y[l???Q_??????l??vq??A???k????#b??HF?Q{?+[|Q??]???????-"??`??) ?Eb)???CEZa??0?B?]?w?dTNV??]??uQ?S??zn?|?T?<|*Nc?m???n?~z?R??????qMo?10o??+?]*???u??C -???!0?W?&-?L???~C7t?:??j?-??)]C??M?{x?a?)???9=???*@?? ?z?":=b??x?i?i?? /?DaXH0? ?,???#/`???A -??P??f????-???m~????????]???hx?!??k????+????]T.Bc2???+?&? -h??5?;?C-?M@?S%?5?[? fTi2???L??Z?????r?]?I?Sn??D]78 -x?t??I??N/bQ?$BD)???v??????B?K??ac??????????Ps%|??C?/??V??D?v?; -%\?h????r????????O???l????1?????|?6??>?M??G??h\RfK%6????????z??L?_b??9f&8?a?=????w?????m?A?:????p?S??N??t]t-?????tl??? ?z6???/5??$S??????T? ;P??YV?/?????????p??????BD?*??&???2:??~??,???}g?LVK?x???um???d -??5??????j?e"yGyF u?k???????e}Pq -?~?x?o?L?w?iA??%O^??X?c{??2?R?????Y.y?????j B??*???g?b?^????_??t16?? ?J????Y???S???>4?O??Ckb?!e?S7???????1~*?6??] ???z??3???? -?"}J?z'x?????S???=???a????Yj!v?'^?w?????G56?4????????B????`?zX?????l?????G?}c?k\????bP??h?w)????>8?h1?d#$Nk|?!???5Ecto?=???,oIDk?????u.?s? -?????u -???%???X?(???mq???IR??????5???g??7kt??N?JK`?????C??J?i\Pq?07??m???n?0"?P|?L'?]L????0j?o:H3xR?[?%Y??h???{??#?C;"\?]??:9???X?&':???????a???(?4??K?????g?D/?@{???`??Q?@??JrM?2b3Z?&???C?"D?&????A????????l?d???B??J?{??Us?%f"?s?u?,N?;??????U???3U>???yJ?~_&6?]?J?%$U?Tb??Qt(???0O?s?1?? ?)?1???(?]#?K?T ??in?????"?Pc?l???q????[. -????q^???s':a?x -.y?0B??+?Z??5???\?kX??5?7?????h? ?3???S+y??]?a????????=*+??x???????? :??.TsnT_??X???G???"?GRB???m6????#???]wn????v*?>E????`????zY?a?Y! OZ?P?q.?? I?D&????????z?D>g\??i??|U?? g?}??M???W?[;??????I?:?h5g???4e?.hk?????v?>??.????y -h_?????LW?????6N$X?>???? ?%4&?`?fp?]?Z??XuGa??.?m?I????fV9?????????>?HS???}a???Ct$:??Th? 3???k0&?kO; A?!?=?=?L??ex? -.E?X[wQ?0E?x??}uA??2??B?+?Z,?V? -?? ]?{!?E5?????x0?t?????R(?? ?lHs~????O]Xsy06-|8x??#??Z??D??9\F3?f?S?`c?R???|??t???????c???d??l?Ik??_???\???w??? -X>??????Pfw??????D?????w??q,???}?_p?#93XD?~@?$$?u4? $?v???GI{????7:j??(??FM?X?????5>?S8?1X??c?S4N????o??o`?Z6?6~`&6?|???[f??????rJ-K?a?=]????u?,??M??v#ku????L???7????????h??H?=?8X??~?+?f?????)?E???.V*?}D/A?? I8m?P?X??P"?"+?????????D~^a???}???@??????7M?????[c?$???p?K????Hw?????????&????"sI?v???$??7?)?P??????Lh?b??,??G^gK????"?)????IF?k?^U??U96?????UH???)??yK3????_7lCl ??g????-jb????86??O?B"??Q?????$??`?? -"?G??"????????9P??R???f???x???#b??O??? RS????c?No?b?F!,#5?C?~m??J9?d?E)?5Mr332y@?$c?`?~?};?|?d?c??????F?Ea??"9??:4?x|n"?!P[??$F??vT??@?Zl???^? -?MD?b? ????C????????????s??N?!?Y?????? -?h?2?Yn?a?9`C?[|n:?es??#?c?f&?l??8D??{????j?CRq???PH?f?w??l??7]??%??????EH?/??]?P????w????#?y??3?H??3V6? -??u??n?U7??????9]????KO?=?? -(???????[T???t???????%H?bt??^F??Q????Vs?$}B??????T8???k??3#?4?m?{L???E?k?'? +??>e?]??{A!2./???2$]`???l???F%????????(?Befru ?i?????l???d????' ?? +?G?? +?d???\???????_?Q???6?~c??`B|?c??1??q#??6??????Q? ~k!??????oi?Q??d1?F?`??????al??R?9!??[????@|]\< ?Q????/|o?(`????/,#J?/qL??i(?#6??????? ?A??!4??"Cn?:B?$P.?1?&?"0W???????W?6?]?P?s?43??cO?n? +????? ??'?v?C?#~i:l??+?-?f?[?????-L5???x?n????XE?R?~Zt4L:?B?!1k??.???5?????L? OK???3?e??#}??8??U?)$? ?d?w??(?9|?/r?'??";?" ?W?D????>YI?|?.?-?>?7?????loz,???l? ?/6*??m?N"q??TX?`Zn;\] ?????3~?x??? s1W?7SPe?H??????,????????i?s?1?b???????+????Y?,?N??!g?????4??I{C-!W?v??g??????S??PF??????I???>_?f??x?H??Uuc?\??G-???1)????&??.In?o???'?;??Te?????????-??*`?]???%?T?H7?0? )??C?E??R?]?1???????7,s??c:2 ?????2Rc?T??????m??=e???e???X:1? +? ??f???"8??(??q?-+(???y???Lr??P at O?)??n?zl?T??(?0?L?v!?+OYY?+B.5???~??=M25?,?8??&>?h???i?US>?z`?rs&?:?zuK;??;r(????5Z0pY"?U@?~?C? ?|? ?????!?9??a?I?m!???Oo???????-3??X??Q? ??t?c?)?}??iN o??? +??[?~Ru?+o??5T?r#a? ??? U?X +?\??%????q?)?!`?M2Lj?jhWZ?? ?? +q?Z?????L????;?k?<$"???K'?W?F???$d,????s?????f????MOmL??l/7???wH?d?B?W??-??:??`????^??`L??\c?(d?? ??|)I4????f???.????? ??%L??r??n?n6!???D?y?WY5,p?J7{???#??K???t???????,?1N? +????G?? ?????rzW????|????O???CZ??Ru? +??iU??L???=??Sj? K0??e?^???o???J???H??*?+H]y??*?L???V?jE??e????z/ -???7?????? -????z??DzL?C57??+????}??4????V??/?z????}?? -2??]:?hJ -O]??m?>`?-??^????jZ?VM"??ZFPH=????gCP??\ ???H):?h?L?v?+|???? ??E =??y?*b??~???0?4?|?qo ????,@???-k??5??$?W???p9????c????R???W??1????5X????^A#?L???l??Wd?y0?!?!???y*?7?;?????????>1??????8,G??? ??Z?jOL?IE?8c?L?????e2????f?(?Q???6 ?_?T???t???d?#D?1T?@?1!??B?F??B??a?S??gV??MS???&????.??vJ)}~kE?????????????)??????????? hf??&??????b ???K,?1????????5?nH?A????.z???????????3?B???TbsI?"????"_G??sR?????Q@ ?Q?X??ByrY???3!&?n? ?g? C(\???9=???[?o?9??4sbg??p%Q?@eo??5?%rA&??????n?9??-ygv?? -??]???5?P -?kP???????????}??U?(h?$???0?5?-z?c"=????C???F -5????B{??DEj????Fn?`???V??]91X?*[=Bnc?7??0???Jp??????^???M*?q???????fU??????n{:????q??????[?`f]?Y;????P???????\?? -V??w6^????~6??_R)/???.4Z????);9 xlJ????e?91???Rx?G+?L??@ -1K???) /?????z???b???????@D????P0y??????{?~?t?Zc+L?O ??H~??? ??az.? ]??????"??n?=jJ??S??/o???le??????xY??i???9A????R 'm?????????!????Q???`?F? ??i??-?.?? ?n?2?9????K?g#??DG?Zy?F8??????2"D{T?Z?q??B%'D4??V?_i?/???h#???2w?liG?F ?D??S\v?<???i?^2 ???????b??h?????dJ?"&$?p/?a????%E????O??$?S??????]{?C?@???B.%???qxRY??????a %ZQ?????E ???Bp???/?.??{???d?6?-??m N????@?`?O??w ????%6?Vs;?p?7?Q???????G*%?????QQ???e? -!?L?}M Id?k????7?????????????A?w?}"{?????^o4?k?p??PnjI???x???0n??? ?y?9??gbzx??g3=?xs}????dbX????????b??????hR??.f?????p??%]?B?x???)M?bD?????:???9+?10DK?G(?=>?7$ ????O?0?Z:L?Z -??j8lB?????y???8(|r???$\?xb??????l'??c??g???p???z????? -,m ???B???l"w.????*????*? ?Il?????Th 4??r? :3??????WA3???5$V??????? ?{8 q?:??v u?#?$:??T??_?q ?4??)?\??P'?^??H-V.Bu?6h??([??q :?W?? -0?J??!?^????=t???????3???? ?H???87??V.<?A\?/?G?58?m?5}p_???kj??gY8????W????6?s??,??u??N -N??-V??Q???i,??|?)6W??????????????2T???w??c? ????c|?E?'?A?k?iq?~k?4?kp???:x??4?AL????@??????U!?????v'?:?9^????wdt??F8????SW?P?f?>"e ??6??fg???5?X^7%N/?? ???(?Od=d?af??A T??u???N??FK????????u?0??R?a?"@???D?b?% &????g?U??+Yr?%?S }zif??????????:EG\?0?=???z$?xrj?aF?qH[-:???PZ]?T9?{u????E#?Z?T8?V???U}? 3#?|? m{ ??Lj??????gE???58?'vt?????Z??~???%:? ??X?t?%????\2???N?L?#K?????Za/??0??????y??(??$??????z?xr?????????O?FM,??+?I[?#???????? lA*:(?5??p?#??Po?U??????7?!???I?`??%??.Id??S?$???^???s3? ?[ye??&???R?=??5?Q*4?0@#??;zo?O +??{????Am??%.D???(?0?=? H??^;?i??p???)r???6p$5k?Z??J?F???o{?bR?[????`????A???'?e????n??KZ???\?Z?9??\p??*?`??A???????z2???xE54??"??f???:t:5i?g?(C??y5?? +?s???5{!k???(??"?~????O? +???_J?)??p?o-oPO??i??R?m +?:???*?? ????5? M?$ ?K?,cm*a?R*??????=X?0??9N? No?:??????????.?b?7?@R????C"? +Cf?$?????????2???????CkW?-?????F9 +? +? ?d?lp???*/??6?b?5]??? ??L?E???Cj?@=?vATlLZ8?q??c???r??D??&J????1v????xms?????{? ?K???V,?* ?k?9??0?Cu;???iV?? +t\????? +`S?of???I???;??=>?????z?????,=???Uwh?$??M?Hr ?\ +???2????~??;??|???k??~??]?????Hc????N +O=6O ???????te?RG??DT?(???T??'C`????????? X??w?|XJ$????K??9?o?????/?_6?C?y?m:???,!?S? y +V,5??i?+?1?p????P????o`8,HN?51???`A]? +???jH??p??}?)?C??? +???T{??0Sc???j?????cj???J?^??/???,??'?T?3??Bq$?xG???<&?-v?q_? ???2?>%B???`????G8M??-=???????)/?B?#??! +z???N1 at Y?f??????_?#K?pq??|??D??????????Y??O???[??K?fc??CN?????} v85?C?????_?oG?s?????? +Cm???????8??????}Zb_3?yi\.[??Z`???????Q2??+??9?????^??P??N??8?%R??I}m??Q??m???W?0???Q?????? ?u?d\??,Rd?|???F????=R+U?? }k???x?|?y0.3??zX?s?o?0I?s????K????????:???t?x?VZ??0??mbu??H ;?o? ?n??mh??>,aNc????U???gc$?!???ySG??I +??i?-ce?i\NJu??(s???o???Y????Tw7!??3V?U????'|???N_???;J?|;???\?U???=?OokrAG??bH +(???t}?BK?s?W?~s??c????e?????????4???8?????\v0??_???2??dt?4??E_A???N+? +???:??M]v??T?YA?X? +???t[???r 4?\5?6?^??%?J?`???H?F?n??????>Zs +??7???2?S?$EEAvI??????????O(??Q5???T?'!???L~4u?[^;s?\?K??+?????%~?G?`U?????M%??7Lx e ?=!^Z5?}C???????Y?_??#f???.??????52eQ/?Dre??????V????k4????re?/+?)????gdj?[PM?}?"??@?? ?<?>6??(?l???x??????h????oFJZ?6?X??ND?c??W?.T??W??5????8??A?G?*?`??5?p?-1Tk????7?????g[}q???u???R@HB +?4/B?B*??IP??$n?f????S'?k,YQ?C?$????? 2??8U?]??4??[W??????3i????S???w{???????1?;??%A???1?J-)??:??Z?{?z?[2i)$??]?'@???????S@|?-?????~??q? +????Dd?O???@;????*????&?p? +]??? +sh???_$U????&??'\??s*=xA'?[???N2?s?? hK?#\ ??U(?7"eR?1$?^??p?9+???b +p??;^DX?T?<$?}???"_?????2??????????*?XT?H9$?~?G??AA??}?'??E??/;?u???z?K?`?O*?lbl?Lt?8???=??G?qc);?o4/???????????????|?_??&???K?B??S2?y????dEr?1)o2?d>q7sD?5}?:^59?JWz,! +?;Ro??",M??4?F:s??nt>)? +?8%? X%?@??Xs`?p2Z0?????$&???????U???a???pz???????z?7?wq?V??R??O|tn}e?Hb?:O?Pp?-?,?[????[0???????pt??<???Q??????=A?????>?P??`???K. ?? ?????:?? +??o???@??<}??jDb,???EA??-,D???4Vl?Z?#?????pw?2#???~?I0??y????s?? +?O???{?I????s??C????Wq??!????w??_Y?d??tt??$~????????4?k?X???+??wE)??wB;?H?????S*f~py??? 4?+?A?<8n??07???~?%??"?q?r +@?{????]?Y d??g???y9???~??A????w+??cD????[C ?@q????W4??y?]TM?*??j(#K???SC???4x8???Z?J??>????|?!`J)?o??+G??'????B???5M????? ?$???Z4?=??A??`?Rm??_?dW???[?? l????? +S&7?\???B?;bF%??2??#??b??aJ4??l???X????@????Q?????|??1?Y?d??V?Z?qO??{? +?> ?5????2?????????@??+W%???e8?i^?1?:L??qx?)t??y?Z?qpo?w-u??R]7?{W~@?{[N??G?8????+?????^?`???7h??Sn +?????i??:?[?pf ??B?Y???]?q?k4??_???Crq?@w?DSI?C| +?????C?|??K:)?&pZh?y.???C?VFJ?y?=????eOM*T?6??;/,????}3=??x??c?#??;%,?>??4?.??@?#?????c9??rO?? +??5.???=/EF?!k? ??,????{$????F??E????2\?N/??*?/??? +N>:?*?m%#??? +?C??1?-%~?qx??????`QA?P??E????u??????~ ????S?/D>^o?b?H!?^'?i???????q?6??8>?t????_PP?l;_7?.2ByI?zVl?_? ?u %?????QC?J?'??n?"??v$S??????z?????6D?? ?x???.Cgcm"??=?fjB?????wK?*?? ?.IuZW4=?5f???n\???VI(Yc$????J???#\3??pzn????#?????????????mu???j4e:??[CmcxB"u?"?? ???]?9?C??W?h?X???????@L*W?_ ?F?????t???G+A???k?~?NZ ?6j????U?v| 8??z?D=??D???????F~?C????v??X?* , +???O?????M\?>&|?E??d?*?6?F_] l1????r??>PI?k?v??f??????m@????fI?0m=?& X??_{??5??????`?? D[ ??n?=????Sm????|?m?????Z_??;?{a?l???s1Lb??h?? ??4???)?"Q\????l? +??b??;?^2,_?W3???>?????#[??????"T???A??? ?&????Y +{????z?of???*x,Kf???i(<8??A?0???S?T????p0??K ?,T?O?<1V????2/???U?n?G???kl?"?wF s????DO?j?????8|?k??c?L\]?$ +\?Y???9????C?8?fe%6?K???9=#?A|J?}N+??]1??AN??4???9??/?0T? b????R?^???o??W???SS?????Oy`W?o??0??f??<??:^?$???X?????0???? ?+/S H???`~?A???N???S????jR??%:?i??I?%?u????(2N?!b}?i????XlRTP?"??? K?j????o??A1=?[??k +?? ?!??u?]??l?????\????;?f?a[???d?#ET?7?M8JpH???C?"~k? ? ??sYq?" A??? +?G?c????,?5?D?C ????J~??t?B?{e?I%? ?V?y?#??2? 8????t?????K??#????OHs??,5???)? +?NY *|??T???!bA?E????o??{~?ih????#;??????-tZ?s??X\R???n;@????I??k~?^?h??X???}??*^\?? :??61???*??B??/ +aB??AQs?{?4y,??6?0;??z8????:v@?w7??H?f?4?l???F??????dx +????Kp??M?A?q ? ?????vQ???%????,?a??B6??O\????kr??;t??????wX???={?????????f??e???{?`??`C???DD??s??UW;????R??j?L8????L???@???vIo?y??N?h?^??l??uqY?*????w4???@?? g2??b[t??? +?RC?6?Ug +J?????????N???E??????H}ND?t&??(td?@?????j??]?e????^??d???* +`??%3Il0K??C'q? +??B?>3+h OK?? ?????p??L? ?3??~rtR??i????}?;?{?.??F=qQu???7r]o?j9?????#|?x/???hZ??B??j??_O??N??MvE????K?0??(??W??4?o???w??'n?s?m??ZD7~???????Si4i6??h +y?A???j9 ]?????i?t[y??y???c??????s?&?p?6?lu?~?1z???N?? b??N[?W???e?V?4??????K????`|:t???????HC?%?,??t?5???|?D&]|?g?Z??8#o#8d???&K??b????V??4q2U???|D??`?#?{$?T{j???.?KG??-'?1J,4?ec`?????????4-??????Z????N^???\?x?q???????T r??x??ju2 Gfqx#i?L?-?=??l?ZD??"S6?Z??Exr????v????1?O?sC??x?BU?nm]??'?>??vvu#???E??v=x1b/?T?+?~???Y???jf?4 +??~i.g ?????q???d?? 8F??g?v?^d?n?d??~?I?4??? ???Ws#?FBG?4?~gM??????2Uc?f???.w??o?IS??"l?$?'???[;??W_????jI-???#j?C?vM?? +? ?Lvb??,???sO}7 ?????N??!~RQ??p?U??w?H ,m?)8? (????????????lFGE}H??#DE??3?A?S,?z??V(???^?6U???>??m?k????????X?????/i?u?,2??a{????? +???1?????PK??C?D? ??|???????O0?b?UUO?N??i?????\??? WmA:?i??j?|??? +????<:-??B^:wW2*????????1? ?t?f??????{??I?Y[??!b$?l????)Qv?{???=??[??Ur??????a?5O(?)??jw?????rM???@mkY/ +P?e?PNkf????#?m?C?????5?D.??a??q??????H2? ??K| +??r? ~?)AC?D??z ?g??? +C'q?'.???G???EAlO?m?y????!t[WO?????p ? +??G?n????hL .???b,??V (vk&???v?QV?!=S??\?z4??e?;?????^??????D? HMm???? +?@??'9Z=?g?N?a??g?36?/n?cOh8s?"wmG???S??c?8|??B?7j??i?!&?B?D???P?????+????+?????/)??Q$???h??~??c8?q?w2Y%9???? +Q?e;???_?P??????:?:?b+??'xJ?q93A%K? ?????Q.??(???????i??6xz?????1???iC!???d8?? +??m???}X???g?\?????V{?\????,=[???????S?d?&dV)????H?|??F??nr??'YQ??;?)B????C???~ +{VM??DD????J??)YN???Z???2??w?u?? +?r????????Q??M?{???`??????%K?????????????IAW0?????BI??],? ? ?0????T{????L/4r?? Ys???o???????r +??]?O?3F????R????Q?72???-??a???^???+0 +??u">&?????Lw????UzK5??????pN??KR?f?&????A??P,????a?????$? +???s?4edr???]+? 98`????f7??nK?{JKQ?z?VV}???+? +?(??p'?CLUg?Ff!?0??cuMuQT{#??g??+????G??J?bg?4U??+_??@??J]?$???{BN????j?CUO????|BO/.????J at w??3??^?????A??7???;t?;?g?u?a![?g??m?M4z????????S?+b????M?V???=,?!3?=p?V??W?Z????$??c??!K??|??<???4?)?????W??cJ?aa1"Y??Y?.b?????S?????MQ')1??8A??^i??It?E%?|??+a??2Q??????bQP.???hSO????%?f'U???(?N?????92c??W>u???t???p0;zG??//+???$gGv???B:?6B?t$E?s?&Y?-?0?>t5???m?H??G0q??:?y]????Ed???4c?s?w?????n%??J???-????D??d???;!??x`??u??5?|o???o??,?????{????UgS?,~%}??i??JGrR?E?%D?? +;R?8?4?B????|?u???P ???x-????P???8??z*????[?L?r??s?M???O ???gW6??-?O??&?c?+3)k????g?Hh??n?}???????? v?x)~B????w"2?R???55ofC ?O????i?????d??c????O??kT ???????a[c?z? ??-??[?o?0/_Jp??;/]???yN1A3?m4`R2)`?!uF??C?P?r?s???t@?@?f??,?^m?S:?? +?BW ?f]????3???q???FX?6?U%PU 8?-?2? ?????<6?cT??[pkW???Sa??J7??&}q0X>]?b????l?J????t??? VQb?]?.N%p????ZI???t?O????$???9hLh??B?@??15??#l?)?ro???c??Ya5??)???X1bC?c{p???&x?]uUj+???????9? + ???????q}???^????(?? +?????_??A?????7lF@`e?g?A??@G9??SYO??xC[?.??G??.A*Z0d?N:?t1???>M??A????V?=5?;???;?z???P?Pr??w????????9"7????ODI?????$?.d8???[Vn?6? +??N?Iu?? ?H:?l?0 +t??^t?x~?8N#[!?5???????=/???8w=???2?X|M?u??1??5?B?D??????%a? ?>|??;|?B?Z?W/j?P??????z?????R?y?????y?[R?t{Q???T??V??O?f?q???? S[??:?? ?,@?A&?h??{????I'M???)d9???????kJ,??e????L?E??'???.?,h?$? ?wj??&3??? +?]???60?[Ot??+????????????a?M)??O?????j?????0h??d????????Fs?~ ????|????W????????????8;?,?????< !.?+ +?Rvi????I0?j?T?M?{BX????????^??4X???bH???J???~f_?c*?????3?????m?4?"?|P?t.o?yu,??{~WW .p???":Z?n?}?Y????"???!?1????'????cI??M????":????B -??Tj?30??T|????N?/??????~z?_?f???????wo?.?3?y)~F?s?L??:?.A?[?KJV7m"???t????\??WIn????kS?????ve???a?? ??????????MV['M?|G]+?E?,??gp?/.?(6o# ??X+???q{?K?r??\?q??W?#)? ?x?=??9?C??dP?1???g?? ????e??08??????0i?l?X???0M?D^??`g?????B?W???????|*i??o?R~)???h??????&7?E2iFI?Y?m _;g?Pf? -??p-7??&@????529??F?@8W?,?VhwTmJ??"X?O????a?fp?? -?l??A?k?? -V??? -??,d?%j?d???lS??#J???sw,?B?!????=B?R???????"?6?????82Rb? ["?3??3&H??zD???V??zC9? ??J?o?5?mu??H)!N?N??:J??d????2z?I????&??}k??5a???' -?T????p?}?F???8 -?Lq_??[: I?? -?O(M+?V/?????#v?B?$2e?g??z?:?Q1??GG??2P??o????90 -??'J?k?d?8??T??E?s~????B?b*E?ct?.?c{???Z???????53HVX??C%????????un_:o??RqK?e????u??IF/0#u1k??:$A~O?????? -?FJ?n???v???? /1??l'0?w?? jW?yl??Gh?y?-?l6^> ???-????? x???0???3??;??[??C@????m*t>???7????E?^(B l=??????>?A????fNk?????n????????C????Q'???6???????B?*?7?`?i?? ?wi ????C??cG??n ??s?7????;pj?Z&?D?M0~I?????n#^??u? X???&????%L7P????p????x?`?&?u?@A???a?Ir'j??a?4w??L? >r? -B?JlR????Y?3?\~?????????=?P A????Q+ ??2?n?????D+?%??u? ??????????????,?{??????/?%??V??q?b]?J??,?O1?\P~?<)???:[f??1R Y???;???N?a"~??8O?!7??L[+W;?????&? A?s?dm? -??_???????'??M&3*o?E??I??;m?)?c?7S6?kB2?&-?O?s??N?Q?J??>???j?? s ??T???|????"???J????}?(~??????p?M?NR?XA?(???(S?WGQ?9&h??zLD?a????a4?????e?h?60 ???$&???-?4????$='??t6??2?Q3?)n?dU~N"|?;nwe???R?"`??!??/???+?E??? $??"???.{?B?)?1??(?o????/?j? ??? 7????F?UQ???v9F]C?P?wa-???1???????W??4? -??MqZ????CN????:??d???????U}B????????t*DX?L??@?^T]??z?? ?)Y??????%R??`j/?Q??TR ?8D;? - ??????;N????*r>?+ #??i?cW?%\??TR3|?????^q?????????b????????-?xi?b?J?P?? ?$U???:?C_(nY ?/"?W?/?gS????2L?4???~l????,?u@<p?;?V\{CCr;V;????ng?C??cd~???I"M???&???`?????# ???#2Qx#{Y??A ??H?F?G??H?Q??@Sr?j???:eg?J?????????8??a??d?? ???p@?^???7????*??sl????tyFw?u??#4? ??;!?????????GQ???o? -?r??@?R???)?(|LG?C^D&:2??b?7G???Y?.? 6??T|w^+?d ?(]??????P??j??H??w??9Q??`X?U?+?L??N?????|h?yb?????P?q??q0??g/??sl?&l?-??1?q?=??v?L#??aq?????BK_m??dcL??n?n??:?(\u??L????? ???5#?I ?+ ?"Z??T???1?QC7m?+?|?????R!?!X/??)M?hZ?t??%??l?i? -N??F&"?>? ?k???3???y???)0??7I{N?? -????pu??3?R????X,??o?b????+?=??6????#nUA?+? ?J&=NB?{??????@???tu"{?&c?0?|X??w?*?Ava1g;??3?6???? =ub\5C??'?????H??F?bh??n?!?#????:??}`??&???W?&???2qL?*??_o??VV????Mv0???? ????3???m?V?L???$x?$?????pT???????2.B%?h?? ?S???~?rP?? _F?@7???????C?f -??)x???5?0 [TRUNCATED] To get the complete diff run: svnlook diff /svnroot/chnosz -r 406 From noreply at r-forge.r-project.org Sat Feb 23 14:07:45 2019 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Sat, 23 Feb 2019 14:07:45 +0100 (CET) Subject: [CHNOSZ-commits] r407 - in pkg/CHNOSZ: . R inst tests/testthat Message-ID: <20190223130745.4B12918CC71@r-forge.r-project.org> Author: jedick Date: 2019-02-23 14:07:44 +0100 (Sat, 23 Feb 2019) New Revision: 407 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/R/diagram.R pkg/CHNOSZ/inst/NEWS pkg/CHNOSZ/tests/testthat/test-diagram.R Log: diagram(): make 'xlim' and 'ylim' apply to 2-D diagrams Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-22 06:12:52 UTC (rev 406) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-23 13:07:44 UTC (rev 407) @@ -1,6 +1,6 @@ -Date: 2019-02-22 +Date: 2019-02-23 Package: CHNOSZ -Version: 1.2.0-14 +Version: 1.2.0-15 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/R/diagram.R =================================================================== --- pkg/CHNOSZ/R/diagram.R 2019-02-22 06:12:52 UTC (rev 406) +++ pkg/CHNOSZ/R/diagram.R 2019-02-23 13:07:44 UTC (rev 407) @@ -206,7 +206,7 @@ } } - ## where we'll put extra output for predominance diagrams (namesx, namesy, inames) + ## where we'll put extra output for predominance diagrams (namesx, namesy) out2D <- list() ### now on to the plotting ### @@ -518,31 +518,30 @@ lapply(linesout, `length<-`, max(lengths(linesout))) } ## label plot function - # calculate coordinates for field labels - plot.names <- function(out, xs, ys, names) { - ll <- ngroups - namesx <- numeric(ll); namesy <- numeric(ll); n <- numeric(ll) - for(j in nrow(out):1) { - # 20091116 for speed, loop over ngroups instead of k (columns) - for(i in 1:ll) { - k <- which(out[j,]==i) - if(length(k)==0) next - namesx[i] <- namesx[i] + sum(xs[k]) - namesy[i] <- namesy[i] + length(k)*ys[nrow(out)+1-j] - n[i] <- n[i] + length(k) - } + plot.names <- function(out, xs, ys, xlim, ylim, names) { + # calculate coordinates for field labels + # revisions: 20091116 for speed, 20190223 work with user-specified xlim and ylim + namesx <- namesy <- rep(NA, length(names)) + inames <- logical(length(names)) + for(i in seq_along(names)) { + this <- which(out==i, arr.ind=TRUE) + if(length(this)==0) next + xsth <- xs[this[, 2]] + ysth <- rev(ys)[this[, 1]] + # use only values within the plot range + rx <- range(xlim) + ry <- range(ylim) + xsth <- xsth[xsth >= rx[1] & xsth <= rx[2]] + ysth <- ysth[ysth >= ry[1] & ysth <= ry[2]] + if(length(xsth)==0 | length(ysth)==0) next + namesx[i] <- mean(xsth) + namesy[i] <- mean(ysth) + inames[i] <- TRUE } - namesx <- namesx[n!=0] - namesy <- namesy[n!=0] - inames <- n!=0 - n <- n[n!=0] - namesx <- namesx/n - namesy <- namesy/n - # plot field labels - # the cex argument in this function specifies the character - # expansion of the labels relative to the current + # fields that really exist on the plot + inames <- !is.na(namesx) if(!is.null(names) & any(inames)) text(namesx, namesy, labels=names[inames], cex=cex.names, col=col.names[inames], font=font, family=family) - return(list(namesx=namesx, namesy=namesy, inames=which(inames))) + return(list(namesx=namesx, namesy=namesy)) } ### done with predominance diagram functions @@ -563,9 +562,18 @@ # the x and y values xs <- eout$vals[[1]] ys <- eout$vals[[2]] - # the limits; they aren't necessarily increasing, so don't use range() - xlim <- c(xs[1], tail(xs, 1)) - ylim <- c(ys[1], tail(ys, 1)) + # the limits of the calculation; they aren't necessarily increasing, so don't use range() + xlim.calc <- c(xs[1], tail(xs, 1)) + ylim.calc <- c(ys[1], tail(ys, 1)) + # add if(is.null) to allow user-specified limits 20190223 + if(is.null(xlim)) { + if(add) xlim <- par("usr")[1:2] + else xlim <- xlim.calc + } + if(is.null(ylim)) { + if(add) ylim <- par("usr")[3:4] + else ylim <- ylim.calc + } # initialize the plot if(!add) { if(is.null(xlab)) xlab <- axis.label(eout$vars[1], basis=eout$basis, molality=molality) @@ -602,23 +610,23 @@ zs <- plotvals[[1]] contour(xs, ys, zs, add=TRUE, col=col, lty=lty, lwd=lwd, labcex=cex, method=contour.method[1]) } - pn <- list(namesx=NULL, namesy=NULL, inames=NULL) + pn <- list(namesx=NULL, namesy=NULL) } else { # put predominance matrix in the right order for image() etc zs <- t(predominant[, ncol(predominant):1]) if(!is.null(fill)) fill.color(xs, ys, zs, fill, ngroups) - pn <- plot.names(zs, xs, ys, names) + pn <- plot.names(zs, xs, ys, xlim, ylim, names) # only draw the lines if there is more than one field 20180923 # (to avoid warnings from contour, which seem to be associated with weird # font metric state and subsequent errors adding e.g. subscripted text to plot) if(length(na.omit(unique(as.vector(zs)))) > 1) { - if(!is.null(dotted)) plot.line(zs, xlim, ylim, dotted, col, lwd, xrange=xrange) - else linesout <- contour.lines(predominant, xlim, ylim, lty=lty, col=col, lwd=lwd) + if(!is.null(dotted)) plot.line(zs, xlim.calc, ylim.calc, dotted, col, lwd, xrange=xrange) + else linesout <- contour.lines(predominant, xlim.calc, ylim.calc, lty=lty, col=col, lwd=lwd) } # re-draw the tick marks and axis lines in case the fill obscured them if(tplot & !identical(fill, "transparent")) thermo.axis() } # done with the 2D plot! - out2D <- list(namesx=pn$namesx, namesy=pn$namesy, inames=pn$inames) + out2D <- list(namesx=pn$namesx, namesy=pn$namesy) } # end if(nd==2) } # end if(plot.it) out <- c(eout, list(plotvar=plotvar, plotvals=plotvals, names=names, predominant=predominant)) Modified: pkg/CHNOSZ/inst/NEWS =================================================================== --- pkg/CHNOSZ/inst/NEWS 2019-02-22 06:12:52 UTC (rev 406) +++ pkg/CHNOSZ/inst/NEWS 2019-02-23 13:07:44 UTC (rev 407) @@ -1,4 +1,4 @@ -CHANGES IN CHNOSZ 1.2.0-14 (2019-02-22) +CHANGES IN CHNOSZ 1.2.0-15 (2019-02-23) --------------------------------------- CRAN COMPLIANCE @@ -67,6 +67,9 @@ output 1 bar for Psat at temperatures less than 100 degrees C (default is TRUE). +- diagram(): 'xlim' and 'ylim' arguments now apply to 2-variable + diagrams. Thanks to Evgeniy Bastrakov for the suggestion. + CHANGES IN CHNOSZ 1.2.0 (2019-02-09) ------------------------------------ Modified: pkg/CHNOSZ/tests/testthat/test-diagram.R =================================================================== --- pkg/CHNOSZ/tests/testthat/test-diagram.R 2019-02-22 06:12:52 UTC (rev 406) +++ pkg/CHNOSZ/tests/testthat/test-diagram.R 2019-02-23 13:07:44 UTC (rev 407) @@ -97,3 +97,20 @@ expect_equal(d$predominant[1, 128], as.numeric(NA)) expect_equal(d$predominant[128, 1], as.numeric(NA)) }) + +## add the test but exclude it for now because plot.it=FALSE doesn't produce values for namesx 20190223 +#test_that("labels are dropped outside of xlim and ylim ranges", { +# basis(c("Fe", "O2", "S2")) +# species(c("iron", "ferrous-oxide", "magnetite", +# "hematite", "pyrite", "pyrrhotite")) +# a <- affinity(S2=c(-50, 0), O2=c(-90, -10), T=200) +# # total range: all species are present +# d <- diagram(a, fill="heat", xlim=NULL, ylim=NULL, plot.it=FALSE) +# expect_equal(sum(is.na(d$namesx)), 0) +# # reduce y-range to exclude hematite +# d <- diagram(a, fill="heat", xlim=NULL, ylim=c(-90, -50), plot.it=FALSE) +# expect_equal(sum(is.na(d$namesx)), 1) +# # reduce x-range to exclude pyrrhotite +# d <- diagram(a, fill="heat", xlim=c(-50, -20), ylim=c(-90, -50), plot.it=FALSE) +# expect_equal(sum(is.na(d$namesx)), 2) +#}) From noreply at r-forge.r-project.org Sat Feb 23 23:58:23 2019 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Sat, 23 Feb 2019 23:58:23 +0100 (CET) Subject: [CHNOSZ-commits] r408 - in pkg/CHNOSZ: . R inst man Message-ID: <20190223225823.2AF2A18CBCE@r-forge.r-project.org> Author: jedick Date: 2019-02-23 23:58:22 +0100 (Sat, 23 Feb 2019) New Revision: 408 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/R/info.R pkg/CHNOSZ/R/retrieve.R pkg/CHNOSZ/inst/NEWS pkg/CHNOSZ/man/retrieve.Rd Log: retrieve(): permit specification of chemical systems Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-23 13:07:44 UTC (rev 407) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-23 22:58:22 UTC (rev 408) @@ -1,6 +1,6 @@ Date: 2019-02-23 Package: CHNOSZ -Version: 1.2.0-15 +Version: 1.2.0-16 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/R/info.R =================================================================== --- pkg/CHNOSZ/R/info.R 2019-02-23 13:07:44 UTC (rev 407) +++ pkg/CHNOSZ/R/info.R 2019-02-23 22:58:22 UTC (rev 408) @@ -27,7 +27,7 @@ ## run info.numeric or info.character depending on the input type if(is.numeric(species)) { out <- lapply(species, info.numeric, check.it) - # if we different states the column names could be different + # if we have different states the column names could be different if(length(unique(unlist(lapply(out, names)))) > ncol(thermo$obigt)) { # make them the same as thermo$obigt out <- lapply(out, function(row) { @@ -36,6 +36,8 @@ } # turn the list into a data frame out <- do.call(rbind, out) + # ensure that the rownames are numeric values (not names possibly inherited from retrieve()) 20190224 + if(!is.null(attr(species, "names"))) row.names(out) <- species } else { # state and species should be same length if(!is.null(state)) { Modified: pkg/CHNOSZ/R/retrieve.R =================================================================== --- pkg/CHNOSZ/R/retrieve.R 2019-02-23 13:07:44 UTC (rev 407) +++ pkg/CHNOSZ/R/retrieve.R 2019-02-23 22:58:22 UTC (rev 408) @@ -1,8 +1,10 @@ # CHNOSZ/retrieve.R # retrieve species with given elements # 20190214 initial version +# 20190224 use ... for multiple arguments (define a chemical system) -retrieve <- function(elements) { +retrieve <- function(..., include.electron = FALSE, include.groups = FALSE, state = NULL) { + ## stoichiometric matrix # what are the formulas of species in the current database? formula <- thermo()$obigt$formula # get a previously calculated stoichiometric matrix, if it matches the current database @@ -20,14 +22,44 @@ # store the stoichiometric matrix for later calculations thermo("stoich" = stoich) } - not.present <- ! elements %in% colnames(stoich) - if(any(not.present)) { - if(sum(not.present)==1) stop(elements[not.present], " is not an element that is present in any species") - else stop(paste(elements[not.present], collapse=", "), " are not elements that are present in any species") + + ## species identification + args <- list(...) + ispecies <- numeric() + for(elements in args) { + not.present <- ! elements %in% colnames(stoich) + if(any(not.present)) { + if(sum(not.present)==1) stop(elements[not.present], " is not an element that is present in any species") + else stop(paste(elements[not.present], collapse=", "), " are not elements that are present in any species") + } + # identify the species that have the elements + has.elements <- rowSums(stoich[, elements, drop = FALSE] != 0) == length(elements) + # which species are these (i.e. the species index) + ispecies <- c(ispecies, which(has.elements)) + ispecies <- ispecies[!duplicated(ispecies)] } - # identify the species that have the elements - has.elements <- rowSums(stoich[, elements, drop = FALSE] != 0) == length(elements) - # which species are these (i.e. the species index) - which(has.elements) + # for a chemical system, defined by multiple arguments, the species can not contain any _other_ elements + if(length(args) > 1) { + syselements <- unlist(args) + isyselements <- colnames(thermo()$stoich) %in% syselements + notsysstoich <- thermo()$stoich[, !isyselements] + iother <- rowSums(notsysstoich[ispecies, ] != 0) > 0 + ispecies <- ispecies[!iother] + # include the species for "Z" (charge) + if(!include.electron) { + ielectron <- names(ispecies) == "(Z-1)" + ispecies <- ispecies[!ielectron] + } + } + # exclude groups and filter states + if(!include.groups) { + igroup <- grepl("^\\[.*\\]$", thermo()$obigt$name[ispecies]) + ispecies <- ispecies[!igroup] + } + if(!is.null(state)) { + istate <- thermo()$obigt$state[ispecies] %in% state + ispecies <- ispecies[istate] + } + ispecies } Modified: pkg/CHNOSZ/inst/NEWS =================================================================== --- pkg/CHNOSZ/inst/NEWS 2019-02-23 13:07:44 UTC (rev 407) +++ pkg/CHNOSZ/inst/NEWS 2019-02-23 22:58:22 UTC (rev 408) @@ -1,4 +1,4 @@ -CHANGES IN CHNOSZ 1.2.0-15 (2019-02-23) +CHANGES IN CHNOSZ 1.2.0-16 (2019-02-24) --------------------------------------- CRAN COMPLIANCE @@ -15,8 +15,9 @@ - Add thermo() as a convenience function to access or modify the package's data, especially various computational options. -- Add retrieve() to retrieve all the species with given elements. Thanks - to Evgeniy Bastrakov for the suggestion. +- Add retrieve() to retrieve all the species having given elements, or + all species in a given chemical system. Thanks to Evgeniy Bastrakov + for the suggestion. - Add AkDi() to calculate thermodynamic properties of aqueous nonelectrolytes using the Akinfiev-Diamond model. Thanks to Evgeniy Modified: pkg/CHNOSZ/man/retrieve.Rd =================================================================== --- pkg/CHNOSZ/man/retrieve.Rd 2019-02-23 13:07:44 UTC (rev 407) +++ pkg/CHNOSZ/man/retrieve.Rd 2019-02-23 22:58:22 UTC (rev 408) @@ -7,17 +7,29 @@ } \usage{ - retrieve(elements) + retrieve(..., include.electron = FALSE, include.groups = FALSE, state = NULL) } \arguments{ - \item{elements}{character, one or more chemical elements} + \item{...}{list, one or more arguments, each of which is a character vector with the names of one or more chemical elements} + \item{include.electron}{logical, include the electron in the result for chemical systems?} + \item{include.groups}{logical, include groups in the result?} + \item{state}{character, filter the result on these state(s).} } \details{ -This function retrieves the species in the thermodynamic database (see \code{\link{thermo}}) that have all of the elements specified in \code{elements}. +This function retrieves the species in the thermodynamic database (see \code{\link{thermo}}) that have all of the elements specified in the arguments. +A single argument is interpreted as a combination of one or more elements that must be present in each species. The return value is a named numeric vector giving the species index (i.e. rownumber(s) of \code{thermo()$obigt}) with names corresponding to the chemical formulas of the species. +If the argument list is empty, then the function returns an empty (length 0) numeric value. +If more than one argument is present, all of the species identified by each argument are combined, then any species containing any other elements are excluded. +This can be used to retrieve all of the species in the database within a given chemical system. +When searching for charged species in a chemical system (using the element named \samp{Z}), the electron is excluded unless \code{include.electron} is TRUE (note that the electron has a chemical formula of \samp{(Z-1)}). + +Groups used in group-additivity calculations, which have names with square brackets (e.g. [-CH2-]), are excluded unless \code{include.groups} is TRUE. +Results can be filtered on physical state by setting the \code{state} argument. + The first time the function is run, it uses \code{\link{i2A}} to build the stoichiometric matrix for the current database. Following runs use the previously calculated stoichiometric matrix, unless a change to the database is detected, which triggers a recalculation. } @@ -29,9 +41,25 @@ \examples{ # species index of Ti-bearing minerals retrieve("Ti") +# thermodynamic data for those minerals +info(retrieve("Ti")) # thermodynamic data for Au-Cl complexes info(retrieve(c("Au", "Cl"))) + +# all species that have Au +retrieve("Au") +# all species that have both Au and Cl +retrieve(c("Au", "Cl")) +# all species that have Au and/or Cl, and no other elements +retrieve("Au", "Cl") +# all species that have Au and/or Cl and/or Z, and no other elements +retrieve("Au", "Cl", "Z") +# include the electron with these species +retrieve("Au", "Cl", "Z", include.electron = TRUE) + +# minerals in the system SiO2-MgO-CaO-CO2 +retrieve("Si", "Mg", "Ca", "C", "O", state="cr") } \concept{Extended workflow} From noreply at r-forge.r-project.org Sun Feb 24 00:25:27 2019 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Sun, 24 Feb 2019 00:25:27 +0100 (CET) Subject: [CHNOSZ-commits] r409 - in pkg/CHNOSZ: . R tests/testthat Message-ID: <20190223232528.03E2E18CE76@r-forge.r-project.org> Author: jedick Date: 2019-02-24 00:25:27 +0100 (Sun, 24 Feb 2019) New Revision: 409 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/R/retrieve.R pkg/CHNOSZ/tests/testthat/test-retrieve.R Log: retrieve(): error messages include quotes around missing elements Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-23 22:58:22 UTC (rev 408) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-23 23:25:27 UTC (rev 409) @@ -1,6 +1,6 @@ Date: 2019-02-23 Package: CHNOSZ -Version: 1.2.0-16 +Version: 1.2.0-17 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/R/retrieve.R =================================================================== --- pkg/CHNOSZ/R/retrieve.R 2019-02-23 22:58:22 UTC (rev 408) +++ pkg/CHNOSZ/R/retrieve.R 2019-02-23 23:25:27 UTC (rev 409) @@ -29,8 +29,8 @@ for(elements in args) { not.present <- ! elements %in% colnames(stoich) if(any(not.present)) { - if(sum(not.present)==1) stop(elements[not.present], " is not an element that is present in any species") - else stop(paste(elements[not.present], collapse=", "), " are not elements that are present in any species") + if(sum(not.present)==1) stop('"', elements[not.present], '" is not an element that is present in any species') + else stop('"', paste(elements[not.present], collapse='", "'), '" are not elements that are present in any species') } # identify the species that have the elements has.elements <- rowSums(stoich[, elements, drop = FALSE] != 0) == length(elements) Modified: pkg/CHNOSZ/tests/testthat/test-retrieve.R =================================================================== --- pkg/CHNOSZ/tests/testthat/test-retrieve.R 2019-02-23 22:58:22 UTC (rev 408) +++ pkg/CHNOSZ/tests/testthat/test-retrieve.R 2019-02-23 23:25:27 UTC (rev 409) @@ -2,9 +2,9 @@ test_that("errors and recalculations produce expected messages", { # this should give an error about one non-element - expect_error(retrieve(c("A", "B", "C")), "A is not an element") + expect_error(retrieve(c("A", "B", "C")), '"A" is not an element') # this should give an error about two non-elements - expect_error(retrieve(c("A", "B", "C", "D")), "A, D are not elements") + expect_error(retrieve(c("A", "B", "C", "D")), '"A", "D" are not elements') # this should recalculate the stoichiometric matrix add.obigt("SUPCRT92") expect_message(retrieve("Ti"), "creating stoichiometric matrix") From noreply at r-forge.r-project.org Sun Feb 24 14:48:00 2019 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Sun, 24 Feb 2019 14:48:00 +0100 (CET) Subject: [CHNOSZ-commits] r410 - in pkg/CHNOSZ: . R demo man tests/testthat Message-ID: <20190224134800.8F6AB18C542@r-forge.r-project.org> Author: jedick Date: 2019-02-24 14:48:00 +0100 (Sun, 24 Feb 2019) New Revision: 410 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/R/add.obigt.R pkg/CHNOSZ/R/diagram.R pkg/CHNOSZ/demo/copper.R pkg/CHNOSZ/demo/glycinate.R pkg/CHNOSZ/demo/lambda.R pkg/CHNOSZ/man/add.obigt.Rd pkg/CHNOSZ/tests/testthat/test-diagram.R Log: some fixups for demos Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-23 23:25:27 UTC (rev 409) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-24 13:48:00 UTC (rev 410) @@ -1,6 +1,6 @@ -Date: 2019-02-23 +Date: 2019-02-24 Package: CHNOSZ -Version: 1.2.0-17 +Version: 1.2.0-18 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/R/add.obigt.R =================================================================== --- pkg/CHNOSZ/R/add.obigt.R 2019-02-23 23:25:27 UTC (rev 409) +++ pkg/CHNOSZ/R/add.obigt.R 2019-02-24 13:48:00 UTC (rev 410) @@ -1,6 +1,9 @@ # CHNOSZ/add.obigt.R # add or change entries in the thermodynamic database +## if this file is interactively sourced, the following are also needed to provide unexported functions: +#source("info.R") + today <- function() { # write today's date in the format used in SUPCRT data files # e.g. 13.May.12 for 2012-05-13 @@ -68,6 +71,15 @@ # transmit the error from makeup stop(e) } + # for aqueous species, supply a value for Z if it is missing, otherwise NA triggers AkDi model 20190224 + isaq <- newrows$state == "aq" + if(any(isaq)) { + mnrf <- makeup(newrows$formula) + if(nrow(newrows)==1) mnrf <- list(mnrf) + Z <- sapply(mnrf, "[", "Z") + Z[is.na(Z)] <- 0 + newrows$z.T[isaq] <- Z[isaq] + } # assign to thermo$obigt thermo$obigt <- rbind(thermo$obigt, newrows) rownames(thermo$obigt) <- NULL Modified: pkg/CHNOSZ/R/diagram.R =================================================================== --- pkg/CHNOSZ/R/diagram.R 2019-02-23 23:25:27 UTC (rev 409) +++ pkg/CHNOSZ/R/diagram.R 2019-02-24 13:48:00 UTC (rev 410) @@ -522,8 +522,8 @@ # calculate coordinates for field labels # revisions: 20091116 for speed, 20190223 work with user-specified xlim and ylim namesx <- namesy <- rep(NA, length(names)) - inames <- logical(length(names)) - for(i in seq_along(names)) { + # even if 'names' is NULL, we run the loop in order to generate namesx and namesy for the output 20190225 + for(i in seq_along(groups)) { this <- which(out==i, arr.ind=TRUE) if(length(this)==0) next xsth <- xs[this[, 2]] @@ -536,11 +536,9 @@ if(length(xsth)==0 | length(ysth)==0) next namesx[i] <- mean(xsth) namesy[i] <- mean(ysth) - inames[i] <- TRUE } # fields that really exist on the plot - inames <- !is.na(namesx) - if(!is.null(names) & any(inames)) text(namesx, namesy, labels=names[inames], cex=cex.names, col=col.names[inames], font=font, family=family) + if(!is.null(names)) text(namesx, namesy, labels=names, cex=cex.names, col=col.names, font=font, family=family) return(list(namesx=namesx, namesy=namesy)) } Modified: pkg/CHNOSZ/demo/copper.R =================================================================== --- pkg/CHNOSZ/demo/copper.R 2019-02-23 23:25:27 UTC (rev 409) +++ pkg/CHNOSZ/demo/copper.R 2019-02-24 13:48:00 UTC (rev 410) @@ -52,7 +52,7 @@ if(names[i]=="HCu(Gly)+2") srt <- 90 if(names[i]=="HCu(Gly)+2") dx <- -0.2 if(names[i]=="Cu(Gly)+") srt <- 90 - text(d$namesx[i]+dx, d$namesy[i]+dy, lab, srt=srt) + text(na.omit(d$namesx)[i]+dx, na.omit(d$namesy)[i]+dy, lab, srt=srt) } # add glycine ionization lines Modified: pkg/CHNOSZ/demo/glycinate.R =================================================================== --- pkg/CHNOSZ/demo/glycinate.R 2019-02-23 23:25:27 UTC (rev 409) +++ pkg/CHNOSZ/demo/glycinate.R 2019-02-24 13:48:00 UTC (rev 410) @@ -34,6 +34,7 @@ reset() # set up the plots +opar <- par(no.readonly = TRUE) layout(matrix(1:6, byrow = TRUE, nrow = 2), widths = c(2, 2, 1)) par(mar = c(4, 3.2, 2.5, 0.5), mgp = c(2.1, 1, 0), las = 1, cex = 0.8) xlab <- axis.label("T") @@ -66,3 +67,4 @@ par(xpd = NA) legend("right", as.expression(lapply(mo, expr.species)), lty = 1, col = 1:5, bty = "n", cex = 1.2, lwd = 2) par(xpd = FALSE) +par(opar) Modified: pkg/CHNOSZ/demo/lambda.R =================================================================== --- pkg/CHNOSZ/demo/lambda.R 2019-02-23 23:25:27 UTC (rev 409) +++ pkg/CHNOSZ/demo/lambda.R 2019-02-24 13:48:00 UTC (rev 410) @@ -84,4 +84,5 @@ plot(Pkb, Qz_lambda$S, type="l", ylim=c(0, 3), ylab=axis.label("DlS"), xlab=Plab) labplot("f") +reset() par(opar) Modified: pkg/CHNOSZ/man/add.obigt.Rd =================================================================== --- pkg/CHNOSZ/man/add.obigt.Rd 2019-02-23 23:25:27 UTC (rev 409) +++ pkg/CHNOSZ/man/add.obigt.Rd 2019-02-24 13:48:00 UTC (rev 410) @@ -51,7 +51,7 @@ An error results if the formula is not valid (i.e. can not be parsed by\code{\link{makeup}}). Additional arguments refer to the name of the property(s) to be updated and are matched to any part of compound column names in \code{\link{thermo}$obigt}, such as \samp{z} or \samp{T} in \samp{z.T}. Unless \samp{state} is specified as one of the properties, its value is taken from \code{thermo$opt$state}. -When adding species, properties that are not specified become NA (except for \samp{state}). +When adding species, properties that are not specified become NA, except for \samp{state}, which takes a default value from \code{thermo$opt$state}, and \samp{z.T}, which for aqueous species is set to the charge calculated from the chemical formula (otherwise, NA charge for newly added species would trigger the \code{\link{AkDi}} model). The values provided should be in the units specifed in the documentation for the \code{thermo} data object, including any order-of-magnitude scaling factors. \code{today} returns the current date in the format adopted for \code{thermo$obigt} (inherited from SUPCRT-format data files) e.g. \samp{13.May.12} for May 13, 2012. Modified: pkg/CHNOSZ/tests/testthat/test-diagram.R =================================================================== --- pkg/CHNOSZ/tests/testthat/test-diagram.R 2019-02-23 23:25:27 UTC (rev 409) +++ pkg/CHNOSZ/tests/testthat/test-diagram.R 2019-02-24 13:48:00 UTC (rev 410) @@ -110,7 +110,7 @@ # # reduce y-range to exclude hematite # d <- diagram(a, fill="heat", xlim=NULL, ylim=c(-90, -50), plot.it=FALSE) # expect_equal(sum(is.na(d$namesx)), 1) -# # reduce x-range to exclude pyrrhotite +# # reduce x-range to exclude pyrite # d <- diagram(a, fill="heat", xlim=c(-50, -20), ylim=c(-90, -50), plot.it=FALSE) # expect_equal(sum(is.na(d$namesx)), 2) #}) From noreply at r-forge.r-project.org Sun Feb 24 23:46:53 2019 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Sun, 24 Feb 2019 23:46:53 +0100 (CET) Subject: [CHNOSZ-commits] r411 - in pkg/CHNOSZ: . inst inst/extdata/OBIGT vignettes Message-ID: <20190224224653.C177618CC08@r-forge.r-project.org> Author: jedick Date: 2019-02-24 23:46:53 +0100 (Sun, 24 Feb 2019) New Revision: 411 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/inst/NEWS pkg/CHNOSZ/inst/extdata/OBIGT/SLOP98.csv pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_aq.csv.xz pkg/CHNOSZ/inst/extdata/OBIGT/refs.csv pkg/CHNOSZ/vignettes/anintro.Rmd pkg/CHNOSZ/vignettes/obigt.Rmd pkg/CHNOSZ/vignettes/obigt.bib Log: OBIGT: add/update Zn species from Akinfiev and Tagirov, 2014 Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-24 13:48:00 UTC (rev 410) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-24 22:46:53 UTC (rev 411) @@ -1,6 +1,6 @@ Date: 2019-02-24 Package: CHNOSZ -Version: 1.2.0-18 +Version: 1.2.0-19 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/inst/NEWS =================================================================== --- pkg/CHNOSZ/inst/NEWS 2019-02-24 13:48:00 UTC (rev 410) +++ pkg/CHNOSZ/inst/NEWS 2019-02-24 22:46:53 UTC (rev 411) @@ -1,4 +1,4 @@ -CHANGES IN CHNOSZ 1.2.0-16 (2019-02-24) +CHANGES IN CHNOSZ 1.2.0-19 (2019-02-25) --------------------------------------- CRAN COMPLIANCE @@ -50,6 +50,8 @@ - Update Pt+2 and complexes with data from Tagirov et al., 2015. +- Update Zn+2 and complexes with data from Akinfiev and Tagirov, 2015. + DOCUMENTATION - In demo/NaCl.R, indicate region not considered by Shock et al., 1992 Modified: pkg/CHNOSZ/inst/extdata/OBIGT/SLOP98.csv =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/SLOP98.csv 2019-02-24 13:48:00 UTC (rev 410) +++ pkg/CHNOSZ/inst/extdata/OBIGT/SLOP98.csv 2019-02-24 22:46:53 UTC (rev 411) @@ -22,18 +22,25 @@ PdOH+,Pd(OH)+,Pd(OH)+,aq,"SS98a.3 [S98]",NA,13.Jul.95,-13130,-24120,-3.4,12.8,-13.5,0.1226,-7.4741,8.6697,-2.4699,19.2537,-0.4271,0.6063,1 Pd(SO4)3-4,Pd(SO4)3-4,Pd(SO4)3-4,aq,"SS98a.3 [S98]",NA,28.Jul.94,-499900,-603950,39.4,-48.2,50.8,10.7074,18.3646,-1.4712,-3.5381,32.1909,-12.8528,5.891,-4 HCl,HCl,HCl,aq,"MS97.2 [S98]",SLOP98.11,30.Jul.96,-30410,-42054,3.2,NA,NA,1.2547,-4.7177,7.6043,-2.584,16.7134,2.8727,-0.7,0 -AgCl,AgCl,AgCl,aq,"SSH97.1 [S98]",NA,16.Sep.97,-17450,-18270,34.1,6.7,25.24,5.2088,4.9399,3.8015,-2.9832,9.8168,-1.6698,-0.03,0 -AgCl2-,AgCl2-,AgCl2-,aq,"SSH97.1 [S98]",NA,16.Sep.97,-51560,-61130,47,7.8,54.37,9.5149,15.4544,-0.3312,-3.4178,19.185,-1.4457,0.9169,-1 -AgCl3-2,AgCl3-2,AgCl3-2,aq,"SSH97.1 [S98]",NA,2.Oct.97,-82710,-105613,44.5,10.69,86.82,14.504,27.6363,-5.1192,-3.9214,35.8339,-0.857,2.5402,-2 -AuCl,AuCl,AuCl,aq,"SSH97.1 [S98]",NA,2.Oct.97,-3184,-2140,41.47,-9.83,38.61,7.0357,9.4008,2.0481,-3.1676,0.0551,-5.0371,-0.038,0 -AuCl2-,AuCl2-,AuCl2-,aq,"SSH97.1 [S98]",NA,2.Oct.97,-36781,-44725,53.6,-24.52,69.26,11.5192,20.3482,-2.2547,-3.6201,-0.6764,-8.03,0.8173,-1 -CuCl,CuCl,CuCl,aq,"SSH97.1 [S98]",NA,2.Oct.97,-22608,-26338,22.06,19.64,17.22,4.1084,2.253,4.8575,-2.8721,17.3292,0.967,-0.038,0 -CuCl2-,CuCl2-,CuCl2-,aq,"SSH97.1 [S98]",NA,2.Oct.97,-58038,-72903,26.96,32.99,45.43,8.3943,12.7182,0.7442,-3.3047,36.7555,3.6846,1.2219,-1 +ZnCl+,ZnCl+,ZnCl+,aq,"SSH97.3 [S98]",NA,16.Sep.97,-66850,-66240,23,19.9,-1.28,1.6583,-3.7293,7.2088,-2.6248,19.6947,1.0191,0.2025,1 +ZnCl2,ZnCl2,ZnCl2,aq,"SSH97.3 [S98]",NA,16.Sep.97,-98300,-109080,27.03,34.7,24.82,5.1486,4.7929,3.8592,-2.9771,26.1528,4.0338,-0.038,0 +ZnCl3-,ZnCl3-,ZnCl3-,aq,"SSH97.3 [S98]",NA,2.Oct.97,-129310,-151060,25,41.97,53.9,9.5636,15.5732,-0.3779,-3.4227,42.2912,5.5147,1.2513,-1 +Zn(Ac)+,Zn(Ac)+,ZnCH3COO+,aq,"SSH97.4 [S98]",NA,18.Sep.97,-125660,-155120,9.4,86.2,21.52,4.8484,4.06,4.1473,-2.9468,60.4626,14.5244,0.41,1 +Zn(Ac)2,Zn(Ac)2,Zn(CH3COO)2,aq,"SSH97.4 [S98]",NA,18.Sep.97,-216450,-271500,22.47,193.3,73.02,11.7443,20.8978,-2.4707,-3.6429,119.1022,36.3407,-0.038,0 +Zn(Ac)3-,Zn(Ac)3-,Zn(CH3COO)3-,aq,"SSH97.4 [S98]",SLOP15.2,2.Jun.98,-305740,-408093,25,316.5,130.4,20.0332,41.1373,-10.4257,-4.4796,203.1827,61.4365,1.2513,-1 +AgCl,AgCl,AgCl,aq,"SSH97.3 [S98]",NA,16.Sep.97,-17450,-18270,34.1,6.7,25.24,5.2088,4.9399,3.8015,-2.9832,9.8168,-1.6698,-0.03,0 +AgCl2-,AgCl2-,AgCl2-,aq,"SSH97.3 [S98]",NA,16.Sep.97,-51560,-61130,47,7.8,54.37,9.5149,15.4544,-0.3312,-3.4178,19.185,-1.4457,0.9169,-1 +AgCl3-2,AgCl3-2,AgCl3-2,aq,"SSH97.3 [S98]",NA,2.Oct.97,-82710,-105613,44.5,10.69,86.82,14.504,27.6363,-5.1192,-3.9214,35.8339,-0.857,2.5402,-2 +AuCl,AuCl,AuCl,aq,"SSH97.3 [S98]",NA,2.Oct.97,-3184,-2140,41.47,-9.83,38.61,7.0357,9.4008,2.0481,-3.1676,0.0551,-5.0371,-0.038,0 +AuCl2-,AuCl2-,AuCl2-,aq,"SSH97.3 [S98]",NA,2.Oct.97,-36781,-44725,53.6,-24.52,69.26,11.5192,20.3482,-2.2547,-3.6201,-0.6764,-8.03,0.8173,-1 +CuCl,CuCl,CuCl,aq,"SSH97.3 [S98]",NA,2.Oct.97,-22608,-26338,22.06,19.64,17.22,4.1084,2.253,4.8575,-2.8721,17.3292,0.967,-0.038,0 +CuCl2-,CuCl2-,CuCl2-,aq,"SSH97.3 [S98]",NA,2.Oct.97,-58038,-72903,26.96,32.99,45.43,8.3943,12.7182,0.7442,-3.3047,36.7555,3.6846,1.2219,-1 Ag(HS)2-,Ag(HS)2-,Ag(HS)2-,aq,"SSH97.1 [S98]",NA,9.Oct.97,0,-8200,44.68,38.1,60.5,10.3654,17.5311,-1.1475,-3.5037,37.2753,4.7273,0.9527,-1 Au(HS)2-,Au(HS)2-,Au(HS)2-,aq,"SSH97.1 [S98]",NA,9.Oct.97,2429,-2509,56.77,6.06,75.39,12.342,22.3572,-3.0443,-3.7032,16.8038,-1.8007,0.7693,-1 Ag+,Ag+,Ag+,aq,"SH88.3 [S92]",NA,07.Nov.97,18427,25275,17.54,7.9,-0.8,1.7285,-3.5608,7.1496,-2.6318,12.7862,-1.4254,0.216,1 Au+,Au+,Au+,aq,"SSWS97.2 [S98]",SH88.1,13.Nov.97,39000,47900,25.6,-0.3,12.5,3.5312,0.8428,5.4139,-2.8137,7.5089,-3.0956,0.1648,1 Cu+,Cu+,Cu+,aq,"SSWS97.2 [S98]",SH88.1,13.Nov.97,11950,17132,9.7,13.7,-8,0.807,-5.804,8.0165,-2.539,17.9233,-0.2438,0.4046,1 +Zn+2,Zn+2,Zn+2,aq,"SSWS97.5 [S98]",SH88.1,07.Nov.97,-35200,-36660,-26.2,-5.33,-24.3,-1.0676,-8.929,6.1282,-2.4098,18.74,-5.37,1.4574,2 AgOH,AgOH,AgOH,aq,"SSWS97 [S98]",NA,14.Nov.97,-21900,-31800,17.2,-10.6,3.9,2.2885,-2.1912,6.6063,-2.6883,-0.3221,-5.1937,-0.03,0 AsO4-3,AsO4-3,AsO4-3,aq,"SSWS97.3 [S98]",NA,11.Nov.97,-154970,-212270,-38.9,-116.1,-18.7,1.0308,-5.2609,7.8091,-2.5614,-12.1352,-26.6841,5.399,-3 HAsO4-2,HAsO4-2,HAsO4-2,aq,"SSWS97.3 [S98]",NA,11.Nov.97,-170790,-216620,-0.4,-47.5,11.3,4.3994,2.9611,4.5853,-2.9013,7.9908,-12.7102,3.2197,-2 @@ -46,11 +53,67 @@ AlOH+2,AlOH+2,AlOH+2,aq,"SSWS97.4 [S98]",NA,13.Nov.97,-165475,-183300,-44.2,13.2,-2.2,2.0469,-2.7813,6.8376,-2.6639,29.7923,-0.3457,1.7247,2 AlO+,AlO+,AlO+1,aq,"SSWS97.4 [S98]",NA,13.Nov.97,-158188,-170900,-27,-30,0.6,2.1705,-2.4811,6.7241,-2.6763,-2.5983,-9.1455,0.957,1 HAlO2,HAlO2(AQ),HAlO2,aq,"SSWS97.4 [S98]",NA,13.Nov.97,-207700,-227500,5,-50,13,3.5338,0.8485,5.4132,-2.814,-23.4129,-13.2195,-0.03,0 +ZnOH+,ZnOH+,ZnOH+1,aq,"SSWS97.5 [S98]",NA,14.Nov.97,-81190,-86990,15,10,-5.3,1.1499,-4.9677,7.6896,-2.5735,15.0306,-0.9975,0.326,1 +ZnO,ZnO,ZnO,aq,"SSWS97.5 [S98]",NA,14.Nov.97,-67420,-78290,-2,-10,-21.9,-1.2418,-10.8072,9.9819,-2.3321,0.0295,-5.0715,-0.03,0 +HZnO2-,HZnO2-,HZnO2-1,aq,"SSWS97.5 [S98]",NA,14.Nov.97,-110720,-142370,-16,20,-13.4,0.5623,-6.4047,8.2588,-2.5141,35.0874,1.0394,1.8669,-1 +ZnO2-2,ZnO2-2,ZnO2-2,aq,"SSWS97.5 [S98]",NA,14.Nov.97,-93290,-132100,-40,-15,-26.4,-0.5559,-9.1347,9.3301,-2.4013,32.5837,-6.09,3.8216,-2 Al(Ac)+2,NA,AlCH3COO+2,aq,"SK93.1 [S98]",NA,5.Apr.93,-207630,-249130,-66.1,72.2,-0.03,2.4411,-1.8235,6.4722,-2.7035,67.0012,11.6689,2.0115,2 Al(Ac)2+,NA,Al(CH3COO)2+,aq,"SK93.1 [S98]",NA,5.Apr.93,-298430,-372080,-59.8,168.7,49.4,8.9971,14.1844,0.1805,-3.3653,117.86,31.3303,1.3918,1 Al(Ac)3,NA,Al(CH3COO)3,aq,"SK93.1 [S98]",NA,5.Apr.93,-391100,-498280,-57,NA,NA,16.0545,31.4184,-6.597,-4.0777,156.5453,49.3293,-0.03,0 Al(Mal)+,NA,AlC3H2O4+,aq,"PSK99.1 [S07]",NA,24.Aug.06,-289589,-331497,-16,-17.9,0,0,0,0,0,2.2763,-6.6807,0.7895,1 Al(Oxal)+,NA,AlC2O4+,aq,"PSK99.1 [S07]",NA,24.Aug.06,-286615,-321675,-25.6,-25.8,0,0,0,0,0,-1.0645,-8.29,0.9437,1 +NaH2AsO4,NA,NaH2AsO4,aq,MA07,MA10,12.Sep.07,-240179,-272608,41.2,37.8,41.1,7.3772,10.2352,1.1421,-3.2022,27.9202,4.6622,-0.038,0 +KH2AsO4,NA,KH2AsO4,aq,MA07,MA10,12.Sep.07,-244935,-274352,54.5,21.9,52.4,8.9277,14.0226,-0.484,-3.3587,18.6125,1.4173,-0.038,0 +MgH2AsO4+,NA,MgH2AsO4+,aq,MA07,MA10,12.Sep.07,-290910,-332717,-10.4,50.7,18.3,4.5105,3.2335,4.1483,-2.9127,42.265,7.2899,0.7009,1 +CaH2AsO4+,NA,CaH2AsO4+,aq,MA07,MA10,12.Sep.07,-314170,-348007,18.5,45.8,22.2,4.8949,4.1724,3.7452,-2.9515,35.3597,6.2862,0.2639,1 +SrH2AsO4+,NA,SrH2AsO4+,aq,MA07,MA10,12.Sep.07,-315896,-347841,27.3,40.1,22.9,4.9488,4.3041,3.6887,-2.957,30.8142,5.1312,0.1301,1 +MnH2AsO4+,NA,MnH2AsO4+,aq,MA07,MA10,12.Sep.07,-236482,-270828,14.5,53.5,23.3,5.0617,4.5799,3.5702,-2.9684,40.4264,7.8583,0.3244,1 +FeH2AsO4+,NA,FeH2AsO4+,aq,MA07,MA10,12.Sep.07,-205693,-243719,1,44.9,17.6,4.3531,2.849,4.3134,-2.8968,37.3097,6.1166,0.5283,1 +CoH2AsO4+,NA,CoH2AsO4+,aq,MA07,MA10,12.Sep.07,-193388,-232357,-1.5,45.2,13.9,3.8628,1.6516,4.8275,-2.8473,37.7921,6.1625,0.5664,1 +NiH2AsO4+,NA,NiH2AsO4+,aq,MA07,MA10,12.Sep.07,-193146,-233785,-7.1,36.4,10,3.358,0.4185,5.3569,-2.7963,33.4496,4.375,0.6516,1 +CuH2AsO4+,NA,CuH2AsO4+,aq,MA07,MA10,12.Sep.07,-166866,-204382,4.1,49.9,14.9,3.9712,1.9164,4.7138,-2.8583,39.7683,7.1249,0.4813,1 +ZnH2AsO4+,NA,ZnH2AsO4+,aq,MA07,MA10,12.Sep.07,-215927,-255372,-0.3,50.7,15.3,4.0397,2.0836,4.642,-2.8652,40.8741,7.2945,0.5485,1 +PbH2AsO4+,NA,PbH2AsO4+,aq,MA07,MA10,12.Sep.07,-187896,-215577,44.7,34.1,25,5.1359,4.7611,3.4924,-2.9759,24.9084,3.9167,-0.1328,1 +AlH2AsO4+2,NA,AlH2AsO4+2,aq,MA07,MA10,12.Sep.07,-299978,-350717,-57,34.9,-7.1,1.4491,-4.244,7.3587,-2.6036,44.5413,4.0694,1.9508,2 +FeH2AsO4+2,NA,FeH2AsO4+2,aq,MA07,MA10,12.Sep.07,-189949,-235535,-39.9,66.2,1.1,2.4901,-1.7013,6.267,-2.7087,60.4374,10.4402,1.6927,2 +NaHAsO4-,NA,NaHAsO4-,aq,MA07,MA10,12.Sep.07,-234025,-272938,19.4,11,16.4,4.464,3.12,4.197,-2.908,24.8601,-0.79,1.3274,-1 +KHAsO4-,NA,KHAsO4-,aq,MA07,MA10,12.Sep.07,-238754,-275247,30.7,3.9,26.1,5.7282,6.2078,2.8713,-3.0357,19.1455,-2.2322,1.1561,-1 +MgHAsO4,NA,MgHAsO4,aq,MA07,MA10,12.Sep.07,-282655,-326456,-17.1,-3.4,-0.5,1.6885,-3.6591,7.1076,-2.6278,3.8675,-3.7233,-0.038,0 +CaHAsO4,NA,CaHAsO4,aq,MA07,MA10,12.Sep.07,-306038,-344341,3.5,-5.6,2,2.0228,-2.8426,6.757,-2.6615,2.5879,-4.1694,-0.038,0 +SrHAsO4,NA,SrHAsO4,aq,MA07,MA10,12.Sep.07,-307750,-344917,9.8,-8.1,2.4,2.0851,-2.6905,6.6917,-2.6678,1.1155,-4.6827,-0.038,0 +MnHAsO4,NA,MnHAsO4,aq,MA07,MA10,12.Sep.07,-229564,-268033,0.7,-2.1,2.7,2.1148,-2.618,6.6606,-2.6708,4.592,-3.4707,-0.038,0 +FeHAsO4,NA,FeHAsO4,aq,MA07,MA10,12.Sep.07,-196961,-237958,-8.9,-5.9,-0.9,1.6263,-3.8112,7.1729,-2.6215,2.3717,-4.2448,-0.038,0 +CoHAsO4,NA,CoHAsO4,aq,MA07,MA10,12.Sep.07,-187516,-229240,-10.7,-5.8,-3.2,1.3102,-4.5832,7.5044,-2.5896,2.4302,-4.2244,-0.038,0 +NiHAsO4,NA,NiHAsO4,aq,MA07,MA10,12.Sep.07,-185083,-227995,-14.7,-9.7,-5.7,0.9749,-5.4021,7.8559,-2.5557,0.1514,-5.0188,-0.038,0 +CuHAsO4,NA,CuHAsO4,aq,MA07,MA10,12.Sep.07,-160044,-200797,-6.7,-3.7,-2.6,1.3964,-4.3727,7.414,-2.5983,3.6572,-3.7966,-0.038,0 +ZnHAsO4,NA,ZnHAsO4,aq,MA07,MA10,12.Sep.07,-209827,-252128,-9.9,-3.4,-2.4,1.4251,-4.3025,7.3838,-2.6012,3.8733,-3.7213,-0.038,0 +PbHAsO4,NA,PbHAsO4,aq,MA07,MA10,12.Sep.07,-180119,-214509,22.2,-10.7,3.7,2.2585,-2.267,6.5099,-2.6853,-0.4328,-5.2225,-0.038,0 +AlHAsO4+,NA,AlHAsO4+,aq,MA07,MA10,12.Sep.07,-295884,-343378,-46.1,-37.3,-8.2,1.0572,-5.2011,7.7697,-2.564,-4.1613,-10.6336,1.242,1 +FeHAsO4+,NA,FeHAsO4+,aq,MA07,MA10,12.Sep.07,-188188,-232211,-34.7,-23.4,-4.9,1.4545,-4.2306,7.353,-2.6042,2.37,-7.8022,1.0694,1 +NaAsO4-2,NA,NaAsO4-2,aq,MA07,MA10,12.Sep.07,-223700,-253943,48.5,-38.4,-17,0.2824,-7.0935,8.5822,-2.4858,6.8433,-10.8648,2.5085,-2 +KAsO4-2,NA,KAsO4-2,aq,MA07,MA10,12.Sep.07,-228428,-249049,84,-45.5,-9.64,1.1121,-5.0669,7.712,-2.5696,-2.2416,-12.307,1.9714,-2 +MgAsO4-,NA,MgAsO4-,aq,MA07,MA10,12.Sep.07,-271474,-307316,9.64,-55,-25.98,-1.3284,-11.0278,10.2713,-2.3232,-12.33,-14.2311,1.3662,-1 +CaAsO4-,NA,CaAsO4-,aq,MA07,MA10,12.Sep.07,-294913,-323114,37.4,-57.2,-25.5,-1.3685,-11.1259,10.3134,-2.3191,-17.4821,-14.6772,1.0531,-1 +SrAsO4-,NA,SrAsO4-,aq,MA07,MA10,12.Sep.07,-296243,-323239,43.9,-59.7,-25.41,-1.3889,-11.1758,10.3349,-2.317,-19.8655,-15.1905,0.9562,-1 +MnAsO4-,NA,MnAsO4-,aq,MA07,MA10,12.Sep.07,-218289,-247805,30.7,-53.7,-25.37,-1.2541,-10.8464,10.1934,-2.3307,-14.5434,-13.9785,1.339,-1 +FeAsO4-,NA,FeAsO4-,aq,MA07,MA10,12.Sep.07,-186668,-218541,21.7,-57.5,-26.07,-1.3653,-11.1181,10.3101,-2.3194,-15.504,-14.7525,1.2932,-1 +CoAsO4-,NA,CoAsO4-,aq,MA07,MA10,12.Sep.07,-177190,-210481,17.6,-57.4,-26.53,-1.4073,-11.2205,10.3541,-2.3152,-14.8722,-14.7322,1.3555,-1 +NiAsO4-,NA,NiAsO4-,aq,MA07,MA10,12.Sep.07,-176304,-211320,11.8,-61.3,-27.01,-1.4432,-11.3083,10.3918,-2.3116,-16.3404,-15.5266,1.4434,-1 +CuAsO4-,NA,CuAsO4-,aq,MA07,MA10,12.Sep.07,-151743,-183607,23.1,-55.3,-26.4,-1.4178,-11.2463,10.3651,-2.3141,-14.418,-14.3044,1.2716,-1 +ZnAsO4-,NA,ZnAsO4-,aq,MA07,MA10,12.Sep.07,-200121,-233853,18.9,-55,-26.36,-1.3907,-11.1799,10.3366,-2.3169,-13.6104,-14.229,1.3358,-1 +PbAsO4-,NA,PbAsO4-,aq,MA07,MA10,12.Sep.07,-169793,-194437,54.9,-62.3,-25.16,-1.4108,-11.2291,10.3577,-2.3148,-22.9414,-15.7303,0.7904,-1 +AlAsO4,NA,AlAsO4,aq,MA07,MA10,12.Sep.07,-285558,-330011,-35.9,-60.2,-9.75,0.418,-6.7624,8.44,-2.4995,-29.3427,-15.3014,-0.038,0 +FeAsO4,NA,FeAsO4,aq,MA07,MA10,12.Sep.07,-177862,-218546,-23.5,-84.8,-13.09,-0.0391,-7.8787,8.9193,-2.4533,-43.7161,-20.3124,-0.038,0 +NaH2AsO3,NA,NaH2AsO3,aq,MA07,MA10,12.Sep.07,-203270,-228832,39.7,28.4,32.7,6.2236,7.4178,2.3518,-3.0857,22.4338,2.7495,-0.038,0 +AgH2AsO3,NA,AgH2AsO3,aq,MA07,MA10,12.Sep.07,-123526,-147071,44.3,25.8,33,6.2709,7.5332,2.3022,-3.0905,20.9088,2.2178,-0.038,0 +MgH2AsO3+,NA,MgH2AsO3+,aq,MA07,MA10,12.Sep.07,-251410,-286183,-11.3,41.3,9.9,3.3617,0.4276,5.353,-2.7967,36.9078,5.3772,0.7149,1 +CaH2AsO3+,NA,CaH2AsO3+,aq,MA07,MA10,12.Sep.07,-274922,-301872,17.1,36.4,13.8,3.7486,1.3726,4.9473,-2.8358,30.0706,4.3735,0.2853,1 +SrH2AsO3+,NA,SrH2AsO3+,aq,MA07,MA10,12.Sep.07,-275601,-300702,25.8,30.7,14.5,3.8032,1.506,4.89,-2.8413,25.5459,3.2185,0.1538,1 +BaH2AsO3+,NA,BaH2AsO3+,aq,MA07,MA10,12.Sep.07,-276315,-297936,40.1,25.6,19.9,4.4634,3.1185,4.1977,-2.908,20.5926,2.1872,-0.0628,1 +CuH2AsO3+,NA,CuH2AsO3+,aq,MA07,MA10,12.Sep.07,-134368,-164924,3,40.5,6.5,2.8237,-0.8865,5.9172,-2.7424,34.4453,5.2122,0.499,1 +PbH2AsO3+,NA,PbH2AsO3+,aq,MA07,MA10,12.Sep.07,-153138,-174063,42.8,24.7,16.5,3.9918,1.9667,4.6922,-2.8603,19.6811,2.0039,-0.1047,1 +AlH2AsO3+2,NA,AlH2AsO3+2,aq,MA07,MA10,12.Sep.07,-266611,-309612,-55.5,25.5,-15.6,0.2882,-7.0795,8.5761,-2.4864,38.8545,2.1567,1.929,2 +FeH2AsO3+2,NA,FeH2AsO3+2,aq,MA07,MA10,12.Sep.07,-154392,-192413,-39.1,56.8,-7.3,1.3321,-4.5295,7.4813,-2.5918,54.8314,8.5274,1.6797,2 PdCl+,PdCl+,PdCl+,aq,"SS98a.3 [S98]",NA,16.Aug.15,3310,-3820,-3.9,21,5.1,2.6729,-1.2577,6.2503,-2.7269,24.1532,1.2501,0.6143,1 PdCl2,PdCl2,PdCl2,aq,"SS98a.3 [S98]",NA,16.Aug.15,-34080,-51390,4.2,37.8,32.4,6.1933,7.3404,2.8664,-3.0824,28.0429,4.665,-0.03,0 PdCl3-,PdCl3-,PdCl3-,aq,"SS98a.3 [S98]",NA,16.Aug.15,-68390,-98890,2.5,44.6,62.9,10.9057,18.8497,-1.6645,-3.5581,46.9452,6.0491,1.5895,-1 Modified: pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_aq.csv.xz =================================================================== --- pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_aq.csv.xz 2019-02-24 13:48:00 UTC (rev 410) +++ pkg/CHNOSZ/inst/extdata/OBIGT/inorganic_aq.csv.xz 2019-02-24 22:46:53 UTC (rev 411) @@ -1,4 +1,4 @@ -?7zXZ???F!t/??????Y]7I??b???9??????TB;q?"?q???cL;?"??e?]??{A!2./???2$]`???l???F%????????(?Befru ?i?????l???d????' ?? ?G?? ?d???\???????_?Q???6?~c??`B|?c??1??q#??6??????Q? ~k!??????oi?Q??d1?F?`??????al??R?9!??[????@|]\< ?Q????/|o?(`????/,#J?/qL??i(?#6??????? ?A??!4??"Cn?:B?$P.?1?&?"0W???????W?6?]?P?s?43??cO?n? -????? ??'?v?C?#~i:l??+?-?f?[?????-L5???x?n????XE?R?~Zt4L:?B?!1k??.???5?????L? OK???3?e??#}??8??U?)$? ?d?w??(?9|?/r?'??";?" ?W?D????>YI?|?.?-?>?7?????loz,???l? ?/6*??m?N"q??TX?`Zn;\] ?????3~?x??? s1W?7SPe?H??????,????????i?s?1?b???????+????Y?,?N??!g?????4??I{C-!W?v??g??????S??PF??????I???>_?f??x?H??Uuc?\??G-???1)????&??.In?o???'?;??Te?????????-??*`?]???%?T?H7?0? )??C?E??R?]?1???????7,s??c:2 ?????2Rc?T??????m??=e???e???X:1? -? ??f???"8??(??q?-+(???y???Lr??P at O?)??n?zl?T??(?0?L?v!?+OYY?+B.5???~??=M25?,?8??&>?h???i?US>?z`?rs&?:?zuK;??;r(????5Z0pY"?U@?~?C? ?|? ?????!?9??a?I?m!???Oo???????-3??X??Q? ??t?c?)?}??iN o??? -??[?~Ru?+o??5T?r#a? ??? U?X -?\??%????q?)?!`?M2Lj?jhWZ?? ?? -q?Z?????L????;?k?<$"???K'?W?F???$d,????s?????f????MOmL??l/7???wH?d?B?W??-??:??`????^??`L??\c?(d?? ??|)I4????f???.????? ??%L??r??n?n6!???D?y?WY5,p?J7{???#??K???t???????,?1N? -????G?? ?????rzW????|????O???CZ??Ru? -??iU??L???=??Sj? K0??e?^???o???J???H??*?+H]y??*?L???V?jE??e????z/ - -4?h?_lyWVDH? Y?y"im???@3?ilb2?P@????j,??t?7??eNuu?*zs?|J8?j?L?9q{?M??z0d??'??? -?*??d+??????(?c????kW?1?TX!?[???????]*%?q?<.? 6p?j??|Wm????7?t?r2?)ng????.??i ?????#Qp??'m??? ????cwK.???y???????.W/?7I=I^-&.?????l?s?L -? b?4??aJ'v[??O?FM,??+?I[?#???????? lA*:(?5??p?#??Po?U??????7?!???I?`??%??.Id??S?$???^???s3? ?[ye??&???R?=??5?Q*4?0@#??;zo?O -??{????Am??%.D???(?0?=? H??^;?i??p???)r???6p$5k?Z??J?F???o{?bR?[????`????A???'?e????n??KZ???\?Z?9??\p??*?`??A???????z2???xE54??"??f???:t:5i?g?(C??y5?? -?s???5{!k???(??"?~????O? -???_J?)??p?o-oPO??i??R?m -?:???*?? ????5? M?$ ?K?,cm*a?R*??????=X?0??9N? No?:??????????.?b?7?@R????C"? -Cf?$?????????2???????CkW?-?????F9 -? -? ?d?lp???*/??6?b?5]??? ??L?E???Cj?@=?vATlLZ8?q??c???r??D??&J????1v????xms?????{? ?K???V,?* ?k?9??0?Cu;???iV?? -t\????? -`S?of???I???;??=>?????z?????,=???Uwh?$??M?Hr ?\ -???2????~??;??|???k??~??]?????Hc????N -O=6O ???????te?RG??DT?(???T??'C`????????? X??w?|XJ$????K??9?o?????/?_6?C?y?m:???,!?S? y -V,5??i?+?1?p????P????o`8,HN?51???`A]? -???jH??p??}?)?C??? -???T{??0Sc???j?????cj???J?^??/???,??'?T?3??Bq$?xG???<&?-v?q_? ???2?>%B???`????G8M??-=???????)/?B?#??! -z???N1 at Y?f??????_?#K?pq??|??D??????????Y??O???[??K?fc??CN?????} v85?C?????_?oG?s?????? -Cm???????8??????}Zb_3?yi\.[??Z`???????Q2??+??9?????^??P??N??8?%R??I}m??Q??m???W?0???Q?????? ?u?d\??,Rd?|???F????=R+U?? }k???x?|?y0.3??zX?s?o?0I?s????K????????:???t?x?VZ??0??mbu??H ;?o? ?n??mh??>,aNc????U???gc$?!???ySG??I -??i?-ce?i\NJu??(s???o???Y????Tw7!??3V?U????'|???N_???;J?|;???\?U???=?OokrAG??bH -(???t}?BK?s?W?~s??c????e?????????4???8?????\v0??_???2??dt?4??E_A???N+? -???:??M]v??T?YA?X? -???t[???r 4?\5?6?^??%?J?`???H?F?n??????>Zs -??7???2?S?$EEAvI??????????O(??Q5???T?'!???L~4u?[^;s?\?K??+?????%~?G?`U?????M%??7Lx e ?=!^Z5?}C???????Y?_??#f???.??????52eQ/?Dre??????V????k4????re?/+?)????gdj?[PM?}?"??@?? ?<?>6??(?l???x??????h????oFJZ?6?X??ND?c??W?.T??W??5????8??A?G?*?`??5?p?-1Tk????7?????g[}q???u???R@HB -?4/B?B*??IP??$n?f????S'?k,YQ?C?$????? 2??8U?]??4??[W??????3i????S???w{???????1?;??%A???1?J-)??:??Z?{?z?[2i)$??]?'@???????S@|?-?????~??q? -????Dd?O???@;????*????&?p? -]??? -sh???_$U????&??'\??s*=xA'?[???N2?s?? hK?#\ ??U(?7"eR?1$?^??p?9+???b -p??;^DX?T?<$?}???"_?????2??????????*?XT?H9$?~?G??AA??}?'??E??/;?u???z?K?`?O*?lbl?Lt?8???=??G?qc);?o4/???????????????|?_??&???K?B??S2?y????dEr?1)o2?d>q7sD?5}?:^59?JWz,! -?;Ro??",M??4?F:s??nt>)? -?8%? X%?@??Xs`?p2Z0?????$&???????U???a???pz???????z?7?wq?V??R??O|tn}e?Hb?:O?Pp?-?,?[????[0???????pt??<???Q??????=A?????>?P??`???K. ?? ?????:?? -??o???@??<}??jDb,???EA??-,D???4Vl?Z?#?????pw?2#???~?I0??y????s?? -?O???{?I????s??C????Wq??!????w??_Y?d??tt??$~????????4?k?X???+??wE)??wB;?H?????S*f~py??? 4?+?A?<8n??07???~?%??"?q?r -@?{????]?Y d??g???y9???~??A????w+??cD????[C ?@q????W4??y?]TM?*??j(#K???SC???4x8???Z?J??>????|?!`J)?o??+G??'????B???5M????? ?$???Z4?=??A??`?Rm??_?dW???[?? l????? -S&7?\???B?;bF%??2??#??b??aJ4??l???X????@????Q?????|??1?Y?d??V?Z?qO??{? -?> ?5????2?????????@??+W%???e8?i^?1?:L??qx?)t??y?Z?qpo?w-u??R]7?{W~@?{[N??G?8????+?????^?`???7h??Sn -?????i??:?[?pf ??B?Y???]?q?k4??_???Crq?@w?DSI?C| -?????C?|??K:)?&pZh?y.???C?VFJ?y?=????eOM*T?6??;/,????}3=??x??c?#??;%,?>??4?.??@?#?????c9??rO?? -??5.???=/EF?!k? ??,????{$????F??E????2\?N/??*?/??? -N>:?*?m%#??? -?C??1?-%~?qx??????`QA?P??E????u??????~ ????S?/D>^o?b?H!?^'?i???????q?6??8>?t????_PP?l;_7?.2ByI?zVl?_? ?u %?????QC?J?'??n?"??v$S??????z?????6D?? ?x???.Cgcm"??=?fjB?????wK?*?? ?.IuZW4=?5f???n\???VI(Yc$????J???#\3??pzn????#?????????????mu???j4e:??[CmcxB"u?"?? ???]?9?C??W?h?X???????@L*W?_ ?F?????t???G+A???k?~?NZ ?6j????U?v| 8??z?D=??D???????F~?C????v??X?* , -???O?????M\?>&|?E??d?*?6?F_] l1????r??>PI?k?v??f??????m@????fI?0m=?& X??_{??5??????`?? D[ ??n?=????Sm????|?m?????Z_??;?{a?l???s1Lb??h?? ??4???)?"Q\????l? -??b??;?^2,_?W3???>?????#[??????"T???A??? ?&????Y -{????z?of???*x,Kf???i(<8??A?0???S?T????p0??K ?,T?O?<1V????2/???U?n?G???kl?"?wF s????DO?j?????8|?k??c?L\]?$ -\?Y???9????C?8?fe%6?K???9=#?A|J?}N+??]1??AN??4???9??/?0T? b????R?^???o??W???SS?????Oy`W?o??0??f??<??:^?$???X?????0???? ?+/S H???`~?A???N???S????jR??%:?i??I?%?u????(2N?!b}?i????XlRTP?"??? K?j????o??A1=?[??k -?? ?!??u?]??l?????\????;?f?a[???d?#ET?7?M8JpH???C?"~k? ? ??sYq?" A??? -?G?c????,?5?D?C ????J~??t?B?{e?I%? ?V?y?#??2? 8????t?????K??#????OHs??,5???)? -?NY *|??T???!bA?E????o??{~?ih????#;??????-tZ?s??X\R???n;@????I??k~?^?h??X???}??*^\?? :??61???*??B??/ -aB??AQs?{?4y,??6?0;??z8????:v@?w7??H?f?4?l???F??????dx -????Kp??M?A?q ? ?????vQ???%????,?a??B6??O\????kr??;t??????wX???={?????????f??e???{?`??`C???DD??s??UW;????R??j?L8????L???@???vIo?y??N?h?^??l??uqY?*????w4???@?? g2??b[t??? -?RC?6?Ug -J?????????N???E??????H}ND?t&??(td?@?????j??]?e????^??d???* -`??%3Il0K??C'q? -??B?>3+h OK?? ?????p??L? ?3??~rtR??i????}?;?{?.??F=qQu???7r]o?j9?????#|?x/???hZ??B??j??_O??N??MvE????K?0??(??W??4?o???w??'n?s?m??ZD7~???????Si4i6??h -y?A???j9 ]?????i?t[y??y???c??????s?&?p?6?lu?~?1z???N?? b??N[?W???e?V?4??????K????`|:t???????HC?%?,??t?5???|?D&]|?g?Z??8#o#8d???&K??b????V??4q2U???|D??`?#?{$?T{j???.?KG??-'?1J,4?ec`?????????4-??????Z????N^???\?x?q???????T r??x??ju2 Gfqx#i?L?-?=??l?ZD??"S6?Z??Exr????v????1?O?sC??x?BU?nm]??'?>??vvu#???E??v=x1b/?T?+?~???Y???jf?4 -??~i.g ?????q???d?? 8F??g?v?^d?n?d??~?I?4??? ???Ws#?FBG?4?~gM??????2Uc?f???.w??o?IS??"l?$?'???[;??W_????jI-???#j?C?vM?? -? ?Lvb??,???sO}7 ?????N??!~RQ??p?U??w?H ,m?)8? (????????????lFGE}H??#DE??3?A?S,?z??V(???^?6U???>??m?k????????X?????/i?u?,2??a{????? -???1?????PK??C?D? ??|???????O0?b?UUO?N??i?????\??? WmA:?i??j?|??? -????<:-??B^:wW2*????????1? ?t?f??????{??I?Y[??!b$?l????)Qv?{???=??[??Ur??????a?5O(?)??jw?????rM???@mkY/ -P?e?PNkf????#?m?C?????5?D.??a??q??????H2? ??K| -??r? ~?)AC?D??z ?g??? -C'q?'.???G???EAlO?m?y????!t[WO?????p ? -??G?n????hL .???b,??V (vk&???v?QV?!=S??\?z4??e?;?????^??????D? HMm???? -?@??'9Z=?g?N?a??g?36?/n?cOh8s?"wmG???S??c?8|??B?7j??i?!&?B?D???P?????+????+?????/)??Q$???h??~??c8?q?w2Y%9???? -Q?e;???_?P??????:?:?b+??'xJ?q93A%K? ?????Q.??(???????i??6xz?????1???iC!???d8?? -??m???}X???g?\?????V{?\????,=[???????S?d?&dV)????H?|??F??nr??'YQ??;?)B????C???~ -{VM??DD????J??)YN???Z???2??w?u?? -?r????????Q??M?{???`??????%K?????????????IAW0?????BI??],? ? ?0????T{????L/4r?? Ys???o???????r -??]?O?3F????R????Q?72???-??a???^???+0 -??u">&?????Lw????UzK5??????pN??KR?f?&????A??P,????a?????$? -???s?4edr???]+? 98`????f7??nK?{JKQ?z?VV}???+? -?(??p'?CLUg?Ff!?0??cuMuQT{#??g??+????G??J?bg?4U??+_??@??J]?$???{BN????j?CUO????|BO/.????J at w??3??^?????A??7???;t?;?g?u?a![?g??m?M4z????????S?+b????M?V???=,?!3?=p?V??W?Z????$??c??!K??|??<???4?)?????W??cJ?aa1"Y??Y?.b?????S?????MQ')1??8A??^i??It?E%?|??+a??2Q??????bQP.???hSO????%?f'U???(?N?????92c??W>u???t???p0;zG??//+???$gGv???B:?6B?t$E?s?&Y?-?0?>t5???m?H??G0q??:?y]????Ed???4c?s?w?????n%??J???-????D??d???;!??x`??u??5?|o???o??,?????{????UgS?,~%}??i??JGrR?E?%D?? -;R?8?4?B????|?u???P ???x-????P???8??z*????[?L?r??s?M???O ???gW6??-?O??&?c?+3)k????g?Hh??n?}???????? v?x)~B????w"2?R???55ofC ?O????i?????d??c????O??kT ???????a[c?z? ??-??[?o?0/_Jp??;/]???yN1A3?m4`R2)`?!uF??C?P?r?s???t@?@?f??,?^m?S:?? -?BW ?f]????3???q???FX?6?U%PU 8?-?2? ?????<6?cT??[pkW???Sa??J7??&}q0X>]?b????l?J????t??? VQb?]?.N%p????ZI???t?O????$???9hLh??B?@??15??#l?)?ro???c??Ya5??)???X1bC?c{p???&x?]uUj+???????9? - ???????q}???^????(?? -?????_??A?????7lF@`e?g?A??@G9??SYO??xC[?.??G??.A*Z0d?N:?t1???>M??A????V?=5?;???;?z???P?Pr??w????????9"7????ODI?????$?.d8???[Vn?6? -??N?Iu?? ?H:?l?0 -t??^t?x~?8N#[!?5???????=/???8w=???2?X|M?u??1??5?B?D??????%a? ?>|??;|?B?Z?W/j?P??????z?????R?y?????y?[R?t{Q???T??V??O?f?q???? S[??:?? ?,@?A&?h??{????I'M???)d9???????kJ,??e????L?E??'???.?,h?$? ?wj??&3??? -?]???60?[Ot??+????????????a?M)??O?????j?????0h??d????????Fs?~ ????|????W????????????8;?,?????< !.?+ -?Rvi????I0?j?T?M?{BX????????^??4X???bH???J???~f_?c*?????3?????m?4?"?|P?t.o?yu,??{~WW .p???":Z?n?}?Y????"???!?1????'????cI??M????":????B - -??s?A??W?9=?????}.???M?pU????q?3?eo=?? q?K<_???Z?$???37??R???P2t?B??_!+?l??=????\?? -???4IM?Q??D"?^?m????&^>??3?????????????Mp?V??O??Q[?y?!:?:g?I@??a??Z?{>????????z??q???`c&?;?4?>?????S -??????Y??[?.?e????M?:mp?U0?????n9????~???W6????q?/??-L??4????Q????????~??[8]??g?G???I?l??*???l??M?d?0O'???;F??)?FpW?B??8??????/}@?&?n???#x?????3????93?? ??|g?&-|W~??>??1=?j??????$????6T???% nHGQ?q??*??????^+E2??bdQ1?q?c??v?8????????????p?V? `??h?t?????n?? ???0c????Rh??*0?hA??? /G??m?????5:??tD?KJ?}o?!M)P?4 ?[?}?} n?^? ? uqk??Khg)???K}:?apJxl?I`\=?????q??y{v???Y?h?:K?+???f????tk??H?????Zs??]g???.2??K?2A9?e?B*??gZ??[8 s-dG???? ?*a??? ?G?? ]J??????S*???L?^ -v$??????!v??`w?jlx!?r???kcW????S"??[??}?? ?z1/E???[ e??'o??qD? ??l?]|G'a??% -????{(?n????\?@}NVVz"???FHkm??Z?\N?wS??^?s?~?hd????os???D'Z??W????cL??M?????;?Y?9u>?^;Q???? ?c??? ?t?u ?(p)o7????i?)?VXAs?g??>? ??l?A?R??e?o?B*??e?}.f?.?+q??????Er?m?A??????q??T??!??N?y???????Y??q?i?L??? 7 PH=??*?P???????F?w?ma?3o?ch????b69??V/?? k??isqB??????I?~}??B-????? D/5?Z??`??o?P???X????0?O?p?S???P?&}R? ?????m?/O`b}?S?B?8??S:?]"6XWw??>#???? ?????[+B /?M.kXR??jg}??^?t#?L???7g?_??C$????(???y^*=y???=??8??-?+@???[?+~?-??^p?D-??????x#?3 ?|p???%C????.???7p??zn??F????Q"Z$;U?'?i?? }?%@???M????????o8?Z????tJ?'?????4L|3??Ynl??gC??8_?M'NH?=Y??XR????~t/!??zBZx6?k???#Hl?0R???/t?{r8??7"???? [TRUNCATED] To get the complete diff run: svnlook diff /svnroot/chnosz -r 411 From noreply at r-forge.r-project.org Mon Feb 25 02:39:52 2019 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Mon, 25 Feb 2019 02:39:52 +0100 (CET) Subject: [CHNOSZ-commits] r412 - in pkg/CHNOSZ: . R man Message-ID: <20190225013952.4ABC418BE5E@r-forge.r-project.org> Author: jedick Date: 2019-02-25 02:39:51 +0100 (Mon, 25 Feb 2019) New Revision: 412 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/R/retrieve.R pkg/CHNOSZ/man/retrieve.Rd Log: retrieve(): add 'add.charge' argument and "all" keyword Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-24 22:46:53 UTC (rev 411) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-25 01:39:51 UTC (rev 412) @@ -1,6 +1,6 @@ -Date: 2019-02-24 +Date: 2019-02-25 Package: CHNOSZ -Version: 1.2.0-19 +Version: 1.2.0-20 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/R/retrieve.R =================================================================== --- pkg/CHNOSZ/R/retrieve.R 2019-02-24 22:46:53 UTC (rev 411) +++ pkg/CHNOSZ/R/retrieve.R 2019-02-25 01:39:51 UTC (rev 412) @@ -3,7 +3,7 @@ # 20190214 initial version # 20190224 use ... for multiple arguments (define a chemical system) -retrieve <- function(..., include.electron = FALSE, include.groups = FALSE, state = NULL) { +retrieve <- function(..., state = NULL, add.charge = TRUE, hide.electron = TRUE, hide.proton = TRUE, hide.groups = TRUE) { ## stoichiometric matrix # what are the formulas of species in the current database? formula <- thermo()$obigt$formula @@ -26,17 +26,26 @@ ## species identification args <- list(...) ispecies <- numeric() + # automatically add charge to a system 20190225 + if(add.charge & length(args) > 1) { + if(!"Z" %in% unlist(args)) args <- c(args, "Z") + } for(elements in args) { - not.present <- ! elements %in% colnames(stoich) - if(any(not.present)) { - if(sum(not.present)==1) stop('"', elements[not.present], '" is not an element that is present in any species') - else stop('"', paste(elements[not.present], collapse='", "'), '" are not elements that are present in any species') + if(identical(elements, "all")) { + ispecies <- 1:nrow(thermo()$obigt) + names(ispecies) <- thermo()$obigt$formula + } else { + not.present <- ! elements %in% colnames(stoich) + if(any(not.present)) { + if(sum(not.present)==1) stop('"', elements[not.present], '" is not an element that is present in any species') + else stop('"', paste(elements[not.present], collapse='", "'), '" are not elements that are present in any species') + } + # identify the species that have the elements + has.elements <- rowSums(stoich[, elements, drop = FALSE] != 0) == length(elements) + # which species are these (i.e. the species index) + ispecies <- c(ispecies, which(has.elements)) + ispecies <- ispecies[!duplicated(ispecies)] } - # identify the species that have the elements - has.elements <- rowSums(stoich[, elements, drop = FALSE] != 0) == length(elements) - # which species are these (i.e. the species index) - ispecies <- c(ispecies, which(has.elements)) - ispecies <- ispecies[!duplicated(ispecies)] } # for a chemical system, defined by multiple arguments, the species can not contain any _other_ elements if(length(args) > 1) { @@ -45,21 +54,26 @@ notsysstoich <- thermo()$stoich[, !isyselements] iother <- rowSums(notsysstoich[ispecies, ] != 0) > 0 ispecies <- ispecies[!iother] - # include the species for "Z" (charge) - if(!include.electron) { - ielectron <- names(ispecies) == "(Z-1)" - ispecies <- ispecies[!ielectron] - } } - # exclude groups and filter states - if(!include.groups) { + # exclude groups and electron and proton + if(hide.groups) { igroup <- grepl("^\\[.*\\]$", thermo()$obigt$name[ispecies]) ispecies <- ispecies[!igroup] } + if(hide.electron) { + ielectron <- names(ispecies) == "(Z-1)" + ispecies <- ispecies[!ielectron] + } + if(hide.proton) { + iproton <- names(ispecies) == "H+" + ispecies <- ispecies[!iproton] + } + # filter states if(!is.null(state)) { istate <- thermo()$obigt$state[ispecies] %in% state ispecies <- ispecies[istate] } + # for names, use e- instead of (Z-1) + names(ispecies)[names(ispecies)=="(Z-1)"] <- "e-" ispecies } - Modified: pkg/CHNOSZ/man/retrieve.Rd =================================================================== --- pkg/CHNOSZ/man/retrieve.Rd 2019-02-24 22:46:53 UTC (rev 411) +++ pkg/CHNOSZ/man/retrieve.Rd 2019-02-25 01:39:51 UTC (rev 412) @@ -7,29 +7,36 @@ } \usage{ - retrieve(..., include.electron = FALSE, include.groups = FALSE, state = NULL) + retrieve(..., state = NULL, add.charge = TRUE, + hide.electron = TRUE, hide.proton = TRUE, hide.groups = TRUE) } \arguments{ \item{...}{list, one or more arguments, each of which is a character vector with the names of one or more chemical elements} - \item{include.electron}{logical, include the electron in the result for chemical systems?} - \item{include.groups}{logical, include groups in the result?} \item{state}{character, filter the result on these state(s).} + \item{add.charge}{logical, add charge to the system?} + \item{hide.electron}{logical, exclude the electron from the result?} + \item{hide.proton}{logical, exclude the proton from the result?} + \item{hide.groups}{logical, exclude groups from the result?} } \details{ This function retrieves the species in the thermodynamic database (see \code{\link{thermo}}) that have all of the elements specified in the arguments. A single argument is interpreted as a combination of one or more elements that must be present in each species. -The return value is a named numeric vector giving the species index (i.e. rownumber(s) of \code{thermo()$obigt}) with names corresponding to the chemical formulas of the species. -If the argument list is empty, then the function returns an empty (length 0) numeric value. +Results can be filtered on physical state by setting the \code{state} argument. -If more than one argument is present, all of the species identified by each argument are combined, then any species containing any other elements are excluded. +If more than one argument is present, all of the species identified by each argument are combined, and all species containing any other elements are excluded. This can be used to retrieve all of the species in the database within a given chemical system. -When searching for charged species in a chemical system (using the element named \samp{Z}), the electron is excluded unless \code{include.electron} is TRUE (note that the electron has a chemical formula of \samp{(Z-1)}). +A chemical system includes charged species if \code{add.charge} is TRUE (the default) or the user supplies the \dQuote{element} of charge (\samp{Z}). -Groups used in group-additivity calculations, which have names with square brackets (e.g. [-CH2-]), are excluded unless \code{include.groups} is TRUE. -Results can be filtered on physical state by setting the \code{state} argument. +The electron and proton are excluded from the result unless \code{hide.electron} and/or \code{hide.proton} is FALSE. +Groups used in group-additivity calculations, which have names with square brackets (e.g. [-CH2-]), are also excluded unless \code{hide.groups} is FALSE. +The return value is a named numeric vector giving the species index (i.e. rownumber(s) of \code{thermo()$obigt}) with names corresponding to the chemical formulas of the species. +However, if electron is included in the result, the result uses its name (\samp{e-}) instead of its chemical formula (\samp{(Z-1)}). +If the argument list is empty, then the function returns an empty (length 0) numeric value. +A special argument value \samp{all} can be used to retrieve all species in the thermodynamic database, including filtering on state and hiding of the proton, electron, and/or groups. + The first time the function is run, it uses \code{\link{i2A}} to build the stoichiometric matrix for the current database. Following runs use the previously calculated stoichiometric matrix, unless a change to the database is detected, which triggers a recalculation. } @@ -44,19 +51,16 @@ # thermodynamic data for those minerals info(retrieve("Ti")) -# thermodynamic data for Au-Cl complexes -info(retrieve(c("Au", "Cl"))) - # all species that have Au retrieve("Au") # all species that have both Au and Cl retrieve(c("Au", "Cl")) -# all species that have Au and/or Cl, and no other elements +# all species that have Au and/or Cl, including charged species, but no other elements retrieve("Au", "Cl") -# all species that have Au and/or Cl and/or Z, and no other elements -retrieve("Au", "Cl", "Z") # include the electron with these species -retrieve("Au", "Cl", "Z", include.electron = TRUE) +retrieve("Au", "Cl", hide.electron = FALSE) +# all uncharged species that have Au and/or Cl +retrieve("Au", "Cl", add.charge = FALSE) # minerals in the system SiO2-MgO-CaO-CO2 retrieve("Si", "Mg", "Ca", "C", "O", state="cr") From noreply at r-forge.r-project.org Mon Feb 25 12:28:33 2019 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Mon, 25 Feb 2019 12:28:33 +0100 (CET) Subject: [CHNOSZ-commits] r413 - in pkg/CHNOSZ: . R man Message-ID: <20190225112833.CB01E18C847@r-forge.r-project.org> Author: jedick Date: 2019-02-25 12:28:33 +0100 (Mon, 25 Feb 2019) New Revision: 413 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/R/AkDi.R pkg/CHNOSZ/R/retrieve.R pkg/CHNOSZ/R/species.R pkg/CHNOSZ/man/retrieve.Rd Log: retrieve(): add 'req1' argument (require first element) Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-25 01:39:51 UTC (rev 412) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-25 11:28:33 UTC (rev 413) @@ -1,6 +1,6 @@ Date: 2019-02-25 Package: CHNOSZ -Version: 1.2.0-20 +Version: 1.2.0-21 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/R/AkDi.R =================================================================== --- pkg/CHNOSZ/R/AkDi.R 2019-02-25 01:39:51 UTC (rev 412) +++ pkg/CHNOSZ/R/AkDi.R 2019-02-25 11:28:33 UTC (rev 413) @@ -22,7 +22,7 @@ for(j in seq_along(property)) { if(property[[j]]=="G") { # send a message - message("AkDi(): Akinfiev-Diamond model for ", PAR$name, " gas to aq") + message("AkDi: Akinfiev-Diamond model for ", PAR$name, " gas to aq") # get gas properties (J mol-1) G_gas <- subcrt(PAR$name, "gas", T=T, P=P, convert=FALSE)$out[[1]]$G # TODO: does this work if E.units is cal or J? Modified: pkg/CHNOSZ/R/retrieve.R =================================================================== --- pkg/CHNOSZ/R/retrieve.R 2019-02-25 01:39:51 UTC (rev 412) +++ pkg/CHNOSZ/R/retrieve.R 2019-02-25 11:28:33 UTC (rev 413) @@ -3,7 +3,7 @@ # 20190214 initial version # 20190224 use ... for multiple arguments (define a chemical system) -retrieve <- function(..., state = NULL, add.charge = TRUE, hide.electron = TRUE, hide.proton = TRUE, hide.groups = TRUE) { +retrieve <- function(..., state = NULL, add.charge = TRUE, hide.groups = TRUE, req1 = FALSE) { ## stoichiometric matrix # what are the formulas of species in the current database? formula <- thermo()$obigt$formula @@ -30,6 +30,7 @@ if(add.charge & length(args) > 1) { if(!"Z" %in% unlist(args)) args <- c(args, "Z") } + # for a numeric first argument, limit the result to only those species 20190225 for(elements in args) { if(identical(elements, "all")) { ispecies <- 1:nrow(thermo()$obigt) @@ -43,6 +44,8 @@ # identify the species that have the elements has.elements <- rowSums(stoich[, elements, drop = FALSE] != 0) == length(elements) # which species are these (i.e. the species index) + # for req1, remember the species containing the first element 20190225 + if(length(ispecies)==0) ispecies1 <- which(has.elements) ispecies <- c(ispecies, which(has.elements)) ispecies <- ispecies[!duplicated(ispecies)] } @@ -55,19 +58,24 @@ iother <- rowSums(notsysstoich[ispecies, ] != 0) > 0 ispecies <- ispecies[!iother] } - # exclude groups and electron and proton + # keep only species that contain the first element + if(req1) { + ispecies <- intersect(ispecies1, ispecies) + names(ispecies) <- thermo()$obigt$name[ispecies] + } + # exclude groups if(hide.groups) { igroup <- grepl("^\\[.*\\]$", thermo()$obigt$name[ispecies]) ispecies <- ispecies[!igroup] } - if(hide.electron) { - ielectron <- names(ispecies) == "(Z-1)" - ispecies <- ispecies[!ielectron] - } - if(hide.proton) { - iproton <- names(ispecies) == "H+" - ispecies <- ispecies[!iproton] - } + #if(hide.electron) { + # ielectron <- names(ispecies) == "(Z-1)" + # ispecies <- ispecies[!ielectron] + #} + #if(hide.proton) { + # iproton <- names(ispecies) == "H+" + # ispecies <- ispecies[!iproton] + #} # filter states if(!is.null(state)) { istate <- thermo()$obigt$state[ispecies] %in% state Modified: pkg/CHNOSZ/R/species.R =================================================================== --- pkg/CHNOSZ/R/species.R 2019-02-25 01:39:51 UTC (rev 412) +++ pkg/CHNOSZ/R/species.R 2019-02-25 11:28:33 UTC (rev 413) @@ -90,7 +90,8 @@ if(!is.null(iobigt)) { if(is.null(thermo$basis)) stop("basis species are not defined") # the coefficients in reactions to form the species from basis species - f <- (species.basis(iobigt)) + # wrap values in unname in case they have names from retrieve(), otherwise makeup() doesn't work as intended 20190225 + f <- (species.basis(unname(iobigt))) # the states and species names state <- as.character(thermo$obigt$state[iobigt]) name <- as.character(thermo$obigt$name[iobigt]) Modified: pkg/CHNOSZ/man/retrieve.Rd =================================================================== --- pkg/CHNOSZ/man/retrieve.Rd 2019-02-25 01:39:51 UTC (rev 412) +++ pkg/CHNOSZ/man/retrieve.Rd 2019-02-25 11:28:33 UTC (rev 413) @@ -7,17 +7,15 @@ } \usage{ - retrieve(..., state = NULL, add.charge = TRUE, - hide.electron = TRUE, hide.proton = TRUE, hide.groups = TRUE) + retrieve(..., state = NULL, add.charge = TRUE, hide.groups = TRUE, req1 = FALSE) } \arguments{ \item{...}{list, one or more arguments, each of which is a character vector with the names of one or more chemical elements} \item{state}{character, filter the result on these state(s).} \item{add.charge}{logical, add charge to the system?} - \item{hide.electron}{logical, exclude the electron from the result?} - \item{hide.proton}{logical, exclude the proton from the result?} \item{hide.groups}{logical, exclude groups from the result?} + \item{req1}{logical, include only species that contain the first element in the system?} } \details{ @@ -28,14 +26,14 @@ If more than one argument is present, all of the species identified by each argument are combined, and all species containing any other elements are excluded. This can be used to retrieve all of the species in the database within a given chemical system. A chemical system includes charged species if \code{add.charge} is TRUE (the default) or the user supplies the \dQuote{element} of charge (\samp{Z}). +If \code{req1} is TRUE, the result corresponds to the intersection of all of the species in the system with those identified by the first argument (i.e. those bearing the first element). -The electron and proton are excluded from the result unless \code{hide.electron} and/or \code{hide.proton} is FALSE. -Groups used in group-additivity calculations, which have names with square brackets (e.g. [-CH2-]), are also excluded unless \code{hide.groups} is FALSE. +Groups used in group-additivity calculations, which have names with square brackets (e.g. [-CH2-]), are excluded unless \code{hide.groups} is FALSE. The return value is a named numeric vector giving the species index (i.e. rownumber(s) of \code{thermo()$obigt}) with names corresponding to the chemical formulas of the species. -However, if electron is included in the result, the result uses its name (\samp{e-}) instead of its chemical formula (\samp{(Z-1)}). +However, if the electron is in the result, its name (\samp{e-}) is used instead of its chemical formula (\samp{(Z-1)}). If the argument list is empty, then the function returns an empty (length 0) numeric value. -A special argument value \samp{all} can be used to retrieve all species in the thermodynamic database, including filtering on state and hiding of the proton, electron, and/or groups. +A special argument value \samp{all} can be used to retrieve all species in the thermodynamic database, including filtering on state and hiding of the groups. The first time the function is run, it uses \code{\link{i2A}} to build the stoichiometric matrix for the current database. Following runs use the previously calculated stoichiometric matrix, unless a change to the database is detected, which triggers a recalculation. @@ -57,13 +55,18 @@ retrieve(c("Au", "Cl")) # all species that have Au and/or Cl, including charged species, but no other elements retrieve("Au", "Cl") -# include the electron with these species -retrieve("Au", "Cl", hide.electron = FALSE) # all uncharged species that have Au and/or Cl retrieve("Au", "Cl", add.charge = FALSE) # minerals in the system SiO2-MgO-CaO-CO2 retrieve("Si", "Mg", "Ca", "C", "O", state="cr") + +# make an Eh-pH diagram for aqueous S-bearing species +basis("CHNOSe") +ispecies <- retrieve("S", "O", "H", req1 = TRUE, state = "aq") +species(ispecies) +a <- affinity(pH = c(0, 14), Eh = c(-1, 1)) +diagram(a, fill = "terrain") } \concept{Extended workflow} From noreply at r-forge.r-project.org Mon Feb 25 14:16:28 2019 From: noreply at r-forge.r-project.org (noreply at r-forge.r-project.org) Date: Mon, 25 Feb 2019 14:16:28 +0100 (CET) Subject: [CHNOSZ-commits] r414 - in pkg/CHNOSZ: . R inst inst/extdata/adds man Message-ID: <20190225131628.73B8218BEA2@r-forge.r-project.org> Author: jedick Date: 2019-02-25 14:16:27 +0100 (Mon, 25 Feb 2019) New Revision: 414 Modified: pkg/CHNOSZ/DESCRIPTION pkg/CHNOSZ/R/protein.info.R pkg/CHNOSZ/inst/CHECKLIST pkg/CHNOSZ/inst/extdata/adds/obigt_check.csv pkg/CHNOSZ/man/retrieve.Rd Log: update obigt_check.csv Modified: pkg/CHNOSZ/DESCRIPTION =================================================================== --- pkg/CHNOSZ/DESCRIPTION 2019-02-25 11:28:33 UTC (rev 413) +++ pkg/CHNOSZ/DESCRIPTION 2019-02-25 13:16:27 UTC (rev 414) @@ -1,6 +1,6 @@ Date: 2019-02-25 Package: CHNOSZ -Version: 1.2.0-21 +Version: 1.2.0-22 Title: Thermodynamic Calculations and Diagrams for Geochemistry Authors at R: c( person("Jeffrey", "Dick", , "j3ffdick at gmail.com", role = c("aut", "cre"), Modified: pkg/CHNOSZ/R/protein.info.R =================================================================== --- pkg/CHNOSZ/R/protein.info.R 2019-02-25 11:28:33 UTC (rev 413) +++ pkg/CHNOSZ/R/protein.info.R 2019-02-25 13:16:27 UTC (rev 414) @@ -16,9 +16,9 @@ # character `protein` and `organism`, e.g. 'LYSC', 'CHICK' # return the row(s) of thermo$protein (possibly per residue) for: # numeric `protein` (the rownumber itself) - t_p <- get("thermo", CHNOSZ)$protein if(is.data.frame(protein)) out <- protein if(is.numeric(protein)) { + t_p <- get("thermo", CHNOSZ)$protein # drop NA matches to thermo$protein iproteins <- 1:nrow(t_p) protein[!protein %in% iproteins] <- NA @@ -29,6 +29,7 @@ # compute per-residue counts if requested if(residue) out[, 5:25] <- out[, 5:25]/rowSums(out[, 6:25]) } else { + t_p <- get("thermo", CHNOSZ)$protein # search for protein by regular expression if(regexp) { iprotein <- grepl(protein, t_p$protein) Modified: pkg/CHNOSZ/inst/CHECKLIST =================================================================== --- pkg/CHNOSZ/inst/CHECKLIST 2019-02-25 11:28:33 UTC (rev 413) +++ pkg/CHNOSZ/inst/CHECKLIST 2019-02-25 13:16:27 UTC (rev 414) @@ -8,7 +8,7 @@ - check output of demo("sources") to make sure all data sources are cited -- recreate extdata/thermo/obigt_check.csv after all data updates: +- recreate extdata/adds/obigt_check.csv after all data updates: co <- check.obigt() write.csv(co, "obigt_check.csv", row.names=FALSE, na="") Modified: pkg/CHNOSZ/inst/extdata/adds/obigt_check.csv =================================================================== --- pkg/CHNOSZ/inst/extdata/adds/obigt_check.csv 2019-02-25 11:28:33 UTC (rev 413) +++ pkg/CHNOSZ/inst/extdata/adds/obigt_check.csv 2019-02-25 13:16:27 UTC (rev 414) @@ -1,9 +1,9 @@ "table","ispecies","name","state","DCp","DV","DG" "OBIGT",14,"CO3-2","aq",,-1.04, "OBIGT",20,"HPO4-2","aq",,-1.02, -"OBIGT",49,"BO2-","aq",,-19.31, -"OBIGT",61,"Cu+2","aq",3.62,, -"OBIGT",65,"NH3","aq",2.75,, +"OBIGT",48,"BO2-","aq",,-19.31, +"OBIGT",60,"Cu+2","aq",3.62,, +"OBIGT",64,"NH3","aq",2.75,, "OBIGT",73,"SO2","aq",11.1,, "OBIGT",91,"LaSO4+","aq",-6.02,, "OBIGT",134,"NdF2+","aq",16.64,6.19, @@ -15,203 +15,197 @@ "OBIGT",185,"EuCl2","aq",-9.84,40.4, "OBIGT",186,"EuCl3-","aq",-17.19,64.47, "OBIGT",187,"EuCl4-2","aq",-26.15,91.04, -"OBIGT",341,"UO4-2","aq",,-1.11, -"OBIGT",378,"Ag(CO3)2-3","aq",,-1.56, -"OBIGT",396,"AgCl4-3","aq",,-1.31, -"OBIGT",444,"CuCl4-2","aq",,-1.07, -"OBIGT",446,"ReO4-","aq",-1.26,, -"OBIGT",455,"PO4-3","aq",,-1.72, -"OBIGT",463,"UO2+2","aq",-1.1,, -"OBIGT",464,"Th+4","aq",,-1.14, -"OBIGT",483,"P2O7-4","aq",,-2.11, -"OBIGT",484,"HP2O7-3","aq",,-1.42, -"OBIGT",498,"SO3-2","aq",,-1.02, -"OBIGT",532,"VO4-3","aq",,-1.63, -"OBIGT",544,"Zr+4","aq",,-1.18, -"OBIGT",551,"Hf+4","aq",,-1.18, -"OBIGT",554,"U+4","aq",,-1.13, -"OBIGT",570,"Ce+4","aq",,-1.13, -"OBIGT",571,"Pr+4","aq",,-1.12, -"OBIGT",572,"Nd+4","aq",,-1.12, -"OBIGT",573,"Pm+4","aq",,-1.13, -"OBIGT",574,"Sm+4","aq",,-1.14, -"OBIGT",575,"Eu+4","aq",,-1.14, -"OBIGT",576,"Gd+4","aq",,-1.16, -"OBIGT",577,"Tb+4","aq",,-1.15, -"OBIGT",578,"Dy+4","aq",,-1.15, -"OBIGT",579,"Ho+4","aq",,-1.15, -"OBIGT",580,"Er+4","aq",,-1.15, -"OBIGT",581,"Tm+4","aq",,-1.16, -"OBIGT",582,"Yb+4","aq",,-1.16, -"OBIGT",583,"Lu+4","aq",,-1.17, -"OBIGT",592,"BeO2-2","aq",,-1.17, -"OBIGT",635,"MnO2-2","aq",,-1.05, -"OBIGT",646,"CoO2-2","aq",,-1.14, -"OBIGT",651,"NiO2-2","aq",,-1.16, -"OBIGT",655,"CuO2-2","aq",,-1.09, -"OBIGT",659,"ZnO2-2","aq",,-1.17, -"OBIGT",674,"CdO2-2","aq",,-1.08, -"OBIGT",692,"RuCl4-2","aq",,-1.09, -"OBIGT",695,"Ru(SO4)3-4","aq",,-1.8, -"OBIGT",702,"RuCl5-2","aq",,-1.49, -"OBIGT",703,"RuCl6-3","aq",,-2.39, -"OBIGT",706,"Ru(SO4)3-3","aq",,-1.3, -"OBIGT",712,"RhCl4-2","aq",,-1.14, -"OBIGT",715,"Rh(SO4)3-4","aq",,-1.82, -"OBIGT",719,"RhCl2+","aq",,4.67, -"OBIGT",724,"Rh(SO4)3-3","aq",,-1.33, -"OBIGT",730,"PdCl4-2","aq",,-1.05, -"OBIGT",733,"Pd(SO4)3-4","aq",,-1.8, -"OBIGT",736,"PtCl+","aq",-3.52,1.25, -"OBIGT",737,"PtCl2","aq",-7.11,2.29, -"OBIGT",738,"PtCl3-","aq",-10.48,1.78, -"OBIGT",739,"PtCl4-2","aq",-13.86,, -"OBIGT",742,"Pt(SO4)3-4","aq",,-1.79, -"OBIGT",745,"CF4","aq",5.9,, -"OBIGT",752,"AsH3","aq",-2.67,, -"OBIGT",841,"MgAsO4-","aq",1.3,, -"OBIGT",844,"MnAsO4-","aq",-1.45,, -"OBIGT",926,"methane","aq",-2.61,, -"OBIGT",931,"hexane","aq",1.43,3.21, -"OBIGT",934,"ethylene","aq",6.12,-3.82, -"OBIGT",958,"propanol","aq",-1.89,, -"OBIGT",1091,"urea","aq",-23.26,23.32, -"OBIGT",1104,"propanoic acid","aq",1.42,, -"OBIGT",1127,"formate","aq",1.96,, -"OBIGT",1129,"propanoate","aq",1.68,, -"OBIGT",1136,"n-decanoate","aq",-1.93,, -"OBIGT",1152,"oxalate-2","aq",-3.19,, -"OBIGT",1419,"Li(Mal)-","aq",,-3.22, -"OBIGT",1423,"Pb(Mal)","aq",,1.16, -"OBIGT",1427,"Pb(Succ)","aq",,1.49, -"OBIGT",1428,"Na(Oxal)-","aq",,-3.14, -"OBIGT",1429,"K(Oxal)-","aq",,-2.75, -"OBIGT",1430,"Fe(Oxal)+","aq",,-2.19, -"OBIGT",1432,"Na(Mal)-","aq",,-3.11, -"OBIGT",1433,"K(Mal)-","aq",,-2.63, -"OBIGT",1435,"La(Mal)+","aq",,-1.92, -"OBIGT",1436,"Gd(Mal)+","aq",,-1.73, -"OBIGT",1437,"Lu(Mal)+","aq",,-2.25, -"OBIGT",1438,"Yb(Mal)+","aq",,-2.05, -"OBIGT",1439,"Th(Mal)+2","aq",-1.29,-4.79, -"OBIGT",1441,"Ce(Mal)+","aq",,-1.75, -"OBIGT",1442,"Nd(Mal)+","aq",4.52,, -"OBIGT",1443,"Sm(Mal)+","aq",,-1.77, -"OBIGT",1444,"Pr(Mal)+","aq",,-1.75, -"OBIGT",1445,"Eu(Mal)+","aq",,-1.87, -"OBIGT",1446,"Tb(Mal)+","aq",,-1.92, -"OBIGT",1447,"Dy(Mal)+","aq",,-1.89, -"OBIGT",1448,"Tm(Mal)+","aq",,-2.08, -"OBIGT",1449,"Ho(Mal)+","aq",,-2.08, -"OBIGT",1450,"Er(Mal)+","aq",,-2.11, -"OBIGT",1451,"Sc(Mal)+","aq",,-1.97, -"OBIGT",1452,"Fe(Mal)+","aq",,-1.97, -"OBIGT",1453,"Na(Succ)-","aq",,-2.82, -"OBIGT",1454,"K(Succ)-","aq",,-2.39, -"OBIGT",1460,"Th(Succ)+2","aq",-1.21,-4.47, -"OBIGT",1465,"NH4(Oxal)-","aq",,-2.62, -"OBIGT",1470,"Yb(Oxal)+","aq",,-2.02, -"OBIGT",1471,"Ce(Oxal)+","aq",,-1.8, -"OBIGT",1472,"Nd(Oxal)+","aq",,-1.8, -"OBIGT",1473,"Eu(Oxal)+","aq",,-1.89, -"OBIGT",1474,"Gd(Oxal)+","aq",,-1.8, -"OBIGT",1475,"Ru(Oxal)+","aq",,-2.41, -"OBIGT",1476,"Pa(Oxal)+2","aq",-1.25,-4.63, -"OBIGT",1477,"Th(Oxal)+2","aq",-1.27,-4.69, -"OBIGT",1478,"U(Oxal)+2","aq",-1.25,-4.63, -"OBIGT",1479,"Np(Oxal)+2","aq",-1.27,-4.69, -"OBIGT",1482,"Am(Oxal)+","aq",,-1.8, -"OBIGT",1483,"Cm(Oxal)+","aq",,-1.8, -"OBIGT",1484,"Y(Oxal)+","aq",,-2.11, -"OBIGT",1489,"La(Oxal)+","aq",,-1.87, -"OBIGT",1490,"Tb(Oxal)+","aq",,-1.92, -"OBIGT",1491,"Er(Oxal)+","aq",,-2.05, -"OBIGT",1492,"Lu(Oxal)+","aq",,-2.19, -"OBIGT",1493,"Cr(Oxal)+","aq",,-2.58, -"OBIGT",1494,"Ga(Oxal)+","aq",,-2.66, -"OBIGT",1495,"Sc(Oxal)+","aq",,-2.13, -"OBIGT",1496,"In(Oxal)+","aq",,-2.19, -"OBIGT",1497,"Pu(Oxal)+2","aq",-1.2,-4.44, -"OBIGT",1498,"NpO2(Oxal)","aq",,-1.94, -"OBIGT",1499,"Sm(Oxal)+","aq",,-1.84, -"OBIGT",1500,"Cs(Mal)-","aq",,-2.39, -"OBIGT",1501,"NH4(Mal)-","aq",,-2.54, -"OBIGT",1506,"In(Mal)+","aq",,-2.11, -"OBIGT",1507,"Y(Mal)+","aq",,-2.02, -"OBIGT",1515,"La(Succ)+","aq",,-1.52, -"OBIGT",1516,"NH4(Succ)-","aq",,-2.26, -"OBIGT",1518,"Fe(Succ)+","aq",,-1.92, -"OBIGT",1519,"Sc(Succ)+","aq",,-1.77, -"OBIGT",1522,"NpO2(Succ)","aq",,-3.16, -"OBIGT",1523,"Sm(Succ)+","aq",,-1.48, -"OBIGT",1524,"Er(Succ)+","aq",,-1.68, -"OBIGT",1525,"U(Succ)+2","aq",-1.15,-4.27, -"OBIGT",1529,"La(Glut)+","aq",,-1.23, -"OBIGT",1530,"Y(Glut)+","aq",,-1.46, -"OBIGT",1531,"Sc(Glut)+","aq",,-1.5, -"OBIGT",1532,"Th(Glut)+2","aq",-1.09,-4.05, -"OBIGT",1535,"Fe(Glut)+","aq",,-1.05, -"OBIGT",1536,"Sm(Glut)+","aq",,-1.2, -"OBIGT",1539,"Er(Glut)+","aq",,-1.4, -"OBIGT",1541,"Ba(Adip)","aq",,1.19, -"OBIGT",1548,"Pb(Adip)","aq",,1.25, -"OBIGT",1549,"Sc(Adip)+","aq",,-1.22, -"OBIGT",1551,"Th(Adip)+2","aq",-1.02,-3.76, -"OBIGT",1552,"U(Adip)+2","aq",-1,-3.71, -"OBIGT",1554,"Li(Oxal)-","aq",,-3.3, -"OBIGT",1558,"Li(Succ)-","aq",,-2.94, -"OBIGT",1560,"Na(Glut)-","aq",,-2.34, -"OBIGT",1561,"K(Glut)-","aq",,-2.05, -"OBIGT",1562,"Li(Glut)-","aq",,-2.66, -"OBIGT",1567,"Na(Adip)-","aq",,-2.05, -"OBIGT",1568,"K(Adip)-","aq",,-1.76, -"OBIGT",1569,"Li(Adip)-","aq",,-2.38, -"OBIGT",1575,"cyclohexane","aq",9.35,6.64, -"OBIGT",1576,"argon","aq",-1.24,-8.59, -"OBIGT",1577,"benzene","aq",,-1.14, -"OBIGT",1578,"CO2","aq",-4.94,, -"OBIGT",1579,"xenon","aq",2.8,, -"OBIGT",1589,"n-butanethiol","aq",2.19,, -"OBIGT",1611,"methyldiethanolamine","aq",1.61,, -"OBIGT",1621,"cysteinate","aq",-1,, -"OBIGT",1647,"glucose","aq",1.11,, -"OBIGT",1675,"guanine","aq",-4.26,, -"OBIGT",1719,"dHUMP-","aq",-3.13,, -"OBIGT",1816,"MgADP-","aq",-1.01,, -"OBIGT",1827,"HNicMP(ox)","aq",,9.4, -"OBIGT",1835,"ribose-5-phosphate","aq",,7.48, -"OBIGT",1837,"ribose-5-phosphate-2","aq",1.53,, -"OBIGT",1838,"H4NADP(red)","aq",1.73,, -"OBIGT",1839,"H3NADP(red)-","aq",2.41,, -"OBIGT",1840,"H2NADP(red)-2","aq",1.28,, -"OBIGT",1841,"HNADP(red)-3","aq",2.09,, -"OBIGT",1842,"NADP(red)-4","aq",1.09,, -"OBIGT",1844,"H3NADP(ox)","aq",1.05,, -"OBIGT",1915,"diglycine+","aq",-177.69,, -"OBIGT",1916,"diglycine-","aq",-49.22,, -"OBIGT",1917,"triglycine+","aq",,1.75, -"OBIGT",1918,"triglycine-","aq",,1.78, -"OBIGT",2048,"jarosite","cr",,,20697 -"OBIGT",2049,"natrojarosite","cr",,,17554 -"OBIGT",2068,"dawsonite","cr",,,4653 -"OBIGT",2089,"n-octadecane","cr",-2.63,, -"OBIGT",2090,"n-nonadecane","cr",-13.32,, -"OBIGT",2091,"n-eicosane","cr",-2.79,, -"OBIGT",2092,"n-heneicosane","cr",-8.61,, -"OBIGT",2093,"n-docosane","cr",-2.63,, -"OBIGT",2094,"n-tricosane","cr",-5.22,, -"OBIGT",2095,"n-tetracosane","cr",-2.02,, -"OBIGT",2096,"n-pentacosane","cr",-2.93,, -"OBIGT",2097,"n-hexacosane","cr",-1.29,, -"OBIGT",2098,"n-heptacosane","cr",-1.23,, -"OBIGT",2150,"carbazole","cr",-43.39,, -"OBIGT",2191,"triphenylene","cr",,,541 -"OBIGT",2504,"deoxyadenosine","cr",,,-2977 -"OBIGT",2691,"n-nonacontane","liq",,,635 -"OBIGT",2698,"2-methyloctane","liq",10,, -"OBIGT",3111,"5,6-dithiadecane","liq",2,, -"OBIGT",3186,"ethylene","gas",-4.59,, -"OBIGT",3196,"3,5-dimethylphenol","gas",,,628 +"OBIGT",340,"UO4-2","aq",,-1.11, +"OBIGT",370,"Ag(CO3)2-3","aq",,-1.56, +"OBIGT",386,"AgCl4-3","aq",,-1.31, +"OBIGT",433,"CuCl4-2","aq",,-1.07, +"OBIGT",435,"ReO4-","aq",-1.26,, +"OBIGT",444,"PO4-3","aq",,-1.72, +"OBIGT",451,"UO2+2","aq",-1.1,, +"OBIGT",452,"Th+4","aq",,-1.14, +"OBIGT",471,"P2O7-4","aq",,-2.11, +"OBIGT",472,"HP2O7-3","aq",,-1.42, +"OBIGT",486,"SO3-2","aq",,-1.02, +"OBIGT",520,"VO4-3","aq",,-1.63, +"OBIGT",531,"Zr+4","aq",,-1.18, +"OBIGT",538,"Hf+4","aq",,-1.18, +"OBIGT",542,"U+4","aq",,-1.13, +"OBIGT",558,"Ce+4","aq",,-1.13, +"OBIGT",559,"Pr+4","aq",,-1.12, +"OBIGT",560,"Nd+4","aq",,-1.12, +"OBIGT",561,"Pm+4","aq",,-1.13, +"OBIGT",562,"Sm+4","aq",,-1.14, +"OBIGT",563,"Eu+4","aq",,-1.14, +"OBIGT",564,"Gd+4","aq",,-1.16, +"OBIGT",565,"Tb+4","aq",,-1.15, +"OBIGT",566,"Dy+4","aq",,-1.15, +"OBIGT",567,"Ho+4","aq",,-1.15, +"OBIGT",568,"Er+4","aq",,-1.15, +"OBIGT",569,"Tm+4","aq",,-1.16, +"OBIGT",570,"Yb+4","aq",,-1.16, +"OBIGT",571,"Lu+4","aq",,-1.17, +"OBIGT",580,"BeO2-2","aq",,-1.17, +"OBIGT",623,"MnO2-2","aq",,-1.05, +"OBIGT",634,"CoO2-2","aq",,-1.14, +"OBIGT",639,"NiO2-2","aq",,-1.16, +"OBIGT",643,"CuO2-2","aq",,-1.09, +"OBIGT",657,"CdO2-2","aq",,-1.08, +"OBIGT",673,"RuCl4-2","aq",,-1.09, +"OBIGT",676,"Ru(SO4)3-4","aq",,-1.8, +"OBIGT",683,"RuCl5-2","aq",,-1.49, +"OBIGT",684,"RuCl6-3","aq",,-2.39, +"OBIGT",687,"Ru(SO4)3-3","aq",,-1.3, +"OBIGT",693,"RhCl4-2","aq",,-1.14, +"OBIGT",696,"Rh(SO4)3-4","aq",,-1.82, +"OBIGT",700,"RhCl2+","aq",,4.67, +"OBIGT",705,"Rh(SO4)3-3","aq",,-1.33, +"OBIGT",708,"CF4","aq",5.9,, +"OBIGT",715,"AsH3","aq",-2.67,, +"OBIGT",841,"AgCl","aq",,-1.88, +"OBIGT",842,"AgCl2-","aq",1.65,, +"OBIGT",847,"CuHS","aq",7.35,-16.2, +"OBIGT",855,"ZnO2-2","aq",,-1.17, +"OBIGT",881,"methane","aq",-2.61,, +"OBIGT",886,"hexane","aq",1.43,3.21, +"OBIGT",889,"ethylene","aq",6.12,-3.82, +"OBIGT",913,"propanol","aq",-1.89,, +"OBIGT",1042,"urea","aq",-23.26,23.32, +"OBIGT",1055,"propanoic acid","aq",1.42,, +"OBIGT",1078,"formate","aq",1.96,, +"OBIGT",1080,"propanoate","aq",1.68,, +"OBIGT",1087,"n-decanoate","aq",-1.93,, +"OBIGT",1103,"oxalate-2","aq",-3.19,, +"OBIGT",1370,"Li(Mal)-","aq",,-3.22, +"OBIGT",1374,"Pb(Mal)","aq",,1.16, +"OBIGT",1378,"Pb(Succ)","aq",,1.49, +"OBIGT",1379,"Na(Oxal)-","aq",,-3.14, +"OBIGT",1380,"K(Oxal)-","aq",,-2.75, +"OBIGT",1381,"Fe(Oxal)+","aq",,-2.19, +"OBIGT",1383,"Na(Mal)-","aq",,-3.11, +"OBIGT",1384,"K(Mal)-","aq",,-2.63, +"OBIGT",1386,"La(Mal)+","aq",,-1.92, +"OBIGT",1387,"Gd(Mal)+","aq",,-1.73, +"OBIGT",1388,"Lu(Mal)+","aq",,-2.25, +"OBIGT",1389,"Yb(Mal)+","aq",,-2.05, +"OBIGT",1390,"Th(Mal)+2","aq",-1.29,-4.79, +"OBIGT",1392,"Ce(Mal)+","aq",,-1.75, +"OBIGT",1393,"Nd(Mal)+","aq",4.52,, +"OBIGT",1394,"Sm(Mal)+","aq",,-1.77, +"OBIGT",1395,"Pr(Mal)+","aq",,-1.75, +"OBIGT",1396,"Eu(Mal)+","aq",,-1.87, +"OBIGT",1397,"Tb(Mal)+","aq",,-1.92, +"OBIGT",1398,"Dy(Mal)+","aq",,-1.89, +"OBIGT",1399,"Tm(Mal)+","aq",,-2.08, +"OBIGT",1400,"Ho(Mal)+","aq",,-2.08, +"OBIGT",1401,"Er(Mal)+","aq",,-2.11, +"OBIGT",1402,"Sc(Mal)+","aq",,-1.97, +"OBIGT",1403,"Fe(Mal)+","aq",,-1.97, +"OBIGT",1404,"Na(Succ)-","aq",,-2.82, +"OBIGT",1405,"K(Succ)-","aq",,-2.39, +"OBIGT",1411,"Th(Succ)+2","aq",-1.21,-4.47, +"OBIGT",1416,"NH4(Oxal)-","aq",,-2.62, +"OBIGT",1421,"Yb(Oxal)+","aq",,-2.02, +"OBIGT",1422,"Ce(Oxal)+","aq",,-1.8, +"OBIGT",1423,"Nd(Oxal)+","aq",,-1.8, +"OBIGT",1424,"Eu(Oxal)+","aq",,-1.89, +"OBIGT",1425,"Gd(Oxal)+","aq",,-1.8, +"OBIGT",1426,"Ru(Oxal)+","aq",,-2.41, +"OBIGT",1427,"Pa(Oxal)+2","aq",-1.25,-4.63, +"OBIGT",1428,"Th(Oxal)+2","aq",-1.27,-4.69, +"OBIGT",1429,"U(Oxal)+2","aq",-1.25,-4.63, +"OBIGT",1430,"Np(Oxal)+2","aq",-1.27,-4.69, +"OBIGT",1433,"Am(Oxal)+","aq",,-1.8, +"OBIGT",1434,"Cm(Oxal)+","aq",,-1.8, +"OBIGT",1435,"Y(Oxal)+","aq",,-2.11, +"OBIGT",1440,"La(Oxal)+","aq",,-1.87, +"OBIGT",1441,"Tb(Oxal)+","aq",,-1.92, +"OBIGT",1442,"Er(Oxal)+","aq",,-2.05, +"OBIGT",1443,"Lu(Oxal)+","aq",,-2.19, +"OBIGT",1444,"Cr(Oxal)+","aq",,-2.58, +"OBIGT",1445,"Ga(Oxal)+","aq",,-2.66, +"OBIGT",1446,"Sc(Oxal)+","aq",,-2.13, +"OBIGT",1447,"In(Oxal)+","aq",,-2.19, +"OBIGT",1448,"Pu(Oxal)+2","aq",-1.2,-4.44, +"OBIGT",1449,"NpO2(Oxal)","aq",,-1.94, +"OBIGT",1450,"Sm(Oxal)+","aq",,-1.84, +"OBIGT",1451,"Cs(Mal)-","aq",,-2.39, +"OBIGT",1452,"NH4(Mal)-","aq",,-2.54, +"OBIGT",1457,"In(Mal)+","aq",,-2.11, +"OBIGT",1458,"Y(Mal)+","aq",,-2.02, +"OBIGT",1466,"La(Succ)+","aq",,-1.52, +"OBIGT",1467,"NH4(Succ)-","aq",,-2.26, +"OBIGT",1469,"Fe(Succ)+","aq",,-1.92, +"OBIGT",1470,"Sc(Succ)+","aq",,-1.77, +"OBIGT",1473,"NpO2(Succ)","aq",,-3.16, +"OBIGT",1474,"Sm(Succ)+","aq",,-1.48, +"OBIGT",1475,"Er(Succ)+","aq",,-1.68, +"OBIGT",1476,"U(Succ)+2","aq",-1.15,-4.27, +"OBIGT",1480,"La(Glut)+","aq",,-1.23, +"OBIGT",1481,"Y(Glut)+","aq",,-1.46, +"OBIGT",1482,"Sc(Glut)+","aq",,-1.5, +"OBIGT",1483,"Th(Glut)+2","aq",-1.09,-4.05, +"OBIGT",1486,"Fe(Glut)+","aq",,-1.05, +"OBIGT",1487,"Sm(Glut)+","aq",,-1.2, +"OBIGT",1490,"Er(Glut)+","aq",,-1.4, +"OBIGT",1492,"Ba(Adip)","aq",,1.19, +"OBIGT",1499,"Pb(Adip)","aq",,1.25, +"OBIGT",1500,"Sc(Adip)+","aq",,-1.22, +"OBIGT",1502,"Th(Adip)+2","aq",-1.02,-3.76, +"OBIGT",1503,"U(Adip)+2","aq",-1,-3.71, +"OBIGT",1505,"Li(Oxal)-","aq",,-3.3, +"OBIGT",1509,"Li(Succ)-","aq",,-2.94, +"OBIGT",1511,"Na(Glut)-","aq",,-2.34, +"OBIGT",1512,"K(Glut)-","aq",,-2.05, +"OBIGT",1513,"Li(Glut)-","aq",,-2.66, +"OBIGT",1518,"Na(Adip)-","aq",,-2.05, +"OBIGT",1519,"K(Adip)-","aq",,-1.76, +"OBIGT",1520,"Li(Adip)-","aq",,-2.38, +"OBIGT",1526,"cyclohexane","aq",9.35,6.64, +"OBIGT",1527,"Ar","aq",-1.24,-8.59, +"OBIGT",1528,"benzene","aq",,-1.14, +"OBIGT",1529,"CO2","aq",-4.94,, +"OBIGT",1530,"Xe","aq",2.8,, +"OBIGT",1540,"n-butanethiol","aq",2.19,, +"OBIGT",1562,"methyldiethanolamine","aq",1.61,, +"OBIGT",1572,"cysteinate","aq",-1,, +"OBIGT",1598,"glucose","aq",1.11,, +"OBIGT",1626,"guanine","aq",-4.26,, +"OBIGT",1670,"dHUMP-","aq",-3.13,, +"OBIGT",1767,"MgADP-","aq",-1.01,, +"OBIGT",1778,"HNicMP(ox)","aq",,9.4, +"OBIGT",1786,"ribose-5-phosphate","aq",,7.48, +"OBIGT",1788,"ribose-5-phosphate-2","aq",1.53,, +"OBIGT",1789,"H4NADP(red)","aq",1.73,, +"OBIGT",1790,"H3NADP(red)-","aq",2.41,, +"OBIGT",1791,"H2NADP(red)-2","aq",1.28,, +"OBIGT",1792,"HNADP(red)-3","aq",2.09,, +"OBIGT",1793,"NADP(red)-4","aq",1.09,, +"OBIGT",1795,"H3NADP(ox)","aq",1.05,, +"OBIGT",1866,"diglycine+","aq",-177.69,, +"OBIGT",1867,"diglycine-","aq",-49.22,, +"OBIGT",1868,"triglycine+","aq",,1.75, +"OBIGT",1869,"triglycine-","aq",,1.78, +"OBIGT",1999,"jarosite","cr",,,20697 +"OBIGT",2000,"natrojarosite","cr",,,17554 +"OBIGT",2019,"dawsonite","cr",,,4653 +"OBIGT",2040,"octadecane","cr",-2.63,, +"OBIGT",2041,"nonadecane","cr",-13.32,, +"OBIGT",2042,"eicosane","cr",-2.79,, +"OBIGT",2043,"heneicosane","cr",-8.61,, +"OBIGT",2044,"docosane","cr",-2.63,, +"OBIGT",2045,"tricosane","cr",-5.22,, +"OBIGT",2046,"tetracosane","cr",-2.02,, +"OBIGT",2047,"pentacosane","cr",-2.93,, +"OBIGT",2048,"hexacosane","cr",-1.29,, +"OBIGT",2049,"heptacosane","cr",-1.23,, +"OBIGT",2101,"carbazole","cr",-43.39,, +"OBIGT",2142,"triphenylene","cr",,,541 +"OBIGT",2455,"deoxyadenosine","cr",,,-2977 +"OBIGT",2642,"nonacontane","liq",,,635 +"OBIGT",2649,"2-methyloctane","liq",10,, +"OBIGT",3062,"5,6-dithiadecane","liq",2,, +"OBIGT",3142,"ethylene","gas",-4.59,, +"OBIGT",3152,"3,5-dimethylphenol","gas",,,628 "DEW",15,"BO(OH)","aq",,,-1111 "DEW",19,"CaCl+","aq",,,-593 "DEW",20,"CaCl2","aq",,,-7937 @@ -246,11 +240,23 @@ "DEW",177,"SO3-2","aq",,-1.02, "DEW",186,"U+4","aq",,-1.13, "DEW",199,"ZnCl3-","aq",,,2264 -"SLOP98",4,"AuCl4-3","aq",,,117800 -"SLOP98",11,"AsO4-3","aq",,-1.65, -"SLOP98",20,"Al+3","aq",1.74,, -"SLOP98",27,"Al(Mal)+","aq",,-2.19, -"SLOP98",28,"Al(Oxal)+","aq",,-2.62, +"SLOP98",12,"PtCl+","aq",-3.52,1.25, +"SLOP98",13,"PtCl2","aq",-7.11,2.29, +"SLOP98",14,"PtCl3-","aq",-10.48,1.78, +"SLOP98",15,"PtCl4-2","aq",-13.86,, +"SLOP98",18,"Pt(SO4)3-4","aq",,-1.79,-2915 +"SLOP98",22,"Pd(SO4)3-4","aq",,-1.8, +"SLOP98",26,"ZnCl3-","aq",,,2264 +"SLOP98",27,"Zn(Ac)+","aq",,,-4547 +"SLOP98",29,"Zn(Ac)3-","aq",,,-13968 +"SLOP98",44,"AsO4-3","aq",,-1.65, +"SLOP98",51,"Al+3","aq",1.74,, +"SLOP98",58,"ZnO2-2","aq",,-1.17, +"SLOP98",62,"Al(Mal)+","aq",,-2.19, +"SLOP98",63,"Al(Oxal)+","aq",,-2.62, +"SLOP98",94,"MgAsO4-","aq",1.3,, +"SLOP98",97,"MnAsO4-","aq",-1.45,, +"SLOP98",119,"PdCl4-2","aq",,-1.05, "SUPCRT92",26,"antigorite","cr",,,812 "SUPCRT92",43,"clinochlore,7a","cr",,,666 "SUPCRT92",59,"daphnite,14a","cr",,,-836 Modified: pkg/CHNOSZ/man/retrieve.Rd =================================================================== --- pkg/CHNOSZ/man/retrieve.Rd 2019-02-25 11:28:33 UTC (rev 413) +++ pkg/CHNOSZ/man/retrieve.Rd 2019-02-25 13:16:27 UTC (rev 414) @@ -7,7 +7,8 @@ } \usage{ - retrieve(..., state = NULL, add.charge = TRUE, hide.groups = TRUE, req1 = FALSE) + retrieve(..., state = NULL, add.charge = TRUE, hide.groups = TRUE, + req1 = FALSE) } \arguments{