MFIX  2016-1
gas_drag.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2 ! !
3 ! Subroutine: GAS_DRAG_W !
4 ! Author: Jay Boyalakuntla Date: 12-Jun-04 !
5 ! !
6 ! Purpose: Account for the equal and opposite drag force on the gas !
7 ! phase due to particles by introducing the drag as a !
8 ! source term. Face centered. !
9 ! !
10 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
11  SUBROUTINE gas_drag_u(A_M, B_M, IER)
12 
13 ! Global Variables:
14 !---------------------------------------------------------------------//
15 ! Runtime Flag: Interpolate DES values
17 ! Flag: Gas sees the effect of particles in gas/solids flows.
18  use discretelement, only: des_oneway_coupled
19 ! Coefficient at cell corners added to the gas momentum A matix.
20  use discretelement, only: drag_am, f_gds
21 ! Coefficient at cell corners added to gas momentum B vector.
22  use discretelement, only: drag_bm
23 ! Volume of X-momentum cell
24  use geometry, only: vol_u
25 ! Flag to calculate Z direction
26  use geometry, only: do_k
27 
28 ! Global Parameters:
29 !---------------------------------------------------------------------//
30 ! Size of IJK arrays and solids phase..
31  use param, only: dimension_3, dimension_m
32 ! Fluid grid loop bounds.
33  use compar, only: ijkstart3, ijkend3
34 ! The I, J, and K values that comprise an IJK
35  use indices, only: i_of, j_of, k_of
36 ! Flag: Fluid exists at indexed cell
37  use functions, only: fluid_at
38 ! IJK of cell to east.
39  use functions, only: east_of
40 ! IJK function for I,J,K that includes mapped indices.
41  use compar, only: funijk_map_c
42 ! Function for averaging to a scalar cell's east face.
43  use fun_avg, only: avg_x
44 ! Domain index bounds.
45  use compar, only: istart2, jstart2, kstart2
46  use compar, only: iend2, jend2, kend2
47 
48  IMPLICIT NONE
49 
50 ! Dummy Arguments:
51 !---------------------------------------------------------------------//
52 ! Septadiagonal matrix A_m
53  DOUBLE PRECISION, INTENT(INOUT) :: A_M(dimension_3,-3:3,0:dimension_m)
54 ! Vector b_m
55  DOUBLE PRECISION, INTENT(INOUT) :: B_M(dimension_3, 0:dimension_m)
56 ! Error index
57  INTEGER, INTENT(INOUT) :: IER
58 
59 
60 ! Local Variables:
61 !---------------------------------------------------------------------//
62 ! Grid cell indices
63  INTEGER :: I, J, K, IJK, IJMK, IJKM, IJMKM, IJKE
64 ! temporary variables for matrix A_M and vector B_M
65  DOUBLE PRECISION :: tmp_A, tmp_B
66 ! Averaging factor
67  DOUBLE PRECISION :: AVG_FACTOR
68 !......................................................................!
69 
70 ! Initialize error flag.
71  ier = 0
72 
73 ! Skip this routine if the gas/solids are only one-way coupled.
74  IF(des_oneway_coupled) RETURN
75 
76 ! Average the interpoalted drag force from the cell corners to the cell face.
78 
79  avg_factor = merge(0.25d0, 0.5d0, do_k)
80 
81 !!$omp parallel do schedule(guided,50) default(none) &
82 !!$omp shared(IJKSTART3, IJKEND3, FUNIJK_MAP_C, I_OF, J_OF, &
83 !!$omp K_OF, DO_K, AVG_FACTOR, DRAG_AM, DRAG_BM, A_M, B_M, VOL_U) &
84 !!$omp private(IJK, I, J, K, IJMK, IJKM, IJMKM, tmp_A, tmp_B)
85  DO ijk = ijkstart3, ijkend3
86 
87  IF(.NOT.fluid_at(ijk)) cycle
88 
89  i = i_of(ijk)
90  j = j_of(ijk)
91  k = k_of(ijk)
92 
93  IF (i.LT.istart2 .OR. i.GT.iend2) cycle
94  IF (j.LT.jstart2 .OR. j.GT.jend2) cycle
95  IF (k.LT.kstart2 .OR. k.GT.kend2) cycle
96 
97  ijmk = funijk_map_c(i, j-1, k)
98 
99  tmp_a = -avg_factor*(drag_am(ijk) + drag_am(ijmk))
100  tmp_b = -avg_factor*(drag_bm(ijk,1) + drag_bm(ijmk,1))
101 
102  IF(do_k) THEN
103  ijkm = funijk_map_c(i, j, k-1)
104  ijmkm = funijk_map_c(i, j-1, k-1)
105  tmp_a = tmp_a - avg_factor* &
106  (drag_am(ijkm) + drag_am(ijmkm))
107  tmp_b = tmp_b - avg_factor* &
108  (drag_bm(ijkm,1) + drag_bm(ijmkm,1))
109  ENDIF
110 
111  a_m(ijk,0,0) = a_m(ijk,0,0) + tmp_a*vol_u(ijk)
112  b_m(ijk,0) = b_m(ijk,0) + tmp_b*vol_u(ijk)
113 
114  ENDDO
115 !!$omp end parallel do
116 
117  ELSE
118 
119 !$omp parallel do default(none) &
120 !$omp private(IJK, I, IJKE, tmp_A, tmp_B) &
121 !$omp shared(IJKSTART3,IJKEND3,I_OF, F_GDS, DRAG_BM, A_M, B_M, VOL_U)
122  DO ijk = ijkstart3, ijkend3
123  IF(fluid_at(ijk)) THEN
124  i = i_of(ijk)
125  ijke = east_of(ijk)
126 
127  tmp_a = avg_x(f_gds(ijk), f_gds(ijke), i)
128  tmp_b = avg_x(drag_bm(ijk,1), drag_bm(ijke,1), i)
129 
130  a_m(ijk,0,0) = a_m(ijk,0,0) - vol_u(ijk) * tmp_a
131  b_m(ijk,0) = b_m(ijk,0) - vol_u(ijk) * tmp_b
132  ENDIF
133  ENDDO
134 !$omp end parallel do
135  ENDIF
136 
137  END SUBROUTINE gas_drag_u
138 
139 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
140 ! !
141 ! Subroutine: GAS_DRAG_V !
142 ! Author: Jay Boyalakuntla Date: 12-Jun-04 !
143 ! !
144 ! Purpose: Account for the equal and opposite drag force on the gas !
145 ! phase due to particles by introducing the drag as a !
146 ! source term. Face centered. !
147 ! !
148 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
149  SUBROUTINE gas_drag_v(A_M, B_M, IER)
151 
152 ! Global Variables:
153 !---------------------------------------------------------------------//
154 ! Runtime Flag: Interpolate DES values
156 ! Flag: Gas sees the effect of particles in gas/solids flows.
157  use discretelement, only: des_oneway_coupled
158 ! Coefficient at cell corners added to the gas momentum A matix.
159  use discretelement, only: drag_am, f_gds
160 ! Coefficient at cell corners added to gas momentum B vector.
161  use discretelement, only: drag_bm
162 ! Volume of Y-momentum cell
163  use geometry, only: vol_v
164 ! Flag to calculate Z direction
165  use geometry, only: do_k
166 
167 ! Global Parameters:
168 !---------------------------------------------------------------------//
169 ! Size of IJK arrays and solids phase..
170  use param, only: dimension_3, dimension_m
171 ! Fluid grid loop bounds.
172  use compar, only: ijkstart3, ijkend3
173 ! The I, J, and K values that comprise an IJK
174  use indices, only: i_of, j_of, k_of
175 ! Flag: Fluid exists at indexed cell
176  use functions, only: fluid_at
177 ! IJK of cell to north.
178  use functions, only: north_of
179 ! IJK function for I,J,K that includes mapped indices.
180  use compar, only: funijk_map_c
181 ! Function for averaging to a scalar cell's north face.
182  use fun_avg, only: avg_y
183 ! Domain index bounds.
184  use compar, only: istart2, jstart2, kstart2
185  use compar, only: iend2, jend2, kend2
186 
187 
188  IMPLICIT NONE
189 
190 ! Dummy Arguments:
191 !---------------------------------------------------------------------//
192 ! Septadiagonal matrix A_m
193  DOUBLE PRECISION, INTENT(INOUT) :: A_M(dimension_3, -3:3, 0:dimension_m)
194 ! Vector b_m
195  DOUBLE PRECISION, INTENT(INOUT) :: B_M(dimension_3, 0:dimension_m)
196 ! Error index
197  INTEGER, INTENT(INOUT) :: IER
198 
199 ! Local Variables:
200 !---------------------------------------------------------------------//
201 ! Grid cell indices
202  INTEGER :: I, J, K, IJK, IMJK, IJKM, IMJKM, IJKN
203 ! temporary variables for matrix A_M and vector B_M
204  DOUBLE PRECISION tmp_A, tmp_B
205 ! Averaging factor
206  DOUBLE PRECISION :: AVG_FACTOR
207 !......................................................................!
208 
209 ! Initialize error flag.
210  ier = 0
211 
212 ! Skip this routine if the gas/solids are only one-way coupled.
213  IF(des_oneway_coupled) RETURN
214 
216 
217  avg_factor = merge(0.25d0, 0.5d0, do_k)
218 
219 !!$omp parallel do schedule (guided,50) default(none) &
220 !!$omp shared(IJKSTART3, IJKEND3, FUNIJK_MAP_C, I_OF, J_OF, &
221 !!$omp K_OF, DO_K, AVG_FACTOR, DRAG_AM, DRAG_BM, A_M, B_M, VOL_V) &
222 !!$omp private(IJK, I, J, K, IMJK, IJKM, IMJKM, tmp_A, tmp_B)
223  DO ijk = ijkstart3, ijkend3
224  IF(.NOT.fluid_at(ijk)) cycle
225 
226  i = i_of(ijk)
227  j = j_of(ijk)
228  k = k_of(ijk)
229 
230  IF (i.LT.istart2 .OR. i.GT.iend2) cycle
231  IF (j.LT.jstart2 .OR. j.GT.jend2) cycle
232  IF (k.LT.kstart2 .OR. k.GT.kend2) cycle
233 
234  imjk = funijk_map_c(i-1,j,k)
235 
236  tmp_a = -avg_factor*(drag_am(ijk) + drag_am(imjk))
237  tmp_b = -avg_factor*(drag_bm(ijk,2) + drag_bm(imjk,2))
238 
239  IF(do_k) THEN
240 
241  ijkm = funijk_map_c(i,j,k-1)
242  imjkm = funijk_map_c(i-1,j,k-1)
243 
244  tmp_a = tmp_a - avg_factor* &
245  (drag_am(ijkm) + drag_am(imjkm))
246  tmp_b = tmp_b - avg_factor* &
247  (drag_bm(ijkm,2) + drag_bm(imjkm,2))
248  ENDIF
249 
250  a_m(ijk,0,0) = a_m(ijk,0,0) + tmp_a*vol_v(ijk)
251  b_m(ijk,0) = b_m(ijk,0) + tmp_b*vol_v(ijk)
252 
253  ENDDO
254 !!$omp end parallel do
255 
256  ELSE
257 
258 !$omp parallel do default(none) &
259 !$omp private(IJK, J, IJKN, tmp_a, tmp_B) &
260 !$omp shared(IJKSTART3, IJKEND3, J_OF, F_GDS, DRAG_AM, DRAG_BM, A_M, B_M, VOL_V)
261  DO ijk = ijkstart3, ijkend3
262  IF(fluid_at(ijk)) THEN
263  j = j_of(ijk)
264  ijkn = north_of(ijk)
265 
266  tmp_a = avg_y(f_gds(ijk), f_gds(ijkn), j)
267  tmp_b = avg_y(drag_bm(ijk,2), drag_bm(ijkn,2), j)
268 
269  a_m(ijk,0,0) = a_m(ijk,0,0) - vol_v(ijk) * tmp_a
270  b_m(ijk,0) = b_m(ijk,0) - vol_v(ijk) * tmp_b
271  ENDIF
272  ENDDO
273 !$omp end parallel do
274  ENDIF
275 
276  END SUBROUTINE gas_drag_v
277 
278 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
279 ! !
280 ! Subroutine: GAS_DRAG_W !
281 ! Author: Jay Boyalakuntla Date: 12-Jun-04 !
282 ! !
283 ! Purpose: Account for the equal and opposite drag force on the gas !
284 ! phase due to particles by introducing the drag as a !
285 ! source term. Face centered. !
286 ! !
287 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
288  SUBROUTINE gas_drag_w(A_M, B_M, IER)
290 ! Global Variables:
291 !---------------------------------------------------------------------//
292 ! Runtime Flag: Interpolate DES values
294 ! Flag: Gas sees the effect of particles in gas/solids flows.
295  use discretelement, only: des_oneway_coupled
296 ! Coefficient at cell corners added to the gas momentum A matix.
297  use discretelement, only: drag_am, f_gds
298 ! Coefficient at cell corners added to gas momentum B vector.
299  use discretelement, only: drag_bm
300 ! Volume of Z-momentum cell
301  use geometry, only: vol_w
302 
303 ! Global Parameters:
304 !---------------------------------------------------------------------//
305 ! Size of IJK arrays and solids phase..
306  use param, only: dimension_3, dimension_m
307 ! Fluid grid loop bounds.
308  use compar, only: ijkstart3, ijkend3
309 ! The I, J, and K values that comprise an IJK
310  use indices, only: i_of, j_of, k_of
311 ! Flag: Fluid exists at indexed cell
312  use functions, only: fluid_at
313 ! IJK of cell to top.
314  use functions, only: top_of
315 ! IJK function for I,J,K that includes mapped indices.
316  use compar, only: funijk_map_c
317 ! Function for averaging to a scalar cell's north face.
318  use fun_avg, only: avg_z
319 ! Domain index bounds.
320  use compar, only: istart2, jstart2, kstart2
321  use compar, only: iend2, jend2, kend2
322 
323  IMPLICIT NONE
324 
325 ! Dummy Arguments:
326 !---------------------------------------------------------------------//
327 ! Septadiagonal matrix A_m
328  DOUBLE PRECISION, INTENT(INOUT) :: A_M(dimension_3,-3:3,0:dimension_m)
329 ! Vector b_m
330  DOUBLE PRECISION, INTENT(INOUT) :: B_M(dimension_3, 0:dimension_m)
331 ! Error index
332  INTEGER, INTENT(INOUT) :: IER
333 
334 ! Local Variables:
335 !---------------------------------------------------------------------//
336 ! Grid cell indices
337  INTEGER :: I, J, K, IJK, IMJK, IJMK, IMJMK, IJKT
338 ! temporary variables for matrix A_M and vector B_M
339  DOUBLE PRECISION tmp_A, tmp_B
340 ! Averaging factor
341 ! (=0.25 in 3D and =0.5 in 2D)
342  DOUBLE PRECISION :: AVG_FACTOR
343 !......................................................................!
344 
345 ! Initialize error flag.
346  ier = 0
347 
348 ! Skip this routine if the gas/solids are only one-way coupled.
349  IF(des_oneway_coupled) RETURN
350 
352 
353  avg_factor = 0.25d0
354 
355 !!$omp parallel do schedule (guided,50) default(none) &
356 !!$omp shared(IJKSTART3, IJKEND3, FUNIJK_MAP_C, I_OF, J_OF, &
357 !!$omp K_OF, AVG_FACTOR, DRAG_AM, DRAG_BM, A_M, B_M, VOL_W) &
358 !!$omp private(IJK, I, J, K, IMJK, IJMK, IMJMK, tmp_A, tmp_B)
359  DO ijk = ijkstart3, ijkend3
360  IF(.NOT.fluid_at(ijk)) cycle
361 
362  i = i_of(ijk)
363  j = j_of(ijk)
364  k = k_of(ijk)
365 
366  IF (i.LT.istart2 .OR. i.GT.iend2) cycle
367  IF (j.LT.jstart2 .OR. j.GT.jend2) cycle
368  IF (k.LT.kstart2 .OR. k.GT.kend2) cycle
369 
370  imjk = funijk_map_c(i-1,j,k)
371  ijmk = funijk_map_c(i,j-1,k)
372  imjmk = funijk_map_c(i-1,j-1,k)
373 
374  tmp_a = -avg_factor*(drag_am(ijk) + drag_am(imjk) + &
375  drag_am(ijmk) + drag_am(imjmk))
376 
377  tmp_b = -avg_factor*(drag_bm(ijk,3) + drag_bm(imjk,3) + &
378  drag_bm(ijmk,3) + drag_bm(imjmk,3))
379 
380  a_m(ijk,0,0) = a_m(ijk,0,0) + tmp_a*vol_w(ijk)
381  b_m(ijk,0) = b_m(ijk,0) + tmp_b*vol_w(ijk)
382 
383  ENDDO
384 !!$omp end parallel do
385 
386  ELSE
387 
388 !$omp parallel do default(none) &
389 !$omp private(IJK, K, IJKT, tmp_A, tmp_B) &
390 !$omp shared(IJKSTART3,IJKEND3,K_OF, F_GDS, DRAG_BM, A_M, B_M, VOL_W)
391  DO ijk = ijkstart3, ijkend3
392  IF(fluid_at(ijk)) THEN
393  k = k_of(ijk)
394  ijkt = top_of(ijk)
395 
396  tmp_a = avg_z(f_gds(ijk), f_gds(ijkt), k)
397  tmp_b = avg_z(drag_bm(ijk,3), drag_bm(ijkt,3), k)
398 
399  a_m(ijk,0,0) = a_m(ijk,0,0) - vol_w(ijk) * tmp_a
400  b_m(ijk,0) = b_m(ijk,0) - vol_w(ijk) * tmp_b
401  ENDIF
402  ENDDO
403 !$omp end parallel do
404 
405  ENDIF
406 
407  RETURN
408  END SUBROUTINE gas_drag_w
integer jend2
Definition: compar_mod.f:80
double precision, dimension(:), allocatable vol_w
Definition: geometry_mod.f:242
integer, dimension(:), allocatable i_of
Definition: indices_mod.f:45
integer ijkend3
Definition: compar_mod.f:80
integer, parameter des_interp_garg
integer dimension_3
Definition: param_mod.f:11
integer istart2
Definition: compar_mod.f:80
integer iend2
Definition: compar_mod.f:80
subroutine gas_drag_u(A_M, B_M, IER)
Definition: gas_drag.f:12
integer kend2
Definition: compar_mod.f:80
integer kstart2
Definition: compar_mod.f:80
integer, dimension(:), allocatable k_of
Definition: indices_mod.f:47
integer, dimension(:), allocatable j_of
Definition: indices_mod.f:46
integer jstart2
Definition: compar_mod.f:80
subroutine gas_drag_w(A_M, B_M, IER)
Definition: gas_drag.f:289
Definition: param_mod.f:2
integer des_interp_scheme_enum
logical do_k
Definition: geometry_mod.f:30
integer ijkstart3
Definition: compar_mod.f:80
double precision, dimension(:), allocatable vol_u
Definition: geometry_mod.f:224
integer dimension_m
Definition: param_mod.f:18
subroutine gas_drag_v(A_M, B_M, IER)
Definition: gas_drag.f:150
double precision, dimension(:), allocatable vol_v
Definition: geometry_mod.f:233