MFIX  2016-1
calc_des_2fluid.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2 ! !
3 ! Subroutine: CALC_DES_2FLUID !
4 ! !
5 ! Purpose: This subroutine is only called from the CONTINUUM side. It !
6 ! is only called at the start of each time step for explicitly coupled!
7 ! cases. Otherwise, it called every iteration. !
8 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
9  SUBROUTINE calc_des_2fluid
10 
11  use discretelement, only: des_continuum_coupled
12  use discretelement, only: des_continuum_hybrid
13  use discretelement, only: des_explicitly_coupled
14 
17 
18  use discretelement, only: des_continuum_coupled
20 
21 ! Contribution to gas momentum equation due to drag
22  use discretelement, only: drag_bm
23 ! Scalar cell center total drag force
24  use discretelement, only: f_gds
25 ! Flag for 3D simulatoins.
26  use geometry, only: do_k
27  use run, only: any_species_eq
28 
29  use des_thermo, only: calc_conv_des
30  use rxns, only: rrate
31 
32  IMPLICIT NONE
33 
34  IF(.NOT.des_continuum_coupled) RETURN
35 
36  IF(des_explicitly_coupled) THEN
37 ! Bin particles to the fluid grid.
39 ! Calculate interpolation weights
41 ! Calculate mean fields (EPg).
42  CALL comp_mean_fields
43 
44 ! Calculate gas phase source terms: gas-solids heat transfer
46 ! Calculate gas phase source terms: gas-solids mass transfer
47  IF(rrate) CALL rxns_gs_gas1
48  ENDIF
49 
50 ! Calculate gas phase source terms: gas-solids drag force.
51  SELECT CASE(des_interp_scheme_enum)
52  CASE(des_interp_garg) ; CALL drag_gs_gas0
53  CASE DEFAULT; CALL drag_gs_gas1
54  END SELECT
55 
56 ! Calculate solids phase source terms: solids-solids drag force.
57  IF(des_continuum_hybrid) THEN
58  SELECT CASE(des_interp_scheme_enum)
59  CASE DEFAULT; CALL drag_ss_tfm_noninterp
60  END SELECT
61  ENDIF
62 
63 ! Apply the diffusion filter.
65  CALL diffuse_mean_field(f_gds,'F_GDS')
66  CALL diffuse_mean_field(drag_bm(:,1),'DRAG_BM(1)')
67  CALL diffuse_mean_field(drag_bm(:,2),'DRAG_BM(2)')
68  IF(do_k) CALL diffuse_mean_field(drag_bm(:,3),'DRAG_BM(3)')
69 ! IF(ENERGY_EQ) THEN
70 ! CALL DIFFUSE_MEAN_FIELD(CONV_Sc,'CONV_Sc')
71 ! CALL DIFFUSE_MEAN_FIELD(CONV_Sp,'CONV_Sp')
72 ! ENDIF
73  ENDIF
74 
75  RETURN
76  END SUBROUTINE calc_des_2fluid
77 
78 
79 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
80 ! Subroutine: DES_2FLUID_CONV !
81 ! Author: J.Musser Date: 15-Jan-11 !
82 ! !
83 ! Purpose: This routine is called from the continuum phase and !
84 ! calculates the source term from the particles to the fluid. !
85 ! !
86 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
87  SUBROUTINE des_2fluid_conv(S_P, S_C)
88 
89  Use discretelement, only: des_explicitly_coupled
90  Use des_thermo, only: conv_sp, conv_sc
91  USE geometry, only: flag
92  Use param, only: dimension_3
93 
94  use run, only: odt
95 ! Flag: Gas sees the effect of particles in gas/solids flows.
96  use discretelement, only: des_oneway_coupled
97 
98  IMPLICIT NONE
99 
100 ! Passed Variables
101 !---------------------------------------------------------------------//
102 ! Source term on LHS
103  DOUBLE PRECISION, INTENT(INOUT) :: S_P(dimension_3)
104 ! Source term on RHS
105  DOUBLE PRECISION, INTENT(INOUT) :: S_C(dimension_3)
106 
107 ! Local variables
108 !---------------------------------------------------------------------//
109  IF(des_oneway_coupled) RETURN
110 
111  IF(des_explicitly_coupled) THEN
112  WHERE(flag==1)
113  s_p = s_p + conv_sp ! GAMMA
114  s_c = s_c + conv_sc ! GAMMA*Tp
115  END WHERE
116 
117 ! Redistribute the energy over the fluid time step. Note that by the
118 ! time this routine is called, S_C and S_P have already been multiplied
119 ! by the fluid cell volume. Thus, the mapping should result in units
120 ! of energy per time.
121  ELSE
122  WHERE(flag==1) &
123  s_c = s_c + odt*conv_sc ! GAMMA*(Tg-Ts)
124  ENDIF
125 
126  RETURN
127  END SUBROUTINE des_2fluid_conv
128 
129 
130 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
131 ! Subroutine: DES_2FLUID_RXNS !
132 ! Author: J.Musser Date: 15-Jan-11 !
133 ! !
134 ! Purpose: This routine is called from the continuum phase and !
135 ! calculates the source term from the particles to the fluid. !
136 ! !
137 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
138  SUBROUTINE des_2fluid_rxns
140  Use discretelement, only: des_explicitly_coupled
141  Use des_thermo, only: conv_sp, conv_sc
142  USE geometry, only: flag
143  Use param, only: dimension_3
144  USE rxns, only : rrate
145  USE rxns
146  USE des_rxns
147  USE energy, only: hor_g
148  use fldvar, only: x_g
149  use run, only: dt
150  use param1, only: zero, small_number, one
151  use stiff_chem, only: stiff_chemistry
152  use compar, only: ijkstart3, ijkend3
153  use geometry, only: vol
154  use functions, only: fluid_at
155  use toleranc, only: zero_x_gs
156 ! Flag: Gas sees the effect of particles in gas/solids flows.
157  use discretelement, only: des_oneway_coupled
158 ! Flag to use stiff chemistry solver
159  use stiff_chem, only: stiff_chemistry
160 
161  IMPLICIT NONE
162 
163 ! Passed Variables
164 !---------------------------------------------------------------------//
165 ! Source term on LHS
166 ! DOUBLE PRECISION, INTENT(INOUT) :: S_P(DIMENSION_3)
167 ! Source term on RHS
168 ! DOUBLE PRECISION, INTENT(INOUT) :: S_C(DIMENSION_3)
169 
170 ! Local variables
171 !---------------------------------------------------------------------//
172  INTEGER :: IJK
173  DOUBLE PRECISION :: toTFM, lDT
174 
175  IF(des_oneway_coupled) RETURN
176  IF(stiff_chemistry) RETURN
177 
178 ! For DEM simulations that do not have a homogeneous gas phase reaction,
179 ! the gas phase arrays need to be cleared.
180  IF(.NOT.rrate .OR. stiff_chemistry) THEN
181  sum_r_g = zero
182  hor_g = zero
183  r_gp = zero
184  rox_gc = zero
185  r_phase = zero
186  ENDIF
187 
188 ! Redistribute the energy over the fluid time step. Note that by the
189 ! time this routine is called, S_C and S_P have already been multiplied
190 ! by the fluid cell volume. Thus, the mapping should result in units
191 ! of energy per time.
192  ldt = merge(one, dt, des_explicitly_coupled)
193 
194  DO ijk=ijkstart3,ijkend3
195  IF(.NOT.fluid_at(ijk)) cycle
196  totfm = one/(ldt * vol(ijk))
197  r_gp(ijk,:) = r_gp(ijk,:) + des_r_gp(ijk,:)*totfm
198  r_phase(ijk,:) = r_phase(ijk,:) + des_r_phase(ijk,:)*totfm
199  sum_r_g(ijk) = sum_r_g(ijk) + des_sum_r_g(ijk)*totfm
200  hor_g(ijk) = hor_g(ijk) + des_hor_g(ijk)*totfm
201  WHERE(x_g(ijk,:) > zero_x_gs) rox_gc(ijk,:) = &
202  rox_gc(ijk,:)+des_r_gc(ijk,:)*totfm/x_g(ijk,:)
203  ENDDO
204 
205  RETURN
206  END SUBROUTINE des_2fluid_rxns
subroutine comp_mean_fields
logical des_diffuse_mean_fields
subroutine calc_des_2fluid
double precision, dimension(:), allocatable conv_sc
subroutine des_2fluid_rxns
integer ijkend3
Definition: compar_mod.f:80
integer, parameter des_interp_garg
double precision, parameter one
Definition: param1_mod.f:29
integer dimension_3
Definition: param_mod.f:11
subroutine drag_gs_gas1
Definition: drag_gs_des1.f:188
double precision, dimension(:), allocatable des_hor_g
Definition: des_rxns_mod.f:46
Definition: rxns_mod.f:1
subroutine drag_gs_gas0
Definition: drag_gs_des0.f:207
logical calc_conv_des
double precision, dimension(:), allocatable des_sum_r_g
Definition: des_rxns_mod.f:42
double precision, dimension(:), allocatable sum_r_g
Definition: rxns_mod.f:28
double precision dt
Definition: run_mod.f:51
subroutine diffuse_mean_field(PHI, VNAME)
subroutine conv_gs_gas1
subroutine calc_interp_weights
double precision, parameter small_number
Definition: param1_mod.f:24
double precision, dimension(:,:), allocatable x_g
Definition: fldvar_mod.f:75
double precision, dimension(:,:), allocatable des_r_gc
Definition: des_rxns_mod.f:40
double precision odt
Definition: run_mod.f:54
logical rrate
Definition: rxns_mod.f:19
logical any_species_eq
Definition: run_mod.f:118
Definition: run_mod.f:13
double precision, dimension(:,:), allocatable r_phase
Definition: rxns_mod.f:38
double precision, dimension(:), allocatable conv_sp
subroutine particles_in_cell
Definition: param_mod.f:2
subroutine drag_ss_tfm_noninterp
double precision, dimension(:,:), allocatable des_r_phase
Definition: des_rxns_mod.f:44
integer des_interp_scheme_enum
double precision, dimension(:,:), allocatable rox_gc
Definition: rxns_mod.f:26
logical do_k
Definition: geometry_mod.f:30
integer ijkstart3
Definition: compar_mod.f:80
double precision, parameter zero_x_gs
Definition: toleranc_mod.f:19
integer, dimension(:), allocatable flag
Definition: geometry_mod.f:99
double precision, dimension(:,:), allocatable des_r_gp
Definition: des_rxns_mod.f:38
subroutine des_2fluid_conv(S_P, S_C)
double precision, dimension(:), allocatable vol
Definition: geometry_mod.f:212
logical stiff_chemistry
double precision, parameter zero
Definition: param1_mod.f:27
double precision, dimension(:,:), allocatable r_gp
Definition: rxns_mod.f:24
double precision, dimension(:), allocatable hor_g
Definition: energy_mod.f:6
subroutine rxns_gs_gas1
Definition: rxns_gs_des1.f:134