MFIX  2016-1
check_chemical_rxns.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2 ! !
3 ! Module name: CHECK_CHEMICAL_RXNS !
4 ! Author: J.Musser Date: 21-MAR-14 !
5 ! !
6 ! Purpose: Check chemical reactions specifications !
7 ! !
8 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
9  SUBROUTINE check_chemical_rxns
10 
11 ! User defined reaction names from reaction blocks @(RXNS)
12  use parse, only: rxn_name, des_rxn_name
13 
15  use parse, only: usrdh, des_usrdh
16  use parse, only: usrfdh, des_usrfdh
17 
18 
19 ! Number of continuum reactions and data object
20  use rxns, only: no_of_rxns, reaction
21 ! Number of discrete reactions and data object
22  use des_rxns, only: no_of_des_rxns, des_reaction
23 ! User specified species names and aliases:
24  use rxns, only: species_g, species_alias_g
25  use rxns, only: species_s, species_alias_s
26 
27 ! Number of continuum solids
28  use physprop, only: smax
29 ! Number of discrete solids
30  use discretelement, only: des_mmax
31 ! Number of species comprising each phase
32  use physprop, only: nmax
33 
34 !
35  use param1, only: undefined_i
36 
37  use rxn_com, only: checkspeciesinc
39 
40 
41  use error_manager
42 
43  IMPLICIT NONE
44 
45 ! Error flag
46  INTEGER :: IER
47 
48 ! Local representation of the number of solids phases.
49  INTEGER :: lMMAX
50 
51 ! Undefined indicates that no reaction block was found in the deck file.
52  IF(no_of_rxns == undefined_i) no_of_rxns = 0
54 
55 ! If there are no chemical reactions, then skip this routine.
56  IF(no_of_rxns + no_of_des_rxns == 0) RETURN
57 
58  CALL init_err_msg('CHECK_CHEMICAL_RXNS')
59 
60 ! Allocate the arrays as a work-around for Intel compiler with debug.
61  IF(no_of_rxns == 0) allocate(rxn_name(1))
62  IF(no_of_des_rxns == 0) allocate(des_rxn_name(1))
63 
64 ! Initialize the number of solids phases.
65  lmmax = smax + des_mmax
66 
67 ! Verify that the species aliases are unique.
68  CALL checkduplicatealiases(nmax(0), species_alias_g(:), &
69  lmmax, nmax(1:lmmax), species_alias_s(:,:))
70 
71 ! Verify that species aliases in the datafile match those in the
72 ! species.inc file.
73  CALL checkspeciesinc(nmax(0), species_alias_g(:), lmmax, &
74  nmax(1:lmmax), species_alias_s(:,:), no_of_rxns, rxn_name(:), &
75  no_of_des_rxns, des_rxn_name)
76 
77 
78  IF(no_of_rxns > 0) THEN
79  CALL check_chemical_rxns_common(no_of_rxns, rxn_name, &
80  rxn_chem_eq, usrdh, usrfdh, reaction)
81  ENDIF
82 
83  IF(no_of_des_rxns > 0) THEN
84  CALL check_chemical_rxns_common(no_of_des_rxns, des_rxn_name, &
85  des_rxn_chem_eq, des_usrdh, des_usrfdh, des_reaction)
86  ENDIF
87 
88  CALL finl_err_msg
89 
90  RETURN
91 
92  CONTAINS
93 
94 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
95 ! !
96 ! Module name: CHECK_CHEMICAL_RXNS_COMMON !
97 ! Author: J.Musser Date: 21-MAR-14 !
98 ! !
99 ! Purpose: Check chemical reactions specifications !
100 ! !
101 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
102  SUBROUTINE check_chemical_rxns_common(COUNT, NAME, CHEM_EQ, DH, &
103  fdh, rxn_array)
105 ! Runtime flags for solving energy and species equations.
106  use run, only: energy_eq, species_eq
107 ! Definition of derived data type
108  use rxn_com, only: reaction_block
109 ! User specified constant specific heats:
110  use physprop, only: c_pg0, c_ps0
111 ! Molecular weights:
112  use physprop, only: mw_g, mw_s
113 ! Flag marking when the thermochemical database is read.
114  use rxns, only: rdatabase
115 
116  use param, only: dim_m, dimension_rxn
117 
118 
119  use parse, only: setreaction
120  use rxn_com, only: checkthermoreqs
121  use rxn_com, only: checkmassbalance
122  use rxn_com, only: calcinterphasetxfr
123  use rxn_com, only: write_rxn_summary
124 
125 
126 
127  use error_manager
128 
129  IMPLICIT NONE
130 
131  INTEGER, INTENT(IN) :: COUNT
132 
133 ! Reaction Names from mfix.dat file:
134  CHARACTER(len=32), INTENT(IN) :: NAME(dimension_rxn)
135 ! Chemical equations:
136  CHARACTER(len=512), INTENT(IN) :: CHEM_EQ(dimension_rxn)
137 ! User defined heat of reaction:
138  DOUBLE PRECISION, INTENT(IN) :: DH(dimension_rxn)
139 ! User defined heat of reaction partitions.
140  DOUBLE PRECISION, INTENT(IN) :: fDH(dimension_rxn,0:dim_m)
141 
142 ! Array of reaction data objects.
143  TYPE(reaction_block), TARGET, ALLOCATABLE :: RXN_ARRAY(:)
144 
145 
146 
147 ! loop/variable indices1
148  INTEGER :: L
149 
150  TYPE(reaction_block), POINTER :: This
151 
152  DOUBLE PRECISION netMassTransfer(0:dim_m)
153 
154 
155 
156 
157  CALL init_err_msg('CHECK_CHEMICAL_RXNS_COMMON')
158 
159 
160 ! Allocate reaction blocks.
161  allocate(rxn_array(count))
162 
163 
164 
165 
166 
167 ! Loop over reaction data pulled from data file.
168  DO l=1, count
169 
170  this => rxn_array(l)
171 
172 ! Store the reaction name.
173  this%Name = trim(name(l))
174 
175 ! This check should not be necessary. Pre-processing by make_mfix and
176 ! reading the data file (PARSE_RXN) should have already caught any
177 ! issues.
178  IF(len_trim(this%Name) == 0) THEN
179  WRITE(err_msg, 1100) l
180  CALL flush_err_msg(abort=.true.)
181  ENDIF
182 
183  1100 FORMAT('Error 1100: No reaction name identified for reaction ', &
184  i3,'.',/'This should have been caught during the parsing ', &
185  'routines.')
186 
187 ! Store the chemical equation.
188  this%ChemEq = trim(chem_eq(l))
189 
190 ! Verify that a chemical equation was given in the data file.
191  IF(len_trim(this%ChemEq) == 0) THEN
192  WRITE(*,1101) trim(this%Name)
193  CALL flush_err_msg(abort=.true.)
194  ENDIF
195 
196  1101 FORMAT('Error 1101: No chemical equation identified for ', &
197  'reaction ',a,'.',/'Please correct the mfix.dat file.')
198 
199 ! Take the data read from the data file and populate the reaction block.
200  CALL setreaction(this, nmax(0), species_alias_g(:),lmmax, &
201  nmax(1:lmmax), species_alias_s(:,:), dh(l), fdh(l,:))
202 
203 ! If the energy equations are not being solved and a user provided
204 ! heat of reaction is given, flag error and exit.
205  IF(.NOT.energy_eq .AND. .NOT.this%Calc_DH) THEN
206  WRITE(err_msg,1200) trim(this%Name)
207  CALL flush_err_msg(abort=.true.)
208  ENDIF
209 
210  1200 FORMAT('Error 1200: Inconsistent user input. Energy equations ', &
211  'are NOT being',/'solved and a user defined heat of reaction',&
212  ' was detected',' for chemical',/' reaction ',a,'.',/'Please',&
213  ' correct the mfix.dat file.')
214 
215 ! Skip empty reactions.
216  IF(this%nSpecies == 0 .AND. this%nPhases == 0) THEN
217  cycle
218 
219 ! Something went wrong while parsing the reaction. This is a sanity
220 ! check and should never be true.
221  ELSEIF((this%nPhases == 0 .AND. this%nSpecies /= 0) .OR. &
222  (this%nPhases /= 0 .AND. this%nSpecies == 0)) THEN
223 
224  WRITE(err_msg,1201) trim(this%Name), this%nPhases, &
225  this%nSpecies
226  CALL flush_err_msg(abort=.true.)
227  ENDIF
228 
229  1201 FORMAT('Error 1201: Illogical data returned from setReaction ', &
230  'for chemical',/'reaction',1x,a,'.',//' Number of phases ', &
231  'identified: ',i3,/'Number of species identified: ',i3,//, &
232  'Please check the mfix.dat file.')
233 
234 ! Verify that the necessary information for each species in the reaction
235 ! was defined.
236  CALL checkthermoreqs(this, species_g, species_s, rdatabase, &
237  mw_g, mw_s, c_pg0, c_ps0)
238 
239 
240 ! Verify Mass Balance (Mass of Reactants = Mass of Products)
241 !---------------------------------------------------------------------//
242  ier = 0
243  CALL checkmassbalance('CHECK_CHEMICAL_RXNS', this, &
244  netmasstransfer(:), ier)
245  IF(ier /= 0) THEN
246  CALL write_rxn_summary(this, species_alias_g(:), &
247  species_alias_s(:,:), .true.)
248  ENDIF
249 
250 ! Determine interphase exchanges
251 !---------------------------------------------------------------------//
252  CALL calcinterphasetxfr('CHECK_CHEMICAL_RXNS', this, &
253  netmasstransfer(:), energy_eq, species_eq(:), &
254  species_alias_g(:), lmmax, species_alias_s(:,:))
255  ENDDO
256 
257 ! Write a summary of the chemical reactions
258 !---------------------------------------------------------------------//
259  DO l=1, count
260  this => rxn_array(l)
261  CALL write_rxn_summary(this, species_alias_g(:), &
262  species_alias_s(:,:), .false.)
263  ENDDO
264 
265  CALL finl_err_msg
266 
267  RETURN
268  END SUBROUTINE check_chemical_rxns_common
269 
270 
271 
272 
273  END SUBROUTINE check_chemical_rxns
274 
double precision, dimension(dim_m) c_ps0
Definition: physprop_mod.f:83
subroutine setreaction(RxN, lNg, lSAg, lM, lNs, lSAs, lDH, lfDH)
Definition: parse_mod.f:71
character(len=18), dimension(dim_m, dim_n_s) species_s
Definition: rxns_mod.f:51
subroutine check_chemical_rxns
character(len=32), dimension(:), allocatable rxn_name
Definition: parse_mod.f:34
integer, parameter dimension_rxn
Definition: param_mod.f:55
subroutine finl_err_msg
double precision c_pg0
Definition: physprop_mod.f:74
Definition: rxns_mod.f:1
logical, dimension(0:dim_m) species_eq
Definition: run_mod.f:115
double precision, dimension(:,:), allocatable des_usrfdh
Definition: parse_mod.f:54
integer, parameter dim_m
Definition: param_mod.f:67
character(len=32), dimension(dim_n_g) species_alias_g
Definition: rxns_mod.f:48
double precision, dimension(dim_n_g) mw_g
Definition: physprop_mod.f:124
character(len=32), dimension(:), allocatable des_rxn_name
Definition: parse_mod.f:48
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 calcinterphasetxfr(CALLER, RxN, lnMT, lEEq, lSEq, lSAg, lMMx, lSAs)
Definition: rxn_com_mod.f:848
subroutine checkspeciesinc(lNg, SA_g, lMMx, lNs, SA_s, lNRxn, lRNames, lNRxn_DES, lRNames_DES)
Definition: rxn_com_mod.f:164
double precision, dimension(:), allocatable usrdh
Definition: parse_mod.f:38
integer no_of_rxns
Definition: rxns_mod.f:41
double precision, dimension(:), allocatable des_usrdh
Definition: parse_mod.f:52
integer no_of_des_rxns
Definition: des_rxns_mod.f:51
Definition: run_mod.f:13
logical, dimension(0:dim_m, dim_n_g) rdatabase
Definition: rxns_mod.f:14
Definition: param_mod.f:2
Definition: parse_mod.f:1
character(len=512), dimension(:), allocatable des_rxn_chem_eq
Definition: parse_mod.f:50
integer, dimension(0:dim_m) nmax
Definition: physprop_mod.f:119
double precision, dimension(:,:), allocatable usrfdh
Definition: parse_mod.f:40
character(len=512), dimension(:), allocatable rxn_chem_eq
Definition: parse_mod.f:36
logical energy_eq
Definition: run_mod.f:100
subroutine checkduplicatealiases(lNg, SA_g, lMMx, lNs, SA_s)
Definition: rxn_com_mod.f:68
double precision, dimension(dim_m, dim_n_s) mw_s
Definition: physprop_mod.f:127
integer, parameter undefined_i
Definition: param1_mod.f:19
character(len=line_length), dimension(line_count) err_msg
subroutine check_chemical_rxns_common(COUNT, NAME, CHEM_EQ, DH, fDH, RXN_ARRAY)
integer smax
Definition: physprop_mod.f:22
character(len=18), dimension(dim_n_g) species_g
Definition: rxns_mod.f:47
character(len=32), dimension(dim_m, dim_n_s) species_alias_s
Definition: rxns_mod.f:52
subroutine checkthermoreqs(RxN, S_g, S_s, rDB, MWg, MWs, Cpg0, Cps0)
Definition: rxn_com_mod.f:595
subroutine flush_err_msg(DEBUG, HEADER, FOOTER, ABORT, LOG, CALL_TREE)