MFIX  2016-1
rxn_com_mod.f
Go to the documentation of this file.
1 MODULE rxn_com
2 
3  USE compar
4  USE exit, only: mfix_exit
5  USE funits
6  USE param
7  USE param1
8 
9 ! The following data types are used to group chemical reaction data.
10 !-----------------------------------------------------------------------
11 
12 ! Species belong to PHASE_ associated with a particular reaction.
13  TYPE species_
14 ! A link between the reacting species' arbitrary index and the
15 ! associated phase index in MFiX.
16  INTEGER pmap
17 ! A link between the reacting species' arbitrary index and the
18 ! associated species index in MFiX.
19  INTEGER smap
20 ! Stoichiometric coefficient of the species from chemical equation.
21  DOUBLE PRECISION coeff
22 ! Molecular weight
23  DOUBLE PRECISION mw
24 ! Fractional mass transfer
25  DOUBLE PRECISION xxfr
26 ! Index indicating enthalpy transfer associated with mass transfer.
27  INTEGER mxfr
28 ! Molecular weight of speices multiplying the stoichiometric coefficient
29  DOUBLE PRECISION mwxstoich
30  END TYPE species_
31 
32 ! Grouping of reaction information.
34 ! Name of reaction construct from data file.
35  CHARACTER(LEN=32) :: name
36 ! User defined chemical equation from data file.
37  CHARACTER(LEN=512) :: chemeq
38 ! Reaction classification: Homogeneous, Heterogeneous, Catalytic.
39  CHARACTER(LEN=16) :: classification
40 ! Indicates if the automated heat of reaction is to be calculated (T) or
41 ! if the user has supplied a heat of reaction (F).
42  LOGICAL calc_dh
43 ! Number of phases associated with the reaction.
44  INTEGER nphases
45 ! Number of species associated with the reaction.
46  INTEGER nspecies
47 ! User-specified heat of reaction split among phases by fracDH
48  DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: hor
49 ! Interphase mass transfer.
50  DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: rphase
51 ! Reactant/Product information
52  TYPE(species_), DIMENSION(:), ALLOCATABLE :: species
53 
54  END TYPE reaction_block
55 
56  CONTAINS
57 
58 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
59 ! Subroutine: checkDuplicateAlaises !
60 ! !
61 ! Purpose: Loop through species in all phases and ensure that no two !
62 ! entries are the same. ***Warning*** Species aliases that were not !
63 ! specified are skipped. Non-specified aliases are treated later in !
64 ! parse_mod.f/mapAliases. !
65 ! !
66 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
67  SUBROUTINE checkduplicatealiases(lNg, SA_g, lMMx, lNs, SA_s)
68 
69  use error_manager
70 
71  IMPLICIT NONE
72 
73 ! Number of gas speices
74  INTEGER, INTENT(IN) :: lNg
75 ! Gas phase species aliases
76  CHARACTER(len=32), DIMENSION(DIM_N_g), INTENT(IN) :: SA_g
77 ! Number of solids phases
78  INTEGER, INTENT(IN) :: lMMx
79 ! Number of species in each solids phase.
80  INTEGER, DIMENSION(DIM_M), INTENT(IN) :: lNs
81 ! Solids phase speices aliases.
82  CHARACTER(len=32), DIMENSION(DIM_M, DIM_N_s), INTENT(IN) :: SA_s
83 
84 ! Loop indices.
85  INTEGER M1, N1 ! Phase, Species
86  INTEGER M2, N2 ! Phase, Species
87 
88  CHARACTER(len=32) SA1, SA2
89 
90  CALL init_err_msg("RXN_COM --> checkDuplicateAliases")
91 
92 ! Set variables for error messages.
93  m1 = 0
94  m2 = 0
95 ! Compare gas phase aliases.
96  DO n1 = 1, lng
97  sa1 =sa_g(n1)
98  IF(len_trim(sa1) == 0) cycle
99  DO n2=n1+1,lng
100  sa2 = sa_g(n2)
101  IF(len_trim(sa2) == 0) cycle
102  IF(comparealiases(sa1, sa2)) GoTo 100
103  ENDDO
104 ! Compare gas and solids phase aliases.
105  DO m2 = 1, lmmx
106  DO n2 = 1, lns(m2)
107  sa2 = sa_s(m2,n2)
108  IF(len_trim(sa2) == 0) cycle
109  IF(comparealiases(sa1, sa2)) GoTo 100
110  ENDDO
111  ENDDO
112  ENDDO
113 ! Compare aliases between solids phases
114  DO m1 = 1, lmmx
115  DO n1 = 1, lns(m1)
116  sa1 = sa_s(m1,n1)
117  IF(len_trim(sa1) == 0) cycle
118 ! Self phase comparison.
119  m2 = m1
120  DO n2=n1+1, lns(m2)
121  sa2 = sa_s(m2,n2)
122  IF(len_trim(sa2) == 0) cycle
123  IF(comparealiases(sa1, sa2)) GoTo 100
124  ENDDO
125 ! Compare with other phases.
126  DO m2 = m1+1, lmmx
127  DO n2 = 1, lns(m2)
128  sa2 = sa_s(m2,n2)
129  IF(len_trim(sa2) == 0) cycle
130  IF(comparealiases(sa1, sa2)) GoTo 100
131  ENDDO
132  ENDDO
133  ENDDO
134  ENDDO
135 
136  CALL finl_err_msg
137  RETURN
138 
139  100 WRITE(err_msg, 1100) m1, n1, sa1, m2, n2, sa2
140  CALL flush_err_msg(abort=.true.)
141 
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.')
146 
147  END SUBROUTINE checkduplicatealiases
148 
149 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
150 ! Function name: checkSpeciesInc() !
151 ! !
152 ! Purpose: Loop through the species.inc file and verify that the !
153 ! match those provided in the datafile. !
154 ! !
155 ! Variables referenced: None !
156 ! !
157 ! Variables modified: None !
158 ! !
159 ! Local variables: None !
160 ! !
161 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
162  SUBROUTINE checkspeciesinc(lNg, SA_g, lMMx, lNs, SA_s, &
163  lnrxn, lrnames, lnrxn_des, lrnames_des)
165  use run, only: reinitializing
166  use error_manager
167  use toleranc
168  USE utilities, ONLY: blank_line, seek_comment
169 
170  IMPLICIT NONE
171 
172 ! Number of gas speices
173  INTEGER, INTENT(IN) :: lNg
174 ! Gas phase species aliases
175  CHARACTER(len=32), DIMENSION(DIM_N_g), INTENT(IN) :: SA_g
176 ! Number of solids phases
177  INTEGER, INTENT(IN) :: lMMx
178 ! Number of species in each solids phase.
179  INTEGER, DIMENSION(DIM_M), INTENT(IN) :: lNs
180 ! Solids phase speices aliases.
181  CHARACTER(len=32), DIMENSION(DIM_M, DIM_N_s), INTENT(IN) :: SA_s
182 ! Number of reactions
183  INTEGER, INTENT(IN) :: lNRxn
184 ! Reaction Names (aliases)
185  CHARACTER(len=32), INTENT(IN) :: lRNames(dimension_rxn)
186 ! Number of discrete reactions
187  INTEGER, INTENT(IN) :: lNRxn_DES
188 ! Reaction Names for discrete solids (aliases)
189  CHARACTER(len=32), INTENT(IN) :: lRNames_DES(dimension_rxn)
190 
191 ! Input/Output status.
192  INTEGER :: IOS
193 ! File unit.
194  INTEGER, PARAMETER :: FUNIT = 167
195 ! Full path to Burcat and Ruscic database
196  CHARACTER(len=255) :: FILENAME
197  CHARACTER(len=128) :: INPUT
198 ! Loop counters
199  INTEGER :: SRC, M
200 ! Position of interest in string.
201  INTEGER :: POS
202 ! Index from species.inc file.
203  INTEGER :: lIndex
204  CHARACTER(len=64) :: lName
205  CHARACTER(len=32) :: tName
206 ! Length of noncomment string
207  INTEGER :: LINE_LEN
208 
209  CALL init_err_msg("RXN_COM --> checkDuplicateAliases")
210 
211  src = 0
212 
213 ! Loop over possible locations .
214  src_lp: DO
215  src = src + 1
216  SELECT CASE(src)
217 
218 ! Check the local run directory.
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
222  IF(.NOT.reinitializing)THEN
223  WRITE(err_msg, 1000)'species.inc'
224  CALL flush_err_msg(header=.false., footer=.false.)
225  ENDIF
226 
227  1000 FORMAT(/2x,'Verifying reaction aliases in ',a)
228 
229 ! No species.inc file was located.
230  CASE DEFAULT
231  IF(.NOT.reinitializing)THEN
232  WRITE(err_msg, 1004)
233  CALL flush_err_msg
234  ENDIF
235  EXIT src_lp
236  END SELECT
237 
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.')
241 
242  rewind(funit)
243  read_lp: DO
244  READ(funit,"(A)",iostat=ios) input
245 
246 ! This is a sanity check because the species.inc file is generated by
247 ! make_mfix and therefore should be the correct format.
248  IF(ios > 0) THEN
249  WRITE(err_msg,1200) trim(adjustl(filename))
250  CALL flush_err_msg(abort=.true.)
251  1200 FORMAT('Error 1200: There was a problem reading file: ',a)
252 
253 ! All entries have been processed.
254  ELSEIF(ios<0)THEN
255  EXIT src_lp
256  ENDIF
257 
258 ! Clean up the input.
259  line_len = seek_comment(input,len(input)) - 1
260  CALL remove_comment(input, line_len + 1, len(input))
261  CALL make_upper_case(input, line_len)
262  CALL replace_tab(input, line_len)
263 
264 ! Skip empty entires.
265  IF(line_len <= 0) cycle read_lp
266  IF(blank_line(input)) cycle read_lp
267 
268  pos = index(input,"INTEGER, PARAMETER ::")
269  IF(pos /= 0) THEN
270  input = input((pos + 21):)
271  ELSE
272  cycle read_lp
273  ENDIF
274 
275 ! We only want to process lines that have = as the other are coments.
276  pos = index(input,"=")
277  IF(pos == 0) cycle read_lp
278 
279 ! Store the species alias.
280  WRITE(lname,"(A)") trim(adjustl(input(:(pos-1))))
281 
282 ! Convert the read index from string to integer. Report any errors.
283  READ(input((pos+1):),*,iostat=ios) lindex
284  IF(ios /= 0) THEN
285  WRITE(err_msg,1205) 'index', trim(input)
286  CALL flush_err_msg(abort=.true.)
287  ENDIF
288 
289  1205 FORMAT('Error 1205: Unable to obtain alias index from species.', &
290  'inc file.',//' INPUT: ',a)
291 
292 ! Match against what was provided in the datafile:
293 ! Gas phase species aliases.
294  IF(lindex <= lng) THEN
295  tname = sa_g(lindex)
296  IF(comparealiases(tname, lname)) cycle read_lp
297  ENDIF
298 
299 ! Solids phase species aliases.
300  DO m = 1, lmmx
301  IF(lindex <= lns(m))THEN
302  tname = sa_s(m, lindex)
303  IF(comparealiases(tname, lname)) cycle read_lp
304  ENDIF
305  ENDDO
306 
307 ! Reaction Names
308  IF(lindex <= lnrxn)THEN
309  tname = lrnames(lindex)
310  IF(comparealiases(tname, lname)) cycle read_lp
311  ENDIF
312 
313 ! Reaction Names for discrete solids
314  IF(lindex <= lnrxn_des)THEN
315  tname = lrnames_des(lindex)
316  IF(comparealiases(tname, lname)) cycle read_lp
317  ENDIF
318 
319  WRITE(err_msg,1300) trim(lname), lindex
320  CALL flush_err_msg
321 
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.')
328 
329  ENDDO read_lp
330  ENDDO src_lp
331 
332  CLOSE(funit)
333  CALL finl_err_msg
334  RETURN
335 
336  END SUBROUTINE checkspeciesinc
337 
338 
339 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
340 ! Function name: compareAlaises() !
341 ! !
342 ! Purpose: !
343 ! !
344 ! Variables referenced: None !
345 ! !
346 ! Variables modified: None !
347 ! !
348 ! Local variables: None !
349 ! !
350 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
351  LOGICAL FUNCTION comparealiases(lS1, lS2, N1, N2)
353  IMPLICIT NONE
354 
355  CHARACTER(len=*), INTENT(IN) :: lS1, lS2
356 
357  INTEGER, OPTIONAL, INTENT(IN) :: N1, N2
358 
359  CALL make_upper_case (ls1, len(ls1))
360  CALL make_upper_case (ls2, len(ls2))
361 
362  comparealiases = .false.
363  IF(trim(ls1) == trim(ls2)) comparealiases = .true.
364 
365  IF(.NOT.comparealiases) RETURN
366 
367  IF(PRESENT(n1) .AND. PRESENT(n2)) THEN
368  IF(n1 == n2) THEN
369  comparealiases = .true.
370  ELSE
371  comparealiases = .false.
372  ENDIF
373  ENDIF
374 
375  RETURN
376  END FUNCTION comparealiases
377 
378 
379 
380 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
381 ! Subroutine: WRITE_RXN_SUMMARY !
382 ! !
383 ! Purpose: !
384 ! !
385 ! Variables referenced: None !
386 ! !
387 ! Variables modified: None !
388 ! !
389 ! Local variables: None !
390 ! !
391 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
392  SUBROUTINE write_rxn_summary(RxN, lSAg, lSAs, ABORT, fUNIT)
394  USE toleranc
395 
396  IMPLICIT NONE
397 
398 ! Data structure for storing reaction data.
399  TYPE(reaction_block), POINTER, INTENT(IN) :: RxN
400 
401 ! Gas phase species aliases
402  CHARACTER(len=32), DIMENSION(DIM_N_g), INTENT(IN) :: lSAg
403 ! Solids phase speices aliases.
404  CHARACTER(len=32), DIMENSION(DIM_M, DIM_N_s), INTENT(IN) :: lSAs
405 ! Flag to abort the run.
406  LOGICAL, INTENT(IN) :: ABORT
407 
408 ! Optional file unit.
409  INTEGER, OPTIONAL :: fUNIT
410 
411  CHARACTER(LEN=72) :: OUTPUT, full, divided, empty
412 
413  CHARACTER(LEN=32) :: lSP
414 
415  INTEGER lN, M, N
416  INTEGER lS, lE
417 
418  INTEGER UNIT_FLAG
419 
420  IF(present(funit)) THEN
421  unit_flag = funit
422  ELSE
423  unit_flag = -1
424  ENDIF
425 
426  empty = ' '
427  CALL write_rs0(empty, unit_flag)
428 
429  full = ''
430  WRITE(full,2000)
431 
432  divided = ''
433  WRITE(divided,2005)
434 
435 ! Lead bar
436  CALL write_rs0(full, unit_flag)
437 ! Reaction Nmae
438  output = ''
439  WRITE(output, 2001)trim(rxn%Name)
440  output(72:72) = '|'
441  CALL write_rs0(output, unit_flag)
442 
443 ! Row Divider
444  CALL write_rs0(full, unit_flag)
445 
446  output = ''
447  WRITE(output, 2002)trim(rxn%ChemEq(1:54))
448  output(72:72) = '|'
449  CALL write_rs0(output, unit_flag)
450 
451  CALL write_rs0(full, unit_flag)
452 
453  IF(rxn%nSpecies > 0) THEN
454 
455  output = ''
456  WRITE(output, 2007)trim(rxn%Classification)
457  output(72:72) = '|'
458  CALL write_rs0(output, unit_flag)
459 ! Row Divider
460  CALL write_rs0(full, unit_flag)
461 
462  WRITE(output,2003); CALL write_rs0(output, unit_flag)
463  WRITE(output,2004); CALL write_rs0(output, unit_flag)
464  CALL write_rs0(divided, unit_flag)
465  ENDIF
466 
467 
468  DO ln = 1, rxn%nSpecies
469 
470  m = rxn%Species(ln)%pMap
471  n = rxn%Species(ln)%sMap
472 
473  WRITE(output,2006)
474 
475  IF(m == 0) THEN
476  IF(len_trim(lsag(n)) > 8) THEN
477  lsp = lsag(n)
478  output(5:13) = lsp(1:8)
479  ELSE
480  ls = (9-int(len_trim(lsag(n))/2))
481  le = ls + len_trim(lsag(n))
482  output(ls:le) = trim(lsag(n))
483  ENDIF
484  WRITE(output(32:35),"(A)") 'Gas'
485  ELSE
486  IF(len_trim(lsas(m,n)) > 8) THEN
487  lsp = lsas(m,n)
488  output(5:13) = lsp(1:8)
489  ELSE
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))
493  ENDIF
494  WRITE(output(30:36),"(A,I2)") 'Solid',m
495  ENDIF
496  WRITE(output(43:44),"(I2)") n
497  WRITE(output(51:60),"(F9.4)") rxn%Species(ln)%MW
498 
499  IF(compare(rxn%Species(ln)%Coeff, zero)) THEN
500  WRITE(output(17:26),"(F9.4)") zero
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'
505  ELSE
506  WRITE(output(17:26),"(F9.4)") rxn%Species(ln)%Coeff
507  WRITE(output(63:70),"(A)") 'Product'
508  ENDIF
509  CALL write_rs0(output, unit_flag)
510  CALL write_rs0(divided, unit_flag)
511 
512  ENDDO
513 
514  CALL write_rs0(empty, unit_flag)
515 
516  IF(abort) CALL mfix_exit(mype)
517  RETURN
518 
519 
520  2000 FORMAT(2x,'|',68('-'),'|')
521 
522  2001 FORMAT(2x,'| Name: ',a)
523  2002 FORMAT(2x,'| Chemical Eq: ',a)
524 
525  2003 FORMAT(' | Species | Stoich | | Species |', &
526  ' Molecular | |')
527 
528  2004 FORMAT(' | Alias | Coeff. | Phase | Index |', &
529  ' Weight | Type |')
530 
531 
532  2005 FORMAT(2x,'|',10('-'),'|',13('-'),'|',9('-'),'|',9('-'),'|', &
533  12('-'),'|',10('-'),'|')
534 
535  2006 FORMAT(2x,'|',10(' '),'|',13(' '),'|',9(' '),'|',9(' '),'|', &
536  12(' '),'|',10(' '),'|')
537 
538 
539  2007 FORMAT(2x,'| Classification: ',a)
540 
541  contains
542 
543 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
544 ! Subroutine: WRITE_RS0 !
545 ! !
546 ! Purpose: !
547 ! !
548 ! Variables referenced: None !
549 ! !
550 ! Variables modified: None !
551 ! !
552 ! Local variables: None !
553 ! !
554 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
555  SUBROUTINE write_rs0(LINE, UFLAG)
557  use run, only: reinitializing
558  use error_manager
559 
560  IMPLICIT NONE
561 
562  CHARACTER(len=*), INTENT(IN) :: LINE
563  INTEGER, INTENT(IN) :: UFLAG
564 
565  CALL init_err_msg("WRITE_RXN_SUMMARY --> WRITE_RS0")
566 
567  IF(uflag == -1)THEN
568  IF(.NOT.reinitializing) THEN
569  WRITE(err_msg,*) line
570  CALL flush_err_msg(header=.false., footer=.false.)
571  ENDIF
572  ELSE
573  WRITE(uflag,*) line
574  ENDIF
575  CALL finl_err_msg
576 
577  RETURN
578  END SUBROUTINE write_rs0
579  END SUBROUTINE write_rxn_summary
580 
581 
582 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
583 ! Subroutine: checkThermoReqs !
584 ! !
585 ! Purpose: !
586 ! !
587 ! Variables referenced: None !
588 ! !
589 ! Variables modified: None !
590 ! !
591 ! Local variables: None !
592 ! !
593 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
594  SUBROUTINE checkthermoreqs(RxN, S_g, S_s, rDB, MWg, MWs, Cpg0, Cps0)
596  use error_manager
597  use toleranc
598 
599  IMPLICIT NONE
600 
601 ! Data structure for storing reaction data.
602  TYPE(reaction_block), POINTER, INTENT(INOUT) :: RxN
603 
604  CHARACTER(len=18), INTENT(IN) :: S_g(dim_n_g)
605  CHARACTER(len=18), INTENT(in) :: S_s(dim_m, dim_n_s)
606  LOGICAL, INTENT(inout) :: rDB(0:dim_m, 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)
610  DOUBLE PRECISION, INTENT(inout) :: MWs(dim_m, dim_n_s)
611 
612  LOGICAL :: CP_FATAL
613  LOGICAL :: CHECK_DATABASE
614 
615  INTEGER :: M, N, lN
616 
617 
618  CALL init_err_msg("RXN_COM --> checkThermoReqs")
619 
620  check_database = .false.
621  cp_fatal = .false.
622 
623 ! Verify that the molecular weights and stoichiometry are consistent and
624 ! determine interphase mass exchanges.
625  DO ln = 1, rxn%nSpecies
626  m = rxn%Species(ln)%pMap
627  n = rxn%Species(ln)%sMap
628  IF(m == 0) THEN
629  IF(cpg0 /= undefined) THEN
630  cp_fatal = .true.
631  ELSEIF((rxn%Calc_DH .AND. .NOT.rdb(m,n)) .OR. &
632  (mwg(n) == undefined)) THEN
633  check_database = .true.
634  ENDIF
635  ELSE
636  IF(cps0(m) /= undefined) THEN
637  cp_fatal = .true.
638  ELSEIF((rxn%Calc_DH .AND. .NOT.rdb(m,n)) .OR. &
639  (mws(m,n) == undefined)) THEN
640  check_database = .true.
641  ENDIF
642  ENDIF
643  ENDDO
644 
645 ! Report errors and messages.
646  IF(cp_fatal) THEN
647 
648  WRITE(err_msg, 1100) trim(rxn%Name)
649  CALL flush_err_msg(abort=.true.)
650 
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.')
655 
656  ELSEIF(check_database) THEN
657 
658  WRITE(err_msg, 1101) trim(rxn%Name)
659  CALL flush_err_msg
660 
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 ', &
664  'necessary data.')
665 
666  ENDIF
667 
668  IF(check_database) THEN
669  WRITE(err_msg, 1200)
670  CALL flush_err_msg(footer=.false.)
671  ENDIF
672 
673  1200 FORMAT('Message 1200: Searching thermochemical databases for ',&
674  'species data.',/' ')
675 
676  DO ln = 1, rxn%nSpecies
677  m = rxn%Species(ln)%pMap
678  n = rxn%Species(ln)%sMap
679  IF(m == 0) THEN
680  IF((rxn%Calc_DH .AND. .NOT.rdb(m,n)) .OR. &
681  (mwg(n) == undefined)) THEN
682 ! Notify the user of the reason the thermochemical database is used.
683 ! Flag that the species name is not provided.
684  IF(s_g(n) == undefined_c) THEN
685  WRITE(err_msg,1000) trim(ivar('SPECIES_g',n))
686  CALL flush_err_msg(abort=.true.)
687  ENDIF
688 
689 ! Update the log files.
690  WRITE(err_msg, 3001) n, trim(s_g(n))
691  CALL flush_err_msg(header=.false., footer=.false.)
692 ! Read the database.
693  CALL read_database(0, n, s_g(n), mwg(n))
694 ! Flag variable to stating that the database was read.
695  rdb(0,n) = .true.
696  ENDIF
697  rxn%Species(ln)%MW = mwg(n)
698  ELSE
699  IF((rxn%Calc_DH .AND. .NOT.rdb(m,n)) .OR. &
700  (mws(m,n) == undefined)) THEN
701 
702 ! Flag that the species name is not provided.
703  IF(s_s(m,n) == undefined_c) THEN
704  WRITE(err_msg,1000) trim(ivar('SPECIES_s',m,n))
705  CALL flush_err_msg(abort=.true.)
706  ENDIF
707 ! Update the log files.
708  WRITE(err_msg, 3001) n, trim(s_s(m,n))
709  CALL flush_err_msg(header=.false., footer=.false.)
710  CALL read_database(m,n,s_s(m,n),mws(m,n))
711 ! Flag variable to stating that the database was read.
712  rdb(m,n) = .true.
713  ENDIF
714  rxn%Species(ln)%MW = mws(m,n)
715  ENDIF
716  ENDDO
717 ! Finalize the error message.
718  IF(check_database) CALL flush_err_msg(header=.false.)
719 
720  3001 FORMAT(/2x,'>',i3,': Species: ',a)
721 
722  CALL finl_err_msg
723 
724  RETURN
725 
726  1000 FORMAT('Error 1000: Required input not specified: ',a,/'Please ',&
727  'correct the mfix.dat file.')
728 
729  END SUBROUTINE checkthermoreqs
730 
731 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
732 ! Subroutine: checkMassBalance !
733 ! !
734 ! Purpose: !
735 ! !
736 ! Variables referenced: None !
737 ! !
738 ! Variables modified: None !
739 ! !
740 ! Local variables: None !
741 ! !
742 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
743  SUBROUTINE checkmassbalance(CALLER, RxN, lnMT, IER)
745  USE toleranc
746 
747  IMPLICIT NONE
748 
749  CHARACTER(len=*), INTENT(IN) :: CALLER
750 
751 ! Data structure for storing reaction data.
752  TYPE(reaction_block), POINTER, INTENT(INOUT) :: RxN
753 
754  DOUBLE PRECISION, INTENT(OUT) :: lnMT(0:dim_m)
755  INTEGER, INTENT(OUT) :: IER
756 
757  INTEGER M, N, lN ! Phase, Species
758  DOUBLE PRECISION rSUM, pSUM
759  DOUBLE PRECISION MWxStoich
760 
761  INTEGER sprCount, sprIndex
762 
763  DOUBLE PRECISION, PARAMETER :: massBalanceTol = 1.0d-3
764 
765 ! Initialize variables
766  ier = 0
767  rsum = zero
768  psum = zero
769  lnmt(:) = zero
770  sprcount = 0
771 
772 ! Verify that the molecular weights and stoichiometry are consistent and
773 ! determine interphase mass exchanges.
774  DO ln = 1, rxn%nSpecies
775  m = rxn%Species(ln)%pMap
776  n = rxn%Species(ln)%sMap
777 
778 ! Multiply the molecular weight and stoichiometric coefficient.
779  mwxstoich = rxn%Species(ln)%MW * rxn%Species(ln)%Coeff
780  rxn%Species(ln)%MWxStoich = mwxstoich
781 ! Calculate the net mass transfer for phase M.
782 ! 0 : no interphase mass transfder
783 ! >0 : gains mass from anther phase
784 ! <0 : transfers mass to anther phase
785  lnmt(m) = lnmt(m) + mwxstoich
786 ! Calculate mass of reactants and products. Used to ensure mass balance.
787  IF(mwxstoich < zero) THEN
788  rsum = rsum - mwxstoich
789  IF(m /= 0) THEN
790  sprcount = sprcount + 1
791  IF(sprcount == 1) THEN
792  sprindex = m
793 ! Verify that there is at most one solids phase fule (reactant).
794  ELSEIF( m /= sprindex) THEN
795  IF(dmp_log) THEN
796  WRITE(*,1002) trim(caller), trim(rxn%Name)
797  WRITE(unit_log,1002) trim(caller), trim(rxn%Name)
798  ier = 1
799  ENDIF
800  ENDIF
801  ENDIF
802  ELSE
803  psum = psum + mwxstoich
804  ENDIF
805  ENDDO
806 ! Verify that the mass of products equals reactants: (Mass Balance)
807  IF (.NOT.compare(rsum,psum)) THEN
808  IF(dmp_log) THEN
809  WRITE(*,1001) trim(caller), trim(rxn%Name), rsum, psum
810  WRITE(unit_log,1001) trim(caller), trim(rxn%Name), rsum,psum
811  ier = 1
812  ENDIF
813  ENDIF
814 
815  RETURN
816 
817 ! Error Messages
818 !---------------------------------------------------------------------//
819 
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,/ &
824  1x,70('*')/)
825 
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, &
830  '.',/1x,70('*')/)
831 
832  END SUBROUTINE checkmassbalance
833 
834 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
835 ! Subroutine: calcInterphaseTxfr !
836 ! !
837 ! Purpose: !
838 ! !
839 ! Variables referenced: None !
840 ! !
841 ! Variables modified: None !
842 ! !
843 ! Local variables: None !
844 ! !
845 !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
846  SUBROUTINE calcinterphasetxfr(CALLER, RxN, lnMT, lEEq, lSEq, &
847  lsag, lmmx, lsas)
849  USE exit, only: mfix_exit
850  USE toleranc
851 
852  IMPLICIT NONE
853 
854  CHARACTER(len=*), INTENT(IN) :: CALLER
855 
856 ! Data structure for storing reaction data.
857  TYPE(reaction_block), POINTER, INTENT(INOUT) :: RxN
858 
859  DOUBLE PRECISION, INTENT(IN) :: lnMT(0:dim_m)
860 ! Energy equation flag
861  LOGICAL, INTENT(IN) :: lEEq
862 ! Gas/Solids Species Eq Flag
863  LOGICAL, INTENT(IN) :: lSEq(0:dim_m)
864 ! Gas phase species aliases
865  CHARACTER(len=32), DIMENSION(DIM_N_g), INTENT(IN) :: lSAg
866 ! Number of solids phases
867  INTEGER, INTENT(IN) :: lMMx
868 ! Solids phase speices aliases.
869  CHARACTER(len=32), DIMENSION(DIM_M, DIM_N_s), INTENT(IN) :: lSAs
870 
871  INTEGER toPhase, toPhaseCount, mCount
872  INTEGER fromPhase, fromPhaseCount
873  INTEGER catPhase
874 
875  INTEGER M, MM, LL
876  INTEGER lM, lN
877 
878  DOUBLE PRECISION, PARAMETER :: massBalanceTol = 1.0d-3
879 
880 ! Initialize interphase exchange terms.
881  IF(Allocated(rxn%rPhase)) rxn%rPhase(:) = zero
882 
883 ! If there is only one phase referenced by the reaction, there there
884 ! should be no interphase mass transfer.
885  IF(rxn%nPhases == 1) THEN
886 ! Interphase mass transfer is set to zero. Small inconsistencies with
887 ! molecular weights can result in a non-zero value for homogeneous
888 ! reactions. Presumably, the mass balance check caught any major errors.
889  rxn%rPhase(:) = zero
890 ! Void interphase transfer flags.
891  DO ln = 1, rxn%nSpecies
892  m = rxn%Species(ln)%pMap
893  rxn%Species(ln)%mXfr = m
894  ENDDO
895  rxn%Classification = "Homogeneous"
896 ! This is a multiphase reaction.
897  ELSE
898 ! Initialize.
899  tophasecount = 0
900  fromphasecount = 0
901  DO m = 0, lmmx
902 ! Determine the number of phases with a net mass gain. Record the index
903 ! of the last phase with a net mass gain.
904  IF (lnmt(m) > massbalancetol) THEN
905  tophasecount = tophasecount + 1
906  tophase = m
907 ! Determine the number of phases with a net mass loss. Record the index
908 ! index of the last phase with a net mass loss.
909  ELSEIF(lnmt(m) < -massbalancetol) THEN
910  fromphasecount = fromphasecount + 1
911  fromphase = m
912  ENDIF
913  ENDDO
914 
915 ! Only one phase has a net mass gain.
916  IF(tophasecount == 1) THEN
917 ! Interphase mass transfer flag.
918  rxn%Classification = "Heterogeneous"
919  DO m = 0, lmmx
920  IF(m /= tophase) THEN
921  IF (tophase < m) THEN
922  lm = 1 + tophase + ((m-1)*m)/2
923  rxn%rPhase(lm) = -lnmt(m)
924  ELSE
925  lm = 1 + m + ((tophase-1)*tophase)/2
926  rxn%rPhase(lm) = lnmt(m)
927  ENDIF
928 
929 ! Verify that if one phase's species equations are solved, that the
930 ! other phase's species equations are solved.
931 
932  IF(abs(rxn%rPhase(lm)) > small_number) THEN
933  IF((lseq(tophase) .AND. .NOT.lseq(m)) .OR. &
934  (.NOT.lseq(tophase) .AND. lseq(m))) THEN
935  IF(dmp_log) THEN
936  WRITE(*,1001) trim(caller)
937  WRITE(unit_log,1001) trim(caller)
938  IF(lseq(m)) THEN
939  WRITE(*,1101) m, 'Solving'
940  WRITE(*,1101) tophase, 'Not Solving'
941  WRITE(unit_log,1101) m, 'Solving'
942  WRITE(unit_log,1101) tophase, &
943  'Not Solving'
944  ELSE
945  WRITE(*,1101) tophase, 'Solving'
946  WRITE(*,1101) m, 'Not Solving'
947  WRITE(unit_log,1101) m, 'Solving'
948  WRITE(unit_log,1101) tophase, &
949  'Not Solving'
950  ENDIF
951  WRITE(*,1000)
952  WRITE(unit_log,1000)
953  ENDIF
954  CALL write_rxn_summary(rxn, lsag(:), &
955  lsas(:,:), .true.)
956  ENDIF
957  ENDIF
958  ENDIF
959  ENDDO
960 
961 ! Set flags for enthalpy transfer associated with mass transfer.
962  IF(leeq .AND. rxn%Calc_DH) THEN
963  DO ln = 1, rxn%nSpecies
964  m = rxn%Species(ln)%pMap
965 ! The gas phase is referenced by the reaction.
966  IF(m == 0) THEN
967 ! The gas phase is the destination phase.
968  IF(tophase == 0) THEN
969 ! Counter for the number of solids phases transfering mass to the
970 ! gas phase.
971  mcount = 0
972 ! Check to see if phase M transfer mass to another solids phase.
973  DO mm = 1, lmmx
974  lm = 1 + (mm-1)*mm/2
975 ! Mass transfer occurs between the gas and solids phase MM.
976  IF(rxn%rPhase(lm) > 0) THEN
977 ! Indicate that phase MM receives mass from phase M.
978  rxn%Species(ln)%mXfr = mm
979 ! The fraction of material transfered from phase 0 to phase MM.
980 ! This variable is not currently used for gas/solids reactions.
981  rxn%Species(ln)%xXfr = zero
982 ! Increment the number of phases the gas receives mass from.
983  mcount = mcount + 1
984  ENDIF
985  ENDDO
986  IF(mcount /= 1) THEN
987  IF(dmp_log) THEN
988  WRITE(*,1002) trim(caller), &
989  trim(rxn%ChemEq)
990  WRITE(*,1000)
991  WRITE(unit_log,1002) trim(caller), &
992  trim(rxn%ChemEq)
993  WRITE(unit_log,1000)
994  ENDIF
995  CALL write_rxn_summary(rxn, lsag(:), &
996  lsas(:,:), .true.)
997  ENDIF
998 
999 ! A solids phase is the destination phase.
1000  ELSE
1001 ! Since only one phase was detected with a net mass gain and the gas
1002 ! phase was detected as a source phase, then all the gas is assigned
1003 ! to the destination phase.
1004  rxn%Species(ln)%mXfr = tophase
1005 ! This variable is not used for gas/solids reactions.
1006  rxn%Species(ln)%xXfr = zero
1007  ENDIF
1008 ! Solids/Solids mass transfer: Enthalpy transfer from mass transfer is
1009 ! only calculated from source phase reactants.
1010  ELSE
1011 ! Check to see if phase M transfer mass to another solids phase.
1012  DO ll = 1, lmmx-1
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
1017 ! Mass transfer occurs between solids phases M and MM, and phase M
1018 ! is the source phase.
1019  IF( m == ll .AND. &
1020  rxn%rPhase(lm) < zero) THEN
1021 ! Indicate that phase MM receives mass from phase M.
1022  rxn%Species(ln)%mXfr = mm
1023 ! Calculate the fraction of material consumed from phase M is transfered
1024 ! to phase MM.
1025  rxn%Species(ln)%xXfr = &
1026  abs(lnmt(mm) / lnmt(ll))
1027 ! Mass transfer occurs between solids phases M and LL, and phase M
1028 ! is the source phase.
1029  ELSEIF( m == mm .AND. &
1030  rxn%rPhase(lm) > zero) THEN
1031 ! Indicate that phase LL receives mass from phase M.
1032  rxn%Species(ln)%mXfr = ll
1033 ! Calculate the fraction of material consumed from phase M is transfered
1034 ! to phase LL.
1035  rxn%Species(ln)%xXfr = &
1036  abs(lnmt(ll) / lnmt(mm))
1037  ENDIF
1038  ENDDO
1039  ENDDO
1040  ENDIF ! Gas or Solids phase.
1041  ENDDO ! Species Loop
1042  ENDIF ! Energy Equation
1043 ! If there is only one phase with a net mass loss, setup the array for
1044 ! interphase mass transfer.
1045  ELSEIF(fromphasecount == 1) THEN
1046  rxn%Classification = "Heterogeneous"
1047  DO m = 0, lmmx
1048  IF (m /= fromphase) THEN
1049  IF(m < fromphase) THEN
1050  lm = 1 + m + ((fromphase-1)*fromphase)/2
1051  rxn%rPhase(lm) = lnmt(m)
1052  ELSE
1053  lm = 1 + fromphase + ((m-1)*m)/2
1054  rxn%rPhase(lm) = -lnmt(m)
1055  ENDIF
1056 
1057 ! Verify that if one phase's species equations are solved, that the
1058 ! other phase's species equations are solved.
1059  IF(abs(rxn%rPhase(lm)) > small_number) THEN
1060  IF((lseq(fromphase) .AND. .NOT.lseq(m)) .OR. &
1061  (.NOT.lseq(fromphase) .AND. lseq(m))) THEN
1062  IF(dmp_log) THEN
1063  WRITE(*,1001) trim(caller)
1064  WRITE(unit_log,1001) trim(caller)
1065  IF(lseq(m)) THEN
1066  WRITE(*,1101) m, 'Solving'
1067  WRITE(*,1101) fromphase, 'Not Solving'
1068  WRITE(unit_log,1101) m, 'Solving'
1069  WRITE(unit_log,1101) fromphase, &
1070  'Not Solving'
1071  ELSE
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'
1076  ENDIF
1077  WRITE(*,1000)
1078  WRITE(unit_log,1000)
1079  ENDIF
1080  CALL write_rxn_summary(rxn, lsag(:), &
1081  lsas(:,:), .true.)
1082  ENDIF
1083  ENDIF
1084  ENDIF
1085  END DO
1086 
1087 ! Set flags for enthalpy transfer associated with mass transfer.
1088  IF(leeq .AND. rxn%Calc_DH) THEN
1089  DO ln = 1, rxn%nSpecies
1090  m = rxn%Species(ln)%pMap
1091 ! Gas/solids reaction: Enthalpy transfer from mass transfer is only
1092 ! calculated from gas phase species.
1093  IF(m == 0) THEN
1094 ! Gas phase is the source phase.
1095  IF(fromphase == 0) THEN
1096 ! Counter for the number of solids phases transfering mass to the
1097 ! gas phase.
1098  mcount = 0
1099 ! Check to see if phase M transfer mass to another solids phase.
1100  DO mm = 1, lmmx
1101  lm = 1 + (mm-1)*mm/2
1102 ! Mass transfer occurs between the gas and solids phases MM.
1103  IF(rxn%rPhase(lm) < 0) THEN
1104 ! Indicate that phase MM receives mass from phase M.
1105  rxn%Species(ln)%mXfr = mm
1106 ! The fraction of material transfered from phase 0 to phase MM.
1107 ! This variable is not currently used for gas/solids reactions.
1108  rxn%Species(ln)%xXfr = zero
1109 ! Increment the number of phases the gas receives mass from.
1110  mcount = mcount + 1
1111  ENDIF
1112  ENDDO
1113  IF(mcount /=1 ) THEN
1114  IF(dmp_log) THEN
1115  WRITE(*,1002) trim(caller), &
1116  trim(rxn%ChemEq)
1117  WRITE(*,1000)
1118  WRITE(unit_log,1002) trim(caller), &
1119  trim(rxn%ChemEq)
1120  WRITE(unit_log,1000)
1121  ENDIF
1122  CALL write_rxn_summary(rxn, lsag(:), &
1123  lsas(:,:), .true.)
1124  ENDIF
1125  ELSE
1126 ! There can be only one solids phase fuel. Store the phase of the
1127 ! solids phase reactant.
1128  rxn%Species(ln)%mXfr = fromphase
1129 ! Mass fraction of transfered material.
1130 ! This variable is not currently used for gas/solids reactions.
1131  rxn%Species(ln)%xXfr = zero
1132  ENDIF
1133 ! Solids/Solids mass transfer: Enthalpy transfer from mass transfer is
1134 ! only calculated from source phase reactants.
1135  ELSE
1136 ! Check to see if phase M transfer mass to another solids phase.
1137  DO ll = 1, lmmx-1
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
1142 ! Mass transfer occurs between solids phases M and MM, and phase M
1143 ! is the source phase.
1144  IF( m == ll .AND. &
1145  rxn%rPhase(lm) < zero) THEN
1146 ! Indicate that phase MM receives mass from phase M.
1147  rxn%Species(ln)%mXfr = mm
1148 ! Calculate the fraction of material consumed from phase M is transfered
1149 ! to phase MM.
1150  rxn%Species(ln)%xXfr = &
1151  abs(lnmt(mm) / lnmt(ll))
1152 ! Mass transfer occurs between solids phases M and LL, and phase M
1153 ! is the source phase.
1154  ELSEIF( m == mm .AND. &
1155  rxn%rPhase(lm) > zero) THEN
1156 ! Indicate that phase LL receives mass from phase M.
1157  rxn%Species(ln)%mXfr = ll
1158 ! Calculate the fraction of material consumed from phase M is transfered
1159 ! to phase LL.
1160  rxn%Species(ln)%xXfr = &
1161  abs(lnmt(ll) / lnmt(mm))
1162  ENDIF
1163  ENDDO
1164  ENDDO
1165  ENDIF ! Gas or Solids phase.
1166  ENDDO ! Species Loop
1167  ENDIF ! Energy Equation
1168 
1169 ! If there are no phases with a net mass gain/loss, check to see if
1170 ! the reaction is turned off.
1171  ELSEIF(tophasecount == 0 .AND. fromphasecount == 0) THEN
1172 ! If the reaction is active, and there is no interphase mass transfer,
1173 ! classify the reaction as catalytic.
1174  IF(rxn%nPhases > 0) rxn%Classification = "Catalytic"
1175  rxn%rPhase(:) = zero
1176 ! Set flags for enthalpy transfer associated with mass transfer.
1177  IF(leeq .AND. rxn%Calc_DH) THEN
1178 
1179 ! Identify the catalyst phase.
1180  catphase = -1
1181  DO ln= 1, rxn%nSpecies
1182  IF(compare(rxn%Species(ln)%Coeff,zero)) THEN
1183  IF(catphase /= -1) THEN
1184  IF(catphase /= rxn%Species(ln)%pMap) THEN
1185  IF(dmp_log) THEN
1186  WRITE(*,1002) trim(caller), &
1187  trim(rxn%Name)
1188  WRITE(*,1000)
1189  WRITE(unit_log,1002) trim(caller), &
1190  trim(rxn%Name)
1191  WRITE(unit_log,1000)
1192  ENDIF
1193  CALL write_rxn_summary(rxn, lsag(:), &
1194  lsas(:,:), .true.)
1195  ENDIF
1196  ELSE
1197  catphase = rxn%Species(ln)%pMap
1198  ENDIF
1199  ENDIF
1200  ENDDO
1201 ! Verify that a catalyst phase was found.
1202  IF(catphase == -1) THEN
1203  IF(dmp_log) THEN
1204  WRITE(*,1003) trim(caller), 'catalyst', &
1205  trim(rxn%Name)
1206  WRITE(*,1000)
1207  WRITE(unit_log,1003) trim(caller), &
1208  'catalyst', trim(rxn%Name)
1209  WRITE(unit_log,1000)
1210  ENDIF
1211  CALL write_rxn_summary(rxn, lsag(:), &
1212  lsas(:,:), .true.)
1213  ENDIF
1214 
1215 ! Identify the reactant phase.
1216  tophase = -1
1217  DO ln = 1, rxn%nSpecies
1218  IF(.NOT.compare(rxn%Species(ln)%Coeff,zero)) THEN
1219  IF(tophase /= -1) THEN
1220  IF(tophase /= rxn%Species(ln)%pMap) THEN
1221  IF(dmp_log) THEN
1222  WRITE(*,1002) trim(caller), &
1223  trim(rxn%Name)
1224  WRITE(*,1000)
1225  WRITE(unit_log,1002) trim(caller), &
1226  trim(rxn%Name)
1227  WRITE(unit_log,1000)
1228  ENDIF
1229  CALL write_rxn_summary(rxn, lsag(:), &
1230  lsas(:,:), .true.)
1231  ENDIF
1232  ELSE
1233  tophase = rxn%Species(ln)%pMap
1234  ENDIF
1235  ENDIF
1236  ENDDO
1237 ! Verify that a reacting phase was found.
1238  IF(tophase == -1) THEN
1239  IF(dmp_log) THEN
1240  WRITE(*,1003) trim(caller), 'reacting', &
1241  trim(rxn%Name)
1242  WRITE(*,1000)
1243  WRITE(unit_log,1003) trim(caller), 'reacting', &
1244  trim(rxn%Name)
1245  WRITE(unit_log,1000)
1246  ENDIF
1247  CALL write_rxn_summary(rxn, lsag(:), lsas(:,:),.true.)
1248  ENDIF
1249 
1250 ! Something when wrong.
1251  IF(catphase == tophase) THEN
1252  IF(dmp_log) THEN
1253  WRITE(*,1004) trim(caller), trim(rxn%Name)
1254  WRITE(*,1000)
1255  WRITE(unit_log,1004) trim(caller),trim(rxn%Name)
1256  WRITE(unit_log,1000)
1257  ENDIF
1258  CALL write_rxn_summary(rxn, lsag(:), lsas(:,:),.true.)
1259 !Gas/solid catalytic reaction:
1260  ELSEIF(tophase == 0) THEN
1261  DO ln = 1, rxn%nSpecies
1262  IF(rxn%Species(ln)%pMap == 0) THEN
1263 ! Indicate that phase MM receives mass from phase M.
1264  rxn%Species(ln)%mXfr = catphase
1265 ! The fraction of material transfered from phase 0 to phase MM.
1266 ! This variable is not currently used for gas/solids reactions.
1267  rxn%Species(ln)%xXfr = zero
1268  ENDIF
1269  ENDDO
1270  ELSEIF(catphase == 0) THEN
1271  DO ln = 1, rxn%nSpecies
1272  IF(rxn%Species(ln)%pMap == 0) THEN
1273 ! Indicate that phase MM receives mass from phase M.
1274  rxn%Species(ln)%mXfr = tophase
1275 ! The fraction of material transfered from phase 0 to phase MM.
1276 ! This variable is not currently used for gas/solids reactions.
1277  rxn%Species(ln)%xXfr = zero
1278  ENDIF
1279  ENDDO
1280  ENDIF
1281  ENDIF ! Energy Equation
1282  ELSE
1283 ! Two or more phases have a net mass loss and two or more phases have
1284 ! a net mass gain. Therefore, the interphase mass transfer cannot be
1285 ! concluded.
1286  CALL write_rxn_summary(rxn, lsag(:), lsas(:,:),.false.)
1287  WRITE(*,1002) trim(caller), trim(rxn%ChemEq)
1288  WRITE(*,1000)
1289  WRITE(unit_log,1002) trim(caller), trim(rxn%ChemEq)
1290  WRITE(unit_log,1000)
1291  CALL mfix_exit(mype)
1292  ENDIF
1293  ENDIF
1294 
1295  RETURN
1296 
1297 ! Error Messages
1298 !---------------------------------------------------------------------//
1299 
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('*')//)
1303 
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.',/)
1309 
1310  1101 FORMAT(' Phase ',i2,': ',a,' species equations.')
1311 
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')
1320 
1321  1003 FORMAT(//1x,70('*')/' From: ',a,' --> RXN_COM -->', &
1322  ' calcInterphaseTxfr',/' Error 1003: Unable to determine ',a, &
1323  ' phase for catalytic reaction'/1x,a,'.')
1324 
1325  1004 FORMAT(//1x,70('*')/' From: ',a,' --> RXN_COM -->', &
1326  ' calcInterphaseTxfr',/' Error 1004: Unable to distinguish', &
1327  ' catalyst phase from reacting phase',/' for catalytic', &
1328  ' reaction ',a,'.')
1329 
1330  END SUBROUTINE calcinterphasetxfr
1331 
1332 
1333 END MODULE rxn_com
integer, parameter dim_n_g
Definition: param_mod.f:69
logical dmp_log
Definition: funits_mod.f:6
character(len=32) function ivar(VAR, i1, i2, i3)
integer, parameter dimension_rxn
Definition: param_mod.f:55
subroutine finl_err_msg
logical function compare(V1, V2)
Definition: toleranc_mod.f:94
subroutine replace_tab(LINE_STRING, MAXCOL)
subroutine remove_comment(LINE, LSTART, MAXCOL)
integer, parameter dim_m
Definition: param_mod.f:67
double precision, parameter undefined
Definition: param1_mod.f:18
integer function seek_comment(LINE, MAXCOL)
subroutine init_err_msg(CALLER)
subroutine checkmassbalance(CALLER, RxN, lnMT, IER)
Definition: rxn_com_mod.f:744
subroutine write_rxn_summary(RxN, lSAg, lSAs, ABORT, fUNIT)
Definition: rxn_com_mod.f:393
subroutine mfix_exit(myID, normal_termination)
Definition: exit.f:5
subroutine calcinterphasetxfr(CALLER, RxN, lnMT, lEEq, lSEq, lSAg, lMMx, lSAs)
Definition: rxn_com_mod.f:848
double precision, parameter small_number
Definition: param1_mod.f:24
subroutine checkspeciesinc(lNg, SA_g, lMMx, lNs, SA_s, lNRxn, lRNames, lNRxn_DES, lRNames_DES)
Definition: rxn_com_mod.f:164
Definition: exit.f:2
integer, parameter unit_log
Definition: funits_mod.f:21
Definition: run_mod.f:13
Definition: param_mod.f:2
logical reinitializing
Definition: run_mod.f:208
integer mype
Definition: compar_mod.f:24
logical function comparealiases(lS1, lS2, N1, N2)
Definition: rxn_com_mod.f:352
subroutine checkduplicatealiases(lNg, SA_g, lMMx, lNs, SA_s)
Definition: rxn_com_mod.f:68
character(len=line_length), dimension(line_count) err_msg
integer, parameter dim_n_s
Definition: param_mod.f:71
subroutine read_database(lM, lN, lName, lMW)
Definition: read_database.f:22
Definition: coeff_mod.f:9
logical function blank_line(line)
subroutine make_upper_case(LINE_STRING, MAXCOL)
subroutine checkthermoreqs(RxN, S_g, S_s, rDB, MWg, MWs, Cpg0, Cps0)
Definition: rxn_com_mod.f:595
double precision, parameter zero
Definition: param1_mod.f:27
subroutine flush_err_msg(DEBUG, HEADER, FOOTER, ABORT, LOG, CALL_TREE)
subroutine write_rs0(LINE, UFLAG)
Definition: rxn_com_mod.f:556
character, parameter undefined_c
Definition: param1_mod.f:20