MFIX  2016-1
calc_gamma_des.f
Go to the documentation of this file.
1 #include "version.inc"
2 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
3 ! Subroutine: DES_CALC_GAMMA !
4 ! !
5 ! Purpose: Calculate the heat transfer coefficient (GAMMAxSA) for !
6 ! particle-fluid heat transfer. !
7 ! !
8 ! Author: J.Musser Date: 16-Jun-10 !
9 ! !
10 ! Comments: !
11 ! !
12 ! REF: Ranz, W.E. and Marshall, W.R., "Friction and transfer !
13 ! coefficients for single particles and packed beds," Chemical !
14 ! Engineering Science, Vol. 48, No. 5, pp 247-253, 1925. !
15 ! !
16 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
17  SUBROUTINE calc_gamma_des(NP, pGAMMA)
18 
19  USE compar
20  USE constant
21  USE des_thermo
22  USE discretelement
23  USE exit, only: mfix_exit
24  USE fldvar
25  USE geometry
26  USE indices
27  USE param1
28  USE physprop
29  USE fun_avg
30  USE functions
31 
32  IMPLICIT NONE
33 
34 ! Passed variables
35 !---------------------------------------------------------------------//
36 ! Index value of particle
37  INTEGER, INTENT(IN) :: NP
38 ! Convective heat transfer coefficient
39  DOUBLE PRECISION, INTENT(OUT) :: pGAMMA
40 
41 ! Local variables
42 !---------------------------------------------------------------------//
43 ! Fluid cell indices
44  INTEGER IMJK, IJMK, IJKM
45 ! Double precision value for 1/3
46  DOUBLE PRECISION, PARAMETER :: THIRD = (1.0d0/3.0d0)
47 
48  DOUBLE PRECISION N_Pr ! Prandtl Number
49  DOUBLE PRECISION N_Re ! Reynolds Number
50  DOUBLE PRECISION N_Nu ! Nusselt Number
51 
52 ! Magnitude of slip velocity
53  DOUBLE PRECISION SLIP
54 ! Fluid velocity
55  DOUBLE PRECISION cUg, cVg, cWg
56  DOUBLE PRECISION Us, Vs, Ws
57 ! Index value of fluid cell
58  INTEGER :: IJK
59 !---------------------------------------------------------------------//
60 
61  ijk = pijk(np,4)
62 ! Initialization
63  imjk = im_of(ijk)
64  ijmk = jm_of(ijk)
65  ijkm = km_of(ijk)
66 
67  SELECT CASE(des_conv_corr_enum)
68 
69  CASE (ranz_1952) ! (Ranz and Mrshall, 1952)
70 ! Initialize variables
71  slip = zero
72  n_re = zero
73  n_nu = zero
74 ! Gas velocity in fluid cell IJK
75  cug = avg_x_e(u_g(imjk), u_g(ijk), 1)
76  cvg = avg_y_n(v_g(ijmk), v_g(ijk))
77 ! Particle Velocity
78  us = des_vel_new(np,1)
79  vs = des_vel_new(np,2)
80 
81 ! Calculate the magnitude of the slip velocity
82  IF(no_k) THEN
83  slip = sqrt((cug-us)**2 + (cvg-vs)**2)
84  ELSE
85  cwg = avg_z_t(w_g(ijkm), w_g(ijk))
86  ws = des_vel_new(np,3)
87  slip = sqrt((cug-us)**2 + (cvg-vs)**2 + (cwg-ws)**2)
88  ENDIF
89 
90 ! Calculate the Prandtl Number
91  IF(k_g(ijk) > zero) THEN
92  n_pr = (c_pg(ijk)*mu_g(ijk))/k_g(ijk)
93  ELSE
94  n_pr = large_number
95  ENDIF
96 
97 ! Calculate the particle Reynolds Number
98  IF(mu_g(ijk) > zero) THEN
99  n_re = (2.0d0*des_radius(np)*slip*ro_g(ijk)) / mu_g(ijk)
100  ELSE
101  n_re = large_number
102  ENDIF
103 
104 ! Calculate the Nusselt Number
105  n_nu = 2.0d0 + 0.6d0 *((n_re)**half * (n_pr)**third)
106 
107 ! Calculate the convective heat transfer coefficient
108  pgamma = (n_nu * k_g(ijk))/(2.0d0 * des_radius(np))
109 
110  CASE DEFAULT
111  WRITE(*,*)'INVALID DES CONVECTION MODEL'
112  error_stop 'INVALID DES CONVECTION MODEL'
113  CALL mfix_exit(mype)
114  END SELECT
115 
116  RETURN
117  END SUBROUTINE calc_gamma_des
integer, parameter ranz_1952
integer des_conv_corr_enum
subroutine mfix_exit(myID, normal_termination)
Definition: exit.f:5
Definition: exit.f:2
double precision, dimension(:), allocatable v_g
Definition: fldvar_mod.f:99
double precision, dimension(:), allocatable w_g
Definition: fldvar_mod.f:111
double precision, parameter half
Definition: param1_mod.f:28
double precision, parameter large_number
Definition: param1_mod.f:23
logical no_k
Definition: geometry_mod.f:28
integer mype
Definition: compar_mod.f:24
double precision, dimension(:), allocatable mu_g
Definition: physprop_mod.f:68
double precision, dimension(:), allocatable u_g
Definition: fldvar_mod.f:87
double precision, dimension(:), allocatable k_g
Definition: physprop_mod.f:92
double precision, dimension(:), allocatable ro_g
Definition: fldvar_mod.f:32
subroutine calc_gamma_des(NP, pGAMMA)
double precision, parameter zero
Definition: param1_mod.f:27
double precision, dimension(:), allocatable c_pg
Definition: physprop_mod.f:80