70 REAL(wp),
ALLOCATABLE,
DIMENSION(:) ::
rvolcgas 183 REAL(wp) :: rho_solid_avg(n_part)
185 REAL(wp) :: rho_solid_tot_avg
187 REAL(wp) :: alfa_s(n_part)
189 REAL(wp) :: atm_volume_fraction
191 REAL(wp) :: volcgas_mix_volume_fraction
199 REAL(wp) :: Rrhovolcgas_mix
203 REAL(wp) :: enth_at_vent
205 REAL(wp) :: mixt_enth , check_enth
207 REAL(wp) :: erupted_mass_Fraction
211 IF ( verbose_level .GE. 1 )
THEN 214 WRITE(*,*)
'--------- initialize_mixture ----------' 222 solid_partial_mass_fraction = solid_partial_mass_fraction0
224 solid_mass_fraction(1:n_part) = solid_mass_fraction0(1:n_part)
228 CALL eval_quad_values
233 IF (
n_gas .GT. 0 )
THEN 254 cpsolid = sum( solid_mass_fraction(1:n_part) * cp_part(1:n_part) ) &
255 / ( sum(solid_mass_fraction(1:n_part) ) )
263 IF ( write_flag )
WRITE(*,*)
'Initial specific enthalpy at vent =', &
276 erupted_mass_fraction
283 solid_mass_fraction = solid_mass_fraction * erupted_mass_fraction
287 IF ( verbose_level .GE. 1 )
THEN 295 WRITE(*,*)
'cpsolid',cpsolid
303 rho_solid_avg(i_part) = 1.0_wp / ( sum( f_quad(:,:,i_part) &
304 * w_quad(:,:,i_part) * m_quad(:,:,i_part) &
305 / rho_quad(:,:,i_part) ) / sum(f_quad(:,:,i_part) &
306 * w_quad(:,:,i_part) * m_quad(:,:,i_part) ) )
310 rho_solid_tot_avg = 1.0_wp / sum( solid_partial_mass_fraction(1:n_part) / &
311 rho_solid_avg(1:n_part) )
317 alfa_s(i_part) = solid_partial_mass_fraction(i_part) * &
318 rho_solid_tot_avg / rho_solid_avg(i_part)
320 IF ( verbose_level .GE. 1 )
THEN 322 WRITE(*,*)
'i_part',i_part
323 WRITE(*,*)
'rho_solid_avg',rho_solid_avg(i_part)
324 WRITE(*,*)
'alfa_s',i_part,alfa_s(i_part)
333 mixt_enth = erupted_mass_fraction * enth_at_vent + &
353 WRITE(*,*)
'WARNING: WATER ADDED AT THE VENT' 354 WRITE(*,*)
'New mixture enthalpy =', mixt_enth
357 WRITE(*,*)
'New mixture temperature =',
t_mix 379 IF (
n_gas .GT. 0 )
THEN 401 rrhovolcgas_mix = 0.0_wp
402 IF (
n_gas .GT. 0 )
THEN 420 rhowv = pa / ( rwv *
t_mix )
423 IF (
n_gas .GT. 0 )
THEN 442 c0 =
rho_mix * solid_mass_fraction(i_part) &
446 DO i_mom = 0,
n_mom-1
454 CALL eval_quad_values
456 IF ( verbose_level .GE. 1 )
THEN 458 WRITE(*,*)
'rhowv',rhowv
462 WRITE(*,*)
'rho_lw',
rho_lw 463 WRITE(*,*)
'rho_solid_tot_avg',rho_solid_tot_avg
494 WRITE(*,*)
'WARNING: calculated initial velocity =',
w 501 IF ( write_flag)
WRITE(*,*) &
502 'WARNING: Initial radius [m] computed from MER and w0 =',
r 514 WRITE(*,*)
'WARNING: Initial vel [m/s] computed from MER and r =',
w 523 IF ( write_flag)
WRITE(*,
'(1x,A,1x,es15.8)') &
528 IF ( verbose_level .GE. 1 )
THEN 530 WRITE(*,*)
'cpsolid',cpsolid
531 WRITE(*,*)
'rho_atm',rho_atm
570 REAL(wp),
INTENT(IN) :: enth
573 REAL(wp),
INTENT(IN) :: pa
575 REAL(wp),
INTENT(IN) :: cpsolid
655 REAL(wp),
INTENT(IN) :: enth
658 REAL(wp),
INTENT(IN) :: pres
660 REAL(wp),
INTENT(IN) :: cpsolid
663 REAL(wp) :: wv_mol_fract
666 REAL(wp) :: da_mol_fract
676 REAL(wp) :: lw_mf0 , lw_mf1 , lw_mf2
678 REAL(wp) :: ice_mf0, ice_mf1, ice_mf2
680 REAL(wp) :: wv_mf0, wv_mf1, wv_mf2
682 REAL(wp) :: f0, f1, f2
684 REAL(wp) :: temp0 , temp1 , temp2
686 REAL(wp) :: enth0 , enth1 , enth2
698 IF (
n_gas .GT. 0)
THEN 731 IF (
n_gas .GT. 0 )
THEN 767 IF ( temp0 .GT. 29.65_wp )
THEN 769 el = 611.2_wp * exp( 17.67_wp * ( temp0 - 273.16_wp ) / ( temp0 - 29.65_wp ) )
770 f0 = ( pres - el ) * wv_mol_fract - el * ( da_mol_fract &
788 IF (
n_gas .GT. 0)
THEN 825 IF ( temp2 .GT. 29.65_wp )
THEN 827 el = 611.2_wp * exp( 17.67_wp * ( temp2-273.16_wp ) / ( temp2 - 29.65_wp ) )
828 f2 = ( pres - el ) * wv_mol_fract - el * da_mol_fract &
841 vapour_liquid_case:
IF ( ( f0 .LT. 0.0_wp ) .AND. ( f2 .LT. 0.0_wp ) )
THEN 851 wv_pres = wv_mol_fract * pres
857 ELSEIF ( ( f0 .GT. 0.0_wp ) .AND. ( f2 .GT. 0.0_wp ) )
THEN 876 lw_mf1 = 0.5_wp * ( lw_mf0 + lw_mf2 )
882 IF (
n_gas .GT. 0 )
THEN 921 IF ( temp1 .GT. 29.65_wp )
THEN 923 el = 611.2_wp * exp( 17.67_wp * ( temp1 - 273.16_wp ) &
924 / ( temp1 - 29.65_wp ) )
925 f1 = ( pres - el ) * wv_mol_fract - el * da_mol_fract - el * &
930 IF ( f1 * f0 .LT. 0.0_wp )
THEN 944 IF ( abs(temp2-temp0) .LT. 1.0e-5_wp )
THEN 952 ELSEIF ( abs(lw_mf2 - lw_mf0) .LT. 1.0e-7_wp )
THEN 964 END IF vapour_liquid_case
983 REAL(wp),
INTENT(IN) :: enth
986 REAL(wp),
INTENT(IN) :: pres
988 REAL(wp),
INTENT(IN) :: cpsolid
991 REAL(wp) :: wv_mol_fract
994 REAL(wp) :: da_mol_fract
1004 REAL(wp) :: lw_mf0 , lw_mf1 , lw_mf2
1006 REAL(wp) :: ice_mf0, ice_mf1, ice_mf2
1008 REAL(wp) :: wv_mf0, wv_mf1, wv_mf2
1010 REAL(wp) :: f0, f1, f2
1012 REAL(wp) :: temp0 , temp1 , temp2
1014 REAL(wp) :: enth0 , enth1 , enth2
1025 temp0 =
t_ref - 40.0_wp
1028 es = -9.097_wp * ( (273.16_wp / temp0 ) - 1.0_wp ) - 3.566_wp * log10(273.16_wp / temp0) &
1029 + 0.876_wp * ( 1.0_wp - (temp0 / 273.16_wp))
1031 es = 611.22_wp * ( 10.0_wp**es )
1033 wv_mol_fract = es / pres
1035 IF (
n_gas .GT. 0 )
THEN 1039 wv_mol_wt * wv_mol_fract ) / (wv_mol_fract - 1.0_wp)
1045 wv_mol_wt * wv_mol_fract ) / (wv_mol_fract - 1.0_wp)
1057 + ice_mf0 * (
c_ice * temp0 ) &
1068 el = 611.2_wp * exp( 17.67_wp * ( temp2 - 273.16_wp ) / ( temp2 - 29.65_wp ) )
1070 wv_mol_fract = el / pres
1072 IF (
n_gas .GT. 0 )
THEN 1076 wv_mol_wt * wv_mol_fract ) / (wv_mol_fract - 1.0_wp)
1082 wv_mol_wt * wv_mol_fract ) / (wv_mol_fract - 1.0_wp)
1099 + ice_mf2 * (
c_ice * temp2 ) &
1109 IF ((f0*f2 .GT. 0.0_wp))
THEN 1118 IF ( ( lw_mf2 .GT. 0.0_wp ) .AND. (lw_mf2 .LT. 1.0_wp ) )
THEN 1127 temp1 = (temp0 + temp2) * 0.5_wp
1129 lw_mf1 = lw_mf2 * ( temp1 - (
t_ref - 40) ) / 40.0_wp
1131 es = -9.097_wp * ( (273.16_wp / temp1 ) - 1.0_wp ) - &
1132 3.566_wp * log10(273.16_wp / temp1) &
1133 + 0.876_wp * ( 1.0_wp - (temp1 / 273.16_wp) )
1135 es = 611.22_wp * ( 10.0_wp**es )
1137 wv_mol_fract = es / pres
1139 IF (
n_gas .GT. 0 )
THEN 1143 wv_mol_wt * wv_mol_fract ) / (wv_mol_fract - 1.0_wp)
1148 wv_mol_wt * wv_mol_fract ) / (wv_mol_fract - 1.0_wp)
1158 + ice_mf1 * (
c_ice * temp1 ) &
1170 IF (f1 * f0 .LT. 0.0_wp)
THEN 1183 IF (abs(temp2-temp0) .LT. 1.0e-5_wp )
THEN 1185 IF ( ( wv_mf1 .LT. 0.0_wp ) .OR. ( ice_mf1 .LT. 0.0_wp ) )
THEN 1187 WRITE(*,*)
'WARNING: negative mass fraction' 1188 WRITE(*,*)
'water_vapor_mass_fraction =', wv_mf1
1189 WRITE(*,*)
'ice_mass_fraction =', ice_mf1
1190 WRITE(*,*)
'liquid_mass_fraction =', ice_mf1
1210 ELSEIF (lw_mf2 .LT. 0.0_wp)
THEN 1234 REAL(wp),
INTENT(IN) :: enth
1237 REAL(wp),
INTENT(IN) :: pres
1239 REAL(wp),
INTENT(IN) :: cpsolid
1242 REAL(wp) :: wv_mol_fract
1245 REAL(wp) :: da_mol_fract
1255 REAL(wp) :: lw_mf0 , lw_mf1 , lw_mf2
1257 REAL(wp) :: ice_mf0, ice_mf1, ice_mf2
1259 REAL(wp) :: wv_mf0, wv_mf1, wv_mf2
1261 REAL(wp) :: f0, f1, f2
1263 REAL(wp) :: temp0 , temp1 , temp2
1265 REAL(wp) :: enth0 , enth1 , enth2
1297 IF (
n_gas .GT. 0)
THEN 1340 IF ( temp0 .GT. 29.65_wp )
THEN 1342 es = -9.097_wp * ( (273.16_wp / temp0 ) - 1.0_wp ) - 3.566_wp * log10(273.16_wp / temp0) &
1343 + 0.876_wp * ( 1.0_wp - (temp0 / 273.16_wp))
1345 es = 611.22_wp * ( 10.0_wp**es )
1371 IF (
n_gas .GT. 0)
THEN 1413 IF ( temp2 .GT. 29.65_wp )
THEN 1415 es = -9.097_wp * ( (273.16_wp / temp2) - 1.0_wp ) - 3.566_wp * log10(273.16_wp / temp2) &
1416 + 0.876_wp * ( 1.0_wp - (temp2 / 273.16_wp))
1418 es = 611.22_wp * ( 10.0_wp**es )
1428 IF ( ( f0 .LT. 0.0_wp ) .AND. ( f2 .LT. 0.0_wp ) )
THEN 1440 ELSEIF ( ( f0 .GT. 0.0_wp ) .AND. ( f2 .GT. 0.0_wp ) )
THEN 1455 ice_mf1 = 0.5_wp * ( ice_mf0 + ice_mf2 )
1466 IF (
n_gas .GT. 0)
THEN 1511 es = -9.097_wp * ( 273.16_wp / temp1 -1.0_wp ) - 3.566_wp * log10(273.16_wp / temp1) &
1512 + 0.876_wp * (1.0_wp - (temp1 / 273.16_wp))
1514 es = 611.22_wp * (10.0_wp**es)
1528 IF ( f1 * f2 .LT. 0.0_wp )
THEN 1542 IF ( abs(temp2-temp0) .LT. 1.0e-3_wp )
THEN 1554 ELSEIF ( abs(ice_mf2 - ice_mf0) .LT. 1.0e-7_wp )
THEN 1587 REAL(wp),
INTENT(IN) :: enth
1590 REAL(wp),
INTENT(IN) :: pres
1592 REAL(wp),
INTENT(IN) :: cpsolid
integer n_mom
Number of moments.
integer n_part
number of particle phases
real(wp) exit_status
exit_status
real(wp) pa
Atmospheric pressure.
real(wp) t_part
Particle temperature for aggregation (Costa model)
real(wp) u
plume x-horizontal velocity
real(wp) rho_atm
Atmospheric density.
real(wp) ice_mass_fraction
mass fraction of ice in the mixture
character(len=20) distribution
Ditribution of the particles: .
subroutine eval_particles_moments
Particles moments computation.
real(wp) liquid_water_mass_fraction
mass fraction of liquid water in the mixture
real(wp), dimension(:), allocatable volcgas_mass_fraction
mass fractions of volcanic gases
real(wp) cpair
specific heat capacity for dry air
real(wp), dimension(:,:,:), allocatable m_quad
Abscissa of quadrature formulas.
real(wp), parameter h_lw0
enthalpy of liquid water at reference temperature (J kg-1)
real(wp) volcgas_mix_mol_fract
subroutine initialize_mixture
Mixture properties initialization.
real(wp), dimension(:), allocatable volcgas_mol_wt
molecular weight of additional volcanic gases
real(wp) gas_volume_fraction
gas vlume fraction in the mixture
real(wp) water_vapor_mass_fraction
mass fraction of water vapor in the mixture
real(wp) rho_ice
Density of ice in the mixture.
logical water_flag
Flag for water.
real(wp) water_volume_fraction0
initial water volume fraction
real(wp) dry_air_mass_fraction
mass fraction of dry air in the mixture
integer n_nodes
Number of nodes for the quadrature.
real(wp) rvolcgas_mix
gas constant of volcanic gases mixture ( J/(kg K) )
real(wp), parameter wv_mol_wt
molecular weight of water vapor
real(wp) volcgas_mix_mass_fraction
mass fraction of the volcanic gas in the mixture
real(wp) added_water_temp
real(wp), dimension(:,:,:), allocatable f_quad
Values of linear reconstructions at quadrature points.
real(wp) added_water_mass_fraction
real(wp), dimension(:,:,:), allocatable rho_quad
Particle densities at quadrature points.
real(wp) cpvolcgas_mix
specific heat of volcanic gases mixture
real(wp), dimension(:), allocatable cp_part
Heat capacity of particle phases.
real(wp), dimension(:), allocatable solid_partial_mass_fraction
mass fraction of the particle phases with respect to the total solid
subroutine eval_temp(enth, pa, cpsolid)
Mixture temperature.
real(wp) solid_tot_volume_fraction
solid volume fraction in the mixture
real(wp) r0
initial radius of the plume
real(wp) rgasmix
universal constant for the mixture
real(wp) water_volume_fraction
water volume fraction in the mixture
real(wp) volcgas_mix_mol_wt
real(wp) atm_mass_fraction
mass fraction of the entrained air in the mixture
real(wp), dimension(:), allocatable solid_mass_fraction
mass fraction of the particle phases with respect to the mixture
subroutine eval_temp_wv_lw_ice(enth, pres, cpsolid)
subroutine eval_temp_wv_lw(enth, pres, cpsolid)
Mixture temperature with vapour and liquid water.
Gas/particles mixture module.
real(wp) rho_mix
mixture density
real(wp), parameter h_wv0
enthalpy of water vapor at reference temperature (J kg-1)
real(wp) water_vapor_volume_fraction
mass fraction of water vapor in the mixture
real(wp) phi
angle between the plume trajectory and ground
real(wp), parameter c_ice
specific heat of ice (J K-1 kg-1)
real(wp) rair
perfect gas constant for dry air ( J/(kg K) )
Method of Moments module.
real(wp), dimension(:), allocatable rvolcgas
gas constants for volcanic gases
logical function isset(var)
Input variable check.
subroutine eval_temp_wv_ice(enth, pres, cpsolid)
real(wp), dimension(:,:,:), allocatable mom
Moments of the particles diameter.
real(wp), parameter t_ref
reference temperature (K)
real(wp) mag_u
velocity magnitude along the centerline
real(wp), parameter da_mol_wt
molecular weight of dry air
real(wp), dimension(:), allocatable solid_partial_mass_fraction0
init mass fraction of the particle phases with respect to the total solid
real(wp), dimension(:,:,:), allocatable w_quad
Weights of quadrature formulas.
real(wp) liquid_water_volume_fraction
mass fraction of liquid water in the mixture
logical initial_neutral_density
logical defining if the plume has neutral density at the base
real(wp) water_mass_fraction
mass fraction of water in the mixture
real(wp) rho_gas
gas phase density
real(wp), dimension(:), allocatable cpvolcgas
specific heat capacity for volcanic gases
real(wp) cpsolid
Average heat capacity of particles.
integer, parameter wp
working precision
real(wp), dimension(:), allocatable solid_mass_fraction0
initial mass fraction of the particle phases with respect to the mixture
real(wp) t_mix
mixture temperature
real(wp), parameter c_lw
specific heat of liquid water (J K-1 kg-1)
real(wp), parameter c_wv
specifc heat of water vapor (J K-1 kg-1)
real(wp) rhovolcgas_mix
volcanic gases mixture density
real(wp) function particles_density(i_part, phi)
Particle density.
real *8 gi
Gravity acceleration.
real(wp) mixture_enthalpy
real(wp), dimension(:), allocatable volcgas_mass_fraction0
initial mass fractions of volcanic gases
real(wp), dimension(:), allocatable rhovolcgas
volcanic gases densities
real(wp), parameter rwv
gas constant for water vapor ( J/(kg K) )
real(wp) t_mix0
initial temperature
real(wp) rho_lw
Density of liquid water in the mixture.
subroutine eval_quad_values
Quadrature values computation.
real(wp), dimension(:,:,:), allocatable mom0
Initial moments of the particles diameter.
real(wp) water_mass_fraction0
initial water mass fraction
integer n_gas
volcanic gas species number
real(wp) solid_tot_mass_fraction
solid mass fraction in the mixture
real(wp) ice_volume_fraction
mass fraction of ice in the mixture
real(wp) gas_mass_fraction
gas mass fraction in the mixture
real(wp) w
plume vertical velocity
subroutine eval_temp_no_water(enth, pres, cpsolid)
integer verbose_level
Level of verbose output (0 = minimal output on screen)