Author Topic: Mineral formula calculations  (Read 3221 times)

Ben Buse

  • Professor
  • ****
  • Posts: 498
Mineral formula calculations
« on: November 01, 2018, 08:25:21 AM »
Hi,

I have a question relating to the mineral formula calculations in PFE when water is present. If we take biotite but the same would apply to amphibole. For the mineral formula calculations are these:

(1) assuming anhydrous,
(2) Should water be specified as OH by dif on a 24 oxygen basis?

Thanks

Ben


Probeman

  • Emeritus
  • *****
  • Posts: 2856
  • Never sleeps...
    • John Donovan
Re: Mineral formula calculations (amphibole code)
« Reply #1 on: November 01, 2018, 09:49:18 AM »
Hi,

I have a question relating to the mineral formula calculations in PFE when water is present. If we take biotite but the same would apply to amphibole. For the mineral formula calculations are these:

(1) assuming anhydrous,
(2) Should water be specified as OH by dif on a 24 oxygen basis?

Thanks

Ben

Hi Ben,
I'm not a geologist so I don't know the answer.  Both the amphibole and biotite codes were written by Jay Ague when he was at UC Berkeley as a grad student (he's now a mineralogy professor at Yale). I would contact him, or maybe even better is ask Dave Adams at the USGS Denver. I know he and Heather Lowers use these mineral recalculation methods.

But in case it helps here is the amphibole re-calculation code:

Code: [Select]
Sub ConvertAmphibole(INORM As Integer, percents() As Single, sample() As TypeSample)
' Amphibole calculation (COMPUTES CALCIC AMPHIBOLE STRUCTURAL FORMULAS)
'  Originally written in FORTRAN by JAY AGUE, translated to Visual Basic by John Donovan
'  Calls ConvertAmphiboleNORM, ConvertAmphiboleAVER, ConvertAmphiboleSUM, ConvertAmphiboleGETFE and ConvertAmphiboleAUTOAV routines

ierror = False
On Error GoTo ConvertAmphiboleError

Const SSTRING1$ = "-----------------------------------------------------------"
Const SSTRING2$ = " ------ "

Dim j As Integer, ip As Integer
Dim IFE As Integer  ' 1 = Fe2O3 analyzed, 2 = Fe2O3 not analyzed
Dim IDEBUG As Integer, IBIG As Integer, NCODE As Integer

Dim PRESS2 As Single, PRESS23 As Single, ATOPT As Single
Dim MNX As Single, MGMFT As Single, MGB As Single, MGTOFE As Single, MGFET As Single
Dim WTPCT As Single, WTT As Single, RAMGFE  As Single
Dim TETAL As Single, OCTA As Single, OCTAL As Single, ANAM4 As Single, ANA12 As Single
Dim FE2X As Single, FE3X As Single, XALVI As Single, tix As Single, CAX As Single, ANAM4X As Single
Dim FERAT As Single, HALMO As Single, HALMF As Single, HALCL As Single, ASITE As Single
Dim WTPCF As Single, WTPCCL As Single, XFOXOH As Single, HALOG As Single
Dim FELOG  As Single, OC1 As Single, OC2 As Single

Dim d As Double

Dim astring As String, bstring As String

Dim WTPC(1 To MAXAMPHI%) As Single, ATOP(1 To MAXAMPHI%) As Single, PMOL(1 To MAXAMPHI%) As Single
Dim ANIO(1 To MAXAMPHI%) As Single, CAT1(1 To MAXAMPHI%) As Single, ANSFO(1 To MAXAMPHI%) As Single
Dim CAT2(1 To MAXAMPHI%) As Single, CAT3(1 To MAXAMPHI%) As Single, CATF(1 To MAXAMPHI%) As Single
Dim CAT4(1 To MAXAMPHI%) As Single, CAT5(1 To MAXAMPHI%) As Single

Dim esym(1 To MAXAMPHI%) As String
     
' Pre-load small values
For j% = 1 To MAXAMPHI%
    WTPC!(j%) = NOT_ANALYZED_VALUE_SINGLE!
Next j%

IDEBUG% = 0
IBIG% = 0
     
' Print calculation
Call IOWriteLog(vbCrLf & "Amphibole Formula Calculations (from Jay Ague AMPHI.F code)...")
     
' Assume Fe2O3 not analyzed
IFE% = 2        ' 1 = Fe2O3 analyzed, 2 = Fe2O3 not analyzed
WTPCT! = 0#
WTT! = 0#

' Load oxide percents
For j% = 1 To sample(1).LastChan%
    ip% = IPOS1%(MAXELM%, sample(1).Elsyms$(j%), Symlo$())
    If ip% <> 0 Then
        If ip% = 14 Then WTPC!(1) = percents!(j%)   ' SiO2
        If ip% = 22 Then WTPC!(2) = percents!(j%)   ' TiO2
        If ip% = 13 Then WTPC!(3) = percents!(j%)   ' Al2O3
        If ip% = 26 Then
            If IFE% = 1 Then
            WTPC!(4) = 0#              ' Fe2O3 (just zero out for now)
            WTPC!(5) = percents!(j%)   ' FeO
            Else
            WTPC!(4) = 0#              ' Fe2O3
            WTPC!(5) = percents!(j%)   ' FeO
            End If
        End If
        If ip% = 12 Then WTPC!(6) = percents!(j%)   ' MgO
        If ip% = 25 Then WTPC!(7) = percents!(j%)   ' MnO
        If ip% = 20 Then WTPC!(8) = percents!(j%)   ' CaO
        If ip% = 11 Then WTPC!(9) = percents!(j%)   ' Na2O
        If ip% = 19 Then WTPC!(10) = percents!(j%)  ' K2O
        If ip% = 9 Then WTPC!(11) = percents!(j%)  ' F
        If ip% = 17 Then WTPC!(12) = percents!(j%)   ' Cl
    End If
Next j%

' Sum total
WTT! = 0#
For j% = 1 To MAXAMPHI%
    WTT! = WTT! + WTPC!(j%)
Next j%

' Begin calculations
For j% = 1 To MAXAMPHI%
    PMOL!(1) = WTPC!(1) / 60.09: esym$(1) = "Si"
    PMOL!(2) = WTPC!(2) / 79.9: esym$(2) = "Ti"
    PMOL!(3) = WTPC!(3) / 101.94: esym$(3) = "Al"
    PMOL!(4) = WTPC!(4) / 159.7: esym$(4) = "Fe+3"
    PMOL!(5) = WTPC!(5) / 71.85: esym$(5) = "Fe+2"
    PMOL!(6) = WTPC!(6) / 40.32: esym$(6) = "Mg"
    PMOL!(7) = WTPC!(7) / 70.94: esym$(7) = "Mn"
    PMOL!(8) = WTPC!(8) / 56.08: esym$(8) = "Ca"
    PMOL!(9) = WTPC!(9) / 61.982: esym$(9) = "Na"
    PMOL!(10) = WTPC!(10) / 94.2: esym$(10) = "K"
    PMOL!(11) = WTPC!(11) / 19#: esym$(11) = "F"
    PMOL!(12) = WTPC!(12) / 35.457: esym$(12) = "Cl"
    If j% <= 2 Then GoTo 102
    If j% = 3 Or j% = 4 Then GoTo 103
    If j% > 4 Then GoTo 104

' 2 OXYGENS (equivalence)
102:
    ATOP!(j%) = PMOL!(j%) * 2#
    GoTo 105

' 3 OXYGENS
103:
    ATOP!(j%) = PMOL!(j%) * 3#
    GoTo 105

' 1 OXYGEN, F, CL
104:
    ATOP!(j%) = PMOL!(j%) * 1#

' Next element
105:
    WTPCT = WTPCT + WTPC!(j%)
Next j%
     
WTPCF = WTPC(11) * 0.4211
WTPCCL = WTPC(12) * 0.2256
WTPCT = WTPCT - WTPCF - WTPCCL
ATOPT = 0#
     
For j% = 1 To MAXAMPHI% - 2
    ATOPT = ATOPT + ATOP!(j%)
Next j%

' USE 46 NEGATIVE CHARGES
d# = 23# / ATOPT!
For j% = 1 To MAXAMPHI%
    ANIO!(j%) = d * ATOP!(j%)
Next j%

For j% = 1 To MAXAMPHI%
      If j% <= 2 Then ANSFO!(j%) = ANIO!(j%) / 2#
      If j% = 3 Or j% = 4 Then ANSFO!(j%) = ANIO!(j%) * 0.6666
      If j% > 4 And j% <= 8 Then ANSFO!(j%) = ANIO!(j%)
      If j% = 9 Or j% = 10 Then ANSFO!(j%) = ANIO!(j%) * 2#
      If j% > 10 Then ANSFO!(j%) = ANIO!(j%)
Next j%

' Call routine NORM to perform the structural formula calculations
If IFE% <> 1 Then
Call ConvertAmphiboleNorm(ANSFO!(), CAT1!(), CAT2!(), CAT3!(), CAT4!(), CAT5!())
If ierror Then Exit Sub
End If

' END NORMALIZATION PROCEDURE (FORMULA IS STORED IN ARRAY CAT1-5())
If DebugMode Then
Call IOWriteLog(vbCrLf & "Entered Amphibole Analysis:")
For j% = 1 To MAXAMPHI%
    If j% = 1 Then astring$ = Format$("SiO2", a80$)
    If j% = 2 Then astring$ = Format$("TiO2", a80$)
    If j% = 3 Then astring$ = Format$("Al2O3", a80$)
    If j% = 4 Then astring$ = Format$("Fe2O3", a80$)
    If j% = 5 Then astring$ = Format$("FeO", a80$)
    If j% = 6 Then astring$ = Format$("MgO", a80$)
    If j% = 7 Then astring$ = Format$("MnO", a80$)
    If j% = 8 Then astring$ = Format$("CaO", a80$)
    If j% = 9 Then astring$ = Format$("Na2O", a80$)
    If j% = 10 Then astring$ = Format$("K2O", a80$)
    If j% = 11 Then astring$ = Format$("F", a80$)
    If j% = 12 Then astring$ = Format$("Cl", a80$)
    If j% <> 4 Then bstring$ = Format$(Format$(WTPC!(j%), f83$), a80)
    If j% = 4 And IFE% = 1 Then bstring$ = Format$(Format$(WTPC!(j%), f83$), a80)
    If j% = 4 And IFE% = 2 Then bstring$ = Format$(Format$(" ---- "), a80)
Call IOWriteLog(bstring$ & a4x$ & astring$)
Next j%
     
Call IOWriteLog(SSTRING2$)
     
astring$ = Format$("TOTAL", a80$)
bstring$ = Format$(Format$(WTT!, f83$), a80)
Call IOWriteLog(bstring$ & a4x$ & astring$)
     
astring$ = Format$("TOTAL-OXYGEN EQUIV. OF F,CL")
bstring$ = Format$(Format$(WTPCT!, f83$), a80)
Call IOWriteLog(bstring$ & a4x$ & astring$)
Call IOWriteLog(SSTRING1$)
End If
     
' Do Fe2O3/FeO calculations (Fe2O3 analyzed)
If IFE% = 1 Then
    NCODE = 0
    For j% = 1 To MAXAMPHI%
        CATF!(j%) = ANSFO!(j%)
    Next j%
End If
     
' Do Fe2O3/FeO calculations (Fe2O3 not analyzed), print out candidate normalizations
If IFE% <> 1 Then
astring$ = a6x$ & Format$("ALL FE2", a80$) & Format$("NORM 1", a80$) & Format$("NORM 2", a80$) & Format$("NORM 3", a80$) & Format$("NORM 4", a80$) & Format$("NORM 5", a80$)
bstring$ = a6x$ & Format$(SSTRING2$, a80$) & Format$(SSTRING2$, a80$) & Format$(SSTRING2$, a80$) & Format$(SSTRING2$, a80$) & Format$(SSTRING2$, a80$) & Format$(SSTRING2$, a80$)
Call IOWriteLog(astring$)
Call IOWriteLog(bstring$)

For j% = 1 To MAXAMPHI%
    If j% = 1 Then astring$ = Format$("Si", a60$)
    If j% = 2 Then astring$ = Format$("Ti", a60$)
    If j% = 3 Then astring$ = Format$("Al", a60$)
    If j% = 4 Then astring$ = Format$("Fe3+", a60$)
    If j% = 5 Then astring$ = Format$("Fe2+", a60$)
    If j% = 6 Then astring$ = Format$("Mg", a60$)
    If j% = 7 Then astring$ = Format$("Mn", a60$)
    If j% = 8 Then astring$ = Format$("Ca", a60$)
    If j% = 9 Then astring$ = Format$("Na", a60$)
    If j% = 10 Then astring$ = Format$("K", a60$)
    If j% = 11 Then astring$ = Format$("F", a60$)
    If j% = 12 Then astring$ = Format$("Cl", a60$)
    bstring$ = Format$(Format$(ANSFO!(j%), f84$), a80$) & Format$(Format$(CAT1!(j%), f84$), a80$)
    bstring$ = bstring$ & Format$(Format$(CAT2!(j%), f84$), a80$) & Format$(Format$(CAT3!(j%), f84$), a80$)
    bstring$ = bstring$ & Format$(Format$(CAT4!(j%), f84$), a80$) & Format$(Format$(CAT5!(j%), f84$), a80$)
Call IOWriteLog$(astring$ & bstring$)
Next j%
     
Call IOWriteLog(vbNullString)
astring$ = a6x$ & "NORM 1: TOTAL-(NA+K)=15   " & "NORM 2: TOTAL-(NA+CA+K)=13"
Call IOWriteLog$(astring$)
astring$ = a6x$ & "NORM 3: TOTAL-K=15        " & "NORM 4: SI+AL=8.0"
Call IOWriteLog$(astring$)
astring$ = a6x$ & "NORM 5: TOTAL=15.8"
Call IOWriteLog$(astring$)
Call IOWriteLog$(SSTRING1$)

' Call averaging routine to determine final structure
Call ConvertAmphiboleAver(ANSFO!(), CAT1!(), CAT2!(), CAT3!(), CAT4!(), CAT5!(), CATF!(), INORM%)
If ierror Then Exit Sub
End If

' Round values in structural formula (array CATF) to 4 decimal places. If Mg = 0, set to 0.0001 to prevent errors.
For j% = 1 To MAXAMPHI%
    CATF!(j%) = MiscSetRounding2!(CATF!(j%), Int(4))
Next j%
If CATF!(6) = 0# Then CATF!(6) = 0.0001

' Compute mole fractions, molar ratios and pressure of crystallization using
'  Mutch et al. (2016) calibration of the Hammarstrom and Zen (1986) barometer

' TETRAHEDRAL AL
      If CATF!(1) < 8 Then
        TETAL = 8# - CATF!(1)
      Else
        TETAL = 0#
      End If

' OCTAHEDRAL AL
      OCTAL = CATF(3) - TETAL
      If (OCTAL < 0#) Then TETAL = CATF(3)
      If (OCTAL < 0#) Then OCTAL = 0#

' NA ON M4 SITE
      ANAM4 = 7# - (CATF(8) + CATF(4) + CATF(5) + CATF(6) + CATF(7) + OCTAL + CATF(2))
      If (ANAM4 < 0#) Then Call IOWriteLog(a6x$ & "***OCTAHEDRAL NA IS NEGATIVE***")

' 12-FOLD NA
      If (ANAM4 < 0#) Then ANA12 = CATF(9)
      If (ANAM4 >= 0#) Then ANA12 = CATF(9) - 1# * ANAM4
      If ((ANAM4 >= 0#) And (ANAM4 > CATF(9))) Then ANA12 = 0#
      If (ANAM4 < 0#) Then Call IOWriteLog(a6x$ & "***ALL NA ASSIGNED TO 12-FOLD SITE***")
      If (ANAM4 < 0#) Then ANAM4 = 0#
      If (ANAM4 > CATF(9)) Then ANAM4 = CATF(9)

' TOTAL OCTAHEDRAL ATOMS
      OCTA = ANAM4 + OCTAL + CATF(8) + CATF(4) + CATF(5) + CATF(6) + CATF(2) + CATF(7)

' X - ALVI
      XALVI = OCTAL / OCTA

' X-FE2+
      FE2X = CATF(5) / OCTA

' X-FE3+
      FE3X = CATF(4) / OCTA

' X - MG
      MGMFT = CATF(6) / OCTA

' X - TI
      tix = CATF(2) / OCTA

' X - MN
      MNX = CATF(7) / OCTA

' X - CA
      CAX = CATF(8) / OCTA

'X - NAM4
      ANAM4X = ANAM4 / OCTA

' A-SITE OCCUPANCY
      ASITE = ANA12 + CATF(10)

' X - F
      HALMF = CATF(11) / 2#
      If (HALMF = 0#) Then HALMF = 0.00001

' X - CL
      HALCL = CATF(12) / 2#
      If (HALCL = 0#) Then HALCL = 0.00001

' X - OH
      HALMO = 1# - HALMF - HALCL
      If (HALMO <= 0#) Then HALMO = 0.00001

' COMPUTE LOG X-F/X-OH
      If HALMF / HALMO > 0# Then XFOXOH = MiscConvertLog10#(CDbl(HALMF / HALMO))

' COMPUTE LOG X-F/X-CL
      If HALMF / HALCL > 0# Then HALOG = MiscConvertLog10#(CDbl(HALMF / HALCL))

' COMPUTE LOG MG/FE2+
      If MGMFT / FE2X > 0# Then RAMGFE = MiscConvertLog10#(CDbl(MGMFT / FE2X))

' COMPUTE LOG (MG/(FE2+ + FE3+))
      If MGMFT / (FE2X + FE3X) > 0# Then MGFET = MiscConvertLog10#(CDbl(MGMFT / (FE2X + FE3X)))

' COMPUTE LOG FE2+/FE3+
      If (FE3X = 0#) Then FE3X = 0.0001
      If FE2X / FE3X > 0# Then FELOG = MiscConvertLog10#(CDbl(FE2X / FE3X))

' COMPUTE MG/(MG+FE2+)
      MGB = CATF(6) / (CATF(6) + CATF(5))

' COMPUTE ALVI+FE3+ + 2TI+ASITE
      OC1 = OCTAL + CATF(4) + 2# * CATF(2) + ASITE

' COMPUTE ALVI+FE3+ +2TI
      OC2 = OCTAL + CATF(4) + 2# * CATF(2)

' COMPUTE FE2+/(FE2+ + FE3+)
      FERAT = CATF(5) / (CATF(5) + CATF(4))

' COMPUTE MG/(MG+FE TOTAL)
      MGTOFE = CATF(6) / (CATF(6) + CATF(4) + CATF(5))

' Compute pressure, both with total Al (all Fe2+) and total Al (Fe2+ - Fe3+)
PRESS2! = 0.5 + 0.331 * ANSFO!(3) + 0.995 * ANSFO!(3) ^ 2       ' changed to Mutch et al. (2016)
PRESS23! = 0.5 + 0.331 * CATF!(3) + 0.995 * CATF!(3) ^ 2        ' changed to Mutch et al. (2016)
If PRESS2! < 0# Or IFE = 1 Then PRESS2! = 0#
If PRESS23! < 0# Then PRESS23! = 0#

Call IOWriteLog(a6x$ & "STRUCTURAL FORMULA:")
Call IOWriteLog(a8x$ & "SI   " & Format$(Format$(CATF(1), f84$), a80$))
Call IOWriteLog(a8x$ & "TI   " & Format$(Format$(CATF(2), f84$), a80$))
Call IOWriteLog(a8x$ & "AL IV" & Format$(Format$(TETAL!, f84$), a80$) & a8x$ & "AL VI" & Format$(Format$(OCTAL!, f84$), a80$))
Call IOWriteLog(a8x$ & "FE3+ " & Format$(Format$(CATF(4), f84$), a80$))
Call IOWriteLog(a8x$ & "FE2+ " & Format$(Format$(CATF(5), f84$), a80$))
Call IOWriteLog(a8x$ & "MG   " & Format$(Format$(CATF(6), f84$), a80$))
Call IOWriteLog(a8x$ & "MN   " & Format$(Format$(CATF(7), f84$), a80$))
Call IOWriteLog(a8x$ & "CA   " & Format$(Format$(CATF(8), f84$), a80$))
Call IOWriteLog(a8x$ & "NA A " & Format$(Format$(ANAM4!, f84$), a80$) & a8x$ & "NA B " & Format$(Format$(ANA12!, f84$), a80$))
Call IOWriteLog(a8x$ & "K    " & Format$(Format$(CATF(10), f84$), a80$))
Call IOWriteLog(a8x$ & "F    " & Format$(Format$(CATF(11), f84$), a80$))
Call IOWriteLog(a8x$ & "CL   " & Format$(Format$(CATF(12), f84$), a80$))
Call IOWriteLog(a8x$ & "OH   " & Format$(Format$(2# - (CATF(11) + CATF(12)), f84$), a80$))

Call IOWriteLog(SSTRING1$)
Call IOWriteLog("MOLE FRACTIONS AND LOGARITHMS OF ATOMIC RATIOS:")

Call IOWriteLog(a6x$ & "X-FE2+= " & Format$(Format$(FE2X!, f83$), a80$) & a6x$ & "X-MG=   " & Format$(Format$(MGMFT!, f83$), a80$))
Call IOWriteLog(a6x$ & "X-FE3+= " & Format$(Format$(FE3X!, f83$), a80$) & a6x$ & "X-ALVI= " & Format$(Format$(XALVI, f83$), a80$))
Call IOWriteLog(a6x$ & "X-MN=   " & Format$(Format$(MNX!, f84$), a80$) & a6x$ & "X-TI=   " & Format$(Format$(tix!, f84$), a80$))
Call IOWriteLog(a6x$ & "X-CA=   " & Format$(Format$(CAX!, f83$), a80$) & a6x$ & "X-NAM4= " & Format$(Format$(ANAM4X!, f84$), a80$) & vbCrLf)

Call IOWriteLog(a6x$ & "MG / (MG + FE2+) =  " & Format$(Format$(MGB!, f83$), a80$))
Call IOWriteLog(a6x$ & "FE2+/(FE2+ + FE3+)= " & Format$(Format$(FERAT!, f83$), a80$))
Call IOWriteLog(a6x$ & "MG/(MG+FE2+ + FE3+)=" & Format$(Format$(MGTOFE!, f83$), a80$) & vbCrLf)

Call IOWriteLog(a6x$ & "X-OH=                     " & Format$(Format$(HALMO!, f83$), a80$) & a4x$ & "X-F=               " & Format$(Format$(HALMF!, f83$), a80$) & a4x & "X-CL=         " & Format$(Format$(HALCL!, f83$), a80$))
Call IOWriteLog(a6x$ & "LOG(X-MG/X-FE2+)=         " & Format$(Format$(RAMGFE!, f83$), a80$) & a4x$ & "LOG(X-F/X-CL)=     " & Format$(Format$(HALOG!, f83$), a80$) & a4x$ & "LOG(X-F/X-OH)=" & Format$(Format$(XFOXOH!, f83$), a80$))
Call IOWriteLog(a6x$ & "LOG(X-MG/(X-FE2+ + FE3+))=" & Format$(Format$(MGFET!, f83$), a80$) & a4x$ & "LOG(X-FE2+/X-FE3+)=" & Format$(Format$(FELOG!, f83$), a80$) & vbCrLf)
Call IOWriteLog(a6x$ & "A-SITE=                   " & Format$(Format$(ASITE!, f83$), a80$) & a4x$ & "TOTAL VI=          " & Format$(Format$(OCTA!, f83$), a80$))
Call IOWriteLog(a6x$ & "ALVI+2TI+A-SITE+FE3+=     " & Format$(Format$(OC1!, f83$), a80$) & a4x$ & "ALVI+2TI+FE3+=     " & Format$(Format$(OC2!, f83$), a80$))
     
Call IOWriteLog(vbNullString)
Call IOWriteLog(a6x$ & "Mutch et al. (2016) Pressure (All FE2+): " & Format$(Format$(PRESS2!, f42$), a80$) & " KBar, " & a4x$ & "(FE2+ -FE3+): " & Format$(Format$(PRESS23!, f42$), a80$) & " KBar")
     
' Output to file (AMPHI.OUT)
astring$ = vbCrLf & "Sample " & VbDquote$ & sample(1).number% & VbDquote$ & vbTab & VbDquote$ & sample(1).Name$ & VbDquote$
Print #tfilenumber%, astring$

astring$ = vbNullString
For j% = 1 To MAXAMPHI%
    If j% = 3 Then
    astring$ = astring$ + MiscAutoFormat$(WTPC!(j%)) & vbTab$ & MiscAutoFormat$(ANSFO!(j%)) & vbTab$ & MiscAutoFormat$(CATF!(j%)) & vbTab$ & MiscAutoFormat$(TETAL!) & vbTab$ & MiscAutoFormat$(OCTAL!) & vbTab & esym$(j%) & vbTab$ & MiscAutoFormat$(PRESS2!) & vbTab$ & MiscAutoFormat$(PRESS23!) & vbCrLf
    ElseIf j = 9 Then
    astring$ = astring$ + MiscAutoFormat$(WTPC!(j%)) & vbTab$ & MiscAutoFormat$(ANSFO!(j%)) & vbTab$ & MiscAutoFormat$(CATF!(j%)) & vbTab$ & MiscAutoFormat$(ANAM4!) & vbTab$ & MiscAutoFormat$(ANA12!) & vbTab & esym$(j%) & vbCrLf
    ElseIf j = 12 Then
    astring$ = astring$ + MiscAutoFormat$(WTPC!(j%)) & vbTab$ & MiscAutoFormat$(ANSFO!(j%)) & vbTab$ & MiscAutoFormat$(CATF!(j%)) & vbTab$ & MiscAutoFormat$(2# - (CATF!(11) + CATF!(12))) & vbTab & esym$(j%) & vbCrLf
    Else
    astring$ = astring$ + MiscAutoFormat$(WTPC!(j%)) & vbTab$ & MiscAutoFormat$(ANSFO!(j%)) & vbTab$ & MiscAutoFormat$(CATF!(j%)) & vbTab & esym$(j%) & vbCrLf
    End If
Next j%
Print #tfilenumber%, astring$
   
astring$ = vbNullString
astring$ = astring$ & MiscAutoFormat$(HALOG!) & vbTab$ & MiscAutoFormat$(RAMGFE!) & vbTab$ & MiscAutoFormat$(MGB!) & vbTab$
astring$ = astring$ & MiscAutoFormat$(FE2X!) & vbTab$ & MiscAutoFormat$(tix!) & vbTab$ & MiscAutoFormat$(XALVI!) & vbTab$
astring$ = astring$ & MiscAutoFormat$(MNX!) & vbTab$ & MiscAutoFormat$(XFOXOH!) & vbTab$ & MiscAutoFormat$(OC1!) & vbTab$
astring$ = astring$ & MiscAutoFormat$(OC2!) & vbTab$ & MiscAutoFormat$(CATF(3)) & vbTab$ & MiscAutoFormat$(ASITE!) & vbTab$
astring$ = astring$ & MiscAutoFormat$(FERAT!) & vbTab$ & MiscAutoFormat$(CATF(1)) & vbCrLf
astring$ = astring$ & MiscAutoFormat$(ANAM4!) & vbTab$ & MiscAutoFormat$(ANA12!) & vbTab$ & MiscAutoFormat$(OCTA!) & vbTab$
astring$ = astring$ & MiscAutoFormat$(CATF!(8)) & vbTab & MiscAutoFormatI$(NCODE%)
Print #tfilenumber%, astring$

' Output to file (AMPHI.DAT)
astring$ = vbCrLf & "Sample " & vbTab & VbDquote$ & sample(1).number% & VbDquote$ & vbTab & VbDquote$ & sample(1).Name$ & VbDquote$
Print #tfilenumber2%, astring$

' Output oxide labels
astring$ = vbNullString
For j% = 1 To MAXAMPHI%
    If j% = 1 Then astring$ = astring$ & "SiO2" & vbTab
    If j% = 2 Then astring$ = astring$ & "TiO2" & vbTab
    If j% = 3 Then
        astring$ = astring$ & "Al2O3" & vbTab
        astring$ = astring$ & "-----" & vbTab
    End If
    If j% = 4 Then astring$ = astring$ & "Fe2O3" & vbTab
    If j% = 5 Then astring$ = astring$ & "FeO" & vbTab
    If j% = 6 Then astring$ = astring$ & "MgO" & vbTab
    If j% = 7 Then astring$ = astring$ & "MnO" & vbTab
    If j% = 8 Then astring$ = astring$ & "CaO" & vbTab
    If j% = 9 Then
        astring$ = astring$ & "Na2O" & vbTab
        astring$ = astring$ & "----" & vbTab
    End If
    If j% = 10 Then astring$ = astring$ & "K2O" & vbTab
    If j% = 11 Then astring$ = astring$ & "F" & vbTab
    If j% = 12 Then astring$ = astring$ & "Cl" & vbTab
Next j%
astring$ = astring$ & "OH" & vbTab
Print #tfilenumber2%, astring$

' Output oxide wt%
astring$ = vbNullString
For j% = 1 To MAXAMPHI%
    If j% = 1 Then astring$ = astring$ & Format$(WTPC!(j%)) & vbTab
    If j% = 2 Then astring$ = astring$ & Format$(WTPC!(j%)) & vbTab
    If j% = 3 Then
        astring$ = astring$ & Format$(WTPC!(j%)) & vbTab
        astring$ = astring$ & Format$(0#) & vbTab
    End If
    If j% = 4 Then astring$ = astring$ & Format$(WTPC!(j%)) & vbTab
    If j% = 5 Then astring$ = astring$ & Format$(WTPC!(j%)) & vbTab
    If j% = 6 Then astring$ = astring$ & Format$(WTPC!(j%)) & vbTab
    If j% = 7 Then astring$ = astring$ & Format$(WTPC!(j%)) & vbTab
    If j% = 8 Then astring$ = astring$ & Format$(WTPC!(j%)) & vbTab
    If j% = 9 Then
        astring$ = astring$ & Format$(WTPC!(j%)) & vbTab
        astring$ = astring$ & Format$(0#) & vbTab
    End If
    If j% = 10 Then astring$ = astring$ & Format$(WTPC!(j%)) & vbTab
    If j% = 11 Then astring$ = astring$ & Format$(WTPC!(j%)) & vbTab
    If j% = 12 Then astring$ = astring$ & Format$(WTPC!(j%)) & vbTab
Next j%
astring$ = astring$ & Format$(2# - (CATF(11) + CATF(12))) & vbTab
Print #tfilenumber2%, astring$

' Output structural formula labels
astring$ = vbNullString
For j% = 1 To MAXAMPHI%
    If j% = 1 Then astring$ = astring$ & VbDquote$ & "SI" & VbDquote$ & vbTab
    If j% = 2 Then astring$ = astring$ & VbDquote$ & "TI" & VbDquote$ & vbTab
    If j% = 3 Then
        astring$ = astring$ & "AL IV" & vbTab
        astring$ = astring$ & "AL VI" & vbTab
    End If
    If j% = 4 Then astring$ = astring$ & VbDquote$ & "FE 3+" & VbDquote$ & vbTab
    If j% = 5 Then astring$ = astring$ & VbDquote$ & "FE 2+" & VbDquote$ & vbTab
    If j% = 6 Then astring$ = astring$ & VbDquote$ & "MG" & VbDquote$ & vbTab
    If j% = 7 Then astring$ = astring$ & VbDquote$ & "Mn" & VbDquote$ & vbTab
    If j% = 8 Then astring$ = astring$ & VbDquote$ & "CA" & VbDquote$ & vbTab
    If j% = 9 Then
        astring$ = astring$ & VbDquote$ & "NA A" & VbDquote$ & vbTab
        astring$ = astring$ & VbDquote$ & "NA B" & VbDquote$ & vbTab
    End If
    If j% = 10 Then astring$ = astring$ & VbDquote$ & "K" & VbDquote$ & vbTab
    If j% = 11 Then astring$ = astring$ & VbDquote$ & "F" & VbDquote$ & vbTab
    If j% = 12 Then astring$ = astring$ & VbDquote$ & "CL" & VbDquote$ & vbTab
Next j%
astring$ = astring$ & VbDquote$ & "OH" & VbDquote$ & vbTab
Print #tfilenumber2%, astring$
   
' Output structural formulas
astring$ = vbNullString
For j% = 1 To MAXAMPHI%
    If j% = 1 Then astring$ = astring$ & Format$(CATF(1)) & vbTab
    If j% = 2 Then astring$ = astring$ & Format$(CATF(2)) & vbTab
    If j% = 3 Then
        astring$ = astring$ & Format$(TETAL!) & vbTab
        astring$ = astring$ & Format$(OCTAL!) & vbTab
    End If
    If j% = 4 Then astring$ = astring$ & Format$(CATF(4)) & vbTab
    If j% = 5 Then astring$ = astring$ & Format$(CATF(5)) & vbTab
    If j% = 6 Then astring$ = astring$ & Format$(CATF(6)) & vbTab
    If j% = 7 Then astring$ = astring$ & Format$(CATF(7)) & vbTab
    If j% = 8 Then astring$ = astring$ & Format$(CATF(8)) & vbTab
    If j% = 9 Then
        astring$ = astring$ & Format$(ANAM4!) & vbTab
        astring$ = astring$ & Format$(ANA12!) & vbTab
    End If
    If j% = 10 Then astring$ = astring$ & Format$(CATF(10)) & vbTab
    If j% = 11 Then astring$ = astring$ & Format$(CATF(11)) & vbTab
    If j% = 12 Then astring$ = astring$ & Format$(CATF(12)) & vbTab
Next j%
astring$ = astring$ & Format$(2# - (CATF(11) + CATF(12))) & vbTab
Print #tfilenumber2%, astring$
   
Exit Sub

' Errors
ConvertAmphiboleError:
MsgBox Error$, vbOKOnly + vbCritical, "ConvertAmphibole"
Close #tfilenumber%
Close #tfilenumber2%
ierror = True
Exit Sub

End Sub

I'll put the biotite code in the next post.
« Last Edit: November 01, 2018, 09:51:14 AM by Probeman »
The only stupid question is the one not asked!

Probeman

  • Emeritus
  • *****
  • Posts: 2856
  • Never sleeps...
    • John Donovan
Re: Mineral formula calculations (biotite code)
« Reply #2 on: November 01, 2018, 09:51:23 AM »
And here is the biotite re-calculation code:

Code: [Select]
Sub ConvertHalog(tfilenumber As Integer, percents() As Single, sample() As TypeSample)
' v. 1.0; WRITTEN BY G. BRIMHALL
'
' v. 1.1; MODIFIED BY JAY AGUE (8-1-84) TO COMPUTE BIOTITE
' COMPONENT ACTIVITIES.  RECALCULATION PROCEDURE ALSO MODIFIED.
'
' v. 1.2; Further modifications to calculation procedure and
' output formats by Jay J. Ague 4/89. One of the more
' important changes has been the incorporation of code
' which rounds the values in the structural formula to
' 4 decimal places before any computations of mole fractions
' etc. takes place. This is to insure consistency between
' the printed (rounded) structural formula and computed
' quantities.
'
' v.1.3, 19 May 98; Jay J. Ague. Updated with atomic and
'   molecular weights from DHZ `92. Output format also modified.
'
' COMPUTES BIOTITE FORMULAS AND SITE OCCUPANCIES AND MOLE FRACTION RATIOS FOR USE IN HALOGEN
' CHEMISTRY AND CHARACTERIZATION OF MINERALIZATION ENVIRONMENTS

ierror = False
On Error GoTo ConvertHalogError

Const MAXBIOT% = 12
Const SSTRING1$ = "-----------------------------------------------------------"
Const SSTRING2$ = " ------ "

Dim IDEBUG As Integer, IBIG As Integer
Dim i As Integer, ip As Integer
     
Dim MNX As Single, MGMFT As Single, MGB As Single, YM32X As Single
Dim SIDER As Single, ANNIT As Single, PHLOG As Single, WTPCT As Single, WTT  As Single
Dim sum1 As Single, sum2 As Single, sum3 As Single, sum4 As Single
Dim WTPCF As Single, WTPCCL As Single, ATOPT As Single, TETAL As Single, OCTAL As Single
Dim XALVI As Single, ALKM As Single, FEX As Single, tix As Single
Dim HALMF As Single, HALMC As Single, HALMO As Single, XFOXOH As Single, HALOG1 As Single, SI As Single
Dim AFEF As Single, AMGF As Single, AFEOH As Single, AMGOH As Single, RAMGFE As Single
Dim XMG As Single, XSID As Single, XAN As Single

Dim d As Double

Dim astring As String, bstring As String

Dim WTPC(1 To MAXBIOT%) As Single, ATOP(1 To MAXBIOT%) As Single, ANSFO(1 To MAXBIOT%) As Single
Dim PMOL(1 To MAXBIOT%) As Single, ANIO(1 To MAXBIOT%) As Single

Dim esym(1 To MAXBIOT%) As String

' Print calculation
Call IOWriteLog(vbCrLf & "Biotite Formula Calculations (from Brimhall and Ague, v. 1.3, HALOG.F code)...")
     
' Load oxide percents
For i% = 1 To sample(1).LastChan%
    ip% = IPOS1%(MAXELM%, sample(1).Elsyms$(i%), Symlo$())
    If ip% <> 0 Then
        If ip% = 14 Then WTPC!(1) = percents!(i%)  ' SiO2
        If ip% = 22 Then WTPC!(2) = percents!(i%)  ' TiO2
        If ip% = 13 Then WTPC!(3) = percents!(i%)  ' Al2O3
        If ip% = 26 Then WTPC!(4) = percents!(i%)  ' FeO
        If ip% = 12 Then WTPC!(5) = percents!(i%)  ' MgO
        If ip% = 20 Then WTPC!(6) = percents!(i%)  ' CaO
        If ip% = 11 Then WTPC!(7) = percents!(i%)  ' Na2O
        If ip% = 56 Then WTPC!(8) = percents!(i%)  ' BaO
        If ip% = 19 Then WTPC!(9) = percents!(i%)  ' K2O
        If ip% = 9 Then WTPC!(10) = percents!(i%)  ' F
        If ip% = 17 Then WTPC!(11) = percents!(i%) ' Cl
        If ip% = 25 Then WTPC!(12) = percents!(i%) ' MnO
    End If
Next i%
       
IDEBUG = 0
IBIG = 0
WTPCT = 0#
WTT = 0#

For i% = 1 To MAXBIOT%
WTT = WTT + WTPC(i%)
Next i%
       
If DebugMode Then
Call IOWriteLog(vbCrLf & "Entered Biotite Analysis:")
For i% = 1 To MAXBIOT%
    If i% = 1 Then astring$ = Format$("SiO2", a80$)
    If i% = 2 Then astring$ = Format$("TiO2", a80$)
    If i% = 3 Then astring$ = Format$("Al2O3", a80$)
    If i% = 4 Then astring$ = Format$("FeO", a80$)
    If i% = 5 Then astring$ = Format$("MgO", a80$)
    If i% = 6 Then astring$ = Format$("MnO", a80$)
    If i% = 7 Then astring$ = Format$("CaO", a80$)
    If i% = 8 Then astring$ = Format$("Na2O", a80$)
    If i% = 9 Then astring$ = Format$("BaO", a80$)
    If i% = 10 Then astring$ = Format$("K2O", a80$)
    If i% = 11 Then astring$ = Format$("F", a80$)
    If i% = 12 Then astring$ = Format$("Cl", a80$)
    bstring$ = Format$(Format$(WTPC!(i%), f83$), a80)
Call IOWriteLog(bstring$ & a4x$ & astring$)
Next i%
Call IOWriteLog(SSTRING2$)
     
astring$ = Format$("TOTAL", a80$)
bstring$ = Format$(Format$(WTT!, f83$), a80)
Call IOWriteLog(bstring$ & a4x$ & astring$)
Call IOWriteLog(SSTRING1$)
End If

' Updated using DHZ '92
For i% = 1 To MAXBIOT%
      PMOL(1) = WTPC(1) / 60.08: esym$(1) = "Si"
      PMOL(2) = WTPC(2) / 79.88: esym$(2) = "Ti"
      PMOL(3) = WTPC(3) / 101.96: esym$(3) = "Al"
      PMOL(4) = WTPC(4) / 71.85: esym$(4) = "Fe+2"
      PMOL(5) = WTPC(5) / 40.3: esym$(5) = "Mg"
      PMOL(6) = WTPC(6) / 56.08: esym$(6) = "Ca"
      PMOL(7) = WTPC(7) / 61.98: esym$(7) = "Na"
      PMOL(8) = WTPC(8) / 153.33: esym$(8) = "Ba"
      PMOL(9) = WTPC(9) / 94.2: esym$(9) = "K"
      PMOL(10) = WTPC(10) / 19#: esym$(10) = "F"
      PMOL(11) = WTPC(11) / 35.45: esym$(11) = "Cl"
      PMOL(12) = WTPC(12) / 70.94: esym$(12) = "Mn"
      If i% <= 2 Then GoTo 102
      If i% = 3 Then GoTo 103
      If i% > 3 Then GoTo 104

' 2 OXYGENS
102:  ATOP(i%) = PMOL(i%) * 2#
      GoTo 105

' 3 OXYGENS
103:  ATOP(i%) = PMOL(i%) * 3#
      GoTo 105

' 1 OXYGENS
104:  ATOP(i%) = PMOL(i%) * 1#

' Total wt percents
105:  WTPCT = WTPCT + WTPC(i%)
Next i%
     
      WTPCF = WTPC(10) * 0.4211
      WTPCCL = WTPC(11) * 0.2256
      WTPCT = WTPCT - 1# * WTPCF - 1# * WTPCCL
      ATOPT = 0#
For i% = 1 To MAXBIOT%
      ATOPT = ATOPT + ATOP(i%)
Next i%
      ATOPT = ATOPT - 1# * ATOP(10) - 1# * ATOP(11)

' SPECIFY NUMBER OF OXYGENS, USE A TOTAL OF 22 NEGATIVE CHARGES
      d# = 11# / ATOPT

For i% = 1 To MAXBIOT%
      ANIO(i%) = d# * ATOP(i%)
Next i%
     
For i% = 1 To MAXBIOT%
      If i% <= 2 Then ANSFO(i%) = ANIO(i%) / 2#
      If i% = 3 Then ANSFO(i%) = ANIO(i%) * (2# / 3#)
      If i% > 3 And i% <= 6 Then ANSFO(i%) = ANIO(i%)
      If i% = 7 Or i% = 9 Then ANSFO(i%) = ANIO(i%) * 2#
      If i% = 8 Then ANSFO(i%) = ANIO(i%)
      If i% > 9 Then ANSFO(i%) = ANIO(i%)
Next i%

' Round values in the structural formula (array ANSFO) to four decimal places
For i% = 1 To MAXBIOT%
    ANSFO!(i%) = MiscSetRounding2!(ANSFO!(i%), Int(4))
Next i%

' TETRAHEDRAL AL
      TETAL = 4# - ANSFO(1)

' OCTAHEDRAL AL
      OCTAL = ANSFO(3) - TETAL
      If OCTAL < 0# Then TETAL = ANSFO(3)
      If OCTAL < 0# Then OCTAL = 0#
      XALVI = OCTAL / (ANSFO(5) + ANSFO(2) + OCTAL + ANSFO(4) + ANSFO(12))

' K20 + NA20 + BA0 + CA0
      ALKM = ANSFO(9) + ANSFO(7) + ANSFO(8) + ANSFO(6)

' X MG (FULL OCTAHEDRAL)
      MGMFT = ANSFO(5) / (ANSFO(5) + ANSFO(2) + OCTAL + ANSFO(4) + ANSFO(12))

' Mg / (Mg + FE)
      MGB = ANSFO(5) / (ANSFO(5) + ANSFO(4))

' X FE++ (FULL OCTAHEDRAL ANNITE)
      FEX = ANSFO(4) / (ANSFO(5) + ANSFO(2) + OCTAL + ANSFO(4) + ANSFO(12))

'  X TI-BIOTITE (FULL OCTAHEDRAL)
      tix = ANSFO(2) / (ANSFO(5) + ANSFO(2) + OCTAL + ANSFO(4) + ANSFO(12))

' X MN- BIOTITE (FULL OCTAHEDRAL)
      MNX = ANSFO(12) / (ANSFO(5) + ANSFO(2) + OCTAL + ANSFO(4) + ANSFO(12))

' X   F
      HALMF = ANSFO(10) / 2#

' X  CL
      HALMC = ANSFO(11) / 2#

' COMPUTE X-OH
      HALMO = 1# - HALMF - HALMC
      If HALMF = 0# Then HALMF = 0.00001
      If HALMC = 0# Then HALMC = 0.00001
      If HALMO <= 0# Then HALMO = 0.00001

' COMPUTE LOG X-F/X-OH
      If HALMF / HALMO > 0# Then XFOXOH = MiscConvertLog10#(CDbl(HALMF / HALMO))
      If HALMF / HALMC > 0# Then HALOG1 = MiscConvertLog10#(CDbl(HALMF / HALMC))

      sum1 = ANSFO(9) + ANSFO(7) + ANSFO(6) + ANSFO(8)
      sum2 = ANSFO(2) + OCTAL + ANSFO(4) + ANSFO(5) + ANSFO(12)
      sum3 = TETAL + ANSFO(1)
      sum4 = ANSFO(10) + ANSFO(11)

' BIOTITE COMPONENT ACTIVITIES
      SI = ANSFO(1)
      AFEF = MiscConvertLog10#(CDbl(ANSFO(9) * ((ANSFO(4) / 3#) ^ 3) * TETAL * ((SI / 3#) ^ 3) * (HALMF ^ 2)))
      AMGF = MiscConvertLog10#(CDbl(ANSFO(9) * ((ANSFO(5) / 3#) ^ 3) * TETAL * ((SI / 3#) ^ 3) * (HALMF ^ 2)))
      AFEOH = MiscConvertLog10#(CDbl(ANSFO(9) * ((ANSFO(4) / 3#) ^ 3) * TETAL * ((SI / 3#) ^ 3) * (HALMO ^ 2)))
      AMGOH = MiscConvertLog10#(CDbl(ANSFO(9) * ((ANSFO(5) / 3#) ^ 3) * TETAL * ((SI / 3#) ^ 3) * (HALMO ^ 2)))

      XMG = (ANSFO(5) / 3#)
      XSID = (((3# - ANSFO(1) / ANSFO(3)) / 1.75) * (1# - XMG))
      XAN = 1# - (XMG + XSID)
      PHLOG = XMG * 100#
      SIDER = XSID * 100#
      ANNIT = XAN * 100#

' COMPUTE Y-INTERCEPT
      RAMGFE = MiscConvertLog10#(CDbl(MGMFT / FEX))
      YM32X = XFOXOH - 1.5 * RAMGFE

Call IOWriteLog(SSTRING2$)
Call IOWriteLog("NUMBER OF ATOMS:")
Call IOWriteLog(a8x$ & "SI   " & Format$(Format$(ANSFO!(1), f84$), a80$))
Call IOWriteLog(a8x$ & "ALIV " & Format$(Format$(TETAL!, f84$), a80$) & a8x$ & "ALVI" & Format$(Format$(OCTAL!, f84$), a80$))
Call IOWriteLog(a8x$ & "TI   " & Format$(Format$(ANSFO!(2), f84$), a80$))
Call IOWriteLog(a8x$ & "FE   " & Format$(Format$(ANSFO!(4), f84$), a80$))
Call IOWriteLog(a8x$ & "MG   " & Format$(Format$(ANSFO!(5), f84$), a80$))
Call IOWriteLog(a8x$ & "MN   " & Format$(Format$(ANSFO!(12), f84$), a80$))
Call IOWriteLog(a8x$ & "CA   " & Format$(Format$(ANSFO!(6), f84$), a80$))
Call IOWriteLog(a8x$ & "NA   " & Format$(Format$(ANSFO!(7), f84$), a80$))
Call IOWriteLog(a8x$ & "BA   " & Format$(Format$(ANSFO!(8), f84$), a80$))
Call IOWriteLog(a8x$ & "K    " & Format$(Format$(ANSFO!(9), f84$), a80$))
Call IOWriteLog(a8x$ & "F    " & Format$(Format$(ANSFO!(10), f84$), a80$))
Call IOWriteLog(a8x$ & "CL   " & Format$(Format$(ANSFO!(11), f84$), a80$))
Call IOWriteLog(a8x$ & "OH   " & Format$(Format$(2# - (ANSFO(11) + ANSFO(10)), f84$), a80$) & "        CALCULATED")

Call IOWriteLog(vbCrLf & "SUMMARY OF BIOTITE GEOCHEMISTRY:")
     
' PRINT OUT BRIMHALL CALCULATIONS
astring$ = vbCrLf
astring$ = astring$ & Format$("LOG(XF/XCL) = ", a18$) & Format$(Format$(HALOG1!, f84$), A10$)
astring$ = astring$ & Format$("LOG(X-F/X-OH) = ", a18$) & Format$(Format$(XFOXOH!, f84$), A10$)
astring$ = astring$ & Format$("LOG(X-MG/X-FE) = ", a18$) & Format$(Format$(RAMGFE!, f84$), A10$)
Call IOWriteLog(astring$)

astring$ = vbNullString
astring$ = astring$ & Format$("X-MG = ", a18$) & Format$(Format$(MGMFT!, f84$), A10$)
astring$ = astring$ & Format$("X-FE = ", a18$) & Format$(Format$(FEX!, f84$), A10$)
astring$ = astring$ & Format$("X-TI = ", a18$) & Format$(Format$(tix!, f84$), A10$)
Call IOWriteLog(astring$)

astring$ = vbNullString
astring$ = astring$ & Format$("X-MN = ", a18$) & Format$(Format$(MNX!, f84$), A10$)
astring$ = astring$ & Format$("X-AL VI = ", a18$) & Format$(Format$(XALVI!, f84$), A10$)
astring$ = astring$ & Format$("MG/(MG+FE) = ", a18$) & Format$(Format$(MGB!, f84$), A10$)
Call IOWriteLog(astring$)
           
astring$ = vbCrLf
astring$ = astring$ & Format$("X-OH = ", a18$) & Format$(Format$(HALMO!, f84$), A10$)
astring$ = astring$ & Format$("X-F = ", a18$) & Format$(Format$(HALMF!, f84$), A10$)
astring$ = astring$ & Format$("X-CL = ", a18$) & Format$(Format$(HALMC!, f84$), A10$)
astring$ = astring$ & Format$("LOG (X-F/X-OH) = ", a18$) & Format$(Format$(XFOXOH!, f84$), A10$)
Call IOWriteLog(astring$)
           
astring$ = vbCrLf
astring$ = astring$ & Format$("TRIANGULAR PLOT        LOG X-F/X-OH  -1.5 * LOG X-MG/X-FE = ") & Format$(Format$(YM32X!, f84$), A10$)
Call IOWriteLog(astring$)
     
astring$ = vbCrLf
astring$ = astring$ & Format$("X-SID: = ", a18$) & Format$(Format$(SIDER!, f84$), A10$)
astring$ = astring$ & Format$("X-ANN: = ", a18$) & Format$(Format$(ANNIT!, f84$), A10$)
astring$ = astring$ & Format$("X-PHLOG: = ", a18$) & Format$(Format$(PHLOG!, f84$), A10$)
Call IOWriteLog(astring$)

astring$ = vbCrLf
astring$ = astring$ & Format$("(K+Na+Ca+Ba)", a22$) & Format$("(Ti+Al(VI)+Fe+Mg+Mn)", a22$) & Format$("(Al(IV)+Si)", a22$) & Format$("(F+CL)", a22$) & vbCrLf
astring$ = astring$ & Format$(Format$(sum1!, f84$), a22$) & Format$(Format$(sum2!, f84$), a22$) & Format$(Format$(sum3!, f84$), a22$) & Format$(Format$(sum4!, f84$), a22$)
Call IOWriteLog(astring$)
           
' WRITE OUTPUT FILE FOR HALOG.OUT (COMPOSITONAL FRAMES)
astring$ = "Sample " & vbTab & VbDquote$ & sample(1).number% & VbDquote$ & vbTab & VbDquote$ & sample(1).Name$ & VbDquote$
Print #tfilenumber%, astring$

astring$ = vbNullString
For i% = 1 To MAXBIOT%
    If i% = 3 Then
        astring$ = astring$ + MiscAutoFormat$(WTPC!(i%)) & vbTab$ & MiscAutoFormat$(ANSFO!(i%)) & vbTab$ & MiscAutoFormat$(TETAL!) & vbTab$ & MiscAutoFormat$(OCTAL!) & vbTab & esym$(i%) & vbCrLf
    ElseIf i% = 11 Then
        astring$ = astring$ + MiscAutoFormat$(WTPC!(i%)) & vbTab$ & MiscAutoFormat$(ANSFO!(i%)) & vbTab$ & MiscAutoFormat$(2# - (ANSFO!(10) + ANSFO!(11))) & vbTab$ & esym$(i%) & vbCrLf
    Else
        astring$ = astring$ + MiscAutoFormat$(WTPC!(i%)) & vbTab$ & MiscAutoFormat$(ANSFO!(i%)) & vbTab$ & esym$(i%) & vbCrLf
    End If
Next i%
Print #tfilenumber%, astring$

astring$ = vbNullString
astring$ = astring$ & MiscAutoFormat$(WTT!) & vbTab$ & MiscAutoFormat$(HALOG1!) & vbTab$ & MiscAutoFormat$(RAMGFE!) & vbTab$ & MiscAutoFormat$(MGMFT!) & vbTab$ & MiscAutoFormat$(FEX!) & vbTab$ & MiscAutoFormat$(tix!) & vbTab$ & MiscAutoFormat$(XALVI!) & vbTab$ & MiscAutoFormat$(MNX!) & vbTab$ & MiscAutoFormat$(XFOXOH!) & vbTab$
astring$ = astring$ & MiscAutoFormat$(SIDER!) & vbTab$ & MiscAutoFormat$(ANNIT!) & vbTab$ & MiscAutoFormat$(PHLOG!) & vbTab$ & MiscAutoFormat$(sum1!) & vbTab$ & MiscAutoFormat$(sum2!)
Print #tfilenumber%, astring$
 
Exit Sub

' Errors
ConvertHalogError:
MsgBox Error$, vbOKOnly + vbCritical, "ConvertHalog"
Close #tfilenumber%
ierror = True
Exit Sub

End Sub
The only stupid question is the one not asked!

Ben Buse

  • Professor
  • ****
  • Posts: 498
Re: Mineral formula calculations
« Reply #3 on: November 05, 2020, 08:32:58 AM »
Hi John,

I wondering would it be possible to "Calculate Formula Based On" X "Atoms of" Sum Cations excluding H.

This seems easier to code then based on Sum of X, Y and Z elements.

Otherwise excess water by diff depresses the number of the other cations.

Thanks

Ben

John Donovan

  • Administrator
  • Emeritus
  • *****
  • Posts: 3304
  • Other duties as assigned...
    • Probe Software
Re: Mineral formula calculations
« Reply #4 on: November 05, 2020, 09:23:41 AM »
Hi John,

I wondering would it be possible to "Calculate Formula Based On" X "Atoms of" Sum Cations excluding H.

This seems easier to code then based on Sum of X, Y and Z elements.

Otherwise excess water by diff depresses the number of the other cations.

Thanks

Ben

Hi Ben,
Anything is possible, but amphiboles and biotites are complicated as you know.  Brian Joy and I are discussing a more robust approach described here:

https://probesoftware.com/smf/index.php?topic=1323.0

which would be based on the actual mineral formula.

But I don't quite understand why including water by difference would depress the formula values of the other cations. As long as the sum of cations includes hydrogen as a cation why would it be a problem?  Can you give us an example of what you mean?
John J. Donovan, Pres. 
(541) 343-3400

"Not Absolutely Certain, Yet Reliable"

Ben Buse

  • Professor
  • ****
  • Posts: 498
Re: Mineral formula calculations
« Reply #5 on: November 09, 2020, 04:57:13 AM »
Hi John,

You're right that it's not a problem when the calculated H2O is correct.

There is a bigger error on the calculated H2O however: it is the sum of all the errors on each element. By not including H when fixing the cation sum, this has less an effect.

I was looking at alunite at the moment, I don't know if its worth doing?

Ben
« Last Edit: November 10, 2020, 01:44:12 PM by John Donovan »

Joseph_Shaw

  • Student
  • *
  • Posts: 3
Changing oxidation state of elements in PfE based on mineral formula?
« Reply #6 on: November 19, 2020, 02:24:32 AM »
Hi all,

I am pretty new to EPMA so apologies if this is a silly question. Is changing the oxidation state of elements manually in PfE a robust way of looking at EPMA data?

I am measuring major elements in alunite, a hydrous sulphate with the general formula:

AB3(XO4)2(OH)6, where 'A' is generally K or Na, 'B' is Al or Fe, and 'X' is S or P. The (OH)6 should account for 25 wt% of the mineral.

In PfE, I am including hydrogen in the analyses to calculate water by difference (so that this is accounted for by the matrix calculations for the other elements). The oxidation state of the elements in alunite (e.g. no oxygens on the 'A' or 'B' site cations is different to the automatically assigned number of oxygens (e.g. K2O, Al2O3 etc) generally assigned when EPMA data are reported in the literature.

If I use the normally assigned oxygens for each element, I get the wrong amount of H2O for alunite (generally 12-19 wt%). However, if I use the 'Elements/cations' menu to change the number of oxygens for each elements based on the mineral formula for alunite (e.g. no oxygens on the potential 'A' and 'B' site elements, and 4 oxygens on the potential 'X' site elements), and then display results as oxides, then I get very close to the correct H2O.

So, the question is, is this way of looking at the data appropriate? And is reporting EPMA oxide wt% data where some of the elements aren't oxides ok (in my PhD thesis)?

Any advice would be appreciated  :)

Joe

AndrewLocock

  • Professor
  • ****
  • Posts: 104
    • University of Alberta Electron Microprobe Laboratory
Re: Mineral formula calculations
« Reply #7 on: November 19, 2020, 07:53:11 AM »
Hello Joseph,
In alunite, Fe is essentially only ferric iron, and you are right, it should therefore should be expressed as Fe2O3 instead of FeO.

Any electro-neutral formula in which O is the only anionic element should be able to be expressed entirely as neutral oxides in percent-by-weight.

Below are the formulas and wt% oxides of the KAl, KFe, NaAl, and NaFe disulfate hexahydroxide end-members.

                 oxide    K2O       Na2O     Al2O3      Fe2O3    SO3     H2O    sum
KAl3(SO4)2(OH)6    wt%   11.37              36.92               38.66   13.05   100.00
KFe3(SO4)2(OH)6    wt%    9.40                          47.83   31.98   10.79   100.00
NaAl3(SO4)2(OH)6   wt%             7.78     38.42               40.22   13.58   100.00
NaFe3(SO4)2(OH)6   wt%             6.39                 49.42   33.04   11.15   100.00

I would suggest that, in addition to expressing Fe as Fe2O3, instead of including H as H2O by difference, that you include H as a ratio to O.
In the alunite-type formulas above, there are 6 H and 14 O. The ratio of H to O is therefore 0.428571 : 1.
The H content will be expressed as neutral H2O in the wt% oxide listings, but in the formula, it will be present as OH.

In summary, in the Elements/cations menu, the only element to change is Fe, and it should be Fe2O3.

Best regards,
Andrew




« Last Edit: November 19, 2020, 08:37:06 AM by John Donovan »

John Donovan

  • Administrator
  • Emeritus
  • *****
  • Posts: 3304
  • Other duties as assigned...
    • Probe Software
Re: Mineral formula calculations
« Reply #8 on: November 19, 2020, 10:59:21 AM »
I am pretty new to EPMA so apologies if this is a silly question. Is changing the oxidation state of elements manually in PfE a robust way of looking at EPMA data?

I am measuring major elements in alunite, a hydrous sulphate with the general formula:

AB3(XO4)2(OH)6, where 'A' is generally K or Na, 'B' is Al or Fe, and 'X' is S or P. The (OH)6 should account for 25 wt% of the mineral.

In PfE, I am including hydrogen in the analyses to calculate water by difference (so that this is accounted for by the matrix calculations for the other elements). The oxidation state of the elements in alunite (e.g. no oxygens on the 'A' or 'B' site cations is different to the automatically assigned number of oxygens (e.g. K2O, Al2O3 etc) generally assigned when EPMA data are reported in the literature.

If I use the normally assigned oxygens for each element, I get the wrong amount of H2O for alunite (generally 12-19 wt%). However, if I use the 'Elements/cations' menu to change the number of oxygens for each elements based on the mineral formula for alunite (e.g. no oxygens on the potential 'A' and 'B' site elements, and 4 oxygens on the potential 'X' site elements), and then display results as oxides, then I get very close to the correct H2O.

So, the question is, is this way of looking at the data appropriate? And is reporting EPMA oxide wt% data where some of the elements aren't oxides ok (in my PhD thesis)?

Any advice would be appreciated  :)

Hi Joe,
The whole reason for including water or OH into the matrix correction is to correct for the effects of these unanalyzed elements on the concentrations of the analyzed elements (and of course as you point out, these unanalyzed elements also affect the calculated formula ratios).  In the past it was assumed that a little extra water or OH or excess oxygen can't have that much of an effect but surprisingly it does.  This topic discusses a number of these situations:

https://probesoftware.com/smf/index.php?topic=92.0

Also this topic:

https://probesoftware.com/smf/index.php?topic=61.0

The point being from a matrix correction standpoint it really doesn't matter how you add in the unanalyzed elements as long as the specified concentrations of these unanalyzed are reasonably close to their expected values.  So by difference or by stoichiometry are both valid methods.

Modifying the cation/oxygen stoichiometries in PfE to match the actual mineral formula sounds perfectly reasonable to me, in fact that is normally what one would expect to have to do to get the correct calculated concentrations since you aren't measuring oxygen!
« Last Edit: November 19, 2020, 02:31:55 PM by John Donovan »
John J. Donovan, Pres. 
(541) 343-3400

"Not Absolutely Certain, Yet Reliable"

Joseph_Shaw

  • Student
  • *
  • Posts: 3
Re: Mineral formula calculations
« Reply #9 on: November 20, 2020, 01:46:43 AM »
Hi John and Andrew,
Thanks a lot for the advice. I will change the oxidation state of Fe (although my samples are generally Al-rich and extremely low Fe) and see how changing the calculation of H affects the results.
Joe

AndrewLocock

  • Professor
  • ****
  • Posts: 104
    • University of Alberta Electron Microprobe Laboratory
Re: Mineral formula calculations
« Reply #10 on: November 20, 2020, 07:48:33 AM »
Hi John and Andrew,
Thanks a lot for the advice. I will change the oxidation state of Fe (although my samples are generally Al-rich and extremely low Fe) and see how changing the calculation of H affects the results.
Joe

Hi Joe,
I suspect that your alunite-group minerals are quite sensitive to damage by the electron beam.
It is possible that self-corrected time-dependent-intensity (TDI) correction of the Na, K, Al and S would help.
I believe that there is a discussion of TDI at:
https://probesoftware.com/smf/index.php?topic=11.msg9000#msg9000

I would also suggest to use a broad beam, say 5 to 10 microns diameter, if possible.
Cheers,
Andrew


Joseph_Shaw

  • Student
  • *
  • Posts: 3
Re: Mineral formula calculations
« Reply #11 on: November 24, 2020, 05:37:48 AM »
Hi John,
You are right - the crystals are very easily damaged. Unfortunately the samples are fine grained (generally sub-10 microns), with voids between grains. We have been getting reasonable results with a 2 micron, 3nA beam and applying a TDI correction.