MFIX  2016-1
calc_u_friction.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
2 ! C
3 ! Subroutine: CALC_Gw_Hw_Cw C
4 ! C
5 ! Purpose: Calculate Gw, Hw, and Cw C
6 ! C
7 ! Author: A. Srivastava & K. Agrawal, Princeton Univ. Date: 10-APR-98 C
8 ! Reviewer: Date: C
9 ! C
10 ! Modified: Sofiane Benyahia, Fluent Inc. Date: 03-FEB-05 C
11 ! Purpose: Include conductivity defined by Simonin and Ahmadi C
12 ! Also included Jenkins small frictional limit C
13 ! C
14 ! Literature/Document References: C
15 ! Johnson, P. C., and Jackson, R., Frictional-collisional C
16 ! constitutive relations for granular materials, with C
17 ! application to plane shearing, Journal of Fluid Mechanics, C
18 ! 1987, 176, pp. 67-93 C
19 ! Jenkins, J. T., and Louge, M. Y., On the flux of fluctuating C
20 ! energy in a collisional grain flow at a flat frictional wall, C
21 ! Physics of Fluids, 1997, 9(10), pp. 2835-2840 C
22 ! C
23 ! See calc_mu_s.f for references on frictional theory models C
24 ! See calc_mu_s.f for references on Ahmadi and Simonin models C
25 ! C
26 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
27 
28  SUBROUTINE calc_gw_hw_cw(g0, EPS, EPG, ep_star_avg, &
29  g0ep_avg, th, mu_g_avg, ro_g_avg, ros_avg, &
30  dp_avg, k_12_avg, tau_12_avg, tau_1_avg, vrel, vslip,&
31  del_u, s_s, s_dd, vel, w_vel, m, gw, hw, cw)
32 
33 !-----------------------------------------------
34 ! Modules
35 !-----------------------------------------------
36  USE param
37  USE param1
38  USE constant
39  USE physprop
40  USE fldvar
41  USE bc
42  USE run
43  USE mpi_utility
44  IMPLICIT NONE
45 !-----------------------------------------------
46 ! Dummy Arguments
47 !-----------------------------------------------
48 ! Radial distribution function of solids phase M with each
49 ! other solids phase
50  DOUBLE PRECISION, INTENT(IN) :: g0
51 ! Average solids volume fraction of each solids phase
52  DOUBLE PRECISION, INTENT(IN) :: EPS
53 ! Average solids and gas volume fraction
54  DOUBLE PRECISION, INTENT(IN) :: EPG, ep_star_avg
55 ! Sum of eps*G_0
56  DOUBLE PRECISION, INTENT(IN) :: g0EP_avg
57 ! Average theta_m
58  DOUBLE PRECISION, INTENT(INOUT) :: TH
59 ! Average gas viscosity
60  DOUBLE PRECISION, INTENT(IN) :: Mu_g_avg
61 ! Average gas density
62  DOUBLE PRECISION, INTENT(IN) :: RO_g_avg
63 ! Average solids density
64  DOUBLE PRECISION, INTENT(IN) :: ROS_avg
65 ! Average particle diameter of each solids phase
66  DOUBLE PRECISION, INTENT(IN) :: DP_avg
67 ! Average cross-correlation K_12 and lagrangian integral time-scale
68  DOUBLE PRECISION, INTENT(IN) :: K_12_avg, Tau_12_avg, Tau_1_avg
69 ! Magnitude of slip velocity between two phases
70  DOUBLE PRECISION, INTENT(IN) :: VREL
71 ! Slip velocity between wall and particles
72  DOUBLE PRECISION, INTENT(IN) :: VSLIP
73 ! Relevant solids velocity at wall
74  DOUBLE PRECISION, INTENT(IN) :: VEL
75 ! Relevant wall velocity
76  DOUBLE PRECISION, INTENT(IN) :: W_VEL
77 ! del.u
78  DOUBLE PRECISION, INTENT(IN) :: DEL_U
79 ! S:S
80  DOUBLE PRECISION, INTENT(IN) :: S_S
81 ! S_dd (d can be x,y or z)
82  DOUBLE PRECISION, INTENT(IN) :: S_dd
83 ! Solids phase index
84  INTEGER, INTENT(IN) :: M
85 ! Wall momentum coefficients:
86 ! 1st term on LHS
87  DOUBLE PRECISION, INTENT(INOUT) :: Gw
88 ! 2nd term on LHS
89  DOUBLE PRECISION, INTENT(INOUT) :: Hw
90 ! all terms appearing on RHS
91  DOUBLE PRECISION, INTENT(INOUT) :: Cw
92 !-----------------------------------------------
93 ! Local Variables
94 !-----------------------------------------------
95 ! Part of wall momentum coefficient in 1st term of LHS
96  DOUBLE PRECISION :: Mu_s
97 ! Term appearing in wall momenutm coefficient of 2nd term LHS
98  DOUBLE PRECISION :: F_2
99 ! Frictional Pressure Pf
100  DOUBLE PRECISION :: Pf
101 ! Critical pressure Pc
102  DOUBLE PRECISION :: Pc
103 ! Chi (appears in frictional boundary condition)
104  DOUBLE PRECISION :: Chi, N_Pff
105 ! Viscosity
106  DOUBLE PRECISION :: Mu
107 ! Bulk viscosity
108  DOUBLE PRECISION :: Mu_b
109 ! Viscosity corrected for interstitial fluid effects
110  DOUBLE PRECISION :: Mu_star
111 ! Reynolds number based on slip velocity
112  DOUBLE PRECISION :: Re_g
113 ! Friction Factor in drag coefficient
114  DOUBLE PRECISION :: C_d
115 ! Drag Coefficient
116  DOUBLE PRECISION :: Beta, DgA
117 ! Square root of S:S or the form suggested by Savage
118  DOUBLE PRECISION :: ZETA
119 ! Constants in Simonin model
120  DOUBLE PRECISION :: Sigma_c, Tau_2_c, Tau_12_st, Nu_t
121  DOUBLE PRECISION :: Tau_2, zeta_c_2, MU_2_T_Kin, Mu_2_Col
122  DOUBLE PRECISION :: Tmp_Ahmadi_Const
123 ! Other local terms
124  DOUBLE PRECISION :: dpc_dphi
125 ! Local variable for rdf
126  DOUBLE PRECISION :: g0_loc
127 !-----------------------------------------------
128 
129 ! This is done here similar to bc_theta to avoid small negative values of
130 ! Theta coming most probably from linear solver
131  IF(th .LE. zero)THEN
132  th = 1d-8
133  IF (mype.eq.pe_io) THEN
134  WRITE(*,*) &
135  'Warning: Negative granular temp at wall set to 1e-8'
136 ! CALL WRITE_ERROR('THETA_HW_CW', LINE, 1)
137  ENDIF
138  ENDIF
139 
140  g0_loc = g0
141 
142 ! modify F_2 if Jenkins BC is used (sof)
143  IF(jenkins) THEN
144 
145  IF (vslip == zero) THEN
146 ! if solids velocity field is initialized to zero, use free slip bc
147  f_2 = zero
148 
149  ELSE
150  IF(ahmadi) THEN
151 ! Ahmadi model uses different solids pressure model
152 ! the coefficient mu in Jenkins paper is defined as tan_Phi_w, that's how
153 ! I understand it from soil mechanic papers, i.e., G.I. Tardos, powder
154 ! Tech. 92 (1997), 61-74. See his equation (1). Define Phi_w in mfix.dat!
155 ! here F_2 divided by VSLIP to use the same bc as Johnson&Jackson
156 
157  f_2 = tan_phi_w*ros_avg*eps* &
158  ((one + 4.0d0*g0ep_avg) + half*(one -c_e*c_e))*th/vslip
159 
160  ELSE
161 ! Simonin or granular models use same solids pressure
162  f_2 = tan_phi_w*ros_avg*eps*(1d0+ 4.d0 * eta *g0ep_avg)*th/vslip
163  ENDIF ! end if(Ahmadi)
164 
165  ENDIF ! endif(vslip==0)
166 
167  ELSE ! if(.not.jenkins)
168 
169  f_2 = (phip*dsqrt(3d0*th)*pi*ros_avg*eps*g0_loc)&
170  /(6d0*(one-ep_star_avg))
171 
172  ENDIF ! end if(Jenkins)/else
173 
174 
175  mu = (5d0*dsqrt(pi*th)*dp_avg*ros_avg)/96d0
176  mu_b = (256d0*mu*eps*g0ep_avg)/(5d0*pi)
177 
178 ! This is from Wen-Yu correlation, you can put here your own single particle drag
179  re_g = epg*ro_g_avg*dp_avg*vrel/mu_g_avg
180  IF (re_g.lt.1000d0) THEN
181  c_d = (24.d0/(re_g+small_number))*(one + 0.15d0 * re_g**0.687d0)
182  ELSE
183  c_d = 0.44d0
184  ENDIF
185  dga = 0.75d0*c_d*ro_g_avg*epg*vrel/(dp_avg*epg**(2.65d0))
186  IF(vrel == zero) dga = large_number
187  beta = switch*eps*dga
188 
189 ! SWITCH enables us to turn on/off the modification to the
190 ! particulate phase viscosity. If we want to simulate gas-particle
191 ! flow then SWITCH=1 to incorporate the effect of drag on the
192 ! particle viscosity. If we want to simulate granular flow
193 ! without the effects of an interstitial gas, SWITCH=0.
194  IF(switch == zero .OR. ro_g_avg == zero)THEN
195  mu_star = mu
196  ELSEIF(th .LT. small_number)THEN
197  mu_star = zero
198  ELSE
199  mu_star = ros_avg*eps* g0_loc*th* mu/ &
200  (ros_avg*g0ep_avg*th + 2.0d0*switch*dga/ros_avg* mu)
201  ENDIF
202 
203  mu_s = ((2d0+alpha)/3d0)*((mu_star/(eta*(2d0-eta)*&
204  g0_loc))*(one+1.6d0*eta*g0ep_avg&
205  )*(one+1.6d0*eta*(3d0*eta-2d0)*&
206  g0ep_avg)+(0.6d0*mu_b*eta))
207 
208 ! particle relaxation time
209  tau_12_st = ros_avg/(dga+small_number)
210 
211  IF(simonin) THEN !see calc_mu_s for explanation of these definitions
212 
213  sigma_c = (one+ c_e)*(3.d0-c_e)/5.d0
214  tau_2_c = dp_avg/(6.d0*eps*g0_loc*dsqrt(16.d0*(th+small_number)/pi))
215  zeta_c_2= 2.d0/5.d0*(one+ c_e)*(3.d0*c_e-one)
216  nu_t = tau_12_avg/tau_12_st
217  tau_2 = one/(2.d0/tau_12_st+sigma_c/tau_2_c)
218  mu_2_t_kin = (2.0d0/3.0d0*k_12_avg*nu_t + th * &
219  (one+ zeta_c_2*eps*g0_loc))*tau_2
220  mu_2_col = 8.d0/5.d0*eps*g0_loc*eta* (mu_2_t_kin+ &
221  dp_avg*dsqrt(th/pi))
222  mu_s = eps*ros_avg*(mu_2_t_kin + mu_2_col)
223  ELSEIF(ahmadi) THEN
224  IF(eps < (one-ep_star_avg)) THEN
225  tmp_ahmadi_const = &
226  one/(one+ tau_1_avg/tau_12_st * (one-eps/(one-ep_star_avg))**3)
227  ELSE
228  tmp_ahmadi_const = one
229  ENDIF
230  mu_s = tmp_ahmadi_const &
231  *0.1045d0*(one/g0_loc+3.2d0*eps+12.1824d0*g0_loc*eps*eps) &
232  *dp_avg*ros_avg* dsqrt(th)
233  ENDIF
234 
235 ! Calculating frictional terms
236  IF ((one-epg)<= eps_f_min) THEN
237  pf = zero
238  chi = zero
239  zeta = 1d0
240  ELSE
241  IF (savage.EQ.1) THEN !form of Savage
242  zeta = ((48d0*eta*(1d0-eta)*ros_avg*eps*eps*g0_loc*&
243  (th**1.5d0))/&
244  (sqrt_pi*dp_avg*2d0*mu_s))**0.5d0
245  ELSEIF (savage.EQ.0) THEN !S:S form
246  zeta = dsqrt(s_s)
247  ELSE
248  zeta = dsqrt(s_s + (th/(dp_avg*dp_avg)))
249  ENDIF
250 
251  IF (epg < ep_star_avg) THEN
252  dpc_dphi = (to_si*fr)*((delta**5)*(2d0*(one-ep_star_avg-delta) - &
253  2d0*eps_f_min)+((one-ep_star_avg-delta)-eps_f_min)&
254  *(5*delta**4))/(delta**10)
255 
256  pc = (to_si*fr)*(((one-ep_star_avg-delta) - eps_f_min)**n_pc)/(delta**d_pc)
257 ! Pc= 1d25*(((ONE-EPG)-(ONE-ep_star_avg))**10d0) ! this is old Pc
258  ELSE
259  pc = fr*(((one-epg) - eps_f_min)**n_pc)/ &
260  (((one-ep_star_avg) - (one-epg) + small_number)**d_pc)
261  ENDIF
262 
263  IF (del_u .GE. zero) THEN
264  n_pff = dsqrt(3d0)/(2d0*sin_phi) !dilatation
265  ELSE
266  n_pff = n_pf !compaction
267  ENDIF
268 
269  IF ((del_u/(zeta*n_pff*dsqrt(2d0)*sin_phi)) .GT. 1d0) THEN
270  pf = zero
271  ELSEIF( del_u == zero ) THEN
272  pf = pc
273  ELSE
274  pf = pc*(1d0 - (del_u/(zeta*n_pff*dsqrt(2d0)*sin_phi)))**&
275  (n_pff-1d0)
276  ENDIF
277 
278  chi = dsqrt(2d0)*pf*sin_phi*(n_pff - (n_pff-1d0)*&
279  ((pf/pc)**(1d0/(n_pff-1d0))))
280 
281  IF (chi< zero) THEN
282  pf = pc*((n_pff/(n_pff-1d0))**(n_pff-1d0))
283  chi = zero
284  ENDIF
285 
286 ! by writing Pf & Chi in the following form, we ensure distribution
287 ! of stresses amoung all solids phases (sof, Oct 24 2005)
288 
289  pf = pf * eps/(one-epg)
290  chi = chi * eps/(one-epg)
291 
292  ENDIF
293 
294 ! Calculating gw, hw, cw
295 
296  gw = one ! we write this in the exact same form as non-frictional JJ BC
297 
298  IF(vslip == zero .OR. zeta == zero) THEN
299  hw = zero
300  ELSE
301  hw = f_2 + pf*tan_phi_w - chi*s_dd*tan_phi_w/zeta
302  hw = hw / (mu_s + chi/(2d0*zeta)) ! this is because Gw is set to one.
303  ENDIF
304  cw = hw * w_vel
305 
306  RETURN
307  END SUBROUTINE calc_gw_hw_cw
double precision c_e
Definition: constant_mod.f:105
double precision to_si
Definition: constant_mod.f:146
double precision n_pf
Definition: constant_mod.f:101
double precision, parameter one
Definition: param1_mod.f:29
double precision, parameter switch
Definition: constant_mod.f:53
double precision n_pc
Definition: constant_mod.f:101
double precision sin_phi
Definition: constant_mod.f:123
subroutine calc_gw_hw_cw(g0, EPS, EPG, ep_star_avg, g0EP_avg, TH, Mu_g_avg, RO_g_avg, ROs_avg, DP_avg, K_12_avg, Tau_12_avg, Tau_1_avg, VREL, VSLIP, DEL_U, S_S, S_dd, VEL, W_VEL, M, gw, hw, cw)
logical jenkins
Definition: run_mod.f:166
double precision, parameter alpha
Definition: constant_mod.f:62
double precision fr
Definition: constant_mod.f:101
double precision, parameter small_number
Definition: param1_mod.f:24
logical simonin
Definition: run_mod.f:143
double precision eta
Definition: constant_mod.f:108
double precision eps_f_min
Definition: constant_mod.f:100
double precision phip
Definition: constant_mod.f:79
integer savage
Definition: run_mod.f:154
double precision, parameter half
Definition: param1_mod.f:28
Definition: run_mod.f:13
double precision, parameter large_number
Definition: param1_mod.f:23
Definition: param_mod.f:2
logical ahmadi
Definition: run_mod.f:146
double precision tan_phi_w
Definition: constant_mod.f:132
double precision, parameter pi
Definition: constant_mod.f:158
double precision, parameter sqrt_pi
Definition: constant_mod.f:161
double precision d_pc
Definition: constant_mod.f:101
double precision delta
Definition: constant_mod.f:101
double precision, parameter zero
Definition: param1_mod.f:27
Definition: bc_mod.f:23