MFIX  2016-1
drag_gp_des.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
2 ! C
3 ! Subroutine: DES_DRAG_GP C
4 ! Purpose: Calculate the gas-particle drag coefficient using C
5 ! the gas velocity interpolated to the particle position C
6 ! and the particle velocity. C
7 ! Invoked from des_drag_gs and calc_des_drag_gs C
8 ! C
9 ! Comments: The BVK drag model and all drag models with the C
10 ! polydisperse correction factor (i.e., suffix _PCF) C
11 ! require an average particle diameter. This has been C
12 ! loosely defined for discrete particles based on their C
13 ! solids phase C
14 ! C
15 ! Variables referenced: C
16 ! Variables modified: C
17 ! Local variables: C
18 ! C
19 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
20  SUBROUTINE des_drag_gp(NP, PARTICLE_VEL, FLUID_VEL, EPg)
21 
22 ! Modules
23 !---------------------------------------------------------------------//
24  USE compar
25  USE constant
26  USE discretelement
27  USE drag
28  USE fldvar
29  USE functions
30  USE geometry
31  USE indices
32  USE machine, only: start_log, end_log
33  USE param
34  USE param1
35  USE physprop
36  USE run
37  USE sendrecv
38  USE ur_facs
39  IMPLICIT NONE
40 
41 ! Dummy arguments
42 !---------------------------------------------------------------------//
43 ! particle number id.
44  INTEGER , INTENT(IN) :: NP
45 ! particle velocity
46  DOUBLE PRECISION, INTENT(IN) :: PARTICLE_VEL(3)
47 ! fluid velocity interpolated to particle position
48  DOUBLE PRECISION, INTENT(IN) :: FLUID_VEL(3)
49 ! Gas phase volume fraction.
50  DOUBLE PREcISION, INTENT(IN) :: EPg
51 
52 ! Local variables
53 !---------------------------------------------------------------------//
54 ! indices, associated with current particle
55  INTEGER :: IJK
56 ! solids phase index, associated with current particle
57  INTEGER :: M
58 ! Slip velocity and its magnitude
59  DOUBLE PRECISION :: VSLP(3), VREL
60 ! gas laminar viscosity redefined here to set viscosity at pressure
61 ! boundaries
62  DOUBLE PRECISION :: Mu
63 ! drag coefficient
64  DOUBLE PRECISION :: DgA
65 ! current value of F_gs (i.e., without underrelaxation)
66  DOUBLE PRECISION F_gstmp
67 ! indices of solids phases (continuous, discrete)
68  INTEGER :: lM
69 ! correction factors for implementing polydisperse drag model
70 ! proposed by van der Hoef et al. (2005)
71  DOUBLE PRECISION :: F_cor, tSUM, tfac
72 ! average particle diameter in polydisperse systems
73  DOUBLE PRECISION :: DPA
74 ! diameter ratio in polydisperse systems
75  DOUBLE PRECISION :: Y_i
76 ! total solids volume fraction and phase volume fraction
77  DOUBLE PRECISION :: PHIS, phism
78 ! aliases for gas density, gas bulk density,
79  DOUBLE PRECISION :: ROg, ROPg
80 ! particle diameter, particle density
81  DOUBLE PRECISION :: DPM, ROd
82 !......................................................................!
83 
84 ! values based on current particle
85  ijk = pijk(np,4)
86 ! solids phase index of current particle
87  m = pijk(np,5)
88 ! Gas material and bulk densities
89  rog = ro_g(ijk)
90  ropg = ro_g(ijk) * epg
91 ! Laminar viscosity.
92  mu = mu_g(ijk)
93 ! Slip velocity and its magnitude
94  vslp = fluid_vel - particle_vel
95  vrel = sqrt(dot_product(vslp, vslp))
96 ! assign variables for short dummy arguments
97  dpm = 2.0d0*des_radius(np)
98  rod = ro_sol(np)
99 ! Total solids volume fraction.
100  phis = one - epg
101 
102 ! determine the drag coefficient
103  SELECT CASE(drag_type_enum)
104 
105  CASE (syam_obrien)
106  CALL drag_syam_obrien(dga,epg,mu,rog,vrel,dpm)
107 
108  CASE (gidaspow)
109  CALL drag_gidaspow(dga,epg,mu,rog,ropg,vrel,dpm)
110 
111  CASE (gidaspow_blend)
112  CALL drag_gidaspow_blend(dga,epg,mu,rog,ropg,vrel,dpm)
113 
114  CASE (wen_yu)
115  CALL drag_wen_yu(dga,epg,mu,ropg,vrel,dpm)
116 
117  CASE (koch_hill)
118  CALL drag_koch_hill(dga,epg,mu,ropg,vrel,dpm,dpm,phis)
119 
120  CASE (user_drag)
121  CALL drag_usr(ijk,np,dga,epg,mu,rog,vrel,dpm,rod, &
122  fluid_vel(1), fluid_vel(2), fluid_vel(3))
123 
124  CASE DEFAULT
125 
126 ! calculate the average particle diameter and particle ratio:
127 ! the loop over discrete solids could be replaced using a loop
128 ! over all particles in the given ijk cell but this should be
129 ! done outside the current particle loop to minimize repetitive
130 ! computational expense
131  tsum = zero
132  DO lm = mmax+1,des_mmax+mmax
133  phism = ep_s(ijk,lm) ! PVOL(NP)/VOL(IJK)
134  IF (phis .GT. zero) THEN
135  tfac = phism/phis
136  tsum = tsum + tfac/dpm
137  ELSE
138  tsum = tsum + one/dpm
139  ENDIF
140  ENDDO
141  IF(des_continuum_hybrid) THEN
142  DO lm = 1,mmax
143  phism = ep_s(ijk,lm)
144  IF(phis > zero) THEN
145  tfac = phism/phis
146  tsum = tsum + tfac/d_p(ijk,lm)
147  ELSE
148  tsum = tsum + one/d_p(ijk,lm)
149  ENDIF
150  ENDDO
151  ENDIF
152  dpa = one / tsum
153  y_i = dpm / dpa
154 
155  SELECT CASE(drag_type_enum)
156  CASE (gidaspow_pcf)
157  CALL drag_gidaspow(dga,epg,mu,rog,ropg,vrel,dpa)
158  CASE (gidaspow_blend_pcf)
159  CALL drag_gidaspow_blend(dga,epg,mu,rog,ropg,vrel,dpa)
160  CASE (wen_yu_pcf)
161  CALL drag_wen_yu(dga,epg,mu,ropg,vrel,dpa)
162  CASE (koch_hill_pcf)
163  CALL drag_koch_hill(dga,epg,mu,ropg,vrel,dpm,dpa,phis)
164  CASE (bvk)
165  CALL drag_bvk(dga,epg,mu,ropg,vrel,dpm,dpa,phis)
166 
167  CASE DEFAULT
168  CALL start_log
169  IF(dmp_log) WRITE (*, '(A,A)') &
170  'Unknown DRAG_TYPE: ', drag_type
171  WRITE (unit_log, '(A,A)') 'Unknown DRAG_TYPE: ', drag_type
172  CALL end_log
173  CALL mfix_exit(mype)
174  END SELECT ! end selection of drag_type
175 
176 ! Modify drag coefficient to account for possible corrections and for
177 ! differences between Model B and Model A; see erratum Beetstra (2007)
178  IF(model_b) THEN
179  IF (m == 1) THEN
180  f_cor = (epg*y_i + phis*y_i**2)
181  ELSE
182  f_cor = (epg*y_i + phis*y_i**2 + &
183  0.064d0*epg*y_i**3)
184  ENDIF
185  ELSE
186  f_cor = y_i
187  ENDIF
188  dga = one/(y_i*y_i) * dga * f_cor
189 
190  END SELECT ! end selection of drag_type
191 
192 
193 
194 ! Calculate the drag coefficient (Model B coeff = Model A coeff/EP_g)
195  IF(model_b) THEN
196  f_gstmp = dga * pvol(np)/ep_g(ijk)
197  ELSE
198  f_gstmp = dga * pvol(np)
199  ENDIF
200 
201 ! Determine drag force coefficient accounting for any under relaxation
202 ! f_gp() = single particle drag excluding vector(v_g - v_p)
203  f_gp(np) = (one - ur_f_gs) * f_gp(np) + ur_f_gs * f_gstmp
204 
205  RETURN
206  END SUBROUTINE des_drag_gp
double precision ur_f_gs
Definition: ur_facs_mod.f:17
double precision, dimension(:), allocatable ep_g
Definition: fldvar_mod.f:15
double precision, parameter one
Definition: param1_mod.f:29
subroutine drag_usr(IJK, M_NP, lDgA, EPg, Mug, ROg, VREL, DPM, ROs, lUg, lVg, lWg)
Definition: usr_drag.f:27
subroutine des_drag_gp(NP, PARTICLE_VEL, FLUID_VEL, EPg)
Definition: drag_gp_des.f:21
Definition: drag_mod.f:11
subroutine drag_bvk(lDgA, EPg, Mug, ROPg, VREL, DPM, DPA, PHIS)
Definition: drag_gs.f:1275
subroutine drag_gidaspow(lDgA, EPg, Mug, ROg, ROPg, VREL, DPM)
Definition: drag_gs.f:480
double precision, dimension(:,:), allocatable d_p
Definition: fldvar_mod.f:57
integer mmax
Definition: physprop_mod.f:19
Definition: run_mod.f:13
Definition: param_mod.f:2
subroutine drag_gidaspow_blend(lDgA, EPg, Mug, ROg, ROPg, VREL, DPM)
Definition: drag_gs.f:558
subroutine drag_koch_hill(lDgA, EPg, Mug, ROPg, VREL, DPM, DPA, PHIS)
Definition: drag_gs.f:1149
integer mype
Definition: compar_mod.f:24
double precision, dimension(:), allocatable mu_g
Definition: physprop_mod.f:68
double precision function ep_s(IJK, xxM)
Definition: fldvar_mod.f:178
subroutine start_log
Definition: machine_mod.f:182
logical model_b
Definition: run_mod.f:88
subroutine drag_wen_yu(lDgA, EPg, Mug, ROPg, VREL, DPM)
Definition: drag_gs.f:640
subroutine drag_syam_obrien(lDgA, EPg, Mug, ROg, VREL, DPM)
Definition: drag_gs.f:389
double precision, dimension(:), allocatable ro_g
Definition: fldvar_mod.f:32
double precision, parameter zero
Definition: param1_mod.f:27
subroutine end_log
Definition: machine_mod.f:208