29 DOUBLE PRECISION mwxstoich
35 CHARACTER(LEN=32) :: name
37 CHARACTER(LEN=512) :: chemeq
39 CHARACTER(LEN=16) :: classification
48 DOUBLE PRECISION,
DIMENSION(:),
ALLOCATABLE :: hor
50 DOUBLE PRECISION,
DIMENSION(:),
ALLOCATABLE :: rphase
52 TYPE(
species_),
DIMENSION(:),
ALLOCATABLE :: species
74 INTEGER,
INTENT(IN) :: lNg
76 CHARACTER(len=32),
DIMENSION(DIM_N_g),
INTENT(IN) :: SA_g
78 INTEGER,
INTENT(IN) :: lMMx
80 INTEGER,
DIMENSION(DIM_M),
INTENT(IN) :: lNs
82 CHARACTER(len=32),
DIMENSION(DIM_M, DIM_N_s),
INTENT(IN) :: SA_s
88 CHARACTER(len=32) SA1, SA2
98 IF(len_trim(sa1) == 0) cycle
101 IF(len_trim(sa2) == 0) cycle
108 IF(len_trim(sa2) == 0) cycle
117 IF(len_trim(sa1) == 0) cycle
122 IF(len_trim(sa2) == 0) cycle
129 IF(len_trim(sa2) == 0) cycle
139 100
WRITE(
err_msg, 1100) m1, n1, sa1, m2, n2, sa2
142 1100
FORMAT(
'Error 1100: Non-unique species aliases detected.',/ &
143 3x,
'Phase: ',i2,
', Species: ',i3,
' - Alias: ',a,/ &
144 3x,
'Phase: ',i2,
', Species: ',i3,
' - Alias: ',a,// &
145 'Please correct the mfix.dat file.')
163 lnrxn, lrnames, lnrxn_des, lrnames_des)
173 INTEGER,
INTENT(IN) :: lNg
175 CHARACTER(len=32),
DIMENSION(DIM_N_g),
INTENT(IN) :: SA_g
177 INTEGER,
INTENT(IN) :: lMMx
179 INTEGER,
DIMENSION(DIM_M),
INTENT(IN) :: lNs
181 CHARACTER(len=32),
DIMENSION(DIM_M, DIM_N_s),
INTENT(IN) :: SA_s
183 INTEGER,
INTENT(IN) :: lNRxn
187 INTEGER,
INTENT(IN) :: lNRxn_DES
194 INTEGER,
PARAMETER :: FUNIT = 167
196 CHARACTER(len=255) :: FILENAME
197 CHARACTER(len=128) :: INPUT
204 CHARACTER(len=64) :: lName
205 CHARACTER(len=32) :: tName
219 CASE(1); filename =
'species.inc' 220 OPEN(convert=
'BIG_ENDIAN',unit=funit,file=trim(filename),status=
'OLD',iostat=ios)
221 IF(ios /= 0) cycle src_lp
223 WRITE(
err_msg, 1000)
'species.inc' 227 1000
FORMAT(/2x,
'Verifying reaction aliases in ',a)
238 1004
FORMAT(
'Warning 1004: Unable to locate the species.inc file. No ',&
239 'verification',/
'of mfix.dat species aliases or reaction ', &
240 'names can be preformed.')
244 READ(funit,
"(A)",iostat=ios) input
249 WRITE(
err_msg,1200) trim(adjustl(filename))
251 1200
FORMAT(
'Error 1200: There was a problem reading file: ',a)
265 IF(line_len <= 0) cycle read_lp
268 pos = index(input,
"INTEGER, PARAMETER ::")
270 input = input((pos + 21):)
276 pos = index(input,
"=")
277 IF(pos == 0) cycle read_lp
280 WRITE(lname,
"(A)") trim(adjustl(input(:(pos-1))))
283 READ(input((pos+1):),*,iostat=ios) lindex
285 WRITE(
err_msg,1205)
'index', trim(input)
289 1205
FORMAT(
'Error 1205: Unable to obtain alias index from species.', &
290 'inc file.',//
' INPUT: ',a)
294 IF(lindex <= lng)
THEN 301 IF(lindex <= lns(m))
THEN 302 tname = sa_s(m, lindex)
308 IF(lindex <= lnrxn)
THEN 309 tname = lrnames(lindex)
314 IF(lindex <= lnrxn_des)
THEN 315 tname = lrnames_des(lindex)
319 WRITE(
err_msg,1300) trim(lname), lindex
322 1300
FORMAT(
'Error 1300: An entry in the species.inc file does not ', &
323 'match any inputs',/
'in the mfix.dat file.'/3x,
'Name: ',a,4x, &
324 'Index: ',i3,/
'If the quantity or order of gas species, ', &
325 'solids species, or chemical',/
'reactions has changed, then ',&
326 'the executable must be re-build. Please',/
'see the document',&
327 'ation for specifying chemical reactions.')
355 CHARACTER(len=*),
INTENT(IN) :: lS1, lS2
357 INTEGER,
OPTIONAL,
INTENT(IN) :: N1, N2
367 IF(
PRESENT(n1) .AND.
PRESENT(n2))
THEN 402 CHARACTER(len=32),
DIMENSION(DIM_N_g),
INTENT(IN) :: lSAg
404 CHARACTER(len=32),
DIMENSION(DIM_M, DIM_N_s),
INTENT(IN) :: lSAs
406 LOGICAL,
INTENT(IN) :: ABORT
409 INTEGER,
OPTIONAL :: fUNIT
411 CHARACTER(LEN=72) :: OUTPUT, full, divided, empty
413 CHARACTER(LEN=32) :: lSP
420 IF(
present(funit))
THEN 439 WRITE(
output, 2001)trim(rxn%Name)
447 WRITE(
output, 2002)trim(rxn%ChemEq(1:54))
453 IF(rxn%nSpecies > 0)
THEN 456 WRITE(
output, 2007)trim(rxn%Classification)
468 DO ln = 1, rxn%nSpecies
470 m = rxn%Species(ln)%pMap
471 n = rxn%Species(ln)%sMap
476 IF(len_trim(lsag(n)) > 8)
THEN 480 ls = (9-int(len_trim(lsag(n))/2))
481 le = ls + len_trim(lsag(n))
482 output(ls:le) = trim(lsag(n))
484 WRITE(
output(32:35),
"(A)")
'Gas' 486 IF(len_trim(lsas(m,n)) > 8)
THEN 490 ls = (9-int(len_trim(lsas(m,n))/2))
491 le = ls + len_trim(lsas(m,n))
492 output(ls:le) = trim(lsas(m,n))
494 WRITE(
output(30:36),
"(A,I2)")
'Solid',m
496 WRITE(
output(43:44),
"(I2)") n
497 WRITE(
output(51:60),
"(F9.4)") rxn%Species(ln)%MW
501 WRITE(
output(63:71),
"(A)")
'Catalyst' 502 ELSEIF(rxn%Species(ln)%Coeff <
zero)
THEN 503 WRITE(
output(17:26),
"(F9.4)") -rxn%Species(ln)%Coeff
504 WRITE(
output(63:71),
"(A)")
'Reactant' 506 WRITE(
output(17:26),
"(F9.4)") rxn%Species(ln)%Coeff
507 WRITE(
output(63:70),
"(A)")
'Product' 520 2000
FORMAT(2x,
'|',68(
'-'),
'|')
522 2001
FORMAT(2x,
'| Name: ',a)
523 2002
FORMAT(2x,
'| Chemical Eq: ',a)
525 2003
FORMAT(
' | Species | Stoich | | Species |', &
528 2004
FORMAT(
' | Alias | Coeff. | Phase | Index |', &
532 2005
FORMAT(2x,
'|',10(
'-'),
'|',13(
'-'),
'|',9(
'-'),
'|',9(
'-'),
'|', &
533 12(
'-'),
'|',10(
'-'),
'|')
535 2006
FORMAT(2x,
'|',10(
' '),
'|',13(
' '),
'|',9(
' '),
'|',9(
' '),
'|', &
536 12(
' '),
'|',10(
' '),
'|')
539 2007
FORMAT(2x,
'| Classification: ',a)
562 CHARACTER(len=*),
INTENT(IN) :: LINE
563 INTEGER,
INTENT(IN) :: UFLAG
604 CHARACTER(len=18),
INTENT(IN) :: S_g(
dim_n_g)
607 DOUBLE PRECISION,
INTENT(in) :: Cpg0
608 DOUBLE PRECISION,
INTENT(in) :: Cps0(
dim_m)
609 DOUBLE PRECISION,
INTENT(inout) :: MWg(
dim_n_g)
613 LOGICAL :: CHECK_DATABASE
620 check_database = .false.
625 DO ln = 1, rxn%nSpecies
626 m = rxn%Species(ln)%pMap
627 n = rxn%Species(ln)%sMap
631 ELSEIF((rxn%Calc_DH .AND. .NOT.rdb(m,n)) .OR. &
633 check_database = .true.
638 ELSEIF((rxn%Calc_DH .AND. .NOT.rdb(m,n)) .OR. &
640 check_database = .true.
648 WRITE(
err_msg, 1100) trim(rxn%Name)
651 1100
FORMAT(
'Error 1100: One or more phases associated with ', &
652 'reaction ',a,/
'has specified constant specific heat (C_PG0/',&
653 'Cps0). This is',/
'not permitted for reacting phases. ', &
654 'Please correct the mfix.dat file.')
656 ELSEIF(check_database)
THEN 658 WRITE(
err_msg, 1101) trim(rxn%Name)
661 1101
FORMAT(
'Message 1101: One or more molecular weights and/or ', &
662 'thermochemical data',/
'is needed for reaction ',a,
'. The ', &
663 'thermochemical database',/
'will be used to gather the ', &
668 IF(check_database)
THEN 673 1200
FORMAT(
'Message 1200: Searching thermochemical databases for ',&
674 'species data.',/
' ')
676 DO ln = 1, rxn%nSpecies
677 m = rxn%Species(ln)%pMap
678 n = rxn%Species(ln)%sMap
680 IF((rxn%Calc_DH .AND. .NOT.rdb(m,n)) .OR. &
690 WRITE(
err_msg, 3001) n, trim(s_g(n))
697 rxn%Species(ln)%MW = mwg(n)
699 IF((rxn%Calc_DH .AND. .NOT.rdb(m,n)) .OR. &
708 WRITE(
err_msg, 3001) n, trim(s_s(m,n))
714 rxn%Species(ln)%MW = mws(m,n)
720 3001
FORMAT(/2x,
'>',i3,
': Species: ',a)
726 1000
FORMAT(
'Error 1000: Required input not specified: ',a,/
'Please ',&
727 'correct the mfix.dat file.')
749 CHARACTER(len=*),
INTENT(IN) :: CALLER
754 DOUBLE PRECISION,
INTENT(OUT) :: lnMT(0:
dim_m)
755 INTEGER,
INTENT(OUT) :: IER
758 DOUBLE PRECISION rSUM, pSUM
759 DOUBLE PRECISION MWxStoich
761 INTEGER sprCount, sprIndex
763 DOUBLE PRECISION,
PARAMETER :: massBalanceTol = 1.0d-3
774 DO ln = 1, rxn%nSpecies
775 m = rxn%Species(ln)%pMap
776 n = rxn%Species(ln)%sMap
779 mwxstoich = rxn%Species(ln)%MW * rxn%Species(ln)%Coeff
780 rxn%Species(ln)%MWxStoich = mwxstoich
785 lnmt(m) = lnmt(m) + mwxstoich
787 IF(mwxstoich <
zero)
THEN 788 rsum = rsum - mwxstoich
790 sprcount = sprcount + 1
791 IF(sprcount == 1)
THEN 794 ELSEIF( m /= sprindex)
THEN 796 WRITE(*,1002) trim(caller), trim(rxn%Name)
797 WRITE(
unit_log,1002) trim(caller), trim(rxn%Name)
803 psum = psum + mwxstoich
807 IF (.NOT.
compare(rsum,psum))
THEN 809 WRITE(*,1001) trim(caller), trim(rxn%Name), rsum, psum
810 WRITE(
unit_log,1001) trim(caller), trim(rxn%Name), rsum,psum
820 1001
FORMAT(/1x,70(
'*')/
' From: ',a,
' --> RXN_COM -->', &
821 ' checkMassBalance',/
' Error 1001: Stoichiometry is not', &
822 ' consistent with molecular weights',/
' for reaction ',a,
'.',/&
823 ' Mass of reactants: ',f12.4,/
' Mass of products: ',f12.4,/ &
826 1002
FORMAT(/1x,70(
'*')/
' From: ',a,
' --> RXN_COM -->', &
827 ' checkMassBalance',/
' Error 1002: More than one solids', &
828 ' phase fules was detected. Unable to',/
' determine solids/', &
829 'solids heat of reaction unambiguously for',/
' reaction ',a, &
854 CHARACTER(len=*),
INTENT(IN) :: CALLER
859 DOUBLE PRECISION,
INTENT(IN) :: lnMT(0:
dim_m)
861 LOGICAL,
INTENT(IN) :: lEEq
863 LOGICAL,
INTENT(IN) :: lSEq(0:
dim_m)
865 CHARACTER(len=32),
DIMENSION(DIM_N_g),
INTENT(IN) :: lSAg
867 INTEGER,
INTENT(IN) :: lMMx
869 CHARACTER(len=32),
DIMENSION(DIM_M, DIM_N_s),
INTENT(IN) :: lSAs
871 INTEGER toPhase, toPhaseCount, mCount
872 INTEGER fromPhase, fromPhaseCount
878 DOUBLE PRECISION,
PARAMETER :: massBalanceTol = 1.0d-3
881 IF(
Allocated(rxn%rPhase)) rxn%rPhase(:) =
zero 885 IF(rxn%nPhases == 1)
THEN 891 DO ln = 1, rxn%nSpecies
892 m = rxn%Species(ln)%pMap
893 rxn%Species(ln)%mXfr = m
895 rxn%Classification =
"Homogeneous" 904 IF (lnmt(m) > massbalancetol)
THEN 905 tophasecount = tophasecount + 1
909 ELSEIF(lnmt(m) < -massbalancetol)
THEN 910 fromphasecount = fromphasecount + 1
916 IF(tophasecount == 1)
THEN 918 rxn%Classification =
"Heterogeneous" 920 IF(m /= tophase)
THEN 921 IF (tophase < m)
THEN 922 lm = 1 + tophase + ((m-1)*m)/2
923 rxn%rPhase(lm) = -lnmt(m)
925 lm = 1 + m + ((tophase-1)*tophase)/2
926 rxn%rPhase(lm) = lnmt(m)
933 IF((lseq(tophase) .AND. .NOT.lseq(m)) .OR. &
934 (.NOT.lseq(tophase) .AND. lseq(m)))
THEN 936 WRITE(*,1001) trim(caller)
939 WRITE(*,1101) m,
'Solving' 940 WRITE(*,1101) tophase,
'Not Solving' 945 WRITE(*,1101) tophase,
'Solving' 946 WRITE(*,1101) m,
'Not Solving' 962 IF(leeq .AND. rxn%Calc_DH)
THEN 963 DO ln = 1, rxn%nSpecies
964 m = rxn%Species(ln)%pMap
968 IF(tophase == 0)
THEN 976 IF(rxn%rPhase(lm) > 0)
THEN 978 rxn%Species(ln)%mXfr = mm
981 rxn%Species(ln)%xXfr =
zero 988 WRITE(*,1002) trim(caller), &
991 WRITE(
unit_log,1002) trim(caller), &
1004 rxn%Species(ln)%mXfr = tophase
1006 rxn%Species(ln)%xXfr =
zero 1013 DO mm = ll + 1, lmmx
1014 IF(m /= ll .AND. m /= mm) cycle
1015 lm = ll + 1 + (mm-1)*mm/2
1016 IF(rxn%rPhase(lm) ==
zero) cycle
1020 rxn%rPhase(lm) <
zero)
THEN 1022 rxn%Species(ln)%mXfr = mm
1025 rxn%Species(ln)%xXfr = &
1026 abs(lnmt(mm) / lnmt(ll))
1029 ELSEIF( m == mm .AND. &
1030 rxn%rPhase(lm) >
zero)
THEN 1032 rxn%Species(ln)%mXfr = ll
1035 rxn%Species(ln)%xXfr = &
1036 abs(lnmt(ll) / lnmt(mm))
1045 ELSEIF(fromphasecount == 1)
THEN 1046 rxn%Classification =
"Heterogeneous" 1048 IF (m /= fromphase)
THEN 1049 IF(m < fromphase)
THEN 1050 lm = 1 + m + ((fromphase-1)*fromphase)/2
1051 rxn%rPhase(lm) = lnmt(m)
1053 lm = 1 + fromphase + ((m-1)*m)/2
1054 rxn%rPhase(lm) = -lnmt(m)
1060 IF((lseq(fromphase) .AND. .NOT.lseq(m)) .OR. &
1061 (.NOT.lseq(fromphase) .AND. lseq(m)))
THEN 1063 WRITE(*,1001) trim(caller)
1066 WRITE(*,1101) m,
'Solving' 1067 WRITE(*,1101) fromphase,
'Not Solving' 1072 WRITE(*,1101) tophase,
'Solving' 1073 WRITE(*,1101) m,
'Not Solving' 1074 WRITE(
unit_log,1101) fromphase,
'Solving' 1075 WRITE(
unit_log,1101) m,
'Not Solving' 1088 IF(leeq .AND. rxn%Calc_DH)
THEN 1089 DO ln = 1, rxn%nSpecies
1090 m = rxn%Species(ln)%pMap
1095 IF(fromphase == 0)
THEN 1101 lm = 1 + (mm-1)*mm/2
1103 IF(rxn%rPhase(lm) < 0)
THEN 1105 rxn%Species(ln)%mXfr = mm
1108 rxn%Species(ln)%xXfr =
zero 1113 IF(mcount /=1 )
THEN 1115 WRITE(*,1002) trim(caller), &
1118 WRITE(
unit_log,1002) trim(caller), &
1128 rxn%Species(ln)%mXfr = fromphase
1131 rxn%Species(ln)%xXfr =
zero 1138 DO mm = ll + 1, lmmx
1139 IF(m /= ll .AND. m /= mm) cycle
1140 lm = ll + 1 + (mm-1)*mm/2
1141 IF(rxn%rPhase(lm) ==
zero) cycle
1145 rxn%rPhase(lm) <
zero)
THEN 1147 rxn%Species(ln)%mXfr = mm
1150 rxn%Species(ln)%xXfr = &
1151 abs(lnmt(mm) / lnmt(ll))
1154 ELSEIF( m == mm .AND. &
1155 rxn%rPhase(lm) >
zero)
THEN 1157 rxn%Species(ln)%mXfr = ll
1160 rxn%Species(ln)%xXfr = &
1161 abs(lnmt(ll) / lnmt(mm))
1171 ELSEIF(tophasecount == 0 .AND. fromphasecount == 0)
THEN 1174 IF(rxn%nPhases > 0) rxn%Classification =
"Catalytic" 1175 rxn%rPhase(:) =
zero 1177 IF(leeq .AND. rxn%Calc_DH)
THEN 1181 DO ln= 1, rxn%nSpecies
1183 IF(catphase /= -1)
THEN 1184 IF(catphase /= rxn%Species(ln)%pMap)
THEN 1186 WRITE(*,1002) trim(caller), &
1189 WRITE(
unit_log,1002) trim(caller), &
1197 catphase = rxn%Species(ln)%pMap
1202 IF(catphase == -1)
THEN 1204 WRITE(*,1003) trim(caller),
'catalyst', &
1207 WRITE(
unit_log,1003) trim(caller), &
1208 'catalyst', trim(rxn%Name)
1217 DO ln = 1, rxn%nSpecies
1219 IF(tophase /= -1)
THEN 1220 IF(tophase /= rxn%Species(ln)%pMap)
THEN 1222 WRITE(*,1002) trim(caller), &
1225 WRITE(
unit_log,1002) trim(caller), &
1233 tophase = rxn%Species(ln)%pMap
1238 IF(tophase == -1)
THEN 1240 WRITE(*,1003) trim(caller),
'reacting', &
1243 WRITE(
unit_log,1003) trim(caller),
'reacting', &
1251 IF(catphase == tophase)
THEN 1253 WRITE(*,1004) trim(caller), trim(rxn%Name)
1255 WRITE(
unit_log,1004) trim(caller),trim(rxn%Name)
1260 ELSEIF(tophase == 0)
THEN 1261 DO ln = 1, rxn%nSpecies
1262 IF(rxn%Species(ln)%pMap == 0)
THEN 1264 rxn%Species(ln)%mXfr = catphase
1267 rxn%Species(ln)%xXfr =
zero 1270 ELSEIF(catphase == 0)
THEN 1271 DO ln = 1, rxn%nSpecies
1272 IF(rxn%Species(ln)%pMap == 0)
THEN 1274 rxn%Species(ln)%mXfr = tophase
1277 rxn%Species(ln)%xXfr =
zero 1287 WRITE(*,1002) trim(caller), trim(rxn%ChemEq)
1289 WRITE(
unit_log,1002) trim(caller), trim(rxn%ChemEq)
1300 1000
FORMAT(/
' Please refer to the Readme file on the required input',&
1301 ' format and make',/
' the necessary corrections to the data', &
1302 ' file.',/1x,70(
'*')//)
1304 1001
FORMAT(//1x,70(
'*')/
' From: ',a,
' --> RXN_COM -->', &
1305 ' calcInterphaseTxfr',/
' Error 1001: A chemical reaction or', &
1306 ' phase change was detected between',/
' a phases solving', &
1307 ' species equations and another phase not solving',/ &
1308 ' species equations.',/)
1310 1101
FORMAT(
' Phase ',i2,
': ',a,
' species equations.')
1312 1002
FORMAT(//1x,70(
'*')/
' From: ',a,
' --> RXN_COM -->', &
1313 ' calcInterphaseTxfr',/
' Error 1002: Reaction complexity', &
1314 ' exceeds implementation capabilities.',/
' Unable to', &
1315 ' determine unambiguously interphase heat or mass transfer.', &
1316 //
' Reaction: ',a,//
' Consider splitting the chemical', &
1317 ' reaction equation into two or more',/
' separate equations.',&
1318 ' The same reaction rate calculated in usr_rates',/
' can be', &
1319 ' used for the multiple reactions to ensure mass')
1321 1003
FORMAT(//1x,70(
'*')/
' From: ',a,
' --> RXN_COM -->', &
1322 ' calcInterphaseTxfr',/
' Error 1003: Unable to determine ',a, &
1323 ' phase for catalytic reaction'/1x,a,
'.')
1325 1004
FORMAT(//1x,70(
'*')/
' From: ',a,
' --> RXN_COM -->', &
1326 ' calcInterphaseTxfr',/
' Error 1004: Unable to distinguish', &
1327 ' catalyst phase from reacting phase',/
' for catalytic', &
integer, parameter dim_n_g
character(len=32) function ivar(VAR, i1, i2, i3)
integer, parameter dimension_rxn
logical function compare(V1, V2)
subroutine replace_tab(LINE_STRING, MAXCOL)
double precision, parameter undefined
integer function seek_comment(LINE, MAXCOL)
subroutine init_err_msg(CALLER)
subroutine checkmassbalance(CALLER, RxN, lnMT, IER)
subroutine write_rxn_summary(RxN, lSAg, lSAs, ABORT, fUNIT)
subroutine mfix_exit(myID, normal_termination)
subroutine calcinterphasetxfr(CALLER, RxN, lnMT, lEEq, lSEq, lSAg, lMMx, lSAs)
double precision, parameter small_number
subroutine checkspeciesinc(lNg, SA_g, lMMx, lNs, SA_s, lNRxn, lRNames, lNRxn_DES, lRNames_DES)
integer, parameter unit_log
logical function comparealiases(lS1, lS2, N1, N2)
subroutine checkduplicatealiases(lNg, SA_g, lMMx, lNs, SA_s)
character(len=line_length), dimension(line_count) err_msg
integer, parameter dim_n_s
subroutine read_database(lM, lN, lName, lMW)
logical function blank_line(line)
subroutine make_upper_case(LINE_STRING, MAXCOL)
subroutine checkthermoreqs(RxN, S_g, S_s, rDB, MWg, MWs, Cpg0, Cps0)
double precision, parameter zero
subroutine flush_err_msg(DEBUG, HEADER, FOOTER, ABORT, LOG, CALL_TREE)
subroutine write_rs0(LINE, UFLAG)
character, parameter undefined_c