PLUME-MoM  1.0
Integralvolcanicplumemodel
 All Classes Files Functions Variables Pages
mixture.f90
Go to the documentation of this file.
1 !********************************************************************************
3 !
9 !********************************************************************************
10 
12 
13  USE variables, ONLY: gi , pi_g
14 
15  IMPLICIT NONE
16 
18  REAL*8 :: gas_mass_fraction
19 
21  REAL*8 :: rho_gas
22 
24  REAL*8 :: rgasmix
25 
27  REAL*8 :: cpmix
28 
30  REAL*8 :: rho_mix
31 
33  LOGICAL :: initial_neutral_density
34 
36  REAL*8 :: tp
37 
39  REAL*8 :: gas_volume_fraction
40 
42  REAL*8 :: solid_tot_volume_fraction
43 
45  REAL*8 :: tp0
46 
48  REAL*8 :: gas_volume_fraction0
49 
51  REAL*8 :: gas_mass_fraction0
52 
54  REAL*8 :: solid_tot_mass_fraction0
55 
56  ! mass flow rate
57  REAL*8 :: mass_flow_rate
58 
60  REAL*8 :: rwvapour
61 
63  REAL*8 :: cpwvapour
64 
66  REAL*8 :: atm_mass_fraction
67 
69  REAL*8 :: wvapour_mass_fraction
70 
71  SAVE
72 
73 CONTAINS
74 
75  !******************************************************************************
77  !
79  !
83  !******************************************************************************
84 
85  SUBROUTINE initialize_mixture
86 
87  ! external variables
88  USE meteo_module, ONLY : ta , pa , rho_atm , rair
89 
90  USE moments_module, ONLY : n_nodes
91 
92  USE particles_module, ONLY: n_part , solid_partial_mass_fraction , &
93  cp_rhop_mom , mom , rhop_mom , distribution
94 
95  USE particles_module, ONLY: distribution_variable
96 
97  USE plume_module, ONLY: w , r , u , mag_u , phi , mfr_exp0, r0
98 
99  USE variables, ONLY: verbose_level
100 
101  ! external procedures
105 
106  IMPLICIT NONE
107 
108  REAL*8 :: rho_solid_avg(n_part)
109 
110  REAL*8 :: rho_solid_tot_avg
111 
112  REAL*8 :: rho_wvapour
113 
114  REAL*8 :: rho_atm_tp
115 
116  REAL*8 :: alfa_s(n_part)
117 
118  REAL*8 :: alfa_g_atm , alfa_g_wvapour
119 
120  REAL*8 :: wvapour_volume_fraction , atm_volume_fraction
121 
122  REAL*8 :: cp_solid0
123 
124  REAL*8, DIMENSION(n_part,n_nodes) :: xi , wi
125 
126  INTEGER :: i_part
127 
128  INTEGER :: i
129 
130  REAL*8 :: part_dens_array(n_nodes)
131 
132  IF ( verbose_level .GE. 1 ) WRITE(*,*) 'initialize_mixture'
133 
134  tp = tp0
135 
136  IF ( initial_neutral_density ) THEN
137 
138  rgasmix = rair
139 
140  ELSE
141 
142  rgasmix = rwvapour
143 
144  END IF
145 
146  rho_atm_tp = pa / ( rair * tp )
147 
148  rho_gas = pa / ( rgasmix * tp )
149 
150  rho_wvapour = pa / ( rwvapour * tp )
151 
152  alfa_g_wvapour = ( rho_gas - rho_atm_tp ) / ( rho_wvapour - rho_atm_tp )
153 
154  alfa_g_atm = 1.d0 - alfa_g_wvapour
155 
156  DO i_part=1,n_part
157 
158  IF ( distribution .EQ. 'constant' ) THEN
159 
160  CALL wheeler_algorithm( mom(i_part,0:1) , xi(i_part,:) , &
161  wi(i_part,:) )
162 
163  ELSE
164 
165  CALL wheeler_algorithm( mom(i_part,:) , xi(i_part,:) , wi(i_part,:) )
166 
167  END IF
168 
169  IF ( verbose_level .GE. 2 ) THEN
170 
171  WRITE(*,*) 'i_part',i_part
172  WRITE(*,*) 'xi',xi(i_part,:)
173  WRITE(*,*) 'wi',wi(i_part,:)
174 
175  END IF
176 
177  DO i=1,n_nodes
178 
179  part_dens_array(i) = particles_density( i_part , xi(i_part,i) )
180 
181  END DO
182 
183 
184  IF ( distribution_variable .EQ. 'particles_number' ) THEN
185 
186  rho_solid_avg(i_part) = sum( part_dens_array * wi(i_part,:) &
187  * xi(i_part,:)**3 ) / mom(i_part,3)
188 
189  ELSEIF ( distribution_variable .EQ. 'mass_fraction' ) THEN
190 
191  rho_solid_avg(i_part) = 1.d0 / ( sum( wi(i_part,:) / part_dens_array )&
192  / mom(i_part,0) )
193 
194  END IF
195 
196  END DO
197 
198  rho_solid_tot_avg = 1.d0 / sum( solid_partial_mass_fraction(1:n_part) / &
199  rho_solid_avg(1:n_part) )
200 
201 
202  DO i_part = 1,n_part
203 
204  alfa_s(i_part) = solid_partial_mass_fraction(i_part) * &
205  rho_solid_tot_avg / rho_solid_avg(i_part)
206 
207  IF ( verbose_level .GE. 1 ) THEN
208 
209  WRITE(*,*) 'i_part',i_part
210  WRITE(*,*) 'rho_solid_avg',rho_solid_avg(i_part)
211  WRITE(*,*) 'rho_solid_avg',rho_solid_avg(i_part)
212  WRITE(*,*) 'alfa_s',i_part,alfa_s(i_part)
213 
214  END IF
215 
216 
217 
218  END DO
219 
220 
221  rho_solid_tot_avg = 1.d0 / sum( solid_partial_mass_fraction(1:n_part) / &
222  rho_solid_avg(1:n_part) )
223 
224  gas_volume_fraction = rho_solid_tot_avg / ( rho_gas * ( 1.d0 / &
225  gas_mass_fraction0 - 1.d0 ) + rho_solid_tot_avg )
226 
227  solid_tot_volume_fraction = 1.d0 - gas_volume_fraction0
228 
229  solid_tot_mass_fraction0 = 1.d0 - gas_mass_fraction0
230 
231  IF ( verbose_level .GE. 1 ) THEN
232 
233  WRITE(*,*) 'solid volume fractions',solid_tot_volume_fraction*alfa_s
234  WRITE(*,*) 'solid_tot_volume_fraction',solid_tot_volume_fraction
235  WRITE(*,*) 'gas_volume_fraction',gas_volume_fraction
236  WRITE(*,*) 'solid_tot_mass_fraction0',solid_tot_mass_fraction0
237  READ(*,*)
238 
239  END IF
240 
241  CALL eval_particles_moments( xi , wi )
242 
243  rho_solid_tot_avg = sum( alfa_s * rho_solid_avg )
244 
245  ! ... Plume density
246  rho_mix = gas_volume_fraction * rho_gas + solid_tot_volume_fraction * &
247  rho_solid_tot_avg
248 
249  atm_volume_fraction = gas_volume_fraction * alfa_g_atm
250 
251  wvapour_volume_fraction = gas_volume_fraction * alfa_g_wvapour
252 
253  atm_mass_fraction = atm_volume_fraction * rho_atm / rho_mix
254 
255  ! WRITE(*,*) 'gas_volume_fraction * alfa_g_atm',gas_volume_fraction , alfa_g_atm
256  ! WRITE(*,*) 'atm_volume_fraction * rho_atm / rho_mix',atm_volume_fraction , rho_atm , rho_mix
257  ! WRITE(*,*) 'MIXTURE: atm_mass_fraction',atm_mass_fraction
258  ! READ(*,*)
259 
260 
261  wvapour_mass_fraction = wvapour_volume_fraction * rho_wvapour / rho_mix
262 
263 
264  ! ... At the beginning the plume is a mixture of water-vapour and particles
265  ! ... only (without entrained air)
266 
267  WRITE(*,*) 'cp_rhop_mom',cp_rhop_mom(:,3)
268  WRITE(*,*) 'rhop_mom',rhop_mom(:,3)
269 
270  cp_solid0 = sum(solid_partial_mass_fraction * cp_rhop_mom(:,3) / &
271  rhop_mom(:,3) )
272 
273  cpmix = gas_mass_fraction0 * cpwvapour + ( 1.d0 - gas_mass_fraction0 ) * &
274  cp_solid0
275 
276  IF ( mfr_exp0 .GT. 0.d0 ) THEN
277 
278  mass_flow_rate = 10.0**mfr_exp0
279 
280  WRITE(*,*) 'WARNING: Fixed mfr =',mass_flow_rate
281 
282  IF ( r0 .EQ. 0.d0 ) THEN
283 
284  IF ( w .EQ. 0.d0 ) THEN
285 
286  ! Equation 4 from Carazzo et al. 2008
287  w = 138 * dsqrt( gas_mass_fraction0 * 100.d0 )
288  mag_u = dsqrt(u*u+w*w)
289  phi = atan(w/u)
290 
291  WRITE(*,*) 'Calculated initial velocity =',w
292 
293  END IF
294 
295  r = dsqrt( mass_flow_rate / ( pi_g * rho_mix * mag_u ) )
296  r0=r
297 
298  WRITE(*,*) 'Calculated radius =',r
299 
300  END IF
301 
302  ELSE
303 
304  mass_flow_rate = pi_g * rho_mix * mag_u * (r**2)
305 
306  END IF
307 
308  IF ( verbose_level .GE. 1 ) THEN
309 
310  WRITE(*,*) 'cpsolid',cp_solid0
311  WRITE(*,*) 'rho_atm',rho_atm
312  WRITE(*,*) 'rho_gas',rho_gas
313  WRITE(*,*) 'rho_mix',rho_mix
314  WRITE(*,*) 'mass_flow_rate',mass_flow_rate
315 
316  READ(*,*)
317 
318  END IF
319 
320  gas_mass_fraction = gas_volume_fraction * rho_gas / rho_mix
321 
322  WRITE(*,*) 'initial mfr',mass_flow_rate
323 
324  RETURN
325  END SUBROUTINE initialize_mixture
326 
327 END MODULE mixture_module
328 
real *8 function particles_density(i_part, diam_in)
Particle density.
Definition: particles.f90:440
Meteo module.
Definition: meteo.f90:11
Global variables.
Definition: variables.f90:10
subroutine initialize_mixture
Mixture properties initialization.
Definition: mixture.f90:85
Gas/particles mixture module.
Definition: mixture.f90:11
Plume module.
Definition: plume.f90:11
Method of Moments module.
Definition: moments.f90:11
subroutine eval_particles_moments(xi, w)
Particles moments computation.
Definition: particles.f90:794
Particles module.
Definition: particles.f90:11
subroutine wheeler_algorithm(m, xi, w)
Wheeler algorithm.
Definition: moments.f90:41