MFIX  2016-1
des_granular_temperature.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
2 ! C
3 ! Subroutine: DES_GRANULAR_TEMPERATURE C
4 ! Purpose: Calculate the DES granular temperature C
5 ! C
6 ! C
7 ! Author: Jay Boyalakuntla Date: 12-Jun-04 C
8 ! Reviewer: Date: C
9 ! Revision: For parallel processing modifications are made to C
10 ! accomodate ghost cells (Pradeep G.) C
11 ! C
12 ! C
13 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
14 
15  SUBROUTINE des_granular_temperature
16 
17 !-----------------------------------------------
18 ! Modules
19 !-----------------------------------------------
20  USE compar
21  USE discretelement
22  USE fldvar, only: u_s, v_s, w_s, theta_m
23  USE fun_avg
24  USE functions
25  USE geometry
26  USE indices
27  USE mpi_utility
28  USE param
29  USE param1
30  USE physprop, only: mmax
31  USE run
32  USE sendrecv
33  IMPLICIT NONE
34 !-----------------------------------------------
35 ! Local Variables
36 !-----------------------------------------------
37 ! indices
38  INTEGER :: I, J, K, IJK
39 !
40  INTEGER :: M, LL
41 ! counter for no. of particles in phase m in cell ijk
42  INTEGER :: NP_PHASE(dimension_3, dimension_m)
43 ! temporary variable for mth phase granular temperature in cell ijk
44  DOUBLE PRECISION :: TEMP(dimension_3, dimension_m)
45 ! accounted for particles
46  INTEGER :: PC
47 ! squared particle velocity v.v
48  DOUBLE PRECISION :: SQR_VEL, SQR_ROT_VEL
49 !-----------------------------------------------
50 
51 ! Calculate a local species granular temperature for current instant of
52 ! time. Note that the following calculation of species granular
53 ! temperature employs a fluctuating particle velocity that is defined
54 ! as the difference between a particles velocity and the corresponding
55 ! local mean velocity of that particles species evaluated at the same
56 ! instant of time.
57 !----------------------------------------------------------------->>>
58 ! The following calculations are performed on the 'fluid' grid
59  temp(:,:) = zero
60  np_phase(:,:) = 0
61  pc = 0
62  DO ll = 1, max_pip
63 ! skipping particles that do not exist
64  IF(is_nonexistent(ll)) cycle
65  pc = pc + 1
66 ! skipping ghost particles
67  IF(is_ghost(ll) .or. is_entering_ghost(ll) .or. is_exiting_ghost(ll)) cycle
68 
69  i = pijk(ll,1)
70  j = pijk(ll,2)
71  k = pijk(ll,3)
72  ijk = pijk(ll,4)
73 
74  m = pijk(ll,5)
75  np_phase(ijk,m) = np_phase(ijk,m) + 1
76 
77  temp(ijk,m) = temp(ijk,m) + &
78  (des_vel_new(ll,1)-u_s(ijk,m))**2
79  temp(ijk,m) = temp(ijk,m) + &
80  (des_vel_new(ll,2)-v_s(ijk,m))**2
81  IF(do_k) THEN
82  temp(ijk,m) = temp(ijk,m) + &
83  (des_vel_new(ll,3)-w_s(ijk,m))**2
84  ENDIF
85 
86  IF(pc .EQ. pip) EXIT
87  ENDDO
88 
89 ! loop over all fluid cells
90  DO ijk = ijkstart3, ijkend3
91  IF(fluid_at(ijk)) THEN
92 
93  DO m = mmax+1,des_mmax+mmax
94  IF (np_phase(ijk,m) > 0 ) THEN
95  theta_m(ijk,m) = temp(ijk,m)/&
96  dble(dimn*np_phase(ijk,m))
97  ELSE
98  theta_m(ijk,m) = zero
99  ENDIF
100  ENDDO
101  ENDIF
102  ENDDO
103 
104 
105 ! Calculate global quantities: granular temperature, kinetic energy,
106 ! potential energy and average velocity at the current instant of time
107 !----------------------------------------------------------------->>>
108 
109 ! initialization for calculations
110  des_ke = zero
111  des_rote = zero
112  des_pe = zero
113  des_vel_avg(:) = zero
114 
115 ! Calculate global average velocity, kinetic energy &
116 ! potential energy
117  pc = 0
118  DO ll = 1, max_pip
119 ! skipping ghost particles and particles that don't exist
120  IF(is_nonexistent(ll)) cycle
121  pc = pc + 1
122  IF(is_ghost(ll) .OR. is_entering_ghost(ll) .OR. is_exiting_ghost(ll)) cycle
123 
124  sqr_vel = zero
125  sqr_rot_vel = zero
126  DO i = 1, dimn
127  sqr_vel = sqr_vel + des_vel_new(ll,i)**2
128  ENDDO
129 
130  DO i = 1, merge(1,3,no_k)
131  sqr_rot_vel = sqr_rot_vel + omega_new(ll,i)**2
132  ENDDO
133 
134 
135  des_ke = des_ke + pmass(ll)/2.d0 * sqr_vel
136 ! Calculation of rotational kinetic energy
137  des_rote = des_rote + &
138  (0.4d0*pmass(ll)*des_radius(ll)**2)/2.d0 * sqr_rot_vel
139  des_pe = des_pe + pmass(ll)*dble(abs(grav(2)))*&
140  des_pos_new(ll,2)
141  des_vel_avg(:) = des_vel_avg(:) + des_vel_new(ll,:)
142 
143  IF(pc .EQ. pip) EXIT
144  ENDDO
145 
146 !Calculating total number of particles in the entire domain
147 !Needed for correct average velocities and granular temp.
148  CALL global_all_sum(pip-ighost_cnt,tot_par)
149  CALL global_all_sum(des_vel_avg(1:dimn))
150 
151 !J.Musser changed PARTICLES TO PIP
152  IF(tot_par > 0) des_vel_avg(:) = des_vel_avg(:)/dble(tot_par)
153 
154 ! The following quantities are primarily used for debugging/developing
155 ! and allow a quick check of the energy conservation in the system.
156 ! In their current form they are best applied to monodisperse cases.
157 ! Calculate x,y,z components of global energy & granular temperature
158  global_gran_energy(:) = zero
159  global_gran_temp(:) = zero
160  pc = 0
161  DO ll = 1, max_pip
162 
163 ! skipping ghost particles and particles that don't exist
164  IF(is_nonexistent(ll)) cycle
165  pc = pc + 1
166  IF(is_ghost(ll) .OR. is_entering_ghost(ll) .OR. is_exiting_ghost(ll)) cycle
167 
168  global_gran_energy(:) = global_gran_energy(:) + &
169  0.5d0*pmass(ll)*(des_vel_new(ll,:)-des_vel_avg(:))**2
170  global_gran_temp(:) = global_gran_temp(:) + &
171  (des_vel_new(ll,:)-des_vel_avg(:))**2
172 
173  IF(pc .EQ. pip) EXIT
174  ENDDO
175 
176  CALL global_all_sum(global_gran_temp)
177  CALL global_all_sum(global_gran_energy)
178  CALL global_all_sum(des_ke)
179  CALL global_all_sum(des_pe)
180  CALL global_all_sum(des_rote)
181 
182  IF(tot_par > 0) global_gran_energy(:) = &
183  global_gran_energy(:)/dble(tot_par)
184  IF(tot_par > 0) global_gran_temp(:) = &
185  global_gran_temp(:)/dble(tot_par)
186 
187  RETURN
188 
189  END SUBROUTINE des_granular_temperature
190 
191 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
192 ! !
193 ! Subroutine: CALC_DES_BEDHEIGHT !
194 ! Purpose: Calculate an average bed height for each solids phase !
195 ! present !
196 ! !
197 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
198 
199  SUBROUTINE calc_des_bedheight
201 !-----------------------------------------------
202 ! Modules
203 !-----------------------------------------------
204  USE compar
205  USE des_bc
206  USE discretelement
207  USE fldvar
208  USE functions
209  USE geometry
210  USE indices
211  USE param, only: dimension_m
212  USE param1, only: zero
213  USE physprop
214  IMPLICIT NONE
215 !-----------------------------------------------
216 ! Local Variables
217 !-----------------------------------------------
218 ! particle index
219  INTEGER :: L
220 ! accounted for particles
221  INTEGER :: PC
222 ! solids phase no.
223  INTEGER :: M
224 ! ijk indices
225  INTEGER :: J, IJK
226 ! average height of fluid cell
227  DOUBLE PRECISION :: hcell
228 ! height of particle (y-position)
229  DOUBLE PRECISION :: hpart
230 ! volume fraction of phase M in fluid cell
231  DOUBLE PRECISION :: EP_SM
232 ! tmp variables for calculations
233  DOUBLE PRECISION :: tmp_num(dimension_m), tmp_den(dimension_m)
234 !-----------------------------------------------
235 
236 ! calculation of bed height following the formulation of Goldschmidt et
237 ! al., Powder Technology 138, 2003, 135-159
238  tmp_num(:) = zero
239  tmp_den(:) = zero
240  DO ijk = ijkstart3, ijkend3
241  j = j_of(ijk)
242  DO m = mmax+1, des_mmax+mmax
243  IF(rop_s(ijk,m) > zero) THEN
244  hcell = 0.5d0*(yn(j)+yn(j-1))
245  ep_sm = ep_s(ijk,m)
246  tmp_num(m) = tmp_num(m) + ep_sm*hcell*vol(ijk)
247  tmp_den(m) = tmp_den(m) + ep_sm*vol(ijk)
248  ENDIF
249  ENDDO
250  ENDDO
251 ! calculate avg height for each phase
252  IF (pip >0) bed_height(:) = tmp_num(:)/tmp_den(:)
253 
254 ! alternative method to calculating bed height (turned off atm)
255  IF(.false.) THEN
256  tmp_num(:) = zero
257  tmp_den(:) = zero
258 
259  pc = 0
260  DO l = 1, max_pip
261 ! skipping ghost particles and particles that don't exist
262  IF(is_nonexistent(l)) cycle
263  pc = pc + 1
264  IF(is_ghost(l) .OR. is_entering_ghost(l) .OR. is_exiting_ghost(l)) cycle
265 
266  m = pijk(l,5)
267  hpart = des_pos_new(l,2)
268  tmp_num(m) = tmp_num(m) + hpart
269  tmp_den(m) = tmp_den(m) + 1
270  IF(pc .EQ. pip) EXIT
271  ENDDO
272  ! calculate avg height for each phase
273  IF (pip >0) bed_height(:) = tmp_num(:)/tmp_den(:)
274  ENDIF
275 
276  RETURN
277 
278  END SUBROUTINE calc_des_bedheight
double precision, dimension(:,:), allocatable v_s
Definition: fldvar_mod.f:105
subroutine calc_des_bedheight
integer ijkend3
Definition: compar_mod.f:80
integer dimension_3
Definition: param_mod.f:11
double precision, dimension(:,:), allocatable w_s
Definition: fldvar_mod.f:117
double precision, dimension(:,:), allocatable u_s
Definition: fldvar_mod.f:93
subroutine des_granular_temperature
integer mmax
Definition: physprop_mod.f:19
integer, dimension(:), allocatable j_of
Definition: indices_mod.f:46
double precision, dimension(:,:), allocatable theta_m
Definition: fldvar_mod.f:149
Definition: run_mod.f:13
Definition: param_mod.f:2
logical no_k
Definition: geometry_mod.f:28
logical do_k
Definition: geometry_mod.f:30
integer ijkstart3
Definition: compar_mod.f:80
double precision function ep_s(IJK, xxM)
Definition: fldvar_mod.f:178
double precision, dimension(:,:), allocatable rop_s
Definition: fldvar_mod.f:51
double precision, dimension(:), allocatable vol
Definition: geometry_mod.f:212
integer dimension_m
Definition: param_mod.f:18
double precision, parameter zero
Definition: param1_mod.f:27