MFIX  2016-1
conv_rop_g.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
2 ! C
3 ! Subroutine: CONV_ROP_g C
4 ! Purpose: Determine convection terms for gas continuity C
5 ! equation. Master routine. C
6 ! C
7 ! Author: M. Syamlal Date: 19-MAR-97 C
8 ! Reviewer: Date: C
9 ! C
10 ! Literature/Document References: C
11 ! Variables referenced: C
12 ! Variables modified: C
13 ! Local variables: C
14 ! C
15 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
16 
17  SUBROUTINE conv_rop_g(A_M, B_M)
18 
19 !-----------------------------------------------
20 ! Modules
21 !-----------------------------------------------
22  USE param
23  USE param1
24  USE fldvar
25  USE run
26  USE compar
27  IMPLICIT NONE
28 !-----------------------------------------------
29 ! Dummy arguments
30 !-----------------------------------------------
31 ! Septadiagonal matrix A_m
32  DOUBLE PRECISION, INTENT(INOUT) :: A_m(dimension_3, -3:3, 0:dimension_m)
33 ! Vector b_m
34  DOUBLE PRECISION, INTENT(INOUT) :: B_m(dimension_3, 0:dimension_m)
35 !-----------------------------------------------
36 
37  IF (discretize(1) == 0) THEN ! 0 & 1 => first order upwinding
38  CALL conv_rop_g0 (a_m)
39  ELSE
40  CALL conv_rop_g1 (a_m)
41  ENDIF
42 
43 
44  RETURN
45  END SUBROUTINE conv_rop_g
46 
47 
48 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
49 ! C
50 ! Subroutine: CONV_ROP_g0 C
51 ! Purpose: Determine convection terms for gas continuity equation C
52 ! C
53 ! Notes: The off-diagonal coefficients calculated here must be C
54 ! positive. The center coefficient and the source vector C
55 ! are negative. -- First order upwinding C
56 ! C
57 ! Author: M. Syamlal Date: 2-JUL-96 C
58 ! Reviewer: Date: C
59 ! C
60 ! Literature/Document References: C
61 ! Variables referenced: C
62 ! Variables modified: C
63 ! Local variables: C
64 ! C
65 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
66 
67  SUBROUTINE conv_rop_g0(A_M)
68 
69 !-----------------------------------------------
70 ! Modules
71 !-----------------------------------------------
72  USE param
73  USE param1
74  USE fldvar
75  USE run
76  USE parallel
77  USE physprop
78  USE geometry
79  USE indices
80  USE pgcor
81  USE compar
82  USE functions
83  IMPLICIT NONE
84 !-----------------------------------------------
85 ! Dummy arguments
86 !-----------------------------------------------
87 ! Septadiagonal matrix A_m
88  DOUBLE PRECISION, INTENT(INOUT) :: A_m(dimension_3, -3:3, 0:dimension_m)
89 !-----------------------------------------------
90 ! Local variables
91 !-----------------------------------------------
92 ! Indices
93  INTEGER :: I, J, K, IJK, IPJK, IJPK, IJKP
94  INTEGER :: IMJK, IJMK, IJKM
95 !-----------------------------------------------
96 
97 
98 ! Calculate convection fluxes through each of the faces
99 
100 !!$omp parallel do private( J, K, IJK, IPJK, IJPK, IJKP, &
101 !!$omp& IMJK, IJMK, IJKM) &
102 !!$omp& schedule(static)
103  DO ijk = ijkstart3, ijkend3
104  IF (phase_4_p_g(ijk) /= 0) THEN
105 ! if phase_4_p_g is assigned the index of a solids phase then this
106 ! section is entered. currently, phase_4_p_g is always assigned to
107 ! the gas phase index 0 and so this section will never be entered.
108 
109 ! it was previously possible for phase_4_p_g to be assigned the index of
110 ! the gas phase in some cells, and the index of a solids phase in other
111 ! cells if that solids phase has close_packed=F and was in higher
112 ! concentrations than the gas. in such a case this branch would become
113 ! activated, while the corresponding solids continuity would become
114 ! skipped. moreover, that solids phase's volume fraction would be
115 ! corrected rather than the gas phases void fraction in calc_vol_fr.
116  i = i_of(ijk)
117  j = j_of(ijk)
118  k = k_of(ijk)
119  ipjk = ip_of(ijk)
120  ijpk = jp_of(ijk)
121  ijkp = kp_of(ijk)
122  imjk = im_of(ijk)
123  ijmk = jm_of(ijk)
124  ijkm = km_of(ijk)
125 
126 ! East face (i+1/2, j, k)
127  a_m(ijk,east,0) = zmax((-u_g(ijk)))*ayz(ijk)
128  a_m(ipjk,west,0) = zmax(u_g(ijk))*ayz(ijk)
129 
130 ! North face (i, j+1/2, k)
131  a_m(ijk,north,0) = zmax((-v_g(ijk)))*axz(ijk)
132  a_m(ijpk,south,0) = zmax(v_g(ijk))*axz(ijk)
133 
134 ! Top face (i, j, k+1/2)
135  IF (do_k) THEN
136  a_m(ijk,top,0) = zmax((-w_g(ijk)))*axy(ijk)
137  a_m(ijkp,bottom,0) = zmax(w_g(ijk))*axy(ijk)
138  ENDIF
139 
140 ! Modify west (i-1/2,j,k), south (i j-1/2,k) and bottom (i,j,k-1/2)
141 ! faces if the neighboring west, south, bottom cells have
142 ! phase_4_p_g of 0
143  IF(phase_4_p_g(imjk)==0) a_m(ijk,west,0)=zmax(u_g(imjk))*ayz(imjk)
144  IF(phase_4_p_g(ijmk)==0) a_m(ijk,south,0)=zmax(v_g(ijmk))*axz(ijmk)
145  IF (do_k) THEN
146  IF(phase_4_p_g(ijkm)==0) a_m(ijk,bottom,0)=zmax(w_g(ijkm))*axy(ijkm)
147  ENDIF
148 
149  ENDIF
150  ENDDO
151 
152  RETURN
153  END SUBROUTINE conv_rop_g0
154 
155 
156 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
157 ! C
158 ! Subroutine: CONV_ROP_g1 C
159 ! Purpose: Determine convection terms for gas continuity equation. C
160 ! C
161 ! Notes: The off-diagonal coefficients calculated here must be C
162 ! positive. The center coefficient and the source vector C
163 ! are negative. -- Higher order schemes C
164 ! C
165 ! Author: M. Syamlal Date:19-MAR-97 C
166 ! Reviewer: Date: C
167 ! C
168 ! Literature/Document References: C
169 ! Variables referenced: C
170 ! Variables modified: C
171 ! Local variables: C
172 ! C
173 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
174 
175  SUBROUTINE conv_rop_g1(A_M)
177 !-----------------------------------------------
178 ! Modules
179 !-----------------------------------------------
180  USE compar
181  USE fldvar
182  USE functions
183  USE geometry
184  USE indices
185  USE parallel
186  USE param
187  USE param1
188  USE pgcor
189  USE physprop
190  USE run
191  USE xsi
192  IMPLICIT NONE
193 !-----------------------------------------------
194 ! D u m m y A r g u m e n t s
195 !-----------------------------------------------
196 ! Septadiagonal matrix A_m
197  DOUBLE PRECISION, INTENT(INOUT) :: A_m(dimension_3, -3:3, 0:dimension_m)
198 !-----------------------------------------------
199 ! Local variables
200 !-----------------------------------------------
201 ! Indices
202  INTEGER :: I, J, K, IJK, IPJK, IJPK, IJKP
203  INTEGER :: IMJK, IJMK, IJKM
204 ! loezos
205  INTEGER :: incr
206 ! temporary use of global arrays:
207 ! xsi_array: convection weighting factors
208  DOUBLE PRECISION :: XSI_e(dimension_3), XSI_n(dimension_3),&
209  XSI_t(dimension_3)
210 !-----------------------------------------------
211 
212 
213 ! loezos
214  incr=0
215 
216 ! Calculate convection factors
217  CALL calc_xsi (discretize(1), rop_g, u_g, v_g, w_g, xsi_e, &
218  xsi_n, xsi_t,incr)
219 
220 ! Calculate convection fluxes through each of the faces
221 
222 !!$omp parallel do private( J, K, IJK, IPJK, IJPK, IJKP, &
223 !!$omp& IMJK, IJMK, IJKM) &
224 !!$omp& schedule(static)
225  DO ijk = ijkstart3, ijkend3
226  IF (phase_4_p_g(ijk) /= 0) THEN
227  i = i_of(ijk)
228  j = j_of(ijk)
229  k = k_of(ijk)
230  ipjk = ip_of(ijk)
231  ijpk = jp_of(ijk)
232  ijkp = kp_of(ijk)
233  imjk = im_of(ijk)
234  ijmk = jm_of(ijk)
235  ijkm = km_of(ijk)
236 
237 ! East face (i+1/2, j, k)
238  a_m(ijk,east,0) = -xsi_e(ijk)*u_g(ijk)*ayz(ijk)
239  a_m(ipjk,west,0) = (one - xsi_e(ijk))*u_g(ijk)*ayz(ijk)
240 
241 ! North face (i, j+1/2, k)
242  a_m(ijk,north,0) = -xsi_n(ijk)*v_g(ijk)*axz(ijk)
243  a_m(ijpk,south,0) = (one - xsi_n(ijk))*v_g(ijk)*axz(ijk)
244 
245 ! Top face (i, j, k+1/2)
246  IF (do_k) THEN
247  a_m(ijk,top,0) = -xsi_t(ijk)*w_g(ijk)*axy(ijk)
248  a_m(ijkp,bottom,0) = (one - xsi_t(ijk))*w_g(ijk)*axy(ijk)
249  ENDIF
250 
251 ! Modify west (i-1/2,j,k), south (i j-1/2,k) and bottom (i,j,k-1/2)
252 ! faces if the neighboring west, south, bottom cells have
253 ! phase_4_p_g of 0
254  IF (phase_4_p_g(imjk) == 0) a_m(ijk,west,0) = (one - xsi_e(imjk))*u_g(&
255  imjk)*ayz(imjk)
256  IF (phase_4_p_g(ijmk) == 0) a_m(ijk,south,0) = (one - xsi_n(ijmk))*v_g(&
257  ijmk)*axz(ijmk)
258  IF (do_k) THEN
259  IF (phase_4_p_g(ijkm) == 0) a_m(ijk,bottom,0) = (one - xsi_t(ijkm))*&
260  w_g(ijkm)*axy(ijkm)
261  ENDIF
262 
263  ENDIF
264  ENDDO
265 
266  RETURN
267  END SUBROUTINE conv_rop_g1
268 
269 
integer, dimension(:), allocatable i_of
Definition: indices_mod.f:45
integer ijkend3
Definition: compar_mod.f:80
Definition: pgcor_mod.f:1
subroutine conv_rop_g(A_M, B_M)
Definition: conv_rop_g.f:18
double precision, parameter one
Definition: param1_mod.f:29
integer dimension_3
Definition: param_mod.f:11
subroutine conv_rop_g1(A_M)
Definition: conv_rop_g.f:176
double precision, dimension(:), allocatable axy
Definition: geometry_mod.f:210
subroutine calc_xsi(DISCR, PHI, U, V, W, XSI_E, XSI_N, XSI_T, incr)
Definition: xsi_mod.f:23
integer east
Definition: param_mod.f:29
double precision, dimension(:), allocatable ayz
Definition: geometry_mod.f:206
Definition: xsi_mod.f:15
subroutine conv_rop_g0(A_M)
Definition: conv_rop_g.f:68
integer, dimension(:), allocatable k_of
Definition: indices_mod.f:47
integer, dimension(:), allocatable j_of
Definition: indices_mod.f:46
integer north
Definition: param_mod.f:37
double precision, dimension(:), allocatable v_g
Definition: fldvar_mod.f:99
integer south
Definition: param_mod.f:41
double precision, dimension(:), allocatable w_g
Definition: fldvar_mod.f:111
Definition: run_mod.f:13
double precision, dimension(:), allocatable axz
Definition: geometry_mod.f:208
Definition: param_mod.f:2
integer, dimension(:), allocatable phase_4_p_g
Definition: pgcor_mod.f:22
logical do_k
Definition: geometry_mod.f:30
integer ijkstart3
Definition: compar_mod.f:80
integer west
Definition: param_mod.f:33
double precision, dimension(:), allocatable u_g
Definition: fldvar_mod.f:87
integer top
Definition: param_mod.f:45
integer, dimension(dim_eqs) discretize
Definition: run_mod.f:67
integer dimension_m
Definition: param_mod.f:18
double precision, dimension(:), allocatable rop_g
Definition: fldvar_mod.f:38
integer bottom
Definition: param_mod.f:49