MFIX  2016-1
calc_vol_fr.f
Go to the documentation of this file.
1 ! TO DO:
2 ! 1. Check the formulation based on MCP.
3 ! 2. The pressure correction should be based on sum of close-packed
4 ! solids?
5 
6 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
7 ! C
8 ! Subroutine: CALC_VOL_FR C
9 ! Purpose: Calculate volume fractions of phases used in pressure C
10 ! corrections. C
11 ! C
12 ! Notes: see mark_phase_4_cor for more details C
13 ! C
14 ! Author: M. Syamlal Date: 5-JUL-96 C
15 ! C
16 ! C
17 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
18  SUBROUTINE calc_vol_fr(P_STAR, RO_G, ROP_G, EP_G, ROP_S, IER)
19 
20 
21 ! Modules
22 !---------------------------------------------------------------------//
23  USE compar
24  USE constant
25  USE discretelement
26  USE functions
27  USE geometry
28  USE indices
29  USE mpi_utility
30  USE parallel
31  USE param
32  USE param1
33  USE pgcor
34  USE physprop
35  USE pscor
36  USE run, only: ghd_2007, kt_type_enum
37  USE sendrecv
38  USE solids_pressure
39  USE visc_s
40  use fldvar, only: ro_s, ep_s
41 
42  IMPLICIT NONE
43 
44 ! Dummy Arguments
45 !---------------------------------------------------------------------//
46 ! Solids pressure
47  DOUBLE PRECISION, INTENT(IN) :: P_star(dimension_3)
48 ! Gas density
49  DOUBLE PRECISION, INTENT(INOUT) :: RO_g(dimension_3)
50 ! Gas bulk density
51  DOUBLE PRECISION, INTENT(INOUT) :: ROP_g(dimension_3)
52 ! Gas volume fraction
53  DOUBLE PRECISION, INTENT(INOUT) :: EP_g(dimension_3)
54 ! solids bulk densities
55  DOUBLE PRECISION, INTENT(INOUT) :: ROP_s(dimension_3, dimension_m)
56 ! error index
57  INTEGER, INTENT(INOUT) :: IER
58 
59 ! Local variables
60 !---------------------------------------------------------------------//
61 ! volume of particle type M for GHD theory
62  DOUBLE PRECISION :: VOL_M
63 ! volume fraction of close-packed region
64  DOUBLE PRECISION :: EPcp
65 ! volume fraction of solids phase
66  DOUBLE PRECISION :: EPS
67 ! sum of volume fractions
68  DOUBLE PRECISION :: SUMVF
69 ! Whichever phase is given by MF becomes the phase whose volume fraction
70 ! is corrected based on all other phases present. Generally MF gets
71 ! defined as 0 so that the gas phase void fraction becomes corrected
72 ! based on the summation of the volume fractions of all other phases
73  INTEGER :: MF
74 ! Whichever phase is given by MCPl becomes the phase whose volume
75 ! fraction is corrected based on value of maximum close packing and all
76 ! other solids phase that can close pack. This is basically a local
77 ! variable for MCP but only in cells where close packed conditions
78 ! exist.
79  INTEGER :: MCPl
80 ! Index of solids phase
81  INTEGER :: M
82 ! Indices
83  INTEGER :: IJK
84 
85 ! Arrays for storing errors:
86 ! 110 - Negative volume fraciton
87 ! 11x - Unclassified
88  INTEGER :: Err_l(0:numpes-1) ! local
89  INTEGER :: Err_g(0:numpes-1) ! global
90 
91  LOGICAL, PARAMETER :: REPORT_NEG_VOLFRAC = .true.
92 
93 ! Flag to write log header
94  LOGICAL :: wHeader
95 !---------------------------------------------------------------------//
96 
97 
98 ! Initialize:
99  wheader = .true.
100 ! Initialize error flag.
101  err_l = 0
102 
103 !!$omp parallel do private(MCPl, EPCP, SUMVF, MF, M) &
104 !!$omp& schedule(static)
105 
106  DO ijk = ijkstart3, ijkend3
107  IF (fluid_at(ijk)) THEN
108 
109 ! calculate the volume fraction of the solids phase based on the volume
110 ! fractions of all other solids phases and on the value of maximum
111 ! packing when that solids phase continuity was not solved for the
112 ! indicated cell.
113 !----------------------------------------------------------------->>>
114  IF (phase_4_p_s(ijk) /= undefined_i) THEN
115 ! for the current cell check if a solids phase continuity was skipped.
116 ! this value will either be undefined (no cell was skipped in any
117 ! solids continuity equations) or be a solids phase index (indicated
118 ! solids continuity was skipped) for a solids phase that does close pack
119 ! (i.e., close_packed=T) and the cell exhibits close packing conditions.
120 ! note: this branch is never entered given the existing version of
121 ! mark_phase_4_cor.
122  mcpl = phase_4_p_s(ijk)
123 
124 ! finding the value of maximum close packing based on the expression for
125 ! plastic pressure
126  epcp = 1. - inv_h(p_star(ijk),ep_g_blend_end(ijk))
127 ! summing the solids volume fraction of all continuum solids phases
128 ! that are marked as close_packed except for the solids phase which
129 ! is also marked by phase_4_p_s (skipping its own continuity)
130  sumvf = zero
131  DO m = 1, mmax+des_mmax
132  IF (close_packed(m) .AND. m/=mcpl) sumvf = sumvf + ep_s(ijk,m)
133  ENDDO
134  rop_s(ijk,mcpl) = (epcp - sumvf)*ro_s(ijk,mcpl)
135  ENDIF
136 !-----------------------------------------------------------------<<<
137 
138 
139 ! calculate the volume fraction of the 'solids' phase based on the
140 ! volume fractions of all other phases (including gas) if the gas
141 ! continuity was solved rather than that phases own continuity.
142 ! if the gas continuity was not solved then calculate the void
143 ! fraction of the gas phase based on all other solids phases.
144 !----------------------------------------------------------------->>>
145 ! for the current cell check if the gas phase continuity was solved for
146 ! the gas phase while the solids phase continuity for the indicated
147 ! solids phase was skipped. this value will either be 0 (gas phase
148 ! continuity was not solved) or be a solids phase index (gas continuity
149 ! was solved while the indicated solids phase continuity was skipped)
150 ! for a solids phase that does not close pack (i.e., close_packed=F) and
151 ! is in greater concentration than the gas phase.
152 ! Note: MF will always be set to 0 here given the existing version of
153 ! mark_phase_4_cor
154  mf = phase_4_p_g(ijk)
155 
156  sumvf = zero
157  IF (0 /= mf) THEN
158 ! if gas continuity was solved rather than the solids phase, then
159 ! include the gas phase void fraction in the summation here.
160  ep_g(ijk) = rop_g(ijk)/ro_g(ijk)
161  sumvf = sumvf + ep_g(ijk)
162  ENDIF
163 
164 ! evaluate mixture bulk density rop_s(mmax) for GHD theory
165  IF(kt_type_enum == ghd_2007) THEN
166  rop_s(ijk,mmax) = zero ! mixture density
167  DO m = 1, smax
168  IF (m /= mf) THEN
169  rop_s(ijk,mmax) = rop_s(ijk,mmax) + ro_s(ijk,m)*ep_s(ijk,m)
170  ENDIF
171  ENDDO
172  ENDIF
173 
174 ! summing the solids volume fraction of all continuum solids phases
175 ! except for the continuum solids phase which was marked by phase_4_p_g
176 ! (skipping its continuity while solving gas continuity)
177  DO m = 1, des_mmax+mmax
178  IF(kt_type_enum == ghd_2007 .AND. m == mmax) cycle
179  IF (m /= mf) sumvf = sumvf + ep_s(ijk,m)
180  ENDDO
181 
182  IF (0 == mf) THEN
183 ! if no gas phase continuity was solved in the current cell then correct
184 ! the void fraction of the gas phase based on the total solids volume
185 ! fraction of all solids phases
186  ep_g(ijk) = one - sumvf
187 
188 ! Set error flag for negative volume fraction.
189  IF (ep_g(ijk) < zero) THEN
190  err_l(mype) = 110
191  IF(report_neg_volfrac) CALL epgerr_log(ijk, wheader)
192  ENDIF
193 
194  rop_g(ijk) = ep_g(ijk)*ro_g(ijk)
195  ELSE
196 ! else correct the volume fraction of the solids phase that was marked
197  rop_s(ijk,mf) = (one - sumvf)*ro_s(ijk,mf)
198  ENDIF
199 !-----------------------------------------------------------------<<<
200 
201  ENDIF ! end if (fluid_at(ijk))
202  ENDDO ! end do (ijk=ijkstart3,ijkend3)
203 
204  CALL send_recv(ep_g, 2)
205  CALL send_recv(rop_g, 2)
206  CALL send_recv(rop_s, 2)
207 
208  CALL global_all_sum(err_l, err_g)
209  ier = maxval(err_g)
210 
211 
212  RETURN
213  END SUBROUTINE calc_vol_fr
214 
215 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
216 ! C
217 ! Subroutine: SET_EP_FACTORS C
218 ! Purpose: Set multiplication factors to ep_g to control the form C
219 ! of the governing equations C
220 ! C
221 ! References: C
222 ! Anderson and Jackson, A fluid mechanical description of fluidized C
223 ! beds, Ind. Eng. Chem. Fundam., 6(4) 1967, 527-539. C
224 ! Ishii, Thermo-fluid dynamic theory of two-phase flow, des Etudes C
225 ! et Recherches D'Electricite de France, Eyrolles, Paris, France C
226 ! 1975. C
227 ! C
228 ! C
229 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
230  SUBROUTINE set_ep_factors
232 ! Modules
233 !---------------------------------------------------------------------//
234  use compar, only: ijkstart3, ijkend3
235  use fldvar, only: ep_g, ep_s
236  use fldvar, only: epg_ifac, eps_ifac, epg_jfac
237  use functions, only: wall_at
238  use param1, only: one, undefined
239  use physprop, only: mmax, mu_s0
240  use run, only: jackson, ishii
241  IMPLICIT NONE
242 ! Local variables
243 !---------------------------------------------------------------------//
244 ! indices
245  INTEGER :: ijk, m
246 !---------------------------------------------------------------------//
247  epg_jfac(:) = one
248  epg_ifac(:) = one
249  eps_ifac(:,:) = one
250 
251  if (jackson) then
252  do ijk = ijkstart3, ijkend3
253  if (wall_at(ijk)) cycle
254  epg_jfac(ijk) = ep_g(ijk)
255  enddo
256  endif
257  if (ishii) then
258  do ijk = ijkstart3, ijkend3
259  if (wall_at(ijk)) cycle
260  epg_ifac(ijk) = ep_g(ijk)
261  do m = 1, mmax
262 ! This seems more appropriate for non-granular systems
263 ! So currently only incorporate this for 'constant' viscosity cases
264  IF (mu_s0(m) /= undefined) THEN
265  eps_ifac(ijk,m) = ep_s(ijk,m)
266  ENDIF
267  enddo
268  enddo
269  endif
270 
271  RETURN
272  END SUBROUTINE set_ep_factors
273 
274 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvv!
275 ! !
276 ! Subroutine: EPgErr_LOG !
277 ! Purpose: Record information about the location and conditions that !
278 ! resulted in a negative gas phase volume fraction. !
279 ! !
280 ! Author: J. Musser Date: 16-APR-15 !
281 ! Reviewer: Date: !
282 ! !
283 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^!
284  SUBROUTINE epgerr_log(IJK, tHeader)
286 ! Simulation time
287  use run, only: time
288 ! Gas phase pressure.
289  use fldvar, only: ep_g, ep_s, rop_s, ro_s, u_s, v_s, w_s
290  use cutcell
291 
292  use physprop, only: smax
293  use compar
294  use indices
295  use functions
296  use error_manager
297 
298 
299  IMPLICIT NONE
300 
301  INTEGER, intent(in) :: IJK
302  LOGICAL, intent(inout) :: tHeader
303 
304  LOGICAL :: lExists
305  CHARACTER(LEN=255) :: lFile
306  INTEGER, parameter :: lUnit = 4868
307  LOGICAL, save :: fHeader = .true.
308 
309  INTEGER :: M
310 
311  lfile = '';
312  if(numpes > 1) then
313  write(lfile,"('EPgErr_',I4.4,'.log')") mype
314  else
315  write(lfile,"('EPgErr.log')")
316  endif
317  inquire(file=trim(lfile),exist=lexists)
318  if(lexists) then
319  open(lunit,file=trim(adjustl(lfile)), &
320  status='old', position='append')
321  else
322  open(lunit,file=trim(adjustl(lfile)), status='new')
323  endif
324 
325  if(fheader) then
326  write(lunit,1000)
327  fheader = .false.
328  endif
329 
330  if(theader) then
331  write(lunit,"(/2x,'Simulation time: ',g12.5)") time
332  theader = .false.
333  endif
334 
335  write(lunit,1001) ijk, i_of(ijk), j_of(ijk), k_of(ijk)
336  write(lunit,"(6x,A,1X,g12.5)",advance='NO') 'EP_g:', ep_g(ijk)
337  DO m=1,smax
338  write(lunit,"(2x,A,1X,g12.5)", advance='NO') &
339  trim(ivar('EP_s',m)), ep_s(ijk,m)
340  ENDDO
341  write(lunit,"(' ')")
342 
343  write(lunit,"(24x)", advance='NO')
344  DO m=1,smax
345  write(lunit,"(2x,A,1X,g12.5)", advance='NO') &
346  trim(ivar('RO_s',m)), ro_s(ijk,m)
347  ENDDO
348  write(lunit,"(' ')")
349 
350  write(lunit,"(24x)", advance='NO')
351  DO m=1,smax
352  write(lunit,"(2x,A,1X,g12.5)", advance='NO') &
353  trim(ivar('ROPs',m)), rop_s(ijk,m)
354  ENDDO
355  write(lunit,"(24x,' ')")
356 
357 
358  write(lunit,"(24x)", advance='NO')
359  DO m=1,smax
360  write(lunit,"(2x,A,1X,g12.5)", advance='NO') &
361  trim(ivar('U_se',m)), u_s(ijk,m)
362  ENDDO
363  write(lunit,"(24x,' ')")
364 
365  write(lunit,"(24x)", advance='NO')
366  DO m=1,smax
367  write(lunit,"(2x,A,1X,g12.5)", advance='NO') &
368  trim(ivar('V_sn',m)), v_s(ijk,m)
369  ENDDO
370  write(lunit,"(24x,' ')")
371 
372  write(lunit,"(24x)", advance='NO')
373  DO m=1,smax
374  write(lunit,"(2x,A,1X,g12.5)", advance='NO') &
375  trim(ivar('W_st',m)), w_s(ijk,m)
376  ENDDO
377  write(lunit,"(24x,' ')")
378 
379  write(lunit,"(24x)", advance='NO')
380  DO m=1,smax
381  write(lunit,"(2x,A,1X,g12.5)", advance='NO') &
382  trim(ivar('U_sw',m)), u_s(west_of(ijk),m)
383  ENDDO
384  write(lunit,"(24x,' ')")
385 
386  write(lunit,"(24x)", advance='NO')
387  DO m=1,smax
388  write(lunit,"(2x,A,1X,g12.5)", advance='NO') &
389  trim(ivar('V_ss',m)), v_s(south_of(ijk),m)
390  ENDDO
391  write(lunit,"(24x,' ')")
392 
393  write(lunit,"(24x)", advance='NO')
394  DO m=1,smax
395  write(lunit,"(2x,A,1X,g12.5)", advance='NO') &
396  trim(ivar('W_sb',m)), w_s(bottom_of(ijk),m)
397  ENDDO
398  write(lunit,"(24x,' ')")
399 
400 
401  if(cartesian_grid) then
402  write(lunit,"(6x,A,1X,L1)",advance='NO') 'Cut Cell:', cut_cell_at(ijk)
403  write(lunit,"(6x,A,1X,L1)") 'Small Cell:', small_cell_at(ijk)
404  write(lunit,"(6x,'Coordinates (E/N/T): ',1X,3(2x, g17.8))") &
405  xg_e(i_of(ijk)), yg_n(j_of(ijk)), zg_t(k_of(ijk))
406  endif
407 
408  close(lunit)
409 
410  RETURN
411 
412  1000 FORMAT('One or more cells have reported a negative gas volume ', &
413  'fraction (EP_g).',/)
414 
415  1001 FORMAT(/4x,'IJK: ',i8,7x,'I: ',i4,' J: ',i4,' K: ',i4)
416 
417  END SUBROUTINE epgerr_log
double precision, dimension(:,:), allocatable v_s
Definition: fldvar_mod.f:105
integer, dimension(:), allocatable i_of
Definition: indices_mod.f:45
integer ijkend3
Definition: compar_mod.f:80
character(len=32) function ivar(VAR, i1, i2, i3)
double precision, dimension(:), allocatable yg_n
Definition: cutcell_mod.f:45
double precision, dimension(:), allocatable ep_g
Definition: fldvar_mod.f:15
Definition: pgcor_mod.f:1
double precision function inv_h(XXX, YYY)
double precision, parameter one
Definition: param1_mod.f:29
integer dimension_3
Definition: param_mod.f:11
double precision, dimension(:), allocatable xg_e
Definition: cutcell_mod.f:44
logical ishii
Definition: run_mod.f:85
double precision, dimension(:,:), allocatable w_s
Definition: fldvar_mod.f:117
subroutine epgerr_log(IJK, tHeader)
Definition: calc_vol_fr.f:285
double precision, dimension(:), allocatable epg_jfac
Definition: fldvar_mod.f:18
logical, dimension(:), allocatable small_cell_at
Definition: cutcell_mod.f:360
double precision, parameter undefined
Definition: param1_mod.f:18
logical, dimension(dim_m) close_packed
Definition: physprop_mod.f:56
double precision, dimension(:,:), allocatable u_s
Definition: fldvar_mod.f:93
integer numpes
Definition: compar_mod.f:24
integer, dimension(:), allocatable phase_4_p_s
Definition: pscor_mod.f:28
logical jackson
Definition: run_mod.f:83
integer, dimension(:), allocatable k_of
Definition: indices_mod.f:47
double precision, dimension(:), allocatable ep_g_blend_end
Definition: visc_s_mod.f:60
integer mmax
Definition: physprop_mod.f:19
integer, dimension(:), allocatable j_of
Definition: indices_mod.f:46
subroutine calc_vol_fr(P_STAR, RO_G, ROP_G, EP_G, ROP_S, IER)
Definition: calc_vol_fr.f:19
Definition: pscor_mod.f:1
Definition: run_mod.f:13
Definition: param_mod.f:2
double precision, dimension(:,:), allocatable ro_s
Definition: fldvar_mod.f:45
logical cartesian_grid
Definition: cutcell_mod.f:13
double precision, dimension(:), allocatable epg_ifac
Definition: fldvar_mod.f:19
integer, dimension(:), allocatable phase_4_p_g
Definition: pgcor_mod.f:22
logical, dimension(:), allocatable cut_cell_at
Definition: cutcell_mod.f:355
integer mype
Definition: compar_mod.f:24
subroutine set_ep_factors
Definition: calc_vol_fr.f:231
integer ijkstart3
Definition: compar_mod.f:80
integer, parameter undefined_i
Definition: param1_mod.f:19
double precision function ep_s(IJK, xxM)
Definition: fldvar_mod.f:178
double precision, dimension(:,:), allocatable eps_ifac
Definition: fldvar_mod.f:20
double precision, dimension(:,:), allocatable rop_s
Definition: fldvar_mod.f:51
integer smax
Definition: physprop_mod.f:22
double precision, dimension(dim_m) mu_s0
Definition: physprop_mod.f:53
double precision time
Definition: run_mod.f:45
double precision, dimension(:), allocatable zg_t
Definition: cutcell_mod.f:46
integer dimension_m
Definition: param_mod.f:18
double precision, parameter zero
Definition: param1_mod.f:27