MFIX  2016-1
calc_coeff.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
2 ! !
3 ! Subroutine: CALC_COEFF_ALL !
4 ! Purpose: This routine directs the calculation of all physical and !
5 ! transport properties, exchange rates, and reaction rates. !
6 ! !
7 ! Author: M. Syamlal Date: 25-AUG-05 !
8 ! Reviewer: Date: !
9 ! !
10 ! Literature/Document References: !
11 ! !
12 ! Variables referenced: !
13 ! Variables modified: !
14 ! Local variables: !
15 ! !
16 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
17  SUBROUTINE calc_coeff_all(FLAG, IER)
18 
19 ! Global variables:
20 !-----------------------------------------------------------------------
21 ! Double precision: 1.0d0
22  use param1, only: one
23 ! Under relaxation factor for gas-solids drag coefficient
24  use ur_facs, only: ur_f_gs
25 ! Under relaxation factor solid conductivity coefficient for IA theory
26  use ur_facs, only: ur_kth_sml
27 ! Flag for DES coupled simulation
28  use discretelement, only: des_continuum_coupled
29 ! Flag for explcit coupling between the fluid and particles.
30  use discretelement, only: des_explicitly_coupled
31 
32  implicit none
33 
34 ! Dummy arguments
35 !-----------------------------------------------------------------------
36 ! FLAG = 0, overwrite the coeff arrays, (e.g. start of a time step)
37 ! FLAG = 1, do not overwrite
38  INTEGER, intent(in) :: FLAG
39 ! Error index
40  INTEGER, intent(inout) :: IER
41 
42 ! Local variables
43 !-----------------------------------------------
44 ! Under relaxation factor for gas-solids drag coefficient
45  DOUBLE PRECISION :: loc_UR_F_gs ! Local copy
46 ! Under relaxation factor solid conductivity coefficient for IA theory
47  DOUBLE PRECISION :: loc_UR_kth_sml ! Local copy
48 
49 !-----------------------------------------------------------------------
50 
51 ! 1) Backup user-defined coefficient relaxation factors.
52 ! 2) Set user-defined coefficient relaxation factors to 1.
53 ! Note that 'FLAG' is hard coded to 0 in time march and reset_new.
54  IF(flag == 0) THEN
55  loc_ur_f_gs = ur_f_gs; ur_f_gs = one
56  loc_ur_kth_sml = ur_kth_sml; ur_kth_sml = one
57  ENDIF
58 
59 ! Calculate all physical properties, transport properties, and exchange
60 ! rates.
61  CALL calc_coeff(ier, 2)
62 
63 ! Calculate reaction rates and interphase mass transfer.
64  CALL calc_rrate(ier)
65 
66 ! Restore all coefficient underrelaxation factors to original values.
67  IF(flag == 0) THEN
68  ur_f_gs = loc_ur_f_gs
69  ur_kth_sml = loc_ur_kth_sml
70  ENDIF
71 
72 ! DES interaction for explictly coupled simulations
73  IF(des_continuum_coupled .AND. des_explicitly_coupled) &
74  CALL calc_des_2fluid
75 
76  RETURN
77  END SUBROUTINE calc_coeff_all
78 
79 
80 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
81 ! !
82 ! Subroutine: CALC_COEFF !
83 ! Purpose: This routine directs the calculation of all physical and !
84 ! transport properties, and exchange rates. !
85 ! !
86 ! Author: M. Syamlal Date: 25-AUG-05 !
87 ! Reviewer: Date: !
88 ! !
89 ! !
90 ! !
91 ! Literature/Document References: !
92 ! !
93 ! Variables referenced: !
94 ! Variables modified: !
95 ! Local variables: !
96 ! !
97 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
98  SUBROUTINE calc_coeff(IER, pLevel)
99 
100 ! Flag for DES coupled simulation
101  use discretelement, only: des_continuum_coupled
102 ! Flag for explcit coupling between the fluid and particles.
103  use discretelement, only: des_explicitly_coupled
104 
105  implicit none
106 
107 ! Dummy arguments
108 !-----------------------------------------------------------------------
109 ! Error index
110  INTEGER, intent(inout) :: IER
111 ! Level to calculate physical properties.
112 ! 0) Only density
113 ! 1) Everything but density
114 ! 2) All physical properties
115  INTEGER, intent(in) :: pLevel
116 !-----------------------------------------------------------------------
117 
118 ! Calculate physical properties: (density, specific heat, diameter)
119  CALL physical_prop(ier, plevel)
120 
121 ! Calculate transport properties: (conductivity, diffusivity, ect)
122  CALL transport_prop(ier)
123 
124 ! Calculate interphase coeffs: (momentum and energy)
125  CALL exchange(ier)
126 
127 ! Calculate DES coupled quantities.
128  IF(des_continuum_coupled .AND. .NOT.des_explicitly_coupled) &
129  CALL calc_des_2fluid
130 
131  RETURN
132  END SUBROUTINE calc_coeff
133 
134 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
135 ! C
136 ! Subroutine: CALC_RRATE C
137 ! Purpose: if rrate then calculate reaction rates and interphase C
138 ! mass transfer. if present, calculate discrete reactions C
139 ! C
140 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
141  SUBROUTINE calc_rrate(IER)
143 !-----------------------------------------------
144 ! Modules
145 !-----------------------------------------------
146  USE discretelement, only : discrete_element
147  USE rxns,only : rrate, use_rrates
148  use run, only: any_species_eq
149 
150  use error_manager
151 
152  IMPLICIT NONE
153 !-----------------------------------------------
154 ! Dummy arguments
155 !-----------------------------------------------
156 !-----------------------------------------------
157 ! Local variables
158 !-----------------------------------------------
159 ! Error index
160  INTEGER, INTENT(INOUT) :: IER
161 
162 !-----------------------------------------------
163 
164 ! Calculate reaction rates and interphase mass transfer
165  IF(rrate) THEN
166 ! Legacy hook: Calculate reactions from rrates.f.
167  IF(use_rrates) THEN
168  CALL rrates (ier)
169  IF(ier .EQ. 1) THEN
170  CALL init_err_msg('CALC_RRATE')
171  WRITE(err_msg, 1000)
172  CALL flush_err_msg(abort=.true.)
173  ENDIF
174  ELSE
175  CALL rrates0 (ier)
176  ENDIF
177 
178 ! DES Chemical reactions
179  IF(any_species_eq .AND. discrete_element) &
180  CALL des_2fluid_rxns
181  ENDIF
182 
183  RETURN
184 
185  1000 FORMAT('Species balance equations are being solved; but chemical',/, &
186  ' reactions are not specified in mfix.dat or in rrates.f.',/, &
187  ' Copy the file mfix/model/rrates.f into the run directory ',/, &
188  ' and remove the initial section that returns IER=1.')
189 
190  END SUBROUTINE calc_rrate
191 
192 
193 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
194 ! !
195 ! Subroutine: CALC_TRD_AND_TAU !
196 ! Purpose: Calculate various terms in the gas and solids phase !
197 ! stress tensor as indicated below !
198 ! !
199 ! Author: M. Syamlal Date: 25-AUG-05 !
200 ! !
201 ! !
202 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
203  SUBROUTINE calc_trd_and_tau()
205  USE run, only: jackson
206 ! Stress tensor trace.
207  USE visc_g, only : trd_g
208  USE visc_s, only : trd_s
209 ! Stress tensor cross terms.
210  USE tau_g, only : tau_u_g, tau_v_g, tau_w_g
211  USE tau_g, only : ctau_u_g, ctau_v_g, ctau_w_g
212  USE tau_s, only : tau_u_s, tau_v_s, tau_w_s
213 ! Runtime flag for DEM model.
214  USE discretelement, only: discrete_element
215 ! Runtime flag for TFM-DEM hybrid model.
216  USE discretelement, only: des_continuum_hybrid
217 
218  USE param1, only: zero
219  implicit none
220 
221 !-----------------------------------------------------------------------
222 
223 ! Calculate the trace of the stress tensor (gas phase; m=0)
224  CALL calc_trd_g (trd_g)
225 
226 ! Calculate the cross terms of the stress tensor (gas phase; m=0)
227  CALL calc_tau_u_g (tau_u_g, ctau_u_g)
228  CALL calc_tau_v_g (tau_v_g, ctau_v_g)
229  CALL calc_tau_w_g (tau_w_g, ctau_w_g)
230 
231  IF (.NOT. jackson) THEN
232  ctau_u_g = zero
233  ctau_v_g = zero
234  ctau_w_g = zero
235  ENDIF
236 
237 ! Bypass the following calculations if there are no TFM solids.
238  IF (.NOT.discrete_element .OR. des_continuum_hybrid) THEN
239 ! Calculate the cross terms of the stress tensor (solids phases; m>0)
240  CALL calc_trd_s (trd_s)
241 ! Calculate the trace of the stress tensor (solids phases; m>0)
242  CALL calc_tau_u_s (tau_u_s)
243  CALL calc_tau_v_s (tau_v_s)
244  CALL calc_tau_w_s (tau_w_s)
245  ENDIF
246 
247  RETURN
248  END SUBROUTINE calc_trd_and_tau
double precision, dimension(:,:), allocatable tau_u_s
Definition: tau_s_mod.f:4
double precision, dimension(:,:), allocatable trd_s
Definition: visc_s_mod.f:63
double precision ur_f_gs
Definition: ur_facs_mod.f:17
subroutine calc_rrate(IER)
Definition: calc_coeff.f:142
subroutine calc_des_2fluid
double precision, dimension(:), allocatable ctau_u_g
Definition: tau_g_mod.f:10
double precision, dimension(:,:), allocatable tau_w_s
Definition: tau_s_mod.f:6
subroutine des_2fluid_rxns
subroutine calc_tau_u_s(lTAU_U_S)
Definition: tau_u_s.f:21
subroutine calc_coeff_all(FLAG, IER)
Definition: calc_coeff.f:18
double precision, parameter one
Definition: param1_mod.f:29
subroutine calc_tau_w_s(lTAU_W_S)
Definition: tau_w_s.f:19
subroutine transport_prop()
Definition: rxns_mod.f:1
double precision, dimension(:,:), allocatable tau_v_s
Definition: tau_s_mod.f:5
Definition: tau_s_mod.f:1
subroutine calc_trd_g(lTRD_G)
Definition: calc_trd_g.f:11
logical jackson
Definition: run_mod.f:83
subroutine init_err_msg(CALLER)
double precision, dimension(:), allocatable ctau_v_g
Definition: tau_g_mod.f:11
logical use_rrates
Definition: rxns_mod.f:21
subroutine physical_prop(IER, LEVEL)
Definition: physical_prop.f:21
subroutine calc_coeff(IER, pLevel)
Definition: calc_coeff.f:99
Definition: tau_g_mod.f:1
double precision, dimension(:), allocatable trd_g
Definition: visc_g_mod.f:4
double precision, dimension(:), allocatable tau_u_g
Definition: tau_g_mod.f:4
subroutine calc_tau_u_g(lTAU_U_G, lctau_u_g)
Definition: tau_u_g.f:52
subroutine calc_trd_s(lTRD_S)
Definition: calc_trd_s.f:11
logical rrate
Definition: rxns_mod.f:19
logical any_species_eq
Definition: run_mod.f:118
subroutine rrates(IER)
Definition: rrates.f:20
subroutine rrates0()
Definition: rrates0.f:29
Definition: run_mod.f:13
subroutine calc_tau_v_g(lTAU_V_G, lctau_v_g)
Definition: tau_v_g.f:36
subroutine calc_trd_and_tau()
Definition: calc_coeff.f:204
double precision, dimension(:), allocatable ctau_w_g
Definition: tau_g_mod.f:12
subroutine exchange(IER)
Definition: exchange.f:13
double precision, dimension(:), allocatable tau_v_g
Definition: tau_g_mod.f:5
character(len=line_length), dimension(line_count) err_msg
double precision, dimension(:), allocatable tau_w_g
Definition: tau_g_mod.f:6
double precision, parameter zero
Definition: param1_mod.f:27
subroutine flush_err_msg(DEBUG, HEADER, FOOTER, ABORT, LOG, CALL_TREE)
subroutine calc_tau_v_s(lTAU_V_S)
Definition: tau_v_s.f:20
subroutine calc_tau_w_g(lTAU_W_G, lctau_w_g)
Definition: tau_w_g.f:62
double precision ur_kth_sml
Definition: ur_facs_mod.f:21