PLUME-MoM-TSM  1.0
VolcanicPlumeModel
mixture.f90
Go to the documentation of this file.
1 !********************************************************************************
3 !
9 !********************************************************************************
10 
12 
13  USE variables, ONLY: gi , pi_g
14  USE variables, ONLY : wp
15 
16  IMPLICIT NONE
17 
19  REAL(wp) :: gas_mass_fraction
20 
22  REAL(wp) :: gas_volume_fraction
23 
25  REAL(wp) :: rho_gas
26 
28  REAL(wp) :: rgasmix
29 
31  REAL(wp) :: rho_mix
32 
35 
37  REAL(wp) :: t_mix
38 
40  REAL(wp) :: exit_status
41 
44 
47 
49  REAL(wp) :: t_mix0
50 
53 
56 
59 
60  ! mass flow rate
61  REAL(wp) :: mass_flow_rate
62 
64  INTEGER :: n_gas
65 
67  REAL(wp), ALLOCATABLE, DIMENSION(:) :: rhovolcgas
68 
70  REAL(wp), ALLOCATABLE, DIMENSION(:) :: rvolcgas
71 
73  REAL(wp), ALLOCATABLE, DIMENSION(:) :: cpvolcgas
74 
76  REAL(wp), ALLOCATABLE, DIMENSION(:) :: volcgas_mol_wt
77 
79  REAL(wp), ALLOCATABLE, DIMENSION(:) :: volcgas_mass_fraction0
80 
82  REAL(wp), ALLOCATABLE, DIMENSION(:) :: volcgas_mass_fraction
83 
85  REAL(wp) :: rhovolcgas_mix
86 
88  REAL(wp) :: rvolcgas_mix
89 
91  REAL(wp) :: cpvolcgas_mix
92 
94  REAL(wp) :: atm_mass_fraction
95 
98 
101 
104 
107 
110 
113 
116 
118  REAL(wp) :: ice_mass_fraction
119 
122 
124 
125  REAL(wp) :: volcgas_mix_mol_wt
126 
127  REAL(wp) :: mixture_enthalpy
128 
130  REAL(wp) :: rho_lw
131 
133  REAL(wp) :: rho_ice
134 
135  REAL(wp) :: added_water_temp
136 
138 
139  SAVE
140 
141 CONTAINS
142 
143  !******************************************************************************
145  !
147  !
151  !******************************************************************************
152 
153  SUBROUTINE initialize_mixture
155  ! external variables
156  USE meteo_module, ONLY : pa , rho_atm , rair , rwv , c_wv
157  USE meteo_module, ONLY : cpair , t_ref , h_wv0 , c_ice, h_lw0 , c_lw , &
159 
160  USE moments_module, ONLY : n_nodes , n_mom , n_sections
161 
164 
167 
168  USE particles_module, ONLY : m_quad , f_quad , w_quad , rho_quad
169 
170  USE plume_module, ONLY: w , r , u , mag_u , phi , log10_mfr, r0
171 
173 
174  ! external procedures
178 
179  USE variables, ONLY: isset
180 
181  IMPLICIT NONE
182 
183  REAL(wp) :: rho_solid_avg(n_part)
184 
185  REAL(wp) :: rho_solid_tot_avg
186 
187  REAL(wp) :: alfa_s(n_part)
188 
189  REAL(wp) :: atm_volume_fraction
190 
191  REAL(wp) :: volcgas_mix_volume_fraction
192 
193  INTEGER :: i_part
194 
195  INTEGER :: i_mom
196 
197  INTEGER :: i_gas
198 
199  REAL(wp) :: Rrhovolcgas_mix
200 
201  REAL(wp) :: rhowv
202 
203  REAL(wp) :: enth_at_vent
204 
205  REAL(wp) :: mixt_enth , check_enth
206 
207  REAL(wp) :: erupted_mass_Fraction
208 
209  REAL(wp) :: C0
210 
211  IF ( verbose_level .GE. 1 ) THEN
212 
213  WRITE(*,*)
214  WRITE(*,*) '--------- initialize_mixture ----------'
215 
216  END IF
217 
218  !--- Mass fractions in the erutped mixture (before adding external water) ---
219 
221 
222  solid_partial_mass_fraction = solid_partial_mass_fraction0
223 
224  solid_mass_fraction(1:n_part) = solid_mass_fraction0(1:n_part)
225 
226  mom = mom0
227 
228  CALL eval_quad_values
229 
230  !WRITE(*,*) 'qui'
231  !WRITE(*,*) 'mom0',mom
232 
233  IF ( n_gas .GT. 0 ) THEN
234 
236 
237  ELSE
238 
240 
241  END IF
242 
244 
245  ! All volcanic water is vapour
247 
248  ! No air is entrained at the vent
249  dry_air_mass_fraction = 0.0_wp
250 
253 
254  cpsolid = sum( solid_mass_fraction(1:n_part) * cp_part(1:n_part) ) &
255  / ( sum(solid_mass_fraction(1:n_part) ) )
256 
257  !Specific enthalpy before addition of external water
258  enth_at_vent = solid_tot_mass_fraction * cpsolid * t_mix0 &
259  + water_vapor_mass_fraction * ( h_wv0 + c_wv * ( t_mix0 - t_ref ) ) &
261 
262 
263  IF ( write_flag ) WRITE(*,*) 'Initial specific enthalpy at vent =', &
264  enth_at_vent
265 
266 
267  !------ Corrections of mass fractions and moments for the added water -------
268  erupted_mass_fraction = 1.0_wp - added_water_mass_fraction
269 
270  water_mass_fraction = water_mass_fraction * erupted_mass_fraction + &
272 
273  dry_air_mass_fraction = dry_air_mass_fraction * erupted_mass_fraction
274 
276  erupted_mass_fraction
277 
279 
282 
283  solid_mass_fraction = solid_mass_fraction * erupted_mass_fraction
284 
285  solid_tot_mass_fraction = solid_tot_mass_fraction * erupted_mass_fraction
286 
287  IF ( verbose_level .GE. 1 ) THEN
288 
289  WRITE(*,*) 'solid_tot_mass_fraction',solid_tot_mass_fraction
290  WRITE(*,*) 'water_mass_fraction', water_mass_fraction
291  WRITE(*,*) 'volcgas_mix_mass_fraction', volcgas_mix_mass_fraction
292  WRITE(*,*) 'dry_air_mass_fraction', dry_air_mass_fraction
293  WRITE(*,*) 'water_vapor_mass_fraction', water_vapor_mass_fraction
294  WRITE(*,*) 'added_water_mass_fraction', added_water_mass_fraction
295  WRITE(*,*) 'cpsolid',cpsolid
296 
297  READ(*,*)
298 
299  END IF
300 
301  DO i_part=1,n_part
302 
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) ) )
307 
308  END DO
309 
310  rho_solid_tot_avg = 1.0_wp / sum( solid_partial_mass_fraction(1:n_part) / &
311  rho_solid_avg(1:n_part) )
312 
313  ! WRITE(*,*) 'rho_solid_tot_avg',rho_solid_tot_avg
314 
315  DO i_part = 1,n_part
316 
317  alfa_s(i_part) = solid_partial_mass_fraction(i_part) * &
318  rho_solid_tot_avg / rho_solid_avg(i_part)
319 
320  IF ( verbose_level .GE. 1 ) THEN
321 
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)
325 
326  END IF
327 
328  END DO
329 
330  ! WRITE(*,*) 'alfa_s',alfa_s
331 
332  !---------- Specific enthalpy after addition of external water --------------
333  mixt_enth = erupted_mass_fraction * enth_at_vent + &
335 
336  ! The new temperature and the partitioning of water is computed
337 
338  CALL eval_temp(mixt_enth,pa,cpsolid)
339 
340  ! Compute the specific enthalpy with the new temperature and the corrected
341  ! mass fractions
342  check_enth = dry_air_mass_fraction * cpair * t_mix &
343  + solid_tot_mass_fraction * cpsolid * t_mix &
344  + water_vapor_mass_fraction * ( h_wv0 + c_wv * ( t_mix - t_ref ) ) &
345  + liquid_water_mass_fraction * ( h_lw0 + c_lw * ( t_mix - t_ref ) ) &
346  + ice_mass_fraction * ( c_ice * t_mix ) &
348 
350 
351  IF ( added_water_mass_fraction .GT. 0.0_wp ) THEN
352 
353  WRITE(*,*) 'WARNING: WATER ADDED AT THE VENT'
354  WRITE(*,*) 'New mixture enthalpy =', mixt_enth
355  ! WRITE(*,*) 'check_enth', check_enth
356  ! WRITE(*,*) 't_mix0,t_mix',t_mix0,t_mix
357  WRITE(*,*) 'New mixture temperature =',t_mix
358  WRITE(*,*) 'New solid mass fraction =',solid_tot_mass_fraction
359  WRITE(*,*) 'New water mass fraction =', water_mass_fraction
360  WRITE(*,*) 'New volcgas mix mass fraction =', volcgas_mix_mass_fraction
361  ! WRITE(*,*) 'dry_air_mass_fraction', dry_air_mass_fraction
362  WRITE(*,*) 'New water vapor mass fraction =', water_vapor_mass_fraction
363  WRITE(*,*) 'New liquid water mass fraction =', liquid_water_mass_fraction
364  ! WRITE(*,*) 'ice_mass_fraction', ice_mass_fraction
365  WRITE(*,*) 'New gas mass fraction =', gas_mass_fraction
366  ! WRITE(*,*) 'vent_water',( water_mass_fraction-added_water_mass_fraction ) / &
367  ! erupted_mass_fraction
368  WRITE(*,*)
369 
370 
371  END IF
372 
373  !--- With the new temperature compute the densities of the gas components ---
374 
375  ! Compute density of gas species and mixture of gas species
376  rvolcgas_mix = 0.0_wp
377  cpvolcgas_mix = 0.0_wp
378 
379  IF ( n_gas .GT. 0 ) THEN
380 
381  DO i_gas = 1,n_gas
382 
384  * rvolcgas(i_gas)
385 
387  * cpvolcgas(i_gas)
388 
389  END DO
390 
393 
394  ELSE
395 
396  rvolcgas_mix = 0.0_wp
397  cpvolcgas_mix = 0.0_wp
398 
399  END IF
400 
401  rrhovolcgas_mix = 0.0_wp
402  IF ( n_gas .GT. 0 ) THEN
403 
404  DO i_gas = 1,n_gas
405 
406  rrhovolcgas_mix = rrhovolcgas_mix + volcgas_mass_fraction(i_gas) &
407  / ( pa / ( rvolcgas(i_gas) * t_mix ) )
408 
409  END DO
410 
411  rhovolcgas_mix = sum(volcgas_mass_fraction(1:n_gas)) / rrhovolcgas_mix
412 
413  ELSE
414 
415  rhovolcgas_mix = 0.0_wp
416 
417  END IF
418 
419  ! Density of water vapour
420  rhowv = pa / ( rwv * t_mix )
421 
422  ! Density of gas mixture (water vapur+volcanic gas). No dry air at the vent
423  IF ( n_gas .GT. 0 ) THEN
424 
427  ELSE
428 
430 
431  END IF
432 
433  ! Density of the mixture at the vent
435  rho_solid_tot_avg + liquid_water_mass_fraction / rho_lw + &
437 
438  DO i_part = 1,n_part
439 
440  ! the coefficient C0 (=mom0) for the particles size distribution is
441  ! evaluated in order to have the corrected bulk density
442  c0 = rho_mix * solid_mass_fraction(i_part) &
443  / sum( mom(1,1:n_sections,i_part) )
444 
445  ! the moments are corrected with the factor C0
446  DO i_mom = 0, n_mom-1
447 
448  mom(i_mom,1:n_sections,i_part) = c0 * mom(i_mom,1:n_sections,i_part)
449 
450  END DO
451 
452  END DO
453 
454  CALL eval_quad_values
455 
456  IF ( verbose_level .GE. 1 ) THEN
457 
458  WRITE(*,*) 'rhowv',rhowv
459  WRITE(*,*) 'rhovolcgas_mix',rhovolcgas_mix
460  WRITE(*,*) 'rho_gas',rho_gas
461  WRITE(*,*) 'rho_ice',rho_ice
462  WRITE(*,*) 'rho_lw',rho_lw
463  WRITE(*,*) 'rho_solid_tot_avg',rho_solid_tot_avg
464  WRITE(*,*) 'rhoB_solid_tot',solid_tot_mass_fraction*rho_mix
465  WRITE(*,*) 'rho_mix',rho_mix
466  READ(*,*)
467 
468  END IF
469 
470  !--------------- Compute volumetric fractions at the vent -------------------
472 
474  rho_solid_tot_avg
475 
476  !---------- Compute the values of mass flow rate, radius and vent -----------
477  !---------- velocity from the input parameters
478 
479  IF ( isset(log10_mfr) ) THEN
480 
481  mass_flow_rate = 10.0_wp**log10_mfr
482 
483  IF ( write_flag ) WRITE(*,*) 'Fixed MER [kg/s] =',mass_flow_rate
484 
485  IF ( .NOT.isset(r0) ) THEN
486 
487  IF ( .NOT.isset(w) ) THEN
488 
489  ! Equation 4 from Carazzo et al. 2008
490  w = 138 * sqrt( water_mass_fraction0 * 100.0_wp )
491  mag_u = sqrt(u*u+w*w)
492  phi = atan(w/u)
493 
494  WRITE(*,*) 'WARNING: calculated initial velocity =',w
495 
496  END IF
497 
498  r = sqrt( mass_flow_rate / ( pi_g * rho_mix * mag_u ) )
499  r0=r
500 
501  IF ( write_flag) WRITE(*,*) &
502  'WARNING: Initial radius [m] computed from MER and w0 =',r
503 
504  ELSE
505 
506  IF ( .NOT.isset(w) ) THEN
507 
508  r = r0
509  w = mass_flow_rate / ( pi_g * rho_mix * r0**2 )
510  u = 1.0e-5_wp
511  mag_u = sqrt(u*u+w*w)
512  phi = atan(w/u)
513 
514  WRITE(*,*) 'WARNING: Initial vel [m/s] computed from MER and r =',w
515 
516  END IF
517 
518  END IF
519 
520  ELSE
521 
522  mass_flow_rate = pi_g * rho_mix * mag_u * (r**2)
523  IF ( write_flag) WRITE(*,'(1x,A,1x,es15.8)') &
524  'Initial MER [kgs-1] computed from r0 and w0 =',mass_flow_rate
525 
526  END IF
527 
528  IF ( verbose_level .GE. 1 ) THEN
529 
530  WRITE(*,*) 'cpsolid',cpsolid
531  WRITE(*,*) 'rho_atm',rho_atm
532  WRITE(*,*) 'rho_gas',rho_gas
533  WRITE(*,*) 'rho_mix',rho_mix
534  WRITE(*,*) 'mass_flow_rate',mass_flow_rate
535  WRITE(*,*) 'solid_mass_flow_rates',mass_flow_rate * &
536  ( 1.0_wp - gas_mass_fraction ) * solid_partial_mass_fraction(1:n_part)
537 
538  !READ(*,*)
539 
540  END IF
541 
542  RETURN
543  END SUBROUTINE initialize_mixture
544 
545  !******************************************************************************
547  !
557  !******************************************************************************
558 
559  SUBROUTINE eval_temp(enth,pa,cpsolid)
561  USE meteo_module, ONLY : t_ref
562 
563  USE particles_module, ONLY : t_part
564 
565  USE variables, ONLY : verbose_level , water_flag
566 
567  IMPLICIT none
568 
570  REAL(wp), INTENT(IN) :: enth
571 
573  REAL(wp), INTENT(IN) :: pa
574 
575  REAL(wp), INTENT(IN) :: cpsolid
576 
577  ! WRITE(*,*) 'eval_temp'
578 
579  IF (water_flag) THEN
580 
581  ! --- CASE1: for t_mix >= T_ref: only water vapour and liquid water -----
582 
583  CALL eval_temp_wv_lw(enth,pa,cpsolid)
584 
587 
588  ! -- CASE2: for T_ref - 40 < t_mix < T_ref: water vapour, liquid water --
589  ! --- and ice -----------------------------------------------------------
590 
591  search_temp: IF ( ( t_mix .GT. (t_ref-40) ) .AND. ( t_mix .LT. t_ref) &
592  .AND. ( liquid_water_mass_fraction .GT. 0.0_wp ) ) THEN
593 
594  CALL eval_temp_wv_lw_ice(enth,pa,cpsolid)
595 
596 
597  ! --- for exit status = 1: no equilibrium between vapour - liquid ---
598  ! --- and ice, skip to CASE 3 (vapour and ice) ----------------------
599 
600  IF (exit_status .EQ. 1.0_wp) CALL eval_temp_wv_ice(enth,pa,cpsolid)
601 
602  ! --- CASE3: for t_mix < T_ref - 40: water vapour and ice ---------------
603 
604  ELSEIF ( t_mix .LT. (t_ref - 40.0_wp) ) THEN
605 
606  CALL eval_temp_wv_ice(enth,pa,cpsolid)
607 
608  END IF search_temp
609 
610  ELSE
611 
612  ! --- Evaluate t_mix for water_flag = false: only water vapour ----------
613 
614  CALL eval_temp_no_water(enth,pa,cpsolid)
615 
616  END IF
617 
620 
621  t_part = t_mix
622 
623  RETURN
624 
625  END SUBROUTINE eval_temp
626 
627 
628  !******************************************************************************
630  !
641  !******************************************************************************
642 
643  SUBROUTINE eval_temp_wv_lw(enth,pres,cpsolid)
645  USE meteo_module, ONLY : cpair , t_ref , h_wv0 , c_wv , c_ice, h_lw0 , &
647 
648  USE variables, ONLY : water_flag
649 
650  ! USE meteo_module
651 
652  IMPLICIT none
653 
655  REAL(wp), INTENT(IN) :: enth
656 
658  REAL(wp), INTENT(IN) :: pres
659 
660  REAL(wp), INTENT(IN) :: cpsolid
661 
663  REAL(wp) :: wv_mol_fract
664 
666  REAL(wp) :: da_mol_fract
667 
669  REAL(wp) :: el
670 
672  REAL(wp) :: es
673 
674  REAL(wp) :: wv_pres
675 
676  REAL(wp) :: lw_mf0 , lw_mf1 , lw_mf2
677 
678  REAL(wp) :: ice_mf0, ice_mf1, ice_mf2
679 
680  REAL(wp) :: wv_mf0, wv_mf1, wv_mf2
681 
682  REAL(wp) :: f0, f1, f2
683 
684  REAL(wp) :: temp0 , temp1 , temp2
685 
686  REAL(wp) :: enth0 , enth1 , enth2
687 
688  !WRITE(*,*) 'water_mass_fraction', water_mass_fraction
689  !WRITE(*,*) 'volcgas_mix_mass_fraction', volcgas_mix_mass_fraction
690  !WRITE(*,*) 'dry_air_mass_fraction', dry_air_mass_fraction
691  !WRITE(*,*) 'water_vapor_mass_fraction', water_vapor_mass_fraction
692  !WRITE(*,*) 'liquid_water_mass_fraction', liquid_water_mass_fraction
693  !WRITE(*,*) 'ice_mass_fraction', ice_mass_fraction
694 
695  !WRITE(*,*)
696  !WRITE(*,*) '************** EVAL TEMP **************'
697 
698  IF ( n_gas .GT. 0) THEN
699 
702 
703  ELSE
704 
706 
707  END IF
708 
709  ! --------- All water is liquid and/or vapour ----------------------------
710 
711  ice_mass_fraction = 0.0_wp
712 
713 
714  ! CASE1: all water is liquid
715 
716  water_vapor_mass_fraction = 1.0e-10_wp
717 
720 
722 
723 
727 
730 
731  IF ( n_gas .GT. 0 ) THEN
732 
733  wv_mol_fract = ( water_vapor_mass_fraction / wv_mol_wt ) / &
737 
742 
743  da_mol_fract = ( dry_air_mass_fraction / da_mol_wt ) / &
747  ELSE
748 
749  wv_mol_fract = ( water_vapor_mass_fraction / wv_mol_wt ) / &
752 
754 
755  da_mol_fract = ( dry_air_mass_fraction / da_mol_wt ) / &
758 
759  END IF
760 
761  temp0 = ( enth - liquid_water_mass_fraction * ( h_lw0 - c_lw * t_ref ) &
762  - water_vapor_mass_fraction * ( h_wv0 - c_wv * t_ref ) ) / &
766 
767  IF ( temp0 .GT. 29.65_wp ) THEN
768 
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 &
772 
773  ELSE
774 
775  el = 0.0_wp
776 
777  END IF
778 
779  ! --------- All water is vapor -------------------------------------------
780 
781  ! CASE1: all water is vapour (no liquid and ice)
782  lw_mf2 = 0.0_wp
783 
787 
788  IF ( n_gas .GT. 0) THEN
789 
790  wv_mol_fract = ( water_vapor_mass_fraction / wv_mol_wt ) / &
794 
799 
800  da_mol_fract = ( dry_air_mass_fraction / da_mol_wt ) / &
804 
805  ELSE
806 
807  wv_mol_fract = ( water_vapor_mass_fraction / wv_mol_wt ) / &
810 
811  volcgas_mix_mol_fract = 0.0_wp
812 
813  da_mol_fract = ( dry_air_mass_fraction / da_mol_wt ) / &
816 
817  END IF
818 
819  temp2 = ( enth - liquid_water_mass_fraction * ( h_lw0 - c_lw * t_ref ) &
820  - water_vapor_mass_fraction * ( h_wv0 - c_wv * t_ref ) ) / &
824 
825  IF ( temp2 .GT. 29.65_wp ) THEN
826 
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 &
829  - el * volcgas_mix_mol_fract
830 
831  ELSE
832 
833  el = 0.0_wp
834 
835  END IF
836 
837 
838  ! --------- Options: all vapour, all liquid, vapour+liquid ---------------
839  temp1 = 0.0_wp
840 
841  vapour_liquid_case:IF ( ( f0 .LT. 0.0_wp ) .AND. ( f2 .LT. 0.0_wp ) ) THEN
842 
843  ! --------- All water is vapour -------------------------------------
845 
848 
849  t_mix = temp2
850 
851  wv_pres = wv_mol_fract * pres
852 
853  ! WRITE(*,*) 'all vapour, t_mix:',t_mix
854 
855  IF ( t_mix .GT. t_ref ) RETURN
856 
857  ELSEIF ( ( f0 .GT. 0.0_wp ) .AND. ( f2 .GT. 0.0_wp ) ) THEN
858 
859  ! --------- All water is liquid --------------------------------------
861 
864 
865  t_mix = temp0
866 
867  !WRITE(*,*) 'all liquid, t_mix:',t_mix
868 
869  IF ( t_mix .GT. t_ref ) RETURN
870 
871  ELSE
872 
873  find_temp1:DO
874 
875  ! ---------- Water is vapour+liquid ------------------------------
876  lw_mf1 = 0.5_wp * ( lw_mf0 + lw_mf2 )
877 
881 
882  IF ( n_gas .GT. 0 ) THEN
883 
884  wv_mol_fract = ( water_vapor_mass_fraction / wv_mol_wt ) / &
888 
893 
894  da_mol_fract = ( dry_air_mass_fraction / da_mol_wt ) / &
898 
899  ELSE
900 
901  wv_mol_fract = ( water_vapor_mass_fraction / wv_mol_wt ) / &
904 
906 
907  da_mol_fract = ( dry_air_mass_fraction / da_mol_wt ) / &
910 
911  END IF
912 
913 
914  temp1 = ( enth - liquid_water_mass_fraction * ( h_lw0 - c_lw*t_ref ) &
915  - water_vapor_mass_fraction * ( h_wv0 - c_wv * t_ref ) ) / &
917  cpsolid + liquid_water_mass_fraction * c_lw + &
920 
921  IF ( temp1 .GT. 29.65_wp ) THEN
922 
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 * &
927 
928  END IF
929 
930  IF ( f1 * f0 .LT. 0.0_wp ) THEN
931 
932  lw_mf2 = lw_mf1
933  f2 = f1
934  temp2 = temp1
935 
936  ELSE
937 
938  lw_mf0 = lw_mf1
939  f0 = f1
940  temp0 = temp1
941 
942  END IF
943 
944  IF ( abs(temp2-temp0) .LT. 1.0e-5_wp ) THEN
945 
946  t_mix = temp1
947 
949 
950  EXIT find_temp1
951 
952  ELSEIF ( abs(lw_mf2 - lw_mf0) .LT. 1.0e-7_wp ) THEN
953 
954  t_mix = temp1
955 
957 
958  EXIT find_temp1
959 
960  END IF
961 
962  END DO find_temp1
963 
964  END IF vapour_liquid_case
965 
966  END SUBROUTINE eval_temp_wv_lw
967 
968 
969 
970 
971  SUBROUTINE eval_temp_wv_lw_ice(enth,pres,cpsolid)
973  USE meteo_module, ONLY : cpair , t_ref , h_wv0 , c_wv , c_ice, h_lw0 , &
975 
976  USE variables, ONLY : water_flag
977 
978  ! USE meteo_module
979 
980  IMPLICIT none
981 
983  REAL(wp), INTENT(IN) :: enth
984 
986  REAL(wp), INTENT(IN) :: pres
987 
988  REAL(wp), INTENT(IN) :: cpsolid
989 
991  REAL(wp) :: wv_mol_fract
992 
994  REAL(wp) :: da_mol_fract
995 
997  REAL(wp) :: el
998 
1000  REAL(wp) :: es
1001 
1002  REAL(wp) :: wv_pres
1003 
1004  REAL(wp) :: lw_mf0 , lw_mf1 , lw_mf2
1005 
1006  REAL(wp) :: ice_mf0, ice_mf1, ice_mf2
1007 
1008  REAL(wp) :: wv_mf0, wv_mf1, wv_mf2
1009 
1010  REAL(wp) :: f0, f1, f2
1011 
1012  REAL(wp) :: temp0 , temp1 , temp2
1013 
1014  REAL(wp) :: enth0 , enth1 , enth2
1015 
1016  exit_status = 0.0_wp
1017 
1018  !REAL(wp) :: exit_status
1019 
1020  ! ------ Water can be liquid, vapour and ice -----------------------------
1021  ! For (T_ref-40) <= T <= T_ref, liquid water mass fraction varies linearly
1022  ! between 0 and equilibrium value at t=T_ref (if positive)
1023 
1024  ! CASE 0: only ice and water vapour at t=T_ref-40
1025  temp0 = t_ref - 40.0_wp
1026 
1027 
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))
1030 
1031  es = 611.22_wp * ( 10.0_wp**es )
1032 
1033  wv_mol_fract = es / pres
1034 
1035  IF ( n_gas .GT. 0 ) THEN
1036 
1037  wv_mf0 = - ( (dry_air_mass_fraction / da_mol_wt + &
1039  wv_mol_wt * wv_mol_fract ) / (wv_mol_fract - 1.0_wp)
1040 
1041  ELSE
1042 
1043  wv_mf0 = - ( (dry_air_mass_fraction / da_mol_wt) * &
1044 
1045  wv_mol_wt * wv_mol_fract ) / (wv_mol_fract - 1.0_wp)
1046 
1047  END IF
1048 
1049  lw_mf0 = 0.0_wp
1050 
1051  ice_mf0 = water_mass_fraction - wv_mf0
1052 
1053  enth0 = dry_air_mass_fraction * cpair * temp0 &
1054  + solid_tot_mass_fraction * cpsolid * temp0 &
1055  + wv_mf0 * ( h_wv0 + c_wv * ( temp0 - t_ref ) ) &
1056  + lw_mf0 * ( h_lw0 + c_lw * ( temp0 - t_ref ) ) &
1057  + ice_mf0 * ( c_ice * temp0 ) &
1059 
1060  f0 = enth - enth0
1061 
1062  !WRITE(*,*) 'CASE0'
1063  !WRITE(*,*) 'lw_mf0,ice_mf0,wv_mf0',lw_mf0,ice_mf0,wv_mf0
1064 
1065  ! CASE 0: only liquid and water vapour at t=T_ref
1066  temp2 = t_ref
1067 
1068  el = 611.2_wp * exp( 17.67_wp * ( temp2 - 273.16_wp ) / ( temp2 - 29.65_wp ) )
1069 
1070  wv_mol_fract = el / pres
1071 
1072  IF ( n_gas .GT. 0 ) THEN
1073 
1074  wv_mf2 = - ( (dry_air_mass_fraction / da_mol_wt + &
1076  wv_mol_wt * wv_mol_fract ) / (wv_mol_fract - 1.0_wp)
1077 
1078  ELSE
1079 
1080  wv_mf2 = - ( (dry_air_mass_fraction / da_mol_wt) * &
1081 
1082  wv_mol_wt * wv_mol_fract ) / (wv_mol_fract - 1.0_wp)
1083 
1084  END IF
1085 
1086  lw_mf2 = water_mass_fraction - wv_mf2
1087  ice_mf2 = 0.0_wp
1088 
1089  !WRITE(*,*) 'CASE2'
1090  !WRITE(*,*) 'wv_mol_fract',wv_mol_fract
1091  !WRITE(*,*) 'pres',pres
1092  !WRITE(*,*) 'lw_mf2,ice_mf2,wv_mf2',lw_mf2,ice_mf2,wv_mf2
1093  !READ(*,*)
1094 
1095  enth2 = dry_air_mass_fraction * cpair * temp2 &
1096  + solid_tot_mass_fraction * cpsolid * temp2 &
1097  + wv_mf2 * ( h_wv0 + c_wv * ( temp2 - t_ref ) ) &
1098  + lw_mf2 * ( h_lw0 + c_lw * ( temp2 - t_ref ) ) &
1099  + ice_mf2 * ( c_ice * temp2 ) &
1101 
1102  f2 = enth - enth2
1103 
1104 
1105  !WRITE(*,*) 'f0,f2',f0,f2
1106  !READ(*,*)
1107 
1108 
1109  IF ((f0*f2 .GT. 0.0_wp)) THEN
1110 
1111  exit_status = 1.0
1112 
1113  RETURN
1114 
1115  END IF
1116 
1117 
1118  IF ( ( lw_mf2 .GT. 0.0_wp ) .AND. (lw_mf2 .LT. 1.0_wp ) ) THEN
1119 
1120  ! --- We enter here if there is liquid water at t=Tref, otherwise
1121  ! --- there are only ice and water vapour
1122 
1123  find_temp:DO
1124  ! search for (T_ref-40) <= T <= T_ref and for mass fractions giving
1125  ! the correct enthalpy
1126 
1127  temp1 = (temp0 + temp2) * 0.5_wp
1128 
1129  lw_mf1 = lw_mf2 * ( temp1 - ( t_ref - 40) ) / 40.0_wp
1130 
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) )
1134 
1135  es = 611.22_wp * ( 10.0_wp**es )
1136 
1137  wv_mol_fract = es / pres
1138 
1139  IF ( n_gas .GT. 0 ) THEN
1140 
1141  wv_mf1 = - ( (dry_air_mass_fraction / da_mol_wt + &
1143  wv_mol_wt * wv_mol_fract ) / (wv_mol_fract - 1.0_wp)
1144 
1145  ELSE
1146 
1147  wv_mf1 = - ( (dry_air_mass_fraction / da_mol_wt) * &
1148  wv_mol_wt * wv_mol_fract ) / (wv_mol_fract - 1.0_wp)
1149 
1150  END IF
1151 
1152  ice_mf1 = water_mass_fraction - wv_mf1 - lw_mf1
1153 
1154  enth1 = dry_air_mass_fraction * cpair * temp1 &
1155  + solid_tot_mass_fraction * cpsolid * temp1 &
1156  + wv_mf1 * ( h_wv0 + c_wv * ( temp1 - t_ref ) ) &
1157  + lw_mf1 * ( h_lw0 + c_lw * ( temp1 - t_ref ) ) &
1158  + ice_mf1 * ( c_ice * temp1 ) &
1160 
1161  f1 = enth - enth1
1162 
1163  !WRITE(*,*) 'f0,f1,f2',f0,f1,f2
1164  ! WRITE(*,*) 'temp0,temp1,temp2',temp0,temp1,temp2
1165 
1166 
1167  !WRITE(*,*) 'lw_mf1,ice_mf1,wv_mf1',lw_mf1,ice_mf1,wv_mf1
1168 
1169 
1170  IF (f1 * f0 .LT. 0.0_wp) THEN
1171 
1172  temp2 = temp1
1173  f2 = f1
1174 
1175  ELSE
1176 
1177  temp0 = temp1
1178  f0 = f1
1179 
1180  END IF
1181 
1182 
1183  IF (abs(temp2-temp0) .LT. 1.0e-5_wp ) THEN
1184 
1185  IF ( ( wv_mf1 .LT. 0.0_wp ) .OR. ( ice_mf1 .LT. 0.0_wp ) ) THEN
1186 
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
1191  READ(*,*)
1192 
1193  END IF
1194 
1195 
1196  water_vapor_mass_fraction = wv_mf1
1197  ice_mass_fraction = ice_mf1
1199  t_mix = temp1
1200 
1201  !WRITE(*,*) 'CHECK: t_mix <= 273.15',' t_mix:',t_mix
1202 
1203  RETURN
1204 
1205  END IF
1206 
1207  END DO find_temp
1208 
1209 
1210  ELSEIF (lw_mf2 .LT. 0.0_wp) THEN
1211 
1212  exit_status = 1.0_wp
1213 
1214  RETURN
1215 
1216  END IF
1217 
1218  END SUBROUTINE eval_temp_wv_lw_ice
1219 
1220 
1221 
1222  SUBROUTINE eval_temp_wv_ice(enth,pres,cpsolid)
1224  USE meteo_module, ONLY : cpair , t_ref , h_wv0 , c_wv , c_ice, h_lw0 , &
1226 
1227  USE variables, ONLY : water_flag
1228 
1229  ! USE meteo_module
1230 
1231  IMPLICIT none
1232 
1234  REAL(wp), INTENT(IN) :: enth
1235 
1237  REAL(wp), INTENT(IN) :: pres
1238 
1239  REAL(wp), INTENT(IN) :: cpsolid
1240 
1242  REAL(wp) :: wv_mol_fract
1243 
1245  REAL(wp) :: da_mol_fract
1246 
1248  REAL(wp) :: el
1249 
1251  REAL(wp) :: es
1252 
1253  REAL(wp) :: wv_pres
1254 
1255  REAL(wp) :: lw_mf0 , lw_mf1 , lw_mf2
1256 
1257  REAL(wp) :: ice_mf0, ice_mf1, ice_mf2
1258 
1259  REAL(wp) :: wv_mf0, wv_mf1, wv_mf2
1260 
1261  REAL(wp) :: f0, f1, f2
1262 
1263  REAL(wp) :: temp0 , temp1 , temp2
1264 
1265  REAL(wp) :: enth0 , enth1 , enth2
1266 
1267 
1268 
1269 
1270 
1271 
1272  ! ------- All water is vapour and/or ice ----------------------------------
1273 
1274  !WRITE(*,*) '! ---- CHECK ice/vapour'
1275 
1276 
1278 
1279 
1280  ice_mf0 = 0.0_wp
1281 
1282  ice_mass_fraction = ice_mf0
1283 
1286 
1287  !WRITE(*,*) '--->water_vapor_mass_fraction',water_vapor_mass_fraction
1288  !WRITE(*,*) '--->liquid_water_mass_fraction',liquid_water_mass_fraction
1289  !WRITE(*,*) '--->ice_mass_fraction',ice_mass_fraction
1290  !WRITE(*,*) '--->volcgas_mix_mass_fraction', volcgas_mix_mass_fraction
1291  !WRITE(*,*) '--->volcgas_mix_mol_wt',volcgas_mix_mol_wt
1292  !WRITE(*,*) '--->water_vapor_mass_fraction',water_vapor_mass_fraction
1293  !WRITE(*,*) '--->wv_mol_wt ', wv_mol_wt
1294  !WRITE(*,*) '--->volcgas_mix_mol_wt',volcgas_mix_mol_wt
1295  !WRITE(*,*) '--->dry_air_mass_fraction',dry_air_mass_fraction
1296 
1297  IF ( n_gas .GT. 0) THEN
1298 
1299  wv_mol_fract = ( water_vapor_mass_fraction / wv_mol_wt ) / &
1303 
1308 
1309  da_mol_fract = ( dry_air_mass_fraction / da_mol_wt ) / &
1313 
1314  ELSE
1315 
1316  wv_mol_fract = ( water_vapor_mass_fraction / wv_mol_wt ) / &
1319 
1320  volcgas_mix_mol_fract = 0.0_wp
1321 
1322  da_mol_fract = ( dry_air_mass_fraction / da_mol_wt ) / &
1325 
1326  END IF
1327 
1328  temp0 = ( enth - liquid_water_mass_fraction * ( h_lw0 - c_lw * t_ref ) &
1329  - water_vapor_mass_fraction * ( h_wv0 - c_wv * t_ref ) ) / &
1333 
1334  !WRITE(*,*) 'water_vapor_mass_fraction',water_vapor_mass_fraction
1335  !WRITE(*,*) 'wv_mol_fract',wv_mol_fract
1336  !WRITE(*,*) 'da_mol_fract',da_mol_fract
1337  !WRITE(*,*) 'volcgas_mix_mol_fract',volcgas_mix_mol_fract
1338  !READ(*,*)
1339 
1340  IF ( temp0 .GT. 29.65_wp ) THEN
1341 
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))
1344 
1345  es = 611.22_wp * ( 10.0_wp**es )
1346 
1347  f0 = ( pres - es ) * wv_mol_fract - es * da_mol_fract - es * volcgas_mix_mol_fract
1348 
1349  END IF
1350 
1351 
1352  ! WRITE(*,*) '! ---- All water is ice'
1353 
1354  ice_mf2 = water_mass_fraction
1355 
1356  ice_mass_fraction = ice_mf2
1357 
1360 
1361  !WRITE(*,*) '--->water_vapor_mass_fraction',water_vapor_mass_fraction
1362  !WRITE(*,*) '--->liquid_water_mass_fraction',liquid_water_mass_fraction
1363  !WRITE(*,*) '--->ice_mass_fraction',ice_mass_fraction
1364  !WRITE(*,*) '--->volcgas_mix_mass_fraction', volcgas_mix_mass_fraction
1365  !WRITE(*,*) '--->volcgas_mix_mol_wt',volcgas_mix_mol_wt
1366  !WRITE(*,*) '--->water_vapor_mass_fraction',water_vapor_mass_fraction
1367  !WRITE(*,*) '--->wv_mol_wt ', wv_mol_wt
1368  !WRITE(*,*) '--->volcgas_mix_mol_wt',volcgas_mix_mol_wt
1369  !WRITE(*,*) '--->dry_air_mass_fraction',dry_air_mass_fraction
1370 
1371  IF ( n_gas .GT. 0) THEN
1372 
1373  wv_mol_fract = ( water_vapor_mass_fraction / wv_mol_wt ) / &
1377 
1382 
1383  da_mol_fract = ( dry_air_mass_fraction / da_mol_wt ) / &
1387 
1388  ELSE
1389 
1390  wv_mol_fract = ( water_vapor_mass_fraction / wv_mol_wt ) / &
1393 
1394  volcgas_mix_mol_fract = 0.0_wp
1395 
1396  da_mol_fract = ( dry_air_mass_fraction / da_mol_wt ) / &
1399 
1400  END IF
1401 
1402  temp2 = ( enth - liquid_water_mass_fraction * ( h_lw0 - c_lw * t_ref ) &
1403  - water_vapor_mass_fraction * ( h_wv0 - c_wv * t_ref ) ) / &
1407 
1408  !WRITE(*,*) 'water_vapor_mass_fraction',water_vapor_mass_fraction
1409  !WRITE(*,*) 'wv_mol_fract',wv_mol_fract
1410  !WRITE(*,*) 'da_mol_fract',da_mol_fract
1411  !WRITE(*,*) 'volcgas_mix_mol_fract',volcgas_mix_mol_fract
1412 
1413  IF ( temp2 .GT. 29.65_wp ) THEN
1414 
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))
1417 
1418  es = 611.22_wp * ( 10.0_wp**es )
1419 
1420  f2 = ( pres - es ) * wv_mol_fract - es * da_mol_fract - es * volcgas_mix_mol_fract
1421 
1422  END IF
1423 
1424  !WRITE(*,*) 'all vapour, t_mix:',temp0
1425  !WRITE(*,*) 'all ice, t_mix:',temp2
1426 
1427 
1428  IF ( ( f0 .LT. 0.0_wp ) .AND. ( f2 .LT. 0.0_wp ) ) THEN !All water is vapour
1429 
1430  ice_mass_fraction = 0.0_wp
1432 
1433  t_mix = temp0
1434 
1435  !WRITE(*,*) 'all vapour, t_mix:',t_mix
1436  !WRITE(*,*) '*****'
1437  !READ(*,*)
1438  RETURN
1439 
1440  ELSEIF ( ( f0 .GT. 0.0_wp ) .AND. ( f2 .GT. 0.0_wp ) ) THEN !All water is ice
1441 
1444 
1445  t_mix = temp2
1446  !WRITE(*,*) 'all ice, t_mix:',t_mix
1447  !WRITE(*,*) '*****'
1448  !READ(*,*)
1449  RETURN
1450 
1451  ELSE !All water is vapour and/or ice
1452 
1453  find_temp2:DO
1454 
1455  ice_mf1 = 0.5_wp * ( ice_mf0 + ice_mf2 )
1456 
1457  ice_mass_fraction = ice_mf1
1458 
1459  !WRITE(*,*) ' ice_mass_fraction ', ice_mass_fraction
1460 
1463 
1464  !WRITE(*,*) ' water_vapor_mass_fraction ', water_vapor_mass_fraction
1465 
1466  IF ( n_gas .GT. 0) THEN
1467 
1468  wv_mol_fract = ( water_vapor_mass_fraction / wv_mol_wt ) / &
1472 
1477 
1478  da_mol_fract = ( dry_air_mass_fraction / da_mol_wt ) / &
1482 
1483 
1484  ELSE
1485 
1486  wv_mol_fract = ( water_vapor_mass_fraction / wv_mol_wt ) / &
1489 
1491 
1492  da_mol_fract = ( dry_air_mass_fraction / da_mol_wt ) / &
1495 
1496  END IF
1497 
1498  !WRITE(*,*) 'water_vapor_mass_fraction',water_vapor_mass_fraction
1499  !WRITE(*,*) 'wv_mol_fract',wv_mol_fract
1500  !WRITE(*,*) 'da_mol_fract',da_mol_fract
1501  !WRITE(*,*) 'volcgas_mix_mol_fract',volcgas_mix_mol_fract
1502 
1503 
1504  temp1 = ( enth - liquid_water_mass_fraction * ( h_lw0 - c_lw*t_ref ) &
1505  - water_vapor_mass_fraction * ( h_wv0 - c_wv * t_ref ) ) / &
1507  cpsolid + liquid_water_mass_fraction * c_lw + &
1510 
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))
1513 
1514  es = 611.22_wp * (10.0_wp**es)
1515 
1516  f1 = ( pres - es ) * wv_mol_fract - es * da_mol_fract - es * volcgas_mix_mol_fract
1517 
1518 
1519 
1520  !WRITE(*,*) 'volcgas_mix_mol_fract ',volcgas_mix_mol_fract
1521  !WRITE(*,*) wv_mol_fract+volcgas_mix_mol_fract+da_mol_fract
1522 
1523  !WRITE(*,*) 't0,t1,t2',temp0,temp1,temp2
1524  !WRITE(*,*) 'lw_mf0,lw_mf1,lw_mf2',lw_mf0,lw_mf1,lw_mf2
1525  !WRITE(*,*) 'f0,f1,f2',f0,f1,f2
1526  !READ(*,*)
1527 
1528  IF ( f1 * f2 .LT. 0.0_wp ) THEN
1529 
1530  ice_mf0 = ice_mf1
1531  f0 = f1
1532  temp0 = temp1
1533 
1534  ELSE
1535 
1536  ice_mf2 = ice_mf1
1537  f2 = f1
1538  temp2 = temp1
1539 
1540  END IF
1541 
1542  IF ( abs(temp2-temp0) .LT. 1.0e-3_wp ) THEN
1543 
1544  t_mix = temp1
1545 
1546  ice_mass_fraction = ice_mf1
1549 
1550 
1551  ! WRITE(*,*)'t_mix 1',t_mix
1552  EXIT find_temp2
1553 
1554  ELSEIF ( abs(ice_mf2 - ice_mf0) .LT. 1.0e-7_wp ) THEN
1555 
1556  t_mix = temp1
1557 
1558  ! WRITE(*,*)'t_mix 2',t_mix
1559 
1560  ice_mass_fraction = ice_mf1
1563 
1564  EXIT find_temp2
1565 
1566  END IF
1567 
1568  END DO find_temp2
1569 
1570  END IF
1571 
1572  END SUBROUTINE eval_temp_wv_ice
1573 
1574 
1575 
1576  SUBROUTINE eval_temp_no_water(enth,pres,cpsolid)
1578  USE meteo_module, ONLY : cpair , t_ref , h_wv0 , c_wv , c_ice, h_lw0 , &
1580 
1581 
1582  ! USE meteo_module
1583 
1584  IMPLICIT none
1585 
1587  REAL(wp), INTENT(IN) :: enth
1588 
1590  REAL(wp), INTENT(IN) :: pres
1591 
1592  REAL(wp), INTENT(IN) :: cpsolid
1593 
1595 
1596  ice_mass_fraction = 0.0_wp
1597 
1599 
1600 
1601 
1602  t_mix = ( enth - liquid_water_mass_fraction * ( h_lw0 - c_lw * t_ref )&
1603  - water_vapor_mass_fraction * ( h_wv0 - c_wv * t_ref ) ) / &
1605  * cpsolid + liquid_water_mass_fraction * c_lw + &
1608 
1609 
1610  !WRITE(*,*) 't_mix ',t_mix
1611  !READ(*,*)
1612  END SUBROUTINE eval_temp_no_water
1613 
1614 
1615 
1616 
1617 END MODULE mixture_module
1618 
1619 
1620 
integer n_mom
Number of moments.
Definition: moments.f90:24
integer n_part
number of particle phases
Definition: particles.f90:23
real(wp) exit_status
exit_status
Definition: mixture.f90:40
real(wp) pa
Atmospheric pressure.
Definition: meteo.f90:79
real(wp) t_part
Particle temperature for aggregation (Costa model)
Definition: particles.f90:161
real(wp) u
plume x-horizontal velocity
Definition: plume.f90:23
real(wp) rho_atm
Atmospheric density.
Definition: meteo.f90:60
real(wp) ice_mass_fraction
mass fraction of ice in the mixture
Definition: mixture.f90:118
character(len=20) distribution
Ditribution of the particles: .
Definition: particles.f90:110
subroutine eval_particles_moments
Particles moments computation.
Definition: particles.f90:1100
real(wp) liquid_water_mass_fraction
mass fraction of liquid water in the mixture
Definition: mixture.f90:106
real(wp), dimension(:), allocatable volcgas_mass_fraction
mass fractions of volcanic gases
Definition: mixture.f90:82
real(wp) cpair
specific heat capacity for dry air
Definition: meteo.f90:91
real(wp), dimension(:,:,:), allocatable m_quad
Abscissa of quadrature formulas.
Definition: particles.f90:131
real(wp), parameter h_lw0
enthalpy of liquid water at reference temperature (J kg-1)
Definition: meteo.f90:103
real(wp) volcgas_mix_mol_fract
Definition: mixture.f90:123
subroutine initialize_mixture
Mixture properties initialization.
Definition: mixture.f90:154
real(wp), dimension(:), allocatable volcgas_mol_wt
molecular weight of additional volcanic gases
Definition: mixture.f90:76
real(wp) gas_volume_fraction
gas vlume fraction in the mixture
Definition: mixture.f90:22
real(wp) water_vapor_mass_fraction
mass fraction of water vapor in the mixture
Definition: mixture.f90:112
integer n_sections
Definition: moments.f90:26
real(wp) rho_ice
Density of ice in the mixture.
Definition: mixture.f90:133
logical water_flag
Flag for water.
Definition: variables.f90:70
real *8 pi_g
Greek pi.
Definition: variables.f90:30
real(wp) water_volume_fraction0
initial water volume fraction
Definition: mixture.f90:52
real(wp) dry_air_mass_fraction
mass fraction of dry air in the mixture
Definition: mixture.f90:100
integer n_nodes
Number of nodes for the quadrature.
Definition: moments.f90:18
logical write_flag
Definition: variables.f90:74
Particles module.
Definition: particles.f90:11
real(wp) rvolcgas_mix
gas constant of volcanic gases mixture ( J/(kg K) )
Definition: mixture.f90:88
real(wp), parameter wv_mol_wt
molecular weight of water vapor
Definition: meteo.f90:115
real(wp) volcgas_mix_mass_fraction
mass fraction of the volcanic gas in the mixture
Definition: mixture.f90:97
logical aggregation_flag
Definition: variables.f90:72
real(wp) added_water_temp
Definition: mixture.f90:135
real(wp), dimension(:,:,:), allocatable f_quad
Values of linear reconstructions at quadrature points.
Definition: particles.f90:158
real(wp) added_water_mass_fraction
Definition: mixture.f90:137
real(wp), dimension(:,:,:), allocatable rho_quad
Particle densities at quadrature points.
Definition: particles.f90:146
real(wp) cpvolcgas_mix
specific heat of volcanic gases mixture
Definition: mixture.f90:91
real(wp), dimension(:), allocatable cp_part
Heat capacity of particle phases.
Definition: particles.f90:92
real(wp), dimension(:), allocatable solid_partial_mass_fraction
mass fraction of the particle phases with respect to the total solid
Definition: particles.f90:26
Meteo module.
Definition: meteo.f90:11
subroutine eval_temp(enth, pa, cpsolid)
Mixture temperature.
Definition: mixture.f90:560
real(wp) solid_tot_volume_fraction
solid volume fraction in the mixture
Definition: mixture.f90:46
real(wp) r0
initial radius of the plume
Definition: plume.f90:37
real(wp) rgasmix
universal constant for the mixture
Definition: mixture.f90:28
real(wp) water_volume_fraction
water volume fraction in the mixture
Definition: mixture.f90:43
real(wp) volcgas_mix_mol_wt
Definition: mixture.f90:125
real(wp) atm_mass_fraction
mass fraction of the entrained air in the mixture
Definition: mixture.f90:94
real(wp), dimension(:), allocatable solid_mass_fraction
mass fraction of the particle phases with respect to the mixture
Definition: particles.f90:35
subroutine eval_temp_wv_lw_ice(enth, pres, cpsolid)
Definition: mixture.f90:972
subroutine eval_temp_wv_lw(enth, pres, cpsolid)
Mixture temperature with vapour and liquid water.
Definition: mixture.f90:644
Gas/particles mixture module.
Definition: mixture.f90:11
real(wp) rho_mix
mixture density
Definition: mixture.f90:31
Plume module.
Definition: plume.f90:11
real(wp), parameter h_wv0
enthalpy of water vapor at reference temperature (J kg-1)
Definition: meteo.f90:97
real(wp) water_vapor_volume_fraction
mass fraction of water vapor in the mixture
Definition: mixture.f90:115
real(wp) phi
angle between the plume trajectory and ground
Definition: plume.f90:27
real(wp), parameter c_ice
specific heat of ice (J K-1 kg-1)
Definition: meteo.f90:109
real(wp) rair
perfect gas constant for dry air ( J/(kg K) )
Definition: meteo.f90:88
Method of Moments module.
Definition: moments.f90:11
real(wp), dimension(:), allocatable rvolcgas
gas constants for volcanic gases
Definition: mixture.f90:70
logical function isset(var)
Input variable check.
Definition: variables.f90:104
subroutine eval_temp_wv_ice(enth, pres, cpsolid)
Definition: mixture.f90:1223
real(wp), dimension(:,:,:), allocatable mom
Moments of the particles diameter.
Definition: particles.f90:53
real(wp), parameter t_ref
reference temperature (K)
Definition: meteo.f90:94
real(wp) mag_u
velocity magnitude along the centerline
Definition: plume.f90:26
real(wp), parameter da_mol_wt
molecular weight of dry air
Definition: meteo.f90:112
real(wp), dimension(:), allocatable solid_partial_mass_fraction0
init mass fraction of the particle phases with respect to the total solid
Definition: particles.f90:29
real(wp), dimension(:,:,:), allocatable w_quad
Weights of quadrature formulas.
Definition: particles.f90:134
real(wp) mass_flow_rate
Definition: mixture.f90:61
real(wp) liquid_water_volume_fraction
mass fraction of liquid water in the mixture
Definition: mixture.f90:109
logical initial_neutral_density
logical defining if the plume has neutral density at the base
Definition: mixture.f90:34
real(wp) water_mass_fraction
mass fraction of water in the mixture
Definition: mixture.f90:103
real(wp) rho_gas
gas phase density
Definition: mixture.f90:25
real(wp), dimension(:), allocatable cpvolcgas
specific heat capacity for volcanic gases
Definition: mixture.f90:73
real(wp) cpsolid
Average heat capacity of particles.
Definition: particles.f90:95
integer, parameter wp
working precision
Definition: variables.f90:21
real(wp), dimension(:), allocatable solid_mass_fraction0
initial mass fraction of the particle phases with respect to the mixture
Definition: particles.f90:38
real(wp) t_mix
mixture temperature
Definition: mixture.f90:37
real(wp), parameter c_lw
specific heat of liquid water (J K-1 kg-1)
Definition: meteo.f90:106
real(wp), parameter c_wv
specifc heat of water vapor (J K-1 kg-1)
Definition: meteo.f90:100
real(wp) rhovolcgas_mix
volcanic gases mixture density
Definition: mixture.f90:85
real(wp) function particles_density(i_part, phi)
Particle density.
Definition: particles.f90:607
real *8 gi
Gravity acceleration.
Definition: variables.f90:24
real(wp) mixture_enthalpy
Definition: mixture.f90:127
real(wp), dimension(:), allocatable volcgas_mass_fraction0
initial mass fractions of volcanic gases
Definition: mixture.f90:79
real(wp), dimension(:), allocatable rhovolcgas
volcanic gases densities
Definition: mixture.f90:67
real(wp) r
plume radius
Definition: plume.f90:22
real(wp), parameter rwv
gas constant for water vapor ( J/(kg K) )
Definition: meteo.f90:118
real(wp) t_mix0
initial temperature
Definition: mixture.f90:49
real(wp) rho_lw
Density of liquid water in the mixture.
Definition: mixture.f90:130
subroutine eval_quad_values
Quadrature values computation.
Definition: particles.f90:1179
real(wp) log10_mfr
Definition: plume.f90:38
real(wp), dimension(:,:,:), allocatable mom0
Initial moments of the particles diameter.
Definition: particles.f90:56
real(wp) water_mass_fraction0
initial water mass fraction
Definition: mixture.f90:55
integer n_gas
volcanic gas species number
Definition: mixture.f90:64
real(wp) solid_tot_mass_fraction
solid mass fraction in the mixture
Definition: mixture.f90:58
real(wp) ice_volume_fraction
mass fraction of ice in the mixture
Definition: mixture.f90:121
Global variables.
Definition: variables.f90:10
real(wp) gas_mass_fraction
gas mass fraction in the mixture
Definition: mixture.f90:19
real(wp) w
plume vertical velocity
Definition: plume.f90:25
subroutine eval_temp_no_water(enth, pres, cpsolid)
Definition: mixture.f90:1577
integer verbose_level
Level of verbose output (0 = minimal output on screen)
Definition: variables.f90:33