MFIX  2016-1
rxns_gs_des1.f
Go to the documentation of this file.
1 #include "version.inc"
2 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
3 ! !
4 ! Module name: CONV_GS_DES1 !
5 ! Author: J.Musser: 16-Jun-10 !
6 ! !
7 ! Purpose: This routine is called from the DISCRETE side to calculate !
8 ! the gas-particle convective heat transfer. !
9 ! !
10 ! Comments: Explicitly coupled simulations use a stored convective !
11 ! heat transfer coefficient. Otherwise, the convective heat transfer !
12 ! coeff is calculated every time step and the total interphase energy !
13 ! transfered is 'stored' and used explictly in the gas phase. The !
14 ! latter conserves all energy
15 ! !
16 ! REF: Zhou, Yu, and Zulli, "Particle scale study of heat transfer in !
17 ! packed and bubbling fluidized beds," AIChE Journal, Vol. 55, !
18 ! no 4, pp 868-884, 2009. !
19 ! !
20 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
21  SUBROUTINE rxns_gs_des1
22 
23  use constant, only: pi
24 ! Flag: The fluid and discrete solids are explicitly coupled.
25  use discretelement, only: des_explicitly_coupled
26  use discretelement, only: dtsolid
27  use discretelement, only: pijk
28  use discretelement, only: max_pip
29 
31 
32  use particle_filter, only: filter_cell
34  use particle_filter, only: filter_size
35 
36  use des_rxns, only: des_r_gp, des_r_gc
37  use des_rxns, only: des_r_phase, des_sum_r_g
38  use des_rxns, only: des_hor_g
39 
40  use physprop, only: nmax
41 
42  use functions, only: fluid_at
43  use functions, only: is_normal
44 
45  use param1, only: zero
46  use des_rxns, only: des_r_s
47  use des_thermo, only: rxns_qs
48 
49  use param1, only: dimension_lm
50  use param, only: dimension_m
51 
52  IMPLICIT NONE
53 
54  INTEGER :: IJK, LC, NP
55 
56 
57 ! Local gas phase values.
58  DOUBLE PRECISION :: lRgp(nmax(0)) ! Rate of species production
59  DOUBLE PRECISION :: lRgc(nmax(0)) ! Rate of species consumption
60  DOUBLE PRECISION :: lHoRg ! Heat of reaction
61  DOUBLE PRECISION :: lSUMRg ! lSUMRg
62 
63 ! Interphase mass transfer
64  DOUBLE PRECISION :: lRPhase(dimension_lm+dimension_m-1)
65 
66  DOUBLE PRECISION :: WEIGHT
67 
68  DO np=1,max_pip
69  IF(.NOT.is_normal(np)) cycle
70 
71 ! Avoid convection calculations in cells without fluid (cut-cell)
72  IF(.NOT.fluid_at(pijk(np,4))) THEN
73  des_r_s(np,:) = zero
74  rxns_qs(np) = zero
75 
76 ! No additional calculations are needed for explictly coupled
77  ELSEIF(.NOT.des_explicitly_coupled) THEN
78 
79 ! Calculate the heat transfer coefficient.
80  CALL calc_rrates_des(np, lrgp, lrgc, lrphase, lhorg, lsumrg)
81 
82 ! Integrate over solids time step and store in global array. This
83 ! needs updated when interpolation is reintroduced into thermo code.
84 !---------------------------------------------------------------------//
85 ! Store the gas phase source terms.
86  IF(des_interp_on) THEN
87  DO lc=1,filter_size
88  ijk = filter_cell(lc,np)
89  weight = dtsolid*filter_weight(lc,np)
90 
91  des_r_gp(ijk,:) = des_r_gp(ijk,:)+lrgp*weight
92  des_r_gc(ijk,:) = des_r_gc(ijk,:)+lrgc*weight
93  des_r_phase(ijk,:) = des_r_phase(ijk,:)+lrphase*weight
94  des_hor_g(ijk) = des_hor_g(ijk) + lhorg*weight
95  des_sum_r_g(ijk) = des_sum_r_g(ijk) + lsumrg*weight
96  ENDDO
97  ELSE
98  ijk = pijk(np,4)
99  weight = dtsolid
100 
101  des_r_gp(ijk,:) = des_r_gp(ijk,:) + lrgp*weight
102  des_r_gc(ijk,:) = des_r_gc(ijk,:) + lrgc*weight
103  des_r_phase(ijk,:) = des_r_phase(ijk,:) + lrphase*weight
104  des_hor_g(ijk) = des_hor_g(ijk) + lhorg*weight
105  des_sum_r_g(ijk) = des_sum_r_g(ijk) + lsumrg*weight
106  ENDIF
107  ENDIF
108  ENDDO
109 
110 ! Note that MPI sync is managed at the end of des_time_march for
111 ! non-explicitly coupled cases that use interpolation.
112 
113  RETURN
114  END SUBROUTINE rxns_gs_des1
115 
116 
117 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
118 ! !
119 ! Subroutine: RXNS_GS_GAS1 !
120 ! Author: J.Musser Date: 21-NOV-14 !
121 ! !
122 ! Purpose: This routine is called from the CONTINUUM. It calculates !
123 ! the scalar cell center drag force acting on the fluid using !
124 ! interpolated values for the gas velocity and volume fraction. The !
125 ! The resulting sources are interpolated back to the fluid grid. !
126 ! !
127 ! NOTE: The loop over particles includes ghost particles so that MPI !
128 ! communications are needed to distribute overlapping force between !
129 ! neighboring grid cells. This is possible because only cells "owned" !
130 ! by the current process will have non-zero weights. !
131 ! !
132 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
133  SUBROUTINE rxns_gs_gas1
135 ! Size of particle array on this process.
136  use discretelement, only: max_pip
137 ! Flag to use interpolation
138  use particle_filter, only: des_interp_on
139 ! Interpolation cells and weights
141 ! IJK of fluid cell containing particles center
142  use discretelement, only: pijk
143 ! Gas phase mass, species, and energy equation sources
145  use des_rxns, only: des_r_phase, des_hor_g
146 ! Number of species for each phase
147  use physprop, only: nmax
148 ! Funtion for identifying fluid cells and normal particles.
149  use functions, only: fluid_at
150  use functions, only: is_normal
151 ! MPI function for collecting interpolated data from ghost cells.
152  use sendrecvnode, only: des_collect_gdata
153 ! MPI wrapper for halo exchange.
154  use sendrecv, only: send_recv
155 ! Fluid time step size.
156  use run, only: dt
157 ! Flag to use stiff chemistry solver
158  use stiff_chem, only: stiff_chemistry
159 ! Routine to sync stiff solver results
161 
162 ! Global Parameters:
163 !---------------------------------------------------------------------//
164 ! Double precision values.
165  use param1, only: zero, one
166  use param1, only: dimension_lm
167  use param, only: dimension_m
168 
169  IMPLICIT NONE
170 
171 ! Loop counters: Particle, fluid cell, neighbor cells
172  INTEGER :: NP, IJK, LC
173 ! Loop bound for filter
174  DOUBLE PRECISION :: GAMMAxTp
175 ! Local gas phase values.
176  DOUBLE PRECISION :: lRgp(nmax(0)) ! Rate of species production
177  DOUBLE PRECISION :: lRgc(nmax(0)) ! Rate of species consumption
178  DOUBLE PRECISION :: lHoRg ! Heat of reaction
179  DOUBLE PRECISION :: lSUMRg ! lSUMRg
180 
181 ! Interphase mass transfer
182  DOUBLE PRECISION :: lRPhase(dimension_lm+dimension_m-1)
183 
184  DOUBLE PRECISION :: WEIGHT
185 
186 ! Initialize fluid cell values.
187  des_r_gp = zero
188  des_r_gc = zero
189  des_r_phase = zero
190  des_hor_g = zero
191  des_sum_r_g = zero
192 
193 ! Calculate the gas phase forces acting on each particle.
194 
195  DO np=1,max_pip
196 
197 ! Only calculate chemical reactions for normal particles that are inside
198 ! fluid cells. Ex: Skip ghost particles or particles that are in a cut-
199 ! cell dead space.
200  IF(.NOT.is_normal(np)) cycle
201  IF(.NOT.fluid_at(pijk(np,4))) cycle
202 
203  ijk = pijk(np,4)
204 
205 ! Calculate the rates of species formation/consumption.
206  CALL calc_rrates_des(np, lrgp, lrgc, lrphase, lhorg, lsumrg)
207 
208 ! Directly integrate fluid cell reaction sources
209  IF(stiff_chemistry) THEN
210  CALL des_stiff_chem(ijk, dt, lrgp, lrgc, lhorg, lsumrg)
211 
212 ! Store the gas phase source terms.
213  ELSEIF(des_interp_on) THEN
214  DO lc=1,filter_size
215  ijk = filter_cell(lc,np)
216  weight = filter_weight(lc,np)
217 
218  des_r_gp(ijk,:) = des_r_gp(ijk,:)+lrgp*weight
219  des_r_gc(ijk,:) = des_r_gc(ijk,:)+lrgc*weight
220  des_r_phase(ijk,:) = des_r_phase(ijk,:)+lrphase*weight
221  des_hor_g(ijk) = des_hor_g(ijk) + lhorg*weight
222  des_sum_r_g(ijk) = des_sum_r_g(ijk) + lsumrg*weight
223  ENDDO
224  ELSE
225  des_r_gp(ijk,:) = des_r_gp(ijk,:) + lrgp
226  des_r_gc(ijk,:) = des_r_gc(ijk,:) + lrgc
227  des_r_phase(ijk,:) = des_r_phase(ijk,:) + lrphase
228  des_hor_g(ijk) = des_hor_g(ijk) + lhorg
229  des_sum_r_g(ijk) = des_sum_r_g(ijk) + lsumrg
230  ENDIF
231  ENDDO
232 
233 ! Make the necessary send/recv calls for field vars
234  IF(stiff_chemistry) THEN
236  ELSE
237 ! Add in data stored in ghost cells from interpolation. This call must
238 ! preceed the SEND_RECV to avoid overwriting ghost cell data.
239  IF(des_interp_on) THEN
240  CALL des_collect_gdata(des_r_gp)
241  CALL des_collect_gdata(des_r_gc)
242  CALL des_collect_gdata(des_r_phase)
243  CALL des_collect_gdata(des_hor_g)
244  CALL des_collect_gdata(des_sum_r_g)
245  ENDIF
246 
247 ! Update the species mass sources in ghost layers.
248  CALL send_recv(des_r_gp, 2)
249  CALL send_recv(des_r_gc, 2)
250  CALL send_recv(des_r_phase, 2)
251  CALL send_recv(des_hor_g, 2)
252  CALL send_recv(des_sum_r_g, 2)
253  ENDIF
254 
255  RETURN
256  END SUBROUTINE rxns_gs_gas1
257 
258 
259 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
260 ! !
261 ! Subroutine: DES_STIFF_CHEM !
262 ! Author: J.Musser Date: 7-FEB-16 !
263 ! !
264 ! Purpose: This routine updates a fluid cell by directly integrating !
265 ! the source terms due to reaction. Note that this routine is called !
266 ! for each particle to prevent over consumption of reactants. !
267 ! !
268 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
269  SUBROUTINE des_stiff_chem(pIJK, pDT, pRgp, pRgc, pHoRg, pSUMRg)
271  USE constant, only: gas_const
272  USE fldvar, only: ep_g, ro_g, rop_g, t_g, x_g, p_g
273  USE geometry, only: vol
274  USE param1, only: zero, small_number, one
275  USE physprop, only: c_pg, mw_g, mw_mix_g
276  use toleranc, only: zero_x_gs
277  use physprop, only: nmax
278 
279  use compar, only: mype
280  IMPLICIT NONE
281 
282 ! Passed variables
283 !---------------------------------------------------------------------//
284  INTEGER, INTENT(IN) :: pIJK ! fluid cell index
285  DOUBLE PRECISION, INTENT(IN) :: pDT ! fluid time step
286  DOUBLE PRECISION, INTENT(IN) :: pRgp(nmax(0)) ! Rate of production
287  DOUBLE PRECISION, INTENT(IN) :: pRgc(nmax(0)) ! Rate of consumption
288  DOUBLE PRECISION, INTENT(IN) :: pHoRg ! Heat of reaction
289  DOUBLE PRECISION, INTENT(IN) :: pSUMRg ! Net mass change
290 
291 ! Local variables
292 !---------------------------------------------------------------------//
293  DOUBLE PRECISION :: lRg(nmax(0)), sumXg
294  DOUBLE PRECISION :: lDToVOL
295  INTEGER :: N
296 !......................................................................!
297 
298 ! Time step divided by cell volume.
299  ldtovol = pdt/vol(pijk)
300 ! Net change in species mass
301  lrg = prgp - prgc
302 
303 ! Gas phase density: ROP_g
304  rop_g(pijk) = rop_g(pijk) + ldtovol*psumrg
305 
306 ! Temperature: T_g
307  t_g(pijk) = t_g(pijk) - ldtovol*(phorg/(rop_g(pijk)*c_pg(pijk)))
308 
309 ! Species mass fractions: X_g
310  DO n=1,nmax(0)
311  x_g(pijk,n) = x_g(pijk,n) + ldtovol * &
312  (lrg(n) - x_g(pijk,n)*psumrg)/(rop_g(pijk))
313  ENDDO
314 
315 ! Cleanup over/under shoots.
316  x_g(pijk,:) = min(max(x_g(pijk,:), zero), one)
317  sumxg = sum(x_g(pijk,:))
318  x_g(pijk,:) = x_g(pijk,:)/sumxg
319 
320 ! Gas phase bulk density is updated within the stiff solver (lVar(1)).
321 ! Now that the gas phase volume fraction is updated, the gas phase
322 ! density can be backed out. RO_g * EP_g = ROP_g
323  IF(ep_g(pijk) > small_number) THEN
324  ro_g(pijk) = rop_g(pijk) / ep_g(pijk)
325  ELSE
326 ! This case shouldn't happen, however HUGE is used to aid in tracking
327 ! errors should this somehow become and issue.
328  ro_g(pijk) = huge(0.0)
329  ENDIF
330 
331 ! Calculate the mixture molecular weight.
332  mw_mix_g(pijk) = sum(x_g(pijk,1:nmax(0))/mw_g(1:nmax(0)))
333  mw_mix_g(pijk) = one/mw_mix_g(pijk)
334 
335 ! Calculate the gas phase pressure.
336  p_g(pijk) = (ro_g(pijk)*gas_const*t_g(pijk))/mw_mix_g(pijk)
337 
338  RETURN
339  END SUBROUTINE des_stiff_chem
double precision, dimension(:,:), allocatable des_r_s
Definition: des_rxns_mod.f:24
integer, dimension(:,:), allocatable filter_cell
double precision, dimension(:), allocatable ep_g
Definition: fldvar_mod.f:15
integer dimension_lm
Definition: param1_mod.f:13
double precision, parameter one
Definition: param1_mod.f:29
double precision, dimension(:), allocatable des_hor_g
Definition: des_rxns_mod.f:46
double precision, dimension(:), allocatable t_g
Definition: fldvar_mod.f:63
double precision gas_const
Definition: constant_mod.f:152
double precision, dimension(:), allocatable des_sum_r_g
Definition: des_rxns_mod.f:42
double precision dt
Definition: run_mod.f:51
subroutine calc_rrates_des(NP, pRgp, pRgc, pRPhase, pHoRg, pSUMRg)
double precision, dimension(:), allocatable p_g
Definition: fldvar_mod.f:26
double precision, dimension(dim_n_g) mw_g
Definition: physprop_mod.f:124
subroutine finalize_stiff_solver
double precision, dimension(:,:), allocatable filter_weight
subroutine des_stiff_chem(pIJK, pDT, pRgp, pRgc, pHoRg, pSUMRg)
Definition: rxns_gs_des1.f:270
double precision, parameter small_number
Definition: param1_mod.f:24
double precision, dimension(:,:), allocatable x_g
Definition: fldvar_mod.f:75
double precision, dimension(:,:), allocatable des_r_gc
Definition: des_rxns_mod.f:40
subroutine rxns_gs_des1
Definition: rxns_gs_des1.f:22
Definition: run_mod.f:13
Definition: param_mod.f:2
double precision, dimension(:,:), allocatable des_r_phase
Definition: des_rxns_mod.f:44
double precision, dimension(:), allocatable mw_mix_g
Definition: physprop_mod.f:130
integer, dimension(0:dim_m) nmax
Definition: physprop_mod.f:119
integer mype
Definition: compar_mod.f:24
double precision, parameter zero_x_gs
Definition: toleranc_mod.f:19
double precision, dimension(:), allocatable rxns_qs
double precision, dimension(:,:), allocatable des_r_gp
Definition: des_rxns_mod.f:38
double precision, parameter pi
Definition: constant_mod.f:158
double precision, dimension(:), allocatable vol
Definition: geometry_mod.f:212
integer dimension_m
Definition: param_mod.f:18
logical stiff_chemistry
double precision, dimension(:), allocatable ro_g
Definition: fldvar_mod.f:32
double precision, dimension(:), allocatable rop_g
Definition: fldvar_mod.f:38
double precision, parameter zero
Definition: param1_mod.f:27
double precision, dimension(:), allocatable c_pg
Definition: physprop_mod.f:80
subroutine rxns_gs_gas1
Definition: rxns_gs_des1.f:134