18 SUBROUTINE calc_vol_fr(P_STAR, RO_G, ROP_G, EP_G, ROP_S, IER)
36 USE run, only: ghd_2007, kt_type_enum
49 DOUBLE PRECISION,
INTENT(INOUT) :: RO_g(
dimension_3)
51 DOUBLE PRECISION,
INTENT(INOUT) :: ROP_g(
dimension_3)
53 DOUBLE PRECISION,
INTENT(INOUT) :: EP_g(
dimension_3)
57 INTEGER,
INTENT(INOUT) :: IER
62 DOUBLE PRECISION :: VOL_M
64 DOUBLE PRECISION :: EPcp
66 DOUBLE PRECISION :: EPS
68 DOUBLE PRECISION :: SUMVF
88 INTEGER :: Err_l(0:
numpes-1)
89 INTEGER :: Err_g(0:
numpes-1)
91 LOGICAL,
PARAMETER :: REPORT_NEG_VOLFRAC = .true.
107 IF (fluid_at(ijk))
THEN 131 DO m = 1,
mmax+des_mmax
134 rop_s(ijk,mcpl) = (epcp - sumvf)*
ro_s(ijk,mcpl)
160 ep_g(ijk) = rop_g(ijk)/ro_g(ijk)
161 sumvf = sumvf + ep_g(ijk)
165 IF(kt_type_enum == ghd_2007)
THEN 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)
186 ep_g(ijk) =
one - sumvf
189 IF (ep_g(ijk) <
zero)
THEN 191 IF(report_neg_volfrac)
CALL epgerr_log(ijk, wheader)
194 rop_g(ijk) = ep_g(ijk)*ro_g(ijk)
197 rop_s(ijk,mf) = (
one - sumvf)*
ro_s(ijk,mf)
253 if (wall_at(ijk)) cycle
259 if (wall_at(ijk)) cycle
301 INTEGER,
intent(in) :: IJK
302 LOGICAL,
intent(inout) :: tHeader
305 CHARACTER(LEN=255) :: lFile
306 INTEGER,
parameter :: lUnit = 4868
307 LOGICAL,
save :: fHeader = .true.
313 write(lfile,
"('EPgErr_',I4.4,'.log')")
mype 315 write(lfile,
"('EPgErr.log')")
317 inquire(file=trim(lfile),exist=lexists)
319 open(lunit,file=trim(adjustl(lfile)), &
320 status=
'old', position=
'append')
322 open(lunit,file=trim(adjustl(lfile)), status=
'new')
331 write(lunit,
"(/2x,'Simulation time: ',g12.5)")
time 336 write(lunit,
"(6x,A,1X,g12.5)",advance=
'NO')
'EP_g:',
ep_g(ijk)
338 write(lunit,
"(2x,A,1X,g12.5)", advance=
'NO') &
343 write(lunit,
"(24x)", advance=
'NO')
345 write(lunit,
"(2x,A,1X,g12.5)", advance=
'NO') &
350 write(lunit,
"(24x)", advance=
'NO')
352 write(lunit,
"(2x,A,1X,g12.5)", advance=
'NO') &
355 write(lunit,
"(24x,' ')")
358 write(lunit,
"(24x)", advance=
'NO')
360 write(lunit,
"(2x,A,1X,g12.5)", advance=
'NO') &
361 trim(
ivar(
'U_se',m)),
u_s(ijk,m)
363 write(lunit,
"(24x,' ')")
365 write(lunit,
"(24x)", advance=
'NO')
367 write(lunit,
"(2x,A,1X,g12.5)", advance=
'NO') &
368 trim(
ivar(
'V_sn',m)),
v_s(ijk,m)
370 write(lunit,
"(24x,' ')")
372 write(lunit,
"(24x)", advance=
'NO')
374 write(lunit,
"(2x,A,1X,g12.5)", advance=
'NO') &
375 trim(
ivar(
'W_st',m)),
w_s(ijk,m)
377 write(lunit,
"(24x,' ')")
379 write(lunit,
"(24x)", advance=
'NO')
381 write(lunit,
"(2x,A,1X,g12.5)", advance=
'NO') &
382 trim(
ivar(
'U_sw',m)),
u_s(west_of(ijk),m)
384 write(lunit,
"(24x,' ')")
386 write(lunit,
"(24x)", advance=
'NO')
388 write(lunit,
"(2x,A,1X,g12.5)", advance=
'NO') &
389 trim(
ivar(
'V_ss',m)),
v_s(south_of(ijk),m)
391 write(lunit,
"(24x,' ')")
393 write(lunit,
"(24x)", advance=
'NO')
395 write(lunit,
"(2x,A,1X,g12.5)", advance=
'NO') &
396 trim(
ivar(
'W_sb',m)),
w_s(bottom_of(ijk),m)
398 write(lunit,
"(24x,' ')")
402 write(lunit,
"(6x,A,1X,L1)",advance=
'NO')
'Cut Cell:',
cut_cell_at 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))") &
412 1000
FORMAT(
'One or more cells have reported a negative gas volume ', &
413 'fraction (EP_g).',/)
415 1001
FORMAT(/4x,
'IJK: ',i8,7x,
'I: ',i4,
' J: ',i4,
' K: ',i4)
double precision, dimension(:,:), allocatable v_s
integer, dimension(:), allocatable i_of
character(len=32) function ivar(VAR, i1, i2, i3)
double precision, dimension(:), allocatable yg_n
double precision, dimension(:), allocatable ep_g
double precision function inv_h(XXX, YYY)
double precision, parameter one
double precision, dimension(:), allocatable xg_e
double precision, dimension(:,:), allocatable w_s
subroutine epgerr_log(IJK, tHeader)
double precision, dimension(:), allocatable epg_jfac
logical, dimension(:), allocatable small_cell_at
double precision, parameter undefined
logical, dimension(dim_m) close_packed
double precision, dimension(:,:), allocatable u_s
integer, dimension(:), allocatable phase_4_p_s
integer, dimension(:), allocatable k_of
double precision, dimension(:), allocatable ep_g_blend_end
integer, dimension(:), allocatable j_of
subroutine calc_vol_fr(P_STAR, RO_G, ROP_G, EP_G, ROP_S, IER)
double precision, dimension(:,:), allocatable ro_s
double precision, dimension(:), allocatable epg_ifac
integer, dimension(:), allocatable phase_4_p_g
logical, dimension(:), allocatable cut_cell_at
subroutine set_ep_factors
integer, parameter undefined_i
double precision function ep_s(IJK, xxM)
double precision, dimension(:,:), allocatable eps_ifac
double precision, dimension(:,:), allocatable rop_s
double precision, dimension(dim_m) mu_s0
double precision, dimension(:), allocatable zg_t
double precision, parameter zero