Merge lp:~ctjacobs-multiphase/fluidity/compressible-multiphase into lp:fluidity

Proposed by Christian Jacobs
Status: Merged
Merged at revision: 4178
Proposed branch: lp:~ctjacobs-multiphase/fluidity/compressible-multiphase
Merge into: lp:fluidity
Diff against target: 22932 lines (+21540/-246)
66 files modified
assemble/Advection_Diffusion_CG.F90 (+41/-28)
assemble/Compressible_Projection.F90 (+1/-1)
assemble/Divergence_Matrix_CG.F90 (+1/-1)
assemble/Divergence_Matrix_CV.F90 (+15/-3)
assemble/Field_Equations_CV.F90 (+182/-85)
assemble/Makefile.dependencies (+3/-2)
assemble/Momentum_Equation.F90 (+12/-1)
main/Fluids.F90 (+1/-2)
manual/bibliography.bib (+11/-0)
manual/configuring_fluidity.tex (+9/-3)
manual/examples.tex (+17/-10)
manual/model_equations.tex (+3/-3)
schemas/prognostic_field_options.rnc (+3/-5)
schemas/prognostic_field_options.rng (+3/-5)
tests/mphase_dusty_gas_shock_tube/mphase_dusty_gas_shock_tube.flml (+5/-5)
tests/mphase_dusty_gas_shock_tube/single_phase_frozen_flow_test.flml (+5/-5)
tests/mphase_mms_p2p1_compressible_ie_heat_flux/MMS_X.flml (+1296/-0)
tests/mphase_mms_p2p1_compressible_ie_heat_flux/Makefile (+8/-0)
tests/mphase_mms_p2p1_compressible_ie_heat_flux/README (+25/-0)
tests/mphase_mms_p2p1_compressible_ie_heat_flux/copy_script (+23/-0)
tests/mphase_mms_p2p1_compressible_ie_heat_flux/function_printer.py (+40/-0)
tests/mphase_mms_p2p1_compressible_ie_heat_flux/mphase_mms_p2p1_compressible_ie.py (+141/-0)
tests/mphase_mms_p2p1_compressible_ie_heat_flux/mphase_mms_p2p1_compressible_ie.sage (+138/-0)
tests/mphase_mms_p2p1_compressible_ie_heat_flux/mphase_mms_p2p1_compressible_ie_tools.py (+68/-0)
tests/mphase_mms_p2p1_compressible_ie_heat_flux/src/MMS_A.geo (+15/-0)
tests/mphase_mms_p2p1_compressible_ie_heat_flux/src/MMS_B.geo (+15/-0)
tests/mphase_mms_p2p1_compressible_ie_heat_flux/src/MMS_C.geo (+15/-0)
tests/mphase_mms_p2p1_compressible_ie_heat_flux/src/MMS_X.geo (+18/-0)
tests/mphase_mms_p2p1_compressible_ie_p1cv/MMS_X.flml (+1235/-0)
tests/mphase_mms_p2p1_compressible_ie_p1cv/Makefile (+8/-0)
tests/mphase_mms_p2p1_compressible_ie_p1cv/copy_script (+23/-0)
tests/mphase_mms_p2p1_compressible_ie_p1cv/mphase_mms_p2p1_compressible_ie_p1cv.sage (+156/-0)
tests/mphase_mms_p2p1_compressible_ie_p1cv/mphase_mms_p2p1_compressible_ie_p1cv.xml (+142/-0)
tests/mphase_mms_p2p1_compressible_ie_p1cv/mphase_mms_p2p1_compressible_ie_p1cv_tools.py (+68/-0)
tests/mphase_mms_p2p1_compressible_ie_p1cv/src/MMS_A.geo (+15/-0)
tests/mphase_mms_p2p1_compressible_ie_p1cv/src/MMS_B.geo (+15/-0)
tests/mphase_mms_p2p1_compressible_ie_p1cv/src/MMS_C.geo (+15/-0)
tests/mphase_mms_p2p1_compressible_ie_p1cv/src/MMS_X.geo (+18/-0)
tests/mphase_mms_p2p1_compressible_ie_p1cv_heat_transfer/MMS_X.flml (+1216/-0)
tests/mphase_mms_p2p1_compressible_ie_p1cv_heat_transfer/Makefile (+8/-0)
tests/mphase_mms_p2p1_compressible_ie_p1cv_heat_transfer/copy_script (+23/-0)
tests/mphase_mms_p2p1_compressible_ie_p1cv_heat_transfer/mphase_mms_p2p1_compressible_ie_p1cv_heat_transfer.sage (+146/-0)
tests/mphase_mms_p2p1_compressible_ie_p1cv_heat_transfer/mphase_mms_p2p1_compressible_ie_p1cv_heat_transfer.xml (+142/-0)
tests/mphase_mms_p2p1_compressible_ie_p1cv_heat_transfer/mphase_mms_p2p1_compressible_ie_p1cv_heat_transfer_tools.py (+68/-0)
tests/mphase_mms_p2p1_compressible_ie_p1cv_heat_transfer/src/MMS_A.geo (+15/-0)
tests/mphase_mms_p2p1_compressible_ie_p1cv_heat_transfer/src/MMS_B.geo (+15/-0)
tests/mphase_mms_p2p1_compressible_ie_p1cv_heat_transfer/src/MMS_C.geo (+15/-0)
tests/mphase_mms_p2p1_compressible_ie_p1cv_heat_transfer/src/MMS_X.geo (+18/-0)
tests/mphase_mms_p2p1_stress_form/Makefile (+1/-1)
tests/mphase_mms_p2p1_vfrac/MMS_X.flml (+1065/-0)
tests/mphase_mms_p2p1_vfrac/Makefile (+8/-0)
tests/mphase_mms_p2p1_vfrac/copy_script (+23/-0)
tests/mphase_mms_p2p1_vfrac/mphase_mms_p2p1_vfrac.sage (+124/-0)
tests/mphase_mms_p2p1_vfrac/mphase_mms_p2p1_vfrac.xml (+134/-0)
tests/mphase_mms_p2p1_vfrac/mphase_mms_p2p1_vfrac_tools.py (+59/-0)
tests/mphase_mms_p2p1_vfrac/src/MMS_A.geo (+15/-0)
tests/mphase_mms_p2p1_vfrac/src/MMS_B.geo (+15/-0)
tests/mphase_mms_p2p1_vfrac/src/MMS_C.geo (+15/-0)
tests/mphase_mms_p2p1_vfrac/src/MMS_X.geo (+18/-0)
tests/mphase_rogue_shock_tube_dense_bed_glass/mphase_rogue_shock_tube_dense_bed_glass.flml (+58/-40)
tests/mphase_rogue_shock_tube_dense_bed_glass/mphase_rogue_shock_tube_dense_bed_glass.xml (+1/-1)
tests/mphase_rogue_shock_tube_dense_bed_glass/src/mphase_rogue_shock_tube_dense_bed_glass.msh (+7183/-0)
tests/mphase_rogue_shock_tube_dense_bed_nylon/get_cloud_front.py (+100/-0)
tests/mphase_rogue_shock_tube_dense_bed_nylon/mphase_rogue_shock_tube_dense_bed_nylon.flml (+62/-44)
tests/mphase_rogue_shock_tube_dense_bed_nylon/mphase_rogue_shock_tube_dense_bed_nylon.xml (+1/-1)
tests/mphase_rogue_shock_tube_dense_bed_nylon/src/mphase_rogue_shock_tube_dense_bed_nylon.msh (+7183/-0)
To merge this branch: bzr merge lp:~ctjacobs-multiphase/fluidity/compressible-multiphase
Reviewer Review Type Date Requested Status
Stephan Kramer Approve
Review via email: mp+130588@code.launchpad.net

Description of the change

Proposing merge of compressible-multiphase branch revisions r4078 to r4108 (inclusive) into trunk.

Summary of changes:
===================
- Added CV support for the multiphase InternalEnergy equation. This is tested with the new MMS test mphase_mms_p2p1_compressible_ie_p1cv.

- Changed -p*div(vfrac*u) to -p*vfrac*div(u) in the InternalEnergy equation.

- Added the option to include or exclude the -p*vfrac*div(u) term in the schema. This term should only be included in the fluid phase.

- Added an options check to make sure the prognostic PhaseVolumeFraction field is in the particle phase(s) only.

- Included the PhaseVolumeFraction in the Diffusivity term if we are solving the multiphase InternalEnergy equation. This allows the user to add in the heat flux term diff( k/Cv*vfrac*grad(ie) ) by specifying an isotropic diffusivity k/Cv.

- The MMS test mphase_mms_p2p1_compressible_ie_heat_flux will not be merged into the trunk, but the .flml will replace the one in longtests/mphase_mms_p2p1_compressible_ie to test the heat flux term.

To post a comment you must log in.
4109. By Christian Jacobs

Improvements to the mphase_rogue_shock_tube_dense_bed_nylon test:
- Switch to stress_form in the Gas phase.
- Include a heat flux term for the Gas phase's InternalEnergy equation.
- Set zero_flux BCs for the prognostic PhaseVolumeFraction so no particles escape.

4110. By Christian Jacobs

Added the .msh file.

4111. By Christian Jacobs

Improvements to the mphase_rogue_shock_tube_dense_bed_glass test:
- Switch to stress_form in the Gas phase.
- Include a heat flux term for the Gas phase's InternalEnergy equation.
- Set zero_flux BCs for the prognostic PhaseVolumeFraction so no particles escape.

Also added the .msh file.

4112. By Christian Jacobs

Corrected the value of k/Cv for the heat flux term.

4113. By Christian Jacobs

Switched to stress_form in the Gas phase.

4114. By Christian Jacobs

Added documentation on the heat flux term and the include_pressure_term option for the InternalEnergy field.

4115. By Christian Jacobs

Merging trunk revisions (from r4095 to r4108 inclusive) into branch.

4116. By Christian Jacobs

Merging trunk revisions (from r4109 to r4125 inclusive) into branch.

4117. By Christian Jacobs

Merging trunk revisions (from r4126 to r4134 inclusive) into branch.

4118. By Christian Jacobs

Corrected a typo in 'make clean' definition.

4119. By Christian Jacobs

Added tephra settling paper reference to the section on the tephra_settling example, and also to the section on Fluidity's incompressible multiphase flow model.

4120. By Christian Jacobs

Merging trunk revisions (from r4135 to r4144 inclusive) into branch.

4121. By Christian Jacobs

Added another compressible multiphase MMS test which, unlike the other MMS tests, uses a prognostic PhaseVolumeFraction field instead of a prescribed one.

4122. By Christian Jacobs

Added an MMS test to check the implementation of the heat transfer term by Gunn (1978). This will be moved to the longtests directory once the compressible-multiphase branch is merged with the trunk.

4123. By Christian Jacobs

Merging trunk revisions (from r4145 to r4147 inclusive) into branch.

4124. By Christian Jacobs

Added a Python script to track the position of the lower and upper front of the 2 cm particle bed in the mphase_rogue_shock_tube_dense_bed_nylon simulation.

The upper front is defined as the position where the particle PhaseVolumeFraction reaches 0.3 (approximately the same value used in the article by Rogue et al. (1998)). For the lower front, a PhaseVolumeFraction value of 0.01 is used since this area is more dilute in comparison to the upper front.

Fluidity's results do not match well with the experimental data, probably because the mesh has been kept quite coarse. Furthermore, Rogue et al. (1998) point out that "the important dilution of the cloud in the lower front area makes the comparison with the experimental position quite ambiguous", so the numerical results should be viewed with caution: http://amcg.ese.ic.ac.uk/~ctj10/images/fronts.png

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

About assemble/Advection_Diffusion_CG.F90:

I'm a bit confused what you've done with the diffusion term. In the comments you claim to implement div( (k/Cv) * vfrac * grad(ie) ). Now k an d Cv are passed down indeed (missing intent in line 531 btw) but not actually used anywhere.

About the new 'compressible' logical what is this used for? At the moment it only seems to decide whether to include the p div u term. But that's now also controlled by the include_pressure_term logical that is set by a new option. Does this mean existing single phase compressible now need to set this option as well? What happens if we're in the (non-compressible) particle phase and still set this option: at the moment it'll just ignore it, do we want an error? Afaics there are two options to determine whether to include the term: 1) we base it purely on the compressible logical and don't have an option 2) we base it purely on the new option. Hm 2) is probably too error prone and if we combine 2) with an error if the user gets it wrong then we might as well do 1). So maybe having an option wasn't such a good idea after all...thoughts?

4125. By Christian Jacobs

Merging trunk revisions (from r4148 to r4159 inclusive) into branch.

4126. By Christian Jacobs

Updated the bibliography.

4127. By Christian Jacobs

The code now includes the p*div(u) term based on the compressible logical only. The include_pressure_term option has been removed.

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

The code now includes the p*div(u) term based on the compressible logical only. The include_pressure_term option has been removed.

Regarding the diffusion term, the idea was for the user to give k/Cv in the .flml file. I've now removed the unused k and Cv variables, since k/Cv will be supplied in the 'diffusivity' tensor.

4128. By Christian Jacobs

Bug fix: use the OldPhaseVolumeFraction field here instead.

4129. By Christian Jacobs

Bug fix: there should be brackets surrounding the material_phase index in this options check.

4130. By Christian Jacobs

Merging trunk revisions (from r4160 to r4172 inclusive) into branch.

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

All looks very good. Ship it!

review: Approve
4131. By Christian Jacobs

Merging trunk revisions (from r4173 to r4177 inclusive) into branch.

Preview Diff

[H/L] Next/Prev Comment, [J/K] Next/Prev File, [N/P] Next/Prev Hunk
1=== modified file 'assemble/Advection_Diffusion_CG.F90'
2--- assemble/Advection_Diffusion_CG.F90 2012-10-04 10:51:59 +0000
3+++ assemble/Advection_Diffusion_CG.F90 2013-02-08 22:48:22 +0000
4@@ -118,6 +118,8 @@
5 logical :: move_mesh
6 ! Include porosity?
7 logical :: include_porosity
8+ ! Is this material_phase compressible?
9+ logical :: compressible = .false.
10 ! Are we running a multiphase flow simulation?
11 logical :: multiphase
12
13@@ -151,8 +153,9 @@
14
15 ! Note: the assembly of the heat transfer term is done here to avoid
16 ! passing in the whole state array to assemble_advection_diffusion_cg.
17- if(have_option("/multiphase_interaction/heat_transfer")) then
18- call add_heat_transfer(state, istate, t, matrix, rhs)
19+ if(have_option("/multiphase_interaction/heat_transfer") .and. &
20+ equation_type_index(trim(t%option_path)) == FIELD_EQUATION_INTERNALENERGY) then
21+ call add_heat_transfer(state, istate, t, matrix, rhs)
22 end if
23 call profiler_toc(t, "assembly")
24
25@@ -520,18 +523,22 @@
26 olddensity=>extract_scalar_field(state, "Old"//trim(density_name))
27 ewrite_minmax(olddensity)
28
29- if(.not.multiphase .or. have_option('/material_phase::'//trim(state%name)//&
30- &'/equation_of_state/compressible')) then
31- call get_option(trim(density%option_path)//"/prognostic/temporal_discretisation/theta", &
32- density_theta)
33+ if(have_option(trim(state%option_path)//'/equation_of_state/compressible')) then
34+ call get_option(trim(density%option_path)//"/prognostic/temporal_discretisation/theta", density_theta)
35+ compressible = .true.
36+
37+ ! We always include the p*div(u) term if this is the compressible phase.
38+ pressure=>extract_scalar_field(state, "Pressure")
39+ ewrite_minmax(pressure)
40 else
41 ! Since the particle phase is always incompressible then its Density
42 ! will not be prognostic. Just use a fixed theta value of 1.0.
43 density_theta = 1.0
44+ compressible = .false.
45+
46+ ! Don't include the p*div(u) term if this is the incompressible particle phase.
47+ pressure => dummydensity
48 end if
49-
50- pressure=>extract_scalar_field(state, "Pressure")
51- ewrite_minmax(pressure)
52
53 case(FIELD_EQUATION_KEPSILON)
54 ewrite(2,*) "Solving k-epsilon equation"
55@@ -860,7 +867,7 @@
56 if(have_absorption) call add_absorption_element_cg(ele, test_function, t, absorption, detwei, matrix_addto, rhs_addto)
57
58 ! Diffusivity
59- if(have_diffusivity) call add_diffusivity_element_cg(ele, t, diffusivity, dt_t, detwei, matrix_addto, rhs_addto)
60+ if(have_diffusivity) call add_diffusivity_element_cg(ele, t, diffusivity, dt_t, nvfrac, detwei, matrix_addto, rhs_addto)
61
62 ! Source
63 if(have_source .and. (.not. add_src_directly_to_rhs)) then
64@@ -868,9 +875,10 @@
65 end if
66
67 ! Pressure
68- if(equation_type==FIELD_EQUATION_INTERNALENERGY) call add_pressurediv_element_cg(ele, test_function, t, &
69- velocity, pressure, nvfrac, &
70- du_t, dnvfrac_t, detwei, rhs_addto)
71+ if(equation_type==FIELD_EQUATION_INTERNALENERGY .and. compressible) then
72+ call add_pressurediv_element_cg(ele, test_function, t, velocity, pressure, nvfrac, du_t, detwei, rhs_addto)
73+ end if
74+
75
76 ! Step 4: Insertion
77
78@@ -1187,9 +1195,9 @@
79
80 end subroutine add_absorption_element_cg
81
82- subroutine add_diffusivity_element_cg(ele, t, diffusivity, dt_t, detwei, matrix_addto, rhs_addto)
83+ subroutine add_diffusivity_element_cg(ele, t, diffusivity, dt_t, nvfrac, detwei, matrix_addto, rhs_addto)
84 integer, intent(in) :: ele
85- type(scalar_field), intent(in) :: t
86+ type(scalar_field), intent(in) :: t, nvfrac
87 type(tensor_field), intent(in) :: diffusivity
88 real, dimension(ele_loc(t, ele), ele_ngi(t, ele), mesh_dim(t)), intent(in) :: dt_t
89 real, dimension(ele_ngi(t, ele)), intent(in) :: detwei
90@@ -1202,9 +1210,22 @@
91 assert(have_diffusivity)
92
93 diffusivity_gi = ele_val_at_quad(diffusivity, ele)
94+
95 if(isotropic_diffusivity) then
96- assert(size(diffusivity_gi, 1) > 0)
97- diffusivity_mat = dshape_dot_dshape(dt_t, dt_t, detwei * diffusivity_gi(1, 1, :))
98+ assert(size(diffusivity_gi, 1) > 0)
99+
100+ if(multiphase .and. equation_type==FIELD_EQUATION_INTERNALENERGY) then
101+ ! This allows us to use the Diffusivity term as the heat flux term
102+ ! in the multiphase InternalEnergy equation: div( (k/Cv) * vfrac * grad(ie) ).
103+ ! The user needs to input k/Cv for the prescribed diffusivity,
104+ ! where k is the effective conductivity and Cv is the specific heat
105+ ! at constant volume. We've assumed this will always be isotropic here.
106+ ! The division by Cv is needed because the heat flux
107+ ! is defined in terms of temperature T = ie/Cv.
108+ diffusivity_mat = dshape_dot_dshape(dt_t, dt_t, detwei * diffusivity_gi(1, 1, :) * ele_val_at_quad(nvfrac, ele))
109+ else
110+ diffusivity_mat = dshape_dot_dshape(dt_t, dt_t, detwei * diffusivity_gi(1, 1, :))
111+ end if
112 else
113 diffusivity_mat = dshape_tensor_dshape(dt_t, diffusivity_gi, dt_t, detwei)
114 end if
115@@ -1215,7 +1236,7 @@
116
117 end subroutine add_diffusivity_element_cg
118
119- subroutine add_pressurediv_element_cg(ele, test_function, t, velocity, pressure, nvfrac, du_t, dnvfrac_t, detwei, rhs_addto)
120+ subroutine add_pressurediv_element_cg(ele, test_function, t, velocity, pressure, nvfrac, du_t, detwei, rhs_addto)
121
122 integer, intent(in) :: ele
123 type(element_type), intent(in) :: test_function
124@@ -1224,23 +1245,15 @@
125 type(scalar_field), intent(in) :: pressure
126 type(scalar_field), intent(in) :: nvfrac
127 real, dimension(ele_loc(velocity, ele), ele_ngi(velocity, ele), mesh_dim(t)), intent(in) :: du_t
128- real, dimension(:, :, :), intent(in) :: dnvfrac_t
129 real, dimension(ele_ngi(t, ele)), intent(in) :: detwei
130 real, dimension(ele_loc(t, ele)), intent(inout) :: rhs_addto
131
132- real, dimension(velocity%dim, ele_ngi(t, ele)) :: nvfracgrad_at_quad
133- real, dimension(ele_ngi(t, ele)) :: udotgradnvfrac_at_quad
134-
135 assert(equation_type==FIELD_EQUATION_INTERNALENERGY)
136 assert(ele_ngi(pressure, ele)==ele_ngi(t, ele))
137
138 if(multiphase) then
139- ! -p * (div(vfrac*nu))
140- nvfracgrad_at_quad = ele_grad_at_quad(nvfrac, ele, dnvfrac_t)
141- udotgradnvfrac_at_quad = sum(nvfracgrad_at_quad*ele_val_at_quad(velocity, ele), 1)
142-
143- rhs_addto = rhs_addto - ( shape_rhs(test_function, ele_div_at_quad(velocity, ele, du_t) * ele_val_at_quad(nvfrac, ele) * ele_val_at_quad(pressure, ele) * detwei) &
144- + shape_rhs(test_function, udotgradnvfrac_at_quad * ele_val_at_quad(pressure, ele) * detwei) )
145+ ! -p * vfrac * div(nu)
146+ rhs_addto = rhs_addto - shape_rhs(test_function, ele_div_at_quad(velocity, ele, du_t) * ele_val_at_quad(pressure, ele) * detwei * ele_val_at_quad(nvfrac, ele))
147 else
148 rhs_addto = rhs_addto - shape_rhs(test_function, ele_div_at_quad(velocity, ele, du_t) * ele_val_at_quad(pressure, ele) * detwei)
149 end if
150
151=== modified file 'assemble/Compressible_Projection.F90'
152--- assemble/Compressible_Projection.F90 2012-08-03 11:18:57 +0000
153+++ assemble/Compressible_Projection.F90 2013-02-08 22:48:22 +0000
154@@ -671,7 +671,7 @@
155 integer:: i
156
157 do i=0, option_count("/material_phase")-1
158- prognostic_pressure_path="/material_phase"//int2str(i)//"/scalar_field::Pressure/prognostic"
159+ prognostic_pressure_path="/material_phase["//int2str(i)//"]/scalar_field::Pressure/prognostic"
160 if (have_option(trim(prognostic_pressure_path)//"/spatial_discretisation/discontinuous_galerkin") &
161 .and. have_option(trim(prognostic_pressure_path)//"/scheme/use_compressible_projection_method")) then
162 FLExit("With a DG pressure you cannot have use_compressible_projection_method")
163
164=== modified file 'assemble/Divergence_Matrix_CG.F90'
165--- assemble/Divergence_Matrix_CG.F90 2012-08-08 19:51:41 +0000
166+++ assemble/Divergence_Matrix_CG.F90 2013-02-08 22:48:22 +0000
167@@ -629,7 +629,7 @@
168 ! If the field and nvfrac meshes are different, then we need to
169 ! compute the derivatives of the nvfrac shape functions.
170 if(.not.(nvfrac%mesh == field%mesh)) then
171- nvfrac_shape => ele_shape(nvfrac%mesh, ele)
172+ nvfrac_shape => ele_shape(nvfrac, ele)
173 call transform_to_physical(coordinate, ele, nvfrac_shape, dshape=dnvfrac_t)
174 else
175 dnvfrac_t = dfield_t
176
177=== modified file 'assemble/Divergence_Matrix_CV.F90'
178--- assemble/Divergence_Matrix_CV.F90 2011-11-25 13:09:24 +0000
179+++ assemble/Divergence_Matrix_CV.F90 2013-02-08 22:48:22 +0000
180@@ -57,7 +57,7 @@
181 !************************************************************************
182 subroutine assemble_divergence_matrix_cv(CT_m, state, ct_rhs, &
183 test_mesh, field, &
184- get_ct, exclude_boundaries)
185+ get_ct, exclude_boundaries, include_vfrac)
186
187 ! inputs/outputs
188 ! bucket full of fields
189@@ -74,6 +74,7 @@
190
191 logical, intent(in), optional :: get_ct
192 logical, intent(in), optional :: exclude_boundaries
193+ logical, intent(in), optional :: include_vfrac
194
195 ! local
196 ! degree of quadrature over cv faces
197@@ -109,7 +110,7 @@
198 real, dimension(:,:,:), allocatable :: ct_mat_local, ct_mat_local_bdy
199 real, dimension(:,:), allocatable :: ct_rhs_local
200
201- logical :: l_get_ct
202+ logical :: l_get_ct, l_include_vfrac
203
204 !! Multiphase variables
205 logical :: multiphase
206@@ -138,6 +139,17 @@
207 else
208 l_get_ct = .true.
209 end if
210+
211+ ! In some cases we might not want to include the PhaseVolumeFraction
212+ ! field in the divergence matrix, even though we are running a multiphase
213+ ! flow simulation.
214+ ! For example, in the InternalEnergy equation we just want
215+ ! div(u), not div(vfrac*u).
216+ if(present(include_vfrac)) then
217+ l_include_vfrac = include_vfrac
218+ else
219+ l_include_vfrac = .true.
220+ end if
221
222 x=>extract_vector_field(state, "Coordinate")
223 allocate(x_ele(x%dim,x%mesh%shape%loc))
224@@ -154,7 +166,7 @@
225 quaddegree=quaddegree)
226
227 ! Check if we need to multiply through by the non-linear volume fraction
228- if(option_count("/material_phase/vector_field::Velocity/prognostic") > 1) then
229+ if(option_count("/material_phase/vector_field::Velocity/prognostic") > 1 .and. l_include_vfrac) then
230 multiphase = .true.
231
232 vfrac => extract_scalar_field(state, "PhaseVolumeFraction")
233
234=== modified file 'assemble/Field_Equations_CV.F90'
235--- assemble/Field_Equations_CV.F90 2012-10-04 10:51:59 +0000
236+++ assemble/Field_Equations_CV.F90 2013-02-08 22:48:22 +0000
237@@ -56,6 +56,7 @@
238 use field_options
239 use state_fields_module
240 use porous_media
241+ use multiphase_module
242
243 implicit none
244
245@@ -93,11 +94,13 @@
246 logical :: assemble_advection_matrix = .true.
247 ! diffusion?
248 logical :: assemble_diffusion = .false.
249+ ! Are we running a multiphase flow simulation?
250+ logical :: multiphase = .false.
251
252 contains
253 !************************************************************************
254 ! solution wrapping subroutines
255- subroutine solve_field_eqn_cv(field_name, state, global_it)
256+ subroutine solve_field_eqn_cv(field_name, state, istate, global_it)
257 !!< Construct and solve the advection-diffusion equation for the given
258 !!< field using control volumes.
259
260@@ -105,6 +108,7 @@
261 character(len=*), intent(in) :: field_name
262 !! Collection of fields defining system state.
263 type(state_type), dimension(:), intent(inout) :: state
264+ integer, intent(in) :: istate ! The material_phase index in which the field called field_name is in.
265 ! global iteration number - passed in so it can be output to file
266 integer, intent(in) :: global_it
267
268@@ -199,6 +203,9 @@
269 !! Temporary pointer to the material_phase's Velocity field
270 type(vector_field), pointer :: temp_velocity_ptr
271 character(len=FIELD_NAME_LEN) :: velocity_equation_type
272+ ! Volume fraction fields for multiphase flow simulation
273+ type(scalar_field), pointer :: vfrac, oldvfrac
274+ type(scalar_field) :: nvfrac ! Non-linear version
275
276 ! assume explicitness?
277 logical :: explicit
278@@ -210,20 +217,20 @@
279 character(len=OPTION_PATH_LEN), dimension(1) :: tdensity_option_path_array
280
281 ewrite(2,*) 'in solve_field_eqn_cv'
282- ewrite(2,*) 'solving for '//field_name//' in state '//trim(state(1)%name)
283+ ewrite(2,*) 'solving for '//field_name//' in state '//trim(state(istate)%name)
284
285 ! extract lots of fields:
286 ! the actual thing we're trying to solve for
287- tfield=>extract_scalar_field(state(1), trim(field_name))
288+ tfield=>extract_scalar_field(state(istate), trim(field_name))
289 ewrite_minmax(tfield)
290 option_path=tfield%option_path
291 ! its previous timelevel - if we're doing more than one iteration per timestep!
292- oldtfield=>extract_scalar_field(state(1), "Old"//trim(field_name))
293+ oldtfield=>extract_scalar_field(state(istate), "Old"//trim(field_name))
294 ! because fluidity resets tfield to oldtfield at the start of every
295 ! global iteration we need to undo this so that the control volume faces
296 ! are discretised using the most up to date values
297 ! therefore extract the iterated values:
298- it_tfield=>extract_scalar_field(state(1), "Iterated"//trim(field_name))
299+ it_tfield=>extract_scalar_field(state(istate), "Iterated"//trim(field_name))
300 ! and set tfield to them:
301 call set(tfield, it_tfield)
302 ewrite_minmax(tfield)
303@@ -253,6 +260,21 @@
304 call allocate(dummydensity, tfield%mesh, name="DummyDensity", field_type=FIELD_TYPE_CONSTANT)
305 call set(dummydensity, 1.0)
306 dummydensity%option_path = " "
307+
308+ ! PhaseVolumeFraction for multiphase flow simulations
309+ if(option_count("/material_phase/vector_field::Velocity/prognostic") > 1) then
310+ multiphase = .true.
311+ vfrac => extract_scalar_field(state(istate), "PhaseVolumeFraction")
312+ call allocate(nvfrac, vfrac%mesh, "NonlinearPhaseVolumeFraction")
313+ call zero(nvfrac)
314+ call get_nonlinear_volume_fraction(state(istate), nvfrac)
315+
316+ ewrite_minmax(nvfrac)
317+
318+ oldvfrac => extract_scalar_field(state(istate), "OldPhaseVolumeFraction")
319+ else
320+ multiphase = .false.
321+ end if
322
323 ! find out equation type and hence if density is needed or not
324 equation_type=equation_type_index(trim(option_path))
325@@ -266,16 +288,18 @@
326
327 case(FIELD_EQUATION_KEPSILON)
328 ! Depending on the equation type, extract the density or set it to some dummy field allocated above
329- temp_velocity_ptr => extract_vector_field(state(1), "Velocity")
330+ temp_velocity_ptr => extract_vector_field(state(istate), "Velocity")
331 call get_option(trim(temp_velocity_ptr%option_path)//"/prognostic/equation[0]/name", velocity_equation_type)
332 select case(velocity_equation_type)
333 case("LinearMomentum")
334 include_density = .true.
335- tdensity=>extract_scalar_field(state(1), "Density")
336- oldtdensity=>extract_scalar_field(state(1), "OldDensity")
337+ tdensity=>extract_scalar_field(state(istate), "Density")
338+ oldtdensity=>extract_scalar_field(state(istate), "OldDensity")
339
340 if(have_option(trim(tdensity%option_path)//"/prognostic")) then
341 prognostic_density = .true.
342+ else
343+ prognostic_density = .false.
344 end if
345 case("Boussinesq")
346 tdensity => dummydensity
347@@ -296,16 +320,18 @@
348 ! density needed so extract the type specified in the input
349 ! ?? are there circumstances where this should be "Iterated"... need to be
350 ! careful with priority ordering
351- tdensity=>extract_scalar_field(state(1), trim(tmpstring))
352+ tdensity=>extract_scalar_field(state(istate), trim(tmpstring))
353 ewrite_minmax(tdensity)
354
355 ! halo exchange? - not currently necessary when suboptimal halo exchange if density
356 ! is solved for with this subroutine and the correct priority ordering.
357- oldtdensity=>extract_scalar_field(state(1), "Old"//trim(tmpstring))
358+ oldtdensity=>extract_scalar_field(state(istate), "Old"//trim(tmpstring))
359 ewrite_minmax(oldtdensity)
360
361 if(have_option(trim(tdensity%option_path)//"/prognostic")) then
362 prognostic_density = .true.
363+ else
364+ prognostic_density = .false.
365 end if
366 end select
367
368@@ -326,14 +352,18 @@
369 ! handily wrapped in a new type...
370 tfield_options=get_cv_options(tfield%option_path, tfield%mesh%shape%numbering%family, mesh_dim(tfield))
371 if(include_density) then
372- tdensity_options=get_cv_options(tdensity_option_path, tdensity%mesh%shape%numbering%family, mesh_dim(tdensity), coefficient_field=.true.)
373+ if(prognostic_density) then
374+ tdensity_options=get_cv_options(tdensity_option_path, tdensity%mesh%shape%numbering%family, mesh_dim(tdensity), coefficient_field=.true.)
375+ else
376+ tdensity_options=tfield_options
377+ end if
378 end if
379
380 ! extract fields from state
381 ! the base Coordinate field
382- x=>extract_vector_field(state(1), "Coordinate")
383+ x=>extract_vector_field(state(istate), "Coordinate")
384 ! the Coordinate field on the same mesh as tfield
385- x_tfield=get_coordinate_field(state(1), tfield%mesh)
386+ x_tfield=get_coordinate_field(state(istate), tfield%mesh)
387
388 ! are we including the mass (generally yes)?
389 include_mass = .not.have_option(trim(tfield%option_path)//"/prognostic/spatial_discretisation/control_volumes/mass_terms/exclude_mass_terms")
390@@ -341,7 +371,7 @@
391 ! are we inclulding advection (generally yes)?
392 include_advection = .not.(tfield_options%facevalue==CV_FACEVALUE_NONE)
393 if(include_advection) then
394- nu=>extract_vector_field(state(1), "NonlinearVelocity")
395+ nu=>extract_vector_field(state(istate), "NonlinearVelocity")
396 ewrite_minmax(nu)
397 ! find relative velocity
398 allocate(advu)
399@@ -354,10 +384,10 @@
400 ewrite(2,*) "Removing velocity from ", trim(field_name)
401 end if
402 ! add in sinking velocity
403- sink=>extract_scalar_field(state(1), trim(field_name)//"SinkingVelocity"&
404+ sink=>extract_scalar_field(state(istate), trim(field_name)//"SinkingVelocity"&
405 &, stat=stat)
406 if(stat==0) then
407- gravity=>extract_vector_field(state(1), "GravityDirection")
408+ gravity=>extract_vector_field(state(istate), "GravityDirection")
409 ! this may perform a "remap" internally from CoordinateMesh to VelocityMesh
410 call addto(advu, gravity, scale=sink)
411 end if
412@@ -365,7 +395,7 @@
413 else
414 ewrite(2,*) 'Excluding advection'
415 advu => dummyvector
416- if(has_scalar_field(state(1), trim(field_name)//"SinkingVelocity")) then
417+ if(has_scalar_field(state(istate), trim(field_name)//"SinkingVelocity")) then
418 ewrite(-1,*) "No advection in "//trim(field_name)
419 FLExit("But you have a sinking velocity on. Can't have that")
420 end if
421@@ -374,7 +404,7 @@
422 ! do we have a diffusivity - this will control whether we construct an auxiliary
423 ! eqn or not (if BassiRebay is selected) or whether we construct gradients (if ElementGradient
424 ! is selected)
425- diffusivity=>extract_tensor_field(state(1), trim(field_name)//"Diffusivity", stat=stat)
426+ diffusivity=>extract_tensor_field(state(istate), trim(field_name)//"Diffusivity", stat=stat)
427 include_diffusion = (stat==0).and.(tfield_options%diffusionscheme/=CV_DIFFUSION_NONE)
428 if(.not.include_diffusion) then
429 diffusivity => dummytensor
430@@ -383,7 +413,7 @@
431 end if
432
433 ! do we have a source?
434- source=>extract_scalar_field(state(1), trim(field_name)//"Source", stat=stat)
435+ source=>extract_scalar_field(state(istate), trim(field_name)//"Source", stat=stat)
436 include_source = (stat==0)
437 if(.not.include_source) then
438 source=>dummyscalar
439@@ -399,7 +429,7 @@
440 end if
441
442 ! do we have an absorption?
443- absorption=>extract_scalar_field(state(1), trim(field_name)//"Absorption", stat=stat)
444+ absorption=>extract_scalar_field(state(istate), trim(field_name)//"Absorption", stat=stat)
445 include_absorption = (stat==0)
446 if(.not.include_absorption) then
447 absorption=>dummyscalar
448@@ -471,7 +501,7 @@
449 option_path_array(1) = trim(option_path) ! temporary hack for compiler failure
450 tdensity_option_path_array(1) = tdensity_option_path
451 call cv_disc_get_cfl_no(option_path_array, &
452- state(1), tfield%mesh, cfl_no, &
453+ state(istate), tfield%mesh, cfl_no, &
454 tdensity_option_path_array)
455
456 ! get the mesh sparsity for the matrices
457@@ -553,7 +583,7 @@
458 include_porosity = .true.
459
460 ! get the porosity theta averaged field - this will allocate it
461- call form_porosity_theta(porosity_theta, state(1), &
462+ call form_porosity_theta(porosity_theta, state(istate), &
463 &option_path = trim(complete_field_path(tfield%option_path))//'/porosity')
464
465 call allocate(t_cvmass_with_porosity, tfield%mesh, name="CVMassWithPorosity")
466@@ -586,8 +616,8 @@
467 FLExit("Moving mesh not set up to work when including porosity")
468 end if
469 ewrite(2,*) "Moving mesh."
470- x_old=>extract_vector_field(state(1), "OldCoordinate")
471- x_new=>extract_vector_field(state(1), "IteratedCoordinate")
472+ x_old=>extract_vector_field(state(istate), "OldCoordinate")
473+ x_new=>extract_vector_field(state(istate), "IteratedCoordinate")
474 call allocate(t_cvmass_old, tfield%mesh, name=trim(field_name)//"OldCVMass")
475 call allocate(t_cvmass_new, tfield%mesh, name=trim(field_name)//"NewCVMass")
476
477@@ -596,7 +626,7 @@
478 ewrite_minmax(t_cvmass_old)
479 ewrite_minmax(t_cvmass_new)
480
481- ug=>extract_vector_field(state(1), "GridVelocity")
482+ ug=>extract_vector_field(state(istate), "GridVelocity")
483 ewrite_minmax(ug)
484
485 ug_cvshape=make_cv_element_shape(cvfaces, ug%mesh%shape)
486@@ -702,14 +732,14 @@
487 ! diffusion matrix then assemble A_m, D_m and rhs here
488 call assemble_advectiondiffusion_m_cv(A_m, rhs, D_m, diff_rhs, &
489 tfield, l_old_tfield, tfield_options, &
490- tdensity, oldtdensity, tdensity_options, &
491- cvfaces, x_cvshape, x_cvbdyshape, &
492+ tdensity, oldtdensity, nvfrac, oldvfrac, &
493+ tdensity_options, cvfaces, x_cvshape, x_cvbdyshape, &
494 u_cvshape, u_cvbdyshape, t_cvshape, &
495 ug_cvshape, ug_cvbdyshape, &
496 x_cvshape_full, x_cvbdyshape_full, &
497 t_cvshape_full, t_cvbdyshape_full, &
498 diff_cvshape_full, diff_cvbdyshape_full, &
499- state, advu, ug, x, x_tfield, cfl_no, sub_dt, &
500+ state(istate:istate), advu, ug, x, x_tfield, cfl_no, sub_dt, &
501 diffusivity, q_cvmass, &
502 mesh_sparsity_x, grad_m_t_sparsity)
503 end if
504@@ -719,10 +749,14 @@
505 tfield, l_old_tfield, &
506 tdensity, oldtdensity, tdensity_options, &
507 source, absorption, tfield_options%theta, &
508- state, advu, sub_dt, explicit, &
509+ state(istate:istate), advu, sub_dt, explicit, &
510 t_cvmass, t_abs_src_cvmass, t_cvmass_old, t_cvmass_new, &
511- D_m, diff_rhs)
512+ D_m, diff_rhs, nvfrac, oldvfrac)
513
514+ if(have_option("/multiphase_interaction/heat_transfer") .and. &
515+ equation_type_index(trim(tfield%option_path)) == FIELD_EQUATION_INTERNALENERGY) then
516+ call add_heat_transfer(state, istate, tfield, M, rhs)
517+ end if
518
519 ! Solve for the change in tfield.
520 if(explicit) then
521@@ -736,7 +770,7 @@
522 call apply_dirichlet_conditions(M, rhs, tfield, sub_dt)
523
524 call zero(delta_tfield)
525- call petsc_solve(delta_tfield, M, rhs, state(1))
526+ call petsc_solve(delta_tfield, M, rhs, state(istate))
527 end if
528
529 ! reset tfield to l_old_tfield before applying change
530@@ -747,7 +781,7 @@
531 call halo_update(tfield) ! exchange the extended halos
532
533 call test_and_write_advection_convergence(tfield, advit_tfield, x, t_cvmass, &
534- filename=trim(state(1)%name)//"__"//trim(tfield%name), &
535+ filename=trim(state(istate)%name)//"__"//trim(tfield%name), &
536 time=time+sub_dt, dt=sub_dt, it=global_it, adv_it=adv_it, &
537 subcyc=sub, error=error)
538
539@@ -806,6 +840,9 @@
540 if (include_porosity) then
541 call deallocate(t_cvmass_with_porosity)
542 end if
543+ if(multiphase) then
544+ call deallocate(nvfrac)
545+ end if
546
547 end subroutine solve_field_eqn_cv
548 ! end of solution wrapping subroutines
549@@ -818,7 +855,7 @@
550 source, absorption, theta, &
551 state, advu, dt, explicit, &
552 cvmass, abs_src_cvmass, cvmass_old, cvmass_new, &
553- D_m, diff_rhs)
554+ D_m, diff_rhs, nvfrac, oldvfrac)
555
556 ! This subroutine assembles the equation
557 ! M(T^{n+1}-T^{n})/\Delta T = rhs
558@@ -862,6 +899,8 @@
559 ! diffusion:
560 type(csr_matrix), intent(inout), optional :: D_m
561 type(scalar_field), intent(inout), optional :: diff_rhs
562+
563+ type(scalar_field), intent(inout), optional :: nvfrac, oldvfrac
564
565 ! local memory:
566 ! for all equation types:
567@@ -1153,38 +1192,50 @@
568 ! [\rho^{n+1}M + dt*A_m + dt*theta*D_m](T^{n+1}-T^{n})/dt = rhs - [A_m + D_m]*T^{n} - diff_rhs - (p+atm_p)*CT_m*u
569
570 ! construct rhs
571- p=>extract_scalar_field(state(1), "Pressure")
572- ewrite_minmax(p)
573- assert(p%mesh==tfield%mesh)
574- ! halo exchange not necessary as it is done straight after solve
575- call get_option(trim(p%option_path)//'/prognostic/atmospheric_pressure', &
576- atmospheric_pressure, default=0.0)
577- gradient_sparsity => get_csr_sparsity_firstorder(state, p%mesh, advu%mesh)
578-
579- call allocate(CT_m, gradient_sparsity, (/1, advu%dim/), name="DivergenceMatrix" )
580- call assemble_divergence_matrix_cv(CT_m, state(1), &
581- test_mesh=p%mesh, field=advu)
582-
583- call allocate(pterm, p%mesh, "PressureTerm")
584-
585- ! construct the pressure term
586- call mult(pterm, CT_m, advu)
587- ! should this really be the advection velocity or just the relative or the nonlinear?
588- pterm%val = pterm%val*(p%val+atmospheric_pressure)
589-
590- call addto(rhs, pterm, -1.0)
591-
592- call deallocate(CT_m)
593- call deallocate(pterm)
594-
595+ if(have_option(trim(state(1)%option_path)//'/equation_of_state/compressible')) then
596+ p=>extract_scalar_field(state(1), "Pressure")
597+ ewrite_minmax(p)
598+ assert(p%mesh==tfield%mesh)
599+ ! halo exchange not necessary as it is done straight after solve
600+ call get_option(trim(p%option_path)//'/prognostic/atmospheric_pressure', &
601+ atmospheric_pressure, default=0.0)
602+ gradient_sparsity => get_csr_sparsity_firstorder(state, p%mesh, advu%mesh)
603+
604+ call allocate(CT_m, gradient_sparsity, (/1, advu%dim/), name="DivergenceMatrix" )
605+ call assemble_divergence_matrix_cv(CT_m, state(1), &
606+ test_mesh=p%mesh, field=advu, include_vfrac=.false.)
607+
608+ call allocate(pterm, p%mesh, "PressureTerm")
609+
610+ ! construct the pressure term
611+ call mult(pterm, CT_m, advu)
612+ if(multiphase) then
613+ call scale(pterm, nvfrac) ! We need vfrac*p*div(u) for the multiphase InternalEnergy equation
614+ end if
615+
616+ ! should this really be the advection velocity or just the relative or the nonlinear?
617+ pterm%val = pterm%val*(p%val+atmospheric_pressure)
618+
619+ call addto(rhs, pterm, -1.0)
620+
621+ call deallocate(CT_m)
622+ call deallocate(pterm)
623+ end if
624+
625 ! construct M
626 if(explicit) then
627 if(include_mass) then
628 call scale(m_cvmass, tdensity)
629+ if(multiphase) then
630+ call scale(m_cvmass, nvfrac)
631+ end if
632 end if
633 else
634 if(include_mass) then
635 call mult_diag(M, tdensity)
636+ if(multiphase) then
637+ call mult_diag(M, nvfrac)
638+ end if
639 end if
640 if(include_advection) call addto(M, A_m, dt)
641 if(include_absorption) call addto_diag(M, massabsorption, theta*dt)
642@@ -1283,8 +1334,8 @@
643 ! assembly subroutines
644 subroutine assemble_advectiondiffusion_m_cv(A_m, rhs, D_m, diff_rhs, &
645 tfield, oldtfield, tfield_options, &
646- tdensity, oldtdensity, tdensity_options, &
647- cvfaces, x_cvshape, x_cvbdyshape, &
648+ tdensity, oldtdensity, nvfrac, oldvfrac, &
649+ tdensity_options, cvfaces, x_cvshape, x_cvbdyshape, &
650 u_cvshape, u_cvbdyshape, t_cvshape, &
651 ug_cvshape, ug_cvbdyshape, &
652 x_cvshape_full, x_cvbdyshape_full, &
653@@ -1346,6 +1397,9 @@
654 type(scalar_field), intent(in) :: cfl_no
655 ! timestep
656 real, intent(in) :: dt
657+
658+ type(scalar_field), intent(in) :: nvfrac, oldvfrac
659+ real, dimension(x_cvshape%ngi) :: nvfrac_gi
660
661 ! mesh sparsity for upwind value matrices
662 type(csr_sparsity), intent(in) :: mesh_sparsity
663@@ -1397,6 +1451,9 @@
664
665 ! loop integers
666 integer :: ele, sele, iloc, oloc, dloc, face, gi, ggi, dim
667+
668+ ! what equation type are we solving for?
669+ integer :: equation_type
670
671 ! upwind value matrices for the fields and densities
672 type(csr_matrix) :: tfield_upwind, &
673@@ -1551,6 +1608,12 @@
674 call transform_to_physical(X, ele, x_shape=x_cvshape_full, &
675 shape=t_cvshape_full, dshape=dt_t)
676 diffusivity_gi = ele_val_at_quad(diffusivity, ele, diff_cvshape_full)
677+
678+ equation_type = equation_type_index(trim(tfield%option_path))
679+ if(multiphase .and. equation_type==FIELD_EQUATION_INTERNALENERGY) then
680+ nvfrac_gi = ele_val_at_quad(nvfrac, ele, diff_cvshape_full)
681+ end if
682+
683 end if
684
685 cfl_ele = ele_val(cfl_no, ele)
686@@ -1561,6 +1624,11 @@
687 if(include_density) then
688 tdensity_ele = ele_val(tdensity, ele)
689 oldtdensity_ele = ele_val(oldtdensity, ele)
690+
691+ if(multiphase) then
692+ tdensity_ele = tdensity_ele*ele_val(nvfrac,ele)
693+ oldtdensity_ele = oldtdensity_ele*ele_val(oldvfrac,ele)
694+ end if
695 end if
696
697 notvisited=.true.
698@@ -1634,28 +1702,25 @@
699 ! do the same for the density but save some effort if it's just a dummy
700 select case (tdensity%field_type)
701 case(FIELD_TYPE_CONSTANT)
702-
703 tdensity_face_val = tdensity_ele(iloc)
704 oldtdensity_face_val = oldtdensity_ele(iloc)
705
706 case default
707-
708 call evaluate_face_val(tdensity_face_val, oldtdensity_face_val, &
709- iloc, oloc, ggi, upwind_nodes, &
710- t_cvshape,&
711- tdensity_ele, oldtdensity_ele, &
712- tdensity_upwind, oldtdensity_upwind, &
713- inflow, cfl_ele, &
714- tdensity_options)
715+ iloc, oloc, ggi, upwind_nodes, &
716+ t_cvshape,&
717+ tdensity_ele, oldtdensity_ele, &
718+ tdensity_upwind, oldtdensity_upwind, &
719+ inflow, cfl_ele, &
720+ tdensity_options)
721
722 end select
723-
724 tdensity_theta_val=theta_val(iloc, oloc, &
725- tdensity_face_val, &
726- oldtdensity_face_val, &
727- tdensity_options%theta, dt, udotn, &
728- xt_ele, tdensity_options%limit_theta, &
729- tdensity_ele, oldtdensity_ele)
730+ tdensity_face_val, &
731+ oldtdensity_face_val, &
732+ tdensity_options%theta, dt, udotn, &
733+ xt_ele, tdensity_options%limit_theta, &
734+ tdensity_ele, oldtdensity_ele)
735
736 if(assemble_advection_matrix) then
737 mat_local(iloc, oloc) = mat_local(iloc, oloc) &
738@@ -1731,16 +1796,35 @@
739 end do dimension_loop1
740
741 case(CV_DIFFUSION_ELEMENTGRADIENT)
742-
743- do dloc=1,size(dt_t,1)
744- ! n_i K_{ij} dT/dx_j
745- diff_mat_local(iloc,dloc) = diff_mat_local(iloc,dloc) - &
746- sum(matmul(diffusivity_gi(:,:,ggi), dt_t(dloc, ggi, :))*normgi, 1)*detwei(ggi)
747-
748- ! notvisited
749- diff_mat_local(oloc, dloc) = diff_mat_local(oloc,dloc) - &
750- sum(matmul(diffusivity_gi(:,:,ggi), dt_t(dloc, ggi, :))*(-normgi), 1)*detwei(ggi)
751- end do
752+
753+ if(multiphase .and. equation_type==FIELD_EQUATION_INTERNALENERGY) then
754+ ! This allows us to use the Diffusivity term as the heat flux term
755+ ! in the multiphase InternalEnergy equation: div( (k/Cv) * vfrac * grad(ie) ).
756+ ! The user needs to input k/Cv for the prescribed diffusivity,
757+ ! where k is the effective conductivity and Cv is the specific heat
758+ ! at constant volume. The division by Cv is needed because the heat flux
759+ ! is defined in terms of temperature T = ie/Cv.
760+
761+ do dloc=1,size(dt_t,1)
762+ ! n_i K_{ij} dT/dx_j
763+ diff_mat_local(iloc,dloc) = diff_mat_local(iloc,dloc) - &
764+ sum(matmul(diffusivity_gi(:,:,ggi), dt_t(dloc, ggi, :))*normgi, 1)*detwei(ggi)*nvfrac_gi(ggi)
765+
766+ ! notvisited
767+ diff_mat_local(oloc, dloc) = diff_mat_local(oloc,dloc) - &
768+ sum(matmul(diffusivity_gi(:,:,ggi), dt_t(dloc, ggi, :))*(-normgi), 1)*detwei(ggi)*nvfrac_gi(ggi)
769+ end do
770+ else
771+ do dloc=1,size(dt_t,1)
772+ ! n_i K_{ij} dT/dx_j
773+ diff_mat_local(iloc,dloc) = diff_mat_local(iloc,dloc) - &
774+ sum(matmul(diffusivity_gi(:,:,ggi), dt_t(dloc, ggi, :))*normgi, 1)*detwei(ggi)
775+
776+ ! notvisited
777+ diff_mat_local(oloc, dloc) = diff_mat_local(oloc,dloc) - &
778+ sum(matmul(diffusivity_gi(:,:,ggi), dt_t(dloc, ggi, :))*(-normgi), 1)*detwei(ggi)
779+ end do
780+ end if
781
782 end select
783 end if
784@@ -1854,17 +1938,30 @@
785 if(tdensity_bc_type(sele)==BC_TYPE_WEAKDIRICHLET) then
786 ghost_tdensity_ele_bdy=ele_val(tdensity_bc, sele)
787 else
788- ghost_tdensity_ele_bdy=face_val(tdensity, sele)
789+ if(multiphase) then
790+ ghost_tdensity_ele_bdy=face_val(tdensity, sele)*face_val(nvfrac, sele)
791+ else
792+ ghost_tdensity_ele_bdy=face_val(tdensity, sele)
793+ end if
794 end if
795
796 if(tdensity_bc_type(sele)==BC_TYPE_WEAKDIRICHLET) then
797 ghost_oldtdensity_ele_bdy=ele_val(tdensity_bc, sele) ! not considering time varying bcs yet
798 else
799- ghost_oldtdensity_ele_bdy=face_val(oldtdensity, sele)
800+ if(multiphase) then
801+ ghost_oldtdensity_ele_bdy=face_val(oldtdensity, sele)*face_val(oldvfrac, sele)
802+ else
803+ ghost_oldtdensity_ele_bdy=face_val(oldtdensity, sele)
804+ end if
805 end if
806
807 tdensity_ele_bdy=face_val(tdensity, sele)
808 oldtdensity_ele_bdy=face_val(oldtdensity, sele)
809+
810+ if(multiphase) then
811+ tdensity_ele_bdy=tdensity_ele_bdy*face_val(nvfrac, sele)
812+ oldtdensity_ele_bdy=oldtdensity_ele_bdy*face_val(oldvfrac, sele)
813+ end if
814 end if
815 end if
816
817
818=== modified file 'assemble/Makefile.dependencies'
819--- assemble/Makefile.dependencies 2013-01-26 18:26:38 +0000
820+++ assemble/Makefile.dependencies 2013-02-08 22:48:22 +0000
821@@ -281,8 +281,9 @@
822 ../include/diagnostic_variables.mod ../include/divergence_matrix_cv.mod \
823 ../include/fdebug.h ../include/fefields.mod ../include/field_options.mod \
824 ../include/fields.mod ../include/global_parameters.mod ../include/halos.mod \
825- ../include/parallel_tools.mod ../include/petsc_solve_state_module.mod \
826- ../include/porous_media.mod ../include/sparse_matrices_fields.mod \
827+ ../include/multiphase_module.mod ../include/parallel_tools.mod \
828+ ../include/petsc_solve_state_module.mod ../include/porous_media.mod \
829+ ../include/sparse_matrices_fields.mod \
830 ../include/sparsity_patterns_meshes.mod ../include/spud.mod \
831 ../include/state_fields_module.mod ../include/state_module.mod \
832 ../include/transform_elements.mod
833
834=== modified file 'assemble/Momentum_Equation.F90'
835--- assemble/Momentum_Equation.F90 2012-12-12 21:42:17 +0000
836+++ assemble/Momentum_Equation.F90 2013-02-08 22:48:22 +0000
837@@ -183,7 +183,7 @@
838 ! Scaled pressure mass matrix - used for preconditioning full projection solve:
839 type(csr_matrix), target :: scaled_pressure_mass_matrix
840 type(csr_sparsity), pointer :: scaled_pressure_mass_matrix_sparsity
841- ! Left hand matrix of CMC. For incompressibe flow this points to ct_m as they are identical,
842+ ! Left hand matrix of CMC. For incompressible flow this points to ct_m as they are identical,
843 ! unless for CG pressure with CV tested continuity case when this matrix will be the
844 ! CV divergence tested matrix and ct_m the CG divergence tested matrix (right hand matrix of CMC).
845 ! For compressible flow this differs to ct_m in that it will contain the variable density.
846@@ -2196,6 +2196,17 @@
847
848 end if
849
850+ ! Check that each particle phase has a PROGNOSTIC PhaseVolumeFraction field.
851+ ! The fluid phase cannot have a prognostic PhaseVolumeFraction as this is not always valid.
852+ ! For example, since we do not include the Density in the advection-diffusion equation for the PhaseVolumeFraction,
853+ ! solving this equation for the compressible fluid phase would not be correct. The particle phases on the other hand
854+ ! are always incompressible where the density is constant.
855+ if(have_option("/material_phase["//int2str(i)//"]/multiphase_properties/particle_diameter") .and. &
856+ .not.(have_option("/material_phase["//int2str(i)//"]/scalar_field::PhaseVolumeFraction/prognostic") .or. &
857+ have_option("/material_phase["//int2str(i)//"]/scalar_field::PhaseVolumeFraction/prescribed"))) then
858+ FLExit("All particle phases must have a prognostic/prescribed PhaseVolumeFraction field. The diagnostic PhaseVolumeFraction field should always be in the continuous/fluid phase.")
859+ end if
860+
861 end do
862
863 ewrite(1,*) 'Finished checking momentum discretisation options'
864
865=== modified file 'main/Fluids.F90'
866--- main/Fluids.F90 2012-10-02 11:35:46 +0000
867+++ main/Fluids.F90 2013-02-08 22:48:22 +0000
868@@ -697,8 +697,7 @@
869
870 ! Solve the pure control volume form of the equations
871 call solve_field_eqn_cv(field_name=trim(field_name_list(it)), &
872- state=state(field_state_list(it):field_state_list(it)), &
873- global_it=its)
874+ state=state, istate=field_state_list(it), global_it=its)
875
876 else if(have_option(trim(field_optionpath_list(it)) // &
877 & "/prognostic/spatial_discretisation/continuous_galerkin")) then
878
879=== modified file 'manual/bibliography.bib'
880--- manual/bibliography.bib 2012-12-04 17:19:40 +0000
881+++ manual/bibliography.bib 2013-02-08 22:48:22 +0000
882@@ -1672,6 +1672,17 @@
883 year = {2003}
884 }
885
886+@Article{ Jacobs_etal_2013,
887+ author = {Jacobs, C. T. and Collins, G. S. and Piggott, M. D. and Kramer, S. C. and Wilson, C. R. G.},
888+ title = {Multiphase flow modelling of volcanic ash particle settling in water using adaptive unstructured meshes},
889+ journal = {Geophysical Journal International},
890+ year = {2013},
891+ volume = {192},
892+ number = {2},
893+ pages = {647--665},
894+ doi = {10.1093/gji/ggs059}
895+}
896+
897 @Article{ jarrin_06,
898 author = {N. Jarrin and S. Benhamadouche and D. Laurence and R. Prosser},
899 journal = {International Journal of Heat and Fluid Flow},
900
901=== modified file 'manual/configuring_fluidity.tex'
902--- manual/configuring_fluidity.tex 2012-12-04 17:19:40 +0000
903+++ manual/configuring_fluidity.tex 2013-02-08 22:48:22 +0000
904@@ -2369,6 +2369,7 @@
905 \begin{equation}
906 \alpha_N = 1 - \sum_{i=1}^{N-1}\alpha_i\textrm{.}
907 \end{equation}
908+For compressible multiphase simulations, the diagnostic PhaseVolumeFraction field should always be in the compressible (fluid) phase. This is because we do not include the Density in the advection-diffusion equation for prognostic PhaseVolumeFraction fields, so solving this equation in the compressible phase would not be correct. The particle phases on the other hand are always incompressible where the density is constant.
909
910 \subsubsection{Inter-phase momentum interaction}
911 Currently, \fluidity\ only supports fluid-particle drag between the continuous phase and dispersed phase(s). This can be enabled by switching on the \option{/multiphase\_interaction/fluid\_particle\_drag} option in Diamond and specifying the drag correlation: Stokes, \cite{wen_yu_1966} or \cite{ergun1952}.
912@@ -2407,20 +2408,20 @@
913 This subsection considers compressible multiphase flow simulations where each phase has its own InternalEnergy field. Users can choose to include the inter-phase heat transfer term by \cite{gunn1978}, denoted $Q$ in Section \ref{sec:multiphase_equations}, on the RHS of each internal energy equation:
914
915 \begin{equation}\label{eq:gunn_heat_transfer_term}
916-Q = \frac{6 k \alpha_p \mathrm{Nu}_p}{d_p^2}\left(\frac{e_f}{C_f} - \frac{e_p}{C_p}\right),
917+Q = \frac{6 k \alpha_p \mathrm{Nu}_p}{d_p^2}\left(\frac{e_f}{C_{v,f}} - \frac{e_p}{C_{v,p}}\right),
918 \end{equation}
919 where
920 \begin{equation}
921 \mathrm{Nu}_p = \left(7 - 10\alpha_f + 5\alpha_f^2\right)\left(1 + 0.7\mathrm{Re}_p^{0.2}\mathrm{Pr}^{\frac{1}{3}}\right) + \left(1.33 - 2.4\alpha_f + 1.2\alpha_f^2\right)\mathrm{Re}_p^{0.7}\mathrm{Pr}^{\frac{1}{3}},
922 \end{equation}
923 \begin{equation}
924- \mathrm{Pr} = \frac{C_f \gamma \mu_f}{k},
925+ \mathrm{Pr} = \frac{C_{v,f} \gamma \mu_f}{k},
926 \end{equation}
927 and
928 \begin{equation}
929 \mathrm{Re} = \frac{\rho_f d_p |\mathbf{u}_f-\mathbf{u}_p|}{\mu_f},
930 \end{equation}
931-are the Nusselt, Prandtl and Reynolds number respectively. $C_i$ denotes the specific heat of phase i at constant volume, and $k$ denotes the effective conductivity of the fluid phase; these must be specified in \option{../multiphase\_properties/effective\_conductivity} and \option{../multiphase\_properties/specific\_heat}. Note that we have written the above in terms of internal energy (rather than temperature) by dividing $e_i$ by the specific heat at constant volume.
932+are the Nusselt, Prandtl and Reynolds number respectively. $C_{v,i}$ denotes the specific heat of phase i at constant volume, and $k$ denotes the effective conductivity of the fluid phase; these must be specified in \option{../multiphase\_properties/effective\_conductivity} and \option{../multiphase\_properties/specific\_heat}. Note that we have written the above in terms of internal energy (rather than temperature) by dividing $e_i$ by the specific heat at constant volume.
933
934 To include this term, switch on the \option{/multiphase\_interaction/heat\_transfer} option in Diamond.
935
936@@ -2463,6 +2464,11 @@
937 \item in the presence of viscosity \option{\ldots/spatial\_discretisation/continuous\_galerkin/stress\_terms/stress\_form} is required and all components of the anisotropic symmetric Viscosity tensor should be filled out. This functionality is only available with continuous Galerkin velocities.
938 \end{itemize}
939
940+\subsection{InternalEnergy options}
941+\begin{itemize}
942+\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.
943+\end{itemize}
944+
945 \subsection{Restrictions: discretisation options and element pairs}
946 Either continuous Galerkin or control volumes can be used as discretisation options for pressure and density (both fields need to have the same option). When using control volumes pressure and density have to be on the same order of parent mesh.
947
948
949=== modified file 'manual/examples.tex'
950--- manual/examples.tex 2012-10-29 14:48:22 +0000
951+++ manual/examples.tex 2013-02-08 22:48:22 +0000
952@@ -307,7 +307,8 @@
953 \begin{equation}
954 E_b = \int \rho(z_*) g z_* \, dz_* \, ,
955 \end{equation}
956-where $g$ is gravity and $\rho$ the density. Most crucially, for a closed system, the background potential energy can only be altered by diapycnal mixing and increases in the background potential energy correspond to mixing in the system. The reference state is calculated using the method of \citet{tseng2001} which uses a probability density function to calculate the value of $z_*$ associated with a given $\rho$ (or here temperature). Here the probability density function is obtained from a set of `mixing bins'. Each mixing bin contains the fraction of fluid in the domain that has temperature within a given range or `class'. A set of mixing bins, the reference state and background potential energy are presented in figure \ref{fig:lock_exchange_mixing}. As the simulation progresses, the mixing and the amount of mixed fluid increases, more rapidly at first as Kelvin--Helmholtz billows form and just after the fronts hit the end walls. Later, as the dynamics become less turbulent and the fluid oscillates back and forth in the tank the mixing is less vigorous. The increase in mixed fluid is compensated for by a decrease in non--mixed fluid.
957+where $g$ is gravity and $\rho$ the density. Most crucially, for a closed system, the background potential energy can only be altered by diapycnal mixing and increases in the background potential energy correspond to mixing in the system. The reference state is calculated using the method of \citet{tseng2001} which uses a probability density function to calculate the value of $z_*$ associated with a given $\rho$ (or here temperature). Here the probability density function is obtained from a set of `mixing bins'. Each mixing bin contains the fraction of fluid in the domain that has temperature within a given range or `class'. A set of mixing bins, the reference state and background potential energy are presented in figure \ref{fig:lock_exchange_mixing}. As the simulation progresses, the mixing and the amount of mixed fluid increases, more rapidly at first as Kelvin--Helmholtz billows form and just after the fronts hit the end walls. Later, as the dynamics become less turbulent and the fluid oscillates back
958+and forth in the tank the mixing is less vigorous. The increase in mixed fluid is compensated for by a decrease in non--mixed fluid.
959
960
961 \begin{figure}[ht]
962@@ -1000,7 +1001,8 @@
963 \label{sec:water_collapse}
964
965 \subsection{Overview}
966-A commonly used validation experiment for multi-material models is that of a collapsing column of liquid, normally water, within an atmosphere or vacuum \citep{lakehal_interface_2002}, also known as the dam break problem. In the experimental set-up a reservoir of water is held behind an impermeable barrier separating it from the rest of the tank. The barrier is then quickly removed, allowing the water column to collapse and flood the remaining sections of the tank. In the numerical analogue the initial condition is generally taken as the trapped water column, still behind the dam. At the start of the simulation the barrier is imagined to have been removed instantaneously and switching on gravity, $|g| = 9.81$, causes the column to collapse. Several experimental set-ups have been published and used as comparison and validation tools for numerical models \citep{martin_part_1952, greaves_simulation_2006}. Those with water depth gauges distributed throughout the tank are particularly useful, allowing the direct comparison of data. Furthermore, pressure gauges located on the tank walls or on any obstacles within the tank provide another useful validation tool.
967+A commonly used validation experiment for multi-material models is that of a collapsing column of liquid, normally water, within an atmosphere or vacuum \citep{lakehal_interface_2002}, also known as the dam break problem. In the experimental set-up a reservoir of water is held behind an impermeable barrier separating it from the rest of the tank. The barrier is then quickly removed, allowing the water column to collapse and flood the remaining sections of the tank. In the numerical analogue the initial condition is generally taken as the trapped water column, still behind the dam. At the start of the simulation the barrier is imagined to have been removed instantaneously and switching on gravity, $|g| = 9.81$, causes the column to collapse. Several experimental set-ups have been published and used as comparison and validation tools for numerical models \citep{martin_part_1952, greaves_simulation_2006}. Those with water depth gauges distributed throughout the tank are particularly useful, allowing the
968+direct comparison of data. Furthermore, pressure gauges located on the tank walls or on any obstacles within the tank provide another useful validation tool.
969
970 In this example, \fluidity\ is used to simulate a simple dam break experiment \citep{zhou_nonlinear_1999}. The example demonstrates the following functionality:
971
972@@ -1018,7 +1020,8 @@
973 \subsection{Problem specification}
974 The experiment on which this example is based was a simple dam break problem in a $3.22\times2\times1m$ (length $\times$ height $\times$ depth) tank \citep{zhou_nonlinear_1999}. A reservoir of water $1.2\times0.6\times1m$ (length $\times$ height $\times$ depth) was held behind a barrier at one end of the tank. Water depth gauges were placed at two points, marked H1 and H2 in Figure \ref{fig:zhouinitial}(a), at $x_1 = 2.725m$ and $2.228m$ respectively. Additionally, a pressure gauge was located at the point marked P2 in Figure \ref{fig:zhouinitial}(a), at $x_2=0.16m$ on the wall facing the initial water column.
975
976-As no variations were introduced in the third dimension, the experiment is reproduced here numerically in two dimensions within the domain $\Omega$: $x_1 \in [0,3.22]$, $x_2 \in [0,2]$ \citep{lee_numerical_2002, colagrossi_numerical_2003, park_volume-of-fluid_2009}. The two materials (water and air) are distinguished by scalar fields $\alpha_k$ representing their volume fraction, where the volume fraction of air $\alpha_2 = 1-\alpha_1$ and $\alpha_1$ is the volume fraction of water. The initial condition of the water volume fraction is shown in Figure \ref{fig:zhouinitial}(a). The presence of water is indicated as a blue region and the interface to air is delineated by contours at volume fraction values of $0.025$, $0.5$ and $0.975$. The densities of the water and air are taken as $ 1,000kg\,m^{-2}$ and $1kg\,m^{-2}$ respectively. Both fluids are treated inviscidly. As the simulation is inviscid, free slip boundary conditions are imposed on the tank bottom, $x_2=0$, and sides, $x_1=0,\,3.22$. The top of the tank, $x_2=2$, is left open.
977+As no variations were introduced in the third dimension, the experiment is reproduced here numerically in two dimensions within the domain $\Omega$: $x_1 \in [0,3.22]$, $x_2 \in [0,2]$ \citep{lee_numerical_2002, colagrossi_numerical_2003, park_volume-of-fluid_2009}. The two materials (water and air) are distinguished by scalar fields $\alpha_k$ representing their volume fraction, where the volume fraction of air $\alpha_2 = 1-\alpha_1$ and $\alpha_1$ is the volume fraction of water. The initial condition of the water volume fraction is shown in Figure \ref{fig:zhouinitial}(a). The presence of water is indicated as a blue region and the interface to air is delineated by contours at volume fraction values of $0.025$, $0.5$ and $0.975$. The densities of the water and air are taken as $ 1,000kg\,m^{-2}$ and $1kg\,m^{-2}$ respectively. Both fluids are treated inviscidly. As the simulation is inviscid, free slip boundary conditions are imposed on the tank bottom, $x_2=0$, and sides, $x_1=0,\,3.22$. The top of
978+the tank, $x_2=2$, is left open.
979
980 \begin{figure}[tbp]
981 \hspace{1cm}(a)
982@@ -1097,7 +1100,8 @@
983 \end{center}
984 \end{figure}
985
986-For validation purposes, the post-processing script provided for this example extracts information from the detector file (pressure) and from the water volume fraction field stored in the vtu files (water depth) and plots these data in comparison with the experimental results. The water depth gauge data is displayed in Figure \ref{fig:zhoudepth} alongside the experimental data. The numerical results show the total thickness of water at the points H1 and H2, discounting any air bubbles that cross the gauges. The simulation results show a close similarity to the experimental results with the exception of a small lip of water when the initial water head passes the gauge. It is unclear what causes this structure, though it may be related to the initial withdrawal of the barrier in the experiment or drag effects from the bottom of the tank. All previous published attempts to model the experiment also fail to reproduce this initial lip \citep{zhou_nonlinear_1999, lee_numerical_2002, colagrossi_numerical_2003, park_volume-of-fluid_2009}.
987+For validation purposes, the post-processing script provided for this example extracts information from the detector file (pressure) and from the water volume fraction field stored in the vtu files (water depth) and plots these data in comparison with the experimental results. The water depth gauge data is displayed in Figure \ref{fig:zhoudepth} alongside the experimental data. The numerical results show the total thickness of water at the points H1 and H2, discounting any air bubbles that cross the gauges. The simulation results show a close similarity to the experimental results with the exception of a small lip of water when the initial water head passes the gauge. It is unclear what causes this structure, though it may be related to the initial withdrawal of the barrier in the experiment or drag effects from the bottom of the tank. All previous published attempts to model the experiment also fail to reproduce this initial lip \citep{zhou_nonlinear_1999, lee_numerical_2002, colagrossi_numerical_2003,
988+park_volume-of-fluid_2009}.
989
990 After $t=1.5s$ the overturning wave starts to pass the water gauges and the match between the experimental results and the numerical simulation deteriorates. As would be expected from such complex behaviour, all previous published attempts have also failed to reproduce the experimental depth gauge data after this point. However, the broad pattern and average depth observed in the simulation after $t=1.5s$ can be seen in Figure \ref{fig:zhoudepth} to match the experiment reasonably well.
991
992@@ -1384,19 +1388,22 @@
993 \label{sec:tephra_settling}
994
995 \subsection{Overview}
996-In this example, \fluidity\ is used to replicate a laboratory experiment of tephra (fine volcanic ash particles) settling through a tank of water \citep{carey1997}. The \cite{carey1997} experiments introduced tephra particles into a $0.3\times 0.3\times 0.7$ m tank, filled with water, from above using a delivery system and a particle disperser. The particles settled through the air in the tank at an approximately constant rate until they landed in the water and began to settle through the water at a much reduced velocity. While the particles in the water were sufficiently dispersed their settling velocity was that predicted by Stokes' flow (a few mm/s). However, the build-up of particles caused by the air-water interface eventually created a layer of particles and water with a bulk density so great, relative to the density of the particle-poor water beneath, as to be gravitationally unstable and promote the formation of a vertical gravity current (plumes). The settling velocity of these plumes of particles and water was observed to be an order of magnitude greater than the Stokes settling velocity of the individual particles.
997-
998-In the \fluidity\ simulations, rather than represent each tephra particle individually using a multimaterial approach (which would be prohibitively expensive), a ``dispersed multiphase'' approach is adopted (see \ref{sec:multiphase_equations}), in which one phase represents the water in the tank and the other phase represents all the particles dispersed within the water. Similar to the water column collapse example (\ref{sec:water_collapse}), a volume fraction field is used to distinguish between the continuous phase (water) and the dispersed phase (particles). In an element the volume fraction of particles represents the fraction of the element volume that is occupied by particles, which is typically very small. In contrast to the multimaterial approach, however, the multiphase approach assigns each phase a separate velocity, allowing the dispersed phase (particles) to move through the continuous phase (water). In this example, the dispersed phase is more dense than the continuous phase and so sinks under the influence of gravity.
999-
1000-The simulation replicates one of the \cite{carey1997} experiments (with a characteristic particle size of 48 $\mu$m) by considering a constant influx of the particle phase into a 2D tank of water. The simulation results can be compared to the experiment in terms of the conditions under which plumes of tephra particles form as well as the settling velocities of the individual particles and plumes. The example demonstrates the following functionality:
1001+In this example, \fluidity\ is used to replicate a laboratory experiment of tephra (fine volcanic ash particles) settling through a tank of water \citep{carey1997}. The experiments by \cite{carey1997} introduced tephra particles into a $0.3\times 0.3\times 0.7$ m tank, filled with water, from above using a delivery system and a particle disperser. The particles settled through the air in the tank at an approximately constant rate until they landed in the water and began to settle through the water at a much reduced velocity. While the particles in the water were sufficiently dispersed their settling velocity was that predicted by Stokes' flow (a few mm/s). However, the build-up of particles caused by the air-water interface eventually created a layer of particles and water with a bulk density so great, relative to the density of the particle-poor water beneath, as to be gravitationally unstable and promote the formation of a vertical gravity current (plumes). The settling velocity of these plumes of particles
1002+and water was observed to be an order of magnitude greater than the Stokes settling velocity of the individual particles.
1003+
1004+In the \fluidity\ simulations, rather than represent each tephra particle individually using a multimaterial approach (which would be prohibitively expensive), a ``dispersed multiphase'' approach is adopted (see \ref{sec:multiphase_equations}), in which one phase represents the water in the tank and the other phase represents all the particles dispersed within the water. Similar to the water column collapse example (\ref{sec:water_collapse}), a volume fraction field is used to distinguish between the continuous phase (water) and the dispersed phase (particles). In an element the volume fraction of particles represents the fraction of the element volume that is occupied by particles, which is typically very small. In contrast to the multimaterial approach, however, the multiphase approach assigns each phase a separate velocity, allowing the dispersed phase (particles) to move through the continuous phase (water). In this example, the dispersed phase is more dense than the continuous phase and so sinks under
1005+the influence of gravity.
1006+
1007+The simulation replicates one of the experiments by \cite{carey1997} (with a characteristic particle size of 48 $\mu$m) by considering a constant influx of the particle phase into a 2D tank of water. The simulation results can be compared to the experiment in terms of the conditions under which plumes of tephra particles form as well as the settling velocities of the individual particles and plumes. The example demonstrates the following functionality:
1008 \begin{itemize}
1009 \item 2D flow
1010 \item Multi-phase flow
1011 \item Incompressible flow
1012 \item Adaptive timestepping
1013 \end{itemize}
1014+The simulation illustrated here took $\sim$1 hour to run in serial on an Intel Xeon E5430 2.66 GHz processor.
1015
1016-The simulation illustrated here took $\sim$1 hour to run in serial on an Intel Xeon E5430 2.66 GHz processor.
1017+For more information about the simulation of volcanic ash particles settling in water using \fluidity, see the paper by \cite{Jacobs_etal_2013}.
1018
1019 \subsection{Problem specification}
1020 The simulation uses a 0.3 x 0.7 metre domain, replicating the cross-section of the water tank used in the experiments, with an initial characteristic element size of 0.01 metres. No normal flow boundary conditions are weakly imposed along with a zero velocity initial condition. The parameters for density, viscosity, particle diameter and gravity are $\rho_p = 2340\ \mathrm{kgm^{-3}}$, $\rho_l = 1000\ \mathrm{kgm^{-3}}$, $\mu_l = 0.001\ \mathrm{Pa\cdot s}$, $d = 48\times 10^{-6}\ \mathrm{m}$, and $\mathbf{g} = 9.8\ \mathrm{ms^{-2}}$ respectively (with the subscripts $p$ and $l$ denoting the properties of the particle/tephra and liquid phase).
1021
1022=== modified file 'manual/model_equations.tex'
1023--- manual/model_equations.tex 2012-12-04 17:19:40 +0000
1024+++ manual/model_equations.tex 2013-02-08 22:48:22 +0000
1025@@ -831,7 +831,7 @@
1026 \nabla\cdot\left(\alpha_i\tautens_i\right) +
1027 \mathbf{F}_i,
1028 \end{equation}
1029-where $\mathbf{u}_i$, $\rho_i$, $\tautens_i$ and $\alpha_i$ are the velocity, density, viscous stress tensor and volume fraction of phase $i$ respectively, and $\mathbf{F}_i$ represents the forces imposed on phase $i$ by the other $N-1$ phases. Details of momentum transfer terms are given in Chapter \ref{chap:configuration}.
1030+where $\mathbf{u}_i$, $\rho_i$, $\tautens_i$ and $\alpha_i$ are the velocity, density, viscous stress tensor and volume fraction of phase $i$ respectively, and $\mathbf{F}_i$ represents the forces imposed on phase $i$ by the other $N-1$ phases. Details of momentum transfer terms are given in Chapter \ref{chap:configuration}. For more information about the incompressible multiphase flow model implemented in Fluidity, see the paper by \cite{Jacobs_etal_2013}.
1031
1032 \subsubsection{Compressible flow}
1033 Fluidity currently only supports the case where the continuous phase is compressible. All other phases (the dispersed phases) are incompressible. The momentum equation is the same as the one given above, but the continuity equation becomes:
1034@@ -842,9 +842,9 @@
1035
1036 An internal energy equation may also need to be solved depending on the equation of state used for the compressible phase. This is given by:
1037 \begin{equation}
1038-\alpha_i\rho_i\frac{\partial e_i}{\partial t} + \alpha_i\rho_i\mathbf{u}_i\cdot\nabla e_i = -p\nabla\cdot\left(\alpha_i\mathbf{u}_i\right) + Q_i
1039+\alpha_i\rho_i\frac{\partial e_i}{\partial t} + \alpha_i\rho_i\mathbf{u}_i\cdot\nabla e_i = -\alpha_i p\nabla\cdot\mathbf{u}_i + \nabla\cdot\left(\alpha_i\frac{k_i}{C_{v,i}}\nabla e_i\right) + Q_i
1040 \end{equation}
1041-where $e_i$ is the internal energy and $Q_i$ is an inter-phase energy transfer term described in Chapter \ref{chap:configuration}.
1042+where $e_i$ is the internal energy, $k_i$ is the effective conductivity, $C_{v,i}$ is the specific heat (at constant volume), and $Q_i$ is an inter-phase energy transfer term described in Chapter \ref{chap:configuration}. Note that, in Fluidity, the pressure term is always neglected in the (incompressible) particle phase's internal energy equation.
1043
1044 \subsection{Porous Media Darcy Flow}
1045 \label{sec:porous_media_darcy_flow_equations}
1046
1047=== modified file 'schemas/prognostic_field_options.rnc'
1048--- schemas/prognostic_field_options.rnc 2013-02-06 18:43:09 +0000
1049+++ schemas/prognostic_field_options.rnc 2013-02-08 22:48:22 +0000
1050@@ -1947,14 +1947,12 @@
1051 attribute name { "ReducedConservationOfMass" },
1052 equation_coefficients
1053 }|
1054- ## ***UNDER TESTING***
1055- ##
1056 ## Select the equation used to solve for this field.
1057 ## Internal Energy equation - requires the selection of a Density field.
1058- ## ONLY WORKS FOR CONTROL VOLUME DISCRETISATIONS
1059+ ## ONLY WORKS FOR CG and CV DISCRETISATIONS
1060 ## Solve the internal energy equation for this field.
1061 ## Requires pressure and velocity fields to be present.
1062- ## Uses a nonconservative time discretisation.
1063+ ## Uses a non-conservative time discretisation.
1064 element equation {
1065 attribute name { "InternalEnergy" },
1066 equation_coefficients
1067@@ -2002,7 +2000,7 @@
1068 coefficient_discretisation_options?
1069 }
1070 )
1071-
1072+
1073 coefficient_discretisation_options =
1074 (
1075 ## Provide discretisation options for the coefficient density field.
1076
1077=== modified file 'schemas/prognostic_field_options.rng'
1078--- schemas/prognostic_field_options.rng 2013-02-06 18:43:09 +0000
1079+++ schemas/prognostic_field_options.rng 2013-02-08 22:48:22 +0000
1080@@ -2400,14 +2400,12 @@
1081 <ref name="equation_coefficients"/>
1082 </element>
1083 <element name="equation">
1084- <a:documentation>***UNDER TESTING***
1085-
1086-Select the equation used to solve for this field.
1087+ <a:documentation>Select the equation used to solve for this field.
1088 Internal Energy equation - requires the selection of a Density field.
1089-ONLY WORKS FOR CONTROL VOLUME DISCRETISATIONS
1090+ONLY WORKS FOR CG and CV DISCRETISATIONS
1091 Solve the internal energy equation for this field.
1092 Requires pressure and velocity fields to be present.
1093-Uses a nonconservative time discretisation.</a:documentation>
1094+Uses a non-conservative time discretisation.</a:documentation>
1095 <attribute name="name">
1096 <value>InternalEnergy</value>
1097 </attribute>
1098
1099=== modified file 'tests/mphase_dusty_gas_shock_tube/mphase_dusty_gas_shock_tube.flml'
1100--- tests/mphase_dusty_gas_shock_tube/mphase_dusty_gas_shock_tube.flml 2012-10-17 15:59:53 +0000
1101+++ tests/mphase_dusty_gas_shock_tube/mphase_dusty_gas_shock_tube.flml 2013-02-08 22:48:22 +0000
1102@@ -165,7 +165,7 @@
1103 <mass_terms/>
1104 </continuous_galerkin>
1105 <conservative_advection>
1106- <real_value rank="0">0.0</real_value>
1107+ <real_value rank="0">1.0</real_value>
1108 </conservative_advection>
1109 </spatial_discretisation>
1110 <temporal_discretisation>
1111@@ -215,7 +215,7 @@
1112 </mass_terms>
1113 <advection_terms/>
1114 <stress_terms>
1115- <tensor_form/>
1116+ <stress_form/>
1117 </stress_terms>
1118 </continuous_galerkin>
1119 <conservative_advection>
1120@@ -268,11 +268,11 @@
1121 <tensor_field name="Viscosity" rank="2">
1122 <prescribed>
1123 <value name="WholeMesh">
1124- <isotropic>
1125+ <anisotropic_asymmetric>
1126 <constant>
1127- <real_value rank="0">1.83e-5</real_value>
1128+ <real_value symmetric="false" dim2="dim" shape="1 1" dim1="dim" rank="2">1.83e-5</real_value>
1129 </constant>
1130- </isotropic>
1131+ </anisotropic_asymmetric>
1132 </value>
1133 <output/>
1134 </prescribed>
1135
1136=== modified file 'tests/mphase_dusty_gas_shock_tube/single_phase_frozen_flow_test.flml'
1137--- tests/mphase_dusty_gas_shock_tube/single_phase_frozen_flow_test.flml 2012-10-17 15:59:53 +0000
1138+++ tests/mphase_dusty_gas_shock_tube/single_phase_frozen_flow_test.flml 2013-02-08 22:48:22 +0000
1139@@ -165,7 +165,7 @@
1140 <mass_terms/>
1141 </continuous_galerkin>
1142 <conservative_advection>
1143- <real_value rank="0">0.0</real_value>
1144+ <real_value rank="0">1.0</real_value>
1145 </conservative_advection>
1146 </spatial_discretisation>
1147 <temporal_discretisation>
1148@@ -215,7 +215,7 @@
1149 </mass_terms>
1150 <advection_terms/>
1151 <stress_terms>
1152- <tensor_form/>
1153+ <stress_form/>
1154 </stress_terms>
1155 </continuous_galerkin>
1156 <conservative_advection>
1157@@ -268,11 +268,11 @@
1158 <tensor_field name="Viscosity" rank="2">
1159 <prescribed>
1160 <value name="WholeMesh">
1161- <isotropic>
1162+ <anisotropic_asymmetric>
1163 <constant>
1164- <real_value rank="0">1.83e-5</real_value>
1165+ <real_value symmetric="false" dim2="dim" shape="1 1" dim1="dim" rank="2">1.83e-5</real_value>
1166 </constant>
1167- </isotropic>
1168+ </anisotropic_asymmetric>
1169 </value>
1170 <output/>
1171 </prescribed>
1172
1173=== added directory 'tests/mphase_mms_p2p1_compressible_ie_heat_flux'
1174=== added file 'tests/mphase_mms_p2p1_compressible_ie_heat_flux/MMS_X.flml'
1175--- tests/mphase_mms_p2p1_compressible_ie_heat_flux/MMS_X.flml 1970-01-01 00:00:00 +0000
1176+++ tests/mphase_mms_p2p1_compressible_ie_heat_flux/MMS_X.flml 2013-02-08 22:48:22 +0000
1177@@ -0,0 +1,1296 @@
1178+<?xml version='1.0' encoding='utf-8'?>
1179+<fluidity_options>
1180+ <simulation_name>
1181+ <string_value lines="1">MMS_X</string_value>
1182+ </simulation_name>
1183+ <problem_type>
1184+ <string_value lines="1">fluids</string_value>
1185+ </problem_type>
1186+ <geometry>
1187+ <dimension>
1188+ <integer_value rank="0">2</integer_value>
1189+ </dimension>
1190+ <mesh name="CoordinateMesh">
1191+ <from_file file_name="src/MMS_X">
1192+ <format name="gmsh"/>
1193+ <stat>
1194+ <include_in_stat/>
1195+ </stat>
1196+ </from_file>
1197+ </mesh>
1198+ <mesh name="VelocityMesh">
1199+ <from_mesh>
1200+ <mesh name="CoordinateMesh"/>
1201+ <mesh_shape>
1202+ <polynomial_degree>
1203+ <integer_value rank="0">2</integer_value>
1204+ </polynomial_degree>
1205+ </mesh_shape>
1206+ <stat>
1207+ <exclude_from_stat/>
1208+ </stat>
1209+ </from_mesh>
1210+ </mesh>
1211+ <mesh name="PressureMesh">
1212+ <from_mesh>
1213+ <mesh name="CoordinateMesh"/>
1214+ <mesh_shape>
1215+ <polynomial_degree>
1216+ <integer_value rank="0">1</integer_value>
1217+ </polynomial_degree>
1218+ </mesh_shape>
1219+ <stat>
1220+ <exclude_from_stat/>
1221+ </stat>
1222+ </from_mesh>
1223+ </mesh>
1224+ <mesh name="ErrorMesh">
1225+ <from_mesh>
1226+ <mesh name="CoordinateMesh"/>
1227+ <mesh_shape>
1228+ <polynomial_degree>
1229+ <integer_value rank="0">4</integer_value>
1230+ </polynomial_degree>
1231+ </mesh_shape>
1232+ <mesh_continuity>
1233+ <string_value>continuous</string_value>
1234+ </mesh_continuity>
1235+ <stat>
1236+ <exclude_from_stat/>
1237+ </stat>
1238+ </from_mesh>
1239+ </mesh>
1240+ <quadrature>
1241+ <degree>
1242+ <integer_value rank="0">8</integer_value>
1243+ </degree>
1244+ </quadrature>
1245+ </geometry>
1246+ <io>
1247+ <dump_format>
1248+ <string_value>vtk</string_value>
1249+ </dump_format>
1250+ <dump_period>
1251+ <constant>
1252+ <real_value rank="0">1000.0</real_value>
1253+ </constant>
1254+ </dump_period>
1255+ <output_mesh name="VelocityMesh"/>
1256+ <stat>
1257+ <output_at_start/>
1258+ </stat>
1259+ </io>
1260+ <timestepping>
1261+ <current_time>
1262+ <real_value rank="0">0.0</real_value>
1263+ </current_time>
1264+ <timestep>
1265+ <real_value rank="0">999.9</real_value>
1266+ <comment>gives a max cfl number of approximately 0.1</comment>
1267+ </timestep>
1268+ <finish_time>
1269+ <real_value rank="0">1000.0</real_value>
1270+ <comment>10.0</comment>
1271+ </finish_time>
1272+ <nonlinear_iterations>
1273+ <integer_value rank="0">2</integer_value>
1274+ <tolerance>
1275+ <real_value rank="0">1.0e-9</real_value>
1276+ <infinity_norm/>
1277+ </tolerance>
1278+ </nonlinear_iterations>
1279+ <steady_state>
1280+ <tolerance>
1281+ <real_value rank="0">1.E-7</real_value>
1282+ <infinity_norm/>
1283+ </tolerance>
1284+ </steady_state>
1285+ </timestepping>
1286+ <physical_parameters>
1287+ <gravity>
1288+ <magnitude>
1289+ <real_value rank="0">1.0</real_value>
1290+ </magnitude>
1291+ <vector_field name="GravityDirection" rank="1">
1292+ <prescribed>
1293+ <mesh name="CoordinateMesh"/>
1294+ <value name="WholeMesh">
1295+ <constant>
1296+ <real_value shape="2" dim1="dim" rank="1">0.707106781 0.707106781</real_value>
1297+ </constant>
1298+ </value>
1299+ <output/>
1300+ <stat>
1301+ <include_in_stat/>
1302+ </stat>
1303+ <detectors>
1304+ <exclude_from_detectors/>
1305+ </detectors>
1306+ </prescribed>
1307+ </vector_field>
1308+ </gravity>
1309+ </physical_parameters>
1310+ <material_phase name="Phase1">
1311+ <equation_of_state>
1312+ <compressible>
1313+ <stiffened_gas>
1314+ <ratio_specific_heats>
1315+ <real_value rank="0">1.4</real_value>
1316+ </ratio_specific_heats>
1317+ </stiffened_gas>
1318+ </compressible>
1319+ </equation_of_state>
1320+ <scalar_field name="Pressure" rank="0">
1321+ <prognostic>
1322+ <mesh name="PressureMesh"/>
1323+ <spatial_discretisation>
1324+ <continuous_galerkin>
1325+ <remove_stabilisation_term/>
1326+ </continuous_galerkin>
1327+ </spatial_discretisation>
1328+ <scheme>
1329+ <poisson_pressure_solution>
1330+ <string_value lines="1">never</string_value>
1331+ </poisson_pressure_solution>
1332+ <use_compressible_projection_method/>
1333+ </scheme>
1334+ <solver>
1335+ <iterative_method name="gmres">
1336+ <restart>
1337+ <integer_value rank="0">30</integer_value>
1338+ </restart>
1339+ </iterative_method>
1340+ <preconditioner name="sor"/>
1341+ <relative_error>
1342+ <real_value rank="0">1.0e-7</real_value>
1343+ </relative_error>
1344+ <max_iterations>
1345+ <integer_value rank="0">10000</integer_value>
1346+ </max_iterations>
1347+ <never_ignore_solver_failures/>
1348+ <diagnostics>
1349+ <monitors/>
1350+ </diagnostics>
1351+ </solver>
1352+ <boundary_conditions name="Incoming">
1353+ <surface_ids>
1354+ <integer_value shape="2" rank="1">7 10</integer_value>
1355+ </surface_ids>
1356+ <type name="dirichlet">
1357+ <python>
1358+ <string_value lines="20" type="code" language="python">def val(X,t):
1359+ import mphase_mms_p2p1_compressible_ie_tools as tools
1360+ return tools.p(X)</string_value>
1361+ </python>
1362+ </type>
1363+ </boundary_conditions>
1364+ <output>
1365+ <include_previous_time_step/>
1366+ </output>
1367+ <stat/>
1368+ <convergence>
1369+ <include_in_convergence/>
1370+ </convergence>
1371+ <detectors>
1372+ <exclude_from_detectors/>
1373+ </detectors>
1374+ <steady_state>
1375+ <exclude_from_steady_state/>
1376+ </steady_state>
1377+ <consistent_interpolation/>
1378+ </prognostic>
1379+ </scalar_field>
1380+ <scalar_field name="Density" rank="0">
1381+ <prognostic>
1382+ <mesh name="PressureMesh"/>
1383+ <spatial_discretisation>
1384+ <control_volumes>
1385+ <face_value name="FirstOrderUpwind"/>
1386+ </control_volumes>
1387+ <conservative_advection>
1388+ <real_value rank="0">0.0</real_value>
1389+ </conservative_advection>
1390+ </spatial_discretisation>
1391+ <temporal_discretisation>
1392+ <theta>
1393+ <real_value rank="0">1.0</real_value>
1394+ </theta>
1395+ </temporal_discretisation>
1396+ <initial_condition name="WholeMesh">
1397+ <python>
1398+ <string_value lines="20" type="code" language="python">def val(X,t):
1399+ import mphase_mms_p2p1_compressible_ie_tools as tools
1400+ return tools.rho1(X)</string_value>
1401+ </python>
1402+ </initial_condition>
1403+ <boundary_conditions name="All">
1404+ <surface_ids>
1405+ <integer_value shape="2" rank="1">7 10</integer_value>
1406+ </surface_ids>
1407+ <type name="dirichlet">
1408+ <python>
1409+ <string_value lines="20" type="code" language="python">def val(X,t):
1410+ import mphase_mms_p2p1_compressible_ie_tools as tools
1411+ return tools.rho1(X)</string_value>
1412+ </python>
1413+ </type>
1414+ </boundary_conditions>
1415+ <scalar_field name="Source" rank="0">
1416+ <prescribed>
1417+ <value name="WholeMesh">
1418+ <python>
1419+ <string_value lines="20" type="code" language="python">def val(X,t):
1420+ import mphase_mms_p2p1_compressible_ie_tools as tools
1421+ return tools.forcing_rho1(X)</string_value>
1422+ </python>
1423+ </value>
1424+ <output/>
1425+ <stat/>
1426+ <detectors>
1427+ <exclude_from_detectors/>
1428+ </detectors>
1429+ </prescribed>
1430+ </scalar_field>
1431+ <output/>
1432+ <stat/>
1433+ <convergence>
1434+ <include_in_convergence/>
1435+ </convergence>
1436+ <detectors>
1437+ <include_in_detectors/>
1438+ </detectors>
1439+ <steady_state>
1440+ <include_in_steady_state/>
1441+ </steady_state>
1442+ <consistent_interpolation/>
1443+ </prognostic>
1444+ </scalar_field>
1445+ <vector_field name="Velocity" rank="1">
1446+ <prognostic>
1447+ <mesh name="VelocityMesh"/>
1448+ <equation name="LinearMomentum"/>
1449+ <spatial_discretisation>
1450+ <continuous_galerkin>
1451+ <stabilisation>
1452+ <no_stabilisation/>
1453+ </stabilisation>
1454+ <mass_terms>
1455+ <lump_mass_matrix>
1456+ <use_submesh/>
1457+ </lump_mass_matrix>
1458+ </mass_terms>
1459+ <advection_terms/>
1460+ <stress_terms>
1461+ <tensor_form/>
1462+ </stress_terms>
1463+ </continuous_galerkin>
1464+ <conservative_advection>
1465+ <real_value rank="0">0.0</real_value>
1466+ </conservative_advection>
1467+ </spatial_discretisation>
1468+ <temporal_discretisation>
1469+ <theta>
1470+ <real_value rank="0">1.0</real_value>
1471+ </theta>
1472+ <relaxation>
1473+ <real_value rank="0">0.5</real_value>
1474+ </relaxation>
1475+ </temporal_discretisation>
1476+ <solver>
1477+ <iterative_method name="gmres">
1478+ <restart>
1479+ <integer_value rank="0">30</integer_value>
1480+ </restart>
1481+ </iterative_method>
1482+ <preconditioner name="sor"/>
1483+ <relative_error>
1484+ <real_value rank="0">1e-7</real_value>
1485+ </relative_error>
1486+ <max_iterations>
1487+ <integer_value rank="0">10000</integer_value>
1488+ </max_iterations>
1489+ <never_ignore_solver_failures/>
1490+ <diagnostics>
1491+ <monitors/>
1492+ </diagnostics>
1493+ </solver>
1494+ <initial_condition name="WholeMesh">
1495+ <python>
1496+ <string_value lines="20" type="code" language="python">def val(X,t):
1497+ import mphase_mms_p2p1_compressible_ie_tools as tools
1498+ return tools.velocity1(X)</string_value>
1499+ </python>
1500+ </initial_condition>
1501+ <boundary_conditions name="All">
1502+ <surface_ids>
1503+ <integer_value shape="4" rank="1">7 8 9 10</integer_value>
1504+ </surface_ids>
1505+ <type name="dirichlet">
1506+ <align_bc_with_cartesian>
1507+ <x_component>
1508+ <python>
1509+ <string_value lines="20" type="code" language="python">def val(X,t):
1510+ import mphase_mms_p2p1_compressible_ie_tools as tools
1511+ return tools.u1(X)</string_value>
1512+ </python>
1513+ </x_component>
1514+ <y_component>
1515+ <python>
1516+ <string_value lines="20" type="code" language="python">def val(X,t):
1517+ import mphase_mms_p2p1_compressible_ie_tools as tools
1518+ return tools.v1(X)</string_value>
1519+ </python>
1520+ </y_component>
1521+ </align_bc_with_cartesian>
1522+ </type>
1523+ </boundary_conditions>
1524+ <tensor_field name="Viscosity" rank="2">
1525+ <prescribed>
1526+ <value name="WholeMesh">
1527+ <isotropic>
1528+ <constant>
1529+ <real_value rank="0">0.7</real_value>
1530+ </constant>
1531+ </isotropic>
1532+ </value>
1533+ <output/>
1534+ </prescribed>
1535+ </tensor_field>
1536+ <vector_field name="Source" rank="1">
1537+ <prescribed>
1538+ <value name="WholeMesh">
1539+ <python>
1540+ <string_value lines="20" type="code" language="python">def val(X,t):
1541+ import mphase_mms_p2p1_compressible_ie_tools as tools
1542+ density = tools.rho1(X)
1543+ forcing_velocity1 = tools.forcing_velocity1(X)
1544+ # Remember to divide through by density here
1545+ # because we multiply through by Density in
1546+ # Momentum_CG.F90.
1547+ return (forcing_velocity1[0]/density, forcing_velocity1[1]/density)</string_value>
1548+ </python>
1549+ </value>
1550+ <output/>
1551+ <stat>
1552+ <include_in_stat/>
1553+ </stat>
1554+ <detectors>
1555+ <exclude_from_detectors/>
1556+ </detectors>
1557+ </prescribed>
1558+ </vector_field>
1559+ <output/>
1560+ <stat>
1561+ <include_in_stat/>
1562+ <previous_time_step>
1563+ <exclude_from_stat/>
1564+ </previous_time_step>
1565+ <nonlinear_field>
1566+ <exclude_from_stat/>
1567+ </nonlinear_field>
1568+ </stat>
1569+ <convergence>
1570+ <include_in_convergence/>
1571+ </convergence>
1572+ <detectors>
1573+ <include_in_detectors/>
1574+ </detectors>
1575+ <steady_state>
1576+ <exclude_from_steady_state/>
1577+ </steady_state>
1578+ <consistent_interpolation/>
1579+ </prognostic>
1580+ </vector_field>
1581+ <scalar_field name="CFLNumber" rank="0">
1582+ <diagnostic>
1583+ <algorithm name="Internal" material_phase_support="multiple"/>
1584+ <mesh name="VelocityMesh"/>
1585+ <output/>
1586+ <stat/>
1587+ <convergence>
1588+ <include_in_convergence/>
1589+ </convergence>
1590+ <detectors>
1591+ <include_in_detectors/>
1592+ </detectors>
1593+ <steady_state>
1594+ <exclude_from_steady_state/>
1595+ </steady_state>
1596+ </diagnostic>
1597+ </scalar_field>
1598+ <scalar_field name="InternalEnergy" rank="0">
1599+ <prognostic>
1600+ <mesh name="PressureMesh"/>
1601+ <equation name="InternalEnergy">
1602+ <density name="Density"/>
1603+ </equation>
1604+ <spatial_discretisation>
1605+ <continuous_galerkin>
1606+ <stabilisation>
1607+ <no_stabilisation/>
1608+ </stabilisation>
1609+ <advection_terms/>
1610+ <mass_terms/>
1611+ </continuous_galerkin>
1612+ <conservative_advection>
1613+ <real_value rank="0">0.0</real_value>
1614+ </conservative_advection>
1615+ </spatial_discretisation>
1616+ <temporal_discretisation>
1617+ <theta>
1618+ <real_value rank="0">1.0</real_value>
1619+ </theta>
1620+ </temporal_discretisation>
1621+ <solver>
1622+ <iterative_method name="gmres">
1623+ <restart>
1624+ <integer_value rank="0">30</integer_value>
1625+ </restart>
1626+ </iterative_method>
1627+ <preconditioner name="sor"/>
1628+ <relative_error>
1629+ <real_value rank="0">1.0e-7</real_value>
1630+ </relative_error>
1631+ <max_iterations>
1632+ <integer_value rank="0">10000</integer_value>
1633+ </max_iterations>
1634+ <ignore_all_solver_failures/>
1635+ <diagnostics>
1636+ <monitors/>
1637+ </diagnostics>
1638+ </solver>
1639+ <initial_condition name="WholeMesh">
1640+ <python>
1641+ <string_value lines="20" type="code" language="python">def val(X,t):
1642+ import mphase_mms_p2p1_compressible_ie_tools as tools
1643+ return tools.ie1(X)</string_value>
1644+ </python>
1645+ </initial_condition>
1646+ <boundary_conditions name="All">
1647+ <surface_ids>
1648+ <integer_value shape="2" rank="1">7 10</integer_value>
1649+ </surface_ids>
1650+ <type name="dirichlet">
1651+ <python>
1652+ <string_value lines="20" type="code" language="python">def val(X,t):
1653+ import mphase_mms_p2p1_compressible_ie_tools as tools
1654+ return tools.ie1(X)</string_value>
1655+ </python>
1656+ </type>
1657+ </boundary_conditions>
1658+ <tensor_field name="Diffusivity" rank="2">
1659+ <prescribed>
1660+ <value name="WholeMesh">
1661+ <isotropic>
1662+ <constant>
1663+ <real_value rank="0">0.001</real_value>
1664+ </constant>
1665+ </isotropic>
1666+ </value>
1667+ <output/>
1668+ </prescribed>
1669+ </tensor_field>
1670+ <scalar_field name="Source" rank="0">
1671+ <prescribed>
1672+ <value name="WholeMesh">
1673+ <python>
1674+ <string_value lines="20" type="code" language="python">def val(X,t):
1675+ import mphase_mms_p2p1_compressible_ie_tools as tools
1676+ return tools.forcing_ie1(X)</string_value>
1677+ </python>
1678+ </value>
1679+ <output/>
1680+ <stat/>
1681+ <detectors>
1682+ <exclude_from_detectors/>
1683+ </detectors>
1684+ </prescribed>
1685+ </scalar_field>
1686+ <output/>
1687+ <stat/>
1688+ <convergence>
1689+ <include_in_convergence/>
1690+ </convergence>
1691+ <detectors>
1692+ <include_in_detectors/>
1693+ </detectors>
1694+ <steady_state>
1695+ <include_in_steady_state/>
1696+ </steady_state>
1697+ <consistent_interpolation/>
1698+ </prognostic>
1699+ </scalar_field>
1700+ <scalar_field name="InternalEnergyAnalytical" rank="0">
1701+ <prescribed>
1702+ <mesh name="ErrorMesh"/>
1703+ <value name="WholeMesh">
1704+ <python>
1705+ <string_value lines="20" type="code" language="python">def val(X,t):
1706+ import mphase_mms_p2p1_compressible_ie_tools as tools
1707+ return tools.ie1(X)</string_value>
1708+ </python>
1709+ </value>
1710+ <output/>
1711+ <stat/>
1712+ <detectors>
1713+ <exclude_from_detectors/>
1714+ </detectors>
1715+ </prescribed>
1716+ </scalar_field>
1717+ <scalar_field name="InternalEnergyError" rank="0">
1718+ <diagnostic>
1719+ <algorithm source_field_2_type="scalar" name="scalar_difference" source_field_1_name="InternalEnergyAnalytical" source_field_2_name="InternalEnergyProjection" material_phase_support="single" source_field_1_type="scalar">
1720+ <absolute_difference/>
1721+ </algorithm>
1722+ <mesh name="ErrorMesh"/>
1723+ <output/>
1724+ <stat/>
1725+ <convergence>
1726+ <include_in_convergence/>
1727+ </convergence>
1728+ <detectors>
1729+ <include_in_detectors/>
1730+ </detectors>
1731+ <steady_state>
1732+ <include_in_steady_state/>
1733+ </steady_state>
1734+ </diagnostic>
1735+ </scalar_field>
1736+ <scalar_field name="InternalEnergyProjection" rank="0">
1737+ <diagnostic>
1738+ <algorithm source_field_type="scalar" material_phase_support="single" name="scalar_galerkin_projection" source_field_name="InternalEnergy">
1739+ <solver>
1740+ <iterative_method name="cg"/>
1741+ <preconditioner name="sor"/>
1742+ <relative_error>
1743+ <real_value rank="0">1e-10</real_value>
1744+ </relative_error>
1745+ <max_iterations>
1746+ <integer_value rank="0">1000</integer_value>
1747+ </max_iterations>
1748+ <never_ignore_solver_failures/>
1749+ <diagnostics>
1750+ <monitors/>
1751+ </diagnostics>
1752+ </solver>
1753+ </algorithm>
1754+ <mesh name="ErrorMesh"/>
1755+ <output/>
1756+ <stat/>
1757+ <convergence>
1758+ <include_in_convergence/>
1759+ </convergence>
1760+ <detectors>
1761+ <include_in_detectors/>
1762+ </detectors>
1763+ <steady_state>
1764+ <include_in_steady_state/>
1765+ </steady_state>
1766+ </diagnostic>
1767+ </scalar_field>
1768+ <scalar_field name="PressureAnalytical" rank="0">
1769+ <prescribed>
1770+ <mesh name="ErrorMesh"/>
1771+ <value name="WholeMesh">
1772+ <python>
1773+ <string_value lines="20" type="code" language="python">def val(X,t):
1774+ import mphase_mms_p2p1_compressible_ie_tools as tools
1775+ return tools.p(X)</string_value>
1776+ </python>
1777+ </value>
1778+ <output/>
1779+ <stat/>
1780+ <detectors>
1781+ <exclude_from_detectors/>
1782+ </detectors>
1783+ </prescribed>
1784+ </scalar_field>
1785+ <scalar_field name="PressureProjection" rank="0">
1786+ <diagnostic>
1787+ <algorithm source_field_type="scalar" material_phase_support="single" name="scalar_galerkin_projection" source_field_name="Pressure">
1788+ <solver>
1789+ <iterative_method name="cg"/>
1790+ <preconditioner name="sor"/>
1791+ <relative_error>
1792+ <real_value rank="0">1e-10</real_value>
1793+ </relative_error>
1794+ <max_iterations>
1795+ <integer_value rank="0">1000</integer_value>
1796+ </max_iterations>
1797+ <never_ignore_solver_failures/>
1798+ <diagnostics>
1799+ <monitors/>
1800+ </diagnostics>
1801+ </solver>
1802+ </algorithm>
1803+ <mesh name="ErrorMesh"/>
1804+ <output/>
1805+ <stat/>
1806+ <convergence>
1807+ <include_in_convergence/>
1808+ </convergence>
1809+ <detectors>
1810+ <include_in_detectors/>
1811+ </detectors>
1812+ <steady_state>
1813+ <exclude_from_steady_state/>
1814+ </steady_state>
1815+ </diagnostic>
1816+ </scalar_field>
1817+ <scalar_field name="PressureError" rank="0">
1818+ <diagnostic>
1819+ <algorithm source_field_2_type="scalar" name="scalar_difference" source_field_1_name="PressureProjection" source_field_2_name="PressureAnalytical" material_phase_support="single" source_field_1_type="scalar">
1820+ <absolute_difference/>
1821+ </algorithm>
1822+ <mesh name="ErrorMesh"/>
1823+ <output/>
1824+ <stat/>
1825+ <convergence>
1826+ <include_in_convergence/>
1827+ </convergence>
1828+ <detectors>
1829+ <include_in_detectors/>
1830+ </detectors>
1831+ <steady_state>
1832+ <include_in_steady_state/>
1833+ </steady_state>
1834+ </diagnostic>
1835+ </scalar_field>
1836+ <scalar_field name="DensityAnalytical" rank="0">
1837+ <prescribed>
1838+ <mesh name="ErrorMesh"/>
1839+ <value name="WholeMesh">
1840+ <python>
1841+ <string_value lines="20" type="code" language="python">def val(X,t):
1842+ import mphase_mms_p2p1_compressible_ie_tools as tools
1843+ return tools.rho1(X)</string_value>
1844+ </python>
1845+ </value>
1846+ <output/>
1847+ <stat/>
1848+ <detectors>
1849+ <exclude_from_detectors/>
1850+ </detectors>
1851+ </prescribed>
1852+ </scalar_field>
1853+ <scalar_field name="DensityError" rank="0">
1854+ <diagnostic>
1855+ <algorithm source_field_2_type="scalar" name="scalar_difference" source_field_1_name="DensityAnalytical" source_field_2_name="DensityProjection" material_phase_support="single" source_field_1_type="scalar">
1856+ <absolute_difference/>
1857+ </algorithm>
1858+ <mesh name="ErrorMesh"/>
1859+ <output/>
1860+ <stat/>
1861+ <convergence>
1862+ <include_in_convergence/>
1863+ </convergence>
1864+ <detectors>
1865+ <include_in_detectors/>
1866+ </detectors>
1867+ <steady_state>
1868+ <include_in_steady_state/>
1869+ </steady_state>
1870+ </diagnostic>
1871+ </scalar_field>
1872+ <scalar_field name="DensityProjection" rank="0">
1873+ <diagnostic>
1874+ <algorithm source_field_type="scalar" material_phase_support="single" name="scalar_galerkin_projection" source_field_name="Density">
1875+ <solver>
1876+ <iterative_method name="cg"/>
1877+ <preconditioner name="sor"/>
1878+ <relative_error>
1879+ <real_value rank="0">1e-10</real_value>
1880+ </relative_error>
1881+ <max_iterations>
1882+ <integer_value rank="0">1000</integer_value>
1883+ </max_iterations>
1884+ <never_ignore_solver_failures/>
1885+ <diagnostics>
1886+ <monitors/>
1887+ </diagnostics>
1888+ </solver>
1889+ </algorithm>
1890+ <mesh name="ErrorMesh"/>
1891+ <output/>
1892+ <stat/>
1893+ <convergence>
1894+ <include_in_convergence/>
1895+ </convergence>
1896+ <detectors>
1897+ <include_in_detectors/>
1898+ </detectors>
1899+ <steady_state>
1900+ <include_in_steady_state/>
1901+ </steady_state>
1902+ </diagnostic>
1903+ </scalar_field>
1904+ <scalar_field name="PhaseVolumeFraction" rank="0">
1905+ <diagnostic>
1906+ <mesh name="CoordinateMesh"/>
1907+ <algorithm name="Internal" material_phase_support="multiple"/>
1908+ <output/>
1909+ <stat/>
1910+ <detectors>
1911+ <include_in_detectors/>
1912+ </detectors>
1913+ </diagnostic>
1914+ </scalar_field>
1915+ <vector_field name="VelocityAnalytical" rank="1">
1916+ <prescribed>
1917+ <mesh name="ErrorMesh"/>
1918+ <value name="WholeMesh">
1919+ <python>
1920+ <string_value lines="20" type="code" language="python">def val(X,t):
1921+ import mphase_mms_p2p1_compressible_ie_tools as tools
1922+ return tools.velocity1(X)</string_value>
1923+ </python>
1924+ </value>
1925+ <output/>
1926+ <stat>
1927+ <include_in_stat/>
1928+ </stat>
1929+ <detectors>
1930+ <exclude_from_detectors/>
1931+ </detectors>
1932+ </prescribed>
1933+ </vector_field>
1934+ <vector_field name="VelocityProjection" rank="1">
1935+ <diagnostic>
1936+ <algorithm source_field_type="vector" material_phase_support="single" name="vector_galerkin_projection" source_field_name="Velocity">
1937+ <solver>
1938+ <iterative_method name="cg"/>
1939+ <preconditioner name="sor"/>
1940+ <relative_error>
1941+ <real_value rank="0">1e-10</real_value>
1942+ </relative_error>
1943+ <max_iterations>
1944+ <integer_value rank="0">1000</integer_value>
1945+ </max_iterations>
1946+ <never_ignore_solver_failures/>
1947+ <diagnostics>
1948+ <monitors/>
1949+ </diagnostics>
1950+ </solver>
1951+ </algorithm>
1952+ <mesh name="ErrorMesh"/>
1953+ <output/>
1954+ <stat>
1955+ <include_in_stat/>
1956+ </stat>
1957+ <convergence>
1958+ <include_in_convergence/>
1959+ </convergence>
1960+ <detectors>
1961+ <include_in_detectors/>
1962+ </detectors>
1963+ <steady_state>
1964+ <exclude_from_steady_state/>
1965+ </steady_state>
1966+ </diagnostic>
1967+ </vector_field>
1968+ <vector_field name="VelocityError" rank="1">
1969+ <diagnostic>
1970+ <algorithm source_field_2_type="vector" name="vector_difference" source_field_1_name="VelocityProjection" source_field_2_name="VelocityAnalytical" material_phase_support="single" source_field_1_type="vector">
1971+ <absolute_difference/>
1972+ </algorithm>
1973+ <mesh name="ErrorMesh"/>
1974+ <output/>
1975+ <stat>
1976+ <include_in_stat/>
1977+ </stat>
1978+ <convergence>
1979+ <include_in_convergence/>
1980+ </convergence>
1981+ <detectors>
1982+ <include_in_detectors/>
1983+ </detectors>
1984+ <steady_state>
1985+ <include_in_steady_state/>
1986+ </steady_state>
1987+ </diagnostic>
1988+ </vector_field>
1989+ </material_phase>
1990+ <material_phase name="Phase2">
1991+ <equation_of_state>
1992+ <fluids>
1993+ <linear>
1994+ <reference_density>
1995+ <real_value rank="0">3.0</real_value>
1996+ </reference_density>
1997+ </linear>
1998+ </fluids>
1999+ </equation_of_state>
2000+ <scalar_field name="Pressure" rank="0">
2001+ <aliased material_phase_name="Phase1" field_name="Pressure"/>
2002+ </scalar_field>
2003+ <scalar_field name="Density" rank="0">
2004+ <diagnostic>
2005+ <algorithm name="Internal" material_phase_support="multiple"/>
2006+ <mesh name="PressureMesh"/>
2007+ <output/>
2008+ <stat/>
2009+ <convergence>
2010+ <include_in_convergence/>
2011+ </convergence>
2012+ <detectors>
2013+ <include_in_detectors/>
2014+ </detectors>
2015+ <steady_state>
2016+ <include_in_steady_state/>
2017+ </steady_state>
2018+ </diagnostic>
2019+ </scalar_field>
2020+ <vector_field name="Velocity" rank="1">
2021+ <prognostic>
2022+ <mesh name="VelocityMesh"/>
2023+ <equation name="LinearMomentum"/>
2024+ <spatial_discretisation>
2025+ <continuous_galerkin>
2026+ <stabilisation>
2027+ <no_stabilisation/>
2028+ </stabilisation>
2029+ <mass_terms>
2030+ <lump_mass_matrix>
2031+ <use_submesh/>
2032+ </lump_mass_matrix>
2033+ </mass_terms>
2034+ <advection_terms/>
2035+ <stress_terms>
2036+ <tensor_form/>
2037+ </stress_terms>
2038+ </continuous_galerkin>
2039+ <conservative_advection>
2040+ <real_value rank="0">0.0</real_value>
2041+ </conservative_advection>
2042+ </spatial_discretisation>
2043+ <temporal_discretisation>
2044+ <theta>
2045+ <real_value rank="0">1.0</real_value>
2046+ </theta>
2047+ <relaxation>
2048+ <real_value rank="0">0.5</real_value>
2049+ </relaxation>
2050+ </temporal_discretisation>
2051+ <solver>
2052+ <iterative_method name="gmres">
2053+ <restart>
2054+ <integer_value rank="0">30</integer_value>
2055+ </restart>
2056+ </iterative_method>
2057+ <preconditioner name="sor"/>
2058+ <relative_error>
2059+ <real_value rank="0">1e-7</real_value>
2060+ </relative_error>
2061+ <max_iterations>
2062+ <integer_value rank="0">10000</integer_value>
2063+ </max_iterations>
2064+ <never_ignore_solver_failures/>
2065+ <diagnostics>
2066+ <monitors/>
2067+ </diagnostics>
2068+ </solver>
2069+ <initial_condition name="WholeMesh">
2070+ <python>
2071+ <string_value lines="20" type="code" language="python">def val(X,t):
2072+ import mphase_mms_p2p1_compressible_ie_tools as tools
2073+ return tools.velocity2(X)</string_value>
2074+ </python>
2075+ </initial_condition>
2076+ <boundary_conditions name="All">
2077+ <surface_ids>
2078+ <integer_value shape="4" rank="1">7 8 9 10</integer_value>
2079+ </surface_ids>
2080+ <type name="dirichlet">
2081+ <align_bc_with_cartesian>
2082+ <x_component>
2083+ <python>
2084+ <string_value lines="20" type="code" language="python">def val(X,t):
2085+ import mphase_mms_p2p1_compressible_ie_tools as tools
2086+ return tools.u2(X)</string_value>
2087+ </python>
2088+ </x_component>
2089+ <y_component>
2090+ <python>
2091+ <string_value lines="20" type="code" language="python">def val(X,t):
2092+ import mphase_mms_p2p1_compressible_ie_tools as tools
2093+ return tools.v2(X)</string_value>
2094+ </python>
2095+ </y_component>
2096+ </align_bc_with_cartesian>
2097+ </type>
2098+ </boundary_conditions>
2099+ <tensor_field name="Viscosity" rank="2">
2100+ <prescribed>
2101+ <value name="WholeMesh">
2102+ <isotropic>
2103+ <constant>
2104+ <real_value rank="0">0.7</real_value>
2105+ </constant>
2106+ </isotropic>
2107+ </value>
2108+ <output/>
2109+ </prescribed>
2110+ </tensor_field>
2111+ <vector_field name="Source" rank="1">
2112+ <prescribed>
2113+ <value name="WholeMesh">
2114+ <python>
2115+ <string_value lines="20" type="code" language="python">def val(X,t):
2116+ import mphase_mms_p2p1_compressible_ie_tools as tools
2117+ density = tools.rho2(X)
2118+ forcing_velocity2 = tools.forcing_velocity2(X)
2119+ # Remember to divide through by density here
2120+ # because we multiply through by Density in
2121+ # Momentum_CG.F90.
2122+ return (forcing_velocity2[0]/density, forcing_velocity2[1]/density)</string_value>
2123+ </python>
2124+ </value>
2125+ <output/>
2126+ <stat>
2127+ <include_in_stat/>
2128+ </stat>
2129+ <detectors>
2130+ <exclude_from_detectors/>
2131+ </detectors>
2132+ </prescribed>
2133+ </vector_field>
2134+ <output/>
2135+ <stat>
2136+ <include_in_stat/>
2137+ <previous_time_step>
2138+ <exclude_from_stat/>
2139+ </previous_time_step>
2140+ <nonlinear_field>
2141+ <exclude_from_stat/>
2142+ </nonlinear_field>
2143+ </stat>
2144+ <convergence>
2145+ <include_in_convergence/>
2146+ </convergence>
2147+ <detectors>
2148+ <include_in_detectors/>
2149+ </detectors>
2150+ <steady_state>
2151+ <exclude_from_steady_state/>
2152+ </steady_state>
2153+ <consistent_interpolation/>
2154+ </prognostic>
2155+ </vector_field>
2156+ <scalar_field name="CFLNumber" rank="0">
2157+ <diagnostic>
2158+ <algorithm name="Internal" material_phase_support="multiple"/>
2159+ <mesh name="VelocityMesh"/>
2160+ <output/>
2161+ <stat/>
2162+ <convergence>
2163+ <include_in_convergence/>
2164+ </convergence>
2165+ <detectors>
2166+ <include_in_detectors/>
2167+ </detectors>
2168+ <steady_state>
2169+ <exclude_from_steady_state/>
2170+ </steady_state>
2171+ </diagnostic>
2172+ </scalar_field>
2173+ <scalar_field name="InternalEnergy" rank="0">
2174+ <prognostic>
2175+ <mesh name="PressureMesh"/>
2176+ <equation name="InternalEnergy">
2177+ <density name="Density"/>
2178+ </equation>
2179+ <spatial_discretisation>
2180+ <continuous_galerkin>
2181+ <stabilisation>
2182+ <no_stabilisation/>
2183+ </stabilisation>
2184+ <advection_terms/>
2185+ <mass_terms/>
2186+ </continuous_galerkin>
2187+ <conservative_advection>
2188+ <real_value rank="0">0.0</real_value>
2189+ </conservative_advection>
2190+ </spatial_discretisation>
2191+ <temporal_discretisation>
2192+ <theta>
2193+ <real_value rank="0">1.0</real_value>
2194+ </theta>
2195+ </temporal_discretisation>
2196+ <solver>
2197+ <iterative_method name="gmres">
2198+ <restart>
2199+ <integer_value rank="0">30</integer_value>
2200+ </restart>
2201+ </iterative_method>
2202+ <preconditioner name="sor"/>
2203+ <relative_error>
2204+ <real_value rank="0">1.0e-7</real_value>
2205+ </relative_error>
2206+ <max_iterations>
2207+ <integer_value rank="0">10000</integer_value>
2208+ </max_iterations>
2209+ <ignore_all_solver_failures/>
2210+ <diagnostics>
2211+ <monitors/>
2212+ </diagnostics>
2213+ </solver>
2214+ <initial_condition name="WholeMesh">
2215+ <python>
2216+ <string_value lines="20" type="code" language="python">def val(X,t):
2217+ import mphase_mms_p2p1_compressible_ie_tools as tools
2218+ return tools.ie2(X)</string_value>
2219+ </python>
2220+ </initial_condition>
2221+ <boundary_conditions name="All">
2222+ <surface_ids>
2223+ <integer_value shape="2" rank="1">7 10</integer_value>
2224+ </surface_ids>
2225+ <type name="dirichlet">
2226+ <python>
2227+ <string_value lines="20" type="code" language="python">def val(X,t):
2228+ import mphase_mms_p2p1_compressible_ie_tools as tools
2229+ return tools.ie2(X)</string_value>
2230+ </python>
2231+ </type>
2232+ </boundary_conditions>
2233+ <tensor_field name="Diffusivity" rank="2">
2234+ <prescribed>
2235+ <value name="WholeMesh">
2236+ <isotropic>
2237+ <constant>
2238+ <real_value rank="0">0.001</real_value>
2239+ </constant>
2240+ </isotropic>
2241+ </value>
2242+ <output/>
2243+ </prescribed>
2244+ </tensor_field>
2245+ <scalar_field name="Source" rank="0">
2246+ <prescribed>
2247+ <value name="WholeMesh">
2248+ <python>
2249+ <string_value lines="20" type="code" language="python">def val(X,t):
2250+ import mphase_mms_p2p1_compressible_ie_tools as tools
2251+ return tools.forcing_ie2(X)</string_value>
2252+ </python>
2253+ </value>
2254+ <output/>
2255+ <stat/>
2256+ <detectors>
2257+ <exclude_from_detectors/>
2258+ </detectors>
2259+ </prescribed>
2260+ </scalar_field>
2261+ <output/>
2262+ <stat/>
2263+ <convergence>
2264+ <include_in_convergence/>
2265+ </convergence>
2266+ <detectors>
2267+ <include_in_detectors/>
2268+ </detectors>
2269+ <steady_state>
2270+ <include_in_steady_state/>
2271+ </steady_state>
2272+ <consistent_interpolation/>
2273+ </prognostic>
2274+ </scalar_field>
2275+ <scalar_field name="InternalEnergyAnalytical" rank="0">
2276+ <prescribed>
2277+ <mesh name="ErrorMesh"/>
2278+ <value name="WholeMesh">
2279+ <python>
2280+ <string_value lines="20" type="code" language="python">def val(X,t):
2281+ import mphase_mms_p2p1_compressible_ie_tools as tools
2282+ return tools.ie2(X)</string_value>
2283+ </python>
2284+ </value>
2285+ <output/>
2286+ <stat/>
2287+ <detectors>
2288+ <exclude_from_detectors/>
2289+ </detectors>
2290+ </prescribed>
2291+ </scalar_field>
2292+ <scalar_field name="InternalEnergyError" rank="0">
2293+ <diagnostic>
2294+ <algorithm source_field_2_type="scalar" name="scalar_difference" source_field_1_name="InternalEnergyAnalytical" source_field_2_name="InternalEnergyProjection" material_phase_support="single" source_field_1_type="scalar">
2295+ <absolute_difference/>
2296+ </algorithm>
2297+ <mesh name="ErrorMesh"/>
2298+ <output/>
2299+ <stat/>
2300+ <convergence>
2301+ <include_in_convergence/>
2302+ </convergence>
2303+ <detectors>
2304+ <include_in_detectors/>
2305+ </detectors>
2306+ <steady_state>
2307+ <include_in_steady_state/>
2308+ </steady_state>
2309+ </diagnostic>
2310+ </scalar_field>
2311+ <scalar_field name="InternalEnergyProjection" rank="0">
2312+ <diagnostic>
2313+ <algorithm source_field_type="scalar" material_phase_support="single" name="scalar_galerkin_projection" source_field_name="InternalEnergy">
2314+ <solver>
2315+ <iterative_method name="cg"/>
2316+ <preconditioner name="sor"/>
2317+ <relative_error>
2318+ <real_value rank="0">1e-10</real_value>
2319+ </relative_error>
2320+ <max_iterations>
2321+ <integer_value rank="0">1000</integer_value>
2322+ </max_iterations>
2323+ <never_ignore_solver_failures/>
2324+ <diagnostics>
2325+ <monitors/>
2326+ </diagnostics>
2327+ </solver>
2328+ </algorithm>
2329+ <mesh name="ErrorMesh"/>
2330+ <output/>
2331+ <stat/>
2332+ <convergence>
2333+ <include_in_convergence/>
2334+ </convergence>
2335+ <detectors>
2336+ <include_in_detectors/>
2337+ </detectors>
2338+ <steady_state>
2339+ <include_in_steady_state/>
2340+ </steady_state>
2341+ </diagnostic>
2342+ </scalar_field>
2343+ <scalar_field name="PhaseVolumeFraction" rank="0">
2344+ <prescribed>
2345+ <mesh name="CoordinateMesh"/>
2346+ <value name="WholeMesh">
2347+ <python>
2348+ <string_value lines="20" type="code" language="python">def val(X,t):
2349+ import mphase_mms_p2p1_compressible_ie_tools as tools
2350+ return tools.vfrac2(X)</string_value>
2351+ </python>
2352+ </value>
2353+ <output/>
2354+ <stat/>
2355+ <detectors>
2356+ <exclude_from_detectors/>
2357+ </detectors>
2358+ </prescribed>
2359+ </scalar_field>
2360+ <scalar_field name="InternalEnergyError2" rank="0">
2361+ <diagnostic>
2362+ <algorithm source_field_2_type="scalar" name="scalar_difference" source_field_1_name="InternalEnergy" source_field_2_name="InternalEnergyAnalytical2" material_phase_support="single" source_field_1_type="scalar"/>
2363+ <mesh name="PressureMesh"/>
2364+ <output/>
2365+ <stat/>
2366+ <convergence>
2367+ <include_in_convergence/>
2368+ </convergence>
2369+ <detectors>
2370+ <include_in_detectors/>
2371+ </detectors>
2372+ <steady_state>
2373+ <include_in_steady_state/>
2374+ </steady_state>
2375+ </diagnostic>
2376+ </scalar_field>
2377+ <scalar_field name="InternalEnergyAnalytical2" rank="0">
2378+ <prescribed>
2379+ <mesh name="PressureMesh"/>
2380+ <value name="WholeMesh">
2381+ <python>
2382+ <string_value lines="20" type="code" language="python">def val(X,t):
2383+ import mphase_mms_p2p1_compressible_ie_tools as tools
2384+ return tools.ie2(X)</string_value>
2385+ </python>
2386+ </value>
2387+ <output/>
2388+ <stat/>
2389+ <detectors>
2390+ <exclude_from_detectors/>
2391+ </detectors>
2392+ </prescribed>
2393+ </scalar_field>
2394+ <vector_field name="VelocityAnalytical" rank="1">
2395+ <prescribed>
2396+ <mesh name="ErrorMesh"/>
2397+ <value name="WholeMesh">
2398+ <python>
2399+ <string_value lines="20" type="code" language="python">def val(X,t):
2400+ import mphase_mms_p2p1_compressible_ie_tools as tools
2401+ return tools.velocity2(X)</string_value>
2402+ </python>
2403+ </value>
2404+ <output/>
2405+ <stat>
2406+ <include_in_stat/>
2407+ </stat>
2408+ <detectors>
2409+ <exclude_from_detectors/>
2410+ </detectors>
2411+ </prescribed>
2412+ </vector_field>
2413+ <vector_field name="VelocityProjection" rank="1">
2414+ <diagnostic>
2415+ <algorithm source_field_type="vector" material_phase_support="single" name="vector_galerkin_projection" source_field_name="Velocity">
2416+ <solver>
2417+ <iterative_method name="gmres">
2418+ <restart>
2419+ <integer_value rank="0">30</integer_value>
2420+ </restart>
2421+ </iterative_method>
2422+ <preconditioner name="sor"/>
2423+ <relative_error>
2424+ <real_value rank="0">1e-10</real_value>
2425+ </relative_error>
2426+ <max_iterations>
2427+ <integer_value rank="0">1000</integer_value>
2428+ </max_iterations>
2429+ <never_ignore_solver_failures/>
2430+ <diagnostics>
2431+ <monitors/>
2432+ </diagnostics>
2433+ </solver>
2434+ </algorithm>
2435+ <mesh name="ErrorMesh"/>
2436+ <output/>
2437+ <stat>
2438+ <include_in_stat/>
2439+ </stat>
2440+ <convergence>
2441+ <include_in_convergence/>
2442+ </convergence>
2443+ <detectors>
2444+ <include_in_detectors/>
2445+ </detectors>
2446+ <steady_state>
2447+ <exclude_from_steady_state/>
2448+ </steady_state>
2449+ </diagnostic>
2450+ </vector_field>
2451+ <vector_field name="VelocityError" rank="1">
2452+ <diagnostic>
2453+ <algorithm source_field_2_type="vector" name="vector_difference" source_field_1_name="VelocityProjection" source_field_2_name="VelocityAnalytical" material_phase_support="single" source_field_1_type="vector">
2454+ <absolute_difference/>
2455+ </algorithm>
2456+ <mesh name="ErrorMesh"/>
2457+ <output/>
2458+ <stat>
2459+ <include_in_stat/>
2460+ </stat>
2461+ <convergence>
2462+ <include_in_convergence/>
2463+ </convergence>
2464+ <detectors>
2465+ <include_in_detectors/>
2466+ </detectors>
2467+ <steady_state>
2468+ <include_in_steady_state/>
2469+ </steady_state>
2470+ </diagnostic>
2471+ </vector_field>
2472+ </material_phase>
2473+</fluidity_options>
2474
2475=== added file 'tests/mphase_mms_p2p1_compressible_ie_heat_flux/Makefile'
2476--- tests/mphase_mms_p2p1_compressible_ie_heat_flux/Makefile 1970-01-01 00:00:00 +0000
2477+++ tests/mphase_mms_p2p1_compressible_ie_heat_flux/Makefile 2013-02-08 22:48:22 +0000
2478@@ -0,0 +1,8 @@
2479+input: clean
2480+ ./copy_script
2481+ gmsh -2 -bin src/MMS_A.geo
2482+ gmsh -2 -bin src/MMS_B.geo
2483+ gmsh -2 -bin src/MMS_C.geo
2484+
2485+clean:
2486+ rm -f *.vtu *.stat *.s *.log *_A* *_B* *_C* matrix* *~ mms_rans_p2p1_keps.py *.pyc fluidity.*
2487
2488=== added file 'tests/mphase_mms_p2p1_compressible_ie_heat_flux/README'
2489--- tests/mphase_mms_p2p1_compressible_ie_heat_flux/README 1970-01-01 00:00:00 +0000
2490+++ tests/mphase_mms_p2p1_compressible_ie_heat_flux/README 2013-02-08 22:48:22 +0000
2491@@ -0,0 +1,25 @@
2492+CREATING mms_rans_p2p1_keps_tools.py:
2493+
2494+edit mms_rans_p2p1_keps.sage as required
2495+in the terminal, run:
2496+sage mms_rans_p2p1_keps.sage > mms_rans_p2p1_keps_tools.py
2497+
2498+EDITING MMS_X.flml and MMS_X.geo (copyscript):
2499+
2500+These are copied to MMS_A, MMS_B, MMS_C, MMS_D cases by copyscript
2501+DO NOT CHANGE - timestep or references to MMS_X in MMS_X.flml
2502+DO NOT CHANGE - n = XX in MMS_X.geo
2503+
2504+DISABLING PARTS OF THE MODEL:
2505+
2506+alternative flml files are included in the alternative_flml folder for debugging failures - these include flml files that have prescribed velocity or k-epsilon fields so that the model can be debugged in stages.
2507+
2508+additionally, individual source and absorbtion terms can be disabled within the flml.
2509+
2510+FUNCTION PRINTER
2511+
2512+run using:
2513+python function_printer.py AA BB CC DD .. n_rows
2514+where:
2515+ AA, BB, CC, DD are names of functions in mms_rans_p2p1_keps_tools.py (any number can be entered)
2516+ n_rows is the number of rows to display the functions on
2517\ No newline at end of file
2518
2519=== added file 'tests/mphase_mms_p2p1_compressible_ie_heat_flux/copy_script'
2520--- tests/mphase_mms_p2p1_compressible_ie_heat_flux/copy_script 1970-01-01 00:00:00 +0000
2521+++ tests/mphase_mms_p2p1_compressible_ie_heat_flux/copy_script 2013-02-08 22:48:22 +0000
2522@@ -0,0 +1,23 @@
2523+#!/bin/bash
2524+
2525+n=4
2526+for F in A B C
2527+do
2528+ echo creating set $F with n_ele=$n
2529+
2530+ cp MMS_X.flml MMS_$F.flml
2531+ sed s/MMS_X/MMS_$F/ MMS_$F.flml > MMS_$F.flml.cp
2532+
2533+ #sed s/XX/$n/ src/MMS_X.geo > src/MMS_$F.geo
2534+
2535+ n=$((n*2))
2536+done
2537+
2538+echo setting flml timestep values
2539+
2540+sed s/999.9/0.005/ MMS_A.flml.cp > MMS_A.flml
2541+rm MMS_A.flml.cp
2542+sed s/999.9/0.0025/ MMS_B.flml.cp > MMS_B.flml
2543+rm MMS_B.flml.cp
2544+sed s/999.9/0.00125/ MMS_C.flml.cp > MMS_C.flml
2545+rm MMS_C.flml.cp
2546
2547=== added file 'tests/mphase_mms_p2p1_compressible_ie_heat_flux/function_printer.py'
2548--- tests/mphase_mms_p2p1_compressible_ie_heat_flux/function_printer.py 1970-01-01 00:00:00 +0000
2549+++ tests/mphase_mms_p2p1_compressible_ie_heat_flux/function_printer.py 2013-02-08 22:48:22 +0000
2550@@ -0,0 +1,40 @@
2551+from mphase_mms_p2p1_compressible_ie_tools import *
2552+from numpy import *
2553+import matplotlib
2554+import matplotlib.pyplot as plt
2555+import sys
2556+
2557+'''
2558+run using:
2559+python function_printer.py AA BB CC DD .. n_rows
2560+where:
2561+ AA, BB, CC, DD are names of functions in mms_rans_p2p1_keps_tools.py (any number can be entered)
2562+ n_rows is the number of rows to display the functions on
2563+'''
2564+
2565+functions = []
2566+for arg in sys.argv[1:-1]:
2567+ functions.append(arg)
2568+n_rows = int(sys.argv[-1])
2569+
2570+matplotlib.rcParams['xtick.direction'] = 'out'
2571+matplotlib.rcParams['ytick.direction'] = 'out'
2572+plt.subplots_adjust(left=None, bottom=None, right=None, top=None,
2573+ wspace=0.2, hspace=0.2)
2574+
2575+res = 50
2576+X = linspace(0.0, pi, res)
2577+Y = linspace(0.0, pi, res)
2578+x = [0,0]
2579+
2580+data = empty([len(functions), res, res])
2581+for z, function in enumerate(functions):
2582+ for j, x[0] in enumerate(X):
2583+ for i, x[1] in enumerate(Y):
2584+ data[z,i,j] = eval(function + '(x)')
2585+ plt.subplot(n_rows, len(functions)/n_rows + 1, z+1)
2586+ CS = plt.contour(X, Y, data[z])
2587+ plt.clabel(CS, inline=1, fontsize=10)
2588+ plt.title(functions[z])
2589+
2590+plt.show()
2591
2592=== added file 'tests/mphase_mms_p2p1_compressible_ie_heat_flux/mphase_mms_p2p1_compressible_ie.py'
2593--- tests/mphase_mms_p2p1_compressible_ie_heat_flux/mphase_mms_p2p1_compressible_ie.py 1970-01-01 00:00:00 +0000
2594+++ tests/mphase_mms_p2p1_compressible_ie_heat_flux/mphase_mms_p2p1_compressible_ie.py 2013-02-08 22:48:22 +0000
2595@@ -0,0 +1,141 @@
2596+# This file was *autogenerated* from the file mphase_mms_p2p1_compressible_ie.sage.
2597+from sage.all_cmdline import * # import sage library
2598+_sage_const_2 = Integer(2); _sage_const_1p0 = RealNumber('1.0'); _sage_const_500p0 = RealNumber('500.0'); _sage_const_1p4 = RealNumber('1.4'); _sage_const_1p5 = RealNumber('1.5'); _sage_const_100p0 = RealNumber('100.0'); _sage_const_0p1 = RealNumber('0.1'); _sage_const_0p5 = RealNumber('0.5'); _sage_const_0p707106781 = RealNumber('0.707106781'); _sage_const_0p7 = RealNumber('0.7'); _sage_const_0p8 = RealNumber('0.8'); _sage_const_3p0 = RealNumber('3.0')
2599+y = var('y')
2600+
2601+def function(phi_0, phi_x, phi_y, phi_xy,
2602+ f_sin_x, f_cos_x, f_sin_y, f_cos_y, f_sin_xy, f_cos_xy,
2603+ alpha_x, alpha_y, alpha_xy):
2604+
2605+ f_0 = phi_0
2606+ f_x = phi_x*(f_sin_x*sin(alpha_x*x) + f_cos_x*cos(alpha_x*x))
2607+ f_y = phi_y*(f_sin_y*sin(alpha_y*y) + f_cos_y*cos(alpha_y*y))
2608+ f_xy = phi_xy*(f_sin_xy*sin(alpha_xy*x*y/pi) + f_cos_xy*cos(alpha_xy*x*y/pi))
2609+ f = f_0 + f_x + f_y + f_xy
2610+ return f
2611+
2612+rho1 = _sage_const_0p5 *(sin(x*x + y*y) + _sage_const_1p5 )
2613+rho2 = _sage_const_3p0
2614+
2615+ie1 = _sage_const_0p5 *(cos(x + y) + _sage_const_1p5 )
2616+ie2 = _sage_const_3p0 *y
2617+
2618+u1 = _sage_const_1p0 *(sin(x**_sage_const_2 +y**_sage_const_2 )+_sage_const_0p5 )
2619+v1 = _sage_const_0p1 *(cos(x**_sage_const_2 +y**_sage_const_2 )+_sage_const_0p5 )
2620+
2621+u2 = _sage_const_1p0 *(sin(x**_sage_const_2 +y**_sage_const_2 )+_sage_const_0p5 )
2622+v2 = _sage_const_0p1 *(cos(x**_sage_const_2 +y**_sage_const_2 )+_sage_const_0p5 )
2623+
2624+gamma = _sage_const_1p4
2625+rho0 = _sage_const_0p5
2626+csq = _sage_const_100p0
2627+#p = csq*(rho1 - rho0)
2628+p = (gamma-_sage_const_1p0 )*ie1*rho1
2629+
2630+vfrac1 = _sage_const_0p8
2631+vfrac2 = _sage_const_1p0 - vfrac1
2632+
2633+nu1 = _sage_const_0p7
2634+nu2 = _sage_const_0p7
2635+
2636+g_x = _sage_const_0p707106781
2637+g_y = _sage_const_0p707106781
2638+
2639+tau_xx1 = nu1*diff(u1,x)
2640+tau_yy1 = nu1*diff(v1,y)
2641+tau_xy1 = nu1*diff(u1,y)
2642+tau_yx1 = nu1*diff(v1,x)
2643+
2644+tau_xx2 = nu2*diff(u2,x)
2645+tau_yy2 = nu2*diff(v2,y)
2646+tau_xy2 = nu2*diff(u2,y)
2647+tau_yx2 = nu2*diff(v2,x)
2648+
2649+Su1 = vfrac1*rho1*u1*diff(u1,x) + vfrac1*rho1*v1*diff(u1,y) - diff(vfrac1*tau_xx1, x) - diff(vfrac1*tau_xy1, y) - vfrac1*g_x*rho1 + vfrac1*diff(p,x)
2650+Sv1 = vfrac1*rho1*u1*diff(v1,x) + vfrac1*rho1*v1*diff(v1,y) - diff(vfrac1*tau_yy1, y) - diff(vfrac1*tau_yx1, x) - vfrac1*g_y*rho1 + vfrac1*diff(p,y)
2651+
2652+Su2 = vfrac2*rho2*u2*diff(u2,x) + vfrac2*rho2*v2*diff(u2,y) - diff(vfrac2*tau_xx2, x) - diff(vfrac2*tau_xy2, y) - vfrac2*g_x*rho2 + vfrac2*diff(p,x)
2653+Sv2 = vfrac2*rho2*u2*diff(v2,x) + vfrac2*rho2*v2*diff(v2,y) - diff(vfrac2*tau_yy2, y) - diff(vfrac2*tau_yx2, x) - vfrac2*g_y*rho2 + vfrac2*diff(p,y)
2654+
2655+Srho1 = diff(vfrac1*u1*rho1,x) + diff(vfrac1*v1*rho1,y) + rho1*diff(u2*vfrac2, x) + rho1*diff(v2*vfrac2, y)
2656+
2657+k = _sage_const_0p5
2658+Cv1 = _sage_const_500p0
2659+Cv2 = _sage_const_500p0
2660+
2661+heat_flux_x1 = (k/Cv1)*vfrac1*diff(ie1,x)
2662+heat_flux_y1 = (k/Cv1)*vfrac1*diff(ie1,y)
2663+heat_flux_x2 = (k/Cv2)*vfrac2*diff(ie2,x)
2664+heat_flux_y2 = (k/Cv2)*vfrac2*diff(ie2,y)
2665+
2666+Sie1 = vfrac1*rho1*u1*diff(ie1, x) + vfrac1*rho1*v1*diff(ie1, y) + vfrac1*p*diff(u1, x) + vfrac1*p*diff(v1, y) - diff(heat_flux_x1, x) - diff(heat_flux_y1, y)
2667+Sie2 = vfrac2*rho2*u2*diff(ie2, x) + vfrac2*rho2*v2*diff(ie2, y) - diff(heat_flux_x2, x) - diff(heat_flux_y2, y)
2668+
2669+print 'from math import sin, cos, tanh, pi'
2670+print ''
2671+print 'def u1(X):'
2672+print ' return', str(u1).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2673+print ''
2674+print 'def v1(X):'
2675+print ' return', str(v1).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2676+print ''
2677+print 'def p(X):'
2678+print ' return', str(p).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2679+print ''
2680+print 'def rho1(X):'
2681+print ' return', str(rho1).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2682+print ''
2683+print 'def ie1(X):'
2684+print ' return', str(ie1).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2685+print ''
2686+print 'def vfrac1(X):'
2687+print ' return', str(vfrac1).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2688+print ''
2689+print 'def forcing_u1(X):'
2690+print ' return', str(Su1).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2691+print ''
2692+print 'def forcing_v1(X):'
2693+print ' return', str(Sv1).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2694+print ''
2695+print 'def forcing_rho1(X):'
2696+print ' return', str(Srho1).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2697+print ''
2698+print 'def forcing_ie1(X):'
2699+print ' return', str(Sie1).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2700+print ''
2701+print 'def velocity1(X):'
2702+print ' return [u1(X), v1(X)]'
2703+print ''
2704+print 'def forcing_velocity1(X):'
2705+print ' return [forcing_u1(X), forcing_v1(X)]'
2706+print ''
2707+print 'def u2(X):'
2708+print ' return', str(u2).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2709+print ''
2710+print 'def v2(X):'
2711+print ' return', str(v2).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2712+print ''
2713+print 'def rho2(X):'
2714+print ' return', str(rho2).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2715+print ''
2716+print 'def ie2(X):'
2717+print ' return', str(ie2).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2718+print ''
2719+print 'def vfrac2(X):'
2720+print ' return', str(vfrac2).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2721+print ''
2722+print 'def forcing_u2(X):'
2723+print ' return', str(Su2).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2724+print ''
2725+print 'def forcing_v2(X):'
2726+print ' return', str(Sv2).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2727+print ''
2728+print 'def forcing_ie2(X):'
2729+print ' return', str(Sie2).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2730+print ''
2731+print 'def velocity2(X):'
2732+print ' return [u2(X), v2(X)]'
2733+print ''
2734+print 'def forcing_velocity2(X):'
2735+print ' return [forcing_u2(X), forcing_v2(X)]'
2736+print ''
2737
2738=== added file 'tests/mphase_mms_p2p1_compressible_ie_heat_flux/mphase_mms_p2p1_compressible_ie.sage'
2739--- tests/mphase_mms_p2p1_compressible_ie_heat_flux/mphase_mms_p2p1_compressible_ie.sage 1970-01-01 00:00:00 +0000
2740+++ tests/mphase_mms_p2p1_compressible_ie_heat_flux/mphase_mms_p2p1_compressible_ie.sage 2013-02-08 22:48:22 +0000
2741@@ -0,0 +1,138 @@
2742+y = var('y')
2743+
2744+def function(phi_0, phi_x, phi_y, phi_xy,
2745+ f_sin_x, f_cos_x, f_sin_y, f_cos_y, f_sin_xy, f_cos_xy,
2746+ alpha_x, alpha_y, alpha_xy):
2747+
2748+ f_0 = phi_0
2749+ f_x = phi_x*(f_sin_x*sin(alpha_x*x) + f_cos_x*cos(alpha_x*x))
2750+ f_y = phi_y*(f_sin_y*sin(alpha_y*y) + f_cos_y*cos(alpha_y*y))
2751+ f_xy = phi_xy*(f_sin_xy*sin(alpha_xy*x*y/pi) + f_cos_xy*cos(alpha_xy*x*y/pi))
2752+ f = f_0 + f_x + f_y + f_xy
2753+ return f
2754+
2755+rho1 = 0.5*(sin(x*x + y*y) + 1.5)
2756+rho2 = 3.0
2757+
2758+ie1 = 0.5*(cos(x + y) + 1.5)
2759+ie2 = 3.0*y
2760+
2761+u1 = 1.0*(sin(x**2+y**2)+0.5)
2762+v1 = 0.1*(cos(x**2+y**2)+0.5)
2763+
2764+u2 = 1.0*(sin(x**2+y**2)+0.5)
2765+v2 = 0.1*(cos(x**2+y**2)+0.5)
2766+
2767+gamma = 1.4
2768+rho0 = 0.5
2769+csq = 100.0
2770+#p = csq*(rho1 - rho0)
2771+p = (gamma-1.0)*ie1*rho1
2772+
2773+vfrac1 = 0.8
2774+vfrac2 = 1.0 - vfrac1
2775+
2776+nu1 = 0.7
2777+nu2 = 0.7
2778+
2779+g_x = 0.707106781
2780+g_y = 0.707106781
2781+
2782+tau_xx1 = nu1*diff(u1,x)
2783+tau_yy1 = nu1*diff(v1,y)
2784+tau_xy1 = nu1*diff(u1,y)
2785+tau_yx1 = nu1*diff(v1,x)
2786+
2787+tau_xx2 = nu2*diff(u2,x)
2788+tau_yy2 = nu2*diff(v2,y)
2789+tau_xy2 = nu2*diff(u2,y)
2790+tau_yx2 = nu2*diff(v2,x)
2791+
2792+Su1 = vfrac1*rho1*u1*diff(u1,x) + vfrac1*rho1*v1*diff(u1,y) - diff(vfrac1*tau_xx1, x) - diff(vfrac1*tau_xy1, y) - vfrac1*g_x*rho1 + vfrac1*diff(p,x)
2793+Sv1 = vfrac1*rho1*u1*diff(v1,x) + vfrac1*rho1*v1*diff(v1,y) - diff(vfrac1*tau_yy1, y) - diff(vfrac1*tau_yx1, x) - vfrac1*g_y*rho1 + vfrac1*diff(p,y)
2794+
2795+Su2 = vfrac2*rho2*u2*diff(u2,x) + vfrac2*rho2*v2*diff(u2,y) - diff(vfrac2*tau_xx2, x) - diff(vfrac2*tau_xy2, y) - vfrac2*g_x*rho2 + vfrac2*diff(p,x)
2796+Sv2 = vfrac2*rho2*u2*diff(v2,x) + vfrac2*rho2*v2*diff(v2,y) - diff(vfrac2*tau_yy2, y) - diff(vfrac2*tau_yx2, x) - vfrac2*g_y*rho2 + vfrac2*diff(p,y)
2797+
2798+Srho1 = diff(vfrac1*u1*rho1,x) + diff(vfrac1*v1*rho1,y) + rho1*diff(u2*vfrac2, x) + rho1*diff(v2*vfrac2, y)
2799+
2800+k = 0.5
2801+Cv1 = 500.0
2802+Cv2 = 500.0
2803+
2804+heat_flux_x1 = (k/Cv1)*vfrac1*diff(ie1,x)
2805+heat_flux_y1 = (k/Cv1)*vfrac1*diff(ie1,y)
2806+heat_flux_x2 = (k/Cv2)*vfrac2*diff(ie2,x)
2807+heat_flux_y2 = (k/Cv2)*vfrac2*diff(ie2,y)
2808+
2809+Sie1 = vfrac1*rho1*u1*diff(ie1, x) + vfrac1*rho1*v1*diff(ie1, y) + vfrac1*p*diff(u1, x) + vfrac1*p*diff(v1, y) - diff(heat_flux_x1, x) - diff(heat_flux_y1, y)
2810+Sie2 = vfrac2*rho2*u2*diff(ie2, x) + vfrac2*rho2*v2*diff(ie2, y) - diff(heat_flux_x2, x) - diff(heat_flux_y2, y)
2811+
2812+print 'from math import sin, cos, tanh, pi'
2813+print ''
2814+print 'def u1(X):'
2815+print ' return', str(u1).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2816+print ''
2817+print 'def v1(X):'
2818+print ' return', str(v1).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2819+print ''
2820+print 'def p(X):'
2821+print ' return', str(p).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2822+print ''
2823+print 'def rho1(X):'
2824+print ' return', str(rho1).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2825+print ''
2826+print 'def ie1(X):'
2827+print ' return', str(ie1).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2828+print ''
2829+print 'def vfrac1(X):'
2830+print ' return', str(vfrac1).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2831+print ''
2832+print 'def forcing_u1(X):'
2833+print ' return', str(Su1).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2834+print ''
2835+print 'def forcing_v1(X):'
2836+print ' return', str(Sv1).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2837+print ''
2838+print 'def forcing_rho1(X):'
2839+print ' return', str(Srho1).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2840+print ''
2841+print 'def forcing_ie1(X):'
2842+print ' return', str(Sie1).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2843+print ''
2844+print 'def velocity1(X):'
2845+print ' return [u1(X), v1(X)]'
2846+print ''
2847+print 'def forcing_velocity1(X):'
2848+print ' return [forcing_u1(X), forcing_v1(X)]'
2849+print ''
2850+print 'def u2(X):'
2851+print ' return', str(u2).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2852+print ''
2853+print 'def v2(X):'
2854+print ' return', str(v2).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2855+print ''
2856+print 'def rho2(X):'
2857+print ' return', str(rho2).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2858+print ''
2859+print 'def ie2(X):'
2860+print ' return', str(ie2).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2861+print ''
2862+print 'def vfrac2(X):'
2863+print ' return', str(vfrac2).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2864+print ''
2865+print 'def forcing_u2(X):'
2866+print ' return', str(Su2).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2867+print ''
2868+print 'def forcing_v2(X):'
2869+print ' return', str(Sv2).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2870+print ''
2871+print 'def forcing_ie2(X):'
2872+print ' return', str(Sie2).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
2873+print ''
2874+print 'def velocity2(X):'
2875+print ' return [u2(X), v2(X)]'
2876+print ''
2877+print 'def forcing_velocity2(X):'
2878+print ' return [forcing_u2(X), forcing_v2(X)]'
2879+print ''
2880
2881=== added file 'tests/mphase_mms_p2p1_compressible_ie_heat_flux/mphase_mms_p2p1_compressible_ie_tools.py'
2882--- tests/mphase_mms_p2p1_compressible_ie_heat_flux/mphase_mms_p2p1_compressible_ie_tools.py 1970-01-01 00:00:00 +0000
2883+++ tests/mphase_mms_p2p1_compressible_ie_heat_flux/mphase_mms_p2p1_compressible_ie_tools.py 2013-02-08 22:48:22 +0000
2884@@ -0,0 +1,68 @@
2885+from math import sin, cos, tanh, pi
2886+
2887+def u1(X):
2888+ return sin(X[0]**2 + X[1]**2) + 0.500
2889+
2890+def v1(X):
2891+ return 0.100*cos(X[0]**2 + X[1]**2) + 0.0500
2892+
2893+def p(X):
2894+ return (0.200*cos(X[0] + X[1]) + 0.300)*(0.500*sin(X[0]**2 + X[1]**2) + 0.750)
2895+
2896+def rho1(X):
2897+ return 0.500*sin(X[0]**2 + X[1]**2) + 0.750
2898+
2899+def ie1(X):
2900+ return 0.500*cos(X[0] + X[1]) + 0.750
2901+
2902+def vfrac1(X):
2903+ return 0.800
2904+
2905+def forcing_u1(X):
2906+ return 2*(0.100*cos(X[0]**2 + X[1]**2) + 0.0500)*(0.400*sin(X[0]**2 + X[1]**2) + 0.600)*X[1]*cos(X[0]**2 + X[1]**2) + 2*(0.400*sin(X[0]**2 + X[1]**2) + 0.600)*(sin(X[0]**2 + X[1]**2) + 0.500)*X[0]*cos(X[0]**2 + X[1]**2) + 0.800*(0.200*cos(X[0] + X[1]) + 0.300)*X[0]*cos(X[0]**2 + X[1]**2) + 2.24*X[0]**2*sin(X[0]**2 + X[1]**2) + 2.24*X[1]**2*sin(X[0]**2 + X[1]**2) - 0.160*(0.500*sin(X[0]**2 + X[1]**2) + 0.750)*sin(X[0] + X[1]) - 0.282842712400000*sin(X[0]**2 + X[1]**2) - 2.24*cos(X[0]**2 + X[1]**2) - 0.424264068600000
2907+
2908+def forcing_v1(X):
2909+ return -0.200*(0.100*cos(X[0]**2 + X[1]**2) + 0.0500)*(0.400*sin(X[0]**2 + X[1]**2) + 0.600)*X[1]*sin(X[0]**2 + X[1]**2) - 0.200*(0.400*sin(X[0]**2 + X[1]**2) + 0.600)*(sin(X[0]**2 + X[1]**2) + 0.500)*X[0]*sin(X[0]**2 + X[1]**2) + 0.800*(0.200*cos(X[0] + X[1]) + 0.300)*X[1]*cos(X[0]**2 + X[1]**2) + 0.224*X[0]**2*cos(X[0]**2 + X[1]**2) + 0.224*X[1]**2*cos(X[0]**2 + X[1]**2) - 0.160*(0.500*sin(X[0]**2 + X[1]**2) + 0.750)*sin(X[0] + X[1]) - 0.0588427124000001*sin(X[0]**2 + X[1]**2) - 0.424264068600000
2910+
2911+def forcing_rho1(X):
2912+ return (0.0800*cos(X[0]**2 + X[1]**2) + 0.0400)*X[1]*cos(X[0]**2 + X[1]**2) + 2.00*(0.500*sin(X[0]**2 + X[1]**2) + 0.750)*X[0]*cos(X[0]**2 + X[1]**2) - 0.200*(0.500*sin(X[0]**2 + X[1]**2) + 0.750)*X[1]*sin(X[0]**2 + X[1]**2) + (0.800*sin(X[0]**2 + X[1]**2) + 0.400)*X[0]*cos(X[0]**2 + X[1]**2)
2913+
2914+def forcing_ie1(X):
2915+ return 1.60*(0.200*cos(X[0] + X[1]) + 0.300)*(0.500*sin(X[0]**2 + X[1]**2) + 0.750)*X[0]*cos(X[0]**2 + X[1]**2) - 0.160*(0.200*cos(X[0] + X[1]) + 0.300)*(0.500*sin(X[0]**2 + X[1]**2) + 0.750)*X[1]*sin(X[0]**2 + X[1]**2) - 0.500*(0.100*cos(X[0]**2 + X[1]**2) + 0.0500)*(0.400*sin(X[0]**2 + X[1]**2) + 0.600)*sin(X[0] + X[1]) - 0.500*(0.400*sin(X[0]**2 + X[1]**2) + 0.600)*(sin(X[0]**2 + X[1]**2) + 0.500)*sin(X[0] + X[1]) + 0.000800*cos(X[0] + X[1])
2916+
2917+def velocity1(X):
2918+ return [u1(X), v1(X)]
2919+
2920+def forcing_velocity1(X):
2921+ return [forcing_u1(X), forcing_v1(X)]
2922+
2923+def u2(X):
2924+ return sin(X[0]**2 + X[1]**2) + 0.500
2925+
2926+def v2(X):
2927+ return 0.100*cos(X[0]**2 + X[1]**2) + 0.0500
2928+
2929+def rho2(X):
2930+ return 3.00
2931+
2932+def ie2(X):
2933+ return 3.00*X[1]
2934+
2935+def vfrac2(X):
2936+ return 0.200
2937+
2938+def forcing_u2(X):
2939+ return 2*(0.0600*cos(X[0]**2 + X[1]**2) + 0.0300)*X[1]*cos(X[0]**2 + X[1]**2) + 0.200*(0.200*cos(X[0] + X[1]) + 0.300)*X[0]*cos(X[0]**2 + X[1]**2) + 2*(0.600*sin(X[0]**2 + X[1]**2) + 0.300)*X[0]*cos(X[0]**2 + X[1]**2) + 0.560*X[0]**2*sin(X[0]**2 + X[1]**2) + 0.560*X[1]**2*sin(X[0]**2 + X[1]**2) - 0.0400*(0.500*sin(X[0]**2 + X[1]**2) + 0.750)*sin(X[0] + X[1]) - 0.560*cos(X[0]**2 + X[1]**2) - 0.424264068600000
2940+
2941+def forcing_v2(X):
2942+ return -0.200*(0.0600*cos(X[0]**2 + X[1]**2) + 0.0300)*X[1]*sin(X[0]**2 + X[1]**2) + 0.200*(0.200*cos(X[0] + X[1]) + 0.300)*X[1]*cos(X[0]**2 + X[1]**2) - 0.200*(0.600*sin(X[0]**2 + X[1]**2) + 0.300)*X[0]*sin(X[0]**2 + X[1]**2) + 0.0560*X[0]**2*cos(X[0]**2 + X[1]**2) + 0.0560*X[1]**2*cos(X[0]**2 + X[1]**2) - 0.0400*(0.500*sin(X[0]**2 + X[1]**2) + 0.750)*sin(X[0] + X[1]) + 0.0560*sin(X[0]**2 + X[1]**2) - 0.424264068600000
2943+
2944+def forcing_ie2(X):
2945+ return 0.180*cos(X[0]**2 + X[1]**2) + 0.0900
2946+
2947+def velocity2(X):
2948+ return [u2(X), v2(X)]
2949+
2950+def forcing_velocity2(X):
2951+ return [forcing_u2(X), forcing_v2(X)]
2952+
2953
2954=== added directory 'tests/mphase_mms_p2p1_compressible_ie_heat_flux/src'
2955=== added file 'tests/mphase_mms_p2p1_compressible_ie_heat_flux/src/MMS_A.geo'
2956--- tests/mphase_mms_p2p1_compressible_ie_heat_flux/src/MMS_A.geo 1970-01-01 00:00:00 +0000
2957+++ tests/mphase_mms_p2p1_compressible_ie_heat_flux/src/MMS_A.geo 2013-02-08 22:48:22 +0000
2958@@ -0,0 +1,15 @@
2959+Point(1) = {-0.1,0.2,0,0.1};
2960+Point(2) = {0.7,0.2,0,0.1};
2961+Point(3) = {0.7,0.8,0,0.1};
2962+Point(4) = {-0.1,0.8,0,0.1};
2963+Line(1) = {4,3};
2964+Line(2) = {3,2};
2965+Line(3) = {2,1};
2966+Line(4) = {1,4};
2967+Line Loop(5) = {1,2,3,4};
2968+Plane Surface(6) = {5};
2969+Physical Line(7) = {3};
2970+Physical Line(8) = {2};
2971+Physical Line(9) = {1};
2972+Physical Line(10) = {4};
2973+Physical Surface(12) = {6};
2974
2975=== added file 'tests/mphase_mms_p2p1_compressible_ie_heat_flux/src/MMS_A.msh'
2976Binary files tests/mphase_mms_p2p1_compressible_ie_heat_flux/src/MMS_A.msh 1970-01-01 00:00:00 +0000 and tests/mphase_mms_p2p1_compressible_ie_heat_flux/src/MMS_A.msh 2013-02-08 22:48:22 +0000 differ
2977=== added file 'tests/mphase_mms_p2p1_compressible_ie_heat_flux/src/MMS_B.geo'
2978--- tests/mphase_mms_p2p1_compressible_ie_heat_flux/src/MMS_B.geo 1970-01-01 00:00:00 +0000
2979+++ tests/mphase_mms_p2p1_compressible_ie_heat_flux/src/MMS_B.geo 2013-02-08 22:48:22 +0000
2980@@ -0,0 +1,15 @@
2981+Point(1) = {-0.1,0.2,0,0.05};
2982+Point(2) = {0.7,0.2,0,0.05};
2983+Point(3) = {0.7,0.8,0,0.05};
2984+Point(4) = {-0.1,0.8,0,0.05};
2985+Line(1) = {4,3};
2986+Line(2) = {3,2};
2987+Line(3) = {2,1};
2988+Line(4) = {1,4};
2989+Line Loop(5) = {1,2,3,4};
2990+Plane Surface(6) = {5};
2991+Physical Line(7) = {3};
2992+Physical Line(8) = {2};
2993+Physical Line(9) = {1};
2994+Physical Line(10) = {4};
2995+Physical Surface(12) = {6};
2996
2997=== added file 'tests/mphase_mms_p2p1_compressible_ie_heat_flux/src/MMS_B.msh'
2998Binary files tests/mphase_mms_p2p1_compressible_ie_heat_flux/src/MMS_B.msh 1970-01-01 00:00:00 +0000 and tests/mphase_mms_p2p1_compressible_ie_heat_flux/src/MMS_B.msh 2013-02-08 22:48:22 +0000 differ
2999=== added file 'tests/mphase_mms_p2p1_compressible_ie_heat_flux/src/MMS_C.geo'
3000--- tests/mphase_mms_p2p1_compressible_ie_heat_flux/src/MMS_C.geo 1970-01-01 00:00:00 +0000
3001+++ tests/mphase_mms_p2p1_compressible_ie_heat_flux/src/MMS_C.geo 2013-02-08 22:48:22 +0000
3002@@ -0,0 +1,15 @@
3003+Point(1) = {-0.1,0.2,0,0.025};
3004+Point(2) = {0.7,0.2,0,0.025};
3005+Point(3) = {0.7,0.8,0,0.025};
3006+Point(4) = {-0.1,0.8,0,0.025};
3007+Line(1) = {4,3};
3008+Line(2) = {3,2};
3009+Line(3) = {2,1};
3010+Line(4) = {1,4};
3011+Line Loop(5) = {1,2,3,4};
3012+Plane Surface(6) = {5};
3013+Physical Line(7) = {3};
3014+Physical Line(8) = {2};
3015+Physical Line(9) = {1};
3016+Physical Line(10) = {4};
3017+Physical Surface(12) = {6};
3018
3019=== added file 'tests/mphase_mms_p2p1_compressible_ie_heat_flux/src/MMS_C.msh'
3020Binary files tests/mphase_mms_p2p1_compressible_ie_heat_flux/src/MMS_C.msh 1970-01-01 00:00:00 +0000 and tests/mphase_mms_p2p1_compressible_ie_heat_flux/src/MMS_C.msh 2013-02-08 22:48:22 +0000 differ
3021=== added file 'tests/mphase_mms_p2p1_compressible_ie_heat_flux/src/MMS_X.geo'
3022--- tests/mphase_mms_p2p1_compressible_ie_heat_flux/src/MMS_X.geo 1970-01-01 00:00:00 +0000
3023+++ tests/mphase_mms_p2p1_compressible_ie_heat_flux/src/MMS_X.geo 2013-02-08 22:48:22 +0000
3024@@ -0,0 +1,18 @@
3025+pi = 3.141592653589793;
3026+n = XX;
3027+
3028+Point(1) = {0.0, 0.0, 0.0, 1};
3029+
3030+Extrude {pi, 0.0, 0.0} {
3031+ Point{1}; Layers{n};
3032+}
3033+
3034+Extrude {0.0, pi, 0.0} {
3035+ Line{1}; Layers{n};
3036+}
3037+
3038+Physical Line(7) = {1};
3039+Physical Line(8) = {2};
3040+Physical Line(9) = {3};
3041+Physical Line(10) = {4};
3042+Physical Surface(6) = {5};
3043
3044=== added directory 'tests/mphase_mms_p2p1_compressible_ie_p1cv'
3045=== added file 'tests/mphase_mms_p2p1_compressible_ie_p1cv/MMS_X.flml'
3046--- tests/mphase_mms_p2p1_compressible_ie_p1cv/MMS_X.flml 1970-01-01 00:00:00 +0000
3047+++ tests/mphase_mms_p2p1_compressible_ie_p1cv/MMS_X.flml 2013-02-08 22:48:22 +0000
3048@@ -0,0 +1,1235 @@
3049+<?xml version='1.0' encoding='utf-8'?>
3050+<fluidity_options>
3051+ <simulation_name>
3052+ <string_value lines="1">MMS_X</string_value>
3053+ </simulation_name>
3054+ <problem_type>
3055+ <string_value lines="1">fluids</string_value>
3056+ </problem_type>
3057+ <geometry>
3058+ <dimension>
3059+ <integer_value rank="0">2</integer_value>
3060+ </dimension>
3061+ <mesh name="CoordinateMesh">
3062+ <from_file file_name="src/MMS_X">
3063+ <format name="gmsh"/>
3064+ <stat>
3065+ <include_in_stat/>
3066+ </stat>
3067+ </from_file>
3068+ </mesh>
3069+ <mesh name="VelocityMesh">
3070+ <from_mesh>
3071+ <mesh name="CoordinateMesh"/>
3072+ <mesh_shape>
3073+ <polynomial_degree>
3074+ <integer_value rank="0">2</integer_value>
3075+ </polynomial_degree>
3076+ </mesh_shape>
3077+ <stat>
3078+ <exclude_from_stat/>
3079+ </stat>
3080+ </from_mesh>
3081+ </mesh>
3082+ <mesh name="PressureMesh">
3083+ <from_mesh>
3084+ <mesh name="CoordinateMesh"/>
3085+ <mesh_shape>
3086+ <polynomial_degree>
3087+ <integer_value rank="0">1</integer_value>
3088+ </polynomial_degree>
3089+ </mesh_shape>
3090+ <stat>
3091+ <exclude_from_stat/>
3092+ </stat>
3093+ </from_mesh>
3094+ </mesh>
3095+ <mesh name="ErrorMesh">
3096+ <from_mesh>
3097+ <mesh name="CoordinateMesh"/>
3098+ <mesh_shape>
3099+ <polynomial_degree>
3100+ <integer_value rank="0">4</integer_value>
3101+ </polynomial_degree>
3102+ </mesh_shape>
3103+ <mesh_continuity>
3104+ <string_value>continuous</string_value>
3105+ </mesh_continuity>
3106+ <stat>
3107+ <exclude_from_stat/>
3108+ </stat>
3109+ </from_mesh>
3110+ </mesh>
3111+ <mesh name="DensityMesh">
3112+ <from_mesh>
3113+ <mesh name="CoordinateMesh"/>
3114+ <mesh_shape>
3115+ <polynomial_degree>
3116+ <integer_value rank="0">2</integer_value>
3117+ </polynomial_degree>
3118+ </mesh_shape>
3119+ <stat>
3120+ <exclude_from_stat/>
3121+ </stat>
3122+ </from_mesh>
3123+ </mesh>
3124+ <quadrature>
3125+ <degree>
3126+ <integer_value rank="0">8</integer_value>
3127+ </degree>
3128+ </quadrature>
3129+ </geometry>
3130+ <io>
3131+ <dump_format>
3132+ <string_value>vtk</string_value>
3133+ </dump_format>
3134+ <dump_period>
3135+ <constant>
3136+ <real_value rank="0">1000.0</real_value>
3137+ </constant>
3138+ </dump_period>
3139+ <output_mesh name="VelocityMesh"/>
3140+ <stat>
3141+ <output_at_start/>
3142+ </stat>
3143+ </io>
3144+ <timestepping>
3145+ <current_time>
3146+ <real_value rank="0">0.0</real_value>
3147+ </current_time>
3148+ <timestep>
3149+ <real_value rank="0">999.9</real_value>
3150+ <comment>gives a max cfl number of approximately 0.1</comment>
3151+ </timestep>
3152+ <finish_time>
3153+ <real_value rank="0">1000.0</real_value>
3154+ <comment>10.0</comment>
3155+ </finish_time>
3156+ <nonlinear_iterations>
3157+ <integer_value rank="0">2</integer_value>
3158+ <tolerance>
3159+ <real_value rank="0">1.0e-9</real_value>
3160+ <infinity_norm/>
3161+ </tolerance>
3162+ </nonlinear_iterations>
3163+ <steady_state>
3164+ <tolerance>
3165+ <real_value rank="0">1.E-7</real_value>
3166+ <infinity_norm/>
3167+ </tolerance>
3168+ </steady_state>
3169+ </timestepping>
3170+ <physical_parameters>
3171+ <gravity>
3172+ <magnitude>
3173+ <real_value rank="0">1.0</real_value>
3174+ </magnitude>
3175+ <vector_field name="GravityDirection" rank="1">
3176+ <prescribed>
3177+ <mesh name="CoordinateMesh"/>
3178+ <value name="WholeMesh">
3179+ <constant>
3180+ <real_value shape="2" dim1="dim" rank="1">0.707106781 0.707106781</real_value>
3181+ </constant>
3182+ </value>
3183+ <output/>
3184+ <stat>
3185+ <include_in_stat/>
3186+ </stat>
3187+ <detectors>
3188+ <exclude_from_detectors/>
3189+ </detectors>
3190+ </prescribed>
3191+ </vector_field>
3192+ </gravity>
3193+ </physical_parameters>
3194+ <material_phase name="Phase1">
3195+ <equation_of_state>
3196+ <compressible>
3197+ <stiffened_gas>
3198+ <ratio_specific_heats>
3199+ <real_value rank="0">1.4</real_value>
3200+ </ratio_specific_heats>
3201+ </stiffened_gas>
3202+ </compressible>
3203+ </equation_of_state>
3204+ <scalar_field name="Pressure" rank="0">
3205+ <prognostic>
3206+ <mesh name="PressureMesh"/>
3207+ <spatial_discretisation>
3208+ <continuous_galerkin>
3209+ <remove_stabilisation_term/>
3210+ </continuous_galerkin>
3211+ </spatial_discretisation>
3212+ <scheme>
3213+ <poisson_pressure_solution>
3214+ <string_value lines="1">never</string_value>
3215+ </poisson_pressure_solution>
3216+ <use_compressible_projection_method/>
3217+ </scheme>
3218+ <solver>
3219+ <iterative_method name="gmres">
3220+ <restart>
3221+ <integer_value rank="0">30</integer_value>
3222+ </restart>
3223+ </iterative_method>
3224+ <preconditioner name="sor"/>
3225+ <relative_error>
3226+ <real_value rank="0">1.0e-7</real_value>
3227+ </relative_error>
3228+ <max_iterations>
3229+ <integer_value rank="0">10000</integer_value>
3230+ </max_iterations>
3231+ <never_ignore_solver_failures/>
3232+ <diagnostics>
3233+ <monitors/>
3234+ </diagnostics>
3235+ </solver>
3236+ <output>
3237+ <include_previous_time_step/>
3238+ </output>
3239+ <stat/>
3240+ <convergence>
3241+ <include_in_convergence/>
3242+ </convergence>
3243+ <detectors>
3244+ <exclude_from_detectors/>
3245+ </detectors>
3246+ <steady_state>
3247+ <exclude_from_steady_state/>
3248+ </steady_state>
3249+ <consistent_interpolation/>
3250+ </prognostic>
3251+ </scalar_field>
3252+ <scalar_field name="Density" rank="0">
3253+ <prognostic>
3254+ <mesh name="DensityMesh"/>
3255+ <spatial_discretisation>
3256+ <control_volumes>
3257+ <face_value name="FirstOrderUpwind"/>
3258+ </control_volumes>
3259+ <conservative_advection>
3260+ <real_value rank="0">0.0</real_value>
3261+ </conservative_advection>
3262+ </spatial_discretisation>
3263+ <temporal_discretisation>
3264+ <theta>
3265+ <real_value rank="0">1.0</real_value>
3266+ </theta>
3267+ </temporal_discretisation>
3268+ <initial_condition name="WholeMesh">
3269+ <python>
3270+ <string_value lines="20" type="code" language="python">def val(X,t):
3271+ import mphase_mms_p2p1_compressible_ie_p1cv_tools as tools
3272+ return tools.rho1(X)</string_value>
3273+ </python>
3274+ </initial_condition>
3275+ <boundary_conditions name="All">
3276+ <surface_ids>
3277+ <integer_value shape="2" rank="1">7 10</integer_value>
3278+ </surface_ids>
3279+ <type name="dirichlet">
3280+ <python>
3281+ <string_value lines="20" type="code" language="python">def val(X,t):
3282+ import mphase_mms_p2p1_compressible_ie_p1cv_tools as tools
3283+ return tools.rho1(X)</string_value>
3284+ </python>
3285+ </type>
3286+ </boundary_conditions>
3287+ <scalar_field name="Source" rank="0">
3288+ <prescribed>
3289+ <value name="WholeMesh">
3290+ <python>
3291+ <string_value lines="20" type="code" language="python">def val(X,t):
3292+ import mphase_mms_p2p1_compressible_ie_p1cv_tools as tools
3293+ return tools.forcing_rho1(X)</string_value>
3294+ </python>
3295+ </value>
3296+ <output/>
3297+ <stat/>
3298+ <detectors>
3299+ <exclude_from_detectors/>
3300+ </detectors>
3301+ </prescribed>
3302+ </scalar_field>
3303+ <output/>
3304+ <stat/>
3305+ <convergence>
3306+ <include_in_convergence/>
3307+ </convergence>
3308+ <detectors>
3309+ <include_in_detectors/>
3310+ </detectors>
3311+ <steady_state>
3312+ <include_in_steady_state/>
3313+ </steady_state>
3314+ <consistent_interpolation/>
3315+ </prognostic>
3316+ </scalar_field>
3317+ <vector_field name="Velocity" rank="1">
3318+ <prognostic>
3319+ <mesh name="VelocityMesh"/>
3320+ <equation name="LinearMomentum"/>
3321+ <spatial_discretisation>
3322+ <continuous_galerkin>
3323+ <stabilisation>
3324+ <no_stabilisation/>
3325+ </stabilisation>
3326+ <mass_terms>
3327+ <lump_mass_matrix>
3328+ <use_submesh/>
3329+ </lump_mass_matrix>
3330+ </mass_terms>
3331+ <advection_terms/>
3332+ <stress_terms>
3333+ <tensor_form/>
3334+ </stress_terms>
3335+ </continuous_galerkin>
3336+ <conservative_advection>
3337+ <real_value rank="0">0.0</real_value>
3338+ </conservative_advection>
3339+ </spatial_discretisation>
3340+ <temporal_discretisation>
3341+ <theta>
3342+ <real_value rank="0">1.0</real_value>
3343+ </theta>
3344+ <relaxation>
3345+ <real_value rank="0">0.5</real_value>
3346+ </relaxation>
3347+ </temporal_discretisation>
3348+ <solver>
3349+ <iterative_method name="gmres">
3350+ <restart>
3351+ <integer_value rank="0">30</integer_value>
3352+ </restart>
3353+ </iterative_method>
3354+ <preconditioner name="sor"/>
3355+ <relative_error>
3356+ <real_value rank="0">1e-7</real_value>
3357+ </relative_error>
3358+ <max_iterations>
3359+ <integer_value rank="0">10000</integer_value>
3360+ </max_iterations>
3361+ <never_ignore_solver_failures/>
3362+ <diagnostics>
3363+ <monitors/>
3364+ </diagnostics>
3365+ </solver>
3366+ <initial_condition name="WholeMesh">
3367+ <constant>
3368+ <real_value shape="2" dim1="dim" rank="1">0.0 0.0</real_value>
3369+ </constant>
3370+ </initial_condition>
3371+ <boundary_conditions name="All">
3372+ <surface_ids>
3373+ <integer_value shape="4" rank="1">7 8 9 10</integer_value>
3374+ </surface_ids>
3375+ <type name="dirichlet">
3376+ <align_bc_with_cartesian>
3377+ <x_component>
3378+ <python>
3379+ <string_value lines="20" type="code" language="python">def val(X,t):
3380+ import mphase_mms_p2p1_compressible_ie_p1cv_tools as tools
3381+ return tools.u1(X)</string_value>
3382+ </python>
3383+ </x_component>
3384+ <y_component>
3385+ <python>
3386+ <string_value lines="20" type="code" language="python">def val(X,t):
3387+ import mphase_mms_p2p1_compressible_ie_p1cv_tools as tools
3388+ return tools.v1(X)</string_value>
3389+ </python>
3390+ </y_component>
3391+ </align_bc_with_cartesian>
3392+ </type>
3393+ </boundary_conditions>
3394+ <tensor_field name="Viscosity" rank="2">
3395+ <prescribed>
3396+ <value name="WholeMesh">
3397+ <isotropic>
3398+ <constant>
3399+ <real_value rank="0">0.7</real_value>
3400+ </constant>
3401+ </isotropic>
3402+ </value>
3403+ <output/>
3404+ </prescribed>
3405+ </tensor_field>
3406+ <vector_field name="Source" rank="1">
3407+ <prescribed>
3408+ <value name="WholeMesh">
3409+ <python>
3410+ <string_value lines="20" type="code" language="python">def val(X,t):
3411+ import mphase_mms_p2p1_compressible_ie_p1cv_tools as tools
3412+ density = tools.rho1(X)
3413+ forcing_velocity1 = tools.forcing_velocity1(X)
3414+ # Remember to divide through by density here
3415+ # because we multiply through by Density in
3416+ # Momentum_CG.F90.
3417+ return (forcing_velocity1[0]/density, forcing_velocity1[1]/density)</string_value>
3418+ </python>
3419+ </value>
3420+ <output/>
3421+ <stat>
3422+ <include_in_stat/>
3423+ </stat>
3424+ <detectors>
3425+ <exclude_from_detectors/>
3426+ </detectors>
3427+ </prescribed>
3428+ </vector_field>
3429+ <output/>
3430+ <stat>
3431+ <include_in_stat/>
3432+ <previous_time_step>
3433+ <exclude_from_stat/>
3434+ </previous_time_step>
3435+ <nonlinear_field>
3436+ <exclude_from_stat/>
3437+ </nonlinear_field>
3438+ </stat>
3439+ <convergence>
3440+ <include_in_convergence/>
3441+ </convergence>
3442+ <detectors>
3443+ <include_in_detectors/>
3444+ </detectors>
3445+ <steady_state>
3446+ <exclude_from_steady_state/>
3447+ </steady_state>
3448+ <consistent_interpolation/>
3449+ </prognostic>
3450+ </vector_field>
3451+ <scalar_field name="CFLNumber" rank="0">
3452+ <diagnostic>
3453+ <algorithm name="Internal" material_phase_support="multiple"/>
3454+ <mesh name="VelocityMesh"/>
3455+ <output/>
3456+ <stat/>
3457+ <convergence>
3458+ <include_in_convergence/>
3459+ </convergence>
3460+ <detectors>
3461+ <include_in_detectors/>
3462+ </detectors>
3463+ <steady_state>
3464+ <exclude_from_steady_state/>
3465+ </steady_state>
3466+ </diagnostic>
3467+ </scalar_field>
3468+ <scalar_field name="InternalEnergy" rank="0">
3469+ <prognostic>
3470+ <mesh name="PressureMesh"/>
3471+ <equation name="InternalEnergy">
3472+ <density name="Density"/>
3473+ </equation>
3474+ <spatial_discretisation>
3475+ <control_volumes>
3476+ <face_value name="FirstOrderUpwind"/>
3477+ <diffusion_scheme name="ElementGradient"/>
3478+ </control_volumes>
3479+ <conservative_advection>
3480+ <real_value rank="0">0.0</real_value>
3481+ </conservative_advection>
3482+ </spatial_discretisation>
3483+ <temporal_discretisation>
3484+ <theta>
3485+ <real_value rank="0">1.0</real_value>
3486+ </theta>
3487+ </temporal_discretisation>
3488+ <solver>
3489+ <iterative_method name="gmres">
3490+ <restart>
3491+ <integer_value rank="0">30</integer_value>
3492+ </restart>
3493+ </iterative_method>
3494+ <preconditioner name="sor"/>
3495+ <relative_error>
3496+ <real_value rank="0">1.0e-7</real_value>
3497+ </relative_error>
3498+ <max_iterations>
3499+ <integer_value rank="0">10000</integer_value>
3500+ </max_iterations>
3501+ <never_ignore_solver_failures/>
3502+ <diagnostics>
3503+ <monitors/>
3504+ </diagnostics>
3505+ </solver>
3506+ <initial_condition name="WholeMesh">
3507+ <python>
3508+ <string_value lines="20" type="code" language="python">def val(X,t):
3509+ import mphase_mms_p2p1_compressible_ie_p1cv_tools as tools
3510+ return tools.ie1(X)</string_value>
3511+ </python>
3512+ </initial_condition>
3513+ <boundary_conditions name="All">
3514+ <surface_ids>
3515+ <integer_value shape="2" rank="1">7 10</integer_value>
3516+ </surface_ids>
3517+ <type name="dirichlet">
3518+ <python>
3519+ <string_value lines="20" type="code" language="python">def val(X,t):
3520+ import mphase_mms_p2p1_compressible_ie_p1cv_tools as tools
3521+ return tools.ie1(X)</string_value>
3522+ </python>
3523+ </type>
3524+ </boundary_conditions>
3525+ <tensor_field name="Diffusivity" rank="2">
3526+ <prescribed>
3527+ <value name="WholeMesh">
3528+ <isotropic>
3529+ <constant>
3530+ <real_value rank="0">0.001</real_value>
3531+ </constant>
3532+ </isotropic>
3533+ </value>
3534+ <output/>
3535+ </prescribed>
3536+ </tensor_field>
3537+ <scalar_field name="Source" rank="0">
3538+ <prescribed>
3539+ <value name="WholeMesh">
3540+ <python>
3541+ <string_value lines="20" type="code" language="python">def val(X,t):
3542+ import mphase_mms_p2p1_compressible_ie_p1cv_tools as tools
3543+ return tools.forcing_ie1(X)</string_value>
3544+ </python>
3545+ </value>
3546+ <output/>
3547+ <stat/>
3548+ <detectors>
3549+ <exclude_from_detectors/>
3550+ </detectors>
3551+ </prescribed>
3552+ </scalar_field>
3553+ <output/>
3554+ <stat/>
3555+ <convergence>
3556+ <include_in_convergence/>
3557+ </convergence>
3558+ <detectors>
3559+ <include_in_detectors/>
3560+ </detectors>
3561+ <steady_state>
3562+ <include_in_steady_state/>
3563+ </steady_state>
3564+ <consistent_interpolation/>
3565+ </prognostic>
3566+ </scalar_field>
3567+ <scalar_field name="InternalEnergyAnalytical" rank="0">
3568+ <prescribed>
3569+ <mesh name="ErrorMesh"/>
3570+ <value name="WholeMesh">
3571+ <python>
3572+ <string_value lines="20" type="code" language="python">def val(X,t):
3573+ import mphase_mms_p2p1_compressible_ie_p1cv_tools as tools
3574+ return tools.ie1(X)</string_value>
3575+ </python>
3576+ </value>
3577+ <output/>
3578+ <stat/>
3579+ <detectors>
3580+ <exclude_from_detectors/>
3581+ </detectors>
3582+ </prescribed>
3583+ </scalar_field>
3584+ <scalar_field name="InternalEnergyError" rank="0">
3585+ <diagnostic>
3586+ <algorithm source_field_2_type="scalar" name="scalar_difference" source_field_1_name="InternalEnergyAnalytical" source_field_2_name="InternalEnergyProjection" material_phase_support="single" source_field_1_type="scalar">
3587+ <absolute_difference/>
3588+ </algorithm>
3589+ <mesh name="ErrorMesh"/>
3590+ <output/>
3591+ <stat/>
3592+ <convergence>
3593+ <include_in_convergence/>
3594+ </convergence>
3595+ <detectors>
3596+ <include_in_detectors/>
3597+ </detectors>
3598+ <steady_state>
3599+ <include_in_steady_state/>
3600+ </steady_state>
3601+ </diagnostic>
3602+ </scalar_field>
3603+ <scalar_field name="InternalEnergyProjection" rank="0">
3604+ <diagnostic>
3605+ <algorithm source_field_type="scalar" material_phase_support="single" name="scalar_galerkin_projection" source_field_name="InternalEnergy">
3606+ <solver>
3607+ <iterative_method name="cg"/>
3608+ <preconditioner name="sor"/>
3609+ <relative_error>
3610+ <real_value rank="0">1e-10</real_value>
3611+ </relative_error>
3612+ <max_iterations>
3613+ <integer_value rank="0">1000</integer_value>
3614+ </max_iterations>
3615+ <never_ignore_solver_failures/>
3616+ <diagnostics>
3617+ <monitors/>
3618+ </diagnostics>
3619+ </solver>
3620+ </algorithm>
3621+ <mesh name="ErrorMesh"/>
3622+ <output/>
3623+ <stat/>
3624+ <convergence>
3625+ <include_in_convergence/>
3626+ </convergence>
3627+ <detectors>
3628+ <include_in_detectors/>
3629+ </detectors>
3630+ <steady_state>
3631+ <include_in_steady_state/>
3632+ </steady_state>
3633+ </diagnostic>
3634+ </scalar_field>
3635+ <scalar_field name="PressureAnalytical" rank="0">
3636+ <prescribed>
3637+ <mesh name="ErrorMesh"/>
3638+ <value name="WholeMesh">
3639+ <python>
3640+ <string_value lines="20" type="code" language="python">def val(X,t):
3641+ import mphase_mms_p2p1_compressible_ie_p1cv_tools as tools
3642+ return tools.p(X)</string_value>
3643+ </python>
3644+ </value>
3645+ <output/>
3646+ <stat/>
3647+ <detectors>
3648+ <exclude_from_detectors/>
3649+ </detectors>
3650+ </prescribed>
3651+ </scalar_field>
3652+ <scalar_field name="PressureProjection" rank="0">
3653+ <diagnostic>
3654+ <algorithm source_field_type="scalar" material_phase_support="single" name="scalar_galerkin_projection" source_field_name="Pressure">
3655+ <solver>
3656+ <iterative_method name="cg"/>
3657+ <preconditioner name="sor"/>
3658+ <relative_error>
3659+ <real_value rank="0">1e-10</real_value>
3660+ </relative_error>
3661+ <max_iterations>
3662+ <integer_value rank="0">1000</integer_value>
3663+ </max_iterations>
3664+ <never_ignore_solver_failures/>
3665+ <diagnostics>
3666+ <monitors/>
3667+ </diagnostics>
3668+ </solver>
3669+ </algorithm>
3670+ <mesh name="ErrorMesh"/>
3671+ <output/>
3672+ <stat/>
3673+ <convergence>
3674+ <include_in_convergence/>
3675+ </convergence>
3676+ <detectors>
3677+ <include_in_detectors/>
3678+ </detectors>
3679+ <steady_state>
3680+ <exclude_from_steady_state/>
3681+ </steady_state>
3682+ </diagnostic>
3683+ </scalar_field>
3684+ <scalar_field name="PressureError" rank="0">
3685+ <diagnostic>
3686+ <algorithm source_field_2_type="scalar" name="scalar_difference" source_field_1_name="PressureProjection" source_field_2_name="PressureAnalytical" material_phase_support="single" source_field_1_type="scalar">
3687+ <absolute_difference/>
3688+ </algorithm>
3689+ <mesh name="ErrorMesh"/>
3690+ <output/>
3691+ <stat/>
3692+ <convergence>
3693+ <include_in_convergence/>
3694+ </convergence>
3695+ <detectors>
3696+ <include_in_detectors/>
3697+ </detectors>
3698+ <steady_state>
3699+ <include_in_steady_state/>
3700+ </steady_state>
3701+ </diagnostic>
3702+ </scalar_field>
3703+ <scalar_field name="DensityAnalytical" rank="0">
3704+ <prescribed>
3705+ <mesh name="ErrorMesh"/>
3706+ <value name="WholeMesh">
3707+ <python>
3708+ <string_value lines="20" type="code" language="python">def val(X,t):
3709+ import mphase_mms_p2p1_compressible_ie_p1cv_tools as tools
3710+ return tools.rho1(X)</string_value>
3711+ </python>
3712+ </value>
3713+ <output/>
3714+ <stat/>
3715+ <detectors>
3716+ <exclude_from_detectors/>
3717+ </detectors>
3718+ </prescribed>
3719+ </scalar_field>
3720+ <scalar_field name="DensityError" rank="0">
3721+ <diagnostic>
3722+ <algorithm source_field_2_type="scalar" name="scalar_difference" source_field_1_name="DensityAnalytical" source_field_2_name="DensityProjection" material_phase_support="single" source_field_1_type="scalar">
3723+ <absolute_difference/>
3724+ </algorithm>
3725+ <mesh name="ErrorMesh"/>
3726+ <output/>
3727+ <stat/>
3728+ <convergence>
3729+ <include_in_convergence/>
3730+ </convergence>
3731+ <detectors>
3732+ <include_in_detectors/>
3733+ </detectors>
3734+ <steady_state>
3735+ <include_in_steady_state/>
3736+ </steady_state>
3737+ </diagnostic>
3738+ </scalar_field>
3739+ <scalar_field name="DensityProjection" rank="0">
3740+ <diagnostic>
3741+ <algorithm source_field_type="scalar" material_phase_support="single" name="scalar_galerkin_projection" source_field_name="Density">
3742+ <solver>
3743+ <iterative_method name="cg"/>
3744+ <preconditioner name="sor"/>
3745+ <relative_error>
3746+ <real_value rank="0">1e-10</real_value>
3747+ </relative_error>
3748+ <max_iterations>
3749+ <integer_value rank="0">1000</integer_value>
3750+ </max_iterations>
3751+ <never_ignore_solver_failures/>
3752+ <diagnostics>
3753+ <monitors/>
3754+ </diagnostics>
3755+ </solver>
3756+ </algorithm>
3757+ <mesh name="ErrorMesh"/>
3758+ <output/>
3759+ <stat/>
3760+ <convergence>
3761+ <include_in_convergence/>
3762+ </convergence>
3763+ <detectors>
3764+ <include_in_detectors/>
3765+ </detectors>
3766+ <steady_state>
3767+ <include_in_steady_state/>
3768+ </steady_state>
3769+ </diagnostic>
3770+ </scalar_field>
3771+ <scalar_field name="PhaseVolumeFraction" rank="0">
3772+ <diagnostic>
3773+ <mesh name="CoordinateMesh"/>
3774+ <algorithm name="Internal" material_phase_support="multiple"/>
3775+ <output/>
3776+ <stat/>
3777+ <detectors>
3778+ <include_in_detectors/>
3779+ </detectors>
3780+ </diagnostic>
3781+ </scalar_field>
3782+ <vector_field name="VelocityAnalytical" rank="1">
3783+ <prescribed>
3784+ <mesh name="ErrorMesh"/>
3785+ <value name="WholeMesh">
3786+ <python>
3787+ <string_value lines="20" type="code" language="python">def val(X,t):
3788+ import mphase_mms_p2p1_compressible_ie_p1cv_tools as tools
3789+ return tools.velocity1(X)</string_value>
3790+ </python>
3791+ </value>
3792+ <output/>
3793+ <stat>
3794+ <include_in_stat/>
3795+ </stat>
3796+ <detectors>
3797+ <exclude_from_detectors/>
3798+ </detectors>
3799+ </prescribed>
3800+ </vector_field>
3801+ <vector_field name="VelocityProjection" rank="1">
3802+ <diagnostic>
3803+ <algorithm source_field_type="vector" material_phase_support="single" name="vector_galerkin_projection" source_field_name="Velocity">
3804+ <solver>
3805+ <iterative_method name="cg"/>
3806+ <preconditioner name="sor"/>
3807+ <relative_error>
3808+ <real_value rank="0">1e-10</real_value>
3809+ </relative_error>
3810+ <max_iterations>
3811+ <integer_value rank="0">1000</integer_value>
3812+ </max_iterations>
3813+ <never_ignore_solver_failures/>
3814+ <diagnostics>
3815+ <monitors/>
3816+ </diagnostics>
3817+ </solver>
3818+ </algorithm>
3819+ <mesh name="ErrorMesh"/>
3820+ <output/>
3821+ <stat>
3822+ <include_in_stat/>
3823+ </stat>
3824+ <convergence>
3825+ <include_in_convergence/>
3826+ </convergence>
3827+ <detectors>
3828+ <include_in_detectors/>
3829+ </detectors>
3830+ <steady_state>
3831+ <exclude_from_steady_state/>
3832+ </steady_state>
3833+ </diagnostic>
3834+ </vector_field>
3835+ <vector_field name="VelocityError" rank="1">
3836+ <diagnostic>
3837+ <algorithm source_field_2_type="vector" name="vector_difference" source_field_1_name="VelocityProjection" source_field_2_name="VelocityAnalytical" material_phase_support="single" source_field_1_type="vector">
3838+ <absolute_difference/>
3839+ </algorithm>
3840+ <mesh name="ErrorMesh"/>
3841+ <output/>
3842+ <stat>
3843+ <include_in_stat/>
3844+ </stat>
3845+ <convergence>
3846+ <include_in_convergence/>
3847+ </convergence>
3848+ <detectors>
3849+ <include_in_detectors/>
3850+ </detectors>
3851+ <steady_state>
3852+ <include_in_steady_state/>
3853+ </steady_state>
3854+ </diagnostic>
3855+ </vector_field>
3856+ <multiphase_properties>
3857+ <effective_conductivity>
3858+ <real_value rank="0">0.5</real_value>
3859+ </effective_conductivity>
3860+ <specific_heat>
3861+ <real_value rank="0">700.0</real_value>
3862+ </specific_heat>
3863+ </multiphase_properties>
3864+ </material_phase>
3865+ <material_phase name="Phase2">
3866+ <equation_of_state>
3867+ <fluids>
3868+ <linear>
3869+ <reference_density>
3870+ <real_value rank="0">3.0</real_value>
3871+ </reference_density>
3872+ </linear>
3873+ </fluids>
3874+ </equation_of_state>
3875+ <scalar_field name="Pressure" rank="0">
3876+ <aliased material_phase_name="Phase1" field_name="Pressure"/>
3877+ </scalar_field>
3878+ <scalar_field name="Density" rank="0">
3879+ <diagnostic>
3880+ <algorithm name="Internal" material_phase_support="multiple"/>
3881+ <mesh name="DensityMesh"/>
3882+ <output/>
3883+ <stat/>
3884+ <convergence>
3885+ <include_in_convergence/>
3886+ </convergence>
3887+ <detectors>
3888+ <include_in_detectors/>
3889+ </detectors>
3890+ <steady_state>
3891+ <include_in_steady_state/>
3892+ </steady_state>
3893+ </diagnostic>
3894+ </scalar_field>
3895+ <vector_field name="Velocity" rank="1">
3896+ <prognostic>
3897+ <mesh name="VelocityMesh"/>
3898+ <equation name="LinearMomentum"/>
3899+ <spatial_discretisation>
3900+ <continuous_galerkin>
3901+ <stabilisation>
3902+ <no_stabilisation/>
3903+ </stabilisation>
3904+ <mass_terms>
3905+ <lump_mass_matrix>
3906+ <use_submesh/>
3907+ </lump_mass_matrix>
3908+ </mass_terms>
3909+ <advection_terms/>
3910+ <stress_terms>
3911+ <tensor_form/>
3912+ </stress_terms>
3913+ </continuous_galerkin>
3914+ <conservative_advection>
3915+ <real_value rank="0">0.0</real_value>
3916+ </conservative_advection>
3917+ </spatial_discretisation>
3918+ <temporal_discretisation>
3919+ <theta>
3920+ <real_value rank="0">1.0</real_value>
3921+ </theta>
3922+ <relaxation>
3923+ <real_value rank="0">0.5</real_value>
3924+ </relaxation>
3925+ </temporal_discretisation>
3926+ <solver>
3927+ <iterative_method name="gmres">
3928+ <restart>
3929+ <integer_value rank="0">30</integer_value>
3930+ </restart>
3931+ </iterative_method>
3932+ <preconditioner name="sor"/>
3933+ <relative_error>
3934+ <real_value rank="0">1e-7</real_value>
3935+ </relative_error>
3936+ <max_iterations>
3937+ <integer_value rank="0">10000</integer_value>
3938+ </max_iterations>
3939+ <never_ignore_solver_failures/>
3940+ <diagnostics>
3941+ <monitors/>
3942+ </diagnostics>
3943+ </solver>
3944+ <initial_condition name="WholeMesh">
3945+ <constant>
3946+ <real_value shape="2" dim1="dim" rank="1">0.0 0.0</real_value>
3947+ </constant>
3948+ </initial_condition>
3949+ <boundary_conditions name="All">
3950+ <surface_ids>
3951+ <integer_value shape="4" rank="1">7 8 9 10</integer_value>
3952+ </surface_ids>
3953+ <type name="dirichlet">
3954+ <align_bc_with_cartesian>
3955+ <x_component>
3956+ <python>
3957+ <string_value lines="20" type="code" language="python">def val(X,t):
3958+ import mphase_mms_p2p1_compressible_ie_p1cv_tools as tools
3959+ return tools.u2(X)</string_value>
3960+ </python>
3961+ </x_component>
3962+ <y_component>
3963+ <python>
3964+ <string_value lines="20" type="code" language="python">def val(X,t):
3965+ import mphase_mms_p2p1_compressible_ie_p1cv_tools as tools
3966+ return tools.v2(X)</string_value>
3967+ </python>
3968+ </y_component>
3969+ </align_bc_with_cartesian>
3970+ </type>
3971+ </boundary_conditions>
3972+ <tensor_field name="Viscosity" rank="2">
3973+ <prescribed>
3974+ <value name="WholeMesh">
3975+ <isotropic>
3976+ <constant>
3977+ <real_value rank="0">0.7</real_value>
3978+ </constant>
3979+ </isotropic>
3980+ </value>
3981+ <output/>
3982+ </prescribed>
3983+ </tensor_field>
3984+ <vector_field name="Source" rank="1">
3985+ <prescribed>
3986+ <value name="WholeMesh">
3987+ <python>
3988+ <string_value lines="20" type="code" language="python">def val(X,t):
3989+ import mphase_mms_p2p1_compressible_ie_p1cv_tools as tools
3990+ density = tools.rho2(X)
3991+ forcing_velocity2 = tools.forcing_velocity2(X)
3992+ # Remember to divide through by density here
3993+ # because we multiply through by Density in
3994+ # Momentum_CG.F90.
3995+ return (forcing_velocity2[0]/density, forcing_velocity2[1]/density)</string_value>
3996+ </python>
3997+ </value>
3998+ <output/>
3999+ <stat>
4000+ <include_in_stat/>
4001+ </stat>
4002+ <detectors>
4003+ <exclude_from_detectors/>
4004+ </detectors>
4005+ </prescribed>
4006+ </vector_field>
4007+ <output/>
4008+ <stat>
4009+ <include_in_stat/>
4010+ <previous_time_step>
4011+ <exclude_from_stat/>
4012+ </previous_time_step>
4013+ <nonlinear_field>
4014+ <exclude_from_stat/>
4015+ </nonlinear_field>
4016+ </stat>
4017+ <convergence>
4018+ <include_in_convergence/>
4019+ </convergence>
4020+ <detectors>
4021+ <include_in_detectors/>
4022+ </detectors>
4023+ <steady_state>
4024+ <exclude_from_steady_state/>
4025+ </steady_state>
4026+ <consistent_interpolation/>
4027+ </prognostic>
4028+ </vector_field>
4029+ <scalar_field name="CFLNumber" rank="0">
4030+ <diagnostic>
4031+ <algorithm name="Internal" material_phase_support="multiple"/>
4032+ <mesh name="VelocityMesh"/>
4033+ <output/>
4034+ <stat/>
4035+ <convergence>
4036+ <include_in_convergence/>
4037+ </convergence>
4038+ <detectors>
4039+ <include_in_detectors/>
4040+ </detectors>
4041+ <steady_state>
4042+ <exclude_from_steady_state/>
4043+ </steady_state>
4044+ </diagnostic>
4045+ </scalar_field>
4046+ <scalar_field name="InternalEnergy" rank="0">
4047+ <prognostic>
4048+ <mesh name="PressureMesh"/>
4049+ <equation name="InternalEnergy">
4050+ <density name="Density"/>
4051+ </equation>
4052+ <spatial_discretisation>
4053+ <control_volumes>
4054+ <face_value name="FirstOrderUpwind"/>
4055+ <diffusion_scheme name="ElementGradient"/>
4056+ </control_volumes>
4057+ <conservative_advection>
4058+ <real_value rank="0">0.0</real_value>
4059+ </conservative_advection>
4060+ </spatial_discretisation>
4061+ <temporal_discretisation>
4062+ <theta>
4063+ <real_value rank="0">1.0</real_value>
4064+ </theta>
4065+ </temporal_discretisation>
4066+ <solver>
4067+ <iterative_method name="gmres">
4068+ <restart>
4069+ <integer_value rank="0">30</integer_value>
4070+ </restart>
4071+ </iterative_method>
4072+ <preconditioner name="sor"/>
4073+ <relative_error>
4074+ <real_value rank="0">1.0e-7</real_value>
4075+ </relative_error>
4076+ <max_iterations>
4077+ <integer_value rank="0">10000</integer_value>
4078+ </max_iterations>
4079+ <never_ignore_solver_failures/>
4080+ <diagnostics>
4081+ <monitors/>
4082+ </diagnostics>
4083+ </solver>
4084+ <initial_condition name="WholeMesh">
4085+ <python>
4086+ <string_value lines="20" type="code" language="python">def val(X,t):
4087+ import mphase_mms_p2p1_compressible_ie_p1cv_tools as tools
4088+ return tools.ie2(X)</string_value>
4089+ </python>
4090+ </initial_condition>
4091+ <boundary_conditions name="All">
4092+ <surface_ids>
4093+ <integer_value shape="2" rank="1">7 10</integer_value>
4094+ </surface_ids>
4095+ <type name="dirichlet">
4096+ <python>
4097+ <string_value lines="20" type="code" language="python">def val(X,t):
4098+ import mphase_mms_p2p1_compressible_ie_p1cv_tools as tools
4099+ return tools.ie2(X)</string_value>
4100+ </python>
4101+ </type>
4102+ </boundary_conditions>
4103+ <tensor_field name="Diffusivity" rank="2">
4104+ <prescribed>
4105+ <value name="WholeMesh">
4106+ <isotropic>
4107+ <constant>
4108+ <real_value rank="0">0.001</real_value>
4109+ </constant>
4110+ </isotropic>
4111+ </value>
4112+ <output/>
4113+ </prescribed>
4114+ </tensor_field>
4115+ <scalar_field name="Source" rank="0">
4116+ <prescribed>
4117+ <value name="WholeMesh">
4118+ <python>
4119+ <string_value lines="20" type="code" language="python">def val(X,t):
4120+ import mphase_mms_p2p1_compressible_ie_p1cv_tools as tools
4121+ return tools.forcing_ie2(X)</string_value>
4122+ </python>
4123+ </value>
4124+ <output/>
4125+ <stat/>
4126+ <detectors>
4127+ <exclude_from_detectors/>
4128+ </detectors>
4129+ </prescribed>
4130+ </scalar_field>
4131+ <output/>
4132+ <stat/>
4133+ <convergence>
4134+ <include_in_convergence/>
4135+ </convergence>
4136+ <detectors>
4137+ <include_in_detectors/>
4138+ </detectors>
4139+ <steady_state>
4140+ <include_in_steady_state/>
4141+ </steady_state>
4142+ <consistent_interpolation/>
4143+ </prognostic>
4144+ </scalar_field>
4145+ <scalar_field name="InternalEnergyAnalytical" rank="0">
4146+ <prescribed>
4147+ <mesh name="PressureMesh"/>
4148+ <value name="WholeMesh">
4149+ <python>
4150+ <string_value lines="20" type="code" language="python">def val(X,t):
4151+ import mphase_mms_p2p1_compressible_ie_p1cv_tools as tools
4152+ return tools.ie2(X)</string_value>
4153+ </python>
4154+ </value>
4155+ <output/>
4156+ <stat/>
4157+ <detectors>
4158+ <exclude_from_detectors/>
4159+ </detectors>
4160+ </prescribed>
4161+ </scalar_field>
4162+ <scalar_field name="PhaseVolumeFraction" rank="0">
4163+ <prescribed>
4164+ <mesh name="CoordinateMesh"/>
4165+ <value name="WholeMesh">
4166+ <python>
4167+ <string_value lines="20" type="code" language="python">def val(X,t):
4168+ import mphase_mms_p2p1_compressible_ie_p1cv_tools as tools
4169+ return tools.vfrac2(X)</string_value>
4170+ </python>
4171+ </value>
4172+ <output/>
4173+ <stat/>
4174+ <detectors>
4175+ <exclude_from_detectors/>
4176+ </detectors>
4177+ </prescribed>
4178+ </scalar_field>
4179+ <scalar_field name="ScalarAbsoluteDifference" rank="0">
4180+ <diagnostic field_name_b="InternalEnergy" field_name_a="InternalEnergyAnalytical">
4181+ <algorithm name="Internal" material_phase_support="multiple"/>
4182+ <mesh name="PressureMesh"/>
4183+ <output/>
4184+ <stat/>
4185+ <convergence>
4186+ <include_in_convergence/>
4187+ </convergence>
4188+ <detectors>
4189+ <include_in_detectors/>
4190+ </detectors>
4191+ <steady_state>
4192+ <include_in_steady_state/>
4193+ </steady_state>
4194+ </diagnostic>
4195+ </scalar_field>
4196+ <vector_field name="VelocityAnalytical" rank="1">
4197+ <prescribed>
4198+ <mesh name="ErrorMesh"/>
4199+ <value name="WholeMesh">
4200+ <python>
4201+ <string_value lines="20" type="code" language="python">def val(X,t):
4202+ import mphase_mms_p2p1_compressible_ie_p1cv_tools as tools
4203+ return tools.velocity2(X)</string_value>
4204+ </python>
4205+ </value>
4206+ <output/>
4207+ <stat>
4208+ <include_in_stat/>
4209+ </stat>
4210+ <detectors>
4211+ <exclude_from_detectors/>
4212+ </detectors>
4213+ </prescribed>
4214+ </vector_field>
4215+ <vector_field name="VelocityProjection" rank="1">
4216+ <diagnostic>
4217+ <algorithm source_field_type="vector" material_phase_support="single" name="vector_galerkin_projection" source_field_name="Velocity">
4218+ <solver>
4219+ <iterative_method name="gmres">
4220+ <restart>
4221+ <integer_value rank="0">30</integer_value>
4222+ </restart>
4223+ </iterative_method>
4224+ <preconditioner name="sor"/>
4225+ <relative_error>
4226+ <real_value rank="0">1e-10</real_value>
4227+ </relative_error>
4228+ <max_iterations>
4229+ <integer_value rank="0">1000</integer_value>
4230+ </max_iterations>
4231+ <never_ignore_solver_failures/>
4232+ <diagnostics>
4233+ <monitors/>
4234+ </diagnostics>
4235+ </solver>
4236+ </algorithm>
4237+ <mesh name="ErrorMesh"/>
4238+ <output/>
4239+ <stat>
4240+ <include_in_stat/>
4241+ </stat>
4242+ <convergence>
4243+ <include_in_convergence/>
4244+ </convergence>
4245+ <detectors>
4246+ <include_in_detectors/>
4247+ </detectors>
4248+ <steady_state>
4249+ <exclude_from_steady_state/>
4250+ </steady_state>
4251+ </diagnostic>
4252+ </vector_field>
4253+ <vector_field name="VelocityError" rank="1">
4254+ <diagnostic>
4255+ <algorithm source_field_2_type="vector" name="vector_difference" source_field_1_name="VelocityProjection" source_field_2_name="VelocityAnalytical" material_phase_support="single" source_field_1_type="vector">
4256+ <absolute_difference/>
4257+ </algorithm>
4258+ <mesh name="ErrorMesh"/>
4259+ <output/>
4260+ <stat>
4261+ <include_in_stat/>
4262+ </stat>
4263+ <convergence>
4264+ <include_in_convergence/>
4265+ </convergence>
4266+ <detectors>
4267+ <include_in_detectors/>
4268+ </detectors>
4269+ <steady_state>
4270+ <include_in_steady_state/>
4271+ </steady_state>
4272+ </diagnostic>
4273+ </vector_field>
4274+ <multiphase_properties>
4275+ <particle_diameter>
4276+ <real_value rank="0">0.1</real_value>
4277+ </particle_diameter>
4278+ <specific_heat>
4279+ <real_value rank="0">700.0</real_value>
4280+ </specific_heat>
4281+ </multiphase_properties>
4282+ </material_phase>
4283+</fluidity_options>
4284
4285=== added file 'tests/mphase_mms_p2p1_compressible_ie_p1cv/Makefile'
4286--- tests/mphase_mms_p2p1_compressible_ie_p1cv/Makefile 1970-01-01 00:00:00 +0000
4287+++ tests/mphase_mms_p2p1_compressible_ie_p1cv/Makefile 2013-02-08 22:48:22 +0000
4288@@ -0,0 +1,8 @@
4289+input: clean
4290+ ./copy_script
4291+ gmsh -2 -bin src/MMS_A.geo
4292+ gmsh -2 -bin src/MMS_B.geo
4293+ gmsh -2 -bin src/MMS_C.geo
4294+
4295+clean:
4296+ rm -f *.vtu *.stat *.s *.log *_A* *_B* *_C* matrix* *~ mphase_mms_p2p1_compressible_ie_p1cv.py *.pyc fluidity.*
4297
4298=== added file 'tests/mphase_mms_p2p1_compressible_ie_p1cv/copy_script'
4299--- tests/mphase_mms_p2p1_compressible_ie_p1cv/copy_script 1970-01-01 00:00:00 +0000
4300+++ tests/mphase_mms_p2p1_compressible_ie_p1cv/copy_script 2013-02-08 22:48:22 +0000
4301@@ -0,0 +1,23 @@
4302+#!/bin/bash
4303+
4304+n=4
4305+for F in A B C
4306+do
4307+ echo creating set $F with n_ele=$n
4308+
4309+ cp MMS_X.flml MMS_$F.flml
4310+ sed s/MMS_X/MMS_$F/ MMS_$F.flml > MMS_$F.flml.cp
4311+
4312+ #sed s/XX/$n/ src/MMS_X.geo > src/MMS_$F.geo
4313+
4314+ n=$((n*2))
4315+done
4316+
4317+echo setting flml timestep values
4318+
4319+sed s/999.9/0.005/ MMS_A.flml.cp > MMS_A.flml
4320+rm MMS_A.flml.cp
4321+sed s/999.9/0.0025/ MMS_B.flml.cp > MMS_B.flml
4322+rm MMS_B.flml.cp
4323+sed s/999.9/0.00125/ MMS_C.flml.cp > MMS_C.flml
4324+rm MMS_C.flml.cp
4325
4326=== added file 'tests/mphase_mms_p2p1_compressible_ie_p1cv/mphase_mms_p2p1_compressible_ie_p1cv.sage'
4327--- tests/mphase_mms_p2p1_compressible_ie_p1cv/mphase_mms_p2p1_compressible_ie_p1cv.sage 1970-01-01 00:00:00 +0000
4328+++ tests/mphase_mms_p2p1_compressible_ie_p1cv/mphase_mms_p2p1_compressible_ie_p1cv.sage 2013-02-08 22:48:22 +0000
4329@@ -0,0 +1,156 @@
4330+y = var('y')
4331+
4332+def function(phi_0, phi_x, phi_y, phi_xy,
4333+ f_sin_x, f_cos_x, f_sin_y, f_cos_y, f_sin_xy, f_cos_xy,
4334+ alpha_x, alpha_y, alpha_xy):
4335+
4336+ f_0 = phi_0
4337+ f_x = phi_x*(f_sin_x*sin(alpha_x*x) + f_cos_x*cos(alpha_x*x))
4338+ f_y = phi_y*(f_sin_y*sin(alpha_y*y) + f_cos_y*cos(alpha_y*y))
4339+ f_xy = phi_xy*(f_sin_xy*sin(alpha_xy*x*y/pi) + f_cos_xy*cos(alpha_xy*x*y/pi))
4340+ f = f_0 + f_x + f_y + f_xy
4341+ return f
4342+
4343+ie1 = 0.5*(cos(x + y) + 1.5)
4344+ie2 = 2.5*(sin(x*x) + 1.5)
4345+#ie2 = 3.0*y
4346+
4347+#u1 = 0.25*(sin(2*x+(x**2)*(y**2))+0.5)
4348+#v1 = 0.1*(cos(x**2+y**2)+0.5)
4349+
4350+#u2 = 1.0*(sin(x**2+y**2)+0.25)
4351+#v2 = 1.15*(cos(x*y)+0.75)
4352+
4353+u1 = 1.0*(sin(x**2+y**2)+0.5)
4354+v1 = 0.1*(cos(x**2+y**2)+0.5)
4355+u2 = cos(x**2+y**2)+2.5*x
4356+v2 = 0.5*x*y
4357+
4358+rho1 = 0.5*(sin(x*x + y*y) + 1.5)
4359+rho2 = 3.0
4360+
4361+ie1 = 1.25*x*y + cos(x + y)
4362+ie2 = sin(x*y)
4363+
4364+
4365+gamma = 1.4
4366+rho0 = 0.5
4367+csq = 100.0
4368+#p = csq*(rho1 - rho0)
4369+p = (gamma-1.0)*ie1*rho1
4370+
4371+#vfrac1 = 0.5*cos(x)*cos(x) + 0.1
4372+vfrac1 = 0.8
4373+vfrac2 = 1.0 - vfrac1
4374+
4375+nu1 = 0.7
4376+nu2 = 0.7
4377+
4378+g_x = 0.707106781
4379+g_y = 0.707106781
4380+
4381+tau_xx1 = nu1*diff(u1,x)
4382+tau_yy1 = nu1*diff(v1,y)
4383+tau_xy1 = nu1*diff(u1,y)
4384+tau_yx1 = nu1*diff(v1,x)
4385+
4386+tau_xx2 = nu2*diff(u2,x)
4387+tau_yy2 = nu2*diff(v2,y)
4388+tau_xy2 = nu2*diff(u2,y)
4389+tau_yx2 = nu2*diff(v2,x)
4390+
4391+Su1 = vfrac1*rho1*u1*diff(u1,x) + vfrac1*rho1*v1*diff(u1,y) - diff(vfrac1*tau_xx1, x) - diff(vfrac1*tau_xy1, y) - vfrac1*g_x*rho1 + vfrac1*diff(p,x)
4392+Sv1 = vfrac1*rho1*u1*diff(v1,x) + vfrac1*rho1*v1*diff(v1,y) - diff(vfrac1*tau_yy1, y) - diff(vfrac1*tau_yx1, x) - vfrac1*g_y*rho1 + vfrac1*diff(p,y)
4393+
4394+Su2 = vfrac2*rho2*u2*diff(u2,x) + vfrac2*rho2*v2*diff(u2,y) - diff(vfrac2*tau_xx2, x) - diff(vfrac2*tau_xy2, y) - vfrac2*g_x*rho2 + vfrac2*diff(p,x)
4395+Sv2 = vfrac2*rho2*u2*diff(v2,x) + vfrac2*rho2*v2*diff(v2,y) - diff(vfrac2*tau_yy2, y) - diff(vfrac2*tau_yx2, x) - vfrac2*g_y*rho2 + vfrac2*diff(p,y)
4396+
4397+Srho1 = diff(vfrac1*u1*rho1,x) + diff(vfrac1*v1*rho1,y) + rho1*diff(u2*vfrac2, x) + rho1*diff(v2*vfrac2, y)
4398+
4399+# Heat transfer term for the internal energy equations
4400+k = 0.5
4401+Cv1 = 500.0
4402+Cv2 = 500.0
4403+d = 0.1
4404+
4405+Pr = Cv1*gamma*nu1/k
4406+Re = rho1*d*(sqrt((u1 - u2)**2 + (v1 - v2)**2))/nu1
4407+Nu = (7.0 - 10.0*vfrac1 + 5.0*vfrac1**2)*(1.0 + 0.7*(Re**0.2)*(Pr**(1.0/3.0))) + (1.33 - 2.4*vfrac1 + 1.2*vfrac1**2)*(Re**0.7)*(Pr**(1.0/3.0))
4408+Q = (6.0*k*vfrac2*Nu/(d**2))*(ie2/Cv2 - ie1/Cv1)
4409+
4410+heat_flux_x1 = (k/Cv1)*vfrac1*diff(ie1,x)
4411+heat_flux_y1 = (k/Cv1)*vfrac1*diff(ie1,y)
4412+heat_flux_x2 = (k/Cv2)*vfrac2*diff(ie2,x)
4413+heat_flux_y2 = (k/Cv2)*vfrac2*diff(ie2,y)
4414+
4415+Sie1 = vfrac1*rho1*u1*diff(ie1, x) + vfrac1*rho1*v1*diff(ie1, y) - diff(heat_flux_x1, x) - diff(heat_flux_y1, y) + vfrac1*p*diff(u1, x) + vfrac1*p*diff(v1, y) #- Q
4416+Sie2 = vfrac2*rho2*u2*diff(ie2, x) + vfrac2*rho2*v2*diff(ie2, y) - diff(heat_flux_x2, x) - diff(heat_flux_y2, y) #+ Q
4417+
4418+print 'from math import sin, cos, tanh, pi, sqrt'
4419+print ''
4420+print 'def u1(X):'
4421+print ' return', str(u1).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
4422+print ''
4423+print 'def v1(X):'
4424+print ' return', str(v1).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
4425+print ''
4426+print 'def p(X):'
4427+print ' return', str(p).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
4428+print ''
4429+print 'def rho1(X):'
4430+print ' return', str(rho1).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
4431+print ''
4432+print 'def ie1(X):'
4433+print ' return', str(ie1).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
4434+print ''
4435+print 'def vfrac1(X):'
4436+print ' return', str(vfrac1).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
4437+print ''
4438+print 'def forcing_u1(X):'
4439+print ' return', str(Su1).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
4440+print ''
4441+print 'def forcing_v1(X):'
4442+print ' return', str(Sv1).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
4443+print ''
4444+print 'def forcing_rho1(X):'
4445+print ' return', str(Srho1).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
4446+print ''
4447+print 'def forcing_ie1(X):'
4448+print ' return', str(Sie1).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
4449+print ''
4450+print 'def velocity1(X):'
4451+print ' return [u1(X), v1(X)]'
4452+print ''
4453+print 'def forcing_velocity1(X):'
4454+print ' return [forcing_u1(X), forcing_v1(X)]'
4455+print ''
4456+print 'def u2(X):'
4457+print ' return', str(u2).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
4458+print ''
4459+print 'def v2(X):'
4460+print ' return', str(v2).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
4461+print ''
4462+print 'def rho2(X):'
4463+print ' return', str(rho2).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
4464+print ''
4465+print 'def ie2(X):'
4466+print ' return', str(ie2).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
4467+print ''
4468+print 'def vfrac2(X):'
4469+print ' return', str(vfrac2).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
4470+print ''
4471+print 'def forcing_u2(X):'
4472+print ' return', str(Su2).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
4473+print ''
4474+print 'def forcing_v2(X):'
4475+print ' return', str(Sv2).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
4476+print ''
4477+print 'def forcing_ie2(X):'
4478+print ' return', str(Sie2).replace('e^', 'exp').replace('^', '**').replace('000000000000', '').replace('x', 'X[0]').replace('y', 'X[1]')
4479+print ''
4480+print 'def velocity2(X):'
4481+print ' return [u2(X), v2(X)]'
4482+print ''
4483+print 'def forcing_velocity2(X):'
4484+print ' return [forcing_u2(X), forcing_v2(X)]'
4485+print ''
4486
4487=== added file 'tests/mphase_mms_p2p1_compressible_ie_p1cv/mphase_mms_p2p1_compressible_ie_p1cv.xml'
4488--- tests/mphase_mms_p2p1_compressible_ie_p1cv/mphase_mms_p2p1_compressible_ie_p1cv.xml 1970-01-01 00:00:00 +0000
4489+++ tests/mphase_mms_p2p1_compressible_ie_p1cv/mphase_mms_p2p1_compressible_ie_p1cv.xml 2013-02-08 22:48:22 +0000
4490@@ -0,0 +1,142 @@
4491+<?xml version="1.0" encoding="UTF-8" ?>
4492+<!DOCTYPE testproblem SYSTEM "regressiontest.dtd">
4493+<testproblem>
4494+ <name>mphase_mms_p2p1_compressible_ie_p1cv</name>
4495+ <owner userid="ctj10"/>
4496+ <tags>flml</tags>
4497+ <problem_definition length="special" nprocs="1">
4498+ <command_line>fluidity -v3 MMS_A.flml &gt; MMS_A.log; fluidity -v3 MMS_B.flml &gt; MMS_B.log; fluidity -v3 MMS_C.flml &gt; MMS_C.log; fluidity -v3 MMS_D.flml &gt; MMS_D.log</command_line>
4499+ </problem_definition>
4500+ <variables>
4501+ <variable name="convergence" language="python">
4502+from fluidity_tools import stat_parser as stat
4503+from math import log
4504+import numpy as np
4505+
4506+meshes = [['A','B']]#, ['B','C']]
4507+
4508+convergence = np.ones(5) * 1e10
4509+
4510+print ''
4511+print 'ORDER OF CONVERGENCE'
4512+print '-------------------------------------------'
4513+
4514+print 'VelocityError:'
4515+print '-------------------------------------------'
4516+
4517+for i, mesh in enumerate(meshes):
4518+
4519+ a_error_x = stat("MMS_"+str(mesh[0])+".stat")["Phase1"]["VelocityError%1"]["l2norm"][-1]
4520+ b_error_x = stat("MMS_"+str(mesh[1])+".stat")["Phase1"]["VelocityError%1"]["l2norm"][-1]
4521+ a_error_y = stat("MMS_"+str(mesh[0])+".stat")["Phase1"]["VelocityError%2"]["l2norm"][-1]
4522+ b_error_y = stat("MMS_"+str(mesh[1])+".stat")["Phase1"]["VelocityError%2"]["l2norm"][-1]
4523+
4524+ ratio_x = a_error_x / b_error_x
4525+ ratio_y = a_error_y / b_error_y
4526+
4527+ print mesh[0] + '->' + mesh[1] + ': ', [log(ratio_x, 2), log(ratio_y, 2)]
4528+
4529+ convergence[0] = min(log(ratio_x, 2), log(ratio_y, 2), convergence[0])
4530+
4531+print '-------------------------------------------'
4532+
4533+fields = [
4534+ 'PressureError',
4535+ 'InternalEnergyError',
4536+ 'DensityError',
4537+ ]
4538+
4539+for i, field in enumerate(fields):
4540+ print field
4541+ print '-------------------------------------------'
4542+
4543+ for j, mesh in enumerate(meshes):
4544+
4545+ a_error = stat("MMS_"+str(mesh[0])+".stat")["Phase1"][field]["l2norm"][-1]
4546+ b_error = stat("MMS_"+str(mesh[1])+".stat")["Phase1"][field]["l2norm"][-1]
4547+
4548+ ratio = a_error / b_error
4549+
4550+ print mesh[0] + '->' + mesh[1] + ': ', log(ratio, 2)
4551+
4552+ convergence[i+1] = min(log(ratio, 2), convergence[i+1])
4553+
4554+ print '-------------------------------------------'
4555+
4556+print ''
4557+
4558+
4559+fields = [
4560+ 'ScalarAbsoluteDifference',
4561+ ]
4562+
4563+for i, field in enumerate(fields):
4564+ print field
4565+ print '-------------------------------------------'
4566+
4567+ for j, mesh in enumerate(meshes):
4568+
4569+ a_error = stat("MMS_"+str(mesh[0])+".stat")["Phase2"][field]["l2norm"][-1]
4570+ b_error = stat("MMS_"+str(mesh[1])+".stat")["Phase2"][field]["l2norm"][-1]
4571+
4572+ ratio = a_error / b_error
4573+
4574+ print mesh[0] + '->' + mesh[1] + ': ', log(ratio, 2)
4575+
4576+ convergence[i+4] = min(log(ratio, 2), convergence[i+1])
4577+
4578+ print '-------------------------------------------'
4579+
4580+print ''
4581+
4582+ </variable>
4583+ <variable name="a_finish_time" language="python">
4584+from fluidity_tools import stat_parser as stat
4585+a_finish_time = stat("MMS_A.stat")["ElapsedTime"]["value"][-1]
4586+ </variable>
4587+ <variable name="b_finish_time" language="python">
4588+from fluidity_tools import stat_parser as stat
4589+b_finish_time = stat("MMS_B.stat")["ElapsedTime"]["value"][-1]
4590+ </variable>
4591+ <variable name="c_finish_time" language="python">
4592+from fluidity_tools import stat_parser as stat
4593+c_finish_time = stat("MMS_C.stat")["ElapsedTime"]["value"][-1]
4594+ </variable>
4595+ <variable name="d_finish_time" language="python">
4596+from fluidity_tools import stat_parser as stat
4597+d_finish_time = stat("MMS_D.stat")["ElapsedTime"]["value"][-1]
4598+ </variable>
4599+ </variables>
4600+ <pass_tests>
4601+ <test name="velocity convergence order > 2.8" language="python">
4602+assert(convergence[0] &gt; 2.8)
4603+ </test>
4604+ <test name="pressure convergence order > 1.9" language="python">
4605+assert(convergence[1] &gt; 1.9)
4606+ </test>
4607+ <test name="ie (phase 1) convergence order > 1.9" language="python">
4608+assert(convergence[2] &gt; 1.9)
4609+ </test>
4610+ <test name="density (phase 1) convergence order > 1.9" language="python">
4611+assert(convergence[3] &gt; 1.9)
4612+ </test>
4613+ <test name="ie (phase 2) convergence order > 1.9" language="python">
4614+assert(convergence[4] &gt; 1.9)
4615+ </test>
4616+ <test name="checking A finished in less than 100 seconds" language="python">
4617+assert(a_finish_time-100.0 &lt; 1.E-10)
4618+ </test>
4619+ <test name="checking B finished in less than 100 seconds" language="python">
4620+assert(b_finish_time-100.0 &lt; 1.E-10)
4621+ </test>
4622+ <test name="checking C finished in less than 100 seconds" language="python">
4623+assert(c_finish_time-100.0 &lt; 1.E-10)
4624+ </test>
4625+ <test name="checking D finished in less than 100 seconds" language="python">
4626+assert(d_finish_time-100.0 &lt; 1.E-10)
4627+ </test>
4628+ </pass_tests>
4629+ <warn_tests>
4630+ </warn_tests>
4631+</testproblem>
4632+
4633
4634=== added file 'tests/mphase_mms_p2p1_compressible_ie_p1cv/mphase_mms_p2p1_compressible_ie_p1cv_tools.py'
4635--- tests/mphase_mms_p2p1_compressible_ie_p1cv/mphase_mms_p2p1_compressible_ie_p1cv_tools.py 1970-01-01 00:00:00 +0000
4636+++ tests/mphase_mms_p2p1_compressible_ie_p1cv/mphase_mms_p2p1_compressible_ie_p1cv_tools.py 2013-02-08 22:48:22 +0000
4637@@ -0,0 +1,68 @@
4638+from math import sin, cos, tanh, pi, sqrt
4639+
4640+def u1(X):
4641+ return sin(X[0]**2 + X[1]**2) + 0.500
4642+
4643+def v1(X):
4644+ return 0.100*cos(X[0]**2 + X[1]**2) + 0.0500
4645+
4646+def p(X):
4647+ return (0.500*sin(X[0]**2 + X[1]**2) + 0.750)*(0.500*X[0]*X[1] + 0.400*cos(X[0] + X[1]))
4648+
4649+def rho1(X):
4650+ return 0.500*sin(X[0]**2 + X[1]**2) + 0.750
4651+
4652+def ie1(X):
4653+ return 1.25*X[0]*X[1] + cos(X[0] + X[1])
4654+
4655+def vfrac1(X):
4656+ return 0.800
4657+
4658+def forcing_u1(X):
4659+ return 2*(0.100*cos(X[0]**2 + X[1]**2) + 0.0500)*(0.400*sin(X[0]**2 + X[1]**2) + 0.600)*X[1]*cos(X[0]**2 + X[1]**2) + 2*(0.400*sin(X[0]**2 + X[1]**2) + 0.600)*(sin(X[0]**2 + X[1]**2) + 0.500)*X[0]*cos(X[0]**2 + X[1]**2) + 0.800*(0.500*X[0]*X[1] + 0.400*cos(X[0] + X[1]))*X[0]*cos(X[0]**2 + X[1]**2) + 2.24*X[0]**2*sin(X[0]**2 + X[1]**2) + 2.24*X[1]**2*sin(X[0]**2 + X[1]**2) + 0.800*(0.500*sin(X[0]**2 + X[1]**2) + 0.750)*(0.500*X[1] - 0.400*sin(X[0] + X[1])) - 0.282842712400000*sin(X[0]**2 + X[1]**2) - 2.24*cos(X[0]**2 + X[1]**2) - 0.424264068600000
4660+
4661+def forcing_v1(X):
4662+ return -0.200*(0.100*cos(X[0]**2 + X[1]**2) + 0.0500)*(0.400*sin(X[0]**2 + X[1]**2) + 0.600)*X[1]*sin(X[0]**2 + X[1]**2) - 0.200*(0.400*sin(X[0]**2 + X[1]**2) + 0.600)*(sin(X[0]**2 + X[1]**2) + 0.500)*X[0]*sin(X[0]**2 + X[1]**2) + 0.800*(0.500*X[0]*X[1] + 0.400*cos(X[0] + X[1]))*X[1]*cos(X[0]**2 + X[1]**2) + 0.224*X[0]**2*cos(X[0]**2 + X[1]**2) + 0.224*X[1]**2*cos(X[0]**2 + X[1]**2) + 0.800*(0.500*sin(X[0]**2 + X[1]**2) + 0.750)*(0.500*X[0] - 0.400*sin(X[0] + X[1])) - 0.0588427124000001*sin(X[0]**2 + X[1]**2) - 0.424264068600000
4663+
4664+def forcing_rho1(X):
4665+ return (0.0800*cos(X[0]**2 + X[1]**2) + 0.0400)*X[1]*cos(X[0]**2 + X[1]**2) + 1.60*(0.500*sin(X[0]**2 + X[1]**2) + 0.750)*X[0]*cos(X[0]**2 + X[1]**2) - 0.160*(0.500*sin(X[0]**2 + X[1]**2) + 0.750)*X[1]*sin(X[0]**2 + X[1]**2) + (0.800*sin(X[0]**2 + X[1]**2) + 0.400)*X[0]*cos(X[0]**2 + X[1]**2) + (0.500*sin(X[0]**2 + X[1]**2) + 0.750)*(-0.400*X[0]*sin(X[0]**2 + X[1]**2) + 0.500) + 0.100*(0.500*sin(X[0]**2 + X[1]**2) + 0.750)*X[0]
4666+
4667+def forcing_ie1(X):
4668+ return 1.60*(0.500*sin(X[0]**2 + X[1]**2) + 0.750)*(0.500*X[0]*X[1] + 0.400*cos(X[0] + X[1]))*X[0]*cos(X[0]**2 + X[1]**2) - 0.160*(0.500*sin(X[0]**2 + X[1]**2) + 0.750)*(0.500*X[0]*X[1] + 0.400*cos(X[0] + X[1]))*X[1]*sin(X[0]**2 + X[1]**2) + (0.100*cos(X[0]**2 + X[1]**2) + 0.0500)*(0.400*sin(X[0]**2 + X[1]**2) + 0.600)*(1.25*X[0] - sin(X[0] + X[1])) + (0.400*sin(X[0]**2 + X[1]**2) + 0.600)*(sin(X[0]**2 + X[1]**2) + 0.500)*(1.25*X[1] - sin(X[0] + X[1])) + 0.00160*cos(X[0] + X[1])
4669+
4670+def velocity1(X):
4671+ return [u1(X), v1(X)]
4672+
4673+def forcing_velocity1(X):
4674+ return [forcing_u1(X), forcing_v1(X)]
4675+
4676+def u2(X):
4677+ return 2.50*X[0] + cos(X[0]**2 + X[1]**2)
4678+
4679+def v2(X):
4680+ return 0.500*X[0]*X[1]
4681+
4682+def rho2(X):
4683+ return 3.00
4684+
4685+def ie2(X):
4686+ return sin(X[0]*X[1])
4687+
4688+def vfrac2(X):
4689+ return 0.200
4690+
4691+def forcing_u2(X):
4692+ return -0.600*X[0]*X[1]**2*sin(X[0]**2 + X[1]**2) + 0.200*(0.500*X[0]*X[1] + 0.400*cos(X[0] + X[1]))*X[0]*cos(X[0]**2 + X[1]**2) + 0.560*X[0]**2*cos(X[0]**2 + X[1]**2) + 0.560*X[1]**2*cos(X[0]**2 + X[1]**2) + 0.200*(0.500*sin(X[0]**2 + X[1]**2) + 0.750)*(0.500*X[1] - 0.400*sin(X[0] + X[1])) - (2.00*X[0]*sin(X[0]**2 + X[1]**2) - 2.50)*(1.50*X[0] + 0.600*cos(X[0]**2 + X[1]**2)) + 0.560*sin(X[0]**2 + X[1]**2) - 0.424264068600000
4693+
4694+def forcing_v2(X):
4695+ return 0.200*(0.500*X[0]*X[1] + 0.400*cos(X[0] + X[1]))*X[1]*cos(X[0]**2 + X[1]**2) + 0.150*X[0]**2*X[1] + 0.200*(0.500*sin(X[0]**2 + X[1]**2) + 0.750)*(0.500*X[0] - 0.400*sin(X[0] + X[1])) + 0.500*(1.50*X[0] + 0.600*cos(X[0]**2 + X[1]**2))*X[1] - 0.424264068600000
4696+
4697+def forcing_ie2(X):
4698+ return 0.300*X[0]**2*X[1]*cos(X[0]*X[1]) + (1.50*X[0] + 0.600*cos(X[0]**2 + X[1]**2))*X[1]*cos(X[0]*X[1]) + 0.000200*X[0]**2*sin(X[0]*X[1]) + 0.000200*X[1]**2*sin(X[0]*X[1])
4699+
4700+def velocity2(X):
4701+ return [u2(X), v2(X)]
4702+
4703+def forcing_velocity2(X):
4704+ return [forcing_u2(X), forcing_v2(X)]
4705+
4706
4707=== added directory 'tests/mphase_mms_p2p1_compressible_ie_p1cv/src'
4708=== added file 'tests/mphase_mms_p2p1_compressible_ie_p1cv/src/MMS_A.geo'
4709--- tests/mphase_mms_p2p1_compressible_ie_p1cv/src/MMS_A.geo 1970-01-01 00:00:00 +0000
4710+++ tests/mphase_mms_p2p1_compressible_ie_p1cv/src/MMS_A.geo 2013-02-08 22:48:22 +0000
4711@@ -0,0 +1,15 @@
4712+Point(1) = {-0.1,0.2,0,0.1};
4713+Point(2) = {0.7,0.2,0,0.1};
4714+Point(3) = {0.7,0.8,0,0.1};
4715+Point(4) = {-0.1,0.8,0,0.1};
4716+Line(1) = {4,3};
4717+Line(2) = {3,2};
4718+Line(3) = {2,1};
4719+Line(4) = {1,4};
4720+Line Loop(5) = {1,2,3,4};
4721+Plane Surface(6) = {5};
4722+Physical Line(7) = {3};
4723+Physical Line(8) = {2};
4724+Physical Line(9) = {1};
4725+Physical Line(10) = {4};
4726+Physical Surface(12) = {6};
4727
4728=== added file 'tests/mphase_mms_p2p1_compressible_ie_p1cv/src/MMS_A.msh'
4729Binary files tests/mphase_mms_p2p1_compressible_ie_p1cv/src/MMS_A.msh 1970-01-01 00:00:00 +0000 and tests/mphase_mms_p2p1_compressible_ie_p1cv/src/MMS_A.msh 2013-02-08 22:48:22 +0000 differ
4730=== added file 'tests/mphase_mms_p2p1_compressible_ie_p1cv/src/MMS_B.geo'
4731--- tests/mphase_mms_p2p1_compressible_ie_p1cv/src/MMS_B.geo 1970-01-01 00:00:00 +0000
4732+++ tests/mphase_mms_p2p1_compressible_ie_p1cv/src/MMS_B.geo 2013-02-08 22:48:22 +0000
4733@@ -0,0 +1,15 @@
4734+Point(1) = {-0.1,0.2,0,0.05};
4735+Point(2) = {0.7,0.2,0,0.05};
4736+Point(3) = {0.7,0.8,0,0.05};
4737+Point(4) = {-0.1,0.8,0,0.05};
4738+Line(1) = {4,3};
4739+Line(2) = {3,2};
4740+Line(3) = {2,1};
4741+Line(4) = {1,4};
4742+Line Loop(5) = {1,2,3,4};
4743+Plane Surface(6) = {5};
4744+Physical Line(7) = {3};
4745+Physical Line(8) = {2};
4746+Physical Line(9) = {1};
4747+Physical Line(10) = {4};
4748+Physical Surface(12) = {6};
4749
4750=== added file 'tests/mphase_mms_p2p1_compressible_ie_p1cv/src/MMS_B.msh'
4751Binary files tests/mphase_mms_p2p1_compressible_ie_p1cv/src/MMS_B.msh 1970-01-01 00:00:00 +0000 and tests/mphase_mms_p2p1_compressible_ie_p1cv/src/MMS_B.msh 2013-02-08 22:48:22 +0000 differ
4752=== added file 'tests/mphase_mms_p2p1_compressible_ie_p1cv/src/MMS_C.geo'
4753--- tests/mphase_mms_p2p1_compressible_ie_p1cv/src/MMS_C.geo 1970-01-01 00:00:00 +0000
4754+++ tests/mphase_mms_p2p1_compressible_ie_p1cv/src/MMS_C.geo 2013-02-08 22:48:22 +0000
4755@@ -0,0 +1,15 @@
4756+Point(1) = {-0.1,0.2,0,0.025};
4757+Point(2) = {0.7,0.2,0,0.025};
4758+Point(3) = {0.7,0.8,0,0.025};
4759+Point(4) = {-0.1,0.8,0,0.025};
4760+Line(1) = {4,3};
4761+Line(2) = {3,2};
4762+Line(3) = {2,1};
4763+Line(4) = {1,4};
4764+Line Loop(5) = {1,2,3,4};
4765+Plane Surface(6) = {5};
4766+Physical Line(7) = {3};
4767+Physical Line(8) = {2};
4768+Physical Line(9) = {1};
4769+Physical Line(10) = {4};
4770+Physical Surface(12) = {6};
4771
4772=== added file 'tests/mphase_mms_p2p1_compressible_ie_p1cv/src/MMS_C.msh'
4773Binary files tests/mphase_mms_p2p1_compressible_ie_p1cv/src/MMS_C.msh 1970-01-01 00:00:00 +0000 and tests/mphase_mms_p2p1_compressible_ie_p1cv/src/MMS_C.msh 2013-02-08 22:48:22 +0000 differ
4774=== added file 'tests/mphase_mms_p2p1_compressible_ie_p1cv/src/MMS_X.geo'
4775--- tests/mphase_mms_p2p1_compressible_ie_p1cv/src/MMS_X.geo 1970-01-01 00:00:00 +0000
4776+++ tests/mphase_mms_p2p1_compressible_ie_p1cv/src/MMS_X.geo 2013-02-08 22:48:22 +0000
4777@@ -0,0 +1,18 @@
4778+pi = 3.141592653589793;
4779+n = XX;
4780+
4781+Point(1) = {0.0, 0.0, 0.0, 1};
4782+
4783+Extrude {pi, 0.0, 0.0} {
4784+ Point{1}; Layers{n};
4785+}
4786+
4787+Extrude {0.0, pi, 0.0} {
4788+ Line{1}; Layers{n};
4789+}
4790+
4791+Physical Line(7) = {1};
4792+Physical Line(8) = {2};
4793+Physical Line(9) = {3};
4794+Physical Line(10) = {4};
4795+Physical Surface(6) = {5};
4796
4797=== added directory 'tests/mphase_mms_p2p1_compressible_ie_p1cv_heat_transfer'
4798=== added file 'tests/mphase_mms_p2p1_compressible_ie_p1cv_heat_transfer/MMS_X.flml'
4799--- tests/mphase_mms_p2p1_compressible_ie_p1cv_heat_transfer/MMS_X.flml 1970-01-01 00:00:00 +0000
4800+++ tests/mphase_mms_p2p1_compressible_ie_p1cv_heat_transfer/MMS_X.flml 2013-02-08 22:48:22 +0000
4801@@ -0,0 +1,1216 @@
4802+<?xml version='1.0' encoding='utf-8'?>
4803+<fluidity_options>
4804+ <simulation_name>
4805+ <string_value lines="1">MMS_X</string_value>
4806+ </simulation_name>
4807+ <problem_type>
4808+ <string_value lines="1">fluids</string_value>
4809+ </problem_type>
4810+ <geometry>
4811+ <dimension>
4812+ <integer_value rank="0">2</integer_value>
4813+ </dimension>
4814+ <mesh name="CoordinateMesh">
4815+ <from_file file_name="src/MMS_X">
4816+ <format name="gmsh"/>
4817+ <stat>
4818+ <include_in_stat/>
4819+ </stat>
4820+ </from_file>
4821+ </mesh>
4822+ <mesh name="VelocityMesh">
4823+ <from_mesh>
4824+ <mesh name="CoordinateMesh"/>
4825+ <mesh_shape>
4826+ <polynomial_degree>
4827+ <integer_value rank="0">2</integer_value>
4828+ </polynomial_degree>
4829+ </mesh_shape>
4830+ <stat>
4831+ <exclude_from_stat/>
4832+ </stat>
4833+ </from_mesh>
4834+ </mesh>
4835+ <mesh name="PressureMesh">
4836+ <from_mesh>
4837+ <mesh name="CoordinateMesh"/>
4838+ <mesh_shape>
4839+ <polynomial_degree>
4840+ <integer_value rank="0">1</integer_value>
4841+ </polynomial_degree>
4842+ </mesh_shape>
4843+ <stat>
4844+ <exclude_from_stat/>
4845+ </stat>
4846+ </from_mesh>
4847+ </mesh>
4848+ <mesh name="ErrorMesh">
4849+ <from_mesh>
4850+ <mesh name="CoordinateMesh"/>
4851+ <mesh_shape>
4852+ <polynomial_degree>
4853+ <integer_value rank="0">4</integer_value>
4854+ </polynomial_degree>
4855+ </mesh_shape>
4856+ <mesh_continuity>
4857+ <string_value>continuous</string_value>
4858+ </mesh_continuity>
4859+ <stat>
4860+ <exclude_from_stat/>
4861+ </stat>
4862+ </from_mesh>
4863+ </mesh>
4864+ <mesh name="DensityMesh">
4865+ <from_mesh>
4866+ <mesh name="CoordinateMesh"/>
4867+ <mesh_shape>
4868+ <polynomial_degree>
4869+ <integer_value rank="0">2</integer_value>
4870+ </polynomial_degree>
4871+ </mesh_shape>
4872+ <stat>
4873+ <exclude_from_stat/>
4874+ </stat>
4875+ </from_mesh>
4876+ </mesh>
4877+ <quadrature>
4878+ <degree>
4879+ <integer_value rank="0">8</integer_value>
4880+ </degree>
4881+ </quadrature>
4882+ </geometry>
4883+ <io>
4884+ <dump_format>
4885+ <string_value>vtk</string_value>
4886+ </dump_format>
4887+ <dump_period>
4888+ <constant>
4889+ <real_value rank="0">1000.0</real_value>
4890+ </constant>
4891+ </dump_period>
4892+ <output_mesh name="VelocityMesh"/>
4893+ <stat>
4894+ <output_at_start/>
4895+ </stat>
4896+ </io>
4897+ <timestepping>
4898+ <current_time>
4899+ <real_value rank="0">0.0</real_value>
4900+ </current_time>
4901+ <timestep>
4902+ <real_value rank="0">999.9</real_value>
4903+ <comment>gives a max cfl number of approximately 0.1</comment>
4904+ </timestep>
4905+ <finish_time>
4906+ <real_value rank="0">1000.0</real_value>
4907+ <comment>10.0</comment>
4908+ </finish_time>
4909+ <nonlinear_iterations>
4910+ <integer_value rank="0">2</integer_value>
4911+ <tolerance>
4912+ <real_value rank="0">1.0e-9</real_value>
4913+ <infinity_norm/>
4914+ </tolerance>
4915+ </nonlinear_iterations>
4916+ <steady_state>
4917+ <tolerance>
4918+ <real_value rank="0">1.E-7</real_value>
4919+ <infinity_norm/>
4920+ </tolerance>
4921+ </steady_state>
4922+ </timestepping>
4923+ <physical_parameters>
4924+ <gravity>
4925+ <magnitude>
4926+ <real_value rank="0">1.0</real_value>
4927+ </magnitude>
4928+ <vector_field name="GravityDirection" rank="1">
4929+ <prescribed>
4930+ <mesh name="CoordinateMesh"/>
4931+ <value name="WholeMesh">
4932+ <constant>
4933+ <real_value shape="2" dim1="dim" rank="1">0.707106781 0.707106781</real_value>
4934+ </constant>
4935+ </value>
4936+ <output/>
4937+ <stat>
4938+ <include_in_stat/>
4939+ </stat>
4940+ <detectors>
4941+ <exclude_from_detectors/>
4942+ </detectors>
4943+ </prescribed>
4944+ </vector_field>
4945+ </gravity>
4946+ </physical_parameters>
4947+ <material_phase name="Fluid">
4948+ <equation_of_state>
4949+ <compressible>
4950+ <stiffened_gas>
4951+ <ratio_specific_heats>
4952+ <real_value rank="0">1.4</real_value>
4953+ </ratio_specific_heats>
4954+ </stiffened_gas>
4955+ </compressible>
4956+ </equation_of_state>
4957+ <scalar_field name="Pressure" rank="0">
4958+ <prognostic>
4959+ <mesh name="PressureMesh"/>
4960+ <spatial_discretisation>
4961+ <continuous_galerkin>
4962+ <remove_stabilisation_term/>
4963+ </continuous_galerkin>
4964+ </spatial_discretisation>
4965+ <scheme>
4966+ <poisson_pressure_solution>
4967+ <string_value lines="1">never</string_value>
4968+ </poisson_pressure_solution>
4969+ <use_compressible_projection_method/>
4970+ </scheme>
4971+ <solver>
4972+ <iterative_method name="gmres">
4973+ <restart>
4974+ <integer_value rank="0">30</integer_value>
4975+ </restart>
4976+ </iterative_method>
4977+ <preconditioner name="sor"/>
4978+ <relative_error>
4979+ <real_value rank="0">1.0e-7</real_value>
4980+ </relative_error>
4981+ <max_iterations>
4982+ <integer_value rank="0">10000</integer_value>
4983+ </max_iterations>
4984+ <never_ignore_solver_failures/>
4985+ <diagnostics>
4986+ <monitors/>
4987+ </diagnostics>
4988+ </solver>
4989+ <output>
4990+ <include_previous_time_step/>
4991+ </output>
4992+ <stat/>
4993+ <convergence>
4994+ <include_in_convergence/>
4995+ </convergence>
4996+ <detectors>
4997+ <exclude_from_detectors/>
4998+ </detectors>
4999+ <steady_state>
5000+ <exclude_from_steady_state/>
The diff has been truncated for viewing.