AshFlow  0.1
ashflowmodel
 All Classes Files Functions Variables Pages
mixture.f90
Go to the documentation of this file.
1 !********************************************************************************
8 !********************************************************************************
9 
11 
12  USE envi_module, ONLY: alpha, t_a, gi
13 
14  IMPLICIT NONE
15 
17  REAL*8 :: C_vmix
18 
20  REAL*8 :: epsilon
21 
23  REAL*8 :: Nmag
24 
26  REAL*8 :: N
27 
29  REAL*8 :: init_N
30 
32  REAL*8 :: lambda
33 
35  REAL*8 :: rhogas
36 
38  REAL*8 :: beta_old
39 
41  REAL*8 :: beta_new
42 
44  REAL*8 :: Ri
45 
47  REAL*8 :: flow_regime
48 
50  REAL*8 :: gas_constmix
51 
53  REAL*8 :: C_s = 1617.D0
54 
56  REAL*8 :: beta
57 
59  REAL*8 :: rhosol_ave
60 
62  REAL*8 :: rwvapour
63 
65  REAL*8 :: cpwvapour
66 
67  REAL*8 :: pi
68 
69  REAL*8 :: initial_velocity
70 
71  REAL*8 :: initial_density
72 
73  REAL*8 :: Cv_magmix
74 
75  REAL*8 :: solidvolumefraction
76  REAL*8 :: gasvolumefraction
77  REAL*8 :: final_solid_mass_flux
78  REAL*8 :: initial_SMF
79 
80  REAL*8 :: deltabeta
81 
82  REAL*8 :: deltabeta_g
83 
84  REAL*8 :: Pdyn
85 
86  REAL*8 :: entrainment_rate
87 
88  SAVE
89 
90 CONTAINS
91 
92  !******************************************************************************
100  !******************************************************************************
101 
102  SUBROUTINE compute_mixture
103  !
104  USE envi_module, ONLY: alpha ,p, c_vair, gas_constair
105  USE current_module, ONLY: u, r, h, t, solid_mass_flux, t0, tvent_flag , &
106  oned_model, initial_mf
107  USE particles_module, ONLY: rhosol, diam, iclass, fracsolid , v_s, s, c_d , &
108  sumsed ,solidmassflux_fract, acc_rate
109  !
110  IMPLICIT NONE
111 
112  INTEGER :: i
113 
114  REAL*8 :: var
115 
116  ! mass fraction of magmatic gas in the mixture (with air and solid)
117  REAL*8 :: nmag_mix
118 
119  ! mass fraction pf magmatic gas in the gas (volcanic+air)
120  REAL*8 :: nmag_gas
121 
122  pi = 4.d0 * atan(1.d0)
123 
124  init_n = n
125 
126  nmag_mix = nmag * ( 1.d0 - n ) / (1.d0 - nmag)
127 
128  lambda = (n - nmag) / ( 1.d0 - nmag )
129 
130  c_vmix = nmag_mix * cpwvapour + lambda * c_vair &
131  + ( 1.d0 - n ) * c_s
132 
133  cv_magmix = nmag * cpwvapour + ( 1.d0 - nmag ) * c_s
134 
135  nmag_gas = nmag_mix / n
136 
137  gas_constmix = rwvapour * nmag_gas + gas_constair * ( 1.d0 - nmag_gas )
138 
139 
140 
141  IF (tvent_flag) THEN
142 
143  ! Calculating the initial temperature using temperature of erupted material
144  ! if not explicitly defined in input file
145  ! Initial temperature in the flow based on the eruption temp (eq. 14 in
146  ! Bursik and Woods 96)
147 
148  t = ( ( 1.d0 - lambda ) * cv_magmix * t0 + lambda * c_vair * t_a ) / &
149  ( ( 1.d0 - lambda )* cv_magmix + lambda * c_vair )
150 
151  ELSE
152 
153  t = t0
154 
155  END IF
156 
157  rhogas = p / ( gas_constmix * t )
158  rhosol_ave = 1/(sum(fracsolid/rhosol))
159  beta = 1.d0 / ( n / rhogas + ( 1.d0 - n ) / rhosol_ave)
160 
161  initial_density = beta
162 
163  ! Flow velocity
164  u = sqrt((beta - alpha) * gi * h / (ri * beta))
165  initial_velocity = u
166 
167  ! Defining entrainment conditions
168  epsilon = 0.075d0 / dsqrt( 1.0d0 + 718.0d0 * ri**2.4d0 )
169 
170  IF ( oned_model ) THEN
171 
172  var = 1.d0
173 
174  ELSE
175 
176  var = r
177 
178  END IF
179 
180  solid_mass_flux = (beta * u * h * var) * ( 1.d0 - n )
181  initial_smf = (beta * u * h * var) * ( 1.d0 - n )
182 
183  initial_mf = (beta * u * h * var) * 2 * pi
184 
185  ! provides the mass_flux of a particle of a given size
186  DO i=1,iclass
187 
188  solidmassflux_fract(i) = solid_mass_flux*fracsolid(i)
189 
190  ! Settling velocity for the particle fraction
191 
192  v_s(i) = dsqrt( (rhosol(i) * gi * diam(i)) / (c_d(i) * beta) )
193 
194  ! SEDIMENTATION for the particle fraction
195 
196  s(i) = 1.d0 / (h * u) * solidmassflux_fract(i) * v_s(i)
197 
198  ENDDO
199 
200  sumsed = sum(s)
201 
202  RETURN
203  END SUBROUTINE compute_mixture
204 
205  !----------------------------------------------------------------------
206 END MODULE mixture_module
207 !----------------------------------------------------------------------
Current module This module contains descriptors for the initial conditions of the flow...
Definition: current.f90:7
Mixture module This module contains all the variables required for describing and calculating the cha...
Definition: mixture.f90:10
subroutine compute_mixture
Computing conditions within mixture This subroutine calculates the characteristics of the mixture by ...
Definition: mixture.f90:102
Particles module This module contains the procedures and the variables related to the solid particles...
Definition: particles.f90:6
environment module This module contains all the variables related to the background environmental con...
Definition: environment.f90:8