Merge lp:~fluidity-core/fluidity/prescribed-regions-adaptivity into lp:fluidity

Proposed by Stephan Kramer
Status: Merged
Merged at revision: 4268
Proposed branch: lp:~fluidity-core/fluidity/prescribed-regions-adaptivity
Merge into: lp:fluidity
Diff against target: 1733 lines (+914/-191) (has conflicts)
31 files modified
assemble/Adapt_Integration.F90 (+9/-0)
assemble/Mba2d_Integration.F90 (+59/-44)
femtools/Adjacency_Lists.F90 (+1/-1)
femtools/Fields_Allocates.F90 (+176/-65)
femtools/Fields_Base.F90 (+31/-9)
femtools/Fields_Data_Types.F90 (+21/-3)
femtools/Surface_Labels.F90 (+46/-39)
femtools/Write_GMSH.F90 (+4/-4)
femtools/Write_Triangle.F90 (+6/-7)
manual/configuring_fluidity.tex (+21/-0)
preprocessor/Populate_Sub_State.F90 (+19/-1)
tests/Stokes_Subduction_VK_Case_1b/Makefile (+0/-1)
tests/Stokes_Subduction_VK_Case_1b/Stokes-Subduction-VK-Case-1b.flml (+1/-1)
tests/flredecomp_2d_fieldweighted/Makefile (+2/-3)
tests/flredecomp_2d_fieldweighted/flredecomp-2d-fieldweighted.flml (+1/-1)
tests/internal_boundary_adaptivity/Makefile (+6/-0)
tests/internal_boundary_adaptivity/internal_boundary.flml (+391/-0)
tests/internal_boundary_adaptivity/internal_boundary_adaptivity.xml (+55/-0)
tests/internal_boundary_adaptivity/src/square.geo (+33/-0)
tests/viscous_fs_zhong_spatial/Makefile (+6/-1)
tests/viscous_fs_zhong_spatial/viscous_fs_zhong_A.flml (+1/-1)
tests/viscous_fs_zhong_spatial/viscous_fs_zhong_B.flml (+1/-1)
tests/viscous_fs_zhong_spatial_explicit/Makefile (+6/-1)
tests/viscous_fs_zhong_spatial_explicit/viscous_fs_zhong_A.flml (+1/-1)
tests/viscous_fs_zhong_spatial_explicit/viscous_fs_zhong_B.flml (+1/-1)
tests/viscous_fs_zhong_spatial_explicit_varrho/Makefile (+6/-1)
tests/viscous_fs_zhong_spatial_explicit_varrho/viscous_fs_zhong_A.flml (+1/-1)
tests/viscous_fs_zhong_spatial_explicit_varrho/viscous_fs_zhong_B.flml (+1/-1)
tests/viscous_fs_zhong_spatial_varrho/Makefile (+6/-1)
tests/viscous_fs_zhong_spatial_varrho/viscous_fs_zhong_A.flml (+1/-1)
tests/viscous_fs_zhong_spatial_varrho/viscous_fs_zhong_B.flml (+1/-1)
Text conflict in tests/viscous_fs_zhong_spatial/Makefile
Text conflict in tests/viscous_fs_zhong_spatial_explicit/Makefile
Text conflict in tests/viscous_fs_zhong_spatial_explicit_varrho/Makefile
Text conflict in tests/viscous_fs_zhong_spatial_varrho/Makefile
To merge this branch: bzr merge lp:~fluidity-core/fluidity/prescribed-regions-adaptivity
Reviewer Review Type Date Requested Status
Samuel Parkinson Approve
Fluidity Core Team Pending
Review via email: mp+176400@code.launchpad.net

Description of the change

Improved support for internal boundaries, in particular 2d adaptivity.

This branch is a bit of a misnomer really, there is nothing specifically about prescribed regions in this merge. After this merge, you can:

* read in a gmsh or triangle mesh with an internal boundary directly.
Previously a hack was needed: by running gmsh2triangle with an extra -i option, the internal facets would be doubled (as needed for Fluidity's data structures) and an extra column in the .edge/.face file would be written out that indicates which element each facet belongs to, so we can distinguish between the two coincident facets. Having both facets in the input mesh also enables the two facets to have a different surface id, thus allowing different boundary conditions on either side of the internal boundary. This functionality is also used in checkpointing of periodic meshes (in particular in periodise) with an aliased and physical surface id on either side of the periodic boundary, which is an internal boundary in the periodic mesh.
For most other practical purposes however having a different boundary condition on either side is not really possible due to restrictions of the assembly code (and in the case of cg having only a single degree of freedom). Moreover a mesh prepared in gmsh will only allow you to to assign one surface id, and will only write out a single facet.
Thus, to cut a long story short, this merge allows you to read in a gmsh file with single facets along the internal boundary directly into Fluidity. The facets will be doubled inside add_faces() and will of course be assigned the same surface id.
* use 2d adaptivity with an internal boundary
Here, only the single valued internal boundary condition is supported. This is because the 2d adaptivity library only deals with single faceted internal boundaries. The internal boundary is given as a constraint to the library, and returned (in the new numbering) after the adapt. A call to add_faces() then takes care of the doubling of the internal facets.

To deal with these changes the following interface changes were introduced:
* rename has_internal_boundaries() to has_discontinuous_internal_boundaries()
This is because this routine now only applies to the case where the internal boundary does have multi-valued surface ids and is read and written with an element_owner column in the mesh file. At the moment this is only used for periodic meshes.
* add unique_surface_element_count()
When the internal facets are duplicated inside add_faces(), the new ones are added at the end of the list of the original, unique facets provided in the mesh. surface_element_count() will include both copies and should be used in most places in the assembly code dealing with boundary conditions. unique_surface_element_count() only counts the original single facets and is only used in some special cases, such as providing the facets to the adaptivity library, or when writing out the .edge/.face file.

This functionality is tested in a new test, internal_boundary_adaptivity.

NOTE that the actual applying of internal boundaries to the equations is not very well tested. This depends very much on which discretisation is used and which type of bcs. It should therefore be carefully evaluated for the case you want to apply it to. You will probably have most luck with strong bcs, with weak bcs your mileage may vary.

To post a comment you must log in.
Revision history for this message
Rhodri Davies (rhodri-davies) wrote :

I have run a suite of 2D simulations, in serial and parallel, to test this branch today. They all worked beautifully. A glance at the code suggests that everything is nicely done, although I suspect there may be somebody better to look at certain aspects than myself. I note that in adapt integration you have the warning:

    if (surface_element_count(input_positions)/=unique_surface_element_count(input_positions%mesh)) then
      ewrite(0,*) "WARNING: It appears you have an internal boundary and you're trying to use 3D adaptivity."
      ewrite(0,*) "This combination has not been tested yet and may not work at all."
      ewrite(0,*) "Please report your experiences to the Fluidity mailing list."
    end if

If you're happy to wait a few days, I can test this with one of Giuseppe's 3D cases and feedback. However, if you're keen to get this merged I can easily do that post merge. Your choice entirely.

Rhod

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

Thanks for testing this, Rhodri!

That warning exists not because "in theory it should work but I haven't had time to test it". It's simply not implemented, the stuff I added for 2d adaptivity is in a completely different code path. So there's three possible outcomes:
1) It crashes immediately
2) It goes through an adapt but the internal boundary dissapears (this is what would happen in 2D before)
3) It somehow magically works (quite unlikely)

Now if there's demand I'm quite happy at implementing it for 3d as well (this should be a lot easier now with the new add_faces() functionality), but I don't think this needs to go in this merge.

Revision history for this message
Jon Hill (jon-hill) wrote :

 - Can you reword the warning from "not tested" to "not implemented". This is more accurate
 - "owner ship" is one word (Fields_Allocates)

Otherwise looks great. I'll leave Sam to do the approve.

4229. By Stephan Kramer

Merge from trunk.

4230. By Stephan Kramer

Changes to error messages, as suggested by jhill.

Revision history for this message
Samuel Parkinson (s-parkinson11) wrote :

Hey Stephan,

Generally all top notch. Just a few comments:
1) in Mba2D_integration.F90 there is a comment saying "not sure this will work with lock_faces". What does this mean?
2) lots of testing which is good, but errors get displayed when running the new test saying "The following boundary ids were specified, but they don't appear in the surface mesh:".
3) You mention that only certain discretisations are supported. Should there be a manual entry listing the caveats under which this is tested and is known to work.

Other than that it's all good.

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

Hey Sam,

Thanks for the review.
Ad 1): had to dig deep in my memory. It seems lock_faces is only used with periodic adaptivity. I think in general internal boundaries would need testing with that anyway. What I specifically had in mind with that comment I can't really work out, so I just removed it.
Ad 2): These are spurious warnings actually. This is a separate problem with prescribed regions. It calls populate state on the substate (the state that is based on the mesh with the prescribed regions removed) and then finds that some of the boundaries do no exist. I have opened a bug report (https://bugs.launchpad.net/fluidity/+bug/1240921) as that should be fixed.
Ad 3): Good point. Will add some stuff to the manual with a lot of caveats.

4231. By Stephan Kramer

Remove unclear comment.

4232. By Stephan Kramer

Say something about internal bcs in the manual, as suggested by sparkinson.

Revision history for this message
Samuel Parkinson (s-parkinson11) :
review: Approve

Preview Diff

[H/L] Next/Prev Comment, [J/K] Next/Prev File, [N/P] Next/Prev Hunk
1=== modified file 'assemble/Adapt_Integration.F90'
2--- assemble/Adapt_Integration.F90 2011-04-22 17:28:48 +0000
3+++ assemble/Adapt_Integration.F90 2013-10-17 12:55:48 +0000
4@@ -357,6 +357,15 @@
5 if(nselm > 0) then
6 call getsndgln(input_positions%mesh, snlist)
7 end if
8+
9+ if (surface_element_count(input_positions)/=unique_surface_element_count(input_positions%mesh)) then
10+ ewrite(0,*) "It appears you have an internal boundary and you're trying to use 3D adaptivity."
11+ ewrite(0,*) "This combination has not been implemented yet."
12+ ! You could try to see if it somehow does work, by simply removing this FLExit()
13+ ! (make sure to check you still have the right internal boundary ids after the adapt)
14+ ! Feel free to discuss on the fluidity mailing list.
15+ FLExit("Cannot have internal boundaries with 3D adaptivity")
16+ end if
17
18 ! Surface IDs
19 allocate(surfid(nselm))
20
21=== modified file 'assemble/Mba2d_Integration.F90'
22--- assemble/Mba2d_Integration.F90 2010-11-25 12:09:32 +0000
23+++ assemble/Mba2d_Integration.F90 2013-10-17 12:55:48 +0000
24@@ -47,7 +47,7 @@
25
26 type(mesh_type), pointer :: xmesh
27
28- integer :: nonods, mxnods, orig_stotel, stotel, mxface, totele, maxele
29+ integer :: nonods, mxnods, orig_stotel, stotel, mxface, totele, maxele, stotel_external
30 real, dimension(:, :), allocatable :: pos
31 integer, dimension(:, :), allocatable :: ipf
32 integer, dimension(:, :), allocatable :: ipe
33@@ -57,7 +57,7 @@
34 integer, dimension(:), allocatable :: iFnc
35 integer, dimension(:), allocatable :: lbE
36 real, dimension(:, :), allocatable :: tmp_metric
37- integer :: i, j, k, partition_surface_id, face
38+ integer :: i, j, k, partition_surface_id, face, face2
39 real :: quality, rQuality
40 integer :: iPrint, ierr, maxWr, maxWi
41 real, dimension(:), allocatable :: rW
42@@ -144,6 +144,7 @@
43 ipf = 0
44 partition_surface_id = maxval(surface_ids) + 1
45 stotel = 0
46+ stotel_external = 0
47
48 call allocate(input_face_numbering_to_mba2d_numbering)
49 do i=1,totele
50@@ -156,8 +157,9 @@
51 call insert(input_face_numbering_to_mba2d_numbering, face, stotel)
52 ipf(1:2, stotel) = face_global_nodes(xmesh, face)
53 ipf(3, stotel) = 0
54- if (face <= orig_stotel) then ! if face is genuinely external, i.e. on the domain exterior
55+ if (face <= orig_stotel) then ! if facet is genuinely external, i.e. on the domain exterior
56 ipf(4, stotel) = surface_ids(face)
57+ stotel_external = stotel_external + 1
58 else
59 ipf(4, stotel) = partition_surface_id
60 end if
61@@ -165,6 +167,28 @@
62 end do
63 end do
64
65+ if (stotel_external<orig_stotel) then
66+ ! not all facets in the surface mesh are external apparently
67+ do face=1, orig_stotel
68+ face2 = face_neigh(xmesh, face)
69+ if (face>face2) then
70+ ! if face==face2 it's an external facet that's dealt with already
71+ ! we check face>face2 to ensure we only copy one of the two coinciding facets
72+ stotel = stotel +1
73+ call insert(input_face_numbering_to_mba2d_numbering, face, stotel)
74+ ipf(1:2, stotel) = face_global_nodes(xmesh, face)
75+ ipf(3, stotel) = 0
76+ ipf(4, stotel) = surface_ids(face)
77+ if (surface_ids(face)/=surface_ids(face2)) then
78+ ! note that we're here checking for the combined surface+coplanar id to be the same
79+ ! but the coplanar id of the 2 facets should always be the same
80+ FLExit("Adaptivity with internal boundaries only works if the surface id is single valued")
81+ end if
82+ end if
83+ end do
84+
85+ end if
86+
87 if (.not. present(lock_faces)) then
88 nfv = 0
89 allocate(ifv(nfv))
90@@ -343,22 +367,9 @@
91 new_mesh%option_path = xmesh%option_path
92
93 if (.not. isparallel()) then
94- allocate(boundary_ids(stotel))
95- allocate(coplanar_ids(stotel))
96- call deinterleave_surface_ids(ipf(4, 1:stotel), max_coplanar_id, boundary_ids, coplanar_ids)
97-
98- allocate(new_sndgln(1:2,1:stotel))
99- new_sndgln=ipf(1:2,1:stotel)
100- call add_faces(new_mesh, sndgln=reshape(new_sndgln, (/ 2*stotel /) ), &
101- boundary_ids=boundary_ids)
102- deallocate(boundary_ids)
103- deallocate(new_sndgln)
104-
105- if(associated(xmesh%faces%coplanar_ids)) then
106- allocate(new_mesh%faces%coplanar_ids(stotel))
107- new_mesh%faces%coplanar_ids = coplanar_ids
108- end if
109- deallocate(coplanar_ids)
110+ allocate(new_sndgln(1:2,1:stotel), mba_boundary_ids(1:stotel))
111+ new_sndgln = ipf(1:2,1:stotel)
112+ mba_boundary_ids =ipf(4,1:stotel)
113 else
114 ! In parallel, we need to filter out the surface elements with colour partition_surface_id, because
115 ! they are not real external faces
116@@ -372,35 +383,39 @@
117 end if
118 end do
119
120+ ! number of surface elements without inter-partition surface elements
121 stotel = j - 1
122- allocate(mba_boundary_ids(stotel))
123-
124- do i=1,stotel
125+ allocate(mba_boundary_ids(1:stotel), new_sndgln(1:2,1:stotel))
126+ do i=1, stotel
127 mba_boundary_ids(i) = ipf(4, fetch(physical_surface_ids, i))
128- end do
129-
130- allocate(boundary_ids(stotel))
131- allocate(coplanar_ids(stotel))
132- call deinterleave_surface_ids(mba_boundary_ids, max_coplanar_id, boundary_ids, coplanar_ids)
133- deallocate(mba_boundary_ids)
134-
135- allocate(new_sndgln(1:2,1:stotel))
136- do i=1,stotel
137- new_sndgln(1:2, i) = ipf(1:2, fetch(physical_surface_ids, i))
138- end do
139- call add_faces(new_mesh, sndgln=reshape(new_sndgln, (/ 2*stotel /) ), &
140- boundary_ids=boundary_ids)
141- deallocate(boundary_ids)
142- deallocate(new_sndgln)
143-
144- if(associated(xmesh%faces%coplanar_ids)) then
145- allocate(new_mesh%faces%coplanar_ids(stotel))
146- new_mesh%faces%coplanar_ids = coplanar_ids
147- end if
148- deallocate(coplanar_ids)
149-
150+ new_sndgln(1:2, i) = ipf(1:2, fetch(physical_surface_ids, i))
151+ end do
152+
153+ do i=1, stotel
154+ new_sndgln(1:2, i) = ipf(1:2, fetch(physical_surface_ids, i))
155+ end do
156 call deallocate(physical_surface_ids)
157 end if
158+
159+ ! add_faces might create extra (internal) surface elements, so we
160+ ! use the combined boundary+coplanar ids first
161+ call add_faces(new_mesh, sndgln=reshape(new_sndgln, (/ 2*stotel /) ), &
162+ boundary_ids=mba_boundary_ids)
163+ deallocate(mba_boundary_ids)
164+ deallocate(new_sndgln)
165+
166+ ! and only deinterleave now we know the total number of elements in the surface mesh
167+ stotel = surface_element_count(new_mesh)
168+ allocate(boundary_ids(1:stotel), coplanar_ids(1:stotel))
169+ call deinterleave_surface_ids(new_mesh%faces%boundary_ids, max_coplanar_id, boundary_ids, coplanar_ids)
170+
171+ new_mesh%faces%boundary_ids = boundary_ids
172+
173+ if(associated(xmesh%faces%coplanar_ids)) then
174+ allocate(new_mesh%faces%coplanar_ids(1:stotel))
175+ new_mesh%faces%coplanar_ids = coplanar_ids
176+ end if
177+ deallocate(boundary_ids, coplanar_ids)
178
179 if(have_option("/mesh_adaptivity/hr_adaptivity/preserve_mesh_regions")&
180 .or.present_and_true(force_preserve_regions)) then
181
182=== modified file 'femtools/Adjacency_Lists.F90'
183--- femtools/Adjacency_Lists.F90 2010-11-09 14:08:19 +0000
184+++ femtools/Adjacency_Lists.F90 2013-10-17 12:55:48 +0000
185@@ -908,7 +908,7 @@
186 if(.not. any(row_idx(j - 1)%ptr == candidate_ele)) cycle ele_loop
187 end do
188
189-#ifndef DDEBUG
190+#ifdef DDEBUG
191 if(adj_ele > 0) then
192 ! We've found more than one adjacent element. We're in trouble.
193 adj_ele = -1
194
195=== modified file 'femtools/Fields_Allocates.F90'
196--- femtools/Fields_Allocates.F90 2013-03-05 10:21:07 +0000
197+++ femtools/Fields_Allocates.F90 2013-10-17 12:55:48 +0000
198@@ -154,7 +154,7 @@
199 integer, intent(in) :: nodes, elements
200 type(element_type), target, intent(in) :: shape
201 character(len=*), intent(in), optional :: name
202- integer :: i, j
203+ integer :: i
204
205 mesh%nodes=nodes
206
207@@ -909,7 +909,7 @@
208
209 integer, dimension(:), allocatable :: ndglno
210 real, dimension(:), pointer :: val
211- integer :: i, j, input_nodes, n_faces
212+ integer :: i, input_nodes, n_faces
213
214 if (present(continuity)) then
215 mesh%continuity=continuity
216@@ -1126,9 +1126,15 @@
217 !! be consistent with that of the periodic face local node numbering.
218 type(integer_hash_table), intent(in), optional :: periodic_face_map
219 !! This list gives the element owning each face in sndgln. This needs
220- !! to be provided when sndgln contains internal faces, as we need to
221- !! decide which of the two adjacent elements the face belongs to
222- !! (used in reading in periodic meshes which include the periodic faces in the surface mesh)
223+ !! to be provided when sndgln contains internal faces and both copies
224+ !! are included, as we need to decide which of the two adjacent elements
225+ !! the facet belongs to (used in reading in periodic meshes which include
226+ !! the periodic facets in the surface mesh with a different surface id on
227+ !! either side of the periodic boundary). If no element_owner information
228+ !! is provided, internal facets in sndgln are assumed to only appear once
229+ !! and a copy will be made, its boundary id will be copied as well. This
230+ !! means afterwards the surface_element_count() will be higher than the
231+ !! number of facets provided in sndgln.
232 integer, dimension(:), intent(in), optional :: element_owner
233 !! See comments above sndgln
234 logical, intent(in), optional :: incomplete_surface_mesh
235@@ -1211,8 +1217,8 @@
236 ! works as long as we're not discontinuous
237 assert( mesh%continuity>=0 )
238
239- ! the periodic faces will be internal faces in the output periodic mesh
240- mesh%faces%has_internal_boundaries = .true.
241+ ! the periodic faces will be discontinuous internal faces in the output periodic mesh
242+ mesh%faces%has_discontinuous_internal_boundaries = .true.
243
244 else if (model%periodic .and. .not. mesh%periodic) then
245
246@@ -1221,7 +1227,7 @@
247 mesh, model, lperiodic_face_map, stat=stat)
248
249 ! the subroutine above only works if the removing of periodic bcs has removed all internal boundaries
250- mesh%faces%has_internal_boundaries = .true.
251+ mesh%faces%has_discontinuous_internal_boundaries = .false.
252
253 else
254 ! Transfer the faces from model to mesh
255@@ -1229,7 +1235,7 @@
256 call incref(mesh%faces%face_list)
257
258 ! have internal faces if the model does
259- mesh%faces%has_internal_boundaries = has_internal_boundaries(model)
260+ mesh%faces%has_discontinuous_internal_boundaries = has_discontinuous_internal_boundaries(model)
261 end if
262
263 ! face_element_list is a pure copy of that of the model
264@@ -1249,6 +1255,7 @@
265 size(mesh%faces%boundary_ids), &
266 trim(mesh%name)//" boundary_ids")
267 #endif
268+ mesh%faces%unique_surface_element_count = model%faces%unique_surface_element_count
269
270 ! same for coplanar ids (if existent)
271 if (associated(model%faces%coplanar_ids)) then
272@@ -1382,15 +1389,16 @@
273 integer, dimension(:), intent(in), optional :: element_owner
274 logical, intent(in), optional :: incomplete_surface_mesh
275
276+ type(integer_hash_table):: internal_facet_map
277 type(element_type), pointer :: mesh_shape
278 type(element_type) :: face_shape
279- logical:: internal_face, surface_elements_added
280+ logical:: surface_elements_added
281 ! listen very carefully, I shall say this only once:
282 logical, save :: warning_given=.false.
283 integer, dimension(:), pointer :: faces, neigh, snodes
284 integer, dimension(2) :: common_elements
285- integer :: nloc, snloc, stotel
286- integer :: bdry_count, ele, sele, j, no_found
287+ integer :: snloc, stotel
288+ integer :: bdry_count, ele, sele, sele2, neighbour_ele, j, no_found
289 integer :: no_faces
290 type(csr_sparsity) :: sparsity
291 type(csr_sparsity) :: nelist
292@@ -1398,7 +1406,6 @@
293 assert(continuity(mesh)>=0)
294
295 mesh_shape=>ele_shape(mesh, 1)
296- nloc=mesh_shape%loc
297
298 ! Calculate the node-to-element list.
299 ! Calculate the element adjacency list.
300@@ -1415,12 +1422,16 @@
301 trim(mesh%name)//" face_element_list")
302 #endif
303
304- mesh%faces%has_internal_boundaries = present(element_owner)
305+ mesh%faces%has_discontinuous_internal_boundaries = present(element_owner)
306+
307+ call allocate(internal_facet_map)
308
309 snloc=face_vertices(mesh_shape)
310 if (present(sndgln)) then
311
312- stotel=size(sndgln)/snloc
313+ stotel=size(sndgln)/snloc ! number of provided surface elements
314+ ! we might add some more when duplicating internal facets
315+ bdry_count=stotel
316
317 do sele=1, stotel
318
319@@ -1432,63 +1443,67 @@
320 if (no_found==1) then
321 ! we have found the adjacent element
322 ele=common_elements(1)
323- internal_face=.false.
324 if (present(element_owner)) then
325- assert(element_owner(sele)==ele)
326+ if (element_owner(sele)/=ele) then
327+ ewrite(0,*) "Surface element: ", sele
328+ ewrite(0,*) "Provided element owner: ", element_owner(sele)
329+ ewrite(0,*) "Found adjacent element: ", ele
330+ FLExit("Provided element ownership information is incorrect")
331+ end if
332 end if
333+ call register_external_surface_element(mesh, sele, ele, snodes)
334 else if (no_found==2 .and. present(element_owner)) then
335- ele=element_owner(sele)
336- if (all(common_elements/=ele)) then
337- FLAbort("Face not adjacent to specified element_owner")
338- end if
339- internal_face=.true.
340- else
341- FLAbort("Surface element in sndgln is not on the surface.")
342- end if
343-
344- mesh%faces%face_element_list(sele)=ele
345-
346- ! now we have to fill in face_list:
347- neigh=>row_m_ptr(mesh%faces%face_list, ele)
348- faces=>row_ival_ptr(mesh%faces%face_list, ele)
349-
350- ! find the matching boundary of this element
351- do j=1, mesh%shape%numbering%boundaries
352- if (neigh(j)<=0 .or. internal_face) then
353- if (SetContains(snodes, mesh%ndglno( (ele-1)*nloc+ &
354- boundary_numbering(mesh%shape%numbering, j) &
355- ))) exit
356- end if
357- end do
358-
359- if (j>mesh%shape%numbering%boundaries) then
360- ! not found a matching boundary, something's wrong
361- FLAbort("Something wrong with the mesh, sndgln, or mesh%nelist")
362-
363- else if (neigh(j)/=0 .and. .not. internal_face) then
364- ! this surface element is already registered
365- ! so apparently there's a duplicate element in the surface mesh
366- ewrite(0,*) 'Surface element:', faces(j),' and ',sele
367- ewrite(0,*) 'Both define the surface element:', snodes
368- FLAbort("Duplicate element in the surface mesh")
369- end if
370-
371- ! register the surface element in face_list
372- faces(j)=sele
373- if (.not. internal_face) then
374- neigh(j)=-j ! negative number indicates exterior boundary
375- else
376- ! if all went well neigh(j) should have the right value:
377- assert( neigh(j)==minval(common_elements, mask=common_elements/=ele) )
378+ ! internal facet with element ownership infomation provided
379+ ! so we assume both of the coinciding internal facets are
380+ ! present in the provided surface mesh and register only
381+ ! one of them here
382+ ele = element_owner(sele)
383+ if (ele==common_elements(1)) then
384+ neighbour_ele = common_elements(2)
385+ else if (ele==common_elements(2)) then
386+ neighbour_ele = common_elements(1)
387+ else
388+ ewrite(0,*) "Surface element: ", sele
389+ ewrite(0,*) "Provided element owner: ", ele
390+ ewrite(0,*) "Found adjacent elements: ", common_elements
391+ FLExit("Provided element owner ship information is incorrect")
392+ end if
393+ call register_internal_surface_element(mesh, sele, ele, neighbour_ele)
394+ else if (no_found==2) then
395+ ! internal facet but not element ownership information:
396+ ! we assume this facet only occurs once and we register both
397+ ! copies at once
398+
399+ ! first one using the current surface element number:
400+ call register_internal_surface_element(mesh, sele, common_elements(1), common_elements(2))
401+
402+ ! for the second one we create a new facet number at the end of the provided number surface
403+ ! elements:
404+ bdry_count = bdry_count+1
405+ call register_internal_surface_element(mesh, bdry_count, common_elements(2), common_elements(1))
406+ ! store this pair so we can later copy the boundary id of the first (sele) to the second one (bdry_count)
407+ call insert(internal_facet_map, sele, bdry_count)
408+
409+ else if (no_found==0) then
410+ ewrite(0,*) "Current surface element: ", sele
411+ ewrite(0,*) "With nodes: ", snodes
412+ FLExit("Surface element does not exist in the mesh")
413+ else
414+ ! no_found>2 apparently
415+ ! this might happen when calling add_faces on meshes with non-trivial toplogy such
416+ ! as calling add_faces on the surface_mesh - we can't really deal with that
417+ ewrite(0,*) "Current surface element: ", sele
418+ ewrite(0,*) "With nodes: ", snodes
419+ FLExit("Surface element (facet) adjacent to more than two elements!")
420 end if
421
422 end do
423
424- bdry_count=stotel
425
426 else
427
428- bdry_count=0
429+ stotel=0 ! number of facets provided in sndgln
430+ bdry_count=0 ! number of facets including the doubling of interior facets
431
432 end if
433
434@@ -1517,12 +1532,22 @@
435 end do
436
437 end do
438- if (surface_elements_added .and. .not. warning_given) then
439+
440+ if (surface_elements_added .and. key_count(internal_facet_map)>0) then
441+ ewrite(0,*) "It appears this mesh has internal boundaries."
442+ ewrite(0,*) "In this case all external boundaries need to be marked with a surface id."
443+ FLExit("Incomplete surface mesh")
444+ else if (surface_elements_added .and. .not. warning_given) then
445 ewrite(0,*) "WARNING: an incomplete surface mesh has been provided."
446 ewrite(0,*) "This will not work in parallel."
447 ewrite(0,*) "All parts of the domain boundary need to be marked with a (physical) surface id."
448 warning_given=.true.
449 end if
450+
451+ if (surface_elements_added) then
452+ stotel = bdry_count
453+ end if
454+
455 end if
456
457 ! the size of this array will be the way to store the n/o
458@@ -1533,15 +1558,24 @@
459 trim(mesh%name)//" boundary_ids")
460 #endif
461
462+ mesh%faces%unique_surface_element_count = stotel
463+ ewrite(2,*) "Number of surface elements: ", bdry_count
464+ ewrite(2,*) "Number of unique surface elements: ", stotel
465+
466 mesh%faces%boundary_ids=0
467 ! copy in supplied boundary ids
468 if (present(boundary_ids)) then
469 if (.not. present(sndgln)) then
470 FLAbort("Boundary ids can only be supplied to add_faces with associated surface mesh")
471- else if (stotel/=size(boundary_ids)) then
472+ else if (size(boundary_ids) /= size(sndgln)/snloc) then
473 FLAbort("Must supply boundary_ids array for the same number of elements as the surface mesh sndgln")
474 end if
475- mesh%faces%boundary_ids(1:stotel)=boundary_ids
476+ mesh%faces%boundary_ids(1:size(boundary_ids))=boundary_ids
477+
478+ do j=1, key_count(internal_facet_map)
479+ call fetch_pair(internal_facet_map, j, sele, sele2)
480+ mesh%faces%boundary_ids(sele2) = boundary_ids(sele)
481+ end do
482 end if
483
484 ! register the rest of the boundaries (the interior ones):
485@@ -1572,9 +1606,86 @@
486 assert(bdry_count==size(mesh%faces%face_list%sparsity%colm))
487 assert(.not.any(mesh%faces%face_list%sparsity%colm==0))
488 assert(.not.any(mesh%faces%face_list%ival==0))
489+
490+ call deallocate(internal_facet_map)
491
492 end subroutine add_faces_face_list
493+
494+ subroutine register_internal_surface_element(mesh, sele, ele, neighbour_ele)
495+ type(mesh_type), intent(inout):: mesh
496+ integer, intent(in):: sele, ele, neighbour_ele
497+
498+ integer, dimension(:), pointer:: neigh, faces
499+ integer:: j
500+
501+ mesh%faces%face_element_list(sele)=ele
502+
503+ ! neigh should contain correct neighbours already for internal facets:
504+ neigh=>row_m_ptr(mesh%faces%face_list, ele)
505+ faces=>row_ival_ptr(mesh%faces%face_list, ele)
506+
507+ ! find the corresponding boundary of ele
508+ ! by searching for neighbour_ele in neigh
509+ do j=1, mesh%shape%numbering%boundaries
510+ if (neigh(j)==neighbour_ele) exit
511+ end do
512+
513+ if (j>mesh%shape%numbering%boundaries) then
514+ ! not found a matching boundary, something's wrong
515+ FLAbort("Something wrong with the mesh, sndgln, or mesh%nelist")
516+ end if
517+
518+ ! register the surface element in face_list
519+ faces(j)=sele
520+
521+ end subroutine register_internal_surface_element
522+
523+ subroutine register_external_surface_element(mesh, sele, ele, snodes)
524+ type(mesh_type), intent(inout):: mesh
525+ integer, intent(in):: sele, ele
526+ integer, dimension(:), intent(in):: snodes
527+
528+ integer, dimension(:), pointer:: neigh, faces, nodes
529+ integer:: j, nloc
530+
531+ nloc = ele_loc(mesh, ele)
532
533+ mesh%faces%face_element_list(sele)=ele
534+
535+ ! for external facets the corresponding entry in neigh
536+ ! is still zero, a negative value will be filled in
537+ ! when it's registered
538+ neigh=>row_m_ptr(mesh%faces%face_list, ele)
539+ faces=>row_ival_ptr(mesh%faces%face_list, ele)
540+ nodes => ele_nodes(mesh, ele)
541+
542+ ! find the matching boundary of ele
543+ do j=1, mesh%shape%numbering%boundaries
544+ ! also check negative entries to check for duplicate registrations
545+ if (neigh(j)<=0) then
546+ if (SetContains(snodes, nodes(boundary_numbering(mesh%shape%numbering, j)))) exit
547+ end if
548+ end do
549+
550+ if (j>mesh%shape%numbering%boundaries) then
551+ ! not found a matching boundary, something's wrong
552+ FLAbort("Something wrong with the mesh, sndgln, or mesh%nelist")
553+ end if
554+
555+ if (neigh(j)/=0) then
556+ ! this surface element is already registered
557+ ! so apparently there's a duplicate element in the surface mesh
558+ ewrite(0,*) 'Surface element:', faces(j),' and ',sele
559+ ewrite(0,*) 'Both define the surface element:', snodes
560+ FLAbort("Duplicate element in the surface mesh")
561+ end if
562+
563+ ! register the surface element in face_list
564+ faces(j)=sele
565+ neigh(j)=-j ! negative number indicates exterior boundary
566+
567+ end subroutine register_external_surface_element
568+
569 subroutine add_faces_face_list_periodic_from_non_periodic_model( &
570 mesh, model, periodic_face_map)
571 ! computes the face_list of a periodic mesh by copying it from
572
573=== modified file 'femtools/Fields_Base.F90'
574--- femtools/Fields_Base.F90 2013-07-31 13:45:29 +0000
575+++ femtools/Fields_Base.F90 2013-10-17 12:55:48 +0000
576@@ -223,6 +223,10 @@
577 & surface_element_count_tensor, surface_element_count_mesh
578 end interface
579
580+ interface unique_surface_element_count
581+ module procedure unique_surface_element_count_mesh
582+ end interface
583+
584 interface surface_element_id
585 module procedure surface_element_id_scalar, surface_element_id_vector, &
586 surface_element_id_mesh
587@@ -262,9 +266,9 @@
588 & mesh_periodic_tensor
589 end interface
590
591- interface has_internal_boundaries
592- module procedure mesh_has_internal_boundaries
593- end interface has_internal_boundaries
594+ interface has_discontinuous_internal_boundaries
595+ module procedure mesh_has_discontinuous_internal_boundaries
596+ end interface has_discontinuous_internal_boundaries
597
598 interface extract_scalar_field ! extract_scalar_field is already used in State.F90
599 module procedure extract_scalar_field_from_vector_field, extract_scalar_field_from_tensor_field
600@@ -412,18 +416,21 @@
601
602 end function mesh_periodic_tensor
603
604- pure function mesh_has_internal_boundaries(mesh)
605- !!< Return whether the mesh has internal boundaries
606- logical :: mesh_has_internal_boundaries
607+ pure function mesh_has_discontinuous_internal_boundaries(mesh)
608+ !!< Return whether the mesh has discontinuous boundaries
609+ !!< These are internal boundaries where the surface id are
610+ !!< allowed to be discontinuous (the pair of adjacent
611+ !!< internal facets can have two different ids).
612+ logical :: mesh_has_discontinuous_internal_boundaries
613 type(mesh_type), intent(in) :: mesh
614
615 if (associated(mesh%faces)) then
616- mesh_has_internal_boundaries = mesh%faces%has_internal_boundaries
617+ mesh_has_discontinuous_internal_boundaries = mesh%faces%has_discontinuous_internal_boundaries
618 else
619- mesh_has_internal_boundaries = .false.
620+ mesh_has_discontinuous_internal_boundaries = .false.
621 end if
622
623- end function mesh_has_internal_boundaries
624+ end function mesh_has_discontinuous_internal_boundaries
625
626 pure function node_count_mesh(mesh) result (node_count)
627 ! Return the number of nodes in a mesh.
628@@ -575,6 +582,21 @@
629
630 end function surface_element_count_mesh
631
632+ pure function unique_surface_element_count_mesh(mesh) result (element_count)
633+ ! Return the number of unique surface elements of a mesh. For internal
634+ ! facets that are part of the surface mesh, each pair of adjacent facets
635+ ! is only counted once.
636+ integer :: element_count
637+ type(mesh_type),intent(in) :: mesh
638+
639+ if (associated(mesh%faces)) then
640+ element_count=mesh%faces%unique_surface_element_count
641+ else
642+ element_count=0
643+ end if
644+
645+ end function unique_surface_element_count_mesh
646+
647 pure function face_count_scalar(field) result (face_count)
648 ! Return the number of faces in a mesh.
649 integer :: face_count
650
651=== modified file 'femtools/Fields_Data_Types.F90'
652--- femtools/Fields_Data_Types.F90 2011-10-06 15:16:29 +0000
653+++ femtools/Fields_Data_Types.F90 2013-10-17 12:55:48 +0000
654@@ -120,9 +120,27 @@
655 integer, dimension(:), pointer :: coplanar_ids => null()
656 !! a DG version of the surface mesh, useful for storing bc values
657 type(mesh_type), pointer:: dg_surface_mesh => null()
658- !! A logical indicating if this mesh has internal boundaries
659- !! This means that element owners need to be written when writing out this mesh
660- logical :: has_internal_boundaries=.false.
661+ !! A logical indicating if this mesh has a discontinuous internal boundary
662+ !! This means that the pairs of internal facets are allowed to have two different
663+ !! surface ids. When writing out this mesh both facets are written out and
664+ !! element owners (an extra column indiciating which element is adjacent to each facet)
665+ !! needs to be written out along with the surface mesh.
666+ !! This is currently only used for periodic meshes which have a physical and aliased surface id
667+ !! along the periodic boundary (which is an internal boundary of the periodic mesh).
668+ !! Note that other meshes (with has_internal_boundaries==.false.) may still have internal facets
669+ !! as part of the surface mesh, in this case the surface ids do have to agree and only one of each
670+ !! pair of facets is written when writing out the mesh.
671+ logical :: has_discontinuous_internal_boundaries=.false.
672+ !! If internal facets are present in the surface mesh (and has_discontinuous_internal_boundaries==.false.)
673+ !! the surface facets are numbered such that 1:unique_surface_element_count visits each external facet
674+ !! and each pair of internal facets only once (the order of this is typically determined by the
675+ !! read-in input mesh in which internal facets are only also only present once)
676+ !! The second facets of each pair of internal facets are numbered
677+ !! unique_surface_element_count+1:surface_element_count (surface_element_count()==size(boundary_ids))
678+ !! For meshes with no internal facets: unique_surface_element_count==surface_element_count()
679+ !! For meshes with has_discontinuous_internal_boundaries no order is guaranteed and also
680+ !! unique_surface_element_count==surface_element_count()
681+ integer :: unique_surface_element_count
682 end type mesh_faces
683
684 type mesh_subdomain_mesh
685
686=== modified file 'femtools/Surface_Labels.F90'
687--- femtools/Surface_Labels.F90 2010-11-16 15:37:38 +0000
688+++ femtools/Surface_Labels.F90 2013-10-17 12:55:48 +0000
689@@ -282,74 +282,73 @@
690 type(vector_field), intent(in):: positions
691 integer, dimension(:), pointer:: coplanar_ids
692 type(mesh_type), pointer:: surface_mesh
693- type(csr_sparsity), pointer :: eelist
694 type(ilist) front
695- real, allocatable, dimension(:,:):: normals, normalgi
696+ real, allocatable, dimension(:,:):: normalgi, normals
697 real, allocatable, dimension(:):: detwei_f
698- integer, allocatable, dimension(:):: face_nodes
699 real coplanar
700- integer, dimension(:), pointer:: neigh
701+ integer, dimension(:), pointer:: neigh, nodes
702 integer current_id, sngi, stotel
703- integer j, k, sele, pos, ele
704+ integer j, k, sele, sele2, pos, ele
705
706+ ewrite(1,*) "Inside get_coplanar_ids"
707+
708 if (.not. has_faces(mesh)) then
709 call add_faces(mesh)
710 end if
711
712 stotel = surface_element_count(mesh)
713+
714+ if (.not. associated(mesh%faces%coplanar_ids)) then
715+ allocate(mesh%faces%coplanar_ids(1:stotel))
716+ coplanar_ids => mesh%faces%coplanar_ids
717+ else
718+ ! we assume they have been calculated already:
719+ coplanar_ids => mesh%faces%coplanar_ids
720+ return
721+ end if
722+
723 if(stotel == 0) then
724 sngi = 0
725 else
726 sngi = face_ngi(mesh, 1)
727 end if
728 surface_mesh => mesh%faces%surface_mesh
729-
730- if (.not. associated(mesh%faces%coplanar_ids)) then
731- allocate(mesh%faces%coplanar_ids(1:stotel))
732- coplanar_ids => mesh%faces%coplanar_ids
733- else
734- ! we assume they have been calculated already:
735- coplanar_ids => mesh%faces%coplanar_ids
736- return
737- end if
738- coplanar_ids => mesh%faces%coplanar_ids
739- allocate( normalgi(positions%dim,sngi), &
740- detwei_f(sngi), face_nodes(1:face_loc(mesh,1)) )
741+
742+ allocate(normalgi(positions%dim,sngi), detwei_f(sngi))
743
744 ! Calculate element normals for all surface elements
745 allocate(normals(positions%dim, stotel))
746 do sele=1, stotel
747 ele=face_ele(mesh, sele)
748- ! we don't want to use face_val on positions
749- ! as it may not have a faces object (as opposed to the mesh)
750- face_nodes=face_global_nodes(mesh, sele)
751 call transform_facet_to_physical( &
752 positions, sele, detwei_f, normalgi)
753 ! average over gauss points:
754 normals(:,sele)=matmul(normalgi, detwei_f)/sum(detwei_f)
755 end do
756- deallocate(normalgi, detwei_f, face_nodes)
757+ deallocate(normalgi, detwei_f)
758
759- ! create element-element list for surface mesh
760- eelist => extract_eelist(surface_mesh)
761+ ! create node-element list for surface mesh
762+ ! (Note that we can't always construct an eelist, which would have been
763+ ! more useful, because the surface mesh may split (for instance where an
764+ ! external boundary meets an internal boundary) in which case multiple
765+ ! surface elements can be connected via the same edge (facet of the surface element))
766+ call add_nelist(surface_mesh)
767
768 coplanar_ids = 0
769 current_id = 1
770 pos = 1
771 do while (.true.)
772- ! Create a new starting point
773+ ! Create a new starting point by finding a surface element without coplanar id
774 do sele=pos, stotel
775- if(coplanar_ids(sele)==0) then
776- ! This is the first element in the new patch
777- pos = sele
778- coplanar_ids(pos) = current_id
779- exit
780- end if
781+ if(coplanar_ids(sele)==0) exit
782 end do
783
784 ! Jump out of this while loop if we are finished
785 if (sele>stotel) exit
786
787+ ! This is the first element in the new patch
788+ pos = sele
789+ coplanar_ids(pos) = current_id
790 ! Initialise the front
791 call insert_ascending(front, pos)
792
793@@ -358,19 +357,25 @@
794 sele = pop(front)
795
796 ! surrounding surface elements:
797- neigh => row_m_ptr(eelist, sele)
798- do j=1, size(neigh)
799- k = neigh(j)
800- if (k>0) then
801- if(coplanar_ids(k)==0) then
802- coplanar = dot_product(normals(:,pos), normals(:,k))
803+ ! note that we not only consider directly adjacent surface elements,
804+ ! but also surface elements that only connect via one other node, as
805+ ! long as they have a normal in the same direction however they should
806+ ! be on the same plane
807+ nodes => ele_nodes(surface_mesh, sele)
808+ do j=1, size(nodes)
809+ ! loop over surface elements connected to nodes(j)
810+ neigh => node_neigh(surface_mesh, nodes(j))
811+ do k=1, size(neigh)
812+ sele2 = neigh(k)
813+ if(coplanar_ids(sele2)==0) then
814+ coplanar = abs(dot_product(normals(:,pos), normals(:,sele2)))
815 if(coplanar>=COPLANAR_MAGIC_NUMBER) then
816
817- call insert_ascending(front, k)
818- coplanar_ids(k) = current_id
819+ call insert_ascending(front, sele2)
820+ coplanar_ids(sele2) = current_id
821 end if
822 end if
823- end if
824+ end do
825 end do
826 end do
827
828@@ -379,6 +384,8 @@
829 end do
830 deallocate(normals)
831
832+ ewrite(2,*) "Before merge_surface_ids, n/o local coplanes:", current_id-1
833+
834 call merge_surface_ids(mesh, coplanar_ids, max_id = current_id - 1)
835
836 end subroutine get_coplanar_ids
837
838=== modified file 'femtools/Write_GMSH.F90'
839--- femtools/Write_GMSH.F90 2011-02-09 19:08:48 +0000
840+++ femtools/Write_GMSH.F90 2013-10-17 12:55:48 +0000
841@@ -258,12 +258,12 @@
842 integer :: e, f, elemID
843 character, parameter :: newLineChar=char(10)
844
845- logical :: internal_boundaries
846+ logical :: needs_element_owners
847
848 ! Gather some info about the mesh
849 numElements = ele_count(mesh)
850- numFaces = surface_element_count(mesh)
851- internal_boundaries = has_internal_boundaries(mesh)
852+ numFaces = unique_surface_element_count(mesh)
853+ needs_element_owners = has_discontinuous_internal_boundaries(mesh)
854
855 ! In the GMSH format, faces are also elements.
856 numGMSHElems = numElements + numFaces
857@@ -320,7 +320,7 @@
858 ! Faces written out first
859
860 ! Number of tags associated with elements
861- if(internal_boundaries) then
862+ if(needs_element_owners) then
863 ! write surface id and element owner
864 numTags = 4
865 else
866
867=== modified file 'femtools/Write_Triangle.F90'
868--- femtools/Write_Triangle.F90 2011-02-09 19:08:48 +0000
869+++ femtools/Write_Triangle.F90 2013-10-17 12:55:48 +0000
870@@ -233,18 +233,17 @@
871 type(mesh_type), intent(in):: mesh
872
873 integer unit, dim, nofaces, i
874- integer :: stotel, dg_total ! dg_total counts each internal face twice
875+ integer :: dg_total ! dg_total counts each internal face twice
876 integer :: ele, neigh, j, face
877 integer, dimension(:), pointer :: neighbours
878
879 unit=free_unit()
880
881 dim=mesh_dim(mesh)
882- stotel=surface_element_count(mesh)
883 dg_total=size(mesh%faces%face_list%sparsity%colm)
884
885- nofaces = (dg_total - stotel) / 2 ! internal faces, only once
886- nofaces = nofaces + stotel ! and the surface mesh
887+ nofaces = (dg_total - surface_element_count(mesh)) / 2 ! internal faces, only once
888+ nofaces = nofaces + unique_surface_element_count(mesh) ! and the surface mesh (again counting internal facets only once)
889
890 select case(dim)
891 case(3)
892@@ -301,7 +300,7 @@
893 unit=free_unit()
894
895 dim=mesh_dim(mesh)
896- nofaces=surface_element_count(mesh)
897+ nofaces=unique_surface_element_count(mesh)
898
899 select case(dim)
900 case(3)
901@@ -315,7 +314,7 @@
902 FLAbort("Invalid dimension")
903 end select
904
905- if (has_internal_boundaries(mesh)) then
906+ if (has_discontinuous_internal_boundaries(mesh)) then
907 ! If the mesh is periodic, we want to write out the parent element of every face
908 nolabels = 2
909 else
910@@ -325,7 +324,7 @@
911 ! header line: nofaces, and number of boundary markers
912 write(unit, *, err=42) nofaces, nolabels
913
914- if (.not. has_internal_boundaries(mesh)) then
915+ if (.not. has_discontinuous_internal_boundaries(mesh)) then
916 do i=1, nofaces
917 write(unit, *, err=42) i, face_global_nodes(mesh, i), &
918 surface_element_id(mesh, i)
919
920=== modified file 'manual/configuring_fluidity.tex'
921--- manual/configuring_fluidity.tex 2013-10-11 10:48:07 +0000
922+++ manual/configuring_fluidity.tex 2013-10-17 12:55:48 +0000
923@@ -1666,6 +1666,27 @@
924 imposes a weak prescribed normal flow boundary condition on the surfaces specified.
925
926
927+\subsection{Internal boundary conditions}\label{sec:internal_bcs}
928+\index{boundary conditions!internal boundaries}
929+Fluidity has some support (with limitations) for applying boundary conditions
930+along internal boundaries. This is done in the normal way
931+by applying physical line/surface ids to the internal boundary, and associating
932+boundary conditions with these in the options file. It should be
933+noted that this functionality is not as well tested as other boundary
934+conditions, so you should always first try it out on a simplified version of
935+your problem to see if it behaves as expected. Strong Dirichlet boundary
936+conditions should work correctly, other boundary condition types may not give
937+the right answer. Since the gmsh .msh format does not give you the
938+option of setting a different surface id on either side of the internal
939+boundary, it is not possible to apply a different boundary condition type or
940+value on either side.
941+
942+When using mesh adaptivity, it will maintain the internal boundary and its
943+surface id. Mesh adaptivity in three dimensions with internal boundaries
944+is currently not supported. For parallel runs you have to use flredecomp (see
945+section \ref{mesh!meshing tools!flredecomp}) to
946+decompose the problem, as fldecomp will refuse any mesh with internal boundaries.
947+
948 \subsection{Special input date for boundary conditions}\label{sec:BCs:specialised}
949
950 When running free surface simulations the surface elevation at the boundary is specified by applying a pressure Dirichlet condition. Since the free surface elevation is often measured data, there are some special possibilities to specify a pressure Dirichlet condition:
951
952=== modified file 'preprocessor/Populate_Sub_State.F90'
953--- preprocessor/Populate_Sub_State.F90 2011-05-05 17:31:42 +0000
954+++ preprocessor/Populate_Sub_State.F90 2013-10-17 12:55:48 +0000
955@@ -67,7 +67,7 @@
956
957 public populate_sub_state, set_full_domain_prescribed_fields, &
958 & sub_state_remap_to_full_mesh, update_subdomain_fields, &
959- & use_sub_state
960+ & use_sub_state, populate_sub_state_module_check_options
961
962 contains
963
964@@ -205,6 +205,9 @@
965 deallocate(prescribed_region_ids)
966 end do
967
968+ ! failing this may be caused by not preserving region ids in adaptivity - see options check below
969+ assert(associated(external_mesh%region_ids))
970+
971 ! Derive subdomain_mesh_element list (an integer set):
972 call allocate(subdomain_mesh_element_list)
973 do ele = 1, element_count(external_mesh)
974@@ -640,4 +643,19 @@
975
976 end subroutine sub_state_remap_to_full_mesh
977
978+ subroutine populate_sub_state_module_check_options
979+
980+ if (option_count('/material_phase/vector_field::Velocity/prognostic/prescribed_region')>0) then
981+
982+ if (have_option('/mesh_adaptivity/hr_adaptivity') .and. &
983+ .not. have_option('/mesh_adaptivity/hr_adaptivity/preserve_mesh_regions')) then
984+
985+ ewrite(0,*) "When using prescribed regions with mesh adaptivity:"
986+ FLExit("Need /mesh_adaptivity/hr_adaptivity/preserve_mesh_regions option")
987+
988+ end if
989+
990+ end if
991+ end subroutine populate_sub_state_module_check_options
992+
993 end module populate_sub_state_module
994
995=== modified file 'tests/Stokes_Subduction_VK_Case_1b/Makefile'
996--- tests/Stokes_Subduction_VK_Case_1b/Makefile 2011-10-21 10:05:25 +0000
997+++ tests/Stokes_Subduction_VK_Case_1b/Makefile 2013-10-17 12:55:48 +0000
998@@ -1,6 +1,5 @@
999 input: clean
1000 cp src/Subduction_Mesh.msh ./
1001- ../../bin/gmsh2triangle --2d -i Subduction_Mesh.msh
1002
1003 clean:
1004 rm -f *.ele *.edge *.node *.vtu *.stat *.msh *.detectors *.dat fluidity.* *_state matrixdump*
1005
1006=== modified file 'tests/Stokes_Subduction_VK_Case_1b/Stokes-Subduction-VK-Case-1b.flml'
1007--- tests/Stokes_Subduction_VK_Case_1b/Stokes-Subduction-VK-Case-1b.flml 2013-01-06 19:51:01 +0000
1008+++ tests/Stokes_Subduction_VK_Case_1b/Stokes-Subduction-VK-Case-1b.flml 2013-10-17 12:55:48 +0000
1009@@ -12,7 +12,7 @@
1010 </dimension>
1011 <mesh name="CoordinateMesh">
1012 <from_file file_name="Subduction_Mesh">
1013- <format name="triangle"/>
1014+ <format name="gmsh"/>
1015 <stat>
1016 <include_in_stat/>
1017 </stat>
1018
1019=== modified file 'tests/flredecomp_2d_fieldweighted/Makefile'
1020--- tests/flredecomp_2d_fieldweighted/Makefile 2012-09-10 14:14:35 +0000
1021+++ tests/flredecomp_2d_fieldweighted/Makefile 2013-10-17 12:55:48 +0000
1022@@ -3,9 +3,8 @@
1023 default: input
1024
1025 input: clean
1026- gmsh -2 -optimize src/Subduction_Mesh.geo
1027- cp src/Subduction_Mesh.msh .
1028- ../../bin/gmsh2triangle --2d -i Subduction_Mesh.msh
1029+ gmsh -2 -optimize src/Subduction_Mesh.geo -o Subduction_Mesh.msh
1030+ ../../bin/gmsh2triangle --2d Subduction_Mesh.msh
1031
1032 clean:
1033 rm -f *.ele *.edge *.node *.vtu *.stat *.msh *.detectors fluidity.* Parallel*
1034
1035=== modified file 'tests/flredecomp_2d_fieldweighted/flredecomp-2d-fieldweighted.flml'
1036--- tests/flredecomp_2d_fieldweighted/flredecomp-2d-fieldweighted.flml 2012-10-17 15:59:53 +0000
1037+++ tests/flredecomp_2d_fieldweighted/flredecomp-2d-fieldweighted.flml 2013-10-17 12:55:48 +0000
1038@@ -2,7 +2,7 @@
1039 <fluidity_options>
1040 <simulation_name>
1041 <string_value lines="1">flredecomp_field_weighted_partition_test</string_value>
1042- <comment>Checks for field_weighted_partitions in flredecomp and gmsh2triangle -i.</comment>
1043+ <comment>Checks for field_weighted_partitions in flredecomp</comment>
1044 </simulation_name>
1045 <problem_type>
1046 <string_value lines="1">stokes</string_value>
1047
1048=== added directory 'tests/internal_boundary_adaptivity'
1049=== added file 'tests/internal_boundary_adaptivity/Makefile'
1050--- tests/internal_boundary_adaptivity/Makefile 1970-01-01 00:00:00 +0000
1051+++ tests/internal_boundary_adaptivity/Makefile 2013-10-17 12:55:48 +0000
1052@@ -0,0 +1,6 @@
1053+input: clean
1054+ gmsh -2 src/square.geo -o square.msh
1055+
1056+clean:
1057+ rm -rf *.msh *.stat *.vtu *.log-0 *.err-0 *checkpoint *.convergence *.log *.node *.edge *.ele *.halo *.pvtu viscous_fs_zhong_B_* viscous_fs_zhong_A_* fluidity.* *.pyc
1058+ rm -rf *checkpoint* matrixdump*
1059
1060=== added file 'tests/internal_boundary_adaptivity/internal_boundary.flml'
1061--- tests/internal_boundary_adaptivity/internal_boundary.flml 1970-01-01 00:00:00 +0000
1062+++ tests/internal_boundary_adaptivity/internal_boundary.flml 2013-10-17 12:55:48 +0000
1063@@ -0,0 +1,391 @@
1064+<?xml version='1.0' encoding='utf-8'?>
1065+<fluidity_options>
1066+ <simulation_name>
1067+ <string_value lines="1">ib</string_value>
1068+ </simulation_name>
1069+ <problem_type>
1070+ <string_value lines="1">fluids</string_value>
1071+ </problem_type>
1072+ <geometry>
1073+ <dimension>
1074+ <integer_value rank="0">2</integer_value>
1075+ </dimension>
1076+ <mesh name="CoordinateMesh">
1077+ <from_file file_name="square">
1078+ <format name="gmsh"/>
1079+ <stat>
1080+ <include_in_stat/>
1081+ </stat>
1082+ </from_file>
1083+ </mesh>
1084+ <mesh name="DGMesh">
1085+ <from_mesh>
1086+ <mesh name="CoordinateMesh"/>
1087+ <mesh_continuity>
1088+ <string_value>discontinuous</string_value>
1089+ </mesh_continuity>
1090+ <stat>
1091+ <exclude_from_stat/>
1092+ </stat>
1093+ </from_mesh>
1094+ </mesh>
1095+ <quadrature>
1096+ <degree>
1097+ <integer_value rank="0">4</integer_value>
1098+ </degree>
1099+ </quadrature>
1100+ </geometry>
1101+ <io>
1102+ <dump_format>
1103+ <string_value>vtk</string_value>
1104+ </dump_format>
1105+ <dump_period>
1106+ <constant>
1107+ <real_value rank="0">1.0</real_value>
1108+ </constant>
1109+ </dump_period>
1110+ <output_mesh name="CoordinateMesh"/>
1111+ <checkpointing>
1112+ <checkpoint_period_in_dumps>
1113+ <integer_value rank="0">1000</integer_value>
1114+ </checkpoint_period_in_dumps>
1115+ <checkpoint_at_end/>
1116+ </checkpointing>
1117+ <stat/>
1118+ </io>
1119+ <timestepping>
1120+ <current_time>
1121+ <real_value rank="0">0.0</real_value>
1122+ </current_time>
1123+ <timestep>
1124+ <real_value rank="0">0.1</real_value>
1125+ </timestep>
1126+ <finish_time>
1127+ <real_value rank="0">0.5</real_value>
1128+ </finish_time>
1129+ </timestepping>
1130+ <material_phase name="Fluid">
1131+ <vector_field name="Velocity" rank="1">
1132+ <prognostic>
1133+ <mesh name="CoordinateMesh"/>
1134+ <equation name="Boussinesq"/>
1135+ <spatial_discretisation>
1136+ <continuous_galerkin>
1137+ <stabilisation>
1138+ <no_stabilisation/>
1139+ </stabilisation>
1140+ <mass_terms>
1141+ <lump_mass_matrix/>
1142+ </mass_terms>
1143+ <advection_terms/>
1144+ <stress_terms>
1145+ <tensor_form/>
1146+ </stress_terms>
1147+ </continuous_galerkin>
1148+ <conservative_advection>
1149+ <real_value rank="0">0.0</real_value>
1150+ </conservative_advection>
1151+ </spatial_discretisation>
1152+ <temporal_discretisation>
1153+ <theta>
1154+ <real_value rank="0">1.0</real_value>
1155+ </theta>
1156+ <relaxation>
1157+ <real_value rank="0">1.0</real_value>
1158+ </relaxation>
1159+ </temporal_discretisation>
1160+ <solver>
1161+ <iterative_method name="gmres">
1162+ <restart>
1163+ <integer_value rank="0">30</integer_value>
1164+ </restart>
1165+ </iterative_method>
1166+ <preconditioner name="sor"/>
1167+ <relative_error>
1168+ <real_value rank="0">1e-7</real_value>
1169+ </relative_error>
1170+ <max_iterations>
1171+ <integer_value rank="0">200</integer_value>
1172+ </max_iterations>
1173+ <never_ignore_solver_failures/>
1174+ <diagnostics>
1175+ <monitors/>
1176+ </diagnostics>
1177+ </solver>
1178+ <initial_condition name="WholeMesh">
1179+ <constant>
1180+ <real_value shape="2" dim1="dim" rank="1">0.0 0.0</real_value>
1181+ </constant>
1182+ </initial_condition>
1183+ <prescribed_region name="Bottom">
1184+ <region_ids>
1185+ <integer_value shape="1" rank="1">2</integer_value>
1186+ </region_ids>
1187+ <constant>
1188+ <real_value shape="2" dim1="dim" rank="1">0.0 0.0</real_value>
1189+ </constant>
1190+ </prescribed_region>
1191+ <boundary_conditions name="TopLeft">
1192+ <surface_ids>
1193+ <integer_value shape="1" rank="1">9</integer_value>
1194+ </surface_ids>
1195+ <type name="dirichlet">
1196+ <align_bc_with_cartesian>
1197+ <x_component>
1198+ <constant>
1199+ <real_value rank="0">1.0</real_value>
1200+ </constant>
1201+ </x_component>
1202+ </align_bc_with_cartesian>
1203+ </type>
1204+ </boundary_conditions>
1205+ <boundary_conditions name="Top">
1206+ <surface_ids>
1207+ <integer_value shape="1" rank="1">8</integer_value>
1208+ </surface_ids>
1209+ <type name="no_normal_flow"/>
1210+ </boundary_conditions>
1211+ <output/>
1212+ <stat>
1213+ <include_in_stat/>
1214+ <previous_time_step>
1215+ <exclude_from_stat/>
1216+ </previous_time_step>
1217+ <nonlinear_field>
1218+ <exclude_from_stat/>
1219+ </nonlinear_field>
1220+ </stat>
1221+ <convergence>
1222+ <include_in_convergence/>
1223+ </convergence>
1224+ <detectors>
1225+ <include_in_detectors/>
1226+ </detectors>
1227+ <steady_state>
1228+ <include_in_steady_state/>
1229+ </steady_state>
1230+ <consistent_interpolation/>
1231+ </prognostic>
1232+ </vector_field>
1233+ <scalar_field name="Scalar" rank="0">
1234+ <prognostic>
1235+ <mesh name="DGMesh"/>
1236+ <equation name="AdvectionDiffusion"/>
1237+ <spatial_discretisation>
1238+ <discontinuous_galerkin>
1239+ <advection_scheme>
1240+ <upwind/>
1241+ <integrate_advection_by_parts>
1242+ <twice/>
1243+ </integrate_advection_by_parts>
1244+ </advection_scheme>
1245+ <diffusion_scheme>
1246+ <bassi_rebay/>
1247+ </diffusion_scheme>
1248+ </discontinuous_galerkin>
1249+ <conservative_advection>
1250+ <real_value rank="0">0.0</real_value>
1251+ </conservative_advection>
1252+ </spatial_discretisation>
1253+ <temporal_discretisation>
1254+ <theta>
1255+ <real_value rank="0">1.0</real_value>
1256+ </theta>
1257+ </temporal_discretisation>
1258+ <solver>
1259+ <iterative_method name="gmres">
1260+ <restart>
1261+ <integer_value rank="0">30</integer_value>
1262+ </restart>
1263+ </iterative_method>
1264+ <preconditioner name="sor"/>
1265+ <relative_error>
1266+ <real_value rank="0">1e-7</real_value>
1267+ </relative_error>
1268+ <max_iterations>
1269+ <integer_value rank="0">200</integer_value>
1270+ </max_iterations>
1271+ <never_ignore_solver_failures/>
1272+ <diagnostics>
1273+ <monitors/>
1274+ </diagnostics>
1275+ </solver>
1276+ <initial_condition name="WholeMesh">
1277+ <constant>
1278+ <real_value rank="0">0.0</real_value>
1279+ </constant>
1280+ </initial_condition>
1281+ <boundary_conditions name="Inflow">
1282+ <surface_ids>
1283+ <integer_value shape="1" rank="1">9</integer_value>
1284+ </surface_ids>
1285+ <type name="dirichlet">
1286+ <constant>
1287+ <real_value rank="0">0.0</real_value>
1288+ </constant>
1289+ </type>
1290+ </boundary_conditions>
1291+ <boundary_conditions name="Bottom">
1292+ <surface_ids>
1293+ <integer_value shape="1" rank="1">6</integer_value>
1294+ </surface_ids>
1295+ <type name="dirichlet">
1296+ <constant>
1297+ <real_value rank="0">0.0</real_value>
1298+ </constant>
1299+ </type>
1300+ </boundary_conditions>
1301+ <boundary_conditions name="InternalBoundary">
1302+ <surface_ids>
1303+ <integer_value shape="1" rank="1">10</integer_value>
1304+ </surface_ids>
1305+ <type name="dirichlet">
1306+ <constant>
1307+ <real_value rank="0">1.0</real_value>
1308+ </constant>
1309+ </type>
1310+ </boundary_conditions>
1311+ <tensor_field name="Diffusivity" rank="2">
1312+ <prescribed>
1313+ <value name="WholeMesh">
1314+ <isotropic>
1315+ <constant>
1316+ <real_value rank="0">0.1</real_value>
1317+ </constant>
1318+ </isotropic>
1319+ </value>
1320+ <output/>
1321+ </prescribed>
1322+ </tensor_field>
1323+ <output/>
1324+ <stat/>
1325+ <convergence>
1326+ <include_in_convergence/>
1327+ </convergence>
1328+ <detectors>
1329+ <include_in_detectors/>
1330+ </detectors>
1331+ <steady_state>
1332+ <include_in_steady_state/>
1333+ </steady_state>
1334+ <consistent_interpolation/>
1335+ </prognostic>
1336+ </scalar_field>
1337+ <scalar_field name="AnalyticalSolutionBottom" rank="0">
1338+ <prescribed>
1339+ <mesh name="DGMesh"/>
1340+ <value name="WholeMesh">
1341+ <python>
1342+ <string_value type="code" lines="20" language="python">def val(X,t):
1343+ return X[1]*2.0</string_value>
1344+ </python>
1345+ </value>
1346+ <output/>
1347+ <stat/>
1348+ <detectors>
1349+ <exclude_from_detectors/>
1350+ </detectors>
1351+ </prescribed>
1352+ </scalar_field>
1353+ <scalar_field name="BottomOnly" rank="0">
1354+ <prescribed>
1355+ <mesh name="DGMesh"/>
1356+ <value name="Top">
1357+ <region_ids>
1358+ <integer_value shape="1" rank="1">1</integer_value>
1359+ </region_ids>
1360+ <constant>
1361+ <real_value rank="0">0.0</real_value>
1362+ </constant>
1363+ </value>
1364+ <value name="Bottom">
1365+ <region_ids>
1366+ <integer_value shape="1" rank="1">2</integer_value>
1367+ </region_ids>
1368+ <constant>
1369+ <real_value rank="0">1.0</real_value>
1370+ </constant>
1371+ </value>
1372+ <output/>
1373+ <stat/>
1374+ <detectors>
1375+ <exclude_from_detectors/>
1376+ </detectors>
1377+ </prescribed>
1378+ </scalar_field>
1379+ <scalar_field name="Error" rank="0">
1380+ <diagnostic>
1381+ <algorithm name="scalar_python_diagnostic" material_phase_support="single">
1382+ <string_value type="code" lines="20" language="python">asb = state.scalar_fields['AnalyticalSolutionBottom']
1383+bo = state.scalar_fields['BottomOnly']
1384+s = state.scalar_fields['Scalar']
1385+field.val[:] = bo.val[:]*(asb.val[:]-s.val[:])</string_value>
1386+ <depends>
1387+ <string_value lines="1">AnalyticalSolutionBottom,BottomOnly</string_value>
1388+ </depends>
1389+ </algorithm>
1390+ <mesh name="DGMesh"/>
1391+ <output/>
1392+ <stat/>
1393+ <convergence>
1394+ <include_in_convergence/>
1395+ </convergence>
1396+ <detectors>
1397+ <include_in_detectors/>
1398+ </detectors>
1399+ <steady_state>
1400+ <include_in_steady_state/>
1401+ </steady_state>
1402+ </diagnostic>
1403+ </scalar_field>
1404+ </material_phase>
1405+ <mesh_adaptivity>
1406+ <mesh_movement>
1407+ <imposed_grid_velocity/>
1408+ <vector_field name="GridVelocity" rank="1">
1409+ <prescribed>
1410+ <mesh name="CoordinateMesh"/>
1411+ <value name="WholeMesh">
1412+ <python>
1413+ <string_value lines="20" type="code" language="python">def val(X,t):
1414+ from math import sin,cos,pi
1415+ v = 0.1*sin(2*pi*X[0])*sin(2*pi*t)*cos(2*pi*(X[1]-0.5))
1416+ return 0.0, v</string_value>
1417+ </python>
1418+ </value>
1419+ <output/>
1420+ <stat>
1421+ <include_in_stat/>
1422+ </stat>
1423+ <detectors>
1424+ <exclude_from_detectors/>
1425+ </detectors>
1426+ </prescribed>
1427+ </vector_field>
1428+ </mesh_movement>
1429+ <hr_adaptivity>
1430+ <period_in_timesteps>
1431+ <integer_value rank="0">3</integer_value>
1432+ </period_in_timesteps>
1433+ <maximum_number_of_nodes>
1434+ <integer_value rank="0">100000</integer_value>
1435+ </maximum_number_of_nodes>
1436+ <enable_gradation/>
1437+ <tensor_field name="MinimumEdgeLengths">
1438+ <anisotropic_symmetric>
1439+ <constant>
1440+ <real_value symmetric="true" dim2="dim" shape="2 2" dim1="dim" rank="2">0.1 0.0 0.0 0.1</real_value>
1441+ </constant>
1442+ </anisotropic_symmetric>
1443+ </tensor_field>
1444+ <tensor_field name="MaximumEdgeLengths">
1445+ <anisotropic_symmetric>
1446+ <constant>
1447+ <real_value symmetric="true" dim2="dim" shape="2 2" dim1="dim" rank="2">0.1 0.0 0.0 0.1</real_value>
1448+ </constant>
1449+ </anisotropic_symmetric>
1450+ </tensor_field>
1451+ <preserve_mesh_regions/>
1452+ </hr_adaptivity>
1453+ </mesh_adaptivity>
1454+</fluidity_options>
1455
1456=== added file 'tests/internal_boundary_adaptivity/internal_boundary_adaptivity.xml'
1457--- tests/internal_boundary_adaptivity/internal_boundary_adaptivity.xml 1970-01-01 00:00:00 +0000
1458+++ tests/internal_boundary_adaptivity/internal_boundary_adaptivity.xml 2013-10-17 12:55:48 +0000
1459@@ -0,0 +1,55 @@
1460+<?xml version='1.0' encoding='utf-8'?>
1461+<testproblem>
1462+ <name>interal_boundary_adaptivity<comment>Tests: internal boundaries+adaptivity+checkpointing</comment></name>
1463+ <owner userid="skramer"/>
1464+ <problem_definition length="short" nprocs="1">
1465+ <command_line>fluidity -v2 -l internal_boundary.flml &amp;&amp;
1466+spud-set ib_1_checkpoint.flml /timestepping/finish_time 0.999999 &amp;&amp;
1467+fluidity -v2 -l ib_1_checkpoint.flml</command_line>
1468+ </problem_definition>
1469+ <variables>
1470+ <variable name="solvers_converged" language="python">import os
1471+files = os.listdir("./")
1472+solvers_converged = not "matrixdump" in files and not "matrixdump.info" in files</variable>
1473+ <variable name="stats" language="python">from fluidity_tools import stat_parser
1474+s=stat_parser("ib.stat")
1475+stats={}
1476+stats["nodes_begin"]=s["CoordinateMesh"]["nodes"][0]
1477+stats["nodes_end"]=s["CoordinateMesh"]["nodes"][-1]
1478+stats["asbmin"]=s["Fluid"]["AnalyticalSolutionBottom"]["min"][-1]
1479+stats["asbmax"]=s["Fluid"]["AnalyticalSolutionBottom"]["max"][-1]
1480+stats["vell2_begin"]=s["Fluid"]["Velocity%magnitude"]["l2norm"][0]
1481+stats["vell2_end"]=s["Fluid"]["Velocity%magnitude"]["l2norm"][-1]
1482+stats["scalarl2_begin"]=s["Fluid"]["Scalar"]["l2norm"][0]
1483+stats["scalarl2_end"]=s["Fluid"]["Scalar"]["l2norm"][-1]</variable>
1484+ <variable name="stats_after_checkpoint" language="python">from fluidity_tools import stat_parser
1485+s=stat_parser("ib_checkpoint.stat")
1486+stats_after_checkpoint={}
1487+stats_after_checkpoint["nodes_begin"]=s["CoordinateMesh"]["nodes"][0]
1488+stats_after_checkpoint["nodes_end"]=s["CoordinateMesh"]["nodes"][-1]
1489+stats_after_checkpoint["asbmin"]=s["Fluid"]["AnalyticalSolutionBottom"]["min"][-1]
1490+stats_after_checkpoint["asbmax"]=s["Fluid"]["AnalyticalSolutionBottom"]["max"][-1]
1491+stats_after_checkpoint["vell2_begin"]=s["Fluid"]["Velocity%magnitude"]["l2norm"][0]
1492+stats_after_checkpoint["vell2_end"]=s["Fluid"]["Velocity%magnitude"]["l2norm"][-1]
1493+stats_after_checkpoint["scalarl2_begin"]=s["Fluid"]["Scalar"]["l2norm"][0]
1494+stats_after_checkpoint["scalarl2_end"]=s["Fluid"]["Scalar"]["l2norm"][-1]
1495+stats_after_checkpoint["error"]=s["Fluid"]["Error"]["l2norm"][-1]</variable>
1496+ </variables>
1497+ <pass_tests>
1498+ <test name="Solvers converged" language="python">assert(solvers_converged)</test>
1499+ <test name="NodesDecreaseInAdapt" language="python">assert stats['nodes_begin']&gt;stats['nodes_end']</test>
1500+ <test name="ScalarL2Increased" language="python">assert stats['scalarl2_begin']&lt;stats['scalarl2_end']</test>
1501+ <test name="VelocityL2Increased" language="python">assert stats['vell2_begin']&lt;stats['vell2_end']</test>
1502+ <test name="NodesDecreaseInAdapt" language="python">assert stats['nodes_begin']&gt;stats['nodes_end']</test>
1503+ <test name="MeshMovementMax" language="python">assert abs(stats['asbmax']-2.06)&lt;1e-3</test>
1504+ <test name="SameNumberOfNodes" language="python">assert stats["nodes_end"]==stats_after_checkpoint["nodes_begin"]</test>
1505+ <test name="NearlySameScalarL2" language="python">assert abs(stats["scalarl2_end"]-stats_after_checkpoint["scalarl2_begin"])&lt;0.03</test>
1506+ <test name="CloseVelocityL2" language="python">assert abs(stats["vell2_end"]-stats_after_checkpoint["vell2_begin"])&lt;0.1</test>
1507+ <test name="ScalarL2IncreasedAfter" language="python">assert stats_after_checkpoint['scalarl2_begin']&lt;stats_after_checkpoint['scalarl2_end']</test>
1508+ <test name="NodesConstantAfter" language="python">assert abs(stats_after_checkpoint['nodes_begin']-stats_after_checkpoint['nodes_end'])&lt;10</test>
1509+ <test name="MeshMovementMin" language="python">assert abs(stats['asbmin']+0.06)&lt;1e-3</test>
1510+ <test name="MeshMovedBackTop" language="python">assert abs(stats_after_checkpoint['asbmax']-2.00)&lt;3e-3</test>
1511+ <test name="MeshMovedBackBottom" language="python">assert abs(stats_after_checkpoint['asbmin'])&lt;3e-3</test>
1512+ <test name="SmallError" language="python">assert abs(stats_after_checkpoint['error'])&lt;0.02</test>
1513+ </pass_tests>
1514+</testproblem>
1515
1516=== added directory 'tests/internal_boundary_adaptivity/src'
1517=== added file 'tests/internal_boundary_adaptivity/src/square.geo'
1518--- tests/internal_boundary_adaptivity/src/square.geo 1970-01-01 00:00:00 +0000
1519+++ tests/internal_boundary_adaptivity/src/square.geo 2013-10-17 12:55:48 +0000
1520@@ -0,0 +1,33 @@
1521+l=20;
1522+p=1.0;
1523+Point(1) = {0, 0, 0};
1524+Extrude {1, 0, 0} {
1525+ Point{1};
1526+}
1527+Extrude {0, 0.5, 0} {
1528+ Line{1};
1529+}
1530+Transfinite Line{1} = l+1;
1531+Transfinite Line{2} = l+1;
1532+Transfinite Line{-3} = (l+2)/2 Using Progression p;
1533+Transfinite Line{-4} = (l+2)/2 Using Progression p;
1534+Transfinite Surface{5} = {1,2,3,4} Right;
1535+Extrude {0, 0.5, 0} {
1536+ Line{2};
1537+}
1538+Transfinite Line{6} = l+1;
1539+Transfinite Line{7} = (l+2)/2 Using Progression p;
1540+Transfinite Line{8} = (l+2)/2 Using Progression p;
1541+Transfinite Surface{9} = {3,4,5,6} Right;
1542+// Bottom
1543+Physical Line(6) = {1};
1544+Physical Line(7) = {4, 8};
1545+// Top
1546+Physical Line(8) = {6};
1547+// Left
1548+Physical Line(9) = {7}; // Top-Left
1549+Physical Line(11) = {3}; // Bottom-Left
1550+// Internal
1551+Physical Line(10) = {2};
1552+Physical Surface(1) = {9}; // Top
1553+Physical Surface(2) = {5}; // Bottom
1554
1555=== modified file 'tests/viscous_fs_zhong_spatial/Makefile'
1556--- tests/viscous_fs_zhong_spatial/Makefile 2013-09-17 15:06:47 +0000
1557+++ tests/viscous_fs_zhong_spatial/Makefile 2013-10-17 12:55:48 +0000
1558@@ -1,8 +1,13 @@
1559 input: clean
1560+<<<<<<< TREE
1561 gmsh -2 src/squareA.geo
1562 ../../bin/gmsh2triangle --2d -i src/squareA.msh
1563 gmsh -2 src/squareB.geo
1564 ../../bin/gmsh2triangle --2d -i src/squareB.msh
1565+=======
1566+ gmsh -2 src/squareA.geo -o squareA.msh
1567+ gmsh -2 src/squareB.geo -o squareB.msh
1568+>>>>>>> MERGE-SOURCE
1569
1570 clean:
1571- rm -rf src/*.msh *.stat *.vtu *.log-0 *.err-0 *checkpoint *.convergence *.log *.node *.edge *.ele *.halo *.pvtu viscous_fs_zhong_B_* viscous_fs_zhong_A_* fluidity.* *.pyc
1572+ rm -rf *.msh *.stat *.vtu *.log-0 *.err-0 *checkpoint *.convergence *.log *.node *.edge *.ele *.halo *.pvtu viscous_fs_zhong_B_* viscous_fs_zhong_A_* fluidity.* *.pyc
1573
1574=== modified file 'tests/viscous_fs_zhong_spatial/viscous_fs_zhong_A.flml'
1575--- tests/viscous_fs_zhong_spatial/viscous_fs_zhong_A.flml 2012-03-16 15:27:11 +0000
1576+++ tests/viscous_fs_zhong_spatial/viscous_fs_zhong_A.flml 2013-10-17 12:55:48 +0000
1577@@ -12,7 +12,7 @@
1578 </dimension>
1579 <mesh name="CoordinateMesh">
1580 <from_file file_name="squareA">
1581- <format name="triangle"/>
1582+ <format name="gmsh"/>
1583 <stat>
1584 <include_in_stat/>
1585 </stat>
1586
1587=== modified file 'tests/viscous_fs_zhong_spatial/viscous_fs_zhong_B.flml'
1588--- tests/viscous_fs_zhong_spatial/viscous_fs_zhong_B.flml 2012-03-16 15:27:11 +0000
1589+++ tests/viscous_fs_zhong_spatial/viscous_fs_zhong_B.flml 2013-10-17 12:55:48 +0000
1590@@ -12,7 +12,7 @@
1591 </dimension>
1592 <mesh name="CoordinateMesh">
1593 <from_file file_name="squareB">
1594- <format name="triangle"/>
1595+ <format name="gmsh"/>
1596 <stat>
1597 <include_in_stat/>
1598 </stat>
1599
1600=== modified file 'tests/viscous_fs_zhong_spatial_explicit/Makefile'
1601--- tests/viscous_fs_zhong_spatial_explicit/Makefile 2013-09-17 15:06:47 +0000
1602+++ tests/viscous_fs_zhong_spatial_explicit/Makefile 2013-10-17 12:55:48 +0000
1603@@ -1,8 +1,13 @@
1604 input: clean
1605+<<<<<<< TREE
1606 gmsh -2 src/squareA.geo
1607 ../../bin/gmsh2triangle --2d -i src/squareA.msh
1608 gmsh -2 src/squareB.geo
1609 ../../bin/gmsh2triangle --2d -i src/squareB.msh
1610+=======
1611+ gmsh -2 src/squareA.geo -o squareA.msh
1612+ gmsh -2 src/squareB.geo -o squareB.msh
1613+>>>>>>> MERGE-SOURCE
1614
1615 clean:
1616- rm -rf src/*.msh *.stat *.vtu *.log-0 *.err-0 *checkpoint *.convergence *.log *.node *.edge *.ele
1617+ rm -rf *.msh *.stat *.vtu *.log-0 *.err-0 *checkpoint *.convergence *.log *.node *.edge *.ele
1618
1619=== modified file 'tests/viscous_fs_zhong_spatial_explicit/viscous_fs_zhong_A.flml'
1620--- tests/viscous_fs_zhong_spatial_explicit/viscous_fs_zhong_A.flml 2012-03-16 15:53:58 +0000
1621+++ tests/viscous_fs_zhong_spatial_explicit/viscous_fs_zhong_A.flml 2013-10-17 12:55:48 +0000
1622@@ -12,7 +12,7 @@
1623 </dimension>
1624 <mesh name="CoordinateMesh">
1625 <from_file file_name="squareA">
1626- <format name="triangle"/>
1627+ <format name="gmsh"/>
1628 <stat>
1629 <include_in_stat/>
1630 </stat>
1631
1632=== modified file 'tests/viscous_fs_zhong_spatial_explicit/viscous_fs_zhong_B.flml'
1633--- tests/viscous_fs_zhong_spatial_explicit/viscous_fs_zhong_B.flml 2012-03-16 15:53:58 +0000
1634+++ tests/viscous_fs_zhong_spatial_explicit/viscous_fs_zhong_B.flml 2013-10-17 12:55:48 +0000
1635@@ -12,7 +12,7 @@
1636 </dimension>
1637 <mesh name="CoordinateMesh">
1638 <from_file file_name="squareB">
1639- <format name="triangle"/>
1640+ <format name="gmsh"/>
1641 <stat>
1642 <include_in_stat/>
1643 </stat>
1644
1645=== modified file 'tests/viscous_fs_zhong_spatial_explicit_varrho/Makefile'
1646--- tests/viscous_fs_zhong_spatial_explicit_varrho/Makefile 2013-09-17 15:06:47 +0000
1647+++ tests/viscous_fs_zhong_spatial_explicit_varrho/Makefile 2013-10-17 12:55:48 +0000
1648@@ -1,8 +1,13 @@
1649 input: clean
1650+<<<<<<< TREE
1651 gmsh -2 src/squareA.geo
1652 ../../bin/gmsh2triangle --2d -i src/squareA.msh
1653 gmsh -2 src/squareB.geo
1654 ../../bin/gmsh2triangle --2d -i src/squareB.msh
1655+=======
1656+ gmsh -2 src/squareA.geo -o squareA.msh
1657+ gmsh -2 src/squareB.geo -o squareB.msh
1658+>>>>>>> MERGE-SOURCE
1659
1660 clean:
1661- rm -rf src/*.msh *.stat *.vtu *.log-0 *.err-0 *checkpoint *.convergence *.log *.node *.edge *.ele
1662+ rm -rf *.msh *.stat *.vtu *.log-0 *.err-0 *checkpoint *.convergence *.log *.node *.edge *.ele
1663
1664=== modified file 'tests/viscous_fs_zhong_spatial_explicit_varrho/viscous_fs_zhong_A.flml'
1665--- tests/viscous_fs_zhong_spatial_explicit_varrho/viscous_fs_zhong_A.flml 2012-03-16 05:00:48 +0000
1666+++ tests/viscous_fs_zhong_spatial_explicit_varrho/viscous_fs_zhong_A.flml 2013-10-17 12:55:48 +0000
1667@@ -12,7 +12,7 @@
1668 </dimension>
1669 <mesh name="CoordinateMesh">
1670 <from_file file_name="squareA">
1671- <format name="triangle"/>
1672+ <format name="gmsh"/>
1673 <stat>
1674 <include_in_stat/>
1675 </stat>
1676
1677=== modified file 'tests/viscous_fs_zhong_spatial_explicit_varrho/viscous_fs_zhong_B.flml'
1678--- tests/viscous_fs_zhong_spatial_explicit_varrho/viscous_fs_zhong_B.flml 2012-03-16 05:00:48 +0000
1679+++ tests/viscous_fs_zhong_spatial_explicit_varrho/viscous_fs_zhong_B.flml 2013-10-17 12:55:48 +0000
1680@@ -12,7 +12,7 @@
1681 </dimension>
1682 <mesh name="CoordinateMesh">
1683 <from_file file_name="squareB">
1684- <format name="triangle"/>
1685+ <format name="gmsh"/>
1686 <stat>
1687 <include_in_stat/>
1688 </stat>
1689
1690=== modified file 'tests/viscous_fs_zhong_spatial_varrho/Makefile'
1691--- tests/viscous_fs_zhong_spatial_varrho/Makefile 2013-09-17 15:02:30 +0000
1692+++ tests/viscous_fs_zhong_spatial_varrho/Makefile 2013-10-17 12:55:48 +0000
1693@@ -1,8 +1,13 @@
1694 input: clean
1695+<<<<<<< TREE
1696 gmsh -2 src/squareA.geo
1697 ../../bin/gmsh2triangle --2d -i src/squareA.msh
1698 gmsh -2 src/squareB.geo
1699 ../../bin/gmsh2triangle --2d -i src/squareB.msh
1700+=======
1701+ gmsh -2 src/squareA.geo -o squareA.msh
1702+ gmsh -2 src/squareB.geo -o squareB.msh
1703+>>>>>>> MERGE-SOURCE
1704
1705 clean:
1706- rm -rf src/*.msh *.stat *.vtu *.log-0 *.err-0 *checkpoint *.convergence *.log *.node *.edge *.ele
1707+ rm -rf *.msh *.stat *.vtu *.log-0 *.err-0 *checkpoint *.convergence *.log *.node *.edge *.ele
1708
1709=== modified file 'tests/viscous_fs_zhong_spatial_varrho/viscous_fs_zhong_A.flml'
1710--- tests/viscous_fs_zhong_spatial_varrho/viscous_fs_zhong_A.flml 2012-03-16 15:53:58 +0000
1711+++ tests/viscous_fs_zhong_spatial_varrho/viscous_fs_zhong_A.flml 2013-10-17 12:55:48 +0000
1712@@ -12,7 +12,7 @@
1713 </dimension>
1714 <mesh name="CoordinateMesh">
1715 <from_file file_name="squareA">
1716- <format name="triangle"/>
1717+ <format name="gmsh"/>
1718 <stat>
1719 <include_in_stat/>
1720 </stat>
1721
1722=== modified file 'tests/viscous_fs_zhong_spatial_varrho/viscous_fs_zhong_B.flml'
1723--- tests/viscous_fs_zhong_spatial_varrho/viscous_fs_zhong_B.flml 2012-03-16 15:53:58 +0000
1724+++ tests/viscous_fs_zhong_spatial_varrho/viscous_fs_zhong_B.flml 2013-10-17 12:55:48 +0000
1725@@ -12,7 +12,7 @@
1726 </dimension>
1727 <mesh name="CoordinateMesh">
1728 <from_file file_name="squareB">
1729- <format name="triangle"/>
1730+ <format name="gmsh"/>
1731 <stat>
1732 <include_in_stat/>
1733 </stat>