[CHNOSZ-commits] r690 - in pkg/CHNOSZ: . R inst inst/extdata/OBIGT inst/tinytest man

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Thu Feb 3 10:47:53 CET 2022


Author: jedick
Date: 2022-02-03 10:47:52 +0100 (Thu, 03 Feb 2022)
New Revision: 690

Modified:
   pkg/CHNOSZ/DESCRIPTION
   pkg/CHNOSZ/R/berman.R
   pkg/CHNOSZ/R/cgl.R
   pkg/CHNOSZ/R/info.R
   pkg/CHNOSZ/inst/NEWS.Rd
   pkg/CHNOSZ/inst/extdata/OBIGT/Berman_cr.csv
   pkg/CHNOSZ/inst/tinytest/test-berman.R
   pkg/CHNOSZ/man/add.OBIGT.Rd
   pkg/CHNOSZ/man/berman.Rd
Log:
Include G, H, S, and V for Berman minerals in info()


Modified: pkg/CHNOSZ/DESCRIPTION
===================================================================
--- pkg/CHNOSZ/DESCRIPTION	2022-02-03 03:47:20 UTC (rev 689)
+++ pkg/CHNOSZ/DESCRIPTION	2022-02-03 09:47:52 UTC (rev 690)
@@ -1,6 +1,6 @@
 Date: 2022-02-03
 Package: CHNOSZ
-Version: 1.4.1-15
+Version: 1.4.1-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/berman.R
===================================================================
--- pkg/CHNOSZ/R/berman.R	2022-02-03 03:47:20 UTC (rev 689)
+++ pkg/CHNOSZ/R/berman.R	2022-02-03 09:47:52 UTC (rev 690)
@@ -4,7 +4,7 @@
 #      in the system Na2O-K2O-CaO-MgO-FeO-Fe2O3-Al2O3-SiO2-TiO2-H2O-CO2.
 #      J. Petrol. 29, 445-522. https://doi.org/10.1093/petrology/29.2.445
 
-berman <- function(name, T = 298.15, P = 1, thisinfo=NULL, check.G=FALSE, calc.transition=TRUE, calc.disorder=TRUE, units="cal") {
+berman <- function(name, T = 298.15, P = 1, check.G=FALSE, calc.transition=TRUE, calc.disorder=TRUE, units="cal") {
   # reference temperature and pressure
   Pr <- 1
   Tr <- 298.15
@@ -56,8 +56,10 @@
   # assign values to the variables used below
   for(i in 1:ncol(dat)) assign(colnames(dat)[i], dat[irow, i])
   # get the entropy of the elements using the chemical formula in thermo()$OBIGT
-  if(is.null(thisinfo)) thisinfo <- info(info(name, "cr"), check.it = FALSE)
-  SPrTr_elements <- convert(entropy(thisinfo$formula), "J")
+  file <- system.file("extdata/OBIGT/Berman_cr.csv", package = "CHNOSZ")
+  dat <- read.csv(file)
+  formula <- dat$formula[match(name, dat$name)]
+  SPrTr_elements <- convert(entropy(formula), "J")
   # check that G in data file is the G of formation from the elements --> Benson-Helgeson convention (DG = DH - T*DS)
   if(check.G) {
     GfPrTr_calc <- HfPrTr - Tr * (SPrTr - SPrTr_elements)

Modified: pkg/CHNOSZ/R/cgl.R
===================================================================
--- pkg/CHNOSZ/R/cgl.R	2022-02-03 03:47:20 UTC (rev 689)
+++ pkg/CHNOSZ/R/cgl.R	2022-02-03 09:47:52 UTC (rev 690)
@@ -16,7 +16,7 @@
     PAR <- parameters[k, ]
     if(all(is.na(PAR[9:21]))) {
       # use Berman equations (parameters not in thermo()$OBIGT)
-      properties <- berman(PAR$name, T=T, P=P, thisinfo=PAR)
+      properties <- berman(PAR$name, T = T, P = P)
       iprop <- match(property, colnames(properties))
       values <- properties[, iprop, drop=FALSE]
     } else {

Modified: pkg/CHNOSZ/R/info.R
===================================================================
--- pkg/CHNOSZ/R/info.R	2022-02-03 03:47:20 UTC (rev 689)
+++ pkg/CHNOSZ/R/info.R	2022-02-03 09:47:52 UTC (rev 690)
@@ -190,12 +190,20 @@
   ispeciesmax <- nrow(thermo$OBIGT)
   if(ispecies > ispeciesmax | ispecies < 1) 
     stop(paste("species index", ispecies, "not found in thermo()$OBIGT\n"))
-  # remove scaling factors on EOS parameters depending on state
-  # use new OBIGT2eos function here
+
+  # Remove scaling factors on EOS parameters depending on state
+  # Use new OBIGT2eos function here
   this <- OBIGT2eos(this, this$state)
-  # identify any missing GHS values
+
+  if(all(is.na(this[, 9:21])) & this$name != "water") {
+    # Get G, H, S, and V from datasets using Berman equations 20220203
+    properties <- subset(berman(), name == this$name)
+    this[, c("G", "H", "S", "V")] <- properties[, c("GfPrTr", "HfPrTr", "SPrTr", "VPrTr")] * c(1, 1, 1, 10)
+  }
+
+  # Identify any missing GHS values
   naGHS <- is.na(this[9:11])
-  # a missing one of G, H or S can cause problems for subcrt calculations at high T
+  # A missing one of G, H or S can cause problems for subcrt calculations at high T
   if(sum(naGHS)==1) {
     # calculate a single missing one of G, H, or S from the others
     GHS <- as.numeric(GHS(as.character(this$formula), G=this[,9], H=this[,10], S=this[,11], E_units=this$E_units))
@@ -203,10 +211,10 @@
       this$name, "(", this$state, ") is NA; set to ", round(GHS[naGHS],2), " ", this$E_units, " mol-1")
     this[, which(naGHS)+8] <- GHS[naGHS]
   } 
-  # now perform consistency checks for GHS and EOS parameters if check.it=TRUE
-  # don't do it for the AkDi species 20190219
+
+  # Perform consistency checks for GHS and EOS parameters if check.it = TRUE
+  # Don't do it for the AkDi species 20190219
   if(check.it & !"xi" %in% colnames(this)) {
-print(paste("check.it:", this$name))
     # check GHS if they are all present
     if(sum(naGHS)==0) calcG <- checkGHS(this)
     # check tabulated heat capacities against EOS parameters

Modified: pkg/CHNOSZ/inst/NEWS.Rd
===================================================================
--- pkg/CHNOSZ/inst/NEWS.Rd	2022-02-03 03:47:20 UTC (rev 689)
+++ pkg/CHNOSZ/inst/NEWS.Rd	2022-02-03 09:47:52 UTC (rev 690)
@@ -10,7 +10,7 @@
 \newcommand{\s}{\ifelse{latex}{\eqn{_{#1}}}{\ifelse{html}{\out{<sub>#1</sub>}}{#1}}}
 \newcommand{\S}{\ifelse{latex}{\eqn{^{#1}}}{\ifelse{html}{\out{<sup>#1</sup>}}{^#1}}}
 
-\section{Changes in CHNOSZ version 1.4.1-13 (2022-02-01)}{
+\section{Changes in CHNOSZ version 1.4.1-16 (2022-02-03)}{
 
   \subsection{OBIGT DATABASE}{
     \itemize{
@@ -48,6 +48,10 @@
 
       \item \strong{multi-metal.Rmd} now has a link to the associated paper
       (\href{https://doi.org/10.1016/j.acags.2021.100059}{Dick, 2021}).
+
+      \item \code{info()} with a numeric argument now includes values of
+      \code{G}, \code{H}, \code{S}, and \code{V} at 25 \degC and 1 bar for
+      minerals with thermodynamic parameters in the Berman equations.
       
     }
   }

Modified: pkg/CHNOSZ/inst/extdata/OBIGT/Berman_cr.csv
===================================================================
--- pkg/CHNOSZ/inst/extdata/OBIGT/Berman_cr.csv	2022-02-03 03:47:20 UTC (rev 689)
+++ pkg/CHNOSZ/inst/extdata/OBIGT/Berman_cr.csv	2022-02-03 09:47:52 UTC (rev 690)
@@ -1,93 +1,93 @@
 name,abbrv,formula,state,ref1,ref2,date,E_units,G,H,S,Cp,V,a1.a,a2.b,a3.c,a4.d,c1.e,c2.f,omega.lambda,z.T
-akermanite,Ak,Ca2MgSi2O7,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-albite,Ab,NaAlSi3O8,cr,Ber88,SHD91,2017-10-03,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-"albite,high",hAb,NaAlSi3O8,cr,Ber88,SHD91,2017-10-03,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-"albite,low",lAb,NaAlSi3O8,cr,Ber88,SHD91,2017-10-03,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-almandine,Alm,Si3Fe3Al2O12,cr,Ber88,Ber90.1,2017-10-03,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-andalusite,And,Al2SiO5,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-anorthite,An,Al2CaSi2O8,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-anthophyllite,Ath,Mg7Si8O24H2,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-antigorite,Atg,Mg48Si34O99H62O48,cr,Ber88,BDat17.1,2017-10-09,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-brucite,Brc,MgO2H2,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-Ca-Al-pyroxene,CTs,CaAl2SiO6,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-calcite,Cal,CaCO3,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-chrysotile,Ctl,Mg3Si2O9H4,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-clinochlore,Chl,Mg5Al2Si3O18H8,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-coesite,Coe,SiO2,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-cordierite,Crd,Mg2Al4Si5O18,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-corundum,Crn,Al2O3,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-"cristobalite,alpha",aCrs,SiO2,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-"cristobalite,beta",bCrs,SiO2,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-diaspore,Dsp,AlO2H,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-diopside,Di,MgCaSi2O6,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-dolomite,Dol,MgCaC2O6,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-"enstatite,clino",Cen,MgSiO3,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-enstatite,En,MgSiO3,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-"enstatite,proto",pEn,MgSiO3,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-fayalite,Fa,Fe2SiO4,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-ferrosilite,Fs,SiFeO3,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-forsterite,Fo,Mg2SiO4,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-gehlenite,Gh,Al2Ca2SiO7,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-grossular,Grs,Ca3Al2Si3O12,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-hematite,Hem,Fe2O3,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-ilmenite,Ilm,FeTiO3,cr,Ber88,Ber90.1,2017-10-03,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-jadeite,Jd,NaAlSi2O6,cr,Ber88,SHD91,2017-10-03,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-kaolinite,Kln,Al2Si2O9H4,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-kyanite,Ky,Al2SiO5,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-lawsonite,Lws,CaAl2Si2O10H4,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-lime,Lm,CaO,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-magnesite,Mst,MgCO3,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-magnetite,Mgs,Fe3O4,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-margarite,Mrg,CaAl4Si2O12H2,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-meionite,Mei,Ca4Al6Si6O27C,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-merwinite,Mw,Ca3MgSi2O8,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-monticellite,Mtc,CaMgSiO4,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-muscovite,Ms,KAl3Si3O12H2,cr,Ber88,SHD91,2017-10-03,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-paragonite,Pg,NaAl3Si3O12H2,cr,Ber88,SHD91,2017-10-03,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-periclase,Per,MgO,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-phlogopite,Phl,KMg3AlSi3O12H2,cr,Ber88,SHD91.1,2017-10-03,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-K-feldspar,Kfs,KAlSi3O8,cr,Ber88,SHD91,2017-10-03,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-"K-feldspar,high",Sa,KAlSi3O8,cr,Ber88,SHD91,2017-10-03,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-"K-feldspar,low",Mc,KAlSi3O8,cr,Ber88,SHD91,2017-10-03,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-prehnite,Prh,Ca2Al2Si3O12H2,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-pyrope,Prp,Mg3Al2Si3O12,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-pyrophyllite,Prl,Al2Si4O12H2,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-quartz,Qz,SiO2,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-"quartz,beta",bQz,SiO2,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-rutile,Rt,TiO2,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-sillimanite,Sil,Al2SiO5,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-sphene,Spn,CaTiSiO5,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-spinel,Spl,MgAl2O4,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-talc,Tlc,Mg3Si4O12H2,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-tremolite,Tr,Ca2Mg5Si8O24H2,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-"tridymite,high",hTrd,SiO2,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-"tridymite,low",lTrd,SiO2,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-wollastonite,Wo,CaSiO3,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-pseudowollastonite,pWo,CaSiO3,cr,Ber88,NA,2017-10-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-annite,Ann,Si3Fe3AlKH2O12,cr,Ber90,SHD91.2,2017-10-03,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-fluormuscovite,Flms,KAl3Si3O10F2,cr,ZS92,NA,2017-10-03,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-fluorphlogopite,Fphl,KMg3AlSi3O10F2,cr,ZS92,NA,2017-10-03,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-fluorannite,Flann,Si3Fe3AlKO10F2,cr,ZS92,NA,2017-10-03,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-fluortremolite,Fltr,Ca2Mg5Si8O22F2,cr,ZS92,NA,2017-10-03,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-fluorapatite,Flap,Ca5P3O12F,cr,ZS92,NA,2017-10-03,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-hydroxyapatite,Hyap,Ca5P3O13H,cr,ZS92,NA,2017-10-03,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-chlorapatite,Clap,Ca5P3O12Cl,cr,ZS92,NA,2017-10-03,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-fluortalc,Fltlc,Mg3Si4O10F2,cr,ZS92,NA,2017-10-03,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-chlorphlogopite,Cphl,KMg3AlSi3O10Cl2,cr,ZS92,NA,2017-10-03,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-chlorannite,Clann,Si3Fe3AlKO10Cl2,cr,ZS92,NA,2017-10-03,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-glaucophane,Gln,Na2Al2Mg3Si8O24H2,cr,Eva90,JUN92,2017-10-03,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-pumpellyite,Pmp,Ca4Al5MgSi6O28H7,cr,Eva90,JUN92,2017-10-03,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-aragonite,Arg,CaCO3,cr,FDM+14.1,NA,2017-10-08,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-hedenbergite,Hd,CaFeSi2O6,cr,DS10,NA,2017-11-08,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-andradite,Adr,Ca3Fe2Si3O12,cr,DS10,NA,2017-11-08,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-ferro-actinolite,Fac,Ca2Fe5Si8O22(OH)2,cr,DS10,NA,2017-11-08,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-grunerite,Gru,Fe7Si8O22(OH)2,cr,DS10,NA,2017-11-08,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-ilvaite,Ilv,CaFe2FeSi2O7O(OH),cr,DS10,NA,2017-11-08,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-sudoite,Sud,Mg2Al4Si3O10(OH)8,cr,VGT92,NA,2019-03-06,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-daphnite,Dph,Fe5Al2Si3O10(OH)8,cr,VPT01,NA,2019-03-06,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-Mg-amesite,Mg-Ame,Mg4Al4Si2O10(OH)8,cr,VPT01,NA,2019-03-06,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-Fe-amesite,Fe-Ame,Fe4Al4Si2O10(OH)8,cr,VPV05,NA,2019-03-06,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-zoisite,Zo,Ca2Al3Si3O13H,cr,Got04,NA,2019-08-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-clinozoisite,Czo,Ca2Al3Si3O13H,cr,Got04,NA,2019-08-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-epidote,Ep,Ca2FeAl2Si3O12(OH),cr,Got04,NA,2019-08-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
-orthoepidote,oEp,Ca2FeAl2Si3O12(OH),cr,Got04,NA,2019-08-01,cal,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+akermanite,Ak,Ca2MgSi2O7,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+albite,Ab,NaAlSi3O8,cr,Ber88,SHD91,2017-10-03,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+"albite,high",hAb,NaAlSi3O8,cr,Ber88,SHD91,2017-10-03,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+"albite,low",lAb,NaAlSi3O8,cr,Ber88,SHD91,2017-10-03,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+almandine,Alm,Si3Fe3Al2O12,cr,Ber88,Ber90.1,2017-10-03,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+andalusite,And,Al2SiO5,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+anorthite,An,Al2CaSi2O8,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+anthophyllite,Ath,Mg7Si8O24H2,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+antigorite,Atg,Mg48Si34O99H62O48,cr,Ber88,BDat17.1,2017-10-09,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+brucite,Brc,MgO2H2,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+Ca-Al-pyroxene,CTs,CaAl2SiO6,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+calcite,Cal,CaCO3,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+chrysotile,Ctl,Mg3Si2O9H4,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+clinochlore,Chl,Mg5Al2Si3O18H8,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+coesite,Coe,SiO2,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+cordierite,Crd,Mg2Al4Si5O18,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+corundum,Crn,Al2O3,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+"cristobalite,alpha",aCrs,SiO2,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+"cristobalite,beta",bCrs,SiO2,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+diaspore,Dsp,AlO2H,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+diopside,Di,MgCaSi2O6,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+dolomite,Dol,MgCaC2O6,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+"enstatite,clino",Cen,MgSiO3,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+enstatite,En,MgSiO3,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+"enstatite,proto",pEn,MgSiO3,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+fayalite,Fa,Fe2SiO4,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+ferrosilite,Fs,SiFeO3,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+forsterite,Fo,Mg2SiO4,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+gehlenite,Gh,Al2Ca2SiO7,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+grossular,Grs,Ca3Al2Si3O12,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+hematite,Hem,Fe2O3,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+ilmenite,Ilm,FeTiO3,cr,Ber88,Ber90.1,2017-10-03,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+jadeite,Jd,NaAlSi2O6,cr,Ber88,SHD91,2017-10-03,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+kaolinite,Kln,Al2Si2O9H4,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+kyanite,Ky,Al2SiO5,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+lawsonite,Lws,CaAl2Si2O10H4,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+lime,Lm,CaO,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+magnesite,Mst,MgCO3,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+magnetite,Mgs,Fe3O4,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+margarite,Mrg,CaAl4Si2O12H2,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+meionite,Mei,Ca4Al6Si6O27C,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+merwinite,Mw,Ca3MgSi2O8,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+monticellite,Mtc,CaMgSiO4,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+muscovite,Ms,KAl3Si3O12H2,cr,Ber88,SHD91,2017-10-03,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+paragonite,Pg,NaAl3Si3O12H2,cr,Ber88,SHD91,2017-10-03,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+periclase,Per,MgO,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+phlogopite,Phl,KMg3AlSi3O12H2,cr,Ber88,SHD91.1,2017-10-03,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+K-feldspar,Kfs,KAlSi3O8,cr,Ber88,SHD91,2017-10-03,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+"K-feldspar,high",Sa,KAlSi3O8,cr,Ber88,SHD91,2017-10-03,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+"K-feldspar,low",Mc,KAlSi3O8,cr,Ber88,SHD91,2017-10-03,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+prehnite,Prh,Ca2Al2Si3O12H2,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+pyrope,Prp,Mg3Al2Si3O12,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+pyrophyllite,Prl,Al2Si4O12H2,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+quartz,Qz,SiO2,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+"quartz,beta",bQz,SiO2,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+rutile,Rt,TiO2,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+sillimanite,Sil,Al2SiO5,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+sphene,Spn,CaTiSiO5,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+spinel,Spl,MgAl2O4,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+talc,Tlc,Mg3Si4O12H2,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+tremolite,Tr,Ca2Mg5Si8O24H2,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+"tridymite,high",hTrd,SiO2,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+"tridymite,low",lTrd,SiO2,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+wollastonite,Wo,CaSiO3,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+pseudowollastonite,pWo,CaSiO3,cr,Ber88,NA,2017-10-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+annite,Ann,Si3Fe3AlKH2O12,cr,Ber90,SHD91.2,2017-10-03,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+fluormuscovite,Flms,KAl3Si3O10F2,cr,ZS92,NA,2017-10-03,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+fluorphlogopite,Fphl,KMg3AlSi3O10F2,cr,ZS92,NA,2017-10-03,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+fluorannite,Flann,Si3Fe3AlKO10F2,cr,ZS92,NA,2017-10-03,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+fluortremolite,Fltr,Ca2Mg5Si8O22F2,cr,ZS92,NA,2017-10-03,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+fluorapatite,Flap,Ca5P3O12F,cr,ZS92,NA,2017-10-03,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+hydroxyapatite,Hyap,Ca5P3O13H,cr,ZS92,NA,2017-10-03,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+chlorapatite,Clap,Ca5P3O12Cl,cr,ZS92,NA,2017-10-03,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+fluortalc,Fltlc,Mg3Si4O10F2,cr,ZS92,NA,2017-10-03,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+chlorphlogopite,Cphl,KMg3AlSi3O10Cl2,cr,ZS92,NA,2017-10-03,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+chlorannite,Clann,Si3Fe3AlKO10Cl2,cr,ZS92,NA,2017-10-03,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+glaucophane,Gln,Na2Al2Mg3Si8O24H2,cr,Eva90,JUN92,2017-10-03,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+pumpellyite,Pmp,Ca4Al5MgSi6O28H7,cr,Eva90,JUN92,2017-10-03,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+aragonite,Arg,CaCO3,cr,FDM+14.1,NA,2017-10-08,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+hedenbergite,Hd,CaFeSi2O6,cr,DS10,NA,2017-11-08,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+andradite,Adr,Ca3Fe2Si3O12,cr,DS10,NA,2017-11-08,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+ferro-actinolite,Fac,Ca2Fe5Si8O22(OH)2,cr,DS10,NA,2017-11-08,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+grunerite,Gru,Fe7Si8O22(OH)2,cr,DS10,NA,2017-11-08,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+ilvaite,Ilv,CaFe2FeSi2O7O(OH),cr,DS10,NA,2017-11-08,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+sudoite,Sud,Mg2Al4Si3O10(OH)8,cr,VGT92,NA,2019-03-06,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+daphnite,Dph,Fe5Al2Si3O10(OH)8,cr,VPT01,NA,2019-03-06,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+Mg-amesite,Mg-Ame,Mg4Al4Si2O10(OH)8,cr,VPT01,NA,2019-03-06,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+Fe-amesite,Fe-Ame,Fe4Al4Si2O10(OH)8,cr,VPV05,NA,2019-03-06,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+zoisite,Zo,Ca2Al3Si3O13H,cr,Got04,NA,2019-08-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+clinozoisite,Czo,Ca2Al3Si3O13H,cr,Got04,NA,2019-08-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+epidote,Ep,Ca2FeAl2Si3O12(OH),cr,Got04,NA,2019-08-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA
+orthoepidote,oEp,Ca2FeAl2Si3O12(OH),cr,Got04,NA,2019-08-01,J,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA,NA

Modified: pkg/CHNOSZ/inst/tinytest/test-berman.R
===================================================================
--- pkg/CHNOSZ/inst/tinytest/test-berman.R	2022-02-03 03:47:20 UTC (rev 689)
+++ pkg/CHNOSZ/inst/tinytest/test-berman.R	2022-02-03 09:47:52 UTC (rev 690)
@@ -1,68 +1,17 @@
 # test-berman.R 20171001
 
-# This is a long test ... only run it "at home" 20220129
-if(!at_home()) exit_file("Skipping long test")
-
 # Load default settings for CHNOSZ
 reset()
 
+# Make sure all Berman minerals are listed with units of J in OBIGT 20220203
+info <- "Berman minerals are listed with units of J in OBIGT"
+file <- system.file("extdata/OBIGT/Berman_cr.csv", package = "CHNOSZ")
+dat <- read.csv(file)
+expect_true(all(dat$E_units == "J"), info = info)
+
 # The maximum absolute pairwise difference between x and y
 maxdiff <- function(x, y) max(abs(y - x))
 
-# get parameters for all available minerals
-dat <- berman()
-mineral <- unique(dat$name)
-prop_Berman <- NULL
-
-info <- "Properties of all minerals are computed without warnings"
-# running this without error means that:
-# - formulas for the minerals are found in thermo()$OBIGT
-# - warning is produced for flourtremolite (GfPrTr(calc) >= 1000 J/cal different from GfPrTr(table))
-expect_warning(properties <- lapply(mineral, berman, check.G = TRUE),
-               "fluortremolite", info = info)
-# save the results so we can use them in the next tests
-assign("prop_Berman", properties, inherits = TRUE)
-
-# assemble a data frame for Berman properties
-prop_Berman <- do.call(rbind, prop_Berman)
-# find the mineral data using Helgeson formulation
-icr <- suppressMessages(info(mineral, "cr"))
-# all of these except rutile (Robie et al., 1979) reference Helgeson et al., 1978
-# NOTE: with check.it = TRUE (the default), this calculates Cp from the tabulated Maier-Kelley parameters
-add.OBIGT("SUPCRT92")
-prop_Helgeson <- suppressMessages(info(icr, check.it = FALSE))
-OBIGT()
-
-# now we can compare Berman and Helgeson G, H, S, Cp, V
-# minerals with missing properties are not matched here
-# (i.e. fluortremolite: no G and H in prop_Helgeson data)
-
-info <- "Berman and Helgeson tabulated properties have large differences for few minerals"
-# which minerals differ in DGf by more than 4 kcal/mol?
-idiffG <- which(abs(prop_Berman$G - prop_Helgeson$G) > 4000)
-DGf.list <- c("paragonite", "anthophyllite", "antigorite", "Ca-Al-pyroxene", "lawsonite", "margarite", "merwinite", "fluorphlogopite")
-expect_true(all(mineral[idiffG] %in% DGf.list), info = info)
-
-# which minerals differ in DHf by more than 4 kcal/mol?
-idiffH <- which(abs(prop_Berman$H - prop_Helgeson$H) > 4000)
-DHf.list <- c("paragonite", "anthophyllite", "antigorite", "Ca-Al-pyroxene", "lawsonite", "margarite", "merwinite", "clinozoisite", "fluorphlogopite")
-expect_true(all(mineral[idiffH] %in% DHf.list), info = info)
-
-# which minerals differ in S by more than 4 cal/K/mol?
-idiffS <- which(abs(prop_Berman$S - prop_Helgeson$S) > 4)
-DS.list <- c("epidote", "annite", "almandine", "fluortremolite", "andradite", "grunerite")
-expect_true(all(mineral[idiffS] %in% DS.list), info = info)
-
-# which minerals differ in Cp by more than 4 cal/K/mol?
-idiffCp <- which(abs(prop_Berman$Cp - prop_Helgeson$Cp) > 4)
-DCp.list <- c("glaucophane", "antigorite", "cristobalite,beta", "K-feldspar", "fluortremolite", "grunerite")
-expect_true(all(mineral[idiffCp] %in% DCp.list), info = info)
-
-# which minerals differ in V by more than 1 cm^3/mol?
-idiffV <- which(abs(prop_Berman$V - prop_Helgeson$V) > 1)
-DV.list <- c("glaucophane", "anthophyllite", "antigorite", "chrysotile", "merwinite", "grunerite")
-expect_true(all(mineral[idiffV] %in% DV.list), info = info)
-
 info <- "high-T,P calculated properties are similar to precalculated ones"
 # Reference values for G were taken from the spreadsheet Berman_Gibbs_Free_Energies.xlsx
 #   (http://www.dewcommunity.org/uploads/4/1/7/6/41765907/sunday_afternoon_sessions__1_.zip accessed on 2017-10-03)
@@ -100,12 +49,75 @@
 sresult <- suppressWarnings(subcrt("H2O", T = seq(0, 500, 100)))
 T <- sresult$out$water$T
 P <- sresult$out$water$P
-# this stopped with a error prior to version 1.1.3-37
+# This stopped with a error prior to version 1.1.3-37
 bresult <- berman("quartz", T = convert(T, "K"), P = P)
 expect_equal(sum(is.na(bresult$G)), 2, info = info)
-# this also now works (producing the same NA values)
+# This also now works (producing the same NA values)
 #subcrt("quartz", T = seq(0, 500, 100))
 
 "NAs don't creep into calculations below 298.15 K for minerals with disorder parameters"
 # 20191116
 expect_false(any(is.na(subcrt("K-feldspar", P = 1, T = seq(273.15, 303.15, 5), convert = FALSE)$out[[1]]$G)), info = info)
+
+
+
+# The next set of tests are long ... only run them "at home" 20220129
+if(!at_home()) exit_file("Skipping long test")
+
+# Get parameters for all available minerals
+dat <- berman()
+mineral <- unique(dat$name)
+
+info <- "Properties of all minerals are computed without errors"
+# Running this without error means that:
+# - formulas for the minerals are found in thermo()$OBIGT
+# - warning is produced for flourtremolite (GfPrTr(calc) >= 1000 J/mol different from GfPrTr(table))
+# - use units = "cal" for comparison with Helgeson minerals below
+expect_warning(properties <- lapply(mineral, berman, check.G = TRUE, units = "cal"),
+               "fluortremolite", info = info)
+# Save the results so we can use them in the next tests
+Berman <- do.call(rbind, properties)
+
+# Find the mineral data using Helgeson formulation
+icr <- suppressMessages(info(mineral, "cr"))
+add.OBIGT("SUPCRT92")
+# NOTE: with check.it = TRUE (the default), this calculates Cp from the tabulated Maier-Kelley parameters
+#Helgeson <- suppressMessages(info(icr, check.it = FALSE))
+Helgeson <- suppressMessages(info(icr))
+
+# Get the minerals that are present in *both* Berman and Helgeson versions
+# All of these except rutile (Robie et al., 1978) reference Helgeson et al., 1978
+iboth <- Helgeson$ref1 %in% c("HDNB78", "RHF78.4")
+mineral <- mineral[iboth]
+Berman <- Berman[iboth, ]
+Helgeson <- Helgeson[iboth, ]
+
+# Now we can compare Berman and Helgeson G, H, S, Cp, V
+# Minerals with missing properties are not matched here
+# (i.e. fluortremolite: no G and H in Helgeson data)
+
+info <- "Berman and Helgeson tabulated properties have large differences for few minerals"
+# Which minerals differ in DGf by more than 4 kcal/mol?
+idiffG <- which(abs(Berman$G - Helgeson$G) > 4000)
+DGf.list <- c("paragonite", "anthophyllite", "antigorite", "Ca-Al-pyroxene", "lawsonite", "margarite", "merwinite", "fluorphlogopite")
+expect_true(identical(sort(mineral[idiffG]), sort(DGf.list)), info = info)
+
+# Which minerals differ in DHf by more than 4 kcal/mol?
+idiffH <- which(abs(Berman$H - Helgeson$H) > 4000)
+DHf.list <- c("paragonite", "anthophyllite", "antigorite", "Ca-Al-pyroxene", "lawsonite", "margarite", "merwinite", "fluorphlogopite")
+expect_true(identical(sort(mineral[idiffH]), sort(DHf.list)), info = info)
+
+# Which minerals differ in S by more than 4 cal/K/mol?
+idiffS <- which(abs(Berman$S - Helgeson$S) > 4)
+DS.list <- c("epidote", "annite", "fluortremolite", "andradite")
+expect_true(identical(sort(mineral[idiffS]), sort(DS.list)), info = info)
+
+# Which minerals differ in Cp by more than 4 cal/K/mol?
+idiffCp <- which(abs(Berman$Cp - Helgeson$Cp) > 4)
+DCp.list <- c("glaucophane", "antigorite", "cristobalite,beta", "K-feldspar", "fluortremolite")
+expect_true(identical(sort(mineral[idiffCp]), sort(DCp.list)), info = info)
+
+# Which minerals differ in V by more than 1 cm^3/mol?
+idiffV <- which(abs(Berman$V - Helgeson$V) > 1)
+DV.list <- c("glaucophane", "anthophyllite", "antigorite", "chrysotile", "merwinite", "grunerite")
+expect_true(identical(sort(mineral[idiffV]), sort(DV.list)), info = info)

Modified: pkg/CHNOSZ/man/add.OBIGT.Rd
===================================================================
--- pkg/CHNOSZ/man/add.OBIGT.Rd	2022-02-03 03:47:20 UTC (rev 689)
+++ pkg/CHNOSZ/man/add.OBIGT.Rd	2022-02-03 09:47:52 UTC (rev 690)
@@ -58,24 +58,28 @@
 \seealso{ \code{\link{thermo}}, \code{\link{util.data}}, \code{\link{mod.buffer}} }
 
 \examples{\dontshow{reset()}
-## modify an existing species (example only)
-ialanine <- mod.OBIGT("alanine", state="cr", G=0, H=0, S=0)
-# we have made the values of G, H, and S inconsistent
+## Modify an existing species (not real properties)
+ialanine <- mod.OBIGT("alanine", state = "cr", G = 0, H = 0, S = 0)
+# We have made the values of G, H, and S inconsistent
 # with the elemental composition of alanine, so the following 
 # now produces a message about that
 info(ialanine)
-## add a species
-iCl2O <- mod.OBIGT("Cl2O", G=20970)
+
+## Add an aqueous species (default) with Gibbs energy given in J/mol and today's date
+date <- as.character(Sys.Date())
+iCl2O <- mod.OBIGT("Cl2O", date = date, E_units = "J", G = 87738)
 info(iCl2O)
-# add a species with a name that is different from the formula
-mod.OBIGT("buckminsterfullerene", formula="C60", state="cr", date=as.character(Sys.Date()))
-# retrieve the species data (thermodynamic properties in this toy example are NA)
-info(info("C60"))
+
+## Add a solid species with a name that is different from the formula
+mod.OBIGT("lorem-ipsum", formula = "C123", state = "cr", G = -12345678)
+# Retrieve the data for this species using either name or formula
+info(info("lorem-ipsum"))
+info(info("C123"))
 # reset database
 OBIGT()
 
-# using add.OBIGT():
-# compare stepwise stability constants of cadmium chloride complexes
+## Using add.OBIGT():
+# Compare stepwise stability constants of cadmium chloride complexes
 # using data from Sverjensky et al., 1997 and Bazarkina et al., 2010
 Cdspecies <- c("Cd+2", "CdCl+", "CdCl2", "CdCl3-", "CdCl4-2")
 P <- c(1, seq(25, 1000, 25))
@@ -89,18 +93,18 @@
   subcrt(c(Cdspecies[i], "Cl-", Cdspecies[i+1]),
     c(-1, -1, 1), T=25, P=P)$out$logK
 })
-# reset default database
-OBIGT()
 matplot(P, do.call(cbind, SSH97), type="l")
 matplot(P, do.call(cbind, BZA10), type="l", add=TRUE, lwd=2)
 legend("topleft", legend=c("", "", "Sverjensky et al., 1997",
[TRUNCATED]

To get the complete diff run:
    svnlook diff /svnroot/chnosz -r 690


More information about the CHNOSZ-commits mailing list