MFIX  2016-1
calc_ps_pic.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
2 ! Subroutine: CALC_PS_PIC !
3 ! Author: R. Garg !
4 ! !
5 ! Purpose: Calculate the particle stress. !
6 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
7  SUBROUTINE calc_ps_pic
8 
9 
10 ! Global Variables:
11 !---------------------------------------------------------------------//
12 ! Flag to use Snider's particle stress model
14 ! Particle stress
15  use mfix_pic, only: pic_p_s
16 
17 ! Module procedures:
18 !---------------------------------------------------------------------//
19  use sendrecv, only: send_recv
20 
21  IMPLICIT NONE
22 
23 !......................................................................!
24 
25 
26  IF(mppic_solid_stress_snider) THEN
28  ELSE
29  CALL calc_ps_pic_garg
30  ENDIF
31 
32  CALL send_recv(pic_p_s,1)
33 
34  RETURN
35  END SUBROUTINE calc_ps_pic
36 
37 
38 
39 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
40 ! Subroutine: CALC_PS_PIC !
41 ! Author: R. Garg !
42 ! !
43 ! Purpose: Evaluate the particle stress model of Snider. !
44 ! !
45 ! REF: D.M. Snider, "Three-Dimensional Multiphase Particle-in-Cell !
46 ! Model for Dense Particle Flows," Journal of Computational !
47 ! Physics, Vol. 170, No. 2, pp. 523-549, 2001. !
48 ! !
49 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
50  SUBROUTINE calc_ps_pic_snider
51 
52 ! Global Variables:
53 !---------------------------------------------------------------------//
54 ! Model parameters for Snider particle stress model
55  use mfix_pic, only: fric_exp_pic
56  use mfix_pic, only: psfac_fric_pic
57  use mfix_pic, only: fric_non_sing_fac
58 ! Calculated particle stress
59  use mfix_pic, only: pic_p_s
60 ! Fluid phase volume fraction
61  use fldvar, only: ep_g
62 ! Fluid volume fraction at close-pack
63  use constant, only: ep_star
64 ! Domain bounds
65  use compar, only: ijkstart3, ijkend3
66 ! Double precision parameters
67  use param1, only: one
68 
69 ! Module procedures:
70 !---------------------------------------------------------------------//
71  use functions, only: fluid_at
72  use functions, only: west_of, east_of
73  use functions, only: south_of, north_of
74  use functions, only: bottom_of, top_of
75 
76  IMPLICIT NONE
77 
78 ! Local Variables:
79 !---------------------------------------------------------------------//
80 ! Loop counter
81  INTEGER :: IJK
82 ! Volume fraction of cell, modified for wall cells.
83  DOUBLE PRECISION :: lEPg
84 !......................................................................!
85 
86  DO ijk = ijkstart3, ijkend3
87 
88  IF(fluid_at(ijk)) THEN
89  lepg = ep_g(ijk)
90  ELSE
91 
92 ! Set the volume fraction in the wall to close pack.
93  lepg = ep_star
94 
95 ! Use the lowest value across all adjacent fluid cells. This is to keep
96 ! cells below close pack from pushing parcels through the walls.
97 ! lIJK = EAST_OF(IJK)
98 ! IF(FLUID_AT(lIJK)) lEPg = min(lEPg, EP_G(lIJK))
99 !! lIJK = WEST_OF(IJK)
100 ! IF(FLUID_AT(lIJK)) lEPg = min(lEPg, EP_G(lIJK))
101 ! lIJK = NORTH_OF(IJK)
102 ! IF(FLUID_AT(lIJK)) lEPg = min(lEPg, EP_G(lIJK))
103 !! lIJK = SOUTH_OF(IJK)
104 ! IF(FLUID_AT(lIJK)) lEPg = min(lEPg, EP_G(lIJK))
105 ! IF(DO_K) THEN
106 ! lIJK = TOP_OF(IJK)
107 ! IF(FLUID_AT(lIJK)) lEPg = min(lEPg, EP_G(lIJK))
108 ! lIJK = BOTTOM_OF(IJK)
109 ! IF(FLUID_AT(lIJK)) lEPg = min(lEPg, EP_G(lIJK))
110 ! ENDIF
111  ENDIF
112 
113 ! Particle stress :: Snider (Eq 33)
114  pic_p_s(ijk,1) = psfac_fric_pic *((one - lepg)**fric_exp_pic)/&
115  max(lepg - ep_star, fric_non_sing_fac*lepg)
116  ENDDO
117 
118 
119 
120  RETURN
121  END SUBROUTINE calc_ps_pic_snider
122 
123 
124 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
125 ! Subroutine: CALC_PS_PIC !
126 ! Author: R. Garg !
127 ! !
128 ! Purpose: Evaluate the particle stress as a coloring function: !
129 ! X=0.0 :: cells below packing limit !
130 ! X=EPg :: cells above packing limit !
131 ! X=1.0 :: wall cells (far avobe max packing) !
132 ! !
133 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
134  SUBROUTINE calc_ps_pic_garg
136 
137 ! Global Variables:
138 !---------------------------------------------------------------------//
139 ! Calculated particle stress
140  use mfix_pic, only: pic_p_s
141 ! Resulting particle stress force
142  use mfix_pic, only: ps_force_pic
143 ! Fluid phase volume fraction
144  use fldvar, only: ep_g
145 ! Fluid volume fraction at close-pack
146  use constant, only: ep_star
147 ! Domain bounds
148  use compar, only: ijkstart3, ijkend3
149 ! Double precision parameters
150  use param1, only: zero, one
151 
152 ! Module procedures:
153 !---------------------------------------------------------------------//
154  use functions, only: fluid_at
155 
156 
157  IMPLICIT NONE
158 
159 
160 ! Local Variables:
161 !---------------------------------------------------------------------//
162 ! Loop counter
163  INTEGER :: IJK
164 !......................................................................!
165 
166 
167 ! The Garg model uses a coloring function approach.
168  DO ijk = ijkstart3, ijkend3
169  ps_force_pic(:,ijk) = zero
170  IF(fluid_at(ijk)) THEN
171  IF(ep_g(ijk) < ep_star) THEN
172  pic_p_s(ijk,1) = (one - ep_g(ijk))
173  ELSE
174  pic_p_s(ijk,1) = zero
175  ENDIF
176  ELSE
177  pic_p_s(ijk,1) = one
178  ENDIF
179  ENDDO
180 
181  RETURN
182  END SUBROUTINE calc_ps_pic_garg
double precision fric_non_sing_fac
Definition: mfix_pic_mod.f:18
subroutine calc_ps_pic
Definition: calc_ps_pic.f:8
integer ijkend3
Definition: compar_mod.f:80
double precision, dimension(:), allocatable ep_g
Definition: fldvar_mod.f:15
double precision fric_exp_pic
Definition: mfix_pic_mod.f:17
double precision, parameter one
Definition: param1_mod.f:29
logical mppic_solid_stress_snider
Definition: mfix_pic_mod.f:20
subroutine calc_ps_pic_garg
Definition: calc_ps_pic.f:135
double precision, dimension(:,:), allocatable pic_p_s
Definition: mfix_pic_mod.f:81
subroutine calc_ps_pic_snider
Definition: calc_ps_pic.f:51
double precision psfac_fric_pic
Definition: mfix_pic_mod.f:16
double precision ep_star
Definition: constant_mod.f:29
integer ijkstart3
Definition: compar_mod.f:80
double precision, dimension(:,:), allocatable ps_force_pic
Definition: mfix_pic_mod.f:25
double precision, parameter zero
Definition: param1_mod.f:27