MFIX  2016-1
rrates0.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
2 ! C
3 ! Module name: RRATES0(IER) C
4 ! Purpose: Calculate reaction rates for various reactions in cell ijk C
5 ! using information from the data file C
6 ! C
7 ! Author: M. Syamlal Date: 3-10-98 C
8 ! Reviewer: Date: C
9 ! C
10 ! Revision Number: 1 C
11 ! Purpose:Replaced routines with new proceedures for automated C
12 ! reaction rate calculations. C
13 ! Author: J. Musser Date: 10-Oct-12 C
14 ! Reviewer: Date: dd-mmm-yy C
15 ! C
16 ! Literature/Document References: C
17 ! C
18 ! Variables referenced: MMAX, IJK, T_g, T_s1, D_p, X_g, X_s, EP_g, C
19 ! P_g, HOR_g, HOR_s C
20 ! C
21 ! C
22 ! Variables modified: M, N, R_gp, R_sp, RoX_gc, RoX_sc, SUM_R_g, C
23 ! SUM_R_s C
24 ! C
25 ! Local variables: C
26 ! C
27 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
28  SUBROUTINE rrates0()
29 
30 ! Global domain parameters.
31 !`````````````````````````````````````````````````````````````````````//
32 ! Blanket access is provided to the following modules as they don't
33 ! contain variables which are likely to be modified 'by accident.'
34  use compar
35  use indices
36  use geometry
37 
38 ! Gas phase global variables:
39 !`````````````````````````````````````````````````````````````````````//
40 ! Species mass fractions.
41  use fldvar, only: x_g
42 ! Temperature.
43  use fldvar, only: t_g
44 ! Rate of production.
45  use rxns, only: r_gp
46 ! Rate of consumption divided by species mass fraction.
47  use rxns, only: rox_gc
48 ! Net rate of change of gas phase mass.
49  use rxns, only: sum_r_g
50 ! Heat of reaction source term
51  use energy, only: hor_g
52 
53 ! Gas phase global variables:
54 !`````````````````````````````````````````````````````````````````````//
55 ! Species mass fractions.
56  use fldvar, only: x_s
57 ! Temperatures.
58  use fldvar, only: t_s
59 ! Rate of production.
60  use rxns, only: r_sp
61 ! Rate of consumption divided by species mass fraction.
62  use rxns, only: rox_sc
63 ! Net rate of change of gas phase mass.
64  use rxns, only: sum_r_s
65 ! Heat of reaction source term
66  use energy, only: hor_s
67 
68 
69 ! Reaction global variables:
70 !`````````````````````````````````````````````````````````````````````//
71 ! Number of TFM reactions.
72  use rxns, only: no_of_rxns
73 ! Rate of interphase mass transfer.
74  use rxns, only: r_phase
75 ! Data structure storing reaction information.
76  use rxns, only: reaction
77 
78 
79 ! Global run-time parameters.
80 !`````````````````````````````````````````````````````````````````````//
81 ! Number of solids phases (or one if MMAX is zero)
82  use param, only: dimension_m
83 ! Number of gas species.
84  use param, only: dimension_n_g
85 ! Number of solids phase species.
86  use param, only: dimension_n_s
87  use param1, only: dimension_lm
88  use param1, only: zero
89 ! Indicates that the energy equations are solved.
90  use run, only: energy_eq
91 ! Indicates that the species equations are solved.
92  use run, only: species_eq
93 ! Simulation units (CGS or SI)
94  use run, only: units
95 ! Number of solids phases.
96  use physprop, only: mmax
97 ! Number of species comprising each phase.
98  use physprop, only: nmax
99 ! Indicate that DEM is used.
100  use discretelement, only: discrete_element
101 ! Indicate that TFM/DEM hybrid is used.
102  use discretelement, only: des_continuum_hybrid
103 ! Small value for species mass fractions
104  use toleranc
105  use functions
106 
107  implicit none
108 
109 ! Local variables:
110 !`````````````````````````````````````````````````````````````````````//
111 ! Index/loop counters
112  INTEGER :: IJK ! fluid cell index
113  INTEGER :: H ! reaction loop counter
114  INTEGER :: L, M ! global phase index loop counters
115  INTEGER :: NN ! global species index
116  INTEGER :: lN ! reaction speices index
117  INTEGER :: lM ! reaction phase index
118  INTEGER :: mXfr ! global phase index for mass transfer
119 
120 ! This is a mask for the number of solids phases. The mask is used to
121 ! avoid issues for DEM based reactions where MMAX and DES_MMAX may be
122 ! in conflict.
123  INTEGER :: lMMAX
124  LOGICAL :: noSolids
125 
126 ! User-defined reaction rates returned from USR_RATES
127  DOUBLE PRECISION RATES(no_of_rxns)
128 ! Reaction and species specific reaction rate.
129  DOUBLE PRECISION lRate
130 
131 ! Single reaction formation/consumption rate of each gas species.
132  DOUBLE PRECISION :: r_Rgp(dimension_n_g)
133  DOUBLE PRECISION :: r_ROXgc(dimension_n_g)
134 ! Single reaction formation/consumption rate of each solids species.
135  DOUBLE PRECISION :: r_Rsp(dimension_m, dimension_n_s)
136  DOUBLE PRECISION :: r_ROXsc(dimension_m, dimension_n_s)
137 
138 ! Rate of interphase enthalpy transfer
139  DOUBLE PRECISION :: r_RxH(0:mmax, 0:mmax)
140 ! Local heat of reactions
141  DOUBLE PRECISION :: r_HoRg, r_HoRs(1:mmax)
142 ! Conversion factor for HoR (CGS to SI)
143  DOUBLE PRECISION :: l_2SI
144 
145 ! Reaction limiters. If a species mass fraction is less than this
146 ! value, then the reaction is suppressed.
147  DOUBLE PRECISION :: speciesLimiter
148 
149 ! External functions:
150 !`````````````````````````````````````````````````````````````````````//
151 ! Calculates enthalpy (cal/gram)
152  DOUBLE PRECISION, EXTERNAL :: CALC_H
153 
154 ! Initialize global storage arrays to zero
155 !---------------------------------------------------------------------//
156 ! Gas Solids
157  r_gp = zero; r_sp = zero
158  rox_gc = zero; rox_sc = zero
159  sum_r_g = zero; sum_r_s = zero
160  hor_g = zero; hor_s = zero
161 
162  r_phase = zero
163 
164 ! Set the species limiter:
165  specieslimiter = zero_x_gs
166 
167 ! Set the conversion factor for heat of reaction.
168  l_2si = merge(4.183925d3, one, units(1:2) == 'SI')
169 
170 ! Set the number of TFM solids phases.
171 ! the following 2 lines could be replaced by assing lmmax=smax
172  nosolids = discrete_element .AND. (.NOT.des_continuum_hybrid)
173  lmmax = merge(0, mmax, nosolids)
174 
175 ! Loop over each fluid cell.
176  DO ijk = ijkstart3, ijkend3
177  IF (fluid_at(ijk)) THEN
178 
179  rates(:) = zero
180 
181 ! Calculate user defined reaction rates.
182  CALL usr_rates(ijk, rates)
183 
184 ! Loop over reactions.
185  rxn_lp: DO h = 1, no_of_rxns
186 
187 ! Skip empty reactions
188  IF(reaction(h)%nSpecies == 0) cycle rxn_lp
189  IF(compare(rates(h),zero)) cycle rxn_lp
190 
191 ! Initialize reaction loop arrays
192  r_rgp = zero; r_roxgc = zero; r_horg = zero
193  r_rsp = zero; r_roxsc = zero; r_hors = zero
194 
195  r_rxh = zero
196 
197 ! Calculate the rate of formation/consumption for each species.
198 !---------------------------------------------------------------------//
199  DO ln = 1, reaction(h)%nSpecies
200 ! Global phase index.
201  m = reaction(h)%Species(ln)%pMap
202 ! Global species index.
203  nn = reaction(h)%Species(ln)%sMap
204 ! Index for interphase mass transfer. For a gas/solid reaction, the
205 ! index is stored with the gas phase. For solid/solid mass transfer
206 ! the index is stored with the source phase.
207  mxfr = reaction(h)%Species(ln)%mXfr
208  lrate = rates(h) * reaction(h)%Species(ln)%MWxStoich
209 ! Gas Phase:
210  IF(m == 0) THEN
211 ! Consumption of gas phase species.
212  IF(lrate < zero) THEN
213  IF(x_g(ijk,nn) > specieslimiter) THEN
214  r_roxgc(nn) = r_roxgc(nn) - lrate/x_g(ijk,nn)
215 ! Enthalpy transfer associated with mass transfer. (gas/solid)
216  IF(m /= mxfr) r_rxh(m,mxfr) = r_rxh(m,mxfr) + &
217  lrate * calc_h(t_g(ijk),0,nn)
218  ELSE
219 ! There is an insignificant amount of reactant. Skip this reaction.
220  rates(h) = zero
221  cycle rxn_lp
222  ENDIF
223  ELSE
224 ! Formation of gas phase species.
225  r_rgp(nn) = r_rgp(nn) + lrate
226 ! Enthalpy transfer associated with mass transfer. (gas/solid)
227  IF(m /= mxfr) r_rxh(m,mxfr) = r_rxh(m,mxfr) + &
228  lrate * calc_h(t_s(ijk,mxfr),0,nn)
229  ENDIF
230 
231 
232 ! Solids Phase M:
233  ELSE
234 ! Consumption of solids phase species.
235  IF(lrate < zero) THEN
236  IF(x_s(ijk,m,nn) > specieslimiter) THEN
237  r_roxsc(m,nn) = r_roxsc(m,nn) - lrate/x_s(ijk,m,nn)
238 ! Enthalpy transfer associated with mass transfer. (solid/solid) This
239 ! is only calculated from the source (reactant) material.
240  IF(m /= mxfr) THEN
241  IF(m < mxfr) THEN
242  r_rxh(m,mxfr) = r_rxh(m,mxfr) + lrate * &
243  reaction(h)%Species(ln)%xXfr * &
244  calc_h(t_s(ijk,m),m,nn)
245  ELSE
246  r_rxh(mxfr,m) = r_rxh(mxfr,m) - lrate * &
247  reaction(h)%Species(ln)%xXfr * &
248  calc_h(t_s(ijk,m),m,nn)
249  ENDIF
250  ENDIF
251  ELSE
252 ! There is an insignificant amount of reactant. Skip this reaction.
253  rates(h) = zero
254  cycle rxn_lp
255  ENDIF
256  ELSE
257 ! Formation of solids phase species.
258  r_rsp(m,nn) = r_rsp(m,nn) + lrate
259  ENDIF
260  ENDIF
261  ENDDO ! Loop of species
262 
263 
264 
265 ! Map the local reaction production/consumption into global variables.
266 !---------------------------------------------------------------------//
267 ! The outer reaction loop was cycled if there was insufficient amount
268 ! of species available.
269 
270 ! Gas phase production
271  r_gp(ijk,:nmax(0)) = r_gp(ijk,:nmax(0)) + &
272  r_rgp(:nmax(0))
273 ! Gas phase consumption divided by species mass fraction
274  rox_gc(ijk,:nmax(0)) = rox_gc(ijk,:nmax(0)) + &
275  r_roxgc(:nmax(0))
276 
277  DO m=1,lmmax
278 ! Solids phase species production
279  r_sp(ijk,m,:nmax(m)) = r_sp(ijk,m,:nmax(m)) + &
280  r_rsp(m,:nmax(m))
281 ! Solids phase species consumption divided by species mass fraction
282  rox_sc(ijk,m,:nmax(m)) = rox_sc(ijk,m,:nmax(m)) + &
283  r_roxsc(m,:nmax(m))
284  ENDDO
285 
286 
287 ! Calculate and store the heat of reaction.
288 !---------------------------------------------------------------------//
289  IF(energy_eq) THEN
290 ! Automated heat of reaction calculations
291  IF(reaction(h)%Calc_DH) THEN
292 ! Loop over reaction species.
293  DO ln = 1, reaction(h)%nSpecies
294 ! Global phase index.
295  m = reaction(h)%Species(ln)%pMap
296 ! Global species index.
297  nn = reaction(h)%Species(ln)%sMap
298 ! Rate of formation/consumption for speices N
299  lrate = rates(h) * reaction(h)%Species(ln)%MWxStoich
300 ! Gas phase enthalpy change from energy equation derivation.
301  IF(m == 0) THEN
302  r_horg = r_horg + calc_h(t_g(ijk),0,nn) * lrate
303 ! Solid phase enthalpy change from energy equation derivation.
304  ELSE
305  r_hors(m) = r_hors(m) + calc_h(t_s(ijk,m),m,nn)*lrate
306  ENDIF
307  ENDDO
308 
309 ! Complete the skew-symettric for enthalpy transfer with mass transfer
310  DO m=1, lmmax
311  DO l=0, m-1
312  r_rxh(m,l) = - r_rxh(l,m)
313  ENDDO
314  ENDDO
315 ! Apply enthalpy transfer associated with mass transfer to get the
316 ! complete heat of reaction of heat phse for Reaction H.
317  DO l=0, lmmax
318  DO m = 0, lmmax
319  IF(l == m) cycle
320  IF(l == 0) THEN
321  r_horg = r_horg - r_rxh(l,m)
322  ELSE
323  r_hors(l) = r_hors(l) - r_rxh(l,m)
324  ENDIF
325  ENDDO
326  ENDDO
327 ! Apply unit conversion and store heats of reaction in the global array.
328  hor_g(ijk) = hor_g(ijk) + l_2si*r_horg
329  DO m=1,lmmax
330  hor_s(ijk,m) = hor_s(ijk,m) + l_2si*r_hors(m)
331  ENDDO
332  ELSE
333 ! User-defined heat of reaction.
334  hor_g(ijk) = hor_g(ijk) + reaction(h)%HoR(0) * rates(h)
335  DO m=1, lmmax
336  hor_s(ijk,m) = hor_s(ijk,m) + &
337  reaction(h)%HoR(m) * rates(h)
338  ENDDO
339  ENDIF
340  ENDIF ! ENERGY_EQ
341 
342 ! Update rate of interphase mass transfer.
343 !---------------------------------------------------------------------//
344  DO lm=1, (dimension_lm+dimension_m-1)
345  r_phase(ijk,lm) = r_phase(ijk,lm) + &
346  rates(h) * reaction(h)%rPHASE(lm)
347  ENDDO
348  ENDDO rxn_lp ! Loop over reactions.
349 
350 
351 ! Calculate the toal rate of formation and consumption for each species.
352 !---------------------------------------------------------------------//
353  IF(species_eq(0)) THEN
354  sum_r_g(ijk) = sum( r_gp(ijk,:nmax(0)) - &
355  rox_gc(ijk,:nmax(0))*x_g(ijk,:nmax(0)))
356  ELSE
357  DO h=1, no_of_rxns
358  IF(reaction(h)%nPhases <= 0) cycle
359  DO m=1, lmmax
360  lm = 1 + ((m-1)*m)/2
361  sum_r_g(ijk) = sum_r_g(ijk) + &
362  rates(h) * reaction(h)%rPHASE(lm)
363  ENDDO
364  ENDDO
365  ENDIF
366 
367  DO m=1, lmmax
368  IF(species_eq(m)) THEN
369  sum_r_s(ijk,m) = sum( r_sp(ijk,m,:nmax(m)) - &
370  rox_sc(ijk,m,:nmax(m))*x_s(ijk,m,:nmax(m)))
371  ELSE
372  DO h=1, no_of_rxns
373  IF(reaction(h)%nPhases <= 0) cycle
374  DO l=0, m-1
375  lm = 1 + l + ((m-1)*m)/2
376  sum_r_s(ijk,m) = sum_r_s(ijk,m) - &
377  rates(h) * reaction(h)%rPHASE(lm)
378  ENDDO
379  DO l=m+1, lmmax
380  lm = 1 + m + ((l-1)*l)/2
381  sum_r_s(ijk,m) = sum_r_s(ijk,m) + &
382  rates(h) * reaction(h)%rPHASE(lm)
383  ENDDO
384  ENDDO
385  ENDIF
386  ENDDO
387 
388 
389  ENDIF ! Fluid_At(IJK)
390  END DO ! IJK
391 
392  RETURN
393 
394  END SUBROUTINE rrates0
integer ijkend3
Definition: compar_mod.f:80
logical function compare(V1, V2)
Definition: toleranc_mod.f:94
integer dimension_lm
Definition: param1_mod.f:13
integer dimension_n_g
Definition: param_mod.f:20
Definition: rxns_mod.f:1
logical, dimension(0:dim_m) species_eq
Definition: run_mod.f:115
double precision, dimension(:), allocatable t_g
Definition: fldvar_mod.f:63
double precision, dimension(:), allocatable sum_r_g
Definition: rxns_mod.f:28
double precision, dimension(:,:), allocatable sum_r_s
Definition: rxns_mod.f:35
subroutine usr_rates(IJK, RATES)
Definition: usr_rates.f:37
double precision, dimension(:,:,:), allocatable rox_sc
Definition: rxns_mod.f:33
integer mmax
Definition: physprop_mod.f:19
double precision, dimension(:,:,:), allocatable x_s
Definition: fldvar_mod.f:78
double precision, dimension(:,:), allocatable t_s
Definition: fldvar_mod.f:66
double precision, dimension(:,:), allocatable x_g
Definition: fldvar_mod.f:75
integer no_of_rxns
Definition: rxns_mod.f:41
double precision, dimension(:,:,:), allocatable r_sp
Definition: rxns_mod.f:31
subroutine rrates0()
Definition: rrates0.f:29
Definition: run_mod.f:13
double precision, dimension(:,:), allocatable r_phase
Definition: rxns_mod.f:38
Definition: param_mod.f:2
character(len=16) units
Definition: run_mod.f:30
double precision, dimension(:,:), allocatable rox_gc
Definition: rxns_mod.f:26
integer, dimension(0:dim_m) nmax
Definition: physprop_mod.f:119
logical energy_eq
Definition: run_mod.f:100
integer ijkstart3
Definition: compar_mod.f:80
double precision, parameter zero_x_gs
Definition: toleranc_mod.f:19
integer dimension_n_s
Definition: param_mod.f:21
integer dimension_m
Definition: param_mod.f:18
double precision, parameter zero
Definition: param1_mod.f:27
double precision, dimension(:,:), allocatable r_gp
Definition: rxns_mod.f:24
double precision, dimension(:), allocatable hor_g
Definition: energy_mod.f:6
double precision, dimension(:,:), allocatable hor_s
Definition: energy_mod.f:9