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