MFIX  2016-1
set_outflow.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
2 ! C
3 ! Subroutine: SET_OUTFLOW C
4 ! Purpose: Set specified outflow bc for pressure outflow, C
5 ! mass outflow, outflow and now also pressure inflow bc C
6 ! C
7 ! Author: M. Syamlal Date: 21-JAN-92 C
8 ! C
9 ! Comments: C
10 ! If the outflow boundary is on the W, S or B side of the domain and C
11 ! the component of velocity through the plane is defined then this C
12 ! routine will NOT modify it (i.e., its value from the momentum C
13 ! solver is maintained). C
14 ! C
15 ! In general it would seem this routine does little more than what C
16 ! is already done within the momentum routines in terms of velocity. C
17 ! The normal component is either 1) untouched if the outflow is on C
18 ! the W, S, B side of the domain or 2) is set to value of the C
19 ! adjacent fluid cell if it is on the E, N, T side (similar to the C
20 ! respective momentum bc routines). The primary addition here is C
21 ! that the tangential components of a bc cell are set to that of C
22 ! the adjacent fluid cell. Note the tangential components are not C
23 ! explicitly handled in the momentum _BC_ routines; instead their C
24 ! values are based on solution of the momentum equation which is C
25 ! replaced here C
26 ! C
27 ! Several routines are called which perform the following tasks: C
28 ! set_outflow_misc - several derived quantities are set in the C
29 ! boundary C
30 ! set_outflow_ep - the void/volume fraction and bulk densities are C
31 ! set in the boundary C
32 ! set_outflow_fluxes - convective fluxes are set in the boundary C
33 ! C
34 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
35  SUBROUTINE set_outflow(BCV)
36 
37 ! Modules
38 !---------------------------------------------------------------------//
39  use bc
40  use bc, only: bc_k_b, bc_k_t
41  use bc, only: bc_j_s, bc_j_n
42  use bc, only: bc_i_w, bc_i_e
43 
44  use fldvar, only: rop_g, rop_s
45  use fldvar, only: u_g, v_g, w_g
46  use fldvar, only: u_s, v_s, w_s
47  use physprop, only: mmax
48 
49  use functions, only: im_of, ip_of, jm_of, jp_of, km_of, kp_of
50  use functions, only: fluid_at
51  use functions, only: is_on_mype_plus2layers
52  use functions, only: funijk
53  use compar, only: dead_cell_at
54 
55  use param, only: dimension_m
56  use param1, only: undefined, zero
57  IMPLICIT NONE
58 
59 ! Dummy arguments
60 !---------------------------------------------------------------------//
61 ! Boundary condition number
62  INTEGER, INTENT(IN) :: BCV
63 
64 ! Local variables
65 !---------------------------------------------------------------------//
66 ! indices
67  INTEGER :: I, J, K, M
68 ! index for boundary cell
69  INTEGER :: IJK
70 ! index for a fluid cell adjacent to the boundary cell
71  INTEGER :: FIJK
72 ! local value for normal component of gas and solids velocity defined
73 ! such that
74  DOUBLE PRECISION :: RVEL_G, RVEL_S(dimension_m)
75 !---------------------------------------------------------------------//
76 
77 ! Loop over the range of boundary cells
78  DO k = bc_k_b(bcv), bc_k_t(bcv)
79  DO j = bc_j_s(bcv), bc_j_n(bcv)
80  DO i = bc_i_w(bcv), bc_i_e(bcv)
81 ! Check if current i,j,k resides on this PE
82  IF (.NOT.is_on_mype_plus2layers(i,j,k)) cycle
83  IF(dead_cell_at(i,j,k)) cycle
84  ijk = funijk(i,j,k)
85 
86 ! Fluid cell at West
87 ! --------------------------------------------------------------------//
88  IF (fluid_at(im_of(ijk))) THEN
89  fijk = im_of(ijk)
90  rvel_g = u_g(fijk)
91  IF (mmax>0) rvel_s(:mmax) = u_s(fijk,:mmax)
92 
93  CALL set_outflow_misc(bcv, ijk, fijk)
94  CALL set_outflow_ep(bcv, ijk, fijk, rvel_g, rvel_s)
95  IF (bc_type_enum(bcv)==p_inflow) &
96  CALL set_pinoutflow(bcv, ijk, fijk, rvel_g, rvel_s)
97 
98 ! Set the boundary cell value of the normal component of velocity
99 ! according to the value in the adjacent fluid cell. Note the value
100 ! of the boundary velocity is a scaled version of the value of the
101 ! adjacent fluid velocity based on the concentration ratio of the fluid
102 ! cell to the boundary cell.
103 ! - For the gas phase, this ratio is most likely 1 except for
104 ! compressible cases with a PO/PI boundary where P_g of the boundary
105 ! is set and may differ from the value of the adjacent fluid cell.
106 ! - For the solids phase this seems unnecessary..? Differences may arise
107 ! if bc_rop_s is set...
108  IF (rop_g(ijk) > zero) THEN
109  u_g(ijk) = rop_g(fijk)*u_g(fijk)/rop_g(ijk)
110  ELSE
111  u_g(ijk) = zero
112  ENDIF
113 
114 ! the tangential components are not explicitly handled in the boundary
115 ! condition routines of the corresponding momentum equation
116  v_g(ijk) = v_g(fijk)
117  w_g(ijk) = w_g(fijk)
118 
119  IF (mmax > 0) THEN
120  WHERE (rop_s(ijk,:mmax) > zero)
121  u_s(ijk,:mmax) = rop_s(fijk,:mmax)*&
122  u_s(fijk,:mmax)/rop_s(ijk,:mmax)
123  ELSEWHERE
124  u_s(ijk,:mmax) = zero
125  END WHERE
126  v_s(ijk,:mmax) = v_s(fijk,:mmax)
127  w_s(ijk,:mmax) = w_s(fijk,:mmax)
128  ENDIF
129 
130  CALL set_outflow_fluxes(ijk, fijk)
131  ENDIF ! end if (fluid_at(im_of(ijk)))
132 
133 
134 ! Fluid cell at East
135 ! --------------------------------------------------------------------//
136  IF (fluid_at(ip_of(ijk))) THEN
137  fijk = ip_of(ijk)
138 ! define normal component such that it is positive when exiting the
139 ! domain
140  rvel_g = -u_g(ijk)
141  IF (mmax >0) rvel_s(:mmax) = -u_s(ijk,:mmax)
142 
143  CALL set_outflow_misc(bcv, ijk, fijk)
144  CALL set_outflow_ep(bcv, ijk, fijk, rvel_g, rvel_s)
145  IF (bc_type_enum(bcv)==p_inflow) &
146  CALL set_pinoutflow(bcv, ijk, fijk, rvel_g, rvel_s)
147 
148 ! provide an initial value for the velocity component through the domain
149 ! otherwise its present value (from solution of the corresponding
150 ! momentum eqn) is kept. values for the velocity components in the off
151 ! directions are modified (needed for PO or O boundaries but not MO or
152 ! PI as velocities should be fully specified by this point)
153  IF (u_g(ijk) == undefined) THEN
154  IF (rop_g(ijk) > zero) THEN
155  u_g(ijk) = rop_g(fijk)*u_g(fijk)/rop_g(ijk)
156  ELSE
157  u_g(ijk) = zero
158  ENDIF
159  ENDIF
160  v_g(ijk) = v_g(fijk)
161  w_g(ijk) = w_g(fijk)
162 
163  DO m = 1, mmax
164  IF (u_s(ijk,m) == undefined) THEN
165  IF (rop_s(ijk,m) > zero) THEN
166  u_s(ijk,m) = rop_s(fijk,m)*&
167  u_s(fijk,m)/rop_s(ijk,m)
168  ELSE
169  u_s(ijk,m) = zero
170  ENDIF
171  ENDIF
172  v_s(ijk,m) = v_s(fijk,m)
173  w_s(ijk,m) = w_s(fijk,m)
174  ENDDO
175 
176  CALL set_outflow_fluxes(ijk, fijk)
177  ENDIF ! end if (fluid_at(ip_of(ijk)))
178 
179 
180 ! Fluid cell at South
181 ! --------------------------------------------------------------------//
182  IF (fluid_at(jm_of(ijk))) THEN
183  fijk = jm_of(ijk)
184  rvel_g = v_g(fijk)
185  IF(mmax>0) rvel_s(:mmax) = v_s(fijk,:mmax)
186 
187  CALL set_outflow_misc(bcv, ijk, fijk)
188  CALL set_outflow_ep(bcv, ijk, fijk, rvel_g, rvel_s)
189  IF (bc_type_enum(bcv)==p_inflow) &
190  CALL set_pinoutflow(bcv, ijk, fijk, rvel_g, rvel_s)
191 
192  IF (rop_g(ijk) > zero) THEN
193  v_g(ijk) = rop_g(fijk)*v_g(fijk)/rop_g(ijk)
194  ELSE
195  v_g(ijk) = zero
196  ENDIF
197  u_g(ijk) = u_g(fijk)
198  w_g(ijk) = w_g(fijk)
199 
200  IF (mmax > 0) THEN
201  WHERE (rop_s(ijk,:mmax) > zero)
202  v_s(ijk,:mmax) = rop_s(fijk,:mmax)*&
203  v_s(fijk,:mmax)/rop_s(ijk,:mmax)
204  ELSEWHERE
205  v_s(ijk,:mmax) = zero
206  END WHERE
207  u_s(ijk,:mmax) = u_s(fijk,:mmax)
208  w_s(ijk,:mmax) = w_s(fijk,:mmax)
209  ENDIF
210 
211  CALL set_outflow_fluxes(ijk, fijk)
212  ENDIF ! end if (fluid_at(jm_of(ijk)))
213 
214 
215 ! Fluid cell at North
216 ! --------------------------------------------------------------------//
217  IF (fluid_at(jp_of(ijk))) THEN
218  fijk = jp_of(ijk)
219  rvel_g = -v_g(ijk)
220  IF (mmax>0) rvel_s(:mmax) = -v_s(ijk,:mmax)
221 
222  CALL set_outflow_misc(bcv, ijk, fijk)
223  CALL set_outflow_ep(bcv, ijk, fijk, rvel_g, rvel_s)
224  IF (bc_type_enum(bcv)==p_inflow) &
225  CALL set_pinoutflow(bcv, ijk, fijk, rvel_g, rvel_s)
226 
227  IF (v_g(ijk) == undefined) THEN
228  IF (rop_g(ijk) > zero) THEN
229  v_g(ijk) = rop_g(fijk)*v_g(fijk)/rop_g(ijk)
230  ELSE
231  v_g(ijk) = zero
232  ENDIF
233  ENDIF
234  u_g(ijk) = u_g(fijk)
235  w_g(ijk) = w_g(fijk)
236 
237  DO m = 1, mmax
238  IF (v_s(ijk,m) == undefined) THEN
239  IF (rop_s(ijk,m) > zero) THEN
240  v_s(ijk,m) = rop_s(fijk,m)*&
241  v_s(fijk,m)/rop_s(ijk,m)
242  ELSE
243  v_s(ijk,m) = zero
244  ENDIF
245  ENDIF
246  u_s(ijk,m) = u_s(fijk,m)
247  w_s(ijk,m) = w_s(fijk,m)
248  ENDDO
249 
250  CALL set_outflow_fluxes(ijk, fijk)
251  ENDIF ! if (fluid_at(jp_of(ijk)))
252 
253 
254 ! Fluid cell at Bottom
255 ! --------------------------------------------------------------------//
256  IF (fluid_at(km_of(ijk))) THEN
257  fijk = km_of(ijk)
258  rvel_g = w_g(fijk)
259  IF (mmax>0) rvel_s(:mmax) = w_s(fijk,:mmax)
260 
261  CALL set_outflow_misc(bcv, ijk, fijk)
262  CALL set_outflow_ep(bcv, ijk, fijk, rvel_g, rvel_s)
263  IF (bc_type_enum(bcv)==p_inflow) &
264  CALL set_pinoutflow(bcv, ijk, fijk, rvel_g, rvel_s)
265 
266  IF (rop_g(ijk) > zero) THEN
267  w_g(ijk) = rop_g(fijk)*w_g(fijk)/rop_g(ijk)
268  ELSE
269  w_g(ijk) = zero
270  ENDIF
271  u_g(ijk) = u_g(fijk)
272  v_g(ijk) = v_g(fijk)
273 
274  IF (mmax > 0) THEN
275  WHERE (rop_s(ijk,:mmax) > zero)
276  w_s(ijk,:mmax) = rop_s(fijk,:mmax)*&
277  w_s(fijk,:mmax)/rop_s(ijk,:mmax)
278  ELSEWHERE
279  w_s(ijk,:mmax) = zero
280  END WHERE
281  u_s(ijk,:mmax) = u_s(fijk,:mmax)
282  v_s(ijk,:mmax) = v_s(fijk,:mmax)
283  ENDIF
284 
285  CALL set_outflow_fluxes(ijk, fijk)
286  ENDIF ! if (fluid_at(km_of(ijk)))
287 
288 
289 ! Fluid cell at Top
290 ! --------------------------------------------------------------------//
291  IF (fluid_at(kp_of(ijk))) THEN
292  fijk = kp_of(ijk)
293  rvel_g = -w_g(ijk)
294  IF (mmax>0) rvel_s(:mmax) = -w_s(ijk,:mmax)
295 
296  CALL set_outflow_misc(bcv, ijk, fijk)
297  CALL set_outflow_ep(bcv, ijk, fijk, rvel_g, rvel_s)
298  IF (bc_type_enum(bcv)==p_inflow) &
299  CALL set_pinoutflow(bcv, ijk, fijk, rvel_g, rvel_s)
300 
301  IF (w_g(ijk) == undefined) THEN
302  IF (rop_g(ijk) > zero) THEN
303  w_g(ijk) = rop_g(fijk)*w_g(fijk)/rop_g(ijk)
304  ELSE
305  w_g(ijk) = zero
306  ENDIF
307  ENDIF
308  u_g(ijk) = u_g(fijk)
309  v_g(ijk) = v_g(fijk)
310 
311  DO m = 1, mmax
312  IF (w_s(ijk,m) == undefined) THEN
313  IF (rop_s(ijk,m) > zero) THEN
314  w_s(ijk,m) = rop_s(fijk,m)*&
315  w_s(fijk,m)/rop_s(ijk,m)
316  ELSE
317  w_s(ijk,m) = zero
318  ENDIF
319  ENDIF
320  u_s(ijk,m) = u_s(fijk,m)
321  v_s(ijk,m) = v_s(fijk,m)
322  ENDDO
323 
324  CALL set_outflow_fluxes(ijk, fijk)
325  ENDIF ! if (fluid_at(kp_of(ijk)))
326 
327  ENDDO ! end do (i=i1,i2)
328  ENDDO ! end do (j=j1,j2)
329  ENDDO ! end do (k=k1,k2)
330 
331  RETURN
332  END SUBROUTINE set_outflow
333 
334 
335 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
336 ! C
337 ! Subroutine: SET_OUTFLOW_MISC C
338 ! Purpose: Set the value of certain variables in the specified C
339 ! outflow boundary cell that would not otherwise be set according C
340 ! to their value in the adjacent fluid cell. C
341 ! C
342 ! READ BEFORE MODIFYING!! C
343 ! For many of the scalar field variables (e.g., T_g, T_s, X_g, X_s, C
344 ! k_turb_g, e_turb_g, theta_m and scalar) their corresponding C
345 ! governing equation solver routine sets its own value in the C
346 ! boundary cell (see bc_phi). So DO NOT set their value here unless C
347 ! a clear explanation to the need is also provided; more likely it C
348 ! should simply be dealt with in the governing equation routine. C
349 ! C
350 ! This routine sets the value of quantites that are derived or with C
351 ! unique solver routines (e.g., P_star, P_s, MW_MIX_g, P_g) since no C
352 ! other routine will. C
353 ! C
354 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
355  SUBROUTINE set_outflow_misc(BCV, IJK, FIJK)
357 ! Global variables
358 !---------------------------------------------------------------------//
359  use bc
360  use run, only: kt_type_enum, ghd_2007
361  use fldvar, only: p_g, ro_g, t_g
362  use fldvar, only: p_s, p_star
363  use physprop, only: smax, mmax
364  use physprop, only: ro_g0, mw_mix_g
365  use eos, only: eosg
366 
367 ! Global parameters
368 !---------------------------------------------------------------------//
369  use param1, only: undefined
370  IMPLICIT NONE
371 
372 ! Dummy arguments
373 !---------------------------------------------------------------------//
374 ! Boundary condition number
375  INTEGER, INTENT(IN) :: BCV
376 ! ijk index for boundary cell
377  INTEGER, INTENT(IN) :: IJK
378 ! ijk index for adjacent fluid cell
379  INTEGER, INTENT(IN) :: FIJK
380 !---------------------------------------------------------------------//
381 
382  IF (bc_type_enum(bcv) /= p_outflow .AND. &
383  bc_type_enum(bcv) /= p_inflow) p_g(ijk) = p_g(fijk)
384 
385  mw_mix_g(ijk) = mw_mix_g(fijk)
386 
387 ! T_g (bc_phi), P_g (above depending on bc), and MW_MIX_G (above) have
388 ! now been defined at IJK
389  IF (ro_g0 == undefined) ro_g(ijk) = &
390  eosg(mw_mix_g(ijk),p_g(ijk),t_g(ijk))
391 
392  IF (smax >0) THEN
393  p_star(ijk) = p_star(fijk)
394  p_s(ijk,:smax) = p_s(fijk,:smax)
395  ENDIF
396 
397  IF (kt_type_enum == ghd_2007 .AND. mmax>0) &
398  p_s(ijk,mmax) = p_s(fijk,mmax)
399 
400  RETURN
401  END SUBROUTINE set_outflow_misc
402 
403 
404 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
405 ! C
406 ! Subroutine: SET_OUTFLOW_EP C
407 ! Purpose: Set the volume fraction/bulk density (i.e., ROP_s, EP_g C
408 ! ROP_S) in the specified outflow boundary cell that would not C
409 ! otherwise be set according to their value in the adjacent fluid C
410 ! cell. C
411 ! C
412 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
413  SUBROUTINE set_outflow_ep(BCV, IJK, FIJK, RVEL_G, RVEL_S)
415 ! Global variables
416 !---------------------------------------------------------------------//
417  use bc
418  use run, only: kt_type_enum, ghd_2007
419  use physprop, only: smax, mmax
420  use fldvar, only: rop_g, ro_g, ep_g
421  use fldvar, only: rop_s, ep_s
422  use discretelement, only: discrete_element, des_mmax
423 ! Global parameters
424 !---------------------------------------------------------------------//
425  use param, only: dimension_m
426  use param1, only: undefined, zero, one
427  IMPLICIT NONE
428 
429 ! Dummy arguments
430 !---------------------------------------------------------------------//
431 ! Boundary condition number
432  INTEGER, INTENT(IN) :: BCV
433 ! ijk index for boundary cell
434  INTEGER, INTENT(IN) :: IJK
435 ! ijk index for adjacent fluid cell
436  INTEGER, INTENT(IN) :: FIJK
437 ! the gas or solids velocity in the fluid cell adjacent to the boundary
438 ! cell dot with the outward normal of that bc plane; defines the gas or
439 ! solids velocity component normal to the bc plane as positive when it
440 ! is flowing into the bc cell from the fluid cell. so, for example, for
441 ! an outflow on the eastern boundary this is the u component of velocity
442 ! while for an outflow on the western boundary this is the -u component,
443 ! etc.
444  DOUBLE PRECISION, INTENT(IN) :: RVEL_G
445  DOUBLE PRECISION, INTENT(IN), DIMENSION(DIMENSION_M) :: RVEL_S
446 
447 ! Local variables
448 !---------------------------------------------------------------------//
449 ! indices
450  INTEGER :: M
451 ! sum of solids phases volume fractions
452  DOUBLE PRECISION :: SUM_EPs
453 ! sum of solids phases bulk densities
454  DOUBLE PRECISION :: SUM_ROPS
455  LOGICAL, SAVE :: FIRST_PASS = .true.
456 !---------------------------------------------------------------------//
457 
458 ! initializing summation quantities
459  sum_rops = zero
460  sum_eps = zero
461 
462  DO m = 1, smax
463 
464  IF(bc_type_enum(bcv) == p_inflow) THEN
465  rop_s(ijk,m) = rop_s(fijk,m)
466  ELSE
467 ! the outflow type bc do not permit 're-entering' solids, in which
468 ! case the solids are removed
469  IF (rvel_s(m) >= zero) THEN
470 ! solids are leaving the domain
471  rop_s(ijk,m) = rop_s(fijk,m)
472  ELSE
473 ! solids cannot enter the domain at an outflow cell
474  rop_s(ijk,m) = zero
475  ENDIF
476  ENDIF
477 
478 ! if bc_rop_s is defined, set value of rop_s in the ijk boundary cell
479 ! according to user definition
480  IF(bc_rop_s(bcv,m)/=undefined) rop_s(ijk,m)=bc_rop_s(bcv,m)
481 
482 ! add to total solids phase bulk density and solids volume fraction
483  sum_rops = sum_rops + rop_s(ijk,m)
484  sum_eps = sum_eps + ep_s(ijk,m)
485  ENDDO ! end do (m=1,smax)
486 
487  IF (kt_type_enum == ghd_2007) rop_s(ijk,mmax) = sum_rops
488 
489 ! this section must be skipped until after the initial setup of the
490 ! discrete element portion of the simulation (set_bc1 is called once
491 ! before the initial dem setup).
492  IF (discrete_element .AND. .NOT.first_pass) THEN
493  first_pass = .false.
494  DO m = mmax+1, des_mmax+mmax
495 ! unlike in the two fluid model, in the discrete element model it is
496 ! possible to actually calculate the bulk density in a flow boundary
497 ! cell. Currently, however, such calculations are not strictly enforced.
498 ! therefore use the bulk density of the adjacent fluid cell
499  rop_s(ijk,m) = rop_s(fijk,m)
500  sum_rops = sum_rops + rop_s(ijk,m)
501  sum_eps = sum_eps + ep_s(ijk,m)
502  ENDDO
503  ENDIF
504 
505 ! if bc_ep_g undefined, set ep_g accordingly (based on flow condition
506 ! or based on bc_rop_s). if bc_ep_g is defined its set value will be
507 ! maintained (from set_bc0).
508  IF (bc_ep_g(bcv) == undefined) ep_g(ijk) = one - sum_eps
509 
510 ! now that ep_g in the boundary cell is known, define the bulk density
511 ! of the gas phase in the boundary cell
512  rop_g(ijk) = ro_g(ijk)*ep_g(ijk)
513 
514  RETURN
515  END SUBROUTINE set_outflow_ep
516 
517 
518 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
519 ! C
520 ! Purpose: Update convective fluxes.... C
521 ! Set the value of the convective fluxes in the specified boundary C
522 ! cell according to their value in the adjacent fluid cell. C
523 ! C
524 ! Comment/concern: C
525 ! Should these be assigned in the same method as the velocity? Note C
526 ! if bc_plane is W, S, B then the normal component of velocity may be C
527 ! assigned a zero value as opposed to value of its neighboring fluid C
528 ! cell. This routine would seem to introduce some inconsistency C
529 ! between velocity and flux at boundary. C
530 ! C
531 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
532 
533  SUBROUTINE set_outflow_fluxes(IJK,FIJK)
535 ! Global variables
536 !---------------------------------------------------------------------//
537  use physprop, only: mmax
538  use run, only: kt_type_enum, ghd_2007
539  use run, only: added_mass
540  use mflux, only: flux_ge, flux_gn, flux_gt
541  use mflux, only: flux_se, flux_sn, flux_st
542  use mflux, only: flux_ne, flux_nn, flux_nt
543  use mflux, only: flux_gse, flux_gsn, flux_gst
544  use mflux, only: flux_sse, flux_ssn, flux_sst
545 
546 ! Dummy arguments
547 !---------------------------------------------------------------------//
548 ! ijk index for boundary cell
549  INTEGER, INTENT(IN) :: IJK
550 ! ijk index for adjacent fluid cell
551  INTEGER, INTENT(IN) :: FIJK
552 !---------------------------------------------------------------------//
553 
554  flux_ge(ijk) = flux_ge(fijk)
555  flux_gn(ijk) = flux_gn(fijk)
556  flux_gt(ijk) = flux_gt(fijk)
557  IF (mmax >0) THEN
558  flux_se(ijk,:mmax) = flux_se(fijk,:mmax)
559  flux_sn(ijk,:mmax) = flux_sn(fijk,:mmax)
560  flux_st(ijk,:mmax) = flux_st(fijk,:mmax)
561  ENDIF
562 
563  IF(added_mass) THEN
564  flux_gse(ijk) = flux_gse(fijk)
565  flux_gsn(ijk) = flux_gsn(fijk)
566  flux_gst(ijk) = flux_gst(fijk)
567  IF (mmax >0) THEN
568  flux_sse(ijk) = flux_sse(fijk)
569  flux_ssn(ijk) = flux_ssn(fijk)
570  flux_sst(ijk) = flux_sst(fijk)
571  ENDIF
572  ENDIF
573 
574  IF (kt_type_enum == ghd_2007) THEN
575  flux_ne(ijk) = flux_ne(fijk)
576  flux_nn(ijk) = flux_nn(fijk)
577  flux_nt(ijk) = flux_nt(fijk)
578  ENDIF
579 
580  RETURN
581  END SUBROUTINE set_outflow_fluxes
582 
583 
584 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
585 ! C
586 ! Purpose: Specify the field variable in the bc cell depending on the C
587 ! flow direction. If flow is into domain apply user specified BC. If C
588 ! the flow is out of the domain follow outflow type approach wherein C
589 ! the value of the adjacent fluid cell is applied to the bc cell. C
590 ! C
591 ! WARNING: this routine only serves to specify the field variables C
592 ! whose governing solver routine invokes bc_phi! do not insert any C
593 ! other settings here (such as derived quantities) as it is likely C
594 ! not appropriate!! C
595 ! C
596 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
597 
598  SUBROUTINE set_pinoutflow(BCV,IJK,FIJK,RVEL_G,RVEL_S)
600 ! Global variables
601 !---------------------------------------------------------------------//
602  use bc, only: bc_t_g, bc_x_g
603  use bc, only: bc_scalar, bc_k_turb_g, bc_e_turb_g
604  use bc, only: bc_t_s, bc_x_s, bc_theta_m
605  use fldvar, only: t_g, t_s, theta_m
606  use fldvar, only: x_g, x_s, scalar
607  use fldvar, only: k_turb_g, e_turb_g
608 ! needed because of ghd theory
609  use fldvar, only: rop_s, ro_s, d_p
610  use run, only: kt_type_enum, ghd_2007
611  use run, only: k_epsilon
612  use physprop, only: nmax, smax, mmax
613  use scalars, only: nscalar, phase4scalar
614 
615 ! Global parameters
616 !---------------------------------------------------------------------//
617  use param, only: dimension_m
618  use param1, only: zero
619  use constant, only: pi
620  IMPLICIT NONE
621 
622 ! Dummy arguments
623 !---------------------------------------------------------------------//
624 ! Boundary condition number
625  INTEGER, INTENT(IN) :: BCV
626 ! index for boundary cell
627  INTEGER, INTENT(IN) :: IJK
628 ! index for a fluid cell adjacent to the boundary cell
629  INTEGER, INTENT(IN) :: FIJK
630 ! gas and solids velocity defined to be positive when flow is leaving
631 ! the domain (outflow!)
632  DOUBLE PRECISION, INTENT(IN) :: RVEL_G, RVEL_S(dimension_m)
633 
634 ! Local variables
635 !---------------------------------------------------------------------//
636 ! number density
637  DOUBLE PRECISION :: Nm, NTot
638 ! indices
639  INTEGER :: M, N, Ms
640 !---------------------------------------------------------------------//
641 
642 ! address gas phase
643  IF (rvel_g < 0) THEN ! inflow (apply BC)
644  t_g(ijk) = bc_t_g(bcv)
645  IF (nmax(0) > 0) &
646  x_g(ijk,:nmax(0)) = bc_x_g(bcv,:nmax(0))
647  IF (k_epsilon) THEN
648  k_turb_g(ijk) = bc_k_turb_g(bcv)
649  e_turb_g(ijk) = bc_e_turb_g(bcv)
650  ENDIF
651  IF (nscalar > 0) THEN
652  DO n = 1,nscalar
653  ms = phase4scalar(n)
654  IF (ms == 0) &
655  scalar(ijk, n) = bc_scalar(bcv,n)
656  ENDDO
657  ENDIF
658  ELSE ! outflow (apply neighbor fluid)
659  t_g(ijk) = t_g(fijk)
660  IF (nmax(0) > 0) &
661  x_g(ijk,:nmax(0)) = x_g(fijk,:nmax(0))
662  IF(k_epsilon) THEN
663  k_turb_g(ijk) = k_turb_g(fijk)
664  e_turb_g(ijk) = e_turb_g(fijk)
665  ENDIF
666  IF (nscalar >0) THEN
667  DO n = 1, nscalar
668  ms = phase4scalar(n)
669  IF (ms == 0) &
670  scalar(ijk, n) = scalar(fijk, n)
671  ENDDO
672  ENDIF
673  ENDIF ! end gas phase
674 
675 ! address solids phases
676  DO m = 1, smax
677  IF (rvel_s(m) < 0) THEN ! inflow (apply BC)
678  t_s(ijk,m) = bc_t_s(bcv,m)
679  theta_m(ijk,m) = bc_theta_m(bcv,m)
680  IF (nmax(m) > 0) &
681  x_s(ijk,m,:nmax(m)) = bc_x_s(bcv,m,:nmax(m))
682  IF (nscalar > 0) THEN
683  DO n = 1,nscalar
684  ms = phase4scalar(n)
685  IF (ms == m) &
686  scalar(ijk, n) = bc_scalar(bcv,n)
687  ENDDO
688  ENDIF
689  ELSE ! outflow (apply neighbor fluid)
690  t_s(ijk,m) = t_s(fijk,m)
691  theta_m(ijk,m) = theta_m(fijk,m)
692  IF (nmax(m) > 0) &
693  x_s(ijk,m,:nmax(m)) = x_s(fijk,m,:nmax(m))
694  IF (nscalar > 0) THEN
695  DO n = 1,nscalar
696  ms = phase4scalar(n)
697  IF (ms == m) &
698  scalar(ijk, n) = scalar(fijk,n)
699  ENDDO
700  ENDIF
701  ENDIF
702  ENDDO
703 
704 
705 ! derived BC field quantity (since it has no explicit user defined BC)
706  IF(kt_type_enum == ghd_2007) THEN
707  ntot = zero
708  DO m = 1, smax
709  nm = rop_s(ijk,m)*6d0/ &
710  (pi*d_p(ijk,m)**3*ro_s(ijk,m))
711  ntot = ntot + nm
712  theta_m(ijk,mmax) = theta_m(ijk,mmax) + &
713  nm*theta_m(ijk,m)
714  ENDDO
715  IF (ntot > zero) &
716  theta_m(ijk,mmax) = theta_m(ijk,mmax) / ntot
717  ENDIF
718 
719  RETURN
720  END SUBROUTINE set_pinoutflow
integer, dimension(dimension_bc) bc_k_b
Definition: bc_mod.f:70
double precision, dimension(:), allocatable flux_ge
Definition: mflux_mod.f:13
double precision, dimension(:), allocatable flux_ne
Definition: mflux_mod.f:51
double precision, dimension(:,:), allocatable v_s
Definition: fldvar_mod.f:105
subroutine set_outflow_misc(BCV, IJK, FIJK)
Definition: set_outflow.f:356
double precision, dimension(:), allocatable ep_g
Definition: fldvar_mod.f:15
double precision, dimension(:), allocatable flux_gst
Definition: mflux_mod.f:32
double precision, dimension(dimension_bc) bc_t_g
Definition: bc_mod.f:97
double precision, dimension(:,:), allocatable flux_st
Definition: mflux_mod.f:24
double precision, dimension(:), allocatable k_turb_g
Definition: fldvar_mod.f:161
double precision, parameter one
Definition: param1_mod.f:29
integer, dimension(dimension_bc) bc_i_w
Definition: bc_mod.f:54
logical added_mass
Definition: run_mod.f:91
double precision, dimension(:,:), allocatable w_s
Definition: fldvar_mod.f:117
integer, dimension(dimension_bc) bc_j_n
Definition: bc_mod.f:66
double precision, dimension(dimension_bc, dim_m, dim_n_s) bc_x_s
Definition: bc_mod.f:254
double precision, dimension(:), allocatable t_g
Definition: fldvar_mod.f:63
double precision, dimension(:), allocatable flux_ssn
Definition: mflux_mod.f:31
double precision, dimension(:,:), allocatable scalar
Definition: fldvar_mod.f:155
subroutine set_outflow_ep(BCV, IJK, FIJK, RVEL_G, RVEL_S)
Definition: set_outflow.f:414
double precision, dimension(:), allocatable p_g
Definition: fldvar_mod.f:26
integer, dimension(dimension_bc) bc_type_enum
Definition: bc_mod.f:146
double precision, parameter undefined
Definition: param1_mod.f:18
double precision, dimension(:,:), allocatable u_s
Definition: fldvar_mod.f:93
double precision, dimension(:), allocatable flux_gse
Definition: mflux_mod.f:28
double precision, dimension(:,:), allocatable d_p
Definition: fldvar_mod.f:57
double precision function eosg(MW, PG, TG)
Definition: eos_mod.f:22
integer, dimension(dimension_bc) bc_k_t
Definition: bc_mod.f:74
integer mmax
Definition: physprop_mod.f:19
logical, dimension(:,:,:), allocatable dead_cell_at
Definition: compar_mod.f:127
double precision, dimension(:,:,:), allocatable x_s
Definition: fldvar_mod.f:78
double precision, dimension(dimension_bc, dim_m) bc_t_s
Definition: bc_mod.f:101
double precision ro_g0
Definition: physprop_mod.f:59
double precision, dimension(:), allocatable flux_gn
Definition: mflux_mod.f:15
double precision, dimension(:,:), allocatable t_s
Definition: fldvar_mod.f:66
double precision, dimension(:,:), allocatable x_g
Definition: fldvar_mod.f:75
subroutine set_outflow_fluxes(IJK, FIJK)
Definition: set_outflow.f:534
integer, dimension(dimension_bc) bc_j_s
Definition: bc_mod.f:62
Definition: eos_mod.f:10
double precision, dimension(dimension_bc, dim_scalar) bc_scalar
Definition: bc_mod.f:384
double precision, dimension(:,:), allocatable theta_m
Definition: fldvar_mod.f:149
double precision, dimension(:), allocatable v_g
Definition: fldvar_mod.f:99
double precision, dimension(:), allocatable w_g
Definition: fldvar_mod.f:111
Definition: run_mod.f:13
Definition: param_mod.f:2
double precision, dimension(:,:), allocatable ro_s
Definition: fldvar_mod.f:45
double precision, dimension(:), allocatable flux_gt
Definition: mflux_mod.f:17
double precision, dimension(:), allocatable mw_mix_g
Definition: physprop_mod.f:130
integer, dimension(0:dim_m) nmax
Definition: physprop_mod.f:119
double precision, dimension(:,:), allocatable p_s
Definition: fldvar_mod.f:123
logical k_epsilon
Definition: run_mod.f:97
double precision, dimension(:), allocatable flux_nt
Definition: mflux_mod.f:55
double precision, dimension(:), allocatable p_star
Definition: fldvar_mod.f:142
double precision, dimension(dimension_bc) bc_e_turb_g
Definition: bc_mod.f:404
double precision, dimension(:), allocatable u_g
Definition: fldvar_mod.f:87
integer nscalar
Definition: scalars_mod.f:7
double precision function ep_s(IJK, xxM)
Definition: fldvar_mod.f:178
double precision, dimension(dimension_bc, dim_m) bc_theta_m
Definition: bc_mod.f:105
double precision, dimension(dimension_bc, dim_n_g) bc_x_g
Definition: bc_mod.f:251
double precision, dimension(dimension_bc) bc_ep_g
Definition: bc_mod.f:77
double precision, dimension(dimension_bc) bc_k_turb_g
Definition: bc_mod.f:403
subroutine set_pinoutflow(BCV, IJK, FIJK, RVEL_G, RVEL_S)
Definition: set_outflow.f:599
double precision, dimension(:,:), allocatable rop_s
Definition: fldvar_mod.f:51
integer smax
Definition: physprop_mod.f:22
double precision, dimension(:,:), allocatable flux_se
Definition: mflux_mod.f:22
double precision, dimension(:), allocatable flux_gsn
Definition: mflux_mod.f:30
integer, dimension(1:dim_scalar) phase4scalar
Definition: scalars_mod.f:10
double precision, parameter pi
Definition: constant_mod.f:158
double precision, dimension(:), allocatable flux_nn
Definition: mflux_mod.f:53
double precision, dimension(:), allocatable e_turb_g
Definition: fldvar_mod.f:162
subroutine set_outflow(BCV)
Definition: set_outflow.f:36
integer dimension_m
Definition: param_mod.f:18
double precision, dimension(:), allocatable ro_g
Definition: fldvar_mod.f:32
double precision, dimension(:), allocatable rop_g
Definition: fldvar_mod.f:38
double precision, dimension(:,:), allocatable flux_sn
Definition: mflux_mod.f:20
integer, dimension(dimension_bc) bc_i_e
Definition: bc_mod.f:58
double precision, parameter zero
Definition: param1_mod.f:27
double precision, dimension(:), allocatable flux_sst
Definition: mflux_mod.f:33
double precision, dimension(dimension_bc, dim_m) bc_rop_s
Definition: bc_mod.f:92
Definition: bc_mod.f:23
double precision, dimension(:), allocatable flux_sse
Definition: mflux_mod.f:29