MFIX  2016-1
des_thermo_conv.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 conv_gs_des1
22 
23  use constant, only: pi
24  Use des_thermo
25  Use discretelement
26  Use fldvar
27  Use interpolation
28  Use param1
29  use des_thermo, only: gammaxsa
30  use geometry, only: no_k
32  use particle_filter, only: filter_cell
34  use particle_filter, only: filter_size
35  use functions, only: fluid_at
36  use functions, only: is_normal
37  IMPLICIT NONE
38 
39  DOUBLE PRECISION :: lTg, GAMMA
40  DOUBLE PRECISION :: Qcv_DT, Qcv
41  DOUBLE PRECISION :: l4Pi
42  INTEGER :: IJK, LC, NP
43 
44  l4pi = 4.0d0*pi
45 
46  DO np=1,max_pip
47  IF(.NOT.is_normal(np)) cycle
48 
49 ! Calculate the gas temperature.
50  IF(des_interp_on) THEN
51  ltg = zero
52  DO lc=1,filter_size
53  ijk = filter_cell(lc,np)
54  ltg = ltg + t_g(ijk)*filter_weight(lc,np)
55  ENDDO
56  ELSE
57  ijk = pijk(np,4)
58  ltg = t_g(ijk)
59  ENDIF
60 
61  ijk = pijk(np,4)
62 
63 ! Avoid convection calculations in cells without fluid (cut-cell)
64  IF(.NOT.fluid_at(ijk)) THEN
65  gammaxsa(np) = zero
66  conv_qs(np) = zero
67 
68 ! For explicit coupling, use the heat transfer coefficient calculated
69 ! for the gas phase heat transfer calculations.
70  ELSEIF(des_explicitly_coupled) THEN
71  conv_qs(np) = gammaxsa(np)*(ltg - des_t_s(np))
72 
73  ELSE
74 
75 ! Calculate the heat transfer coefficient.
76  CALL calc_gamma_des(np, gamma)
77  gammaxsa(np) = gamma* l4pi*des_radius(np)*des_radius(np)
78 
79 ! Calculate the rate of heat transfer to the particle
80  qcv = gammaxsa(np)*(ltg - des_t_s(np))
81 ! Store convection source in global energy source array.
82  q_source(np) = q_source(np) + qcv
83 
84 ! Calculate the gas phase source term components.
85  qcv_dt = qcv*dtsolid
86  IF(des_interp_on) THEN
87  DO lc=1,filter_size
88  conv_sc(ijk)=conv_sc(ijk)-qcv_dt*filter_weight(lc,np)
89  ENDDO
90  ELSE
91  conv_sc(ijk) = conv_sc(ijk) - qcv_dt
92  ENDIF
93  ENDIF
94  ENDDO
95 
96 ! Note that MPI sync is managed at the end of des_time_march for
97 ! non-explicitly coupled cases that use interpolation.
98 
99  RETURN
100  END SUBROUTINE conv_gs_des1
101 
102 
103 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
104 ! !
105 ! Subroutine: CONV_GS_GAS1 !
106 ! Author: J.Musser Date: 21-NOV-14 !
107 ! !
108 ! !
109 ! Purpose: This routine is called from the CONTINUUM. It calculates !
110 ! the scalar cell center drag force acting on the fluid using !
111 ! interpolated values for the gas velocity and volume fraction. The !
112 ! The resulting sources are interpolated back to the fluid grid. !
113 ! !
114 ! NOTE: The loop over particles includes ghost particles so that MPI !
115 ! communications are needed to distribute overlapping force between !
116 ! neighboring grid cells. This is possible because only cells "owned" !
117 ! by the current process will have non-zero weights. !
118 ! !
119 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
120  SUBROUTINE conv_gs_gas1
122 ! Flag: The fluid and discrete solids are explicitly coupled.
123  use discretelement, only: des_explicitly_coupled
124 ! Size of particle array on this process.
125  use discretelement, only: max_pip
126 ! Flag to use interpolation
127  use particle_filter, only: des_interp_on
128 ! Interpolation cells and weights
130 ! IJK of fluid cell containing particles center
131  use discretelement, only: pijk
132 ! Particle temperature
133  use des_thermo, only: des_t_s
134 ! Gas phase energy equation sources
135  use des_thermo, only: conv_sp, conv_sc
136  Use discretelement, only: des_radius
137 ! Heat transfer coefficint (GAMMA) multiplied by sufrace area
138  use des_thermo, only: gammaxsa
139 ! Funtion for identifying fluid cells and normal particles.
140  use functions, only: fluid_at
141  use functions, only: is_normal
142 ! MPI function for collecting interpolated data from ghost cells.
143  use sendrecvnode, only: des_collect_gdata
144 ! MPI wrapper for halo exchange.
145  use sendrecv, only: send_recv
146 
147 ! Global Parameters:
148 !---------------------------------------------------------------------//
149 ! Double precision values.
150  use param1, only: zero, one
151  use constant, only: pi
152 
153  IMPLICIT NONE
154 
155 ! Loop counters: Particle, fluid cell, neighbor cells
156  INTEGER :: NP, IJK, LC
157 ! Interpolation weight
158  DOUBLE PRECISION :: WEIGHT
159  DOUBLE PRECISION :: GAMMAxSAxTp, GAMMA
160  DOUBLE PRECISION :: l4Pi
161 
162  l4pi = 4.0d0*pi
163 
164 ! Initialize fluid cell values.
165  conv_sc = zero
166  conv_sp = zero
167 
168 ! Calculate the gas phase forces acting on each particle.
169  DO np=1,max_pip
170 
171  IF(.NOT.is_normal(np)) cycle
172  IF(.NOT.fluid_at(pijk(np,4))) cycle
173 
174 ! Calculate the heat transfer coefficient.
175  CALL calc_gamma_des(np, gamma)
176 
177 ! Calculate the surface area of the particle
178 
179  gammaxsa(np) = gamma*l4pi*des_radius(np)*des_radius(np)
180  gammaxsaxtp = gammaxsa(np)*des_t_s(np)
181 
182  IF(des_interp_on) THEN
183  DO lc=1,filter_size
184  ijk = filter_cell(lc,np)
185  weight = filter_weight(lc,np)
186 
187  conv_sc(ijk) = conv_sc(ijk) + weight*gammaxsaxtp
188  conv_sp(ijk) = conv_sp(ijk) + weight*gammaxsa(np)
189  ENDDO
190  ELSE
191  ijk = pijk(np,4)
192 
193  conv_sc(ijk) = conv_sc(ijk) + gammaxsaxtp
194  conv_sp(ijk) = conv_sp(ijk) + gammaxsa(np)
195  ENDIF
196 
197  ENDDO
198 
199 ! Add in data stored in ghost cells from interpolation. This call must
200 ! preceed the SEND_RECV to avoid overwriting ghost cell data.
201  IF(des_interp_on) THEN
202  CALL des_collect_gdata(conv_sc)
203  CALL des_collect_gdata(conv_sp)
204  ENDIF
205 
206 ! Update the drag force and sources in ghost layers.
207  CALL send_recv(conv_sc, 2)
208  CALL send_recv(conv_sp, 2)
209 
210  RETURN
211  END SUBROUTINE conv_gs_gas1
212 
213 
214 
215 
216 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
217 ! Subroutine: ZERO_ENERGY_SOURCE !
218 ! !
219 ! Purpose: ZERO out the array that passes energy source terms back to !
220 ! the continuum model. Additional entries may be needed to include !
221 ! heat transfer to the hybrid mode. !
222 ! !
223 ! Author: J.Musser Date: 15-Jan-11 !
224 ! !
225 ! Comments: !
226 ! !
227 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
228  SUBROUTINE zero_energy_source
230  Use des_thermo
231  Use param1
232 
233  IMPLICIT NONE
234 
235  conv_sc = zero
236  conv_sp = zero
237 
238  RETURN
239  END SUBROUTINE zero_energy_source
240 
double precision, dimension(:), allocatable gammaxsa
double precision, dimension(:), allocatable conv_sc
integer, dimension(:,:), allocatable filter_cell
double precision, dimension(:), allocatable des_t_s
double precision, parameter one
Definition: param1_mod.f:29
double precision, dimension(:), allocatable t_g
Definition: fldvar_mod.f:63
subroutine conv_gs_des1
subroutine conv_gs_gas1
double precision, dimension(:,:), allocatable filter_weight
double precision, dimension(:), allocatable conv_sp
logical no_k
Definition: geometry_mod.f:28
subroutine zero_energy_source
double precision, parameter pi
Definition: constant_mod.f:158
subroutine calc_gamma_des(NP, pGAMMA)
double precision, parameter zero
Definition: param1_mod.f:27