MFIX  2016-1
adjust_theta.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
2 ! C
3 ! Subroutine: ADJUST_THETA C
4 ! Purpose: Remove small negative values of theta caused by linear C
5 ! solvers C
6 ! C
7 ! Author: M. Syamlal Date: 02-APR-98 C
8 ! C
9 ! Modified: S. Benyahia Date: 02-AUG-06 C
10 ! Purpose: check for small negative numbers at walls C
11 ! (not just fluid cells) C
12 ! C
13 ! C
14 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
15 
16  SUBROUTINE adjust_theta(M, IER)
17 
18 !-----------------------------------------------
19 ! Modules
20 !-----------------------------------------------
21  USE param1, only: zero
22  USE toleranc, only: zero_ep_s
23  USE constant, only: pi, to_si
24 ! granular temperature of solids phase m
25  USE fldvar, only: theta_m
26 ! material density of solids phase m
27  USE fldvar, only: ro_s
28 ! particle diameter of solids phase m
29  USE fldvar, only: d_p
30 ! number of solids phases
31  USE physprop, only: smax
32 ! kt types
33  USE run, only: kt_type
34  USE run, only: kt_type_enum
35  USE run, only: lun_1984
36  USE run, only: simonin_1996
37  USE run, only: ahmadi_1995
38  USE run, only: gd_1999
39  USE run, only: gtsh_2012
40  USE run, only: ia_2005
41  USE run, only: ghd_2007
42 ! needed for function.inc
43  USE compar
44  USE exit, only: mfix_exit
45  USE functions
46  USE geometry
47  USE indices
48 
49  IMPLICIT NONE
50 !-----------------------------------------------
51 ! Dummy arguments
52 !-----------------------------------------------
53 ! solids phase
54  INTEGER, INTENT(IN) :: M
55 ! error indicator
56  INTEGER, INTENT(INOUT) :: IER
57 !-----------------------------------------------
58 ! Local variables
59 !-----------------------------------------------
60 ! Indices
61  INTEGER :: IJK
62 ! Solids phase index
63  INTEGER :: L
64 ! Particle mass and diameter for use with those kinetic theories
65 ! that include mass of particle in definition of theta
66  DOUBLE PRECISION :: M_PM, D_PM
67 ! small value of theta_m
68  DOUBLE PRECISION :: smallTheta
69 !-----------------------------------------------
70 
71  ier = 0
72  smalltheta = (to_si)**4 * zero_ep_s
73 
74  DO ijk = ijkstart3, ijkend3
75  IF ( fluid_at(ijk) ) THEN
76 
77  SELECT CASE(kt_type_enum)
78  CASE (lun_1984, simonin_1996, ahmadi_1995, gd_1999, &
79  gtsh_2012)
80  IF (theta_m(ijk,m) < smalltheta) &
81  theta_m(ijk,m) = smalltheta
82 
83  CASE (ia_2005)
84  d_pm = d_p(ijk,m)
85  m_pm = (pi/6.d0)*(d_pm**3)*ro_s(ijk,m)
86  IF (theta_m(ijk,m) < smalltheta*m_pm) &
87  theta_m(ijk,m) = smalltheta*m_pm
88 
89  CASE (ghd_2007)
90  m_pm = zero
91  DO l = 1,smax
92  d_pm = d_p(ijk,l)
93  m_pm = m_pm +(pi/6.d0)*(d_pm**3)*ro_s(ijk,l)
94  ENDDO
95  m_pm = m_pm/dble(smax)
96  IF (theta_m(ijk,m) < smalltheta*m_pm) &
97  theta_m(ijk,m) = smalltheta*m_pm
98 
99  CASE DEFAULT
100 ! should never hit this
101  WRITE (*, '(A)') 'ADJUST_THETA'
102  WRITE (*, '(A,A)') 'Unknown KT_TYPE: ', kt_type
103  call mfix_exit(mype)
104  END SELECT ! end selection of kt_type_enum
105  ENDIF ! end if (fluid_at)
106  ENDDO ! end do ijk
107 
108  RETURN
109  END SUBROUTINE adjust_theta
110 
double precision to_si
Definition: constant_mod.f:146
integer ijkend3
Definition: compar_mod.f:80
double precision, dimension(:,:), allocatable d_p
Definition: fldvar_mod.f:57
subroutine mfix_exit(myID, normal_termination)
Definition: exit.f:5
Definition: exit.f:2
double precision, parameter zero_ep_s
Definition: toleranc_mod.f:15
double precision, dimension(:,:), allocatable theta_m
Definition: fldvar_mod.f:149
Definition: run_mod.f:13
double precision, dimension(:,:), allocatable ro_s
Definition: fldvar_mod.f:45
subroutine adjust_theta(M, IER)
Definition: adjust_theta.f:17
integer mype
Definition: compar_mod.f:24
integer ijkstart3
Definition: compar_mod.f:80
integer smax
Definition: physprop_mod.f:22
double precision, parameter pi
Definition: constant_mod.f:158
double precision, parameter zero
Definition: param1_mod.f:27