Merge lp:~ctjacobs-multiphase/fluidity/enforce-hydrostatic-balance into lp:fluidity

Proposed by Christian Jacobs
Status: Merged
Merged at revision: 4232
Proposed branch: lp:~ctjacobs-multiphase/fluidity/enforce-hydrostatic-balance
Merge into: lp:fluidity
Diff against target: 7805 lines (+7293/-76)
36 files modified
assemble/Momentum_CG.F90 (+57/-12)
assemble/Momentum_DG.F90 (+42/-11)
assemble/Momentum_Equation.F90 (+19/-0)
manual/configuring_fluidity.tex (+11/-0)
schemas/equation_of_state.rnc (+67/-53)
schemas/equation_of_state.rng (+14/-0)
schemas/prognostic_field_options.rnc (+1/-0)
tests/inlet_velocity_bc_compressible/Makefile (+17/-0)
tests/inlet_velocity_bc_compressible/inlet_velocity_bc_compressible.xml (+63/-0)
tests/inlet_velocity_bc_compressible/inlet_velocity_bc_compressible_1d.flml (+537/-0)
tests/inlet_velocity_bc_compressible_without_gravity/Makefile (+21/-0)
tests/inlet_velocity_bc_compressible_without_gravity/inlet_velocity_bc_compressible_without_gravity.xml (+95/-0)
tests/inlet_velocity_bc_compressible_without_gravity/inlet_velocity_bc_compressible_without_gravity_1d.flml (+436/-0)
tests/inlet_velocity_bc_compressible_without_gravity/inlet_velocity_bc_compressible_without_gravity_pseudo1d.flml (+430/-0)
tests/inlet_velocity_bc_compressible_without_gravity/src/inlet_velocity_bc_compressible_without_gravity_pseudo1d.geo (+19/-0)
tests/inlet_velocity_bc_incompressible/Makefile (+17/-0)
tests/inlet_velocity_bc_incompressible/inlet_velocity_bc_incompressible.flml (+381/-0)
tests/inlet_velocity_bc_incompressible/inlet_velocity_bc_incompressible.xml (+47/-0)
tests/mphase_inlet_velocity_bc_compressible/Makefile (+17/-0)
tests/mphase_inlet_velocity_bc_compressible/mphase_inlet_velocity_bc_compressible.flml (+863/-0)
tests/mphase_inlet_velocity_bc_compressible/mphase_inlet_velocity_bc_compressible.xml (+48/-0)
tests/mphase_strong_pressure_bc_compressible/Makefile (+19/-0)
tests/mphase_strong_pressure_bc_compressible/mphase_strong_pressure_bc_compressible.xml (+73/-0)
tests/mphase_strong_pressure_bc_compressible/mphase_strong_pressure_bc_compressible_p0p1.flml (+735/-0)
tests/mphase_strong_pressure_bc_compressible/mphase_strong_pressure_bc_compressible_p2p1.flml (+742/-0)
tests/mphase_subtract_out_reference_profile/Makefile (+17/-0)
tests/mphase_subtract_out_reference_profile/mphase_subtract_out_reference_profile.xml (+51/-0)
tests/mphase_subtract_out_reference_profile/mphase_subtract_out_reference_profile_1d.flml (+829/-0)
tests/strong_pressure_bc_compressible/Makefile (+17/-0)
tests/strong_pressure_bc_compressible/strong_pressure_bc_compressible.flml (+411/-0)
tests/strong_pressure_bc_compressible/strong_pressure_bc_compressible.xml (+52/-0)
tests/subtract_out_reference_profile/Makefile (+22/-0)
tests/subtract_out_reference_profile/src/subtract_out_reference_profile_pseudo1d.geo (+19/-0)
tests/subtract_out_reference_profile/subtract_out_reference_profile.xml (+50/-0)
tests/subtract_out_reference_profile/subtract_out_reference_profile_1d.flml (+525/-0)
tests/subtract_out_reference_profile/subtract_out_reference_profile_pseudo1d.flml (+529/-0)
To merge this branch: bzr merge lp:~ctjacobs-multiphase/fluidity/enforce-hydrostatic-balance
Reviewer Review Type Date Requested Status
Stephan Kramer Approve
James Robert Percival Pending
Review via email: mp+168560@code.launchpad.net

Description of the change

This merge will add a pressure/density splitting technique (see Giraldo and Restelli (2008), doi: 10.1016/j.jcp.2007.12.009), which helps to prevent spurious oscillations in the pressure field when using unbalanced finite element pairs.

When the enforce_hydrostatic_balance option (under the Velocity field) is enabled, the Density and Pressure fields are split up into a hydrostatic component (') and a perturbed component (''). The hydrostatic components, denoted p' and rho', satisfy the balance: grad(p') = rho'*g. The hydrostatic components are then subtracted from the pressure and density used in the pressure gradient and buoyancy terms in the momentum equation. This works with both CG and DG Velocity discretisations.

This merge also includes: single-phase and multiphase tests for this functionality, a description in the manual and schema, and some extra sanity checks regarding the application of pressure boundary conditions and inlet velocity boundary conditions for the multiphase flow model.

To post a comment you must log in.
Revision history for this message
Christian Jacobs (ctjacobs) wrote :
Revision history for this message
James Robert Percival (j-percival) wrote :

Code looks fine to me, and the test appears sensible. Modulo concerns about the name enforce_hydrostatic_balance I think this is good to go. Actually, it's probably worth checking with Stephan what name he thinks is sensible for this. If we ever get keen we could also try implementing the sound proof equations using the same technology.

Revision history for this message
Stephan Kramer (s-kramer) wrote :

First of all: great job - as always, well written, tested and documented. We had a little discussion off-line (also with input from CianW) that I'll summarize below. Main points were:
* The approach here deviates from all the other hydrostatic/geostrophic balance options in that the hydrostatic pressure is not actually subtracted from the Pressure field, i.e. Pressure is still the combined Pressure, it's only subtracted in the momentum equation. This is not what happens with the subtract_out_hydrostatic_level option under eos/fluids/linear or with HydrostaticPressure or GeostrophicPressure fields. In fact the Giraldo paper that you cite does exactly what these other options do, i.e. only the perturbed pressure occurs in the momentum equation (of course the hydrostatic part then reappears in the linearized continuity equation). In any case, I don't think this really matters in practice so we're happy to go with it as it is, as long as it's clearly explained.

* Since this is an option that is sort of orthogonal to subtract_out_hydrostatic and probably only applicable for compressible flows - we thought it'd be best to have it as and option under equation_of_state/compressible/. Granted, subtract_out_hydrostatic probably shouldn't have been under eos in the first place, but that situation stems from long fluidity history and it's probably better to remain consistent with it for now. (This is a thing we can easily fix in the next generation of Fluidity).

* we didn't really like enforce_hydrostatic as the name for the option as we're not really enforcing anything - we're merely helping it find a balance in cases there is one. Suggestions were subtract_out_reference_(pressure_)profile. It would be good to emphasize the difference with the fluids/linear subtract option (i.e. the hydrostatic reference component is *not* subtracted from the Pressure field).

* In the naming of the fields currently called HydrostaticBalancePressure and HydrostaticBalanceDensity it's probably better to make a clearer distinction with the other hydrostatic balance fields (HydrostaticPressure and GeostrophicPressure) by choosing names such as HydrostaticReferencePressure and HydrostaticReferenceDensity. This makes it more clear that these are meant to be set up as time-independent, user-provided reference profiles. Also reference density/pressure (profile) seems to be a term that's used more often for this sort of thing (see a.o. Vallis) as a natural extension of constant reference density \rho_0

* It would be good to emphasize in the documentation that these fields are meant to be set up as vertical profiles (i.e. horizontally constant).

Some notes, reading through the diffs:

Momentum_DG.F90, line 2365: the sign of ele_val(pressure_bc, face) seems to change - not sure that's correct?

bibliography.bib: you seem to break the convention for citation keys that's used here

4227. By Christian Jacobs

- Changed the sign of ele_val(pressure_bc, face) in Momentum_DG.F90. This shouldn't affect any existing setups.
- Removed the reference to Giraldo and Restelli (2008).
- Renamed HydrostaticBalancePressure and HydrostaticBalanceDensity to HydrostaticReferencePressure and HydrostaticReferenceDensity, respectively.
- Added the sentence in the schema and manual about the differences between this approach and the other approaches used in Fluidity, as noted by Stephan.
- Renamed enforce_hydrostatic_balance to subtract_out_reference_profile under the compressible EoS options.

4228. By Christian Jacobs

Corrected option name.

4229. By Christian Jacobs

Corrected field names.

4230. By Christian Jacobs

Renamed the tests to subtract_out_reference_profile and mphase_subtract_out_reference_profile.

4231. By Christian Jacobs

Corrected pass_tests in the .xml.

Revision history for this message
Christian Jacobs (ctjacobs) wrote :

Changes have now been made to address Stephan's comments. The buildbot queue has a green light. Stephan/James: can you please take a look and let me know what you think.

Revision history for this message
Stephan Kramer (s-kramer) wrote :

Brilliant. Thanks a lot for that. I'm entirely happy now.

review: Approve
4232. By Christian Jacobs

Merge in trunk.

Preview Diff

[H/L] Next/Prev Comment, [J/K] Next/Prev File, [N/P] Next/Prev Hunk
1=== modified file 'assemble/Momentum_CG.F90'
2--- assemble/Momentum_CG.F90 2013-03-06 13:20:27 +0000
3+++ assemble/Momentum_CG.F90 2013-07-10 19:09:26 +0000
4@@ -156,6 +156,13 @@
5 ! wetting and drying switch
6 logical :: have_wd_abs
7
8+ ! If .true., the pressure and density fields will be split up into hydrostatic
9+ ! and perturbed components. The hydrostatic components will be subtracted
10+ ! from the pressure and density used in the pressure gradient and buoyancy terms
11+ ! in the momentum equation. This helps to maintain hydrostatic balance and prevent
12+ ! spurious oscillations in the pressure field when using unbalanced finite element pairs.
13+ logical :: subtract_out_reference_profile
14+
15 ! scale factor for the absorption
16 real :: vvr_sf
17 ! scale factor for the free surface stabilisation
18@@ -255,6 +262,9 @@
19 ! for temperature dependent viscosity :
20 type(scalar_field), pointer :: temperature
21
22+ ! Fields for the subtract_out_reference_profile option under the Velocity field
23+ type(scalar_field), pointer :: hb_density, hb_pressure
24+
25 integer :: stat, dim, ele, sele
26
27 ! Fields for vertical velocity relaxation
28@@ -360,6 +370,21 @@
29 end if
30 ewrite_minmax(buoyancy)
31
32+ ! Splits up the Density and Pressure fields into a hydrostatic component (') and a perturbed component ('').
33+ ! The hydrostatic components, denoted p' and rho', should satisfy the balance: grad(p') = rho'*g
34+ ! We subtract the hydrostatic component from the density used in the buoyancy term of the momentum equation.
35+ if (have_option(trim(state%option_path)//'/equation_of_state/compressible/subtract_out_reference_profile')) then
36+ subtract_out_reference_profile = .true.
37+ hb_density => extract_scalar_field(state, "HydrostaticReferenceDensity", stat)
38+ if(stat /= 0) then
39+ FLExit("When using the subtract_out_reference_profile option, please set a (prescribed) HydrostaticReferenceDensity field.")
40+ ewrite(-1,*) 'The HydrostaticReferenceDensity field, defining the hydrostatic component of the density field, needs to be set.'
41+ end if
42+ else
43+ subtract_out_reference_profile = .false.
44+ hb_density => dummyscalar
45+ end if
46+
47 viscosity=>extract_tensor_field(state, "Viscosity", stat)
48 have_viscosity = stat == 0
49 if(.not. have_viscosity) then
50@@ -684,7 +709,7 @@
51 call construct_momentum_element_cg(state, ele, big_m, rhs, ct_m, mass, inverse_masslump, &
52 x, x_old, x_new, u, oldu, nu, ug, &
53 density, ct_rhs, &
54- source, absorption, buoyancy, gravity, &
55+ source, absorption, buoyancy, hb_density, gravity, &
56 viscosity, grad_u, &
57 fnu, tnu, leonard, strainprod, alpha, gamma, &
58 gp, surfacetension, &
59@@ -730,6 +755,14 @@
60 fs_sf=get_surface_stab_scale_factor(u)
61 end if
62
63+ if(subtract_out_reference_profile.and.integrate_continuity_by_parts.and.(assemble_ct_matrix_here .or. include_pressure_and_continuity_bcs)) then
64+ hb_pressure => extract_scalar_field(state, "HydrostaticReferencePressure", stat)
65+ if(stat /= 0) then
66+ FLExit("When using the subtract_out_reference_profile option, please set a (prescribed) HydrostaticReferencePressure field.")
67+ ewrite(-1,*) 'The HydrostaticReferencePressure field, defining the hydrostatic component of the pressure field, needs to be set.'
68+ end if
69+ end if
70+
71 surface_element_loop: do sele=1, surface_element_count(u)
72
73 ! if no_normal flow and no other condition in the tangential directions, or if periodic
74@@ -744,7 +777,7 @@
75 call construct_momentum_surface_element_cg(sele, big_m, rhs, ct_m, ct_rhs, &
76 inverse_masslump, x, u, nu, ug, density, gravity, &
77 velocity_bc, velocity_bc_type, &
78- pressure_bc, pressure_bc_type, &
79+ pressure_bc, pressure_bc_type, hb_pressure, &
80 assemble_ct_matrix_here, include_pressure_and_continuity_bcs, oldu, nvfrac)
81
82 end do surface_element_loop
83@@ -898,7 +931,7 @@
84 subroutine construct_momentum_surface_element_cg(sele, big_m, rhs, ct_m, ct_rhs, &
85 masslump, x, u, nu, ug, density, gravity, &
86 velocity_bc, velocity_bc_type, &
87- pressure_bc, pressure_bc_type, &
88+ pressure_bc, pressure_bc_type, hb_pressure, &
89 assemble_ct_matrix_here, include_pressure_and_continuity_bcs,&
90 oldu, nvfrac)
91
92@@ -923,6 +956,7 @@
93
94 type(scalar_field), intent(in) :: pressure_bc
95 integer, dimension(:), intent(in) :: pressure_bc_type
96+ type(scalar_field), intent(in) :: hb_pressure
97
98 logical, intent(in) :: assemble_ct_matrix_here, include_pressure_and_continuity_bcs
99
100@@ -1028,8 +1062,15 @@
101 ! /
102 ! add -| N_i M_j \vec n p_j, where p_j are the prescribed bc values
103 ! /
104- call addto(rhs, dim, u_nodes_bdy, -matmul( ele_val(pressure_bc, sele), &
105- ct_mat_bdy(dim,:,:) ))
106+ if (subtract_out_reference_profile) then
107+ ! Here we subtract the hydrostatic component from the pressure boundary condition used in the surface integral when
108+ ! assembling ct_m. Hopefully this will be the same as the pressure boundary condition itself.
109+ call addto(rhs, dim, u_nodes_bdy, -matmul(ele_val(pressure_bc, sele)-face_val(hb_pressure, sele), &
110+ ct_mat_bdy(dim,:,:) ))
111+ else
112+ call addto(rhs, dim, u_nodes_bdy, -matmul( ele_val(pressure_bc, sele), &
113+ ct_mat_bdy(dim,:,:) ))
114+ end if
115 end if
116 end do
117 end if
118@@ -1125,7 +1166,7 @@
119 mass, masslump, &
120 x, x_old, x_new, u, oldu, nu, ug, &
121 density, ct_rhs, &
122- source, absorption, buoyancy, gravity, &
123+ source, absorption, buoyancy, hb_density, gravity, &
124 viscosity, grad_u, &
125 fnu, tnu, leonard, strainprod, alpha, gamma, &
126 gp, surfacetension, &
127@@ -1172,6 +1213,8 @@
128 ! Temperature dependent viscosity:
129 type(scalar_field), intent(in) :: temperature
130
131+ type(scalar_field), intent(in) :: hb_density
132+
133 ! Non-linear approximation of the volume fraction
134 type(scalar_field), intent(in) :: nvfrac
135 ! Pointer to the nvfrac field's shape function
136@@ -1347,7 +1390,7 @@
137
138 ! Buoyancy terms
139 if(have_gravity) then
140- call add_buoyancy_element_cg(x, ele, test_function, u, buoyancy, gravity, nvfrac, detwei, rhs_addto)
141+ call add_buoyancy_element_cg(x, ele, test_function, u, buoyancy, hb_density, gravity, nvfrac, detwei, rhs_addto)
142 end if
143
144 ! Surface tension
145@@ -1673,12 +1716,12 @@
146
147 end subroutine add_sources_element_cg
148
149- subroutine add_buoyancy_element_cg(positions, ele, test_function, u, buoyancy, gravity, nvfrac, detwei, rhs_addto)
150+ subroutine add_buoyancy_element_cg(positions, ele, test_function, u, buoyancy, hb_density, gravity, nvfrac, detwei, rhs_addto)
151 type(vector_field), intent(in) :: positions
152 integer, intent(in) :: ele
153 type(element_type), intent(in) :: test_function
154 type(vector_field), intent(in) :: u
155- type(scalar_field), intent(in) :: buoyancy
156+ type(scalar_field), intent(in) :: buoyancy, hb_density
157 type(vector_field), intent(in) :: gravity
158 type(scalar_field), intent(in) :: nvfrac
159 real, dimension(ele_ngi(u, ele)), intent(in) :: detwei
160@@ -1687,12 +1730,14 @@
161 real, dimension(ele_ngi(u, ele)) :: nvfrac_gi
162 real, dimension(ele_ngi(u, ele)) :: coefficient_detwei
163
164- if(multiphase) then
165- nvfrac_gi = ele_val_at_quad(nvfrac, ele)
166+ if (subtract_out_reference_profile) then
167+ coefficient_detwei = gravity_magnitude*(ele_val_at_quad(buoyancy, ele)-ele_val_at_quad(hb_density, ele))*detwei
168+ else
169+ coefficient_detwei = gravity_magnitude*ele_val_at_quad(buoyancy, ele)*detwei
170 end if
171
172- coefficient_detwei = gravity_magnitude*ele_val_at_quad(buoyancy, ele)*detwei
173 if(multiphase) then
174+ nvfrac_gi = ele_val_at_quad(nvfrac, ele)
175 coefficient_detwei = coefficient_detwei*nvfrac_gi
176 end if
177
178
179=== modified file 'assemble/Momentum_DG.F90'
180--- assemble/Momentum_DG.F90 2013-05-30 09:33:45 +0000
181+++ assemble/Momentum_DG.F90 2013-07-10 19:09:26 +0000
182@@ -135,6 +135,7 @@
183 logical :: have_advection
184 logical :: move_mesh
185 logical :: have_pressure_bc
186+ logical :: subtract_out_reference_profile
187
188 real :: gravity_magnitude
189
190@@ -215,6 +216,9 @@
191 !! Surface tension field
192 type(tensor_field) :: surfacetension
193
194+ ! Fields for the subtract_out_reference_profile option under the Velocity field
195+ type(scalar_field), pointer :: hb_density, hb_pressure
196+
197 !! field over the entire surface mesh, giving bc values
198 type(vector_field) :: velocity_bc
199 type(scalar_field) :: pressure_bc
200@@ -395,6 +399,20 @@
201 end if
202 ewrite_minmax(buoyancy)
203
204+ ! Splits up the Density and Pressure fields into a hydrostatic component (') and a perturbed component ('').
205+ ! The hydrostatic components, denoted p' and rho', should satisfy the balance: grad(p') = rho'*g
206+ ! We subtract the hydrostatic component from the density used in the buoyancy term of the momentum equation.
207+ if (have_option(trim(state%option_path)//'/equation_of_state/compressible/subtract_out_reference_profile')) then
208+ subtract_out_reference_profile = .true.
209+ hb_density => extract_scalar_field(state, "HydrostaticReferenceDensity")
210+
211+ if(l_include_pressure_bcs) then
212+ hb_pressure => extract_scalar_field(state, "HydrostaticReferencePressure")
213+ end if
214+ else
215+ subtract_out_reference_profile = .false.
216+ end if
217+
218 Viscosity=extract_tensor_field(state, "Viscosity", stat)
219 have_viscosity = (stat==0)
220 if (.not.have_viscosity) then
221@@ -661,7 +679,7 @@
222 ele = fetch(colours(clr), nnid)
223 call construct_momentum_element_dg(ele, big_m, rhs, &
224 & X, U, advecting_velocity, U_mesh, X_old, X_new, &
225- & Source, Buoyancy, gravity, Abs, Viscosity, &
226+ & Source, Buoyancy, hb_density, hb_pressure, gravity, Abs, Viscosity, &
227 & P, Rho, surfacetension, q_mesh, &
228 & velocity_bc, velocity_bc_type, &
229 & pressure_bc, pressure_bc_type, &
230@@ -718,7 +736,7 @@
231 end subroutine construct_momentum_dg
232
233 subroutine construct_momentum_element_dg(ele, big_m, rhs, &
234- &X, U, U_nl, U_mesh, X_old, X_new, Source, Buoyancy, gravity, Abs, &
235+ &X, U, U_nl, U_mesh, X_old, X_new, Source, Buoyancy, hb_density, hb_pressure, gravity, Abs, &
236 &Viscosity, P, Rho, surfacetension, q_mesh, &
237 &velocity_bc, velocity_bc_type, &
238 &pressure_bc, pressure_bc_type, &
239@@ -748,6 +766,7 @@
240 !! Viscosity
241 type(tensor_field) :: Viscosity
242 type(scalar_field) :: P, Rho
243+ type(scalar_field), intent(in) :: hb_density, hb_pressure
244 !! surfacetension
245 type(tensor_field) :: surfacetension
246 !! field containing the bc values of velocity
247@@ -821,7 +840,7 @@
248 integer :: start, finish
249
250 ! Variable transform times quadrature weights.
251- real, dimension(ele_ngi(U,ele)) :: detwei, detwei_old, detwei_new
252+ real, dimension(ele_ngi(U,ele)) :: detwei, detwei_old, detwei_new, coefficient_detwei
253 ! Transformed gradient function for velocity.
254 real, dimension(ele_loc(U, ele), ele_ngi(U, ele), mesh_dim(U)) :: du_t
255 ! Transformed gradient function for grid velocity.
256@@ -1252,22 +1271,28 @@
257
258 if(have_gravity.and.acceleration.and.assemble_element) then
259 ! buoyancy
260+ if(subtract_out_reference_profile) then
261+ coefficient_detwei = detwei*gravity_magnitude*(ele_val_at_quad(buoyancy, ele)-ele_val_at_quad(hb_density, ele))
262+ else
263+ coefficient_detwei = detwei*gravity_magnitude*ele_val_at_quad(buoyancy, ele)
264+ end if
265+
266 if (on_sphere) then
267 ! If were on a spherical Earth evaluate the direction of the gravity vector
268 ! exactly at quadrature points.
269 rhs_addto(:, :loc) = rhs_addto(:, :loc) + shape_vector_rhs(u_shape, &
270 sphere_inward_normal_at_quad_ele(X, ele), &
271- detwei*gravity_magnitude*ele_val_at_quad(buoyancy, ele))
272+ coefficient_detwei)
273 else
274
275 if(multiphase) then
276 rhs_addto(:, :loc) = rhs_addto(:, :loc) + shape_vector_rhs(u_shape, &
277 ele_val_at_quad(gravity, ele), &
278- detwei*gravity_magnitude*ele_val_at_quad(buoyancy, ele)*nvfrac_gi)
279+ coefficient_detwei*nvfrac_gi)
280 else
281 rhs_addto(:, :loc) = rhs_addto(:, :loc) + shape_vector_rhs(u_shape, &
282 ele_val_at_quad(gravity, ele), &
283- detwei*gravity_magnitude*ele_val_at_quad(buoyancy, ele))
284+ coefficient_detwei)
285 end if
286
287 end if
288@@ -1691,7 +1716,7 @@
289 & rhs_addto, Grad_U_mat_q, Div_U_mat_q, X,&
290 & Rho, U, U_nl, U_mesh, P, q_mesh, surfacetension, &
291 & velocity_bc, velocity_bc_type, &
292- & pressure_bc, pressure_bc_type, &
293+ & pressure_bc, pressure_bc_type, hb_pressure, &
294 & subcycle_m_tensor_addto, nvfrac, &
295 & ele2grad_mat=ele2grad_mat, kappa_mat=kappa_mat, &
296 & inverse_mass_mat=inverse_mass_mat, &
297@@ -1704,7 +1729,7 @@
298 & rhs_addto, Grad_U_mat_q, Div_U_mat_q, X,&
299 & Rho, U, U_nl, U_mesh, P, q_mesh, surfacetension, &
300 & velocity_bc, velocity_bc_type, &
301- & pressure_bc, pressure_bc_type, &
302+ & pressure_bc, pressure_bc_type, hb_pressure, &
303 & subcycle_m_tensor_addto, nvfrac)
304 end if
305 end if
306@@ -1973,7 +1998,7 @@
307 & rhs_addto, Grad_U_mat, Div_U_mat, X, Rho, U,&
308 & U_nl, U_mesh, P, q_mesh, surfacetension, &
309 & velocity_bc, velocity_bc_type, &
310- & pressure_bc, pressure_bc_type, &
311+ & pressure_bc, pressure_bc_type, hb_pressure, &
312 & subcycle_m_tensor_addto, nvfrac, &
313 & ele2grad_mat, kappa_mat, inverse_mass_mat, &
314 & viscosity, viscosity_mat)
315@@ -2002,6 +2027,7 @@
316 integer, dimension(:,:), intent(in) :: velocity_bc_type
317 type(scalar_field), intent(in) :: pressure_bc
318 integer, dimension(:), intent(in) :: pressure_bc_type
319+ type(scalar_field), intent(in) :: hb_pressure
320
321 !! Computation of primal fluxes and penalty fluxes
322 real, intent(in), optional, dimension(:,:,:) :: ele2grad_mat
323@@ -2334,8 +2360,13 @@
324 ! add -| N_i M_j \vec n p_j, where p_j are the prescribed bc values
325 ! /
326 do dim = 1, U%dim
327- rhs_addto(dim,u_face_l) = rhs_addto(dim,u_face_l) - &
328- matmul( ele_val(pressure_bc, face), mnCT(1,dim,:,:) )
329+ if(subtract_out_reference_profile) then
330+ rhs_addto(dim,u_face_l) = rhs_addto(dim,u_face_l) - &
331+ matmul( ele_val(pressure_bc, face) - face_val(hb_pressure, face), mnCT(1,dim,:,:) )
332+ else
333+ rhs_addto(dim,u_face_l) = rhs_addto(dim,u_face_l) - &
334+ matmul( ele_val(pressure_bc, face), mnCT(1,dim,:,:) )
335+ end if
336 end do
337 end if
338
339
340=== modified file 'assemble/Momentum_Equation.F90'
341--- assemble/Momentum_Equation.F90 2013-03-03 01:36:16 +0000
342+++ assemble/Momentum_Equation.F90 2013-07-10 19:09:26 +0000
343@@ -1515,6 +1515,11 @@
344 type(vector_field) :: delta_u
345 type(vector_field), pointer :: positions
346
347+ ! Fields for the subtract_out_reference_profile option under the Velocity field
348+ type(scalar_field), pointer :: hb_pressure
349+ type(scalar_field) :: combined_p
350+ integer :: stat
351+
352 ewrite(1,*) 'Entering advance_velocity'
353
354
355@@ -1539,6 +1544,20 @@
356 &have_option('/ocean_forcing/shelf')) then
357 ewrite(1,*) "shelf: Entering compute_pressure_and_tidal_gradient"
358 call compute_pressure_and_tidal_gradient(state(istate), delta_u, ct_m(istate)%ptr, p_theta, x)
359+ else if (have_option(trim(state(istate)%option_path)//'/equation_of_state/compressible/subtract_out_reference_profile')) then
360+ ! Splits up the Density and Pressure fields into a hydrostatic component (') and a perturbed component ('').
361+ ! The hydrostatic components, denoted p' and rho', should satisfy the balance: grad(p') = rho'*g
362+ ! We subtract the hydrostatic component from the pressure used in the pressure gradient term of the momentum equation.
363+ hb_pressure => extract_scalar_field(state(istate), "HydrostaticReferencePressure", stat)
364+ if(stat /= 0) then
365+ FLExit("When using the subtract_out_reference_profile option, please set a (prescribed) HydrostaticReferencePressure field.")
366+ ewrite(-1,*) 'The HydrostaticReferencePressure field, defining the hydrostatic component of the pressure field, needs to be set.'
367+ end if
368+ call allocate(combined_p,p_theta%mesh, "PressurePerturbation")
369+ call set(combined_p, p_theta)
370+ call addto(combined_p, hb_pressure, scale=-1.0)
371+ call mult_T(delta_u, ct_m(istate)%ptr, combined_p)
372+ call deallocate(combined_p)
373 else
374 call mult_T(delta_u, ct_m(istate)%ptr, p_theta)
375 end if
376
377=== modified file 'manual/configuring_fluidity.tex'
378--- manual/configuring_fluidity.tex 2013-05-29 18:26:30 +0000
379+++ manual/configuring_fluidity.tex 2013-07-10 19:09:26 +0000
380@@ -2483,6 +2483,17 @@
381
382 \emph{Important note when using 'stress form' and 'partial stress form' with a CG velocity field:} when using isotropic viscosities, and not the 'tensor form' of the viscosity term, all components of viscosity must be set to equal to the isotropic viscosity due to the method of implementation. If using an anisotropic viscosity with the 'partial stress form' or 'stress form' consult the schema and query the code to understand how the viscosity tensor must be defined. This does not apply when using DG discretisations.
383
384+\subsubsection{Hydrostatic balance}
385+The option \option{subtract\_out\_reference\_profile} splits up the Density and Pressure fields into a hydrostatic (reference) component (') and a perturbed component (''). The hydrostatic (reference) components, denoted $p^{\prime}$ and $\rho^{\prime}$, should satisfy the balance:
386+\begin{equation}
387+ \nabla p^{\prime} = \rho^{\prime}\mathbf{g}
388+\end{equation}
389+Enabling this option will subtract the hydrostatic components, specified here, from the pressure and density used in the pressure gradient and buoyancy terms in the momentum equation. This helps to maintain hydrostatic balance and prevent spurious oscillations in the pressure field when using unbalanced finite element pairs.
390+
391+To use this option you will also need to create two prescribed scalar fields, called HydrostaticReferencePressure and HydrostaticReferenceDensity, which define $p^{\prime}$ and $\rho^{\prime}$. These must be on the same mesh as pressure and density, respectively, and are meant to be set up as vertical profiles (i.e. constant in the horizontal direction).
392+
393+Note that unlike all the other hydrostatic/geostrophic balance options in Fluidity (i.e. \option{subtract\_out\_hydrostatic\_level} under the linear incompressible EoS option, or with HydrostaticPressure or GeostrophicPressure fields), the hydrostatic pressure is not subtracted from the Pressure field itself. In other words, the Pressure field that gets solved for (and output in the .vtu files) is still the combined Pressure ($p = p^{\prime} + \rho^{\prime}$), and the hydrostatic pressure $p^{\prime}$ is only subtracted in the momentum equation.
394+
395 \subsection{InternalEnergy options}
396 \begin{itemize}
397 \item The optional heat flux term can be included via the InternalEnergy's Diffusivity field. Users will need to specify an isotropic value for $\frac{k}{C_v}$, where $k$ is the effective conductivity and $C_v$ is the specific heat at constant volume.
398
399=== modified file 'schemas/equation_of_state.rnc'
400--- schemas/equation_of_state.rnc 2012-05-30 07:26:05 +0000
401+++ schemas/equation_of_state.rnc 2013-07-10 19:09:26 +0000
402@@ -91,62 +91,76 @@
403 (
404 ## Equations of state for compressible applications
405 element compressible {
406- ## Stiffened Gas EoS
407- ##
408- ## Used with compressible simulations
409- element stiffened_gas {
410- ## reference uncompressed density
411- ##
412- ## if activated then either Liquid EoS or
413- ## full Stiffened Gas EoS
414- element reference_density {
415- real
416- }?,
417- ## Ratio of specific heats at constant
418- ## pressure to that at constant volume
419- ##
420- ## Requires an energy field.
421- ## If activated then a full Stiffened Gas EoS
422- element ratio_specific_heats {
423- real
424- }?,
425- ## bulk_sound_speed_squared = isothermal_bulk_modulus/reference_density
426- ##
427- ## if activated then either full or partial Liquid EoS or full
428+ (
429 ## Stiffened Gas EoS
430- element bulk_sound_speed_squared {
431- real
432- }?
433- }|
434- ## Giraldo et. al. 2008, J. Comp. Phys.
435- ##
436- ## Used with compressible simulations
437- element giraldo {
438- ## reference pressure
439- ##
440- ## The pressure at which potential temperature
441- ## equals actual temperature. Normally taken to
442- ## be the surface pressure, 1.0e05.
443- element reference_pressure {
444- real
445- },
446- ## Heat capacity at constant pressure
447- element C_P {
448- real
449- },
450- ## Heat capacity at constant volume
451- element C_V {
452- real
453+ ##
454+ ## Used with compressible simulations
455+ element stiffened_gas {
456+ ## reference uncompressed density
457+ ##
458+ ## if activated then either Liquid EoS or
459+ ## full Stiffened Gas EoS
460+ element reference_density {
461+ real
462+ }?,
463+ ## Ratio of specific heats at constant
464+ ## pressure to that at constant volume
465+ ##
466+ ## Requires an energy field.
467+ ## If activated then a full Stiffened Gas EoS
468+ element ratio_specific_heats {
469+ real
470+ }?,
471+ ## bulk_sound_speed_squared = isothermal_bulk_modulus/reference_density
472+ ##
473+ ## if activated then either full or partial Liquid EoS or full
474+ ## Stiffened Gas EoS
475+ element bulk_sound_speed_squared {
476+ real
477+ }?
478+ }|
479+ ## Giraldo et. al. 2008, J. Comp. Phys.
480+ ##
481+ ## Used with compressible simulations
482+ element giraldo {
483+ ## reference pressure
484+ ##
485+ ## The pressure at which potential temperature
486+ ## equals actual temperature. Normally taken to
487+ ## be the surface pressure, 1.0e05.
488+ element reference_pressure {
489+ real
490+ },
491+ ## Heat capacity at constant pressure
492+ element C_P {
493+ real
494+ },
495+ ## Heat capacity at constant volume
496+ element C_V {
497+ real
498+ }
499+ }|
500+ ## Foam EoS
501+ ## Used with compressible simulations of liquid drainage in foams.
502+ ## It describes the liquid content in the foam as the product of the
503+ ## Plateau border cross sectional area and the local Plateau
504+ ## border length per unit volume (lambda).
505+ element foam {
506+ empty
507 }
508- }|
509- ## Foam EoS
510- ## Used with compressible simulations of liquid drainage in foams.
511- ## It describes the liquid content in the foam as the product of the
512- ## Plateau border cross sectional area and the local Plateau
513- ## border length per unit volume (lambda).
514- element foam {
515+ ),
516+ ## This splits up the Density and Pressure fields into a hydrostatic (reference) component (') and a perturbed component ('').
517+ ## The hydrostatic (reference) components, denoted p' and rho', should satisfy the balance:
518+ ## grad(p') = rho'*g
519+ ##
520+ ## Enabling this option will subtract the hydrostatic components, specified here, from the pressure and density used in the pressure gradient and buoyancy terms in the momentum equation. This helps to maintain hydrostatic balance and prevent spurious oscillations in the pressure field when using unbalanced finite element pairs.
521+ ##
522+ ## Note 1: You will also need to create two prescribed scalar fields, called HydrostaticReferencePressure and HydrostaticReferenceDensity, which define p' and rho'. These must be on the same mesh as pressure and density, respectively. Also, these fields are meant to be time-independent and set up as vertical profiles (i.e. constant in the horizontal direction).
523+ ##
524+ ## Note 2: Unlike all the other hydrostatic/geostrophic balance options in Fluidity (i.e. subtract_out_hydrostatic_level under the linear incompressible EoS option, or with HydrostaticPressure or GeostrophicPressure fields), the hydrostatic pressure is not subtracted from the Pressure field itself. In other words, the Pressure field that gets solved for (and output in the .vtu files) is still the combined Pressure (p = p' + p''), and the hydrostatic pressure p' is only subtracted in the momentum equation.
525+ element subtract_out_reference_profile {
526 empty
527- }
528+ }?
529 }
530 )
531
532
533=== modified file 'schemas/equation_of_state.rng'
534--- schemas/equation_of_state.rng 2012-05-30 07:26:05 +0000
535+++ schemas/equation_of_state.rng 2013-07-10 19:09:26 +0000
536@@ -162,6 +162,20 @@
537 <empty/>
538 </element>
539 </choice>
540+ <optional>
541+ <element name="subtract_out_reference_profile">
542+ <a:documentation>This splits up the Density and Pressure fields into a hydrostatic (reference) component (') and a perturbed component ('').
543+The hydrostatic (reference) components, denoted p' and rho', should satisfy the balance:
544+grad(p') = rho'*g
545+
546+Enabling this option will subtract the hydrostatic components, specified here, from the pressure and density used in the pressure gradient and buoyancy terms in the momentum equation. This helps to maintain hydrostatic balance and prevent spurious oscillations in the pressure field when using unbalanced finite element pairs.
547+
548+Note 1: You will also need to create two prescribed scalar fields, called HydrostaticReferencePressure and HydrostaticReferenceDensity, which define p' and rho'. These must be on the same mesh as pressure and density, respectively. Also, these fields are meant to be time-independent and set up as vertical profiles (i.e. constant in the horizontal direction).
549+
550+Note 2: Unlike all the other hydrostatic/geostrophic balance options in Fluidity (i.e. subtract_out_hydrostatic_level under the linear incompressible EoS option, or with HydrostaticPressure or GeostrophicPressure fields), the hydrostatic pressure is not subtracted from the Pressure field itself. In other words, the Pressure field that gets solved for (and output in the .vtu files) is still the combined Pressure (p = p' + p''), and the hydrostatic pressure p' is only subtracted in the momentum equation.</a:documentation>
551+ <empty/>
552+ </element>
553+ </optional>
554 </element>
555 </define>
556 </grammar>
557
558=== modified file 'schemas/prognostic_field_options.rnc'
559--- schemas/prognostic_field_options.rnc 2013-05-31 07:10:50 +0000
560+++ schemas/prognostic_field_options.rnc 2013-07-10 19:09:26 +0000
561@@ -1200,6 +1200,7 @@
562 }?
563 }?
564 }?,
565+
566 ## SurfaceTension
567 element tensor_field {
568 attribute name { "SurfaceTension" },
569
570=== added directory 'tests/inlet_velocity_bc_compressible'
571=== added file 'tests/inlet_velocity_bc_compressible/Makefile'
572--- tests/inlet_velocity_bc_compressible/Makefile 1970-01-01 00:00:00 +0000
573+++ tests/inlet_velocity_bc_compressible/Makefile 2013-07-10 19:09:26 +0000
574@@ -0,0 +1,17 @@
575+preprocess:
576+ @echo **********Creating 1D mesh
577+ ../../bin/interval --dx=100.0 -- 0.0 10000.0 line
578+
579+run:
580+ @echo **********Running simulation
581+ ../../bin/fluidity -v2 -l inlet_velocity_bc_compressible_1d.flml
582+
583+input: clean preprocess
584+
585+clean:
586+ rm -f *.stat *.steady_state*
587+ rm -f *.d.* *.vtu
588+ rm -f *.msh
589+ rm -f *.ele *.edge *.node *.poly *.bound
590+ rm -f matrixdump* *.log* *.err*
591+
592
593=== added file 'tests/inlet_velocity_bc_compressible/inlet_velocity_bc_compressible.xml'
594--- tests/inlet_velocity_bc_compressible/inlet_velocity_bc_compressible.xml 1970-01-01 00:00:00 +0000
595+++ tests/inlet_velocity_bc_compressible/inlet_velocity_bc_compressible.xml 2013-07-10 19:09:26 +0000
596@@ -0,0 +1,63 @@
597+<?xml version="1.0" encoding="UTF-8" ?>
598+<!DOCTYPE testproblem SYSTEM "regressiontest.dtd">
599+
600+<testproblem>
601+
602+ <name>inlet_velocity_bc_compressible</name>
603+ <owner userid="ctj10"/>
604+ <tags>flml</tags>
605+
606+ <problem_definition length="medium" nprocs="1">
607+ <command_line>make run</command_line>
608+ </problem_definition>
609+
610+ <variables>
611+ <variable name="gas_velocity_max_1d" language="python">
612+from fluidity_tools import stat_parser
613+s = stat_parser("inlet_velocity_bc_compressible_1d.stat")
614+gas_velocity_max_1d = s["Gas"]["Velocity%magnitude"]["max"][-1]
615+ </variable>
616+
617+ <variable name="gas_velocity_min_1d" language="python">
618+from fluidity_tools import stat_parser
619+s = stat_parser("inlet_velocity_bc_compressible_1d.stat")
620+gas_velocity_min_1d = s["Gas"]["Velocity%magnitude"]["min"][-1]
621+ </variable>
622+
623+ <variable name="gas_density_max_1d" language="python">
624+from fluidity_tools import stat_parser
625+s = stat_parser("inlet_velocity_bc_compressible_1d.stat")
626+gas_density_max_1d = s["Gas"]["Density"]["max"][-1]
627+ </variable>
628+
629+ <variable name="gas_density_min_1d" language="python">
630+from fluidity_tools import stat_parser
631+s = stat_parser("inlet_velocity_bc_compressible_1d.stat")
632+gas_density_min_1d = s["Gas"]["Density"]["min"][-1]
633+ </variable>
634+
635+ <variable name="solvers_converged" language="python">
636+import os
637+files = os.listdir("./")
638+solvers_converged = not "matrixdump" in files and not "matrixdump.info" in files
639+ </variable>
640+ </variables>
641+
642+ <pass_tests>
643+ <test name="Gas::Velocity is at least 300 m/s everywhere in the 1D test case" language="python">
644+assert(abs(gas_velocity_max_1d) &lt;= 800.0 and abs(gas_velocity_min_1d) &gt;= 300.0)
645+ </test>
646+
647+ <test name="Gas::Density is between 0.05 and 0.25 kg/m^3 everywhere in the 1D test case" language="python">
648+assert(abs(gas_density_max_1d) &lt;= 0.25 and abs(gas_density_min_1d) &gt;= 0.05)
649+ </test>
650+
651+ <test name="Solvers converged" language="python">
652+assert(solvers_converged)
653+ </test>
654+ </pass_tests>
655+
656+ <warn_tests>
657+ </warn_tests>
658+
659+</testproblem>
660
661=== added file 'tests/inlet_velocity_bc_compressible/inlet_velocity_bc_compressible_1d.flml'
662--- tests/inlet_velocity_bc_compressible/inlet_velocity_bc_compressible_1d.flml 1970-01-01 00:00:00 +0000
663+++ tests/inlet_velocity_bc_compressible/inlet_velocity_bc_compressible_1d.flml 2013-07-10 19:09:26 +0000
664@@ -0,0 +1,537 @@
665+<?xml version='1.0' encoding='utf-8'?>
666+<fluidity_options>
667+ <simulation_name>
668+ <string_value lines="1">inlet_velocity_bc_compressible_1d</string_value>
669+ </simulation_name>
670+ <problem_type>
671+ <string_value lines="1">fluids</string_value>
672+ </problem_type>
673+ <geometry>
674+ <dimension>
675+ <integer_value rank="0">1</integer_value>
676+ </dimension>
677+ <mesh name="CoordinateMesh">
678+ <from_file file_name="line">
679+ <format name="triangle"/>
680+ <stat>
681+ <include_in_stat/>
682+ </stat>
683+ </from_file>
684+ </mesh>
685+ <mesh name="VelocityMesh">
686+ <from_mesh>
687+ <mesh name="CoordinateMesh"/>
688+ <mesh_shape>
689+ <polynomial_degree>
690+ <integer_value rank="0">0</integer_value>
691+ </polynomial_degree>
692+ </mesh_shape>
693+ <mesh_continuity>
694+ <string_value>discontinuous</string_value>
695+ </mesh_continuity>
696+ <stat>
697+ <exclude_from_stat/>
698+ </stat>
699+ </from_mesh>
700+ </mesh>
701+ <mesh name="PressureMesh">
702+ <from_mesh>
703+ <mesh name="CoordinateMesh"/>
704+ <mesh_shape>
705+ <polynomial_degree>
706+ <integer_value rank="0">1</integer_value>
707+ </polynomial_degree>
708+ </mesh_shape>
709+ <stat>
710+ <exclude_from_stat/>
711+ </stat>
712+ </from_mesh>
713+ </mesh>
714+ <mesh name="DensityMesh">
715+ <from_mesh>
716+ <mesh name="CoordinateMesh"/>
717+ <mesh_shape>
718+ <polynomial_degree>
719+ <integer_value rank="0">1</integer_value>
720+ </polynomial_degree>
721+ </mesh_shape>
722+ <stat>
723+ <exclude_from_stat/>
724+ </stat>
725+ </from_mesh>
726+ </mesh>
727+ <mesh name="GeostrophicMesh">
728+ <from_mesh>
729+ <mesh name="CoordinateMesh"/>
730+ <mesh_shape>
731+ <polynomial_degree>
732+ <integer_value rank="0">1</integer_value>
733+ </polynomial_degree>
734+ </mesh_shape>
735+ <stat>
736+ <exclude_from_stat/>
737+ </stat>
738+ </from_mesh>
739+ </mesh>
740+ <quadrature>
741+ <degree>
742+ <integer_value rank="0">4</integer_value>
743+ </degree>
744+ </quadrature>
745+ </geometry>
746+ <io>
747+ <dump_format>
748+ <string_value>vtk</string_value>
749+ </dump_format>
750+ <dump_period>
751+ <constant>
752+ <real_value rank="0">0</real_value>
753+ </constant>
754+ </dump_period>
755+ <output_mesh name="PressureMesh"/>
756+ <stat>
757+ <output_at_start/>
758+ </stat>
759+ </io>
760+ <timestepping>
761+ <current_time>
762+ <real_value rank="0">0</real_value>
763+ </current_time>
764+ <timestep>
765+ <real_value rank="0">0.01</real_value>
766+ </timestep>
767+ <finish_time>
768+ <real_value rank="0">600.0</real_value>
769+ </finish_time>
770+ <nonlinear_iterations>
771+ <integer_value rank="0">2</integer_value>
772+ <tolerance>
773+ <real_value rank="0">1.0e-9</real_value>
774+ <infinity_norm/>
775+ </tolerance>
776+ </nonlinear_iterations>
777+ <adaptive_timestep>
778+ <requested_cfl>
779+ <real_value rank="0">0.5</real_value>
780+ </requested_cfl>
781+ <courant_number name="CFLNumber">
782+ <mesh name="VelocityMesh"/>
783+ </courant_number>
784+ <minimum_timestep>
785+ <real_value rank="0">0.001</real_value>
786+ </minimum_timestep>
787+ <increase_tolerance>
788+ <real_value rank="0">1.1</real_value>
789+ </increase_tolerance>
790+ </adaptive_timestep>
791+ </timestepping>
792+ <physical_parameters>
793+ <gravity>
794+ <magnitude>
795+ <real_value rank="0">9.8</real_value>
796+ </magnitude>
797+ <vector_field name="GravityDirection" rank="1">
798+ <prescribed>
799+ <mesh name="CoordinateMesh"/>
800+ <value name="WholeMesh">
801+ <constant>
802+ <real_value shape="1" dim1="dim" rank="1">-1</real_value>
803+ </constant>
804+ </value>
805+ <output/>
806+ <stat>
807+ <include_in_stat/>
808+ </stat>
809+ <detectors>
810+ <exclude_from_detectors/>
811+ </detectors>
812+ </prescribed>
813+ </vector_field>
814+ </gravity>
815+ </physical_parameters>
816+ <material_phase name="Gas">
817+ <equation_of_state>
818+ <compressible>
819+ <stiffened_gas>
820+ <ratio_specific_heats>
821+ <real_value rank="0">1.33</real_value>
822+ </ratio_specific_heats>
823+ </stiffened_gas>
824+ <subtract_out_reference_profile/>
825+ </compressible>
826+ </equation_of_state>
827+ <scalar_field name="Pressure" rank="0">
828+ <prognostic>
829+ <mesh name="PressureMesh"/>
830+ <spatial_discretisation>
831+ <continuous_galerkin>
832+ <remove_stabilisation_term/>
833+ <integrate_continuity_by_parts/>
834+ </continuous_galerkin>
835+ </spatial_discretisation>
836+ <scheme>
837+ <poisson_pressure_solution>
838+ <string_value lines="1">never</string_value>
839+ </poisson_pressure_solution>
840+ <use_compressible_projection_method/>
841+ </scheme>
842+ <solver>
843+ <iterative_method name="gmres">
844+ <restart>
845+ <integer_value rank="0">30</integer_value>
846+ </restart>
847+ </iterative_method>
848+ <preconditioner name="sor"/>
849+ <relative_error>
850+ <real_value rank="0">1.0e-7</real_value>
851+ </relative_error>
852+ <max_iterations>
853+ <integer_value rank="0">1000</integer_value>
854+ </max_iterations>
855+ <never_ignore_solver_failures/>
856+ <diagnostics>
857+ <monitors/>
858+ </diagnostics>
859+ </solver>
860+ <initial_condition name="WholeMesh">
861+ <python>
862+ <string_value lines="20" type="code" language="python">def val(X,t):
863+ from math import exp
864+ T0 = 288.15 # K
865+ R = 287.058 # Specific gas constant in J/Kg
866+ g = 9.8 # m/s**2
867+ h = X[0] # m
868+ p0 = 101325
869+ e = T0*1406.0
870+ gamma = 1.33
871+ p = p0*exp(-(g*h)/((gamma-1.0)*e))
872+ return p</string_value>
873+ </python>
874+ </initial_condition>
875+ <boundary_conditions name="Right">
876+ <surface_ids>
877+ <integer_value shape="1" rank="1">2</integer_value>
878+ </surface_ids>
879+ <type name="dirichlet">
880+ <python>
881+ <string_value lines="20" type="code" language="python">def val(X,t):
882+ from math import exp
883+ T0 = 288.15 # K
884+ R = 287.058 # Specific gas constant in J/Kg
885+ g = 9.8 # m/s**2
886+ h = X[0] # m
887+ p0 = 101325
888+ e = T0*1406.0
889+ gamma = 1.33
890+ p = p0*exp(-(g*h)/((gamma-1.0)*e))
891+ return p</string_value>
892+ </python>
893+ </type>
894+ </boundary_conditions>
895+ <output/>
896+ <stat/>
897+ <convergence>
898+ <include_in_convergence/>
899+ </convergence>
900+ <detectors>
901+ <exclude_from_detectors/>
902+ </detectors>
903+ <steady_state>
904+ <include_in_steady_state/>
905+ </steady_state>
906+ <no_interpolation/>
907+ </prognostic>
908+ </scalar_field>
909+ <scalar_field name="Density" rank="0">
910+ <prognostic>
911+ <mesh name="DensityMesh"/>
912+ <spatial_discretisation>
913+ <control_volumes>
914+ <face_value name="FirstOrderUpwind"/>
915+ </control_volumes>
916+ <conservative_advection>
917+ <real_value rank="0">1.0</real_value>
918+ </conservative_advection>
919+ </spatial_discretisation>
920+ <temporal_discretisation>
921+ <theta>
922+ <real_value rank="0">1.0</real_value>
923+ </theta>
924+ </temporal_discretisation>
925+ <initial_condition name="WholeMesh">
926+ <python>
927+ <string_value lines="20" type="code" language="python">def val(X,t):
928+ from math import exp
929+ T0 = 288.15 # K
930+ R = 287.058 # Specific gas constant in J/Kg
931+ g = 9.8 # m/s**2
932+ h = X[0] # m
933+ p0 = 101325
934+ e = T0*1406.0
935+ gamma = 1.33
936+ p = p0*exp(-(g*h)/((gamma-1.0)*e))
937+ rho = p/((gamma-1.0)*e)
938+ return rho</string_value>
939+ </python>
940+ </initial_condition>
941+ <boundary_conditions name="Left">
942+ <surface_ids>
943+ <integer_value shape="1" rank="1">1</integer_value>
944+ </surface_ids>
945+ <type name="dirichlet">
946+ <constant>
947+ <real_value rank="0">0.181985215</real_value>
948+ </constant>
949+ </type>
950+ </boundary_conditions>
951+ <output/>
952+ <stat/>
953+ <convergence>
954+ <include_in_convergence/>
955+ </convergence>
956+ <detectors>
957+ <include_in_detectors/>
958+ </detectors>
959+ <steady_state>
960+ <include_in_steady_state/>
961+ </steady_state>
962+ <consistent_interpolation/>
963+ </prognostic>
964+ </scalar_field>
965+ <vector_field name="Velocity" rank="1">
966+ <prognostic>
967+ <mesh name="VelocityMesh"/>
968+ <equation name="LinearMomentum"/>
969+ <spatial_discretisation>
970+ <discontinuous_galerkin>
971+ <viscosity_scheme>
972+ <compact_discontinuous_galerkin/>
973+ <tensor_form/>
974+ </viscosity_scheme>
975+ <advection_scheme>
976+ <upwind/>
977+ <integrate_advection_by_parts>
978+ <twice/>
979+ </integrate_advection_by_parts>
980+ </advection_scheme>
981+ </discontinuous_galerkin>
982+ <conservative_advection>
983+ <real_value rank="0">0</real_value>
984+ </conservative_advection>
985+ </spatial_discretisation>
986+ <temporal_discretisation>
987+ <theta>
988+ <real_value rank="0">1.0</real_value>
989+ </theta>
990+ <relaxation>
991+ <real_value rank="0">0.5</real_value>
992+ </relaxation>
993+ </temporal_discretisation>
994+ <solver>
995+ <iterative_method name="gmres">
996+ <restart>
997+ <integer_value rank="0">30</integer_value>
998+ </restart>
999+ </iterative_method>
1000+ <preconditioner name="sor"/>
1001+ <relative_error>
1002+ <real_value rank="0">1.0e-7</real_value>
1003+ </relative_error>
1004+ <max_iterations>
1005+ <integer_value rank="0">1000</integer_value>
1006+ </max_iterations>
1007+ <never_ignore_solver_failures/>
1008+ <diagnostics>
1009+ <monitors/>
1010+ </diagnostics>
1011+ </solver>
1012+ <initial_condition name="WholeMesh">
1013+ <constant>
1014+ <real_value shape="1" dim1="dim" rank="1">0</real_value>
1015+ </constant>
1016+ </initial_condition>
1017+ <boundary_conditions name="Left">
1018+ <surface_ids>
1019+ <integer_value shape="1" rank="1">1</integer_value>
1020+ </surface_ids>
1021+ <type name="dirichlet">
1022+ <align_bc_with_cartesian>
1023+ <x_component>
1024+ <constant>
1025+ <real_value rank="0">300</real_value>
1026+ </constant>
1027+ </x_component>
1028+ </align_bc_with_cartesian>
1029+ </type>
1030+ </boundary_conditions>
1031+ <tensor_field name="Viscosity" rank="2">
1032+ <prescribed>
1033+ <value name="WholeMesh">
1034+ <anisotropic_asymmetric>
1035+ <constant>
1036+ <real_value symmetric="false" dim2="dim" shape="1 1" dim1="dim" rank="2">1.85e-5</real_value>
1037+ </constant>
1038+ </anisotropic_asymmetric>
1039+ </value>
1040+ <output/>
1041+ </prescribed>
1042+ </tensor_field>
1043+ <output/>
1044+ <stat>
1045+ <include_in_stat/>
1046+ <previous_time_step>
1047+ <exclude_from_stat/>
1048+ </previous_time_step>
1049+ <nonlinear_field>
1050+ <exclude_from_stat/>
1051+ </nonlinear_field>
1052+ </stat>
1053+ <convergence>
1054+ <include_in_convergence/>
1055+ </convergence>
1056+ <detectors>
1057+ <include_in_detectors/>
1058+ </detectors>
1059+ <steady_state>
1060+ <include_in_steady_state/>
1061+ </steady_state>
1062+ <consistent_interpolation/>
1063+ </prognostic>
1064+ </vector_field>
1065+ <scalar_field name="CFLNumber" rank="0">
1066+ <diagnostic>
1067+ <algorithm name="Internal" material_phase_support="multiple"/>
1068+ <mesh name="VelocityMesh"/>
1069+ <output/>
1070+ <stat/>
1071+ <convergence>
1072+ <include_in_convergence/>
1073+ </convergence>
1074+ <detectors>
1075+ <include_in_detectors/>
1076+ </detectors>
1077+ <steady_state>
1078+ <include_in_steady_state/>
1079+ </steady_state>
1080+ </diagnostic>
1081+ </scalar_field>
1082+ <scalar_field name="InternalEnergy" rank="0">
1083+ <prognostic>
1084+ <mesh name="PressureMesh"/>
1085+ <equation name="InternalEnergy">
1086+ <density name="Density"/>
1087+ </equation>
1088+ <spatial_discretisation>
1089+ <control_volumes>
1090+ <face_value name="FirstOrderUpwind"/>
1091+ <diffusion_scheme name="BassiRebay"/>
1092+ </control_volumes>
1093+ <conservative_advection>
1094+ <real_value rank="0">0.0</real_value>
1095+ </conservative_advection>
1096+ </spatial_discretisation>
1097+ <temporal_discretisation>
1098+ <theta>
1099+ <real_value rank="0">1.0</real_value>
1100+ </theta>
1101+ </temporal_discretisation>
1102+ <solver>
1103+ <iterative_method name="gmres">
1104+ <restart>
1105+ <integer_value rank="0">30</integer_value>
1106+ </restart>
1107+ </iterative_method>
1108+ <preconditioner name="sor"/>
1109+ <relative_error>
1110+ <real_value rank="0">1.0e-7</real_value>
1111+ </relative_error>
1112+ <max_iterations>
1113+ <integer_value rank="0">1000</integer_value>
1114+ </max_iterations>
1115+ <never_ignore_solver_failures/>
1116+ <diagnostics>
1117+ <monitors/>
1118+ </diagnostics>
1119+ </solver>
1120+ <initial_condition name="WholeMesh">
1121+ <constant>
1122+ <real_value rank="0">405138.9</real_value>
1123+ </constant>
1124+ </initial_condition>
1125+ <boundary_conditions name="Left">
1126+ <surface_ids>
1127+ <integer_value shape="1" rank="1">1</integer_value>
1128+ </surface_ids>
1129+ <type name="dirichlet">
1130+ <constant>
1131+ <real_value rank="0">1687200</real_value>
1132+ </constant>
1133+ </type>
1134+ </boundary_conditions>
1135+ <output/>
1136+ <stat/>
1137+ <convergence>
1138+ <include_in_convergence/>
1139+ </convergence>
1140+ <detectors>
1141+ <include_in_detectors/>
1142+ </detectors>
1143+ <steady_state>
1144+ <include_in_steady_state/>
1145+ </steady_state>
1146+ <consistent_interpolation/>
1147+ </prognostic>
1148+ </scalar_field>
1149+ <scalar_field name="HydrostaticReferencePressure" rank="0">
1150+ <prescribed>
1151+ <mesh name="PressureMesh"/>
1152+ <value name="WholeMesh">
1153+ <python>
1154+ <string_value lines="20" type="code" language="python">def val(X,t):
1155+ from math import exp
1156+ T0 = 288.15 # K
1157+ R = 287.058 # Specific gas constant in J/Kg
1158+ g = 9.8 # m/s**2
1159+ h = X[0] # m
1160+ p0 = 101325
1161+ e = T0*1406.0
1162+ gamma = 1.33
1163+ p = p0*exp(-(g*h)/((gamma-1.0)*e))
1164+ return p</string_value>
1165+ </python>
1166+ </value>
1167+ <output/>
1168+ <stat/>
1169+ <detectors>
1170+ <exclude_from_detectors/>
1171+ </detectors>
1172+ </prescribed>
1173+ </scalar_field>
1174+ <scalar_field name="HydrostaticReferenceDensity" rank="0">
1175+ <prescribed>
1176+ <mesh name="PressureMesh"/>
1177+ <value name="WholeMesh">
1178+ <python>
1179+ <string_value lines="20" type="code" language="python">def val(X,t):
1180+ from math import exp
1181+ T0 = 288.15 # K
1182+ R = 287.058 # Specific gas constant in J/Kg
1183+ g = 9.8 # m/s**2
1184+ h = X[0] # m
1185+ p0 = 101325
1186+ e = T0*1406.0
1187+ gamma = 1.33
1188+ p = p0*exp(-(g*h)/((gamma-1.0)*e))
1189+ rho = p/((gamma-1.0)*e)
1190+ return rho</string_value>
1191+ </python>
1192+ </value>
1193+ <output/>
1194+ <stat/>
1195+ <detectors>
1196+ <exclude_from_detectors/>
1197+ </detectors>
1198+ </prescribed>
1199+ </scalar_field>
1200+ </material_phase>
1201+</fluidity_options>
1202
1203=== added directory 'tests/inlet_velocity_bc_compressible_without_gravity'
1204=== added file 'tests/inlet_velocity_bc_compressible_without_gravity/Makefile'
1205--- tests/inlet_velocity_bc_compressible_without_gravity/Makefile 1970-01-01 00:00:00 +0000
1206+++ tests/inlet_velocity_bc_compressible_without_gravity/Makefile 2013-07-10 19:09:26 +0000
1207@@ -0,0 +1,21 @@
1208+preprocess:
1209+ @echo **********Creating 1D mesh
1210+ ../../bin/interval --dx=100.0 -- 0.0 10000.0 line
1211+ @echo **********Creating 2D mesh
1212+ gmsh -2 -o inlet_velocity_bc_compressible_without_gravity_pseudo1d.msh src/inlet_velocity_bc_compressible_without_gravity_pseudo1d.geo
1213+ ../../bin/gmsh2triangle --2d inlet_velocity_bc_compressible_without_gravity_pseudo1d.msh
1214+
1215+run:
1216+ @echo **********Running simulation
1217+ ../../bin/fluidity inlet_velocity_bc_compressible_without_gravity_1d.flml
1218+ ../../bin/fluidity inlet_velocity_bc_compressible_without_gravity_pseudo1d.flml
1219+
1220+input: clean preprocess
1221+
1222+clean:
1223+ rm -f *.stat *.steady_state*
1224+ rm -f *.d.* *.vtu
1225+ rm -f *.msh
1226+ rm -f *.ele *.edge *.node *.poly *.bound
1227+ rm -f matrixdump* *.log* *.err*
1228+
1229
1230=== added file 'tests/inlet_velocity_bc_compressible_without_gravity/inlet_velocity_bc_compressible_without_gravity.xml'
1231--- tests/inlet_velocity_bc_compressible_without_gravity/inlet_velocity_bc_compressible_without_gravity.xml 1970-01-01 00:00:00 +0000
1232+++ tests/inlet_velocity_bc_compressible_without_gravity/inlet_velocity_bc_compressible_without_gravity.xml 2013-07-10 19:09:26 +0000
1233@@ -0,0 +1,95 @@
1234+<?xml version="1.0" encoding="UTF-8" ?>
1235+<!DOCTYPE testproblem SYSTEM "regressiontest.dtd">
1236+
1237+<testproblem>
1238+
1239+ <name>inlet_velocity_bc_compressible_without_gravity</name>
1240+ <owner userid="ctj10"/>
1241+ <tags>flml</tags>
1242+
1243+ <problem_definition length="medium" nprocs="1">
1244+ <command_line>make run</command_line>
1245+ </problem_definition>
1246+
1247+ <variables>
1248+ <variable name="gas_velocity_max_1d" language="python">
1249+from fluidity_tools import stat_parser
1250+s = stat_parser("inlet_velocity_bc_compressible_without_gravity_1d.stat")
1251+gas_velocity_max_1d = s["Gas"]["Velocity%magnitude"]["max"][-1]
1252+ </variable>
1253+
1254+ <variable name="gas_velocity_min_1d" language="python">
1255+from fluidity_tools import stat_parser
1256+s = stat_parser("inlet_velocity_bc_compressible_without_gravity_1d.stat")
1257+gas_velocity_min_1d = s["Gas"]["Velocity%magnitude"]["min"][-1]
1258+ </variable>
1259+
1260+ <variable name="gas_velocity_max_pseudo1d" language="python">
1261+from fluidity_tools import stat_parser
1262+s = stat_parser("inlet_velocity_bc_compressible_without_gravity_pseudo1d.stat")
1263+gas_velocity_max_pseudo1d = s["Gas"]["Velocity%magnitude"]["max"][-1]
1264+ </variable>
1265+
1266+ <variable name="gas_velocity_min_pseudo1d" language="python">
1267+from fluidity_tools import stat_parser
1268+s = stat_parser("inlet_velocity_bc_compressible_without_gravity_pseudo1d.stat")
1269+gas_velocity_min_pseudo1d = s["Gas"]["Velocity%magnitude"]["min"][-1]
1270+ </variable>
1271+
1272+ <variable name="gas_density_max_1d" language="python">
1273+from fluidity_tools import stat_parser
1274+s = stat_parser("inlet_velocity_bc_compressible_without_gravity_1d.stat")
1275+gas_density_max_1d = s["Gas"]["Density"]["max"][-1]
1276+ </variable>
1277+
1278+ <variable name="gas_density_min_1d" language="python">
1279+from fluidity_tools import stat_parser
1280+s = stat_parser("inlet_velocity_bc_compressible_without_gravity_1d.stat")
1281+gas_density_min_1d = s["Gas"]["Density"]["min"][-1]
1282+ </variable>
1283+
1284+ <variable name="gas_density_max_pseudo1d" language="python">
1285+from fluidity_tools import stat_parser
1286+s = stat_parser("inlet_velocity_bc_compressible_without_gravity_pseudo1d.stat")
1287+gas_density_max_pseudo1d = s["Gas"]["Density"]["max"][-1]
1288+ </variable>
1289+
1290+ <variable name="gas_density_min_pseudo1d" language="python">
1291+from fluidity_tools import stat_parser
1292+s = stat_parser("inlet_velocity_bc_compressible_without_gravity_pseudo1d.stat")
1293+gas_density_min_pseudo1d = s["Gas"]["Density"]["min"][-1]
1294+ </variable>
1295+
1296+ <variable name="solvers_converged" language="python">
1297+import os
1298+files = os.listdir("./")
1299+solvers_converged = not "matrixdump" in files and not "matrixdump.info" in files
1300+ </variable>
1301+ </variables>
1302+
1303+ <pass_tests>
1304+ <test name="Gas::Velocity is 300 m/s everywhere in the 1D test case" language="python">
1305+assert(abs(gas_velocity_max_1d - 300) &lt; 1 and abs(gas_velocity_min_1d - 300) &lt; 1)
1306+ </test>
1307+
1308+ <test name="Gas::Velocity is 300 m/s everywhere in the pseudo-1D test case" language="python">
1309+assert(abs(gas_velocity_max_pseudo1d - 300) &lt; 1 and abs(gas_velocity_min_pseudo1d - 300) &lt; 1)
1310+ </test>
1311+
1312+ <test name="Gas::Density is 0.181985215 kg/m^3 everywhere in the 1D test case" language="python">
1313+assert(abs(gas_density_max_1d - 0.181985215) &lt; 1e-2 and abs(gas_density_min_1d - 0.181985215) &lt; 1e-2)
1314+ </test>
1315+
1316+ <test name="Gas::Density is 0.181985215 kg/m^3 everywhere in the pseudo-1D test case" language="python">
1317+assert(abs(gas_density_max_pseudo1d - 0.181985215) &lt; 1e-2 and abs(gas_density_min_pseudo1d - 0.181985215) &lt; 1e-2)
1318+ </test>
1319+
1320+ <test name="Solvers converged" language="python">
1321+assert(solvers_converged)
1322+ </test>
1323+ </pass_tests>
1324+
1325+ <warn_tests>
1326+ </warn_tests>
1327+
1328+</testproblem>
1329
1330=== added file 'tests/inlet_velocity_bc_compressible_without_gravity/inlet_velocity_bc_compressible_without_gravity_1d.flml'
1331--- tests/inlet_velocity_bc_compressible_without_gravity/inlet_velocity_bc_compressible_without_gravity_1d.flml 1970-01-01 00:00:00 +0000
1332+++ tests/inlet_velocity_bc_compressible_without_gravity/inlet_velocity_bc_compressible_without_gravity_1d.flml 2013-07-10 19:09:26 +0000
1333@@ -0,0 +1,436 @@
1334+<?xml version='1.0' encoding='utf-8'?>
1335+<fluidity_options>
1336+ <simulation_name>
1337+ <string_value lines="1">inlet_velocity_bc_compressible_without_gravity_1d</string_value>
1338+ </simulation_name>
1339+ <problem_type>
1340+ <string_value lines="1">fluids</string_value>
1341+ </problem_type>
1342+ <geometry>
1343+ <dimension>
1344+ <integer_value rank="0">1</integer_value>
1345+ </dimension>
1346+ <mesh name="CoordinateMesh">
1347+ <from_file file_name="line">
1348+ <format name="triangle"/>
1349+ <stat>
1350+ <include_in_stat/>
1351+ </stat>
1352+ </from_file>
1353+ </mesh>
1354+ <mesh name="VelocityMesh">
1355+ <from_mesh>
1356+ <mesh name="CoordinateMesh"/>
1357+ <mesh_shape>
1358+ <polynomial_degree>
1359+ <integer_value rank="0">0</integer_value>
1360+ </polynomial_degree>
1361+ </mesh_shape>
1362+ <mesh_continuity>
1363+ <string_value>discontinuous</string_value>
1364+ </mesh_continuity>
1365+ <stat>
1366+ <exclude_from_stat/>
1367+ </stat>
1368+ </from_mesh>
1369+ </mesh>
1370+ <mesh name="PressureMesh">
1371+ <from_mesh>
1372+ <mesh name="CoordinateMesh"/>
1373+ <mesh_shape>
1374+ <polynomial_degree>
1375+ <integer_value rank="0">1</integer_value>
1376+ </polynomial_degree>
1377+ </mesh_shape>
1378+ <stat>
1379+ <exclude_from_stat/>
1380+ </stat>
1381+ </from_mesh>
1382+ </mesh>
1383+ <mesh name="DensityMesh">
1384+ <from_mesh>
1385+ <mesh name="CoordinateMesh"/>
1386+ <mesh_shape>
1387+ <polynomial_degree>
1388+ <integer_value rank="0">1</integer_value>
1389+ </polynomial_degree>
1390+ </mesh_shape>
1391+ <stat>
1392+ <exclude_from_stat/>
1393+ </stat>
1394+ </from_mesh>
1395+ </mesh>
1396+ <mesh name="GeostrophicMesh">
1397+ <from_mesh>
1398+ <mesh name="CoordinateMesh"/>
1399+ <mesh_shape>
1400+ <polynomial_degree>
1401+ <integer_value rank="0">1</integer_value>
1402+ </polynomial_degree>
1403+ </mesh_shape>
1404+ <stat>
1405+ <exclude_from_stat/>
1406+ </stat>
1407+ </from_mesh>
1408+ </mesh>
1409+ <quadrature>
1410+ <degree>
1411+ <integer_value rank="0">4</integer_value>
1412+ </degree>
1413+ </quadrature>
1414+ </geometry>
1415+ <io>
1416+ <dump_format>
1417+ <string_value>vtk</string_value>
1418+ </dump_format>
1419+ <dump_period>
1420+ <constant>
1421+ <real_value rank="0">10.0</real_value>
1422+ </constant>
1423+ </dump_period>
1424+ <output_mesh name="PressureMesh"/>
1425+ <stat>
1426+ <output_at_start/>
1427+ </stat>
1428+ </io>
1429+ <timestepping>
1430+ <current_time>
1431+ <real_value rank="0">0</real_value>
1432+ </current_time>
1433+ <timestep>
1434+ <real_value rank="0">0.01</real_value>
1435+ </timestep>
1436+ <finish_time>
1437+ <real_value rank="0">600.0</real_value>
1438+ </finish_time>
1439+ <nonlinear_iterations>
1440+ <integer_value rank="0">2</integer_value>
1441+ <tolerance>
1442+ <real_value rank="0">1.0e-9</real_value>
1443+ <infinity_norm/>
1444+ </tolerance>
1445+ </nonlinear_iterations>
1446+ <adaptive_timestep>
1447+ <requested_cfl>
1448+ <real_value rank="0">0.5</real_value>
1449+ </requested_cfl>
1450+ <courant_number name="CFLNumber">
1451+ <mesh name="VelocityMesh"/>
1452+ </courant_number>
1453+ <minimum_timestep>
1454+ <real_value rank="0">0.001</real_value>
1455+ </minimum_timestep>
1456+ <increase_tolerance>
1457+ <real_value rank="0">1.1</real_value>
1458+ </increase_tolerance>
1459+ </adaptive_timestep>
1460+ <steady_state>
1461+ <tolerance>
1462+ <real_value rank="0">1.0e-6</real_value>
1463+ <infinity_norm/>
1464+ </tolerance>
1465+ </steady_state>
1466+ </timestepping>
1467+ <material_phase name="Gas">
1468+ <equation_of_state>
1469+ <compressible>
1470+ <stiffened_gas>
1471+ <ratio_specific_heats>
1472+ <real_value rank="0">1.33</real_value>
1473+ </ratio_specific_heats>
1474+ </stiffened_gas>
1475+ </compressible>
1476+ </equation_of_state>
1477+ <scalar_field name="Pressure" rank="0">
1478+ <prognostic>
1479+ <mesh name="PressureMesh"/>
1480+ <spatial_discretisation>
1481+ <continuous_galerkin>
1482+ <remove_stabilisation_term/>
1483+ <integrate_continuity_by_parts/>
1484+ </continuous_galerkin>
1485+ </spatial_discretisation>
1486+ <scheme>
1487+ <poisson_pressure_solution>
1488+ <string_value lines="1">never</string_value>
1489+ </poisson_pressure_solution>
1490+ <use_compressible_projection_method/>
1491+ </scheme>
1492+ <solver>
1493+ <iterative_method name="gmres">
1494+ <restart>
1495+ <integer_value rank="0">30</integer_value>
1496+ </restart>
1497+ </iterative_method>
1498+ <preconditioner name="sor"/>
1499+ <relative_error>
1500+ <real_value rank="0">1.0e-7</real_value>
1501+ </relative_error>
1502+ <max_iterations>
1503+ <integer_value rank="0">1000</integer_value>
1504+ </max_iterations>
1505+ <never_ignore_solver_failures/>
1506+ <diagnostics>
1507+ <monitors/>
1508+ </diagnostics>
1509+ </solver>
1510+ <initial_condition name="WholeMesh">
1511+ <constant>
1512+ <real_value rank="0">101325</real_value>
1513+ </constant>
1514+ </initial_condition>
1515+ <boundary_conditions name="Right">
1516+ <surface_ids>
1517+ <integer_value shape="1" rank="1">2</integer_value>
1518+ </surface_ids>
1519+ <type name="dirichlet">
1520+ <constant>
1521+ <real_value rank="0">101325</real_value>
1522+ </constant>
1523+ </type>
1524+ </boundary_conditions>
1525+ <output/>
1526+ <stat/>
1527+ <convergence>
1528+ <include_in_convergence/>
1529+ </convergence>
1530+ <detectors>
1531+ <exclude_from_detectors/>
1532+ </detectors>
1533+ <steady_state>
1534+ <include_in_steady_state/>
1535+ </steady_state>
1536+ <no_interpolation/>
1537+ </prognostic>
1538+ </scalar_field>
1539+ <scalar_field name="Density" rank="0">
1540+ <prognostic>
1541+ <mesh name="DensityMesh"/>
1542+ <spatial_discretisation>
1543+ <control_volumes>
1544+ <face_value name="FirstOrderUpwind"/>
1545+ </control_volumes>
1546+ <conservative_advection>
1547+ <real_value rank="0">1.0</real_value>
1548+ </conservative_advection>
1549+ </spatial_discretisation>
1550+ <temporal_discretisation>
1551+ <theta>
1552+ <real_value rank="0">1.0</real_value>
1553+ </theta>
1554+ </temporal_discretisation>
1555+ <initial_condition name="WholeMesh">
1556+ <constant>
1557+ <real_value rank="0">0.757877001</real_value>
1558+ </constant>
1559+ </initial_condition>
1560+ <boundary_conditions name="Left">
1561+ <surface_ids>
1562+ <integer_value shape="1" rank="1">1</integer_value>
1563+ </surface_ids>
1564+ <type name="dirichlet">
1565+ <constant>
1566+ <real_value rank="0">0.181985215</real_value>
1567+ </constant>
1568+ </type>
1569+ </boundary_conditions>
1570+ <output/>
1571+ <stat/>
1572+ <convergence>
1573+ <include_in_convergence/>
1574+ </convergence>
1575+ <detectors>
1576+ <include_in_detectors/>
1577+ </detectors>
1578+ <steady_state>
1579+ <include_in_steady_state/>
1580+ </steady_state>
1581+ <consistent_interpolation/>
1582+ </prognostic>
1583+ </scalar_field>
1584+ <vector_field name="Velocity" rank="1">
1585+ <prognostic>
1586+ <mesh name="VelocityMesh"/>
1587+ <equation name="LinearMomentum"/>
1588+ <spatial_discretisation>
1589+ <discontinuous_galerkin>
1590+ <viscosity_scheme>
1591+ <compact_discontinuous_galerkin/>
1592+ <tensor_form/>
1593+ </viscosity_scheme>
1594+ <advection_scheme>
1595+ <upwind/>
1596+ <integrate_advection_by_parts>
1597+ <twice/>
1598+ </integrate_advection_by_parts>
1599+ </advection_scheme>
1600+ </discontinuous_galerkin>
1601+ <conservative_advection>
1602+ <real_value rank="0">0</real_value>
1603+ </conservative_advection>
1604+ </spatial_discretisation>
1605+ <temporal_discretisation>
1606+ <theta>
1607+ <real_value rank="0">1.0</real_value>
1608+ </theta>
1609+ <relaxation>
1610+ <real_value rank="0">0.5</real_value>
1611+ </relaxation>
1612+ </temporal_discretisation>
1613+ <solver>
1614+ <iterative_method name="gmres">
1615+ <restart>
1616+ <integer_value rank="0">30</integer_value>
1617+ </restart>
1618+ </iterative_method>
1619+ <preconditioner name="sor"/>
1620+ <relative_error>
1621+ <real_value rank="0">1.0e-7</real_value>
1622+ </relative_error>
1623+ <max_iterations>
1624+ <integer_value rank="0">1000</integer_value>
1625+ </max_iterations>
1626+ <never_ignore_solver_failures/>
1627+ <diagnostics>
1628+ <monitors/>
1629+ </diagnostics>
1630+ </solver>
1631+ <initial_condition name="WholeMesh">
1632+ <constant>
1633+ <real_value shape="1" dim1="dim" rank="1">0</real_value>
1634+ </constant>
1635+ </initial_condition>
1636+ <boundary_conditions name="Left">
1637+ <surface_ids>
1638+ <integer_value shape="1" rank="1">1</integer_value>
1639+ </surface_ids>
1640+ <type name="dirichlet">
1641+ <align_bc_with_cartesian>
1642+ <x_component>
1643+ <constant>
1644+ <real_value rank="0">300</real_value>
1645+ </constant>
1646+ </x_component>
1647+ </align_bc_with_cartesian>
1648+ </type>
1649+ </boundary_conditions>
1650+ <tensor_field name="Viscosity" rank="2">
1651+ <prescribed>
1652+ <value name="WholeMesh">
1653+ <isotropic>
1654+ <constant>
1655+ <real_value rank="0">1.85e-5</real_value>
1656+ </constant>
1657+ </isotropic>
1658+ </value>
1659+ <output/>
1660+ </prescribed>
1661+ </tensor_field>
1662+ <output/>
1663+ <stat>
1664+ <include_in_stat/>
1665+ <previous_time_step>
1666+ <exclude_from_stat/>
1667+ </previous_time_step>
1668+ <nonlinear_field>
1669+ <exclude_from_stat/>
1670+ </nonlinear_field>
1671+ </stat>
1672+ <convergence>
1673+ <include_in_convergence/>
1674+ </convergence>
1675+ <detectors>
1676+ <include_in_detectors/>
1677+ </detectors>
1678+ <steady_state>
1679+ <include_in_steady_state/>
1680+ </steady_state>
1681+ <consistent_interpolation/>
1682+ </prognostic>
1683+ </vector_field>
1684+ <scalar_field name="CFLNumber" rank="0">
1685+ <diagnostic>
1686+ <algorithm name="Internal" material_phase_support="multiple"/>
1687+ <mesh name="VelocityMesh"/>
1688+ <output/>
1689+ <stat/>
1690+ <convergence>
1691+ <include_in_convergence/>
1692+ </convergence>
1693+ <detectors>
1694+ <include_in_detectors/>
1695+ </detectors>
1696+ <steady_state>
1697+ <include_in_steady_state/>
1698+ </steady_state>
1699+ </diagnostic>
1700+ </scalar_field>
1701+ <scalar_field name="InternalEnergy" rank="0">
1702+ <prognostic>
1703+ <mesh name="PressureMesh"/>
1704+ <equation name="InternalEnergy">
1705+ <density name="Density"/>
1706+ </equation>
1707+ <spatial_discretisation>
1708+ <control_volumes>
1709+ <face_value name="FirstOrderUpwind"/>
1710+ <diffusion_scheme name="BassiRebay"/>
1711+ </control_volumes>
1712+ <conservative_advection>
1713+ <real_value rank="0">0.0</real_value>
1714+ </conservative_advection>
1715+ </spatial_discretisation>
1716+ <temporal_discretisation>
1717+ <theta>
1718+ <real_value rank="0">1.0</real_value>
1719+ </theta>
1720+ </temporal_discretisation>
1721+ <solver>
1722+ <iterative_method name="gmres">
1723+ <restart>
1724+ <integer_value rank="0">30</integer_value>
1725+ </restart>
1726+ </iterative_method>
1727+ <preconditioner name="sor"/>
1728+ <relative_error>
1729+ <real_value rank="0">1.0e-7</real_value>
1730+ </relative_error>
1731+ <max_iterations>
1732+ <integer_value rank="0">1000</integer_value>
1733+ </max_iterations>
1734+ <never_ignore_solver_failures/>
1735+ <diagnostics>
1736+ <monitors/>
1737+ </diagnostics>
1738+ </solver>
1739+ <initial_condition name="WholeMesh">
1740+ <constant>
1741+ <real_value rank="0">405138.9</real_value>
1742+ </constant>
1743+ </initial_condition>
1744+ <boundary_conditions name="Left">
1745+ <surface_ids>
1746+ <integer_value shape="1" rank="1">1</integer_value>
1747+ </surface_ids>
1748+ <type name="dirichlet">
1749+ <constant>
1750+ <real_value rank="0">1687200</real_value>
1751+ </constant>
1752+ </type>
1753+ </boundary_conditions>
1754+ <output/>
1755+ <stat/>
1756+ <convergence>
1757+ <include_in_convergence/>
1758+ </convergence>
1759+ <detectors>
1760+ <include_in_detectors/>
1761+ </detectors>
1762+ <steady_state>
1763+ <include_in_steady_state/>
1764+ </steady_state>
1765+ <consistent_interpolation/>
1766+ </prognostic>
1767+ </scalar_field>
1768+ </material_phase>
1769+</fluidity_options>
1770
1771=== added file 'tests/inlet_velocity_bc_compressible_without_gravity/inlet_velocity_bc_compressible_without_gravity_pseudo1d.flml'
1772--- tests/inlet_velocity_bc_compressible_without_gravity/inlet_velocity_bc_compressible_without_gravity_pseudo1d.flml 1970-01-01 00:00:00 +0000
1773+++ tests/inlet_velocity_bc_compressible_without_gravity/inlet_velocity_bc_compressible_without_gravity_pseudo1d.flml 2013-07-10 19:09:26 +0000
1774@@ -0,0 +1,430 @@
1775+<?xml version='1.0' encoding='utf-8'?>
1776+<fluidity_options>
1777+ <simulation_name>
1778+ <string_value lines="1">inlet_velocity_bc_compressible_without_gravity_pseudo1d</string_value>
1779+ </simulation_name>
1780+ <problem_type>
1781+ <string_value lines="1">fluids</string_value>
1782+ </problem_type>
1783+ <geometry>
1784+ <dimension>
1785+ <integer_value rank="0">2</integer_value>
1786+ </dimension>
1787+ <mesh name="CoordinateMesh">
1788+ <from_file file_name="inlet_velocity_bc_compressible_without_gravity_pseudo1d">
1789+ <format name="triangle"/>
1790+ <stat>
1791+ <include_in_stat/>
1792+ </stat>
1793+ </from_file>
1794+ </mesh>
1795+ <mesh name="VelocityMesh">
1796+ <from_mesh>
1797+ <mesh name="CoordinateMesh"/>
1798+ <mesh_shape>
1799+ <polynomial_degree>
1800+ <integer_value rank="0">2</integer_value>
1801+ </polynomial_degree>
1802+ </mesh_shape>
1803+ <stat>
1804+ <exclude_from_stat/>
1805+ </stat>
1806+ </from_mesh>
1807+ </mesh>
1808+ <mesh name="PressureMesh">
1809+ <from_mesh>
1810+ <mesh name="CoordinateMesh"/>
1811+ <mesh_shape>
1812+ <polynomial_degree>
1813+ <integer_value rank="0">1</integer_value>
1814+ </polynomial_degree>
1815+ </mesh_shape>
1816+ <stat>
1817+ <exclude_from_stat/>
1818+ </stat>
1819+ </from_mesh>
1820+ </mesh>
1821+ <quadrature>
1822+ <degree>
1823+ <integer_value rank="0">4</integer_value>
1824+ </degree>
1825+ </quadrature>
1826+ </geometry>
1827+ <io>
1828+ <dump_format>
1829+ <string_value>vtk</string_value>
1830+ </dump_format>
1831+ <dump_period>
1832+ <constant>
1833+ <real_value rank="0">10.0</real_value>
1834+ </constant>
1835+ </dump_period>
1836+ <output_mesh name="VelocityMesh"/>
1837+ <stat>
1838+ <output_at_start/>
1839+ </stat>
1840+ </io>
1841+ <timestepping>
1842+ <current_time>
1843+ <real_value rank="0">0</real_value>
1844+ </current_time>
1845+ <timestep>
1846+ <real_value rank="0">0.001</real_value>
1847+ </timestep>
1848+ <finish_time>
1849+ <real_value rank="0">600.0</real_value>
1850+ </finish_time>
1851+ <nonlinear_iterations>
1852+ <integer_value rank="0">2</integer_value>
1853+ <tolerance>
1854+ <real_value rank="0">1.0e-7</real_value>
1855+ <infinity_norm/>
1856+ </tolerance>
1857+ </nonlinear_iterations>
1858+ <adaptive_timestep>
1859+ <requested_cfl>
1860+ <real_value rank="0">0.5</real_value>
1861+ </requested_cfl>
1862+ <courant_number name="CFLNumber">
1863+ <mesh name="VelocityMesh"/>
1864+ </courant_number>
1865+ <minimum_timestep>
1866+ <real_value rank="0">0.001</real_value>
1867+ </minimum_timestep>
1868+ <increase_tolerance>
1869+ <real_value rank="0">1.1</real_value>
1870+ </increase_tolerance>
1871+ </adaptive_timestep>
1872+ <steady_state>
1873+ <tolerance>
1874+ <real_value rank="0">1.0e-6</real_value>
1875+ <infinity_norm/>
1876+ </tolerance>
1877+ </steady_state>
1878+ </timestepping>
1879+ <material_phase name="Gas">
1880+ <equation_of_state>
1881+ <compressible>
1882+ <stiffened_gas>
1883+ <ratio_specific_heats>
1884+ <real_value rank="0">1.33</real_value>
1885+ </ratio_specific_heats>
1886+ </stiffened_gas>
1887+ </compressible>
1888+ </equation_of_state>
1889+ <scalar_field name="Pressure" rank="0">
1890+ <prognostic>
1891+ <mesh name="PressureMesh"/>
1892+ <spatial_discretisation>
1893+ <continuous_galerkin>
1894+ <remove_stabilisation_term/>
1895+ <integrate_continuity_by_parts/>
1896+ </continuous_galerkin>
1897+ </spatial_discretisation>
1898+ <scheme>
1899+ <poisson_pressure_solution>
1900+ <string_value lines="1">never</string_value>
1901+ </poisson_pressure_solution>
1902+ <use_compressible_projection_method/>
1903+ </scheme>
1904+ <solver>
1905+ <iterative_method name="gmres">
1906+ <restart>
1907+ <integer_value rank="0">30</integer_value>
1908+ </restart>
1909+ </iterative_method>
1910+ <preconditioner name="sor"/>
1911+ <relative_error>
1912+ <real_value rank="0">1.0e-7</real_value>
1913+ </relative_error>
1914+ <max_iterations>
1915+ <integer_value rank="0">1000</integer_value>
1916+ </max_iterations>
1917+ <never_ignore_solver_failures/>
1918+ <diagnostics>
1919+ <monitors/>
1920+ </diagnostics>
1921+ </solver>
1922+ <initial_condition name="WholeMesh">
1923+ <constant>
1924+ <real_value rank="0">101325</real_value>
1925+ </constant>
1926+ </initial_condition>
1927+ <boundary_conditions name="Top">
1928+ <surface_ids>
1929+ <integer_value shape="1" rank="1">333</integer_value>
1930+ </surface_ids>
1931+ <type name="dirichlet">
1932+ <constant>
1933+ <real_value rank="0">101325</real_value>
1934+ </constant>
1935+ </type>
1936+ </boundary_conditions>
1937+ <output/>
1938+ <stat/>
1939+ <convergence>
1940+ <include_in_convergence/>
1941+ </convergence>
1942+ <detectors>
1943+ <exclude_from_detectors/>
1944+ </detectors>
1945+ <steady_state>
1946+ <include_in_steady_state/>
1947+ </steady_state>
1948+ <no_interpolation/>
1949+ </prognostic>
1950+ </scalar_field>
1951+ <scalar_field name="Density" rank="0">
1952+ <prognostic>
1953+ <mesh name="PressureMesh"/>
1954+ <spatial_discretisation>
1955+ <control_volumes>
1956+ <face_value name="FirstOrderUpwind"/>
1957+ </control_volumes>
1958+ <conservative_advection>
1959+ <real_value rank="0">1.0</real_value>
1960+ </conservative_advection>
1961+ </spatial_discretisation>
1962+ <temporal_discretisation>
1963+ <theta>
1964+ <real_value rank="0">1.0</real_value>
1965+ </theta>
1966+ </temporal_discretisation>
1967+ <initial_condition name="WholeMesh">
1968+ <constant>
1969+ <real_value rank="0">0.757877001</real_value>
1970+ </constant>
1971+ </initial_condition>
1972+ <boundary_conditions name="Vent">
1973+ <surface_ids>
1974+ <integer_value shape="1" rank="1">999</integer_value>
1975+ </surface_ids>
1976+ <type name="dirichlet">
1977+ <constant>
1978+ <real_value rank="0">0.181985215</real_value>
1979+ </constant>
1980+ </type>
1981+ </boundary_conditions>
1982+ <output/>
1983+ <stat/>
1984+ <convergence>
1985+ <include_in_convergence/>
1986+ </convergence>
1987+ <detectors>
1988+ <include_in_detectors/>
1989+ </detectors>
1990+ <steady_state>
1991+ <include_in_steady_state/>
1992+ </steady_state>
1993+ <consistent_interpolation/>
1994+ </prognostic>
1995+ </scalar_field>
1996+ <vector_field name="Velocity" rank="1">
1997+ <prognostic>
1998+ <mesh name="VelocityMesh"/>
1999+ <equation name="LinearMomentum"/>
2000+ <spatial_discretisation>
2001+ <continuous_galerkin>
2002+ <stabilisation>
2003+ <streamline_upwind>
2004+ <nu_bar_optimal/>
2005+ <nu_scale name="0.5">
2006+ <real_value shape="1" rank="0">0.5</real_value>
2007+ </nu_scale>
2008+ </streamline_upwind>
2009+ </stabilisation>
2010+ <mass_terms>
2011+ <lump_mass_matrix>
2012+ <use_submesh/>
2013+ </lump_mass_matrix>
2014+ </mass_terms>
2015+ <advection_terms/>
2016+ <stress_terms>
2017+ <stress_form/>
2018+ </stress_terms>
2019+ </continuous_galerkin>
2020+ <conservative_advection>
2021+ <real_value rank="0">0.0</real_value>
2022+ </conservative_advection>
2023+ </spatial_discretisation>
2024+ <temporal_discretisation>
2025+ <theta>
2026+ <real_value rank="0">1.0</real_value>
2027+ </theta>
2028+ <relaxation>
2029+ <real_value rank="0">0.5</real_value>
2030+ </relaxation>
2031+ </temporal_discretisation>
2032+ <solver>
2033+ <iterative_method name="gmres">
2034+ <restart>
2035+ <integer_value rank="0">30</integer_value>
2036+ </restart>
2037+ </iterative_method>
2038+ <preconditioner name="sor"/>
2039+ <relative_error>
2040+ <real_value rank="0">1.0e-7</real_value>
2041+ </relative_error>
2042+ <max_iterations>
2043+ <integer_value rank="0">1000</integer_value>
2044+ </max_iterations>
2045+ <never_ignore_solver_failures/>
2046+ <diagnostics>
2047+ <monitors/>
2048+ </diagnostics>
2049+ </solver>
2050+ <initial_condition name="WholeMesh">
2051+ <constant>
2052+ <real_value shape="2" dim1="dim" rank="1">0.0 0.0</real_value>
2053+ </constant>
2054+ </initial_condition>
2055+ <boundary_conditions name="Vent">
2056+ <surface_ids>
2057+ <integer_value shape="1" rank="1">999</integer_value>
2058+ </surface_ids>
2059+ <type name="dirichlet">
2060+ <align_bc_with_cartesian>
2061+ <x_component>
2062+ <constant>
2063+ <real_value rank="0">0.0</real_value>
2064+ </constant>
2065+ </x_component>
2066+ <y_component>
2067+ <constant>
2068+ <real_value rank="0">300</real_value>
2069+ </constant>
2070+ </y_component>
2071+ </align_bc_with_cartesian>
2072+ </type>
2073+ </boundary_conditions>
2074+ <boundary_conditions name="Left">
2075+ <surface_ids>
2076+ <integer_value shape="1" rank="1">111</integer_value>
2077+ </surface_ids>
2078+ <type name="dirichlet">
2079+ <align_bc_with_cartesian>
2080+ <x_component>
2081+ <constant>
2082+ <real_value rank="0">0</real_value>
2083+ </constant>
2084+ </x_component>
2085+ </align_bc_with_cartesian>
2086+ </type>
2087+ </boundary_conditions>
2088+ <boundary_conditions name="Right">
2089+ <surface_ids>
2090+ <integer_value shape="1" rank="1">222</integer_value>
2091+ </surface_ids>
2092+ <type name="dirichlet">
2093+ <align_bc_with_cartesian>
2094+ <x_component>
2095+ <constant>
2096+ <real_value rank="0">0</real_value>
2097+ </constant>
2098+ </x_component>
2099+ </align_bc_with_cartesian>
2100+ </type>
2101+ </boundary_conditions>
2102+ <tensor_field name="Viscosity" rank="2">
2103+ <prescribed>
2104+ <value name="WholeMesh">
2105+ <anisotropic_asymmetric>
2106+ <constant>
2107+ <real_value symmetric="false" dim2="dim" shape="2 2" dim1="dim" rank="2">1.85e-5 1.85e-5 1.85e-5 1.85e-5</real_value>
2108+ </constant>
2109+ </anisotropic_asymmetric>
2110+ </value>
2111+ <output/>
2112+ </prescribed>
2113+ </tensor_field>
2114+ <output/>
2115+ <stat>
2116+ <include_in_stat/>
2117+ <previous_time_step>
2118+ <exclude_from_stat/>
2119+ </previous_time_step>
2120+ <nonlinear_field>
2121+ <exclude_from_stat/>
2122+ </nonlinear_field>
2123+ </stat>
2124+ <convergence>
2125+ <include_in_convergence/>
2126+ </convergence>
2127+ <detectors>
2128+ <include_in_detectors/>
2129+ </detectors>
2130+ <steady_state>
2131+ <include_in_steady_state/>
2132+ </steady_state>
2133+ <consistent_interpolation/>
2134+ </prognostic>
2135+ </vector_field>
2136+ <scalar_field name="InternalEnergy" rank="0">
2137+ <prognostic>
2138+ <mesh name="PressureMesh"/>
2139+ <equation name="InternalEnergy">
2140+ <density name="Density"/>
2141+ </equation>
2142+ <spatial_discretisation>
2143+ <control_volumes>
2144+ <face_value name="FirstOrderUpwind"/>
2145+ <diffusion_scheme name="BassiRebay"/>
2146+ </control_volumes>
2147+ <conservative_advection>
2148+ <real_value rank="0">0.0</real_value>
2149+ </conservative_advection>
2150+ </spatial_discretisation>
2151+ <temporal_discretisation>
2152+ <theta>
2153+ <real_value rank="0">1.0</real_value>
2154+ </theta>
2155+ </temporal_discretisation>
2156+ <solver>
2157+ <iterative_method name="gmres">
2158+ <restart>
2159+ <integer_value rank="0">30</integer_value>
2160+ </restart>
2161+ </iterative_method>
2162+ <preconditioner name="sor"/>
2163+ <relative_error>
2164+ <real_value rank="0">1.0e-7</real_value>
2165+ </relative_error>
2166+ <max_iterations>
2167+ <integer_value rank="0">1000</integer_value>
2168+ </max_iterations>
2169+ <never_ignore_solver_failures/>
2170+ <diagnostics>
2171+ <monitors/>
2172+ </diagnostics>
2173+ </solver>
2174+ <initial_condition name="WholeMesh">
2175+ <constant>
2176+ <real_value rank="0">405138.9</real_value>
2177+ </constant>
2178+ </initial_condition>
2179+ <boundary_conditions name="Vent">
2180+ <surface_ids>
2181+ <integer_value shape="1" rank="1">999</integer_value>
2182+ </surface_ids>
2183+ <type name="dirichlet">
2184+ <constant>
2185+ <real_value rank="0">1687200</real_value>
2186+ </constant>
2187+ </type>
2188+ </boundary_conditions>
2189+ <output/>
2190+ <stat/>
2191+ <convergence>
2192+ <include_in_convergence/>
2193+ </convergence>
2194+ <detectors>
2195+ <include_in_detectors/>
2196+ </detectors>
2197+ <steady_state>
2198+ <include_in_steady_state/>
2199+ </steady_state>
2200+ <consistent_interpolation/>
2201+ </prognostic>
2202+ </scalar_field>
2203+ </material_phase>
2204+</fluidity_options>
2205
2206=== added directory 'tests/inlet_velocity_bc_compressible_without_gravity/src'
2207=== added file 'tests/inlet_velocity_bc_compressible_without_gravity/src/inlet_velocity_bc_compressible_without_gravity_pseudo1d.geo'
2208--- tests/inlet_velocity_bc_compressible_without_gravity/src/inlet_velocity_bc_compressible_without_gravity_pseudo1d.geo 1970-01-01 00:00:00 +0000
2209+++ tests/inlet_velocity_bc_compressible_without_gravity/src/inlet_velocity_bc_compressible_without_gravity_pseudo1d.geo 2013-07-10 19:09:26 +0000
2210@@ -0,0 +1,19 @@
2211+dx = 100.0;
2212+Point(1) = {0.0, 0.0, 0.0, dx};
2213+
2214+Extrude {dx,0,0} {
2215+ Point{1}; Layers{dx/dx};
2216+}
2217+Extrude {0,10000,0} {
2218+ Line{1}; Layers{10000/dx};
2219+}
2220+
2221+// Top
2222+Physical Line(333) = {2};
2223+// Sides
2224+Physical Line(111) = {3};
2225+Physical Line(222) = {4};
2226+// Bottom
2227+Physical Line(999) = {1};
2228+
2229+Physical Surface(1000) = {5};
2230
2231=== added directory 'tests/inlet_velocity_bc_incompressible'
2232=== added file 'tests/inlet_velocity_bc_incompressible/Makefile'
2233--- tests/inlet_velocity_bc_incompressible/Makefile 1970-01-01 00:00:00 +0000
2234+++ tests/inlet_velocity_bc_incompressible/Makefile 2013-07-10 19:09:26 +0000
2235@@ -0,0 +1,17 @@
2236+preprocess:
2237+ @echo **********Creating 1D mesh
2238+ ../../bin/interval --dx=100.0 -- 0.0 10000.0 line
2239+
2240+run:
2241+ @echo **********Running simulation
2242+ ../../bin/fluidity -v2 -l inlet_velocity_bc_incompressible.flml
2243+
2244+input: clean preprocess
2245+
2246+clean:
2247+ rm -f *.stat *.steady_state*
2248+ rm -f *.d.* *.vtu
2249+ rm -f *.msh
2250+ rm -f *.ele *.edge *.node *.poly *.bound
2251+ rm -f matrixdump* *.log* *.err*
2252+
2253
2254=== added file 'tests/inlet_velocity_bc_incompressible/inlet_velocity_bc_incompressible.flml'
2255--- tests/inlet_velocity_bc_incompressible/inlet_velocity_bc_incompressible.flml 1970-01-01 00:00:00 +0000
2256+++ tests/inlet_velocity_bc_incompressible/inlet_velocity_bc_incompressible.flml 2013-07-10 19:09:26 +0000
2257@@ -0,0 +1,381 @@
2258+<?xml version='1.0' encoding='utf-8'?>
2259+<fluidity_options>
2260+ <simulation_name>
2261+ <string_value lines="1">inlet_velocity_bc_incompressible</string_value>
2262+ </simulation_name>
2263+ <problem_type>
2264+ <string_value lines="1">fluids</string_value>
2265+ </problem_type>
2266+ <geometry>
2267+ <dimension>
2268+ <integer_value rank="0">1</integer_value>
2269+ </dimension>
2270+ <mesh name="CoordinateMesh">
2271+ <from_file file_name="line">
2272+ <format name="triangle"/>
2273+ <stat>
2274+ <include_in_stat/>
2275+ </stat>
2276+ </from_file>
2277+ </mesh>
2278+ <mesh name="VelocityMesh">
2279+ <from_mesh>
2280+ <mesh name="CoordinateMesh"/>
2281+ <mesh_shape>
2282+ <polynomial_degree>
2283+ <integer_value rank="0">2</integer_value>
2284+ </polynomial_degree>
2285+ </mesh_shape>
2286+ <stat>
2287+ <exclude_from_stat/>
2288+ </stat>
2289+ </from_mesh>
2290+ </mesh>
2291+ <mesh name="PressureMesh">
2292+ <from_mesh>
2293+ <mesh name="CoordinateMesh"/>
2294+ <mesh_shape>
2295+ <polynomial_degree>
2296+ <integer_value rank="0">1</integer_value>
2297+ </polynomial_degree>
2298+ </mesh_shape>
2299+ <stat>
2300+ <exclude_from_stat/>
2301+ </stat>
2302+ </from_mesh>
2303+ </mesh>
2304+ <mesh name="DensityMesh">
2305+ <from_mesh>
2306+ <mesh name="CoordinateMesh"/>
2307+ <mesh_shape>
2308+ <polynomial_degree>
2309+ <integer_value rank="0">1</integer_value>
2310+ </polynomial_degree>
2311+ </mesh_shape>
2312+ <stat>
2313+ <exclude_from_stat/>
2314+ </stat>
2315+ </from_mesh>
2316+ </mesh>
2317+ <mesh name="GeostrophicMesh">
2318+ <from_mesh>
2319+ <mesh name="CoordinateMesh"/>
2320+ <mesh_shape>
2321+ <polynomial_degree>
2322+ <integer_value rank="0">1</integer_value>
2323+ </polynomial_degree>
2324+ </mesh_shape>
2325+ <stat>
2326+ <exclude_from_stat/>
2327+ </stat>
2328+ </from_mesh>
2329+ </mesh>
2330+ <quadrature>
2331+ <degree>
2332+ <integer_value rank="0">4</integer_value>
2333+ </degree>
2334+ </quadrature>
2335+ </geometry>
2336+ <io>
2337+ <dump_format>
2338+ <string_value>vtk</string_value>
2339+ </dump_format>
2340+ <dump_period>
2341+ <constant>
2342+ <real_value rank="0">0</real_value>
2343+ </constant>
2344+ </dump_period>
2345+ <output_mesh name="PressureMesh"/>
2346+ <stat>
2347+ <output_at_start/>
2348+ </stat>
2349+ </io>
2350+ <timestepping>
2351+ <current_time>
2352+ <real_value rank="0">0</real_value>
2353+ </current_time>
2354+ <timestep>
2355+ <real_value rank="0">0.01</real_value>
2356+ </timestep>
2357+ <finish_time>
2358+ <real_value rank="0">20.0</real_value>
2359+ </finish_time>
2360+ <nonlinear_iterations>
2361+ <integer_value rank="0">2</integer_value>
2362+ <tolerance>
2363+ <real_value rank="0">1.0e-9</real_value>
2364+ <infinity_norm/>
2365+ </tolerance>
2366+ </nonlinear_iterations>
2367+ <adaptive_timestep>
2368+ <requested_cfl>
2369+ <real_value rank="0">0.25</real_value>
2370+ </requested_cfl>
2371+ <courant_number name="CFLNumber">
2372+ <mesh name="VelocityMesh"/>
2373+ </courant_number>
2374+ <minimum_timestep>
2375+ <real_value rank="0">0.001</real_value>
2376+ </minimum_timestep>
2377+ <increase_tolerance>
2378+ <real_value rank="0">1.1</real_value>
2379+ </increase_tolerance>
2380+ </adaptive_timestep>
2381+ </timestepping>
2382+ <physical_parameters>
2383+ <gravity>
2384+ <magnitude>
2385+ <real_value rank="0">9.8</real_value>
2386+ </magnitude>
2387+ <vector_field name="GravityDirection" rank="1">
2388+ <prescribed>
2389+ <mesh name="CoordinateMesh"/>
2390+ <value name="WholeMesh">
2391+ <constant>
2392+ <real_value shape="1" dim1="dim" rank="1">-1</real_value>
2393+ </constant>
2394+ </value>
2395+ <output/>
2396+ <stat>
2397+ <include_in_stat/>
2398+ </stat>
2399+ <detectors>
2400+ <exclude_from_detectors/>
2401+ </detectors>
2402+ </prescribed>
2403+ </vector_field>
2404+ </gravity>
2405+ </physical_parameters>
2406+ <material_phase name="Gas">
2407+ <equation_of_state>
2408+ <fluids>
2409+ <linear>
2410+ <reference_density>
2411+ <real_value rank="0">1.23</real_value>
2412+ </reference_density>
2413+ </linear>
2414+ </fluids>
2415+ </equation_of_state>
2416+ <scalar_field name="Pressure" rank="0">
2417+ <prognostic>
2418+ <mesh name="PressureMesh"/>
2419+ <spatial_discretisation>
2420+ <continuous_galerkin>
2421+ <remove_stabilisation_term/>
2422+ <integrate_continuity_by_parts/>
2423+ </continuous_galerkin>
2424+ </spatial_discretisation>
2425+ <scheme>
2426+ <poisson_pressure_solution>
2427+ <string_value lines="1">never</string_value>
2428+ </poisson_pressure_solution>
2429+ <use_compressible_projection_method/>
2430+ </scheme>
2431+ <solver>
2432+ <iterative_method name="gmres">
2433+ <restart>
2434+ <integer_value rank="0">30</integer_value>
2435+ </restart>
2436+ </iterative_method>
2437+ <preconditioner name="sor"/>
2438+ <relative_error>
2439+ <real_value rank="0">1.0e-7</real_value>
2440+ </relative_error>
2441+ <max_iterations>
2442+ <integer_value rank="0">1000</integer_value>
2443+ </max_iterations>
2444+ <never_ignore_solver_failures/>
2445+ <diagnostics>
2446+ <monitors/>
2447+ </diagnostics>
2448+ </solver>
2449+ <initial_condition name="WholeMesh">
2450+ <python>
2451+ <string_value lines="20" type="code" language="python">def val(X,t):
2452+ from math import exp
2453+ T0 = 288.15 # K
2454+ R = 287.058 # Specific gas constant in J/Kg
2455+ g = 9.8 # m/s**2
2456+ h = X[0] # m
2457+ p0 = 101325
2458+ e = T0*1406.0
2459+ gamma = 1.33
2460+ p = 101325 - 1.23*g*h
2461+ return p</string_value>
2462+ </python>
2463+ </initial_condition>
2464+ <boundary_conditions name="Right">
2465+ <surface_ids>
2466+ <integer_value shape="1" rank="1">2</integer_value>
2467+ </surface_ids>
2468+ <type name="dirichlet">
2469+ <python>
2470+ <string_value lines="20" type="code" language="python">def val(X,t):
2471+ from math import exp
2472+ T0 = 288.15 # K
2473+ R = 287.058 # Specific gas constant in J/Kg
2474+ g = 9.8 # m/s**2
2475+ h = X[0] # m
2476+ p0 = 101325
2477+ e = T0*1406.0
2478+ gamma = 1.33
2479+ p = 101325 - 1.23*g*h
2480+ return p</string_value>
2481+ </python>
2482+ </type>
2483+ </boundary_conditions>
2484+ <output/>
2485+ <stat/>
2486+ <convergence>
2487+ <include_in_convergence/>
2488+ </convergence>
2489+ <detectors>
2490+ <exclude_from_detectors/>
2491+ </detectors>
2492+ <steady_state>
2493+ <include_in_steady_state/>
2494+ </steady_state>
2495+ <no_interpolation/>
2496+ </prognostic>
2497+ </scalar_field>
2498+ <scalar_field name="Density" rank="0">
2499+ <diagnostic>
2500+ <algorithm name="Internal" material_phase_support="multiple"/>
2501+ <mesh name="PressureMesh"/>
2502+ <output/>
2503+ <stat/>
2504+ <convergence>
2505+ <include_in_convergence/>
2506+ </convergence>
2507+ <detectors>
2508+ <include_in_detectors/>
2509+ </detectors>
2510+ <steady_state>
2511+ <include_in_steady_state/>
2512+ </steady_state>
2513+ </diagnostic>
2514+ </scalar_field>
2515+ <vector_field name="Velocity" rank="1">
2516+ <prognostic>
2517+ <mesh name="VelocityMesh"/>
2518+ <equation name="LinearMomentum"/>
2519+ <spatial_discretisation>
2520+ <continuous_galerkin>
2521+ <stabilisation>
2522+ <streamline_upwind>
2523+ <nu_bar_optimal/>
2524+ <nu_scale name="0.5">
2525+ <real_value shape="1" rank="0">0.5</real_value>
2526+ </nu_scale>
2527+ </streamline_upwind>
2528+ </stabilisation>
2529+ <mass_terms>
2530+ <lump_mass_matrix/>
2531+ </mass_terms>
2532+ <advection_terms/>
2533+ <stress_terms>
2534+ <stress_form/>
2535+ </stress_terms>
2536+ </continuous_galerkin>
2537+ <conservative_advection>
2538+ <real_value rank="0">0</real_value>
2539+ </conservative_advection>
2540+ </spatial_discretisation>
2541+ <temporal_discretisation>
2542+ <theta>
2543+ <real_value rank="0">1.0</real_value>
2544+ </theta>
2545+ <relaxation>
2546+ <real_value rank="0">0.5</real_value>
2547+ </relaxation>
2548+ </temporal_discretisation>
2549+ <solver>
2550+ <iterative_method name="gmres">
2551+ <restart>
2552+ <integer_value rank="0">30</integer_value>
2553+ </restart>
2554+ </iterative_method>
2555+ <preconditioner name="sor"/>
2556+ <relative_error>
2557+ <real_value rank="0">1.0e-7</real_value>
2558+ </relative_error>
2559+ <max_iterations>
2560+ <integer_value rank="0">1000</integer_value>
2561+ </max_iterations>
2562+ <never_ignore_solver_failures/>
2563+ <diagnostics>
2564+ <monitors/>
2565+ </diagnostics>
2566+ </solver>
2567+ <initial_condition name="WholeMesh">
2568+ <constant>
2569+ <real_value shape="1" dim1="dim" rank="1">0</real_value>
2570+ </constant>
2571+ </initial_condition>
2572+ <boundary_conditions name="Left">
2573+ <surface_ids>
2574+ <integer_value shape="1" rank="1">1</integer_value>
2575+ </surface_ids>
2576+ <type name="dirichlet">
2577+ <align_bc_with_cartesian>
2578+ <x_component>
2579+ <constant>
2580+ <real_value rank="0">300</real_value>
2581+ </constant>
2582+ </x_component>
2583+ </align_bc_with_cartesian>
2584+ </type>
2585+ </boundary_conditions>
2586+ <tensor_field name="Viscosity" rank="2">
2587+ <prescribed>
2588+ <value name="WholeMesh">
2589+ <anisotropic_asymmetric>
2590+ <constant>
2591+ <real_value symmetric="false" dim2="dim" shape="1 1" dim1="dim" rank="2">1.85e-5</real_value>
2592+ </constant>
2593+ </anisotropic_asymmetric>
2594+ </value>
2595+ <output/>
2596+ </prescribed>
2597+ </tensor_field>
2598+ <output/>
2599+ <stat>
2600+ <include_in_stat/>
2601+ <previous_time_step>
2602+ <exclude_from_stat/>
2603+ </previous_time_step>
2604+ <nonlinear_field>
2605+ <exclude_from_stat/>
2606+ </nonlinear_field>
2607+ </stat>
2608+ <convergence>
2609+ <include_in_convergence/>
2610+ </convergence>
2611+ <detectors>
2612+ <include_in_detectors/>
2613+ </detectors>
2614+ <steady_state>
2615+ <include_in_steady_state/>
2616+ </steady_state>
2617+ <consistent_interpolation/>
2618+ </prognostic>
2619+ </vector_field>
2620+ <scalar_field name="CFLNumber" rank="0">
2621+ <diagnostic>
2622+ <algorithm name="Internal" material_phase_support="multiple"/>
2623+ <mesh name="VelocityMesh"/>
2624+ <output/>
2625+ <stat/>
2626+ <convergence>
2627+ <include_in_convergence/>
2628+ </convergence>
2629+ <detectors>
2630+ <include_in_detectors/>
2631+ </detectors>
2632+ <steady_state>
2633+ <include_in_steady_state/>
2634+ </steady_state>
2635+ </diagnostic>
2636+ </scalar_field>
2637+ </material_phase>
2638+</fluidity_options>
2639
2640=== added file 'tests/inlet_velocity_bc_incompressible/inlet_velocity_bc_incompressible.xml'
2641--- tests/inlet_velocity_bc_incompressible/inlet_velocity_bc_incompressible.xml 1970-01-01 00:00:00 +0000
2642+++ tests/inlet_velocity_bc_incompressible/inlet_velocity_bc_incompressible.xml 2013-07-10 19:09:26 +0000
2643@@ -0,0 +1,47 @@
2644+<?xml version="1.0" encoding="UTF-8" ?>
2645+<!DOCTYPE testproblem SYSTEM "regressiontest.dtd">
2646+
2647+<testproblem>
2648+
2649+ <name>inlet_velocity_bc_incompressible</name>
2650+ <owner userid="ctj10"/>
2651+ <tags>flml</tags>
2652+
2653+ <problem_definition length="short" nprocs="1">
2654+ <command_line>make run</command_line>
2655+ </problem_definition>
2656+
2657+ <variables>
2658+ <variable name="gas_velocity_max" language="python">
2659+from fluidity_tools import stat_parser
2660+s = stat_parser("inlet_velocity_bc_incompressible.stat")
2661+gas_velocity_max = s["Gas"]["Velocity%1"]["max"][-1]
2662+ </variable>
2663+
2664+ <variable name="gas_velocity_min" language="python">
2665+from fluidity_tools import stat_parser
2666+s = stat_parser("inlet_velocity_bc_incompressible.stat")
2667+gas_velocity_min = s["Gas"]["Velocity%1"]["min"][-1]
2668+ </variable>
2669+
2670+ <variable name="solvers_converged" language="python">
2671+import os
2672+files = os.listdir("./")
2673+solvers_converged = not "matrixdump" in files and not "matrixdump.info" in files
2674+ </variable>
2675+ </variables>
2676+
2677+ <pass_tests>
2678+ <test name="Gas::Velocity is 300 m/s everywhere" language="python">
2679+assert(abs(gas_velocity_max - 300) &lt; 1e-7 and abs(gas_velocity_min - 300) &lt; 1e-7)
2680+ </test>
2681+
2682+ <test name="Solvers converged" language="python">
2683+assert(solvers_converged)
2684+ </test>
2685+ </pass_tests>
2686+
2687+ <warn_tests>
2688+ </warn_tests>
2689+
2690+</testproblem>
2691
2692=== added directory 'tests/mphase_inlet_velocity_bc_compressible'
2693=== added file 'tests/mphase_inlet_velocity_bc_compressible/Makefile'
2694--- tests/mphase_inlet_velocity_bc_compressible/Makefile 1970-01-01 00:00:00 +0000
2695+++ tests/mphase_inlet_velocity_bc_compressible/Makefile 2013-07-10 19:09:26 +0000
2696@@ -0,0 +1,17 @@
2697+preprocess:
2698+ @echo **********Creating 1D mesh
2699+ ../../bin/interval --dx=1000.0 -- 0.0 10000.0 line
2700+
2701+run:
2702+ @echo **********Running simulation
2703+ ../../bin/fluidity mphase_inlet_velocity_bc_compressible.flml
2704+
2705+input: clean preprocess
2706+
2707+clean:
2708+ rm -f *.stat *.steady_state*
2709+ rm -f *.d.* *.vtu
2710+ rm -f *.msh
2711+ rm -f *.ele *.edge *.node *.poly *.bound
2712+ rm -f matrixdump* *.log* *.err*
2713+
2714
2715=== added file 'tests/mphase_inlet_velocity_bc_compressible/mphase_inlet_velocity_bc_compressible.flml'
2716--- tests/mphase_inlet_velocity_bc_compressible/mphase_inlet_velocity_bc_compressible.flml 1970-01-01 00:00:00 +0000
2717+++ tests/mphase_inlet_velocity_bc_compressible/mphase_inlet_velocity_bc_compressible.flml 2013-07-10 19:09:26 +0000
2718@@ -0,0 +1,863 @@
2719+<?xml version='1.0' encoding='utf-8'?>
2720+<fluidity_options>
2721+ <simulation_name>
2722+ <string_value lines="1">mphase_inlet_velocity_bc_compressible</string_value>
2723+ </simulation_name>
2724+ <problem_type>
2725+ <string_value lines="1">fluids</string_value>
2726+ </problem_type>
2727+ <geometry>
2728+ <dimension>
2729+ <integer_value rank="0">1</integer_value>
2730+ </dimension>
2731+ <mesh name="CoordinateMesh">
2732+ <from_file file_name="line">
2733+ <format name="triangle"/>
2734+ <stat>
2735+ <include_in_stat/>
2736+ </stat>
2737+ </from_file>
2738+ </mesh>
2739+ <mesh name="VelocityMesh">
2740+ <from_mesh>
2741+ <mesh name="CoordinateMesh"/>
2742+ <mesh_shape>
2743+ <polynomial_degree>
2744+ <integer_value rank="0">0</integer_value>
2745+ </polynomial_degree>
2746+ </mesh_shape>
2747+ <mesh_continuity>
2748+ <string_value>discontinuous</string_value>
2749+ </mesh_continuity>
2750+ <stat>
2751+ <exclude_from_stat/>
2752+ </stat>
2753+ </from_mesh>
2754+ </mesh>
2755+ <mesh name="PressureMesh">
2756+ <from_mesh>
2757+ <mesh name="CoordinateMesh"/>
2758+ <mesh_shape>
2759+ <polynomial_degree>
2760+ <integer_value rank="0">1</integer_value>
2761+ </polynomial_degree>
2762+ </mesh_shape>
2763+ <stat>
2764+ <exclude_from_stat/>
2765+ </stat>
2766+ </from_mesh>
2767+ </mesh>
2768+ <mesh name="DensityMesh">
2769+ <from_mesh>
2770+ <mesh name="CoordinateMesh"/>
2771+ <mesh_shape>
2772+ <polynomial_degree>
2773+ <integer_value rank="0">1</integer_value>
2774+ </polynomial_degree>
2775+ </mesh_shape>
2776+ <stat>
2777+ <exclude_from_stat/>
2778+ </stat>
2779+ </from_mesh>
2780+ </mesh>
2781+ <quadrature>
2782+ <degree>
2783+ <integer_value rank="0">3</integer_value>
2784+ </degree>
2785+ </quadrature>
2786+ </geometry>
2787+ <io>
2788+ <dump_format>
2789+ <string_value>vtk</string_value>
2790+ </dump_format>
2791+ <dump_period>
2792+ <constant>
2793+ <real_value rank="0">0</real_value>
2794+ </constant>
2795+ </dump_period>
2796+ <output_mesh name="PressureMesh"/>
2797+ <stat>
2798+ <output_at_start/>
2799+ </stat>
2800+ </io>
2801+ <timestepping>
2802+ <current_time>
2803+ <real_value rank="0">0</real_value>
2804+ </current_time>
2805+ <timestep>
2806+ <real_value rank="0">1.0</real_value>
2807+ </timestep>
2808+ <finish_time>
2809+ <real_value rank="0">100.0</real_value>
2810+ </finish_time>
2811+ <nonlinear_iterations>
2812+ <integer_value rank="0">50</integer_value>
2813+ <tolerance>
2814+ <real_value rank="0">1.0e-4</real_value>
2815+ <infinity_norm/>
2816+ </tolerance>
2817+ </nonlinear_iterations>
2818+ </timestepping>
2819+ <physical_parameters>
2820+ <gravity>
2821+ <magnitude>
2822+ <real_value rank="0">9.8</real_value>
2823+ </magnitude>
2824+ <vector_field name="GravityDirection" rank="1">
2825+ <prescribed>
2826+ <mesh name="CoordinateMesh"/>
2827+ <value name="WholeMesh">
2828+ <constant>
2829+ <real_value shape="1" dim1="dim" rank="1">-1.0</real_value>
2830+ </constant>
2831+ </value>
2832+ <output/>
2833+ <stat>
2834+ <include_in_stat/>
2835+ </stat>
2836+ <detectors>
2837+ <exclude_from_detectors/>
2838+ </detectors>
2839+ </prescribed>
2840+ </vector_field>
2841+ </gravity>
2842+ </physical_parameters>
2843+ <material_phase name="Gas">
2844+ <equation_of_state>
2845+ <compressible>
2846+ <stiffened_gas>
2847+ <ratio_specific_heats>
2848+ <real_value rank="0">1.33</real_value>
2849+ </ratio_specific_heats>
2850+ </stiffened_gas>
2851+ <subtract_out_reference_profile/>
2852+ </compressible>
2853+ </equation_of_state>
2854+ <scalar_field name="Pressure" rank="0">
2855+ <prognostic>
2856+ <mesh name="PressureMesh"/>
2857+ <spatial_discretisation>
2858+ <continuous_galerkin>
2859+ <remove_stabilisation_term/>
2860+ <integrate_continuity_by_parts/>
2861+ </continuous_galerkin>
2862+ </spatial_discretisation>
2863+ <scheme>
2864+ <poisson_pressure_solution>
2865+ <string_value lines="1">never</string_value>
2866+ </poisson_pressure_solution>
2867+ <use_compressible_projection_method/>
2868+ </scheme>
2869+ <solver>
2870+ <iterative_method name="gmres">
2871+ <restart>
2872+ <integer_value rank="0">30</integer_value>
2873+ </restart>
2874+ </iterative_method>
2875+ <preconditioner name="sor"/>
2876+ <relative_error>
2877+ <real_value rank="0">1.0e-7</real_value>
2878+ </relative_error>
2879+ <max_iterations>
2880+ <integer_value rank="0">1000</integer_value>
2881+ </max_iterations>
2882+ <never_ignore_solver_failures/>
2883+ <diagnostics>
2884+ <monitors/>
2885+ </diagnostics>
2886+ </solver>
2887+ <initial_condition name="WholeMesh">
2888+ <python>
2889+ <string_value lines="20" type="code" language="python">def val(X,t):
2890+ from math import exp
2891+ T0 = 288.15 # K
2892+ R = 287.058 # Specific gas constant in J/Kg
2893+ g = 9.8 # m/s**2
2894+ h = X[0] # m
2895+ p0 = 101325
2896+ e = T0*1406.0
2897+ gamma = 1.33
2898+ p = p0*exp(-(g*h)/((gamma-1.0)*e))
2899+ return p</string_value>
2900+ </python>
2901+ </initial_condition>
2902+ <boundary_conditions name="Right">
2903+ <surface_ids>
2904+ <integer_value shape="1" rank="1">2</integer_value>
2905+ </surface_ids>
2906+ <type name="dirichlet">
2907+ <python>
2908+ <string_value lines="20" type="code" language="python">def val(X,t):
2909+ from math import exp
2910+ T0 = 288.15 # K
2911+ R = 287.058 # Specific gas constant in J/Kg
2912+ g = 9.8 # m/s**2
2913+ h = X[0] # m
2914+ p0 = 101325
2915+ e = T0*1406.0
2916+ gamma = 1.33
2917+ p = p0*exp(-(g*h)/((gamma-1.0)*e))
2918+ return p</string_value>
2919+ </python>
2920+ </type>
2921+ </boundary_conditions>
2922+ <boundary_conditions name="Left">
2923+ <surface_ids>
2924+ <integer_value shape="1" rank="1">1</integer_value>
2925+ </surface_ids>
2926+ <type name="dirichlet">
2927+ <constant>
2928+ <real_value rank="0">101325</real_value>
2929+ </constant>
2930+ </type>
2931+ </boundary_conditions>
2932+ <output/>
2933+ <stat/>
2934+ <convergence>
2935+ <include_in_convergence/>
2936+ </convergence>
2937+ <detectors>
2938+ <exclude_from_detectors/>
2939+ </detectors>
2940+ <steady_state>
2941+ <include_in_steady_state/>
2942+ </steady_state>
2943+ <no_interpolation/>
2944+ </prognostic>
2945+ </scalar_field>
2946+ <scalar_field name="Density" rank="0">
2947+ <prognostic>
2948+ <mesh name="DensityMesh"/>
2949+ <spatial_discretisation>
2950+ <control_volumes>
2951+ <face_value name="FirstOrderUpwind"/>
2952+ </control_volumes>
2953+ <conservative_advection>
2954+ <real_value rank="0">1.0</real_value>
2955+ </conservative_advection>
2956+ </spatial_discretisation>
2957+ <temporal_discretisation>
2958+ <theta>
2959+ <real_value rank="0">1.0</real_value>
2960+ </theta>
2961+ </temporal_discretisation>
2962+ <initial_condition name="WholeMesh">
2963+ <python>
2964+ <string_value lines="20" type="code" language="python">def val(X,t):
2965+ from math import exp
2966+ T0 = 288.15 # K
2967+ R = 287.058 # Specific gas constant in J/Kg
2968+ g = 9.8 # m/s**2
2969+ h = X[0] # m
2970+ p0 = 101325
2971+ e = T0*1406.0
2972+ gamma = 1.33
2973+ p = p0*exp(-(g*h)/((gamma-1.0)*e))
2974+ rho = p/((gamma-1.0)*e)
2975+ return rho</string_value>
2976+ </python>
2977+ </initial_condition>
2978+ <boundary_conditions name="Left">
2979+ <surface_ids>
2980+ <integer_value shape="1" rank="1">1</integer_value>
2981+ </surface_ids>
2982+ <type name="dirichlet">
2983+ <constant>
2984+ <real_value rank="0">0.181985215</real_value>
2985+ </constant>
2986+ </type>
2987+ </boundary_conditions>
2988+ <output/>
2989+ <stat/>
2990+ <convergence>
2991+ <include_in_convergence/>
2992+ </convergence>
2993+ <detectors>
2994+ <include_in_detectors/>
2995+ </detectors>
2996+ <steady_state>
2997+ <include_in_steady_state/>
2998+ </steady_state>
2999+ <consistent_interpolation/>
3000+ </prognostic>
3001+ </scalar_field>
3002+ <vector_field name="Velocity" rank="1">
3003+ <prognostic>
3004+ <mesh name="VelocityMesh"/>
3005+ <equation name="LinearMomentum"/>
3006+ <spatial_discretisation>
3007+ <discontinuous_galerkin>
3008+ <viscosity_scheme>
3009+ <compact_discontinuous_galerkin/>
3010+ <tensor_form/>
3011+ </viscosity_scheme>
3012+ <advection_scheme>
3013+ <upwind/>
3014+ <integrate_advection_by_parts>
3015+ <twice/>
3016+ </integrate_advection_by_parts>
3017+ </advection_scheme>
3018+ </discontinuous_galerkin>
3019+ <conservative_advection>
3020+ <real_value rank="0">0</real_value>
3021+ </conservative_advection>
3022+ </spatial_discretisation>
3023+ <temporal_discretisation>
3024+ <theta>
3025+ <real_value rank="0">1.0</real_value>
3026+ </theta>
3027+ <relaxation>
3028+ <real_value rank="0">0.5</real_value>
3029+ </relaxation>
3030+ </temporal_discretisation>
3031+ <solver>
3032+ <iterative_method name="gmres">
3033+ <restart>
3034+ <integer_value rank="0">30</integer_value>
3035+ </restart>
3036+ </iterative_method>
3037+ <preconditioner name="sor"/>
3038+ <relative_error>
3039+ <real_value rank="0">1.0e-7</real_value>
3040+ </relative_error>
3041+ <max_iterations>
3042+ <integer_value rank="0">1000</integer_value>
3043+ </max_iterations>
3044+ <never_ignore_solver_failures/>
3045+ <diagnostics>
3046+ <monitors/>
3047+ </diagnostics>
3048+ </solver>
3049+ <initial_condition name="WholeMesh">
3050+ <constant>
3051+ <real_value shape="1" dim1="dim" rank="1">0</real_value>
3052+ </constant>
3053+ </initial_condition>
3054+ <boundary_conditions name="Left">
3055+ <surface_ids>
3056+ <integer_value shape="1" rank="1">1</integer_value>
3057+ </surface_ids>
3058+ <type name="dirichlet">
3059+ <align_bc_with_cartesian>
3060+ <x_component>
3061+ <constant>
3062+ <real_value rank="0">300</real_value>
3063+ </constant>
3064+ </x_component>
3065+ </align_bc_with_cartesian>
3066+ </type>
3067+ </boundary_conditions>
3068+ <tensor_field name="Viscosity" rank="2">
3069+ <prescribed>
3070+ <value name="WholeMesh">
3071+ <anisotropic_asymmetric>
3072+ <constant>
3073+ <real_value symmetric="false" dim2="dim" shape="1 1" dim1="dim" rank="2">1.85e-5</real_value>
3074+ </constant>
3075+ </anisotropic_asymmetric>
3076+ </value>
3077+ <output/>
3078+ </prescribed>
3079+ </tensor_field>
3080+ <output/>
3081+ <stat>
3082+ <include_in_stat/>
3083+ <previous_time_step>
3084+ <exclude_from_stat/>
3085+ </previous_time_step>
3086+ <nonlinear_field>
3087+ <exclude_from_stat/>
3088+ </nonlinear_field>
3089+ </stat>
3090+ <convergence>
3091+ <include_in_convergence/>
3092+ </convergence>
3093+ <detectors>
3094+ <include_in_detectors/>
3095+ </detectors>
3096+ <steady_state>
3097+ <include_in_steady_state/>
3098+ </steady_state>
3099+ <consistent_interpolation/>
3100+ </prognostic>
3101+ </vector_field>
3102+ <scalar_field name="CFLNumber" rank="0">
3103+ <diagnostic>
3104+ <algorithm name="Internal" material_phase_support="multiple"/>
3105+ <mesh name="VelocityMesh"/>
3106+ <output/>
3107+ <stat/>
3108+ <convergence>
3109+ <include_in_convergence/>
3110+ </convergence>
3111+ <detectors>
3112+ <include_in_detectors/>
3113+ </detectors>
3114+ <steady_state>
3115+ <include_in_steady_state/>
3116+ </steady_state>
3117+ </diagnostic>
3118+ </scalar_field>
3119+ <scalar_field name="InternalEnergy" rank="0">
3120+ <prognostic>
3121+ <mesh name="PressureMesh"/>
3122+ <equation name="InternalEnergy">
3123+ <density name="Density">
3124+ <discretisation_options>
3125+ <spatial_discretisation>
3126+ <control_volumes>
3127+ <face_value name="FirstOrderUpwind"/>
3128+ </control_volumes>
3129+ </spatial_discretisation>
3130+ <temporal_discretisation>
3131+ <theta>
3132+ <real_value rank="0">1.0</real_value>
3133+ </theta>
3134+ <control_volumes/>
3135+ </temporal_discretisation>
3136+ </discretisation_options>
3137+ </density>
3138+ </equation>
3139+ <spatial_discretisation>
3140+ <control_volumes>
3141+ <face_value name="FirstOrderUpwind"/>
3142+ <diffusion_scheme name="ElementGradient"/>
3143+ </control_volumes>
3144+ <conservative_advection>
3145+ <real_value rank="0">0.0</real_value>
3146+ </conservative_advection>
3147+ </spatial_discretisation>
3148+ <temporal_discretisation>
3149+ <theta>
3150+ <real_value rank="0">1.0</real_value>
3151+ </theta>
3152+ </temporal_discretisation>
3153+ <solver>
3154+ <iterative_method name="gmres">
3155+ <restart>
3156+ <integer_value rank="0">30</integer_value>
3157+ </restart>
3158+ </iterative_method>
3159+ <preconditioner name="sor"/>
3160+ <relative_error>
3161+ <real_value rank="0">1.0e-7</real_value>
3162+ </relative_error>
3163+ <max_iterations>
3164+ <integer_value rank="0">1000</integer_value>
3165+ </max_iterations>
3166+ <never_ignore_solver_failures/>
3167+ <diagnostics>
3168+ <monitors/>
3169+ </diagnostics>
3170+ </solver>
3171+ <initial_condition name="WholeMesh">
3172+ <constant>
3173+ <real_value rank="0">405138.9</real_value>
3174+ </constant>
3175+ </initial_condition>
3176+ <boundary_conditions name="Left">
3177+ <surface_ids>
3178+ <integer_value shape="1" rank="1">1</integer_value>
3179+ </surface_ids>
3180+ <type name="dirichlet">
3181+ <constant>
3182+ <real_value rank="0">1687200</real_value>
3183+ </constant>
3184+ </type>
3185+ </boundary_conditions>
3186+ <output/>
3187+ <stat/>
3188+ <convergence>
3189+ <include_in_convergence/>
3190+ </convergence>
3191+ <detectors>
3192+ <include_in_detectors/>
3193+ </detectors>
3194+ <steady_state>
3195+ <include_in_steady_state/>
3196+ </steady_state>
3197+ <consistent_interpolation/>
3198+ </prognostic>
3199+ </scalar_field>
3200+ <scalar_field name="HydrostaticReferencePressure" rank="0">
3201+ <prescribed>
3202+ <mesh name="PressureMesh"/>
3203+ <value name="WholeMesh">
3204+ <python>
3205+ <string_value lines="20" type="code" language="python">def val(X,t):
3206+ from math import exp
3207+ T0 = 288.15 # K
3208+ R = 287.058 # Specific gas constant in J/Kg
3209+ g = 9.8 # m/s**2
3210+ h = X[0] # m
3211+ p0 = 101325
3212+ e = T0*1406.0
3213+ gamma = 1.33
3214+ p = p0*exp(-(g*h)/((gamma-1.0)*e))
3215+ return p</string_value>
3216+ </python>
3217+ </value>
3218+ <output/>
3219+ <stat/>
3220+ <detectors>
3221+ <exclude_from_detectors/>
3222+ </detectors>
3223+ </prescribed>
3224+ </scalar_field>
3225+ <scalar_field name="HydrostaticReferenceDensity" rank="0">
3226+ <prescribed>
3227+ <mesh name="PressureMesh"/>
3228+ <value name="WholeMesh">
3229+ <python>
3230+ <string_value lines="20" type="code" language="python">def val(X,t):
3231+ from math import exp
3232+ T0 = 288.15 # K
3233+ R = 287.058 # Specific gas constant in J/Kg
3234+ g = 9.8 # m/s**2
3235+ h = X[0] # m
3236+ p0 = 101325
3237+ e = T0*1406.0
3238+ gamma = 1.33
3239+ p = p0*exp(-(g*h)/((gamma-1.0)*e))
3240+ rho = p/((gamma-1.0)*e)
3241+ return rho</string_value>
3242+ </python>
3243+ </value>
3244+ <output/>
3245+ <stat/>
3246+ <detectors>
3247+ <exclude_from_detectors/>
3248+ </detectors>
3249+ </prescribed>
3250+ </scalar_field>
3251+ <scalar_field name="PhaseVolumeFraction" rank="0">
3252+ <diagnostic>
3253+ <mesh name="CoordinateMesh"/>
3254+ <algorithm name="Internal" material_phase_support="multiple"/>
3255+ <output/>
3256+ <stat/>
3257+ <detectors>
3258+ <include_in_detectors/>
3259+ </detectors>
3260+ </diagnostic>
3261+ </scalar_field>
3262+ <multiphase_properties>
3263+ <effective_conductivity>
3264+ <real_value rank="0">0.5</real_value>
3265+ </effective_conductivity>
3266+ <specific_heat>
3267+ <real_value rank="0">1406</real_value>
3268+ </specific_heat>
3269+ </multiphase_properties>
3270+ </material_phase>
3271+ <material_phase name="Particles">
3272+ <equation_of_state>
3273+ <fluids>
3274+ <linear>
3275+ <reference_density>
3276+ <real_value rank="0">2400</real_value>
3277+ </reference_density>
3278+ </linear>
3279+ </fluids>
3280+ </equation_of_state>
3281+ <scalar_field name="Pressure" rank="0">
3282+ <aliased material_phase_name="Gas" field_name="Pressure"/>
3283+ </scalar_field>
3284+ <scalar_field name="Density" rank="0">
3285+ <diagnostic>
3286+ <algorithm name="Internal" material_phase_support="multiple"/>
3287+ <mesh name="PressureMesh"/>
3288+ <output/>
3289+ <stat/>
3290+ <convergence>
3291+ <include_in_convergence/>
3292+ </convergence>
3293+ <detectors>
3294+ <include_in_detectors/>
3295+ </detectors>
3296+ <steady_state>
3297+ <include_in_steady_state/>
3298+ </steady_state>
3299+ </diagnostic>
3300+ </scalar_field>
3301+ <vector_field name="Velocity" rank="1">
3302+ <prognostic>
3303+ <mesh name="VelocityMesh"/>
3304+ <equation name="LinearMomentum"/>
3305+ <spatial_discretisation>
3306+ <discontinuous_galerkin>
3307+ <viscosity_scheme>
3308+ <compact_discontinuous_galerkin/>
3309+ <tensor_form/>
3310+ </viscosity_scheme>
3311+ <advection_scheme>
3312+ <upwind/>
3313+ <integrate_advection_by_parts>
3314+ <twice/>
3315+ </integrate_advection_by_parts>
3316+ </advection_scheme>
3317+ </discontinuous_galerkin>
3318+ <conservative_advection>
3319+ <real_value rank="0">0</real_value>
3320+ </conservative_advection>
3321+ </spatial_discretisation>
3322+ <temporal_discretisation>
3323+ <theta>
3324+ <real_value rank="0">1.0</real_value>
3325+ </theta>
3326+ <relaxation>
3327+ <real_value rank="0">0.5</real_value>
3328+ </relaxation>
3329+ </temporal_discretisation>
3330+ <solver>
3331+ <iterative_method name="gmres">
3332+ <restart>
3333+ <integer_value rank="0">30</integer_value>
3334+ </restart>
3335+ </iterative_method>
3336+ <preconditioner name="sor"/>
3337+ <relative_error>
3338+ <real_value rank="0">1.0e-7</real_value>
3339+ </relative_error>
3340+ <max_iterations>
3341+ <integer_value rank="0">1000</integer_value>
3342+ </max_iterations>
3343+ <never_ignore_solver_failures/>
3344+ <diagnostics>
3345+ <monitors/>
3346+ </diagnostics>
3347+ </solver>
3348+ <initial_condition name="WholeMesh">
3349+ <constant>
3350+ <real_value shape="1" dim1="dim" rank="1">0</real_value>
3351+ </constant>
3352+ </initial_condition>
3353+ <boundary_conditions name="Left">
3354+ <surface_ids>
3355+ <integer_value shape="1" rank="1">1</integer_value>
3356+ </surface_ids>
3357+ <type name="dirichlet">
3358+ <align_bc_with_cartesian>
3359+ <x_component>
3360+ <constant>
3361+ <real_value rank="0">300</real_value>
3362+ </constant>
3363+ </x_component>
3364+ </align_bc_with_cartesian>
3365+ </type>
3366+ </boundary_conditions>
3367+ <tensor_field name="Viscosity" rank="2">
3368+ <prescribed>
3369+ <value name="WholeMesh">
3370+ <isotropic>
3371+ <constant>
3372+ <real_value rank="0">0.5</real_value>
3373+ </constant>
3374+ </isotropic>
3375+ </value>
3376+ <output/>
3377+ </prescribed>
3378+ </tensor_field>
3379+ <output/>
3380+ <stat>
3381+ <include_in_stat/>
3382+ <previous_time_step>
3383+ <exclude_from_stat/>
3384+ </previous_time_step>
3385+ <nonlinear_field>
3386+ <exclude_from_stat/>
3387+ </nonlinear_field>
3388+ </stat>
3389+ <convergence>
3390+ <include_in_convergence/>
3391+ </convergence>
3392+ <detectors>
3393+ <include_in_detectors/>
3394+ </detectors>
3395+ <steady_state>
3396+ <include_in_steady_state/>
3397+ </steady_state>
3398+ <consistent_interpolation/>
3399+ </prognostic>
3400+ </vector_field>
3401+ <scalar_field name="CFLNumber" rank="0">
3402+ <diagnostic>
3403+ <algorithm name="Internal" material_phase_support="multiple"/>
3404+ <mesh name="VelocityMesh"/>
3405+ <output/>
3406+ <stat/>
3407+ <convergence>
3408+ <include_in_convergence/>
3409+ </convergence>
3410+ <detectors>
3411+ <include_in_detectors/>
3412+ </detectors>
3413+ <steady_state>
3414+ <include_in_steady_state/>
3415+ </steady_state>
3416+ </diagnostic>
3417+ </scalar_field>
3418+ <scalar_field name="InternalEnergy" rank="0">
3419+ <prognostic>
3420+ <mesh name="PressureMesh"/>
3421+ <equation name="InternalEnergy">
3422+ <density name="Density">
3423+ <discretisation_options>
3424+ <spatial_discretisation>
3425+ <control_volumes>
3426+ <face_value name="FirstOrderUpwind"/>
3427+ </control_volumes>
3428+ </spatial_discretisation>
3429+ <temporal_discretisation>
3430+ <theta>
3431+ <real_value rank="0">1.0</real_value>
3432+ </theta>
3433+ <control_volumes/>
3434+ </temporal_discretisation>
3435+ </discretisation_options>
3436+ </density>
3437+ </equation>
3438+ <spatial_discretisation>
3439+ <control_volumes>
3440+ <face_value name="FirstOrderUpwind"/>
3441+ <diffusion_scheme name="ElementGradient"/>
3442+ </control_volumes>
3443+ <conservative_advection>
3444+ <real_value rank="0">0.0</real_value>
3445+ </conservative_advection>
3446+ </spatial_discretisation>
3447+ <temporal_discretisation>
3448+ <theta>
3449+ <real_value rank="0">1.0</real_value>
3450+ </theta>
3451+ </temporal_discretisation>
3452+ <solver>
3453+ <iterative_method name="gmres">
3454+ <restart>
3455+ <integer_value rank="0">30</integer_value>
3456+ </restart>
3457+ </iterative_method>
3458+ <preconditioner name="sor"/>
3459+ <relative_error>
3460+ <real_value rank="0">1.0e-7</real_value>
3461+ </relative_error>
3462+ <max_iterations>
3463+ <integer_value rank="0">1000</integer_value>
3464+ </max_iterations>
3465+ <never_ignore_solver_failures/>
3466+ <diagnostics>
3467+ <monitors/>
3468+ </diagnostics>
3469+ </solver>
3470+ <initial_condition name="WholeMesh">
3471+ <constant>
3472+ <real_value rank="0">274895.1</real_value>
3473+ </constant>
3474+ </initial_condition>
3475+ <boundary_conditions name="Left">
3476+ <surface_ids>
3477+ <integer_value shape="1" rank="1">1</integer_value>
3478+ </surface_ids>
3479+ <type name="dirichlet">
3480+ <constant>
3481+ <real_value rank="0">1144800</real_value>
3482+ </constant>
3483+ </type>
3484+ </boundary_conditions>
3485+ <output/>
3486+ <stat/>
3487+ <convergence>
3488+ <include_in_convergence/>
3489+ </convergence>
3490+ <detectors>
3491+ <include_in_detectors/>
3492+ </detectors>
3493+ <steady_state>
3494+ <include_in_steady_state/>
3495+ </steady_state>
3496+ <consistent_interpolation/>
3497+ </prognostic>
3498+ </scalar_field>
3499+ <scalar_field name="PhaseVolumeFraction" rank="0">
3500+ <prognostic>
3501+ <mesh name="CoordinateMesh"/>
3502+ <equation name="AdvectionDiffusion"/>
3503+ <spatial_discretisation>
3504+ <control_volumes>
3505+ <face_value name="FirstOrderUpwind"/>
3506+ <diffusion_scheme name="ElementGradient"/>
3507+ </control_volumes>
3508+ <conservative_advection>
3509+ <real_value rank="0">0.0</real_value>
3510+ </conservative_advection>
3511+ </spatial_discretisation>
3512+ <temporal_discretisation>
3513+ <theta>
3514+ <real_value rank="0">1.0</real_value>
3515+ </theta>
3516+ </temporal_discretisation>
3517+ <solver>
3518+ <iterative_method name="gmres">
3519+ <restart>
3520+ <integer_value rank="0">30</integer_value>
3521+ </restart>
3522+ </iterative_method>
3523+ <preconditioner name="sor"/>
3524+ <relative_error>
3525+ <real_value rank="0">1.0e-7</real_value>
3526+ </relative_error>
3527+ <max_iterations>
3528+ <integer_value rank="0">1000</integer_value>
3529+ </max_iterations>
3530+ <never_ignore_solver_failures/>
3531+ <diagnostics>
3532+ <monitors/>
3533+ </diagnostics>
3534+ </solver>
3535+ <initial_condition name="WholeMesh">
3536+ <constant>
3537+ <real_value rank="0">1.0e-7</real_value>
3538+ </constant>
3539+ </initial_condition>
3540+ <boundary_conditions name="Left">
3541+ <surface_ids>
3542+ <integer_value shape="1" rank="1">1</integer_value>
3543+ </surface_ids>
3544+ <type name="dirichlet">
3545+ <constant>
3546+ <real_value rank="0">1.0e-4</real_value>
3547+ </constant>
3548+ </type>
3549+ </boundary_conditions>
3550+ <output/>
3551+ <stat/>
3552+ <convergence>
3553+ <include_in_convergence/>
3554+ </convergence>
3555+ <detectors>
3556+ <include_in_detectors/>
3557+ </detectors>
3558+ <steady_state>
3559+ <include_in_steady_state/>
3560+ </steady_state>
3561+ <consistent_interpolation/>
3562+ </prognostic>
3563+ </scalar_field>
3564+ <multiphase_properties>
3565+ <particle_diameter>
3566+ <real_value rank="0">2e-4</real_value>
3567+ </particle_diameter>
3568+ <specific_heat>
3569+ <real_value rank="0">954</real_value>
3570+ </specific_heat>
3571+ </multiphase_properties>
3572+ </material_phase>
3573+ <multiphase_interaction>
3574+ <fluid_particle_drag>
3575+ <drag_correlation name="wen_yu"/>
3576+ </fluid_particle_drag>
3577+ <heat_transfer>
3578+ <heat_transfer_coefficient name="gunn"/>
3579+ </heat_transfer>
3580+ </multiphase_interaction>
3581+</fluidity_options>
3582
3583=== added file 'tests/mphase_inlet_velocity_bc_compressible/mphase_inlet_velocity_bc_compressible.xml'
3584--- tests/mphase_inlet_velocity_bc_compressible/mphase_inlet_velocity_bc_compressible.xml 1970-01-01 00:00:00 +0000
3585+++ tests/mphase_inlet_velocity_bc_compressible/mphase_inlet_velocity_bc_compressible.xml 2013-07-10 19:09:26 +0000
3586@@ -0,0 +1,48 @@
3587+<?xml version="1.0" encoding="UTF-8" ?>
3588+<!DOCTYPE testproblem SYSTEM "regressiontest.dtd">
3589+
3590+<testproblem>
3591+
3592+ <name>mphase_inlet_velocity_bc_compressible</name>
3593+ <owner userid="ctj10"/>
3594+ <tags>flml</tags>
3595+
3596+ <problem_definition length="medium" nprocs="1">
3597+ <command_line>make run</command_line>
3598+ </problem_definition>
3599+
3600+ <variables>
3601+ <variable name="gas_velocity_max" language="python">
3602+from fluidity_tools import stat_parser
3603+s = stat_parser("mphase_inlet_velocity_bc_compressible.stat")
3604+gas_velocity_max = s["Gas"]["Velocity%1"]["max"][-1]
3605+ </variable>
3606+ <variable name="gas_velocity_min" language="python">
3607+from fluidity_tools import stat_parser
3608+s = stat_parser("mphase_inlet_velocity_bc_compressible.stat")
3609+gas_velocity_min = s["Gas"]["Velocity%1"]["min"][-1]
3610+ </variable>
3611+ <variable name="solvers_converged" language="python">
3612+import os
3613+files = os.listdir("./")
3614+solvers_converged = not "matrixdump" in files and not "matrixdump.info" in files
3615+ </variable>
3616+ </variables>
3617+
3618+ <pass_tests>
3619+ <test name="Gas::Velocity is at most ~300 m/s" language="python">
3620+assert(abs(gas_velocity_max) &lt; 305)
3621+ </test>
3622+ <test name="Gas::Velocity is at least 75 m/s" language="python">
3623+# Note: the velocity won't be 300 m/s everywhere because of the effects of changing density and pressure.
3624+assert(abs(gas_velocity_min) &gt; 75)
3625+ </test>
3626+ <test name="Solvers converged" language="python">
3627+assert(solvers_converged)
3628+ </test>
3629+ </pass_tests>
3630+
3631+ <warn_tests>
3632+ </warn_tests>
3633+
3634+</testproblem>
3635
3636=== added directory 'tests/mphase_strong_pressure_bc_compressible'
3637=== added file 'tests/mphase_strong_pressure_bc_compressible/Makefile'
3638--- tests/mphase_strong_pressure_bc_compressible/Makefile 1970-01-01 00:00:00 +0000
3639+++ tests/mphase_strong_pressure_bc_compressible/Makefile 2013-07-10 19:09:26 +0000
3640@@ -0,0 +1,19 @@
3641+preprocess:
3642+ @echo **********Creating 1D mesh
3643+ ../../bin/interval --dx=100.0 -- 0.0 10000.0 line
3644+
3645+run:
3646+ @echo **********Running P2-P1 simulation
3647+ ../../bin/fluidity mphase_strong_pressure_bc_compressible_p2p1.flml
3648+ @echo **********Running P0-P1 simulation
3649+ ../../bin/fluidity mphase_strong_pressure_bc_compressible_p0p1.flml
3650+
3651+input: clean preprocess
3652+
3653+clean:
3654+ rm -f *.stat *.steady_state*
3655+ rm -f *.d.* *.vtu
3656+ rm -f *.msh
3657+ rm -f *.ele *.edge *.node *.poly *.bound
3658+ rm -f matrixdump* *.log* *.err*
3659+
3660
3661=== added file 'tests/mphase_strong_pressure_bc_compressible/mphase_strong_pressure_bc_compressible.xml'
3662--- tests/mphase_strong_pressure_bc_compressible/mphase_strong_pressure_bc_compressible.xml 1970-01-01 00:00:00 +0000
3663+++ tests/mphase_strong_pressure_bc_compressible/mphase_strong_pressure_bc_compressible.xml 2013-07-10 19:09:26 +0000
3664@@ -0,0 +1,73 @@
3665+<?xml version="1.0" encoding="UTF-8" ?>
3666+<!DOCTYPE testproblem SYSTEM "regressiontest.dtd">
3667+
3668+<testproblem>
3669+
3670+ <name>mphase_strong_pressure_bc_compressible</name>
3671+ <owner userid="ctj10"/>
3672+ <tags>flml</tags>
3673+
3674+ <problem_definition length="medium" nprocs="1">
3675+ <command_line>make run</command_line>
3676+ </problem_definition>
3677+
3678+ <variables>
3679+ <variable name="gas_velocity_max_p2p1" language="python">
3680+from fluidity_tools import stat_parser
3681+s = stat_parser("mphase_strong_pressure_bc_compressible_p2p1.stat")
3682+gas_velocity_max_p2p1 = s["Gas"]["Velocity%1"]["max"][-1]
3683+ </variable>
3684+ <variable name="gas_pressure_max_p2p1" language="python">
3685+from fluidity_tools import stat_parser
3686+s = stat_parser("mphase_strong_pressure_bc_compressible_p2p1.stat")
3687+gas_pressure_max_p2p1 = s["Gas"]["Pressure"]["max"][-1]
3688+ </variable>
3689+ <variable name="gas_pressure_min_p2p1" language="python">
3690+from fluidity_tools import stat_parser
3691+s = stat_parser("mphase_strong_pressure_bc_compressible_p2p1.stat")
3692+gas_pressure_min_p2p1 = s["Gas"]["Pressure"]["min"][-1]
3693+ </variable>
3694+ <variable name="gas_velocity_max_p0p1" language="python">
3695+from fluidity_tools import stat_parser
3696+s = stat_parser("mphase_strong_pressure_bc_compressible_p0p1.stat")
3697+gas_velocity_max_p0p1 = s["Gas"]["Velocity%1"]["max"][-1]
3698+ </variable>
3699+ <variable name="gas_pressure_max_p0p1" language="python">
3700+from fluidity_tools import stat_parser
3701+s = stat_parser("mphase_strong_pressure_bc_compressible_p0p1.stat")
3702+gas_pressure_max_p0p1 = s["Gas"]["Pressure"]["max"][-1]
3703+ </variable>
3704+ <variable name="gas_pressure_min_p0p1" language="python">
3705+from fluidity_tools import stat_parser
3706+s = stat_parser("mphase_strong_pressure_bc_compressible_p0p1.stat")
3707+gas_pressure_min_p0p1 = s["Gas"]["Pressure"]["min"][-1]
3708+ </variable>
3709+ <variable name="solvers_converged" language="python">
3710+import os
3711+files = os.listdir("./")
3712+solvers_converged = not "matrixdump" in files and not "matrixdump.info" in files
3713+ </variable>
3714+ </variables>
3715+
3716+ <pass_tests>
3717+ <test name="Gas::Velocity is always zero everywhere (P2-P1 simulation)" language="python">
3718+assert(abs(gas_velocity_max_p2p1) &lt; 1e-7)
3719+ </test>
3720+ <test name="Gas::Pressure is always 101325 Pa everywhere (P2-P1 simulation)" language="python">
3721+assert(abs(gas_pressure_max_p2p1) - 101325 &lt; 1.0e-7 and abs(gas_pressure_min_p2p1) - 101325 &lt; 1.0e-7)
3722+ </test>
3723+ <test name="Gas::Velocity is always zero everywhere (P0-P1 simulation)" language="python">
3724+assert(abs(gas_velocity_max_p0p1) &lt; 1e-7)
3725+ </test>
3726+ <test name="Gas::Pressure is always 101325 Pa everywhere (P0-P1 simulation)" language="python">
3727+assert(abs(gas_pressure_max_p0p1) - 101325 &lt; 1.0e-7 and abs(gas_pressure_min_p0p1) - 101325 &lt; 1.0e-7)
3728+ </test>
3729+ <test name="Solvers converged" language="python">
3730+assert(solvers_converged)
3731+ </test>
3732+ </pass_tests>
3733+
3734+ <warn_tests>
3735+ </warn_tests>
3736+
3737+</testproblem>
3738
3739=== added file 'tests/mphase_strong_pressure_bc_compressible/mphase_strong_pressure_bc_compressible_p0p1.flml'
3740--- tests/mphase_strong_pressure_bc_compressible/mphase_strong_pressure_bc_compressible_p0p1.flml 1970-01-01 00:00:00 +0000
3741+++ tests/mphase_strong_pressure_bc_compressible/mphase_strong_pressure_bc_compressible_p0p1.flml 2013-07-10 19:09:26 +0000
3742@@ -0,0 +1,735 @@
3743+<?xml version='1.0' encoding='utf-8'?>
3744+<fluidity_options>
3745+ <simulation_name>
3746+ <string_value lines="1">mphase_strong_pressure_bc_compressible_p0p1</string_value>
3747+ </simulation_name>
3748+ <problem_type>
3749+ <string_value lines="1">fluids</string_value>
3750+ </problem_type>
3751+ <geometry>
3752+ <dimension>
3753+ <integer_value rank="0">1</integer_value>
3754+ </dimension>
3755+ <mesh name="CoordinateMesh">
3756+ <from_file file_name="line">
3757+ <format name="triangle"/>
3758+ <stat>
3759+ <include_in_stat/>
3760+ </stat>
3761+ </from_file>
3762+ </mesh>
3763+ <mesh name="VelocityMesh">
3764+ <from_mesh>
3765+ <mesh name="CoordinateMesh"/>
3766+ <mesh_shape>
3767+ <polynomial_degree>
3768+ <integer_value rank="0">0</integer_value>
3769+ </polynomial_degree>
3770+ </mesh_shape>
3771+ <mesh_continuity>
3772+ <string_value>discontinuous</string_value>
3773+ </mesh_continuity>
3774+ <stat>
3775+ <exclude_from_stat/>
3776+ </stat>
3777+ </from_mesh>
3778+ </mesh>
3779+ <mesh name="PressureMesh">
3780+ <from_mesh>
3781+ <mesh name="CoordinateMesh"/>
3782+ <mesh_shape>
3783+ <polynomial_degree>
3784+ <integer_value rank="0">1</integer_value>
3785+ </polynomial_degree>
3786+ </mesh_shape>
3787+ <stat>
3788+ <exclude_from_stat/>
3789+ </stat>
3790+ </from_mesh>
3791+ </mesh>
3792+ <mesh name="DensityMesh">
3793+ <from_mesh>
3794+ <mesh name="CoordinateMesh"/>
3795+ <mesh_shape>
3796+ <polynomial_degree>
3797+ <integer_value rank="0">1</integer_value>
3798+ </polynomial_degree>
3799+ </mesh_shape>
3800+ <stat>
3801+ <exclude_from_stat/>
3802+ </stat>
3803+ </from_mesh>
3804+ </mesh>
3805+ <mesh name="GeostrophicMesh">
3806+ <from_mesh>
3807+ <mesh name="CoordinateMesh"/>
3808+ <mesh_shape>
3809+ <polynomial_degree>
3810+ <integer_value rank="0">1</integer_value>
3811+ </polynomial_degree>
3812+ </mesh_shape>
3813+ <stat>
3814+ <exclude_from_stat/>
3815+ </stat>
3816+ </from_mesh>
3817+ </mesh>
3818+ <quadrature>
3819+ <degree>
3820+ <integer_value rank="0">4</integer_value>
3821+ </degree>
3822+ </quadrature>
3823+ </geometry>
3824+ <io>
3825+ <dump_format>
3826+ <string_value>vtk</string_value>
3827+ </dump_format>
3828+ <dump_period>
3829+ <constant>
3830+ <real_value rank="0">0</real_value>
3831+ </constant>
3832+ </dump_period>
3833+ <output_mesh name="PressureMesh"/>
3834+ <stat>
3835+ <output_at_start/>
3836+ </stat>
3837+ </io>
3838+ <timestepping>
3839+ <current_time>
3840+ <real_value rank="0">0</real_value>
3841+ </current_time>
3842+ <timestep>
3843+ <real_value rank="0">0.001</real_value>
3844+ </timestep>
3845+ <finish_time>
3846+ <real_value rank="0">600.0</real_value>
3847+ </finish_time>
3848+ <nonlinear_iterations>
3849+ <integer_value rank="0">2</integer_value>
3850+ <tolerance>
3851+ <real_value rank="0">1.0e-9</real_value>
3852+ <infinity_norm/>
3853+ </tolerance>
3854+ </nonlinear_iterations>
3855+ <adaptive_timestep>
3856+ <requested_cfl>
3857+ <real_value rank="0">0.25</real_value>
3858+ </requested_cfl>
3859+ <courant_number name="CFLNumber">
3860+ <mesh name="VelocityMesh"/>
3861+ </courant_number>
3862+ <minimum_timestep>
3863+ <real_value rank="0">0.001</real_value>
3864+ </minimum_timestep>
3865+ <increase_tolerance>
3866+ <real_value rank="0">1.1</real_value>
3867+ </increase_tolerance>
3868+ </adaptive_timestep>
3869+ </timestepping>
3870+ <material_phase name="Gas">
3871+ <equation_of_state>
3872+ <compressible>
3873+ <stiffened_gas>
3874+ <ratio_specific_heats>
3875+ <real_value rank="0">1.33</real_value>
3876+ </ratio_specific_heats>
3877+ </stiffened_gas>
3878+ </compressible>
3879+ </equation_of_state>
3880+ <scalar_field name="Pressure" rank="0">
3881+ <prognostic>
3882+ <mesh name="PressureMesh"/>
3883+ <spatial_discretisation>
3884+ <continuous_galerkin>
3885+ <remove_stabilisation_term/>
3886+ <integrate_continuity_by_parts/>
3887+ </continuous_galerkin>
3888+ </spatial_discretisation>
3889+ <scheme>
3890+ <poisson_pressure_solution>
3891+ <string_value lines="1">never</string_value>
3892+ </poisson_pressure_solution>
3893+ <use_compressible_projection_method/>
3894+ </scheme>
3895+ <solver>
3896+ <iterative_method name="gmres">
3897+ <restart>
3898+ <integer_value rank="0">30</integer_value>
3899+ </restart>
3900+ </iterative_method>
3901+ <preconditioner name="sor"/>
3902+ <relative_error>
3903+ <real_value rank="0">1.0e-7</real_value>
3904+ </relative_error>
3905+ <max_iterations>
3906+ <integer_value rank="0">1000</integer_value>
3907+ </max_iterations>
3908+ <never_ignore_solver_failures/>
3909+ <diagnostics>
3910+ <monitors/>
3911+ </diagnostics>
3912+ </solver>
3913+ <initial_condition name="WholeMesh">
3914+ <constant>
3915+ <real_value rank="0">101325</real_value>
3916+ </constant>
3917+ </initial_condition>
3918+ <boundary_conditions name="Right">
3919+ <surface_ids>
3920+ <integer_value shape="1" rank="1">2</integer_value>
3921+ </surface_ids>
3922+ <type name="dirichlet">
3923+ <constant>
3924+ <real_value rank="0">101325</real_value>
3925+ </constant>
3926+ </type>
3927+ </boundary_conditions>
3928+ <output/>
3929+ <stat/>
3930+ <convergence>
3931+ <include_in_convergence/>
3932+ </convergence>
3933+ <detectors>
3934+ <exclude_from_detectors/>
3935+ </detectors>
3936+ <steady_state>
3937+ <include_in_steady_state/>
3938+ </steady_state>
3939+ <no_interpolation/>
3940+ </prognostic>
3941+ </scalar_field>
3942+ <scalar_field name="Density" rank="0">
3943+ <prognostic>
3944+ <mesh name="DensityMesh"/>
3945+ <spatial_discretisation>
3946+ <control_volumes>
3947+ <face_value name="FirstOrderUpwind"/>
3948+ </control_volumes>
3949+ <conservative_advection>
3950+ <real_value rank="0">1.0</real_value>
3951+ </conservative_advection>
3952+ </spatial_discretisation>
3953+ <temporal_discretisation>
3954+ <theta>
3955+ <real_value rank="0">1.0</real_value>
3956+ </theta>
3957+ </temporal_discretisation>
3958+ <initial_condition name="WholeMesh">
3959+ <constant>
3960+ <real_value rank="0">0.757877001</real_value>
3961+ </constant>
3962+ </initial_condition>
3963+ <boundary_conditions name="Right">
3964+ <surface_ids>
3965+ <integer_value shape="1" rank="1">2</integer_value>
3966+ </surface_ids>
3967+ <type name="dirichlet">
3968+ <constant>
3969+ <real_value rank="0">0.757877001</real_value>
3970+ </constant>
3971+ </type>
3972+ </boundary_conditions>
3973+ <output/>
3974+ <stat/>
3975+ <convergence>
3976+ <include_in_convergence/>
3977+ </convergence>
3978+ <detectors>
3979+ <include_in_detectors/>
3980+ </detectors>
3981+ <steady_state>
3982+ <include_in_steady_state/>
3983+ </steady_state>
3984+ <consistent_interpolation/>
3985+ </prognostic>
3986+ </scalar_field>
3987+ <vector_field name="Velocity" rank="1">
3988+ <prognostic>
3989+ <mesh name="VelocityMesh"/>
3990+ <equation name="LinearMomentum"/>
3991+ <spatial_discretisation>
3992+ <discontinuous_galerkin>
3993+ <viscosity_scheme>
3994+ <compact_discontinuous_galerkin/>
3995+ <tensor_form/>
3996+ </viscosity_scheme>
3997+ <advection_scheme>
3998+ <upwind/>
3999+ <integrate_advection_by_parts>
4000+ <twice/>
4001+ </integrate_advection_by_parts>
4002+ </advection_scheme>
4003+ </discontinuous_galerkin>
4004+ <conservative_advection>
4005+ <real_value rank="0">0</real_value>
4006+ </conservative_advection>
4007+ </spatial_discretisation>
4008+ <temporal_discretisation>
4009+ <theta>
4010+ <real_value rank="0">1.0</real_value>
4011+ </theta>
4012+ <relaxation>
4013+ <real_value rank="0">0.5</real_value>
4014+ </relaxation>
4015+ </temporal_discretisation>
4016+ <solver>
4017+ <iterative_method name="gmres">
4018+ <restart>
4019+ <integer_value rank="0">30</integer_value>
4020+ </restart>
4021+ </iterative_method>
4022+ <preconditioner name="sor"/>
4023+ <relative_error>
4024+ <real_value rank="0">1.0e-7</real_value>
4025+ </relative_error>
4026+ <max_iterations>
4027+ <integer_value rank="0">1000</integer_value>
4028+ </max_iterations>
4029+ <never_ignore_solver_failures/>
4030+ <diagnostics>
4031+ <monitors/>
4032+ </diagnostics>
4033+ </solver>
4034+ <initial_condition name="WholeMesh">
4035+ <constant>
4036+ <real_value shape="1" dim1="dim" rank="1">0</real_value>
4037+ </constant>
4038+ </initial_condition>
4039+ <boundary_conditions name="Left">
4040+ <surface_ids>
4041+ <integer_value shape="1" rank="1">1</integer_value>
4042+ </surface_ids>
4043+ <type name="dirichlet">
4044+ <align_bc_with_cartesian>
4045+ <x_component>
4046+ <constant>
4047+ <real_value rank="0">0</real_value>
4048+ </constant>
4049+ </x_component>
4050+ </align_bc_with_cartesian>
4051+ </type>
4052+ </boundary_conditions>
4053+ <tensor_field name="Viscosity" rank="2">
4054+ <prescribed>
4055+ <value name="WholeMesh">
4056+ <anisotropic_asymmetric>
4057+ <constant>
4058+ <real_value symmetric="false" dim2="dim" shape="1 1" dim1="dim" rank="2">1.85e-5</real_value>
4059+ </constant>
4060+ </anisotropic_asymmetric>
4061+ </value>
4062+ <output/>
4063+ </prescribed>
4064+ </tensor_field>
4065+ <output/>
4066+ <stat>
4067+ <include_in_stat/>
4068+ <previous_time_step>
4069+ <exclude_from_stat/>
4070+ </previous_time_step>
4071+ <nonlinear_field>
4072+ <exclude_from_stat/>
4073+ </nonlinear_field>
4074+ </stat>
4075+ <convergence>
4076+ <include_in_convergence/>
4077+ </convergence>
4078+ <detectors>
4079+ <include_in_detectors/>
4080+ </detectors>
4081+ <steady_state>
4082+ <include_in_steady_state/>
4083+ </steady_state>
4084+ <consistent_interpolation/>
4085+ </prognostic>
4086+ </vector_field>
4087+ <scalar_field name="CFLNumber" rank="0">
4088+ <diagnostic>
4089+ <algorithm name="Internal" material_phase_support="multiple"/>
4090+ <mesh name="VelocityMesh"/>
4091+ <output/>
4092+ <stat/>
4093+ <convergence>
4094+ <include_in_convergence/>
4095+ </convergence>
4096+ <detectors>
4097+ <include_in_detectors/>
4098+ </detectors>
4099+ <steady_state>
4100+ <include_in_steady_state/>
4101+ </steady_state>
4102+ </diagnostic>
4103+ </scalar_field>
4104+ <scalar_field name="InternalEnergy" rank="0">
4105+ <prognostic>
4106+ <mesh name="PressureMesh"/>
4107+ <equation name="InternalEnergy">
4108+ <density name="Density">
4109+ <discretisation_options>
4110+ <spatial_discretisation>
4111+ <control_volumes>
4112+ <face_value name="FirstOrderUpwind"/>
4113+ </control_volumes>
4114+ </spatial_discretisation>
4115+ <temporal_discretisation>
4116+ <theta>
4117+ <real_value rank="0">1.0</real_value>
4118+ </theta>
4119+ <control_volumes/>
4120+ </temporal_discretisation>
4121+ </discretisation_options>
4122+ </density>
4123+ </equation>
4124+ <spatial_discretisation>
4125+ <control_volumes>
4126+ <face_value name="FirstOrderUpwind"/>
4127+ <diffusion_scheme name="ElementGradient"/>
4128+ </control_volumes>
4129+ <conservative_advection>
4130+ <real_value rank="0">0.0</real_value>
4131+ </conservative_advection>
4132+ </spatial_discretisation>
4133+ <temporal_discretisation>
4134+ <theta>
4135+ <real_value rank="0">1.0</real_value>
4136+ </theta>
4137+ </temporal_discretisation>
4138+ <solver>
4139+ <iterative_method name="gmres">
4140+ <restart>
4141+ <integer_value rank="0">30</integer_value>
4142+ </restart>
4143+ </iterative_method>
4144+ <preconditioner name="sor"/>
4145+ <relative_error>
4146+ <real_value rank="0">1.0e-7</real_value>
4147+ </relative_error>
4148+ <max_iterations>
4149+ <integer_value rank="0">1000</integer_value>
4150+ </max_iterations>
4151+ <never_ignore_solver_failures/>
4152+ <diagnostics>
4153+ <monitors/>
4154+ </diagnostics>
4155+ </solver>
4156+ <initial_condition name="WholeMesh">
4157+ <constant>
4158+ <real_value rank="0">405138.9</real_value>
4159+ </constant>
4160+ </initial_condition>
4161+ <output/>
4162+ <stat/>
4163+ <convergence>
4164+ <include_in_convergence/>
4165+ </convergence>
4166+ <detectors>
4167+ <include_in_detectors/>
4168+ </detectors>
4169+ <steady_state>
4170+ <include_in_steady_state/>
4171+ </steady_state>
4172+ <consistent_interpolation/>
4173+ </prognostic>
4174+ </scalar_field>
4175+ <scalar_field name="PhaseVolumeFraction" rank="0">
4176+ <diagnostic>
4177+ <mesh name="CoordinateMesh"/>
4178+ <algorithm name="Internal" material_phase_support="multiple"/>
4179+ <output/>
4180+ <stat/>
4181+ <detectors>
4182+ <include_in_detectors/>
4183+ </detectors>
4184+ </diagnostic>
4185+ </scalar_field>
4186+ <multiphase_properties>
4187+ <effective_conductivity>
4188+ <real_value rank="0">0.5</real_value>
4189+ </effective_conductivity>
4190+ <specific_heat>
4191+ <real_value rank="0">1406</real_value>
4192+ </specific_heat>
4193+ </multiphase_properties>
4194+ </material_phase>
4195+ <material_phase name="Particles">
4196+ <equation_of_state>
4197+ <fluids>
4198+ <linear>
4199+ <reference_density>
4200+ <real_value rank="0">2400</real_value>
4201+ </reference_density>
4202+ </linear>
4203+ </fluids>
4204+ </equation_of_state>
4205+ <scalar_field name="Pressure" rank="0">
4206+ <aliased material_phase_name="Gas" field_name="Pressure"/>
4207+ </scalar_field>
4208+ <scalar_field name="Density" rank="0">
4209+ <diagnostic>
4210+ <algorithm name="Internal" material_phase_support="multiple"/>
4211+ <mesh name="PressureMesh"/>
4212+ <output/>
4213+ <stat/>
4214+ <convergence>
4215+ <include_in_convergence/>
4216+ </convergence>
4217+ <detectors>
4218+ <include_in_detectors/>
4219+ </detectors>
4220+ <steady_state>
4221+ <include_in_steady_state/>
4222+ </steady_state>
4223+ </diagnostic>
4224+ </scalar_field>
4225+ <vector_field name="Velocity" rank="1">
4226+ <prognostic>
4227+ <mesh name="VelocityMesh"/>
4228+ <equation name="LinearMomentum"/>
4229+ <spatial_discretisation>
4230+ <discontinuous_galerkin>
4231+ <viscosity_scheme>
4232+ <compact_discontinuous_galerkin/>
4233+ <tensor_form/>
4234+ </viscosity_scheme>
4235+ <advection_scheme>
4236+ <upwind/>
4237+ <integrate_advection_by_parts>
4238+ <twice/>
4239+ </integrate_advection_by_parts>
4240+ </advection_scheme>
4241+ </discontinuous_galerkin>
4242+ <conservative_advection>
4243+ <real_value rank="0">0</real_value>
4244+ </conservative_advection>
4245+ </spatial_discretisation>
4246+ <temporal_discretisation>
4247+ <theta>
4248+ <real_value rank="0">1.0</real_value>
4249+ </theta>
4250+ <relaxation>
4251+ <real_value rank="0">0.5</real_value>
4252+ </relaxation>
4253+ </temporal_discretisation>
4254+ <solver>
4255+ <iterative_method name="gmres">
4256+ <restart>
4257+ <integer_value rank="0">30</integer_value>
4258+ </restart>
4259+ </iterative_method>
4260+ <preconditioner name="sor"/>
4261+ <relative_error>
4262+ <real_value rank="0">1.0e-7</real_value>
4263+ </relative_error>
4264+ <max_iterations>
4265+ <integer_value rank="0">1000</integer_value>
4266+ </max_iterations>
4267+ <never_ignore_solver_failures/>
4268+ <diagnostics>
4269+ <monitors/>
4270+ </diagnostics>
4271+ </solver>
4272+ <initial_condition name="WholeMesh">
4273+ <constant>
4274+ <real_value shape="1" dim1="dim" rank="1">0</real_value>
4275+ </constant>
4276+ </initial_condition>
4277+ <boundary_conditions name="Left">
4278+ <surface_ids>
4279+ <integer_value shape="1" rank="1">1</integer_value>
4280+ </surface_ids>
4281+ <type name="dirichlet">
4282+ <align_bc_with_cartesian>
4283+ <x_component>
4284+ <constant>
4285+ <real_value rank="0">0</real_value>
4286+ </constant>
4287+ </x_component>
4288+ </align_bc_with_cartesian>
4289+ </type>
4290+ </boundary_conditions>
4291+ <tensor_field name="Viscosity" rank="2">
4292+ <prescribed>
4293+ <value name="WholeMesh">
4294+ <isotropic>
4295+ <constant>
4296+ <real_value rank="0">0.5</real_value>
4297+ </constant>
4298+ </isotropic>
4299+ </value>
4300+ <output/>
4301+ </prescribed>
4302+ </tensor_field>
4303+ <output/>
4304+ <stat>
4305+ <include_in_stat/>
4306+ <previous_time_step>
4307+ <exclude_from_stat/>
4308+ </previous_time_step>
4309+ <nonlinear_field>
4310+ <exclude_from_stat/>
4311+ </nonlinear_field>
4312+ </stat>
4313+ <convergence>
4314+ <include_in_convergence/>
4315+ </convergence>
4316+ <detectors>
4317+ <include_in_detectors/>
4318+ </detectors>
4319+ <steady_state>
4320+ <include_in_steady_state/>
4321+ </steady_state>
4322+ <consistent_interpolation/>
4323+ </prognostic>
4324+ </vector_field>
4325+ <scalar_field name="CFLNumber" rank="0">
4326+ <diagnostic>
4327+ <algorithm name="Internal" material_phase_support="multiple"/>
4328+ <mesh name="VelocityMesh"/>
4329+ <output/>
4330+ <stat/>
4331+ <convergence>
4332+ <include_in_convergence/>
4333+ </convergence>
4334+ <detectors>
4335+ <include_in_detectors/>
4336+ </detectors>
4337+ <steady_state>
4338+ <include_in_steady_state/>
4339+ </steady_state>
4340+ </diagnostic>
4341+ </scalar_field>
4342+ <scalar_field name="InternalEnergy" rank="0">
4343+ <prognostic>
4344+ <mesh name="PressureMesh"/>
4345+ <equation name="InternalEnergy">
4346+ <density name="Density">
4347+ <discretisation_options>
4348+ <spatial_discretisation>
4349+ <control_volumes>
4350+ <face_value name="FirstOrderUpwind"/>
4351+ </control_volumes>
4352+ </spatial_discretisation>
4353+ <temporal_discretisation>
4354+ <theta>
4355+ <real_value rank="0">1.0</real_value>
4356+ </theta>
4357+ <control_volumes/>
4358+ </temporal_discretisation>
4359+ </discretisation_options>
4360+ </density>
4361+ </equation>
4362+ <spatial_discretisation>
4363+ <control_volumes>
4364+ <face_value name="FirstOrderUpwind"/>
4365+ <diffusion_scheme name="ElementGradient"/>
4366+ </control_volumes>
4367+ <conservative_advection>
4368+ <real_value rank="0">0.0</real_value>
4369+ </conservative_advection>
4370+ </spatial_discretisation>
4371+ <temporal_discretisation>
4372+ <theta>
4373+ <real_value rank="0">1.0</real_value>
4374+ </theta>
4375+ </temporal_discretisation>
4376+ <solver>
4377+ <iterative_method name="gmres">
4378+ <restart>
4379+ <integer_value rank="0">30</integer_value>
4380+ </restart>
4381+ </iterative_method>
4382+ <preconditioner name="sor"/>
4383+ <relative_error>
4384+ <real_value rank="0">1.0e-7</real_value>
4385+ </relative_error>
4386+ <max_iterations>
4387+ <integer_value rank="0">1000</integer_value>
4388+ </max_iterations>
4389+ <never_ignore_solver_failures/>
4390+ <diagnostics>
4391+ <monitors/>
4392+ </diagnostics>
4393+ </solver>
4394+ <initial_condition name="WholeMesh">
4395+ <constant>
4396+ <real_value rank="0">274895.1</real_value>
4397+ </constant>
4398+ </initial_condition>
4399+ <output/>
4400+ <stat/>
4401+ <convergence>
4402+ <include_in_convergence/>
4403+ </convergence>
4404+ <detectors>
4405+ <include_in_detectors/>
4406+ </detectors>
4407+ <steady_state>
4408+ <include_in_steady_state/>
4409+ </steady_state>
4410+ <consistent_interpolation/>
4411+ </prognostic>
4412+ </scalar_field>
4413+ <scalar_field name="PhaseVolumeFraction" rank="0">
4414+ <prognostic>
4415+ <mesh name="CoordinateMesh"/>
4416+ <equation name="AdvectionDiffusion"/>
4417+ <spatial_discretisation>
4418+ <control_volumes>
4419+ <face_value name="FirstOrderUpwind"/>
4420+ <diffusion_scheme name="ElementGradient"/>
4421+ </control_volumes>
4422+ <conservative_advection>
4423+ <real_value rank="0">1.0</real_value>
4424+ </conservative_advection>
4425+ </spatial_discretisation>
4426+ <temporal_discretisation>
4427+ <theta>
4428+ <real_value rank="0">1.0</real_value>
4429+ </theta>
4430+ </temporal_discretisation>
4431+ <solver>
4432+ <iterative_method name="gmres">
4433+ <restart>
4434+ <integer_value rank="0">30</integer_value>
4435+ </restart>
4436+ </iterative_method>
4437+ <preconditioner name="sor"/>
4438+ <relative_error>
4439+ <real_value rank="0">1.0e-7</real_value>
4440+ </relative_error>
4441+ <max_iterations>
4442+ <integer_value rank="0">1000</integer_value>
4443+ </max_iterations>
4444+ <never_ignore_solver_failures/>
4445+ <diagnostics>
4446+ <monitors/>
4447+ </diagnostics>
4448+ </solver>
4449+ <initial_condition name="WholeMesh">
4450+ <constant>
4451+ <real_value rank="0">1.0e-7</real_value>
4452+ </constant>
4453+ </initial_condition>
4454+ <output/>
4455+ <stat/>
4456+ <convergence>
4457+ <include_in_convergence/>
4458+ </convergence>
4459+ <detectors>
4460+ <include_in_detectors/>
4461+ </detectors>
4462+ <steady_state>
4463+ <include_in_steady_state/>
4464+ </steady_state>
4465+ <consistent_interpolation/>
4466+ </prognostic>
4467+ </scalar_field>
4468+ <multiphase_properties>
4469+ <particle_diameter>
4470+ <real_value rank="0">2e-4</real_value>
4471+ </particle_diameter>
4472+ <specific_heat>
4473+ <real_value rank="0">954</real_value>
4474+ </specific_heat>
4475+ </multiphase_properties>
4476+ </material_phase>
4477+</fluidity_options>
4478
4479=== added file 'tests/mphase_strong_pressure_bc_compressible/mphase_strong_pressure_bc_compressible_p2p1.flml'
4480--- tests/mphase_strong_pressure_bc_compressible/mphase_strong_pressure_bc_compressible_p2p1.flml 1970-01-01 00:00:00 +0000
4481+++ tests/mphase_strong_pressure_bc_compressible/mphase_strong_pressure_bc_compressible_p2p1.flml 2013-07-10 19:09:26 +0000
4482@@ -0,0 +1,742 @@
4483+<?xml version='1.0' encoding='utf-8'?>
4484+<fluidity_options>
4485+ <simulation_name>
4486+ <string_value lines="1">mphase_strong_pressure_bc_compressible_p2p1</string_value>
4487+ </simulation_name>
4488+ <problem_type>
4489+ <string_value lines="1">fluids</string_value>
4490+ </problem_type>
4491+ <geometry>
4492+ <dimension>
4493+ <integer_value rank="0">1</integer_value>
4494+ </dimension>
4495+ <mesh name="CoordinateMesh">
4496+ <from_file file_name="line">
4497+ <format name="triangle"/>
4498+ <stat>
4499+ <include_in_stat/>
4500+ </stat>
4501+ </from_file>
4502+ </mesh>
4503+ <mesh name="VelocityMesh">
4504+ <from_mesh>
4505+ <mesh name="CoordinateMesh"/>
4506+ <mesh_shape>
4507+ <polynomial_degree>
4508+ <integer_value rank="0">2</integer_value>
4509+ </polynomial_degree>
4510+ </mesh_shape>
4511+ <stat>
4512+ <exclude_from_stat/>
4513+ </stat>
4514+ </from_mesh>
4515+ </mesh>
4516+ <mesh name="PressureMesh">
4517+ <from_mesh>
4518+ <mesh name="CoordinateMesh"/>
4519+ <mesh_shape>
4520+ <polynomial_degree>
4521+ <integer_value rank="0">1</integer_value>
4522+ </polynomial_degree>
4523+ </mesh_shape>
4524+ <stat>
4525+ <exclude_from_stat/>
4526+ </stat>
4527+ </from_mesh>
4528+ </mesh>
4529+ <mesh name="DensityMesh">
4530+ <from_mesh>
4531+ <mesh name="CoordinateMesh"/>
4532+ <mesh_shape>
4533+ <polynomial_degree>
4534+ <integer_value rank="0">1</integer_value>
4535+ </polynomial_degree>
4536+ </mesh_shape>
4537+ <stat>
4538+ <exclude_from_stat/>
4539+ </stat>
4540+ </from_mesh>
4541+ </mesh>
4542+ <mesh name="GeostrophicMesh">
4543+ <from_mesh>
4544+ <mesh name="CoordinateMesh"/>
4545+ <mesh_shape>
4546+ <polynomial_degree>
4547+ <integer_value rank="0">1</integer_value>
4548+ </polynomial_degree>
4549+ </mesh_shape>
4550+ <stat>
4551+ <exclude_from_stat/>
4552+ </stat>
4553+ </from_mesh>
4554+ </mesh>
4555+ <quadrature>
4556+ <degree>
4557+ <integer_value rank="0">4</integer_value>
4558+ </degree>
4559+ </quadrature>
4560+ </geometry>
4561+ <io>
4562+ <dump_format>
4563+ <string_value>vtk</string_value>
4564+ </dump_format>
4565+ <dump_period>
4566+ <constant>
4567+ <real_value rank="0">0</real_value>
4568+ </constant>
4569+ </dump_period>
4570+ <output_mesh name="PressureMesh"/>
4571+ <stat>
4572+ <output_at_start/>
4573+ </stat>
4574+ </io>
4575+ <timestepping>
4576+ <current_time>
4577+ <real_value rank="0">0</real_value>
4578+ </current_time>
4579+ <timestep>
4580+ <real_value rank="0">0.001</real_value>
4581+ </timestep>
4582+ <finish_time>
4583+ <real_value rank="0">600.0</real_value>
4584+ </finish_time>
4585+ <nonlinear_iterations>
4586+ <integer_value rank="0">2</integer_value>
4587+ <tolerance>
4588+ <real_value rank="0">1.0e-9</real_value>
4589+ <infinity_norm/>
4590+ </tolerance>
4591+ </nonlinear_iterations>
4592+ <adaptive_timestep>
4593+ <requested_cfl>
4594+ <real_value rank="0">0.25</real_value>
4595+ </requested_cfl>
4596+ <courant_number name="CFLNumber">
4597+ <mesh name="VelocityMesh"/>
4598+ </courant_number>
4599+ <minimum_timestep>
4600+ <real_value rank="0">0.001</real_value>
4601+ </minimum_timestep>
4602+ <increase_tolerance>
4603+ <real_value rank="0">1.1</real_value>
4604+ </increase_tolerance>
4605+ </adaptive_timestep>
4606+ </timestepping>
4607+ <material_phase name="Gas">
4608+ <equation_of_state>
4609+ <compressible>
4610+ <stiffened_gas>
4611+ <ratio_specific_heats>
4612+ <real_value rank="0">1.33</real_value>
4613+ </ratio_specific_heats>
4614+ </stiffened_gas>
4615+ </compressible>
4616+ </equation_of_state>
4617+ <scalar_field name="Pressure" rank="0">
4618+ <prognostic>
4619+ <mesh name="PressureMesh"/>
4620+ <spatial_discretisation>
4621+ <continuous_galerkin>
4622+ <remove_stabilisation_term/>
4623+ <integrate_continuity_by_parts/>
4624+ </continuous_galerkin>
4625+ </spatial_discretisation>
4626+ <scheme>
4627+ <poisson_pressure_solution>
4628+ <string_value lines="1">never</string_value>
4629+ </poisson_pressure_solution>
4630+ <use_compressible_projection_method/>
4631+ </scheme>
4632+ <solver>
4633+ <iterative_method name="gmres">
4634+ <restart>
4635+ <integer_value rank="0">30</integer_value>
4636+ </restart>
4637+ </iterative_method>
4638+ <preconditioner name="sor"/>
4639+ <relative_error>
4640+ <real_value rank="0">1.0e-7</real_value>
4641+ </relative_error>
4642+ <max_iterations>
4643+ <integer_value rank="0">1000</integer_value>
4644+ </max_iterations>
4645+ <never_ignore_solver_failures/>
4646+ <diagnostics>
4647+ <monitors/>
4648+ </diagnostics>
4649+ </solver>
4650+ <initial_condition name="WholeMesh">
4651+ <constant>
4652+ <real_value rank="0">101325</real_value>
4653+ </constant>
4654+ </initial_condition>
4655+ <boundary_conditions name="Right">
4656+ <surface_ids>
4657+ <integer_value shape="1" rank="1">2</integer_value>
4658+ </surface_ids>
4659+ <type name="dirichlet">
4660+ <constant>
4661+ <real_value rank="0">101325</real_value>
4662+ </constant>
4663+ </type>
4664+ </boundary_conditions>
4665+ <output/>
4666+ <stat/>
4667+ <convergence>
4668+ <include_in_convergence/>
4669+ </convergence>
4670+ <detectors>
4671+ <exclude_from_detectors/>
4672+ </detectors>
4673+ <steady_state>
4674+ <include_in_steady_state/>
4675+ </steady_state>
4676+ <no_interpolation/>
4677+ </prognostic>
4678+ </scalar_field>
4679+ <scalar_field name="Density" rank="0">
4680+ <prognostic>
4681+ <mesh name="DensityMesh"/>
4682+ <spatial_discretisation>
4683+ <control_volumes>
4684+ <face_value name="FirstOrderUpwind"/>
4685+ </control_volumes>
4686+ <conservative_advection>
4687+ <real_value rank="0">1.0</real_value>
4688+ </conservative_advection>
4689+ </spatial_discretisation>
4690+ <temporal_discretisation>
4691+ <theta>
4692+ <real_value rank="0">1.0</real_value>
4693+ </theta>
4694+ </temporal_discretisation>
4695+ <initial_condition name="WholeMesh">
4696+ <constant>
4697+ <real_value rank="0">0.757877001</real_value>
4698+ </constant>
4699+ </initial_condition>
4700+ <boundary_conditions name="Right">
4701+ <surface_ids>
4702+ <integer_value shape="1" rank="1">2</integer_value>
4703+ </surface_ids>
4704+ <type name="dirichlet">
4705+ <constant>
4706+ <real_value rank="0">0.757877001</real_value>
4707+ </constant>
4708+ </type>
4709+ </boundary_conditions>
4710+ <output/>
4711+ <stat/>
4712+ <convergence>
4713+ <include_in_convergence/>
4714+ </convergence>
4715+ <detectors>
4716+ <include_in_detectors/>
4717+ </detectors>
4718+ <steady_state>
4719+ <include_in_steady_state/>
4720+ </steady_state>
4721+ <consistent_interpolation/>
4722+ </prognostic>
4723+ </scalar_field>
4724+ <vector_field name="Velocity" rank="1">
4725+ <prognostic>
4726+ <mesh name="VelocityMesh"/>
4727+ <equation name="LinearMomentum"/>
4728+ <spatial_discretisation>
4729+ <continuous_galerkin>
4730+ <stabilisation>
4731+ <streamline_upwind_petrov_galerkin>
4732+ <nu_bar_optimal/>
4733+ <nu_scale name="0.5">
4734+ <real_value shape="1" rank="0">0.5</real_value>
4735+ </nu_scale>
4736+ </streamline_upwind_petrov_galerkin>
4737+ </stabilisation>
4738+ <mass_terms>
4739+ <lump_mass_matrix/>
4740+ </mass_terms>
4741+ <advection_terms/>
4742+ <stress_terms>
4743+ <stress_form/>
4744+ </stress_terms>
4745+ </continuous_galerkin>
4746+ <conservative_advection>
4747+ <real_value rank="0">0</real_value>
4748+ </conservative_advection>
4749+ </spatial_discretisation>
4750+ <temporal_discretisation>
4751+ <theta>
4752+ <real_value rank="0">1.0</real_value>
4753+ </theta>
4754+ <relaxation>
4755+ <real_value rank="0">0.5</real_value>
4756+ </relaxation>
4757+ </temporal_discretisation>
4758+ <solver>
4759+ <iterative_method name="gmres">
4760+ <restart>
4761+ <integer_value rank="0">30</integer_value>
4762+ </restart>
4763+ </iterative_method>
4764+ <preconditioner name="sor"/>
4765+ <relative_error>
4766+ <real_value rank="0">1.0e-7</real_value>
4767+ </relative_error>
4768+ <max_iterations>
4769+ <integer_value rank="0">1000</integer_value>
4770+ </max_iterations>
4771+ <never_ignore_solver_failures/>
4772+ <diagnostics>
4773+ <monitors/>
4774+ </diagnostics>
4775+ </solver>
4776+ <initial_condition name="WholeMesh">
4777+ <constant>
4778+ <real_value shape="1" dim1="dim" rank="1">0</real_value>
4779+ </constant>
4780+ </initial_condition>
4781+ <boundary_conditions name="Left">
4782+ <surface_ids>
4783+ <integer_value shape="1" rank="1">1</integer_value>
4784+ </surface_ids>
4785+ <type name="dirichlet">
4786+ <align_bc_with_cartesian>
4787+ <x_component>
4788+ <constant>
4789+ <real_value rank="0">0</real_value>
4790+ </constant>
4791+ </x_component>
4792+ </align_bc_with_cartesian>
4793+ </type>
4794+ </boundary_conditions>
4795+ <tensor_field name="Viscosity" rank="2">
4796+ <prescribed>
4797+ <value name="WholeMesh">
4798+ <anisotropic_asymmetric>
4799+ <constant>
4800+ <real_value symmetric="false" dim2="dim" shape="1 1" dim1="dim" rank="2">1.85e-5</real_value>
4801+ </constant>
4802+ </anisotropic_asymmetric>
4803+ </value>
4804+ <output/>
4805+ </prescribed>
4806+ </tensor_field>
4807+ <output/>
4808+ <stat>
4809+ <include_in_stat/>
4810+ <previous_time_step>
4811+ <exclude_from_stat/>
4812+ </previous_time_step>
4813+ <nonlinear_field>
4814+ <exclude_from_stat/>
4815+ </nonlinear_field>
4816+ </stat>
4817+ <convergence>
4818+ <include_in_convergence/>
4819+ </convergence>
4820+ <detectors>
4821+ <include_in_detectors/>
4822+ </detectors>
4823+ <steady_state>
4824+ <include_in_steady_state/>
4825+ </steady_state>
4826+ <consistent_interpolation/>
4827+ </prognostic>
4828+ </vector_field>
4829+ <scalar_field name="CFLNumber" rank="0">
4830+ <diagnostic>
4831+ <algorithm name="Internal" material_phase_support="multiple"/>
4832+ <mesh name="VelocityMesh"/>
4833+ <output/>
4834+ <stat/>
4835+ <convergence>
4836+ <include_in_convergence/>
4837+ </convergence>
4838+ <detectors>
4839+ <include_in_detectors/>
4840+ </detectors>
4841+ <steady_state>
4842+ <include_in_steady_state/>
4843+ </steady_state>
4844+ </diagnostic>
4845+ </scalar_field>
4846+ <scalar_field name="InternalEnergy" rank="0">
4847+ <prognostic>
4848+ <mesh name="PressureMesh"/>
4849+ <equation name="InternalEnergy">
4850+ <density name="Density">
4851+ <discretisation_options>
4852+ <spatial_discretisation>
4853+ <control_volumes>
4854+ <face_value name="FirstOrderUpwind"/>
4855+ </control_volumes>
4856+ </spatial_discretisation>
4857+ <temporal_discretisation>
4858+ <theta>
4859+ <real_value rank="0">1.0</real_value>
4860+ </theta>
4861+ <control_volumes/>
4862+ </temporal_discretisation>
4863+ </discretisation_options>
4864+ </density>
4865+ </equation>
4866+ <spatial_discretisation>
4867+ <control_volumes>
4868+ <face_value name="FirstOrderUpwind"/>
4869+ <diffusion_scheme name="ElementGradient"/>
4870+ </control_volumes>
4871+ <conservative_advection>
4872+ <real_value rank="0">0.0</real_value>
4873+ </conservative_advection>
4874+ </spatial_discretisation>
4875+ <temporal_discretisation>
4876+ <theta>
4877+ <real_value rank="0">1.0</real_value>
4878+ </theta>
4879+ </temporal_discretisation>
4880+ <solver>
4881+ <iterative_method name="gmres">
4882+ <restart>
4883+ <integer_value rank="0">30</integer_value>
4884+ </restart>
4885+ </iterative_method>
4886+ <preconditioner name="sor"/>
4887+ <relative_error>
4888+ <real_value rank="0">1.0e-7</real_value>
4889+ </relative_error>
4890+ <max_iterations>
4891+ <integer_value rank="0">1000</integer_value>
4892+ </max_iterations>
4893+ <never_ignore_solver_failures/>
4894+ <diagnostics>
4895+ <monitors/>
4896+ </diagnostics>
4897+ </solver>
4898+ <initial_condition name="WholeMesh">
4899+ <constant>
4900+ <real_value rank="0">405138.9</real_value>
4901+ </constant>
4902+ </initial_condition>
4903+ <output/>
4904+ <stat/>
4905+ <convergence>
4906+ <include_in_convergence/>
4907+ </convergence>
4908+ <detectors>
4909+ <include_in_detectors/>
4910+ </detectors>
4911+ <steady_state>
4912+ <include_in_steady_state/>
4913+ </steady_state>
4914+ <consistent_interpolation/>
4915+ </prognostic>
4916+ </scalar_field>
4917+ <scalar_field name="PhaseVolumeFraction" rank="0">
4918+ <diagnostic>
4919+ <mesh name="CoordinateMesh"/>
4920+ <algorithm name="Internal" material_phase_support="multiple"/>
4921+ <output/>
4922+ <stat/>
4923+ <detectors>
4924+ <include_in_detectors/>
4925+ </detectors>
4926+ </diagnostic>
4927+ </scalar_field>
4928+ <multiphase_properties>
4929+ <effective_conductivity>
4930+ <real_value rank="0">0.5</real_value>
4931+ </effective_conductivity>
4932+ <specific_heat>
4933+ <real_value rank="0">1406</real_value>
4934+ </specific_heat>
4935+ </multiphase_properties>
4936+ </material_phase>
4937+ <material_phase name="Particles">
4938+ <equation_of_state>
4939+ <fluids>
4940+ <linear>
4941+ <reference_density>
4942+ <real_value rank="0">2400</real_value>
4943+ </reference_density>
4944+ </linear>
4945+ </fluids>
4946+ </equation_of_state>
4947+ <scalar_field name="Pressure" rank="0">
4948+ <aliased material_phase_name="Gas" field_name="Pressure"/>
4949+ </scalar_field>
4950+ <scalar_field name="Density" rank="0">
4951+ <diagnostic>
4952+ <algorithm name="Internal" material_phase_support="multiple"/>
4953+ <mesh name="PressureMesh"/>
4954+ <output/>
4955+ <stat/>
4956+ <convergence>
4957+ <include_in_convergence/>
4958+ </convergence>
4959+ <detectors>
4960+ <include_in_detectors/>
4961+ </detectors>
4962+ <steady_state>
4963+ <include_in_steady_state/>
4964+ </steady_state>
4965+ </diagnostic>
4966+ </scalar_field>
4967+ <vector_field name="Velocity" rank="1">
4968+ <prognostic>
4969+ <mesh name="VelocityMesh"/>
4970+ <equation name="LinearMomentum"/>
4971+ <spatial_discretisation>
4972+ <continuous_galerkin>
4973+ <stabilisation>
4974+ <streamline_upwind_petrov_galerkin>
4975+ <nu_bar_optimal/>
4976+ <nu_scale name="0.5">
4977+ <real_value shape="1" rank="0">0.5</real_value>
4978+ </nu_scale>
4979+ </streamline_upwind_petrov_galerkin>
4980+ </stabilisation>
4981+ <mass_terms>
4982+ <lump_mass_matrix/>
4983+ </mass_terms>
4984+ <advection_terms/>
4985+ <stress_terms>
4986+ <tensor_form/>
4987+ </stress_terms>
4988+ </continuous_galerkin>
4989+ <conservative_advection>
4990+ <real_value rank="0">0</real_value>
4991+ </conservative_advection>
4992+ </spatial_discretisation>
4993+ <temporal_discretisation>
4994+ <theta>
4995+ <real_value rank="0">1.0</real_value>
4996+ </theta>
4997+ <relaxation>
4998+ <real_value rank="0">0.5</real_value>
4999+ </relaxation>
5000+ </temporal_discretisation>
The diff has been truncated for viewing.