Merge lp:~amcg-stokes/fluidity/remove_compressible_projection_option into lp:fluidity

Proposed by Cian Wilson
Status: Merged
Merged at revision: 4277
Proposed branch: lp:~amcg-stokes/fluidity/remove_compressible_projection_option
Merge into: lp:fluidity
Diff against target: 1537 lines (+323/-572)
30 files modified
assemble/Compressible_Projection.F90 (+53/-81)
assemble/Divergence_Matrix_CV.F90 (+18/-76)
assemble/Momentum_Equation.F90 (+0/-7)
preprocessor/Populate_State.F90 (+3/-3)
schemas/fluidity_options.rng (+3/-1)
schemas/prognostic_field_options.rnc (+65/-101)
schemas/prognostic_field_options.rng (+56/-99)
schemas/test_advection_diffusion_options.rnc (+55/-91)
schemas/test_advection_diffusion_options.rng (+49/-92)
tests/1mat-shocktube-gmsh/1material_shocktube.flml (+1/-1)
tests/1mat-shocktube/1material_shocktube.flml (+1/-1)
tests/foam_2d_p1dgp2_weak_strong/drainage_a.flml (+1/-1)
tests/inlet_velocity_bc_compressible/inlet_velocity_bc_compressible_1d.flml (+1/-1)
tests/inlet_velocity_bc_compressible_without_gravity/inlet_velocity_bc_compressible_without_gravity_1d.flml (+1/-1)
tests/inlet_velocity_bc_compressible_without_gravity/inlet_velocity_bc_compressible_without_gravity_pseudo1d.flml (+1/-1)
tests/inlet_velocity_bc_incompressible/inlet_velocity_bc_incompressible.flml (+1/-1)
tests/mmat-impact/2material_impact.flml (+1/-1)
tests/mmat-shocktube/1material_shocktube.flml (+1/-1)
tests/mphase_dusty_gas_shock_tube/mphase_dusty_gas_shock_tube.flml (+1/-1)
tests/mphase_dusty_gas_shock_tube/single_phase_frozen_flow_test.flml (+1/-1)
tests/mphase_inlet_velocity_bc_compressible/mphase_inlet_velocity_bc_compressible.flml (+1/-1)
tests/mphase_rogue_shock_tube_dense_bed_glass/mphase_rogue_shock_tube_dense_bed_glass.flml (+1/-1)
tests/mphase_rogue_shock_tube_dense_bed_nylon/mphase_rogue_shock_tube_dense_bed_nylon.flml (+1/-1)
tests/mphase_strong_pressure_bc_compressible/mphase_strong_pressure_bc_compressible_p0p1.flml (+1/-1)
tests/mphase_strong_pressure_bc_compressible/mphase_strong_pressure_bc_compressible_p2p1.flml (+1/-1)
tests/mphase_subtract_out_reference_profile/mphase_subtract_out_reference_profile_1d.flml (+1/-1)
tests/shocktube_1d/shocktube.flml (+1/-1)
tests/strong_pressure_bc_compressible/strong_pressure_bc_compressible.flml (+1/-1)
tests/subtract_out_reference_profile/subtract_out_reference_profile_1d.flml (+1/-1)
tests/subtract_out_reference_profile/subtract_out_reference_profile_pseudo1d.flml (+1/-1)
To merge this branch: bzr merge lp:~amcg-stokes/fluidity/remove_compressible_projection_option
Reviewer Review Type Date Requested Status
Rhodri Davies Approve
Stephan Kramer Approve
Review via email: mp+192971@code.launchpad.net

Description of the change

This merge would remove the use_compressible_projection_method option from underneath scalar_field::Pressure/prognostic/scheme. This option was already half deprecated and replaced with checking if the eos was compressible or not so this just completes that task. The only functionality lost is a normalization option that was not used.

Green buildbot queue available here: http://buildbot-ocean.ese.ic.ac.uk:8080/waterfall?show=remove_compressible_projection_option

Updates to long tests to follow.

To post a comment you must log in.
Revision history for this message
Stephan Kramer (s-kramer) wrote :

Looks eminently sensible to me. Maybe should check with Tim what the status of the release is - don't think this necessarily needs to go in before?

review: Approve
Revision history for this message
Rhodri Davies (rhodri-davies) wrote :

Looks fantastic to me.

review: Approve

Preview Diff

[H/L] Next/Prev Comment, [J/K] Next/Prev File, [N/P] Next/Prev Hunk
1=== modified file 'assemble/Compressible_Projection.F90'
2--- assemble/Compressible_Projection.F90 2013-03-03 01:36:16 +0000
3+++ assemble/Compressible_Projection.F90 2013-10-28 23:25:09 +0000
4@@ -104,15 +104,11 @@
5 logical, intent(in) :: cmcget
6
7 ! local:
8- integer :: norm_stat
9- character(len=FIELD_NAME_LEN) :: normalisation_field
10-
11 type(scalar_field) :: eospressure, drhodp
12- type(scalar_field), pointer :: normalisation, &
13- density, olddensity
14+ type(scalar_field), pointer :: density, olddensity
15 type(scalar_field), pointer :: pressure
16 type(scalar_field), pointer :: p_cvmass
17- type(scalar_field) :: lhsfield, invnorm, absrhs
18+ type(scalar_field) :: lhsfield, absrhs
19
20 type(scalar_field), pointer :: source, absorption
21 integer :: stat
22@@ -135,24 +131,6 @@
23
24 ewrite_minmax(p_cvmass)
25
26- call get_option(trim(pressure%option_path)//"/prognostic/scheme/use_compressible_projection_method/normalisation/name", &
27- normalisation_field, stat=norm_stat)
28- if(norm_stat==0) then
29- normalisation=>extract_scalar_field(state, trim(normalisation_field))
30- else
31- allocate(normalisation)
32- call allocate(normalisation, pressure%mesh, "DummyNormalisation", field_type=FIELD_TYPE_CONSTANT)
33- call set(normalisation, 1.0)
34- end if
35-
36- call allocate(invnorm, normalisation%mesh, "InverseNormalisation", field_type=normalisation%field_type)
37- call invert(normalisation, invnorm)
38-
39- if(norm_stat/=0) then
40- call deallocate(normalisation)
41- deallocate(normalisation)
42- end if
43-
44 call allocate(lhsfield, pressure%mesh, "LHSField")
45
46 call allocate(eospressure, pressure%mesh, 'EOSPressure')
47@@ -172,10 +150,9 @@
48
49 call set(lhsfield, p_cvmass)
50 call scale(lhsfield, drhodp)
51- call scale(lhsfield, invnorm)
52 call addto_diag(cmc, lhsfield, scale=1./(dt*dt*theta_divergence*theta_pg))
53
54-! rhs = invnorm*p_cvmass* &
55+! rhs = p_cvmass* &
56 ! ( (1./dt)*(olddensity - density + drhodp*(eospressure - (pressure + atmospheric_pressure)))
57 ! +(absorption)*(drhodp*theta_pg*(eospressure - (pressure + atmospheric_pressure)) - theta_pg*density - (1-theta_pg)*olddensity)
58 ! +source)
59@@ -216,13 +193,11 @@
60 end if
61
62 call scale(rhs, p_cvmass)
63- call scale(rhs, invnorm)
64
65 call deallocate(eospressure)
66 call deallocate(drhodp)
67
68 call deallocate(lhsfield)
69- call deallocate(invnorm)
70
71 end if
72
73@@ -241,14 +216,12 @@
74 logical, intent(in) :: cmcget
75
76 ! local:
77- integer :: i, stat, norm_stat
78+ integer :: i, stat
79 character(len=OPTION_PATH_LEN) :: pressure_option_path
80- character(len=FIELD_NAME_LEN) :: normalisation_field
81
82- type(scalar_field) :: materialpressure, materialdrhodp, normdensity, &
83- normolddensity, normmatdrhodpp, normdrhodp
84- type(scalar_field), pointer :: normalisation, &
85- volumefraction, oldvolumefraction, materialdensity, oldmaterialdensity
86+ type(scalar_field) :: materialpressure, materialdrhodp, density, &
87+ olddensity, matdrhodpp, drhodp
88+ type(scalar_field), pointer :: volumefraction, oldvolumefraction, materialdensity, oldmaterialdensity
89 type(scalar_field), pointer :: dummy_ones
90
91 type(scalar_field), pointer :: pressure
92@@ -256,6 +229,8 @@
93 type(scalar_field) :: cv_mass, tempfield
94
95 real :: atmospheric_pressure
96+ ! Do we want to use the compressible projection method?
97+ logical :: have_compressible_eos
98
99 ewrite(1,*) 'Entering assemble_mmat_compressible_projection_cv'
100
101@@ -266,9 +241,17 @@
102 end if
103 pressure_option_path=trim(pressure%option_path)
104
105+ have_compressible_eos = .false.
106+ state_loop: do i = 1, size(state)
107+ have_compressible_eos = have_option("/material_phase::"//trim(state(i)%name)//"/equation_of_state/compressible")
108+ if(have_compressible_eos) then
109+ exit state_loop
110+ end if
111+ end do state_loop
112+
113 call zero(rhs)
114
115- if(have_option(trim(pressure_option_path)//"/prognostic/scheme/use_compressible_projection_method")) THEN
116+ if(have_compressible_eos) THEN
117
118 ! only do all this if we need to make cmc (otherwise we'd be adding repeatedly)
119 if(cmcget) then
120@@ -285,21 +268,18 @@
121 call get_option(trim(pressure_option_path)//'/prognostic/atmospheric_pressure', &
122 atmospheric_pressure, default=0.0)
123
124- call get_option(trim(pressure_option_path)//"/prognostic/scheme/use_compressible_projection_method/normalisation/name", &
125- normalisation_field, stat=norm_stat)
126-
127 call allocate(materialpressure, pressure%mesh, 'MaterialEOSPressure')
128 call allocate(materialdrhodp, pressure%mesh, 'DerivativeMaterialdensityWRTBulkPressure')
129
130- call allocate(normdensity, pressure%mesh, 'NormalisedMaterialDensity')
131- call allocate(normolddensity, pressure%mesh, 'NormalisedOldMaterialDensity')
132- call allocate(normmatdrhodpp, pressure%mesh, 'NormalisedMaterialPressure')
133- call allocate(normdrhodp, pressure%mesh, 'NormalisedDrhodp')
134+ call allocate(density, pressure%mesh, 'MaterialDensity')
135+ call allocate(olddensity, pressure%mesh, 'OldMaterialDensity')
136+ call allocate(matdrhodpp, pressure%mesh, 'MaterialPressure')
137+ call allocate(drhodp, pressure%mesh, 'Drhodp')
138
139- normdensity%val = 0.0
140- normolddensity%val = 0.0
141- normmatdrhodpp%val = 0.0
142- normdrhodp%val=0.0
143+ density%val = 0.0
144+ olddensity%val = 0.0
145+ matdrhodpp%val = 0.0
146+ drhodp%val=0.0
147
148 do i = 1,size(state)
149
150@@ -314,48 +294,38 @@
151 materialdensity=>extract_scalar_field(state(i),'MaterialDensity')
152 oldmaterialdensity=>extract_scalar_field(state(i),'OldMaterialDensity')
153
154- if(norm_stat==0) then
155- normalisation=>extract_scalar_field(state(i), trim(normalisation_field))
156- else
157- normalisation=>dummy_ones
158- end if
159-
160- normdensity%val = normdensity%val &
161- + materialdensity%val*volumefraction%val/ &
162- normalisation%val
163- normolddensity%val = normolddensity%val &
164- + oldmaterialdensity%val*oldvolumefraction%val/ &
165- normalisation%val
166- normmatdrhodpp%val = normmatdrhodpp%val &
167- + materialpressure%val*materialdrhodp%val*volumefraction%val/ &
168- normalisation%val
169- normdrhodp%val = normdrhodp%val &
170- + materialdrhodp%val*volumefraction%val/ &
171- normalisation%val
172+ density%val = density%val &
173+ + materialdensity%val*volumefraction%val
174+ olddensity%val = olddensity%val &
175+ + oldmaterialdensity%val*oldvolumefraction%val
176+ matdrhodpp%val = matdrhodpp%val &
177+ + materialpressure%val*materialdrhodp%val*volumefraction%val
178+ drhodp%val = drhodp%val &
179+ + materialdrhodp%val*volumefraction%val
180 endif
181
182 end do
183
184 call zero(tempfield)
185- tempfield%val = (1./(dt*dt))*cv_mass%val*normdrhodp%val
186+ tempfield%val = (1./(dt*dt))*cv_mass%val*drhodp%val
187
188 call addto_diag(cmc, tempfield)
189
190 rhs%val = (1./dt)*cv_mass%val* &
191 ( &
192- normolddensity%val &
193- - normdensity%val &
194+ olddensity%val &
195+ - density%val &
196 ) &
197 +(1./dt)*cv_mass%val* &
198 ( &
199- normmatdrhodpp%val &
200- - normdrhodp%val*(pressure%val+atmospheric_pressure) &
201+ matdrhodpp%val &
202+ - drhodp%val*(pressure%val+atmospheric_pressure) &
203 )
204
205- call deallocate(normdensity)
206- call deallocate(normolddensity)
207- call deallocate(normmatdrhodpp)
208- call deallocate(normdrhodp)
209+ call deallocate(density)
210+ call deallocate(olddensity)
211+ call deallocate(matdrhodpp)
212+ call deallocate(drhodp)
213
214 call deallocate(materialpressure)
215 call deallocate(materialdrhodp)
216@@ -667,15 +637,17 @@
217
218 subroutine compressible_projection_check_options
219
220- character(len=OPTION_PATH_LEN):: prognostic_pressure_path
221- integer:: i
222+ character(len=OPTION_PATH_LEN):: pressure_option_path
223+ integer:: iphase
224+ logical:: have_compressible_eos
225
226- do i=0, option_count("/material_phase")-1
227- prognostic_pressure_path="/material_phase["//int2str(i)//"]/scalar_field::Pressure/prognostic"
228- if (have_option(trim(prognostic_pressure_path)//"/spatial_discretisation/discontinuous_galerkin") &
229- .and. have_option(trim(prognostic_pressure_path)//"/scheme/use_compressible_projection_method")) then
230- FLExit("With a DG pressure you cannot have use_compressible_projection_method")
231- end if
232+ do iphase=0, option_count("/material_phase")-1
233+ have_compressible_eos = have_option("/material_phase["//int2str(iphase)//"]/equation_of_state/compressible")
234+ pressure_option_path = "/material_phase["//int2str(iphase)//"]/scalar_field::Pressure"
235+ if(have_compressible_eos.and. &
236+ have_option(trim(pressure_option_path)//"/prognostic/spatial_discretisation/discontinuous_galerkin")) then
237+ FLExit("With a DG pressure you cannot have use a compressible eos")
238+ end if
239 end do
240
241 end subroutine compressible_projection_check_options
242
243=== modified file 'assemble/Divergence_Matrix_CV.F90'
244--- assemble/Divergence_Matrix_CV.F90 2013-03-06 13:20:27 +0000
245+++ assemble/Divergence_Matrix_CV.F90 2013-10-28 23:25:09 +0000
246@@ -499,10 +499,8 @@
247 real :: dens_theta_val
248 real :: dens_face_val
249 real :: olddens_face_val
250- real, dimension(:), allocatable :: dens_ele, olddens_ele, &
251- norm_ele
252- real, dimension(:), allocatable :: dens_ele_bdy, olddens_ele_bdy, &
253- norm_ele_bdy
254+ real, dimension(:), allocatable :: dens_ele, olddens_ele
255+ real, dimension(:), allocatable :: dens_ele_bdy, olddens_ele_bdy
256 real, dimension(:), allocatable :: ghost_dens_ele_bdy, ghost_olddens_ele_bdy
257
258 logical, dimension(:), allocatable :: notvisited
259@@ -540,10 +538,6 @@
260
261 type(cv_options_type) :: dens_options
262
263- type(scalar_field), pointer :: normalisation
264- character(len=FIELD_NAME_LEN) :: normalisation_field
265- integer :: norm_stat
266-
267 integer, dimension(:,:), allocatable :: velocity_bc_type
268 real, dimension(:,:), allocatable :: velocity_bc_val
269 type(vector_field) :: velocity_bc
270@@ -610,18 +604,6 @@
271
272 end if
273
274- call get_option(trim(p%option_path)//"/prognostic/scheme/use_compressible_projection_method/normalisation/name", &
275- normalisation_field, stat=norm_stat)
276-
277- ! get the normalisation field (if we need one)
278- if(norm_stat==0) then
279- normalisation=>extract_scalar_field(state, trim(normalisation_field))
280- else
281- allocate(normalisation)
282- call allocate(normalisation, p%mesh, name="DummyNormalisation", field_type=FIELD_TYPE_CONSTANT)
283- call set(normalisation, 1.0)
284- end if
285-
286 ! find courant number (if needed)
287 option_path_array(1) = trim(dens%option_path) ! temporary hack for compiler failure
288 call cv_disc_get_cfl_no(option_path_array, &
289@@ -639,8 +621,7 @@
290 normgi(x%dim))
291 allocate(cfl_ele(ele_loc(p,1)), &
292 dens_ele(ele_loc(p,1)), &
293- olddens_ele(ele_loc(p,1)), &
294- norm_ele(ele_loc(normalisation,1)))
295+ olddens_ele(ele_loc(p,1)))
296 allocate(notvisited(x_cvshape%ngi))
297 allocate(ctp_mat_local(x%dim, p%mesh%shape%loc, u_cvshape%loc))
298
299@@ -659,8 +640,6 @@
300 dens_ele = ele_val(dens, ele)
301 olddens_ele = ele_val(olddens, ele)
302
303- norm_ele = ele_val(normalisation, ele)
304-
305 notvisited=.true.
306
307 ctp_mat_local = 0.0
308@@ -710,9 +689,9 @@
309 inner_dimension_loop: do dim = 1, size(normgi)
310
311 ctp_mat_local(dim, iloc, jloc) = ctp_mat_local(dim, iloc, jloc) &
312- + face_value*normgi(dim)/norm_ele(iloc)
313+ + face_value*normgi(dim)
314 ctp_mat_local(dim, oloc, jloc) = ctp_mat_local(dim, oloc, jloc) &
315- + face_value*(-normgi(dim))/norm_ele(oloc) ! notvisited
316+ + face_value*(-normgi(dim)) ! notvisited
317
318 end do inner_dimension_loop
319
320@@ -743,8 +722,7 @@
321 dens_ele_bdy(face_loc(dens,1)), &
322 olddens_ele_bdy(face_loc(dens,1)), &
323 ghost_dens_ele_bdy(face_loc(dens,1)), &
324- ghost_olddens_ele_bdy(face_loc(dens,1)), &
325- norm_ele_bdy(face_loc(normalisation,1)))
326+ ghost_olddens_ele_bdy(face_loc(dens,1)))
327 allocate(dens_bc_type(surface_element_count(dens)), &
328 u_nodes_bdy(face_loc(u,1)), &
329 p_nodes_bdy(face_loc(p,1)), &
330@@ -798,8 +776,6 @@
331 dens_ele_bdy=face_val(dens, sele)
332 olddens_ele_bdy=face_val(olddens, sele)
333
334- norm_ele_bdy=face_val(normalisation, sele)
335-
336 ctp_mat_local_bdy = 0.0
337 ct_rhs_local = 0.0
338
339@@ -821,8 +797,7 @@
340 income=1.0
341 end if
342
343- face_value = (income*ghost_dens_ele_bdy(iloc) + (1.-income)*dens_ele_bdy(iloc))/&
344- norm_ele_bdy(iloc)
345+ face_value = (income*ghost_dens_ele_bdy(iloc) + (1.-income)*dens_ele_bdy(iloc))
346
347 surface_nodal_loop_j: do jloc = 1, u_cvbdyshape%loc
348
349@@ -876,7 +851,7 @@
350 call deallocate(dens_cvbdyshape)
351 deallocate(x_ele_bdy, detwei_bdy, normal_bdy, u_bdy_f)
352 deallocate(u_nodes_bdy, p_nodes_bdy)
353- deallocate(dens_ele_bdy, olddens_ele_bdy, norm_ele_bdy)
354+ deallocate(dens_ele_bdy, olddens_ele_bdy)
355 deallocate(ghost_dens_ele_bdy, ghost_olddens_ele_bdy)
356 call deallocate(dens_bc)
357 deallocate(dens_bc_type)
358@@ -888,16 +863,12 @@
359 call deallocate(cvfaces)
360 call deallocate(relu)
361 deallocate(x_ele, x_f, detwei, normal, normgi, u_f)
362- deallocate(cfl_ele, dens_ele, olddens_ele, norm_ele)
363+ deallocate(cfl_ele, dens_ele, olddens_ele)
364 deallocate(notvisited)
365
366 call deallocate(dens_upwind)
367 call deallocate(olddens_upwind)
368 call deallocate(cfl_no)
369- if(norm_stat/=0) then
370- call deallocate(normalisation)
371- deallocate(normalisation)
372- end if
373 call deallocate(x_p)
374
375 end subroutine assemble_1mat_compressible_divergence_matrix_cv
376@@ -927,11 +898,9 @@
377 real :: matvfrac_face_val, matdens_face_val
378 real :: oldmatvfrac_face_val, oldmatdens_face_val
379 real, dimension(:), allocatable :: matdens_ele, oldmatdens_ele, &
380- matvfrac_ele, oldmatvfrac_ele, &
381- norm_ele
382+ matvfrac_ele, oldmatvfrac_ele
383 real, dimension(:), allocatable :: matdens_ele_bdy, oldmatdens_ele_bdy, &
384- matvfrac_ele_bdy, oldmatvfrac_ele_bdy, &
385- norm_ele_bdy
386+ matvfrac_ele_bdy, oldmatvfrac_ele_bdy
387 real, dimension(:), allocatable :: ghost_matdens_ele_bdy, ghost_oldmatdens_ele_bdy, &
388 ghost_matvfrac_ele_bdy, ghost_oldmatvfrac_ele_bdy
389
390@@ -979,10 +948,6 @@
391 type(cv_options_type) :: matvfrac_options
392 type(cv_options_type) :: matdens_options
393
394- type(scalar_field), pointer :: normalisation, dummyones
395- character(len=FIELD_NAME_LEN) :: normalisation_field
396- integer :: norm_stat
397-
398 integer, dimension(:,:), allocatable :: velocity_bc_type
399 type(vector_field) :: velocity_bc
400
401@@ -1034,8 +999,7 @@
402 matvfrac_ele(ele_loc(p,1)), &
403 oldmatvfrac_ele(ele_loc(p,1)), &
404 matdens_ele(ele_loc(p,1)), &
405- oldmatdens_ele(ele_loc(p,1)), &
406- norm_ele(ele_loc(x,1)))
407+ oldmatdens_ele(ele_loc(p,1)))
408 allocate(visited(x_cvshape%ngi))
409 allocate(ctp_mat_local(x%dim, p%mesh%shape%loc, u_cvshape%loc))
410
411@@ -1050,13 +1014,6 @@
412 call allocate(dummyvfrac, p%mesh, name="DummyVFrac", field_type=FIELD_TYPE_CONSTANT)
413 call set(dummyvfrac, 1.0)
414
415- allocate(dummyones)
416- call allocate(dummyones, p%mesh, name="DummyOnes", field_type=FIELD_TYPE_CONSTANT)
417- call set(dummyones, 1.0)
418-
419- call get_option(trim(p%option_path)//"/prognostic/scheme/use_compressible_projection_method/normalisation/name", &
420- normalisation_field, stat=norm_stat)
421-
422 allocate(dummyvfrac_bc_type(surface_element_count(dummyvfrac)))
423 bc_mesh=>get_dg_surface_mesh(p%mesh)
424 call allocate(summatvfrac_bc, bc_mesh, name="SumVolumeFractionsBCs")
425@@ -1178,13 +1135,6 @@
426 matvfrac_options = get_cv_options(vfrac_option_path, matvfrac%mesh%shape%numbering%family, mesh_dim(matvfrac))
427 end if
428
429- ! get the normalisation field (if we need one)
430- if(norm_stat==0) then
431- normalisation=>extract_scalar_field(state(i), trim(normalisation_field))
432- else
433- normalisation=>dummyones
434- end if
435-
436 do ele=1, element_count(p)
437 x_ele=ele_val(x, ele)
438 x_f=ele_val_at_quad(x, ele, x_cvshape)
439@@ -1202,8 +1152,6 @@
440 matdens_ele = ele_val(matdens, ele)
441 oldmatdens_ele = ele_val(oldmatdens, ele)
442
443- norm_ele = ele_val(normalisation, ele)
444-
445 visited=0
446
447 ctp_mat_local = 0.0
448@@ -1287,9 +1235,9 @@
449 do dim = 1, size(normgi)
450
451 ctp_mat_local(dim, iloc, jloc) = ctp_mat_local(dim, iloc, jloc) &
452- + face_value*normgi(dim)/norm_ele(iloc)
453+ + face_value*normgi(dim)
454 ctp_mat_local(dim, oloc, jloc) = ctp_mat_local(dim, oloc, jloc) &
455- + face_value*(-normgi(dim))/norm_ele(oloc) ! notvisited
456+ + face_value*(-normgi(dim)) ! notvisited
457
458 end do
459
460@@ -1324,8 +1272,7 @@
461 ghost_matdens_ele_bdy(face_loc(p,1)), &
462 ghost_oldmatdens_ele_bdy(face_loc(p,1)), &
463 ghost_matvfrac_ele_bdy(face_loc(p,1)), &
464- ghost_oldmatvfrac_ele_bdy(face_loc(p,1)), &
465- norm_ele_bdy(face_loc(x,1)))
466+ ghost_oldmatvfrac_ele_bdy(face_loc(p,1)))
467 allocate(matvfrac_bc_type(surface_element_count(matvfrac)), &
468 matdens_bc_type(surface_element_count(matdens)), &
469 nodes_bdy(face_loc(u,1)), &
470@@ -1387,8 +1334,6 @@
471 matdens_ele_bdy=face_val(matdens, sele)
472 oldmatdens_ele_bdy=face_val(oldmatdens, sele)
473
474- norm_ele_bdy=face_val(normalisation, sele)
475-
476 ctp_mat_local_bdy = 0.0
477
478 do iloc = 1, p%mesh%faces%shape%loc
479@@ -1410,8 +1355,7 @@
480 end if
481
482 face_value = (income*ghost_matvfrac_ele_bdy(iloc) + (1.-income)*matvfrac_ele_bdy(iloc))* &
483- (income*ghost_matdens_ele_bdy(iloc) + (1.-income)*matdens_ele_bdy(iloc))/&
484- norm_ele_bdy(iloc)
485+ (income*ghost_matdens_ele_bdy(iloc) + (1.-income)*matdens_ele_bdy(iloc))
486
487 do jloc = 1, u_cvbdyshape%loc
488
489@@ -1448,7 +1392,7 @@
490 call deallocate(p_cvbdyshape)
491 deallocate(x_ele_bdy, detwei_bdy, normal_bdy, u_bdy_f)
492 deallocate(nodes_bdy)
493- deallocate(matdens_ele_bdy, oldmatdens_ele_bdy, matvfrac_ele_bdy, oldmatvfrac_ele_bdy, norm_ele_bdy)
494+ deallocate(matdens_ele_bdy, oldmatdens_ele_bdy, matvfrac_ele_bdy, oldmatvfrac_ele_bdy)
495 deallocate(ghost_matdens_ele_bdy, ghost_oldmatdens_ele_bdy, &
496 ghost_matvfrac_ele_bdy, ghost_oldmatvfrac_ele_bdy)
497 call deallocate(matvfrac_bc)
498@@ -1466,7 +1410,7 @@
499 call deallocate(cvfaces)
500 call deallocate(relu)
501 deallocate(x_ele, x_f, detwei, normal, normgi, u_f)
502- deallocate(cfl_ele, matvfrac_ele, oldmatvfrac_ele, matdens_ele, oldmatdens_ele, norm_ele)
503+ deallocate(cfl_ele, matvfrac_ele, oldmatvfrac_ele, matdens_ele, oldmatdens_ele)
504 deallocate(visited)
505
506 call deallocate(matdens_upwind)
507@@ -1480,8 +1424,6 @@
508 call deallocate(dummyvfrac)
509 deallocate(dummyvfrac)
510 deallocate(dummyvfrac_bc_type)
511- call deallocate(dummyones)
512- deallocate(dummyones)
513 call deallocate(x_p)
514
515 call clean_deferred_deletion(state)
516
517=== modified file 'assemble/Momentum_Equation.F90'
518--- assemble/Momentum_Equation.F90 2013-10-07 16:23:35 +0000
519+++ assemble/Momentum_Equation.F90 2013-10-28 23:25:09 +0000
520@@ -2011,13 +2011,6 @@
521 ewrite(-1,*) "mass_terms/lump_mass_matrix"
522 FLExit("Good luck!")
523 end if
524-
525- else if(have_option("/material_phase["//int2str(i)//&
526- &"]/scalar_field::Pressure/prognostic"//&
527- &"/scheme/use_compressible_projection_method")) then
528- ewrite(-1,*) "You must lump the velocity mass matrix with the"
529- ewrite(-1,*) "compressible projection method."
530- FLExit("Sorry.")
531 end if
532
533 end if
534
535=== modified file 'preprocessor/Populate_State.F90'
536--- preprocessor/Populate_State.F90 2013-10-07 16:23:35 +0000
537+++ preprocessor/Populate_State.F90 2013-10-28 23:25:09 +0000
538@@ -3908,11 +3908,11 @@
539 if (have_option(trim(pressure_path))) then
540
541 ! Check that compressible projection method is used:
542- compressible_projection = have_option(trim(pressure_path)//&
543- "/scheme/use_compressible_projection_method")
544+ compressible_projection = have_option("/material_phase[0]"//&
545+ "/equation_of_state/compressible")
546
547 if(.not.(compressible_projection)) then
548- FLExit("For foam problems you need to use the compressible projection method.")
549+ FLExit("For foam problems you need to use a compressible eos.")
550 end if
551 end if
552
553
554=== modified file 'schemas/fluidity_options.rng'
555--- schemas/fluidity_options.rng 2013-10-11 10:48:07 +0000
556+++ schemas/fluidity_options.rng 2013-10-28 23:25:09 +0000
557@@ -3788,7 +3788,9 @@
558 <empty/>
559 </element>
560 <element name="type">
561- <a:documentation>Implements a prescribed normal flow. Works for DG only.</a:documentation>
562+ <a:documentation>Implements a prescribed normal flow. Works for DG only. This
563+implements a weakly imposed bounadry condition normal to the surface.
564+Note: Positive points out of the domain, negative into the domain.</a:documentation>
565 <attribute name="name">
566 <value>prescribed_normal_flow</value>
567 </attribute>
568
569=== modified file 'schemas/prognostic_field_options.rnc'
570--- schemas/prognostic_field_options.rnc 2013-10-07 16:23:35 +0000
571+++ schemas/prognostic_field_options.rnc 2013-10-28 23:25:09 +0000
572@@ -1360,107 +1360,71 @@
573 comment
574 )
575 },
576- (
577- ## Use the incompressible projection method to determine
578- ## the pressure and satisfy continuity
579- element use_projection_method {
580- ## Assemble and use the full schur complement.
581- ## This allows you to not lump the mass matrix if you're using
582- ## cg and to use the full momentum matrix in the projection if
583- ## you so desire.
584- element full_schur_complement {
585- (
586- ## Specify the inner matrix (IM) to form the projection schur complement (C^T*IM^{-1}*C).
587- ## Use the full mass matrix.
588- ##
589- ## Make sure you've not lumped your mass in the velocity spatial_discretisation if you want to be consistent!
590- element inner_matrix {
591- attribute name { "FullMassMatrix" },
592- element solver {
593- linear_solver_options_sym
594- }
595- }|
596- ## Specify the inner matrix (IM) to form the projection schur complement (C^T*IM^{-1}*C).
597- ## Use the full momentum matrix.
598- ##
599- ## Doesn't really matter if you've lumped your mass or not but why would you if you're doing a full inner solve anyway?
600- element inner_matrix {
601- attribute name { "FullMomentumMatrix" },
602- element solver {
603- linear_solver_options_asym_vector
604- }
605- }
606- ),
607- (
608- ## Specify the preconditioner matrix to use on the schur complement.
609- ##
610- ## For DG, the LumpedSchurComplement is our best approximation to CMC.
611- element preconditioner_matrix {
612- attribute name { "LumpedSchurComplement" },
613- element lump_on_submesh {
614- empty
615- }?
616- }|
617- ## Specify the preconditioner matrix to use on the schur complement.
618- ##
619- ## DiagonalSchurComplement = C_P^T * [(Big_m)_diagonal]^-1 * C
620- element preconditioner_matrix {
621- attribute name { "DiagonalSchurComplement" },
622- empty
623- }|
624- ## Specify the preconditioner matrix to use on the schur complement.
625- ##
626- ## Pressure Mass Matrix, scaled with the inverse of viscosity. This is
627- ## shown to be spectrally equivalent to the Schur complement.
628- ## Note that this currently only works with isoviscous and/or isotropic
629- ## viscosity tensors.
630- element preconditioner_matrix {
631- attribute name { "ScaledPressureMassMatrix" },
632- empty
633- }|
634- ## Specify the preconditioner matrix to use on the schur complement.
635- element preconditioner_matrix {
636- attribute name { "NoPreconditionerMatrix" },
637- empty
638- }
639- )
640- }?
641- }|
642- ## Use the compressible projection method to determine the
643- ## pressure and satisfy continuity and the eos.
644- ## This is only currently compatible with control volume
645- ## pressure spatial discretisations and requires a
646- ## multimaterial eos.
647- element use_compressible_projection_method {
648- (
649- ## Variable (normally a density) used to normalise
650- ## each materials contribution
651- ## to the C_P^T matrix. Leave unselected for no normalisation.
652- ## Selects the MaterialDensity field.
653- element normalisation {
654- attribute name{ "MaterialDensity" },
655- empty
656- }|
657- ## Variable (normally a density) used to normalise
658- ## each materials contribution
659- ## to the C_P^T matrix. Leave unselected for no normalisation.
660- ## Selects the bulk Density field.
661- element normalisation {
662- attribute name{ "Density" },
663- empty
664- }|
665- ## Variable (normally a density) used to normalise
666- ## each materials contribution
667- ## to the C_P^T matrix. Leave unselected for no normalisation.
668- ## Allows the selection of an arbitrary field.
669- element normalisation {
670- attribute name{ string },
671- empty
672- }
673- )?
674-
675- }
676- ),
677+ ## Use the incompressible projection method to determine
678+ ## the pressure and satisfy continuity
679+ element use_projection_method {
680+ ## Assemble and use the full schur complement.
681+ ## This allows you to not lump the mass matrix if you're using
682+ ## cg and to use the full momentum matrix in the projection if
683+ ## you so desire.
684+ element full_schur_complement {
685+ (
686+ ## Specify the inner matrix (IM) to form the projection schur complement (C^T*IM^{-1}*C).
687+ ## Use the full mass matrix.
688+ ##
689+ ## Make sure you've not lumped your mass in the velocity spatial_discretisation if you want to be consistent!
690+ element inner_matrix {
691+ attribute name { "FullMassMatrix" },
692+ element solver {
693+ linear_solver_options_sym
694+ }
695+ }|
696+ ## Specify the inner matrix (IM) to form the projection schur complement (C^T*IM^{-1}*C).
697+ ## Use the full momentum matrix.
698+ ##
699+ ## Doesn't really matter if you've lumped your mass or not but why would you if you're doing a full inner solve anyway?
700+ element inner_matrix {
701+ attribute name { "FullMomentumMatrix" },
702+ element solver {
703+ linear_solver_options_asym_vector
704+ }
705+ }
706+ ),
707+ (
708+ ## Specify the preconditioner matrix to use on the schur complement.
709+ ##
710+ ## For DG, the LumpedSchurComplement is our best approximation to CMC.
711+ element preconditioner_matrix {
712+ attribute name { "LumpedSchurComplement" },
713+ element lump_on_submesh {
714+ empty
715+ }?
716+ }|
717+ ## Specify the preconditioner matrix to use on the schur complement.
718+ ##
719+ ## DiagonalSchurComplement = C_P^T * [(Big_m)_diagonal]^-1 * C
720+ element preconditioner_matrix {
721+ attribute name { "DiagonalSchurComplement" },
722+ empty
723+ }|
724+ ## Specify the preconditioner matrix to use on the schur complement.
725+ ##
726+ ## Pressure Mass Matrix, scaled with the inverse of viscosity. This is
727+ ## shown to be spectrally equivalent to the Schur complement.
728+ ## Note that this currently only works with isoviscous and/or isotropic
729+ ## viscosity tensors.
730+ element preconditioner_matrix {
731+ attribute name { "ScaledPressureMassMatrix" },
732+ empty
733+ }|
734+ ## Specify the preconditioner matrix to use on the schur complement.
735+ element preconditioner_matrix {
736+ attribute name { "NoPreconditionerMatrix" },
737+ empty
738+ }
739+ )
740+ }?
741+ },
742 ## rediscretise the equations at every timestep and iteration
743 ## (this is useful as a debugging tool but shouldn't be necessary for any application runs)
744 element update_discretised_equation {
745
746=== modified file 'schemas/prognostic_field_options.rng'
747--- schemas/prognostic_field_options.rng 2013-10-07 16:23:35 +0000
748+++ schemas/prognostic_field_options.rng 2013-10-28 23:25:09 +0000
749@@ -1676,130 +1676,87 @@
750 </element>
751 <ref name="comment"/>
752 </element>
753- <choice>
754- <element name="use_projection_method">
755- <a:documentation>Use the incompressible projection method to determine
756+ <element name="use_projection_method">
757+ <a:documentation>Use the incompressible projection method to determine
758 the pressure and satisfy continuity</a:documentation>
759- <optional>
760- <element name="full_schur_complement">
761- <a:documentation>Assemble and use the full schur complement.
762+ <optional>
763+ <element name="full_schur_complement">
764+ <a:documentation>Assemble and use the full schur complement.
765 This allows you to not lump the mass matrix if you're using
766 cg and to use the full momentum matrix in the projection if
767 you so desire.</a:documentation>
768- <choice>
769- <element name="inner_matrix">
770- <a:documentation>Specify the inner matrix (IM) to form the projection schur complement (C^T*IM^{-1}*C).
771+ <choice>
772+ <element name="inner_matrix">
773+ <a:documentation>Specify the inner matrix (IM) to form the projection schur complement (C^T*IM^{-1}*C).
774 Use the full mass matrix.
775
776 Make sure you've not lumped your mass in the velocity spatial_discretisation if you want to be consistent!</a:documentation>
777- <attribute name="name">
778- <value>FullMassMatrix</value>
779- </attribute>
780- <element name="solver">
781- <ref name="linear_solver_options_sym"/>
782- </element>
783+ <attribute name="name">
784+ <value>FullMassMatrix</value>
785+ </attribute>
786+ <element name="solver">
787+ <ref name="linear_solver_options_sym"/>
788 </element>
789- <element name="inner_matrix">
790- <a:documentation>Specify the inner matrix (IM) to form the projection schur complement (C^T*IM^{-1}*C).
791+ </element>
792+ <element name="inner_matrix">
793+ <a:documentation>Specify the inner matrix (IM) to form the projection schur complement (C^T*IM^{-1}*C).
794 Use the full momentum matrix.
795
796 Doesn't really matter if you've lumped your mass or not but why would you if you're doing a full inner solve anyway?</a:documentation>
797- <attribute name="name">
798- <value>FullMomentumMatrix</value>
799- </attribute>
800- <element name="solver">
801- <ref name="linear_solver_options_asym_vector"/>
802- </element>
803+ <attribute name="name">
804+ <value>FullMomentumMatrix</value>
805+ </attribute>
806+ <element name="solver">
807+ <ref name="linear_solver_options_asym_vector"/>
808 </element>
809- </choice>
810- <choice>
811- <element name="preconditioner_matrix">
812- <a:documentation>Specify the preconditioner matrix to use on the schur complement.
813+ </element>
814+ </choice>
815+ <choice>
816+ <element name="preconditioner_matrix">
817+ <a:documentation>Specify the preconditioner matrix to use on the schur complement.
818
819 For DG, the LumpedSchurComplement is our best approximation to CMC.</a:documentation>
820- <attribute name="name">
821- <value>LumpedSchurComplement</value>
822- </attribute>
823- <optional>
824- <element name="lump_on_submesh">
825- <empty/>
826- </element>
827- </optional>
828- </element>
829- <element name="preconditioner_matrix">
830- <a:documentation>Specify the preconditioner matrix to use on the schur complement.
831+ <attribute name="name">
832+ <value>LumpedSchurComplement</value>
833+ </attribute>
834+ <optional>
835+ <element name="lump_on_submesh">
836+ <empty/>
837+ </element>
838+ </optional>
839+ </element>
840+ <element name="preconditioner_matrix">
841+ <a:documentation>Specify the preconditioner matrix to use on the schur complement.
842
843 DiagonalSchurComplement = C_P^T * [(Big_m)_diagonal]^-1 * C</a:documentation>
844- <attribute name="name">
845- <value>DiagonalSchurComplement</value>
846- </attribute>
847- <empty/>
848- </element>
849- <element name="preconditioner_matrix">
850- <a:documentation>Specify the preconditioner matrix to use on the schur complement.
851+ <attribute name="name">
852+ <value>DiagonalSchurComplement</value>
853+ </attribute>
854+ <empty/>
855+ </element>
856+ <element name="preconditioner_matrix">
857+ <a:documentation>Specify the preconditioner matrix to use on the schur complement.
858
859 Pressure Mass Matrix, scaled with the inverse of viscosity. This is
860 shown to be spectrally equivalent to the Schur complement.
861 Note that this currently only works with isoviscous and/or isotropic
862 viscosity tensors.</a:documentation>
863- <attribute name="name">
864- <value>ScaledPressureMassMatrix</value>
865- </attribute>
866- <empty/>
867- </element>
868- <element name="preconditioner_matrix">
869- <a:documentation>Specify the preconditioner matrix to use on the schur complement.</a:documentation>
870- <attribute name="name">
871- <value>NoPreconditionerMatrix</value>
872- </attribute>
873- <empty/>
874- </element>
875- </choice>
876- </element>
877- </optional>
878- </element>
879- <element name="use_compressible_projection_method">
880- <a:documentation>Use the compressible projection method to determine the
881-pressure and satisfy continuity and the eos.
882-This is only currently compatible with control volume
883-pressure spatial discretisations and requires a
884-multimaterial eos.</a:documentation>
885- <optional>
886- <choice>
887- <element name="normalisation">
888- <a:documentation>Variable (normally a density) used to normalise
889-each materials contribution
890-to the C_P^T matrix. Leave unselected for no normalisation.
891-Selects the MaterialDensity field.</a:documentation>
892- <attribute name="name">
893- <value>MaterialDensity</value>
894- </attribute>
895- <empty/>
896- </element>
897- <element name="normalisation">
898- <a:documentation>Variable (normally a density) used to normalise
899-each materials contribution
900-to the C_P^T matrix. Leave unselected for no normalisation.
901-Selects the bulk Density field.</a:documentation>
902- <attribute name="name">
903- <value>Density</value>
904- </attribute>
905- <empty/>
906- </element>
907- <element name="normalisation">
908- <a:documentation>Variable (normally a density) used to normalise
909-each materials contribution
910-to the C_P^T matrix. Leave unselected for no normalisation.
911-Allows the selection of an arbitrary field.</a:documentation>
912- <attribute name="name">
913- <data type="string" datatypeLibrary=""/>
914+ <attribute name="name">
915+ <value>ScaledPressureMassMatrix</value>
916+ </attribute>
917+ <empty/>
918+ </element>
919+ <element name="preconditioner_matrix">
920+ <a:documentation>Specify the preconditioner matrix to use on the schur complement.</a:documentation>
921+ <attribute name="name">
922+ <value>NoPreconditionerMatrix</value>
923 </attribute>
924 <empty/>
925 </element>
926 </choice>
927- </optional>
928- </element>
929- </choice>
930+ </element>
931+ </optional>
932+ </element>
933 <optional>
934 <element name="update_discretised_equation">
935 <a:documentation>rediscretise the equations at every timestep and iteration
936
937=== modified file 'schemas/test_advection_diffusion_options.rnc'
938--- schemas/test_advection_diffusion_options.rnc 2013-09-23 20:07:28 +0000
939+++ schemas/test_advection_diffusion_options.rnc 2013-10-28 23:25:09 +0000
940@@ -1470,97 +1470,61 @@
941 comment
942 )
943 },
944- (
945- ## Use the incompressible projection method to determine
946- ## the pressure and satisfy continuity
947- element use_projection_method {
948- ## Assemble and use the full schur complement.
949- ## This allows you to not lump the mass matrix if you're using
950- ## cg and to use the full momentum matrix in the projection if
951- ## you so desire.
952- element full_schur_complement {
953- (
954- ## Specify the inner matrix (IM) to form the projection schur complement (C^T*IM^{-1}*C).
955- ## Use the full mass matrix.
956- ##
957- ## Make sure you've not lumped your mass in the velocity spatial_discretisation if you want to be consistent!
958- element inner_matrix {
959- attribute name { "FullMassMatrix" },
960- element solver {
961- linear_solver_options_sym
962- }
963- }|
964- ## Specify the inner matrix (IM) to form the projection schur complement (C^T*IM^{-1}*C).
965- ## Use the full momentum matrix.
966- ##
967- ## Doesn't really matter if you've lumped your mass or not but why would you if you're doing a full inner solve anyway?
968- element inner_matrix {
969- attribute name { "FullMomentumMatrix" },
970- element solver {
971- linear_solver_options_asym
972- }
973- }
974- ),
975- (
976- ## Specify the preconditioner matrix to use on the schur complement.
977- ##
978- ## For DG, the LumpedSchurComplement is our best approximation to CMC.
979- element preconditioner_matrix {
980- attribute name { "LumpedSchurComplement" },
981- element lump_on_submesh {
982- empty
983- }?
984- }|
985- ## Specify the preconditioner matrix to use on the schur complement.
986- ##
987- ## DiagonalSchurComplement = C_P^T * [(Big_m)_diagonal]^-1 * C
988- element preconditioner_matrix {
989- attribute name { "DiagonalSchurComplement" },
990- empty
991- }|
992- ## Specify the preconditioner matrix to use on the schur complement.
993- element preconditioner_matrix {
994- attribute name { "NoPreconditionerMatrix" },
995- empty
996- }
997- )
998- }?
999- }|
1000- ## Use the compressible projection method to determine the
1001- ## pressure and satisfy continuity and the eos.
1002- ## This is only currently compatible with control volume
1003- ## pressure spatial discretisations and requires a
1004- ## multimaterial eos.
1005- element use_compressible_projection_method {
1006- (
1007- ## Variable (normally a density) used to normalise
1008- ## each materials contribution
1009- ## to the C_P^T matrix. Leave unselected for no normalisation.
1010- ## Selects the MaterialDensity field.
1011- element normalisation {
1012- attribute name{ "MaterialDensity" },
1013- empty
1014- }|
1015- ## Variable (normally a density) used to normalise
1016- ## each materials contribution
1017- ## to the C_P^T matrix. Leave unselected for no normalisation.
1018- ## Selects the bulk Density field.
1019- element normalisation {
1020- attribute name{ "Density" },
1021- empty
1022- }|
1023- ## Variable (normally a density) used to normalise
1024- ## each materials contribution
1025- ## to the C_P^T matrix. Leave unselected for no normalisation.
1026- ## Allows the selection of an arbitrary field.
1027- element normalisation {
1028- attribute name{ string },
1029- empty
1030- }
1031- )?
1032-
1033- }
1034- ),
1035+ ## Use the incompressible projection method to determine
1036+ ## the pressure and satisfy continuity
1037+ element use_projection_method {
1038+ ## Assemble and use the full schur complement.
1039+ ## This allows you to not lump the mass matrix if you're using
1040+ ## cg and to use the full momentum matrix in the projection if
1041+ ## you so desire.
1042+ element full_schur_complement {
1043+ (
1044+ ## Specify the inner matrix (IM) to form the projection schur complement (C^T*IM^{-1}*C).
1045+ ## Use the full mass matrix.
1046+ ##
1047+ ## Make sure you've not lumped your mass in the velocity spatial_discretisation if you want to be consistent!
1048+ element inner_matrix {
1049+ attribute name { "FullMassMatrix" },
1050+ element solver {
1051+ linear_solver_options_sym
1052+ }
1053+ }|
1054+ ## Specify the inner matrix (IM) to form the projection schur complement (C^T*IM^{-1}*C).
1055+ ## Use the full momentum matrix.
1056+ ##
1057+ ## Doesn't really matter if you've lumped your mass or not but why would you if you're doing a full inner solve anyway?
1058+ element inner_matrix {
1059+ attribute name { "FullMomentumMatrix" },
1060+ element solver {
1061+ linear_solver_options_asym
1062+ }
1063+ }
1064+ ),
1065+ (
1066+ ## Specify the preconditioner matrix to use on the schur complement.
1067+ ##
1068+ ## For DG, the LumpedSchurComplement is our best approximation to CMC.
1069+ element preconditioner_matrix {
1070+ attribute name { "LumpedSchurComplement" },
1071+ element lump_on_submesh {
1072+ empty
1073+ }?
1074+ }|
1075+ ## Specify the preconditioner matrix to use on the schur complement.
1076+ ##
1077+ ## DiagonalSchurComplement = C_P^T * [(Big_m)_diagonal]^-1 * C
1078+ element preconditioner_matrix {
1079+ attribute name { "DiagonalSchurComplement" },
1080+ empty
1081+ }|
1082+ ## Specify the preconditioner matrix to use on the schur complement.
1083+ element preconditioner_matrix {
1084+ attribute name { "NoPreconditionerMatrix" },
1085+ empty
1086+ }
1087+ )
1088+ }?
1089+ },
1090 ## rediscretise the equations at every timestep and iteration
1091 ## (for instance if using a compressible formulation
1092 ## or if density varies a lot or if not using a Boussinesque approximation)
1093
1094=== modified file 'schemas/test_advection_diffusion_options.rng'
1095--- schemas/test_advection_diffusion_options.rng 2013-09-23 20:07:28 +0000
1096+++ schemas/test_advection_diffusion_options.rng 2013-10-28 23:25:09 +0000
1097@@ -1725,118 +1725,75 @@
1098 </element>
1099 <ref name="comment"/>
1100 </element>
1101- <choice>
1102- <element name="use_projection_method">
1103- <a:documentation>Use the incompressible projection method to determine
1104+ <element name="use_projection_method">
1105+ <a:documentation>Use the incompressible projection method to determine
1106 the pressure and satisfy continuity</a:documentation>
1107- <optional>
1108- <element name="full_schur_complement">
1109- <a:documentation>Assemble and use the full schur complement.
1110+ <optional>
1111+ <element name="full_schur_complement">
1112+ <a:documentation>Assemble and use the full schur complement.
1113 This allows you to not lump the mass matrix if you're using
1114 cg and to use the full momentum matrix in the projection if
1115 you so desire.</a:documentation>
1116- <choice>
1117- <element name="inner_matrix">
1118- <a:documentation>Specify the inner matrix (IM) to form the projection schur complement (C^T*IM^{-1}*C).
1119+ <choice>
1120+ <element name="inner_matrix">
1121+ <a:documentation>Specify the inner matrix (IM) to form the projection schur complement (C^T*IM^{-1}*C).
1122 Use the full mass matrix.
1123
1124 Make sure you've not lumped your mass in the velocity spatial_discretisation if you want to be consistent!</a:documentation>
1125- <attribute name="name">
1126- <value>FullMassMatrix</value>
1127- </attribute>
1128- <element name="solver">
1129- <ref name="linear_solver_options_sym"/>
1130- </element>
1131+ <attribute name="name">
1132+ <value>FullMassMatrix</value>
1133+ </attribute>
1134+ <element name="solver">
1135+ <ref name="linear_solver_options_sym"/>
1136 </element>
1137- <element name="inner_matrix">
1138- <a:documentation>Specify the inner matrix (IM) to form the projection schur complement (C^T*IM^{-1}*C).
1139+ </element>
1140+ <element name="inner_matrix">
1141+ <a:documentation>Specify the inner matrix (IM) to form the projection schur complement (C^T*IM^{-1}*C).
1142 Use the full momentum matrix.
1143
1144 Doesn't really matter if you've lumped your mass or not but why would you if you're doing a full inner solve anyway?</a:documentation>
1145- <attribute name="name">
1146- <value>FullMomentumMatrix</value>
1147- </attribute>
1148- <element name="solver">
1149- <ref name="linear_solver_options_asym"/>
1150- </element>
1151+ <attribute name="name">
1152+ <value>FullMomentumMatrix</value>
1153+ </attribute>
1154+ <element name="solver">
1155+ <ref name="linear_solver_options_asym"/>
1156 </element>
1157- </choice>
1158- <choice>
1159- <element name="preconditioner_matrix">
1160- <a:documentation>Specify the preconditioner matrix to use on the schur complement.
1161+ </element>
1162+ </choice>
1163+ <choice>
1164+ <element name="preconditioner_matrix">
1165+ <a:documentation>Specify the preconditioner matrix to use on the schur complement.
1166
1167 For DG, the LumpedSchurComplement is our best approximation to CMC.</a:documentation>
1168- <attribute name="name">
1169- <value>LumpedSchurComplement</value>
1170- </attribute>
1171- <optional>
1172- <element name="lump_on_submesh">
1173- <empty/>
1174- </element>
1175- </optional>
1176- </element>
1177- <element name="preconditioner_matrix">
1178- <a:documentation>Specify the preconditioner matrix to use on the schur complement.
1179+ <attribute name="name">
1180+ <value>LumpedSchurComplement</value>
1181+ </attribute>
1182+ <optional>
1183+ <element name="lump_on_submesh">
1184+ <empty/>
1185+ </element>
1186+ </optional>
1187+ </element>
1188+ <element name="preconditioner_matrix">
1189+ <a:documentation>Specify the preconditioner matrix to use on the schur complement.
1190
1191 DiagonalSchurComplement = C_P^T * [(Big_m)_diagonal]^-1 * C</a:documentation>
1192- <attribute name="name">
1193- <value>DiagonalSchurComplement</value>
1194- </attribute>
1195- <empty/>
1196- </element>
1197- <element name="preconditioner_matrix">
1198- <a:documentation>Specify the preconditioner matrix to use on the schur complement.</a:documentation>
1199- <attribute name="name">
1200- <value>NoPreconditionerMatrix</value>
1201- </attribute>
1202- <empty/>
1203- </element>
1204- </choice>
1205- </element>
1206- </optional>
1207- </element>
1208- <element name="use_compressible_projection_method">
1209- <a:documentation>Use the compressible projection method to determine the
1210-pressure and satisfy continuity and the eos.
1211-This is only currently compatible with control volume
1212-pressure spatial discretisations and requires a
1213-multimaterial eos.</a:documentation>
1214- <optional>
1215- <choice>
1216- <element name="normalisation">
1217- <a:documentation>Variable (normally a density) used to normalise
1218-each materials contribution
1219-to the C_P^T matrix. Leave unselected for no normalisation.
1220-Selects the MaterialDensity field.</a:documentation>
1221- <attribute name="name">
1222- <value>MaterialDensity</value>
1223- </attribute>
1224- <empty/>
1225- </element>
1226- <element name="normalisation">
1227- <a:documentation>Variable (normally a density) used to normalise
1228-each materials contribution
1229-to the C_P^T matrix. Leave unselected for no normalisation.
1230-Selects the bulk Density field.</a:documentation>
1231- <attribute name="name">
1232- <value>Density</value>
1233- </attribute>
1234- <empty/>
1235- </element>
1236- <element name="normalisation">
1237- <a:documentation>Variable (normally a density) used to normalise
1238-each materials contribution
1239-to the C_P^T matrix. Leave unselected for no normalisation.
1240-Allows the selection of an arbitrary field.</a:documentation>
1241- <attribute name="name">
1242- <data type="string" datatypeLibrary=""/>
1243+ <attribute name="name">
1244+ <value>DiagonalSchurComplement</value>
1245+ </attribute>
1246+ <empty/>
1247+ </element>
1248+ <element name="preconditioner_matrix">
1249+ <a:documentation>Specify the preconditioner matrix to use on the schur complement.</a:documentation>
1250+ <attribute name="name">
1251+ <value>NoPreconditionerMatrix</value>
1252 </attribute>
1253 <empty/>
1254 </element>
1255 </choice>
1256- </optional>
1257- </element>
1258- </choice>
1259+ </element>
1260+ </optional>
1261+ </element>
1262 <optional>
1263 <element name="update_discretised_equation">
1264 <a:documentation>rediscretise the equations at every timestep and iteration
1265
1266=== modified file 'tests/1mat-shocktube-gmsh/1material_shocktube.flml'
1267--- tests/1mat-shocktube-gmsh/1material_shocktube.flml 2013-01-27 03:54:57 +0000
1268+++ tests/1mat-shocktube-gmsh/1material_shocktube.flml 2013-10-28 23:25:09 +0000
1269@@ -98,7 +98,7 @@
1270 <poisson_pressure_solution>
1271 <string_value lines="1">never</string_value>
1272 </poisson_pressure_solution>
1273- <use_compressible_projection_method/>
1274+ <use_projection_method/>
1275 </scheme>
1276 <solver>
1277 <iterative_method name="gmres">
1278
1279=== modified file 'tests/1mat-shocktube/1material_shocktube.flml'
1280--- tests/1mat-shocktube/1material_shocktube.flml 2013-01-27 03:54:57 +0000
1281+++ tests/1mat-shocktube/1material_shocktube.flml 2013-10-28 23:25:09 +0000
1282@@ -98,7 +98,7 @@
1283 <poisson_pressure_solution>
1284 <string_value lines="1">never</string_value>
1285 </poisson_pressure_solution>
1286- <use_compressible_projection_method/>
1287+ <use_projection_method/>
1288 </scheme>
1289 <solver>
1290 <iterative_method name="gmres">
1291
1292=== modified file 'tests/foam_2d_p1dgp2_weak_strong/drainage_a.flml'
1293--- tests/foam_2d_p1dgp2_weak_strong/drainage_a.flml 2013-05-30 11:47:42 +0000
1294+++ tests/foam_2d_p1dgp2_weak_strong/drainage_a.flml 2013-10-28 23:25:09 +0000
1295@@ -114,7 +114,7 @@
1296 <poisson_pressure_solution>
1297 <string_value lines="1">never</string_value>
1298 </poisson_pressure_solution>
1299- <use_compressible_projection_method/>
1300+ <use_projection_method/>
1301 <update_discretised_equation/>
1302 </scheme>
1303 <solver>
1304
1305=== modified file 'tests/inlet_velocity_bc_compressible/inlet_velocity_bc_compressible_1d.flml'
1306--- tests/inlet_velocity_bc_compressible/inlet_velocity_bc_compressible_1d.flml 2013-07-04 19:47:22 +0000
1307+++ tests/inlet_velocity_bc_compressible/inlet_velocity_bc_compressible_1d.flml 2013-10-28 23:25:09 +0000
1308@@ -173,7 +173,7 @@
1309 <poisson_pressure_solution>
1310 <string_value lines="1">never</string_value>
1311 </poisson_pressure_solution>
1312- <use_compressible_projection_method/>
1313+ <use_projection_method/>
1314 </scheme>
1315 <solver>
1316 <iterative_method name="gmres">
1317
1318=== modified file 'tests/inlet_velocity_bc_compressible_without_gravity/inlet_velocity_bc_compressible_without_gravity_1d.flml'
1319--- tests/inlet_velocity_bc_compressible_without_gravity/inlet_velocity_bc_compressible_without_gravity_1d.flml 2013-06-10 21:48:04 +0000
1320+++ tests/inlet_velocity_bc_compressible_without_gravity/inlet_velocity_bc_compressible_without_gravity_1d.flml 2013-10-28 23:25:09 +0000
1321@@ -154,7 +154,7 @@
1322 <poisson_pressure_solution>
1323 <string_value lines="1">never</string_value>
1324 </poisson_pressure_solution>
1325- <use_compressible_projection_method/>
1326+ <use_projection_method/>
1327 </scheme>
1328 <solver>
1329 <iterative_method name="gmres">
1330
1331=== modified file 'tests/inlet_velocity_bc_compressible_without_gravity/inlet_velocity_bc_compressible_without_gravity_pseudo1d.flml'
1332--- tests/inlet_velocity_bc_compressible_without_gravity/inlet_velocity_bc_compressible_without_gravity_pseudo1d.flml 2013-06-10 21:48:04 +0000
1333+++ tests/inlet_velocity_bc_compressible_without_gravity/inlet_velocity_bc_compressible_without_gravity_pseudo1d.flml 2013-10-28 23:25:09 +0000
1334@@ -125,7 +125,7 @@
1335 <poisson_pressure_solution>
1336 <string_value lines="1">never</string_value>
1337 </poisson_pressure_solution>
1338- <use_compressible_projection_method/>
1339+ <use_projection_method/>
1340 </scheme>
1341 <solver>
1342 <iterative_method name="gmres">
1343
1344=== modified file 'tests/inlet_velocity_bc_incompressible/inlet_velocity_bc_incompressible.flml'
1345--- tests/inlet_velocity_bc_incompressible/inlet_velocity_bc_incompressible.flml 2013-06-10 21:48:04 +0000
1346+++ tests/inlet_velocity_bc_incompressible/inlet_velocity_bc_incompressible.flml 2013-10-28 23:25:09 +0000
1347@@ -169,7 +169,7 @@
1348 <poisson_pressure_solution>
1349 <string_value lines="1">never</string_value>
1350 </poisson_pressure_solution>
1351- <use_compressible_projection_method/>
1352+ <use_projection_method/>
1353 </scheme>
1354 <solver>
1355 <iterative_method name="gmres">
1356
1357=== modified file 'tests/mmat-impact/2material_impact.flml'
1358--- tests/mmat-impact/2material_impact.flml 2012-12-11 18:13:04 +0000
1359+++ tests/mmat-impact/2material_impact.flml 2013-10-28 23:25:09 +0000
1360@@ -115,7 +115,7 @@
1361 <poisson_pressure_solution>
1362 <string_value lines="1">never</string_value>
1363 </poisson_pressure_solution>
1364- <use_compressible_projection_method/>
1365+ <use_projection_method/>
1366 <update_discretised_equation/>
1367 </scheme>
1368 <solver>
1369
1370=== modified file 'tests/mmat-shocktube/1material_shocktube.flml'
1371--- tests/mmat-shocktube/1material_shocktube.flml 2013-01-27 03:54:57 +0000
1372+++ tests/mmat-shocktube/1material_shocktube.flml 2013-10-28 23:25:09 +0000
1373@@ -98,7 +98,7 @@
1374 <poisson_pressure_solution>
1375 <string_value lines="1">never</string_value>
1376 </poisson_pressure_solution>
1377- <use_compressible_projection_method/>
1378+ <use_projection_method/>
1379 </scheme>
1380 <solver>
1381 <iterative_method name="gmres">
1382
1383=== modified file 'tests/mphase_dusty_gas_shock_tube/mphase_dusty_gas_shock_tube.flml'
1384--- tests/mphase_dusty_gas_shock_tube/mphase_dusty_gas_shock_tube.flml 2013-01-27 03:54:57 +0000
1385+++ tests/mphase_dusty_gas_shock_tube/mphase_dusty_gas_shock_tube.flml 2013-10-28 23:25:09 +0000
1386@@ -121,7 +121,7 @@
1387 <poisson_pressure_solution>
1388 <string_value lines="1">never</string_value>
1389 </poisson_pressure_solution>
1390- <use_compressible_projection_method/>
1391+ <use_projection_method/>
1392 </scheme>
1393 <solver>
1394 <iterative_method name="preonly"/>
1395
1396=== modified file 'tests/mphase_dusty_gas_shock_tube/single_phase_frozen_flow_test.flml'
1397--- tests/mphase_dusty_gas_shock_tube/single_phase_frozen_flow_test.flml 2012-10-26 20:16:46 +0000
1398+++ tests/mphase_dusty_gas_shock_tube/single_phase_frozen_flow_test.flml 2013-10-28 23:25:09 +0000
1399@@ -121,7 +121,7 @@
1400 <poisson_pressure_solution>
1401 <string_value lines="1">never</string_value>
1402 </poisson_pressure_solution>
1403- <use_compressible_projection_method/>
1404+ <use_projection_method/>
1405 </scheme>
1406 <solver>
1407 <iterative_method name="preonly"/>
1408
1409=== modified file 'tests/mphase_inlet_velocity_bc_compressible/mphase_inlet_velocity_bc_compressible.flml'
1410--- tests/mphase_inlet_velocity_bc_compressible/mphase_inlet_velocity_bc_compressible.flml 2013-07-04 19:47:22 +0000
1411+++ tests/mphase_inlet_velocity_bc_compressible/mphase_inlet_velocity_bc_compressible.flml 2013-10-28 23:25:09 +0000
1412@@ -146,7 +146,7 @@
1413 <poisson_pressure_solution>
1414 <string_value lines="1">never</string_value>
1415 </poisson_pressure_solution>
1416- <use_compressible_projection_method/>
1417+ <use_projection_method/>
1418 </scheme>
1419 <solver>
1420 <iterative_method name="gmres">
1421
1422=== modified file 'tests/mphase_rogue_shock_tube_dense_bed_glass/mphase_rogue_shock_tube_dense_bed_glass.flml'
1423--- tests/mphase_rogue_shock_tube_dense_bed_glass/mphase_rogue_shock_tube_dense_bed_glass.flml 2013-04-24 14:56:59 +0000
1424+++ tests/mphase_rogue_shock_tube_dense_bed_glass/mphase_rogue_shock_tube_dense_bed_glass.flml 2013-10-28 23:25:09 +0000
1425@@ -105,7 +105,7 @@
1426 <poisson_pressure_solution>
1427 <string_value lines="1">never</string_value>
1428 </poisson_pressure_solution>
1429- <use_compressible_projection_method/>
1430+ <use_projection_method/>
1431 </scheme>
1432 <solver>
1433 <iterative_method name="gmres">
1434
1435=== modified file 'tests/mphase_rogue_shock_tube_dense_bed_nylon/mphase_rogue_shock_tube_dense_bed_nylon.flml'
1436--- tests/mphase_rogue_shock_tube_dense_bed_nylon/mphase_rogue_shock_tube_dense_bed_nylon.flml 2013-04-24 14:56:59 +0000
1437+++ tests/mphase_rogue_shock_tube_dense_bed_nylon/mphase_rogue_shock_tube_dense_bed_nylon.flml 2013-10-28 23:25:09 +0000
1438@@ -105,7 +105,7 @@
1439 <poisson_pressure_solution>
1440 <string_value lines="1">never</string_value>
1441 </poisson_pressure_solution>
1442- <use_compressible_projection_method/>
1443+ <use_projection_method/>
1444 </scheme>
1445 <solver>
1446 <iterative_method name="gmres">
1447
1448=== modified file 'tests/mphase_strong_pressure_bc_compressible/mphase_strong_pressure_bc_compressible_p0p1.flml'
1449--- tests/mphase_strong_pressure_bc_compressible/mphase_strong_pressure_bc_compressible_p0p1.flml 2013-06-10 22:28:16 +0000
1450+++ tests/mphase_strong_pressure_bc_compressible/mphase_strong_pressure_bc_compressible_p0p1.flml 2013-10-28 23:25:09 +0000
1451@@ -148,7 +148,7 @@
1452 <poisson_pressure_solution>
1453 <string_value lines="1">never</string_value>
1454 </poisson_pressure_solution>
1455- <use_compressible_projection_method/>
1456+ <use_projection_method/>
1457 </scheme>
1458 <solver>
1459 <iterative_method name="gmres">
1460
1461=== modified file 'tests/mphase_strong_pressure_bc_compressible/mphase_strong_pressure_bc_compressible_p2p1.flml'
1462--- tests/mphase_strong_pressure_bc_compressible/mphase_strong_pressure_bc_compressible_p2p1.flml 2013-06-10 22:28:16 +0000
1463+++ tests/mphase_strong_pressure_bc_compressible/mphase_strong_pressure_bc_compressible_p2p1.flml 2013-10-28 23:25:09 +0000
1464@@ -145,7 +145,7 @@
1465 <poisson_pressure_solution>
1466 <string_value lines="1">never</string_value>
1467 </poisson_pressure_solution>
1468- <use_compressible_projection_method/>
1469+ <use_projection_method/>
1470 </scheme>
1471 <solver>
1472 <iterative_method name="gmres">
1473
1474=== modified file 'tests/mphase_subtract_out_reference_profile/mphase_subtract_out_reference_profile_1d.flml'
1475--- tests/mphase_subtract_out_reference_profile/mphase_subtract_out_reference_profile_1d.flml 2013-07-05 00:58:58 +0000
1476+++ tests/mphase_subtract_out_reference_profile/mphase_subtract_out_reference_profile_1d.flml 2013-10-28 23:25:09 +0000
1477@@ -160,7 +160,7 @@
1478 <poisson_pressure_solution>
1479 <string_value lines="1">never</string_value>
1480 </poisson_pressure_solution>
1481- <use_compressible_projection_method/>
1482+ <use_projection_method/>
1483 </scheme>
1484 <solver>
1485 <iterative_method name="gmres">
1486
1487=== modified file 'tests/shocktube_1d/shocktube.flml'
1488--- tests/shocktube_1d/shocktube.flml 2013-01-27 03:54:57 +0000
1489+++ tests/shocktube_1d/shocktube.flml 2013-10-28 23:25:09 +0000
1490@@ -74,7 +74,7 @@
1491 <poisson_pressure_solution>
1492 <string_value lines="1">never</string_value>
1493 </poisson_pressure_solution>
1494- <use_compressible_projection_method/>
1495+ <use_projection_method/>
1496 </scheme>
1497 <solver>
1498 <iterative_method name="preonly"/>
1499
1500=== modified file 'tests/strong_pressure_bc_compressible/strong_pressure_bc_compressible.flml'
1501--- tests/strong_pressure_bc_compressible/strong_pressure_bc_compressible.flml 2013-06-10 21:15:35 +0000
1502+++ tests/strong_pressure_bc_compressible/strong_pressure_bc_compressible.flml 2013-10-28 23:25:09 +0000
1503@@ -132,7 +132,7 @@
1504 <poisson_pressure_solution>
1505 <string_value lines="1">never</string_value>
1506 </poisson_pressure_solution>
1507- <use_compressible_projection_method/>
1508+ <use_projection_method/>
1509 </scheme>
1510 <solver>
1511 <iterative_method name="gmres">
1512
1513=== modified file 'tests/subtract_out_reference_profile/subtract_out_reference_profile_1d.flml'
1514--- tests/subtract_out_reference_profile/subtract_out_reference_profile_1d.flml 2013-07-05 00:58:58 +0000
1515+++ tests/subtract_out_reference_profile/subtract_out_reference_profile_1d.flml 2013-10-28 23:25:09 +0000
1516@@ -172,7 +172,7 @@
1517 <poisson_pressure_solution>
1518 <string_value lines="1">never</string_value>
1519 </poisson_pressure_solution>
1520- <use_compressible_projection_method/>
1521+ <use_projection_method/>
1522 </scheme>
1523 <solver>
1524 <iterative_method name="gmres">
1525
1526=== modified file 'tests/subtract_out_reference_profile/subtract_out_reference_profile_pseudo1d.flml'
1527--- tests/subtract_out_reference_profile/subtract_out_reference_profile_pseudo1d.flml 2013-07-05 00:58:58 +0000
1528+++ tests/subtract_out_reference_profile/subtract_out_reference_profile_pseudo1d.flml 2013-10-28 23:25:09 +0000
1529@@ -147,7 +147,7 @@
1530 <poisson_pressure_solution>
1531 <string_value lines="1">never</string_value>
1532 </poisson_pressure_solution>
1533- <use_compressible_projection_method/>
1534+ <use_projection_method/>
1535 </scheme>
1536 <solver>
1537 <iterative_method name="gmres">