Merge lp:~r-nelson/fluidity/parallel_sigma into lp:fluidity

Proposed by Rhodri Nelson
Status: Work in progress
Proposed branch: lp:~r-nelson/fluidity/parallel_sigma
Merge into: lp:fluidity
Diff against target: 357 lines (+166/-46)
3 files modified
horizontal_adaptivity/Combine_Meshes.F90 (+164/-44)
horizontal_adaptivity/Extrude.F90 (+1/-1)
horizontal_adaptivity/Extrude_radially.F90 (+1/-1)
To merge this branch: bzr merge lp:~r-nelson/fluidity/parallel_sigma
Reviewer Review Type Date Requested Status
Simon Funke Needs Information
Review via email: mp+71571@code.launchpad.net

Description of the change

Fixed a bug with Sigma coordinates in parallel. Instead of using a pre-existing chain as a dummy chain to create the initial mesh, a specific dummy chain is now created. This ensures consistency across all processors.

Also, updated a couple of interfaces to be more in line with the fluidity style.

To post a comment you must log in.
Revision history for this message
Simon Funke (simon-funke) wrote :

This merge request has empty? What happened?

review: Needs Information
Revision history for this message
Lawrence Mitchell (wence) wrote :

I think the relevant differences in the branch are already in trunk (see r3545)

Revision history for this message
Adam Candy (asc) wrote :

That was my conclusion too.
It'd be good to check that there isn't some extra code that was meant to be included in this merge - Rhodri? Let us know when you're back online - さっぽろはどうですか? おげんきで!

Revision history for this message
Rhodri Nelson (r-nelson) wrote :

Something strange seems to have happened, which was probably my mistake. I modified my trunk and then made a branch from it but for some reason none of the changes were ported into the branch. Maybe it's because I forgot to commit them locally or something? I can't access Rossby at the moment though so can't get hold of the code. I'll update the other merge request later though as I have that on my laptop.

lp:~r-nelson/fluidity/parallel_sigma updated
3551. By Rhodri Nelson

Updating some local changes.

Revision history for this message
Rhodri Nelson (r-nelson) wrote :

The relevant changes have now been uploaded to Launchpad.

Unmerged revisions

3551. By Rhodri Nelson

Updating some local changes.

Preview Diff

[H/L] Next/Prev Comment, [J/K] Next/Prev File, [N/P] Next/Prev Hunk
1=== modified file 'horizontal_adaptivity/Combine_Meshes.F90'
2--- horizontal_adaptivity/Combine_Meshes.F90 2011-08-01 16:03:12 +0000
3+++ horizontal_adaptivity/Combine_Meshes.F90 2011-09-08 00:21:25 +0000
4@@ -22,27 +22,32 @@
5 contains
6
7 subroutine combine_z_meshes(h_mesh, z_meshes, out_mesh, &
8- full_shape, mesh_name, option_path, sl)
9- !! Given the h_mesh and a z_mesh under each node of it combines these
10- !! into a full horiz+vertic. mesh
11- type(vector_field), intent(inout):: h_mesh
12- type(vector_field), dimension(:), intent(in):: z_meshes
13- type(vector_field), intent(out):: out_mesh
14- type(element_type), intent(in):: full_shape
15- !! the name of the topol. mesh to be created, not the coordinate field
16- character(len=*), intent(in):: mesh_name, option_path
17- logical, intent(in), optional :: sl
18- logical :: sigma_layers
19+ full_shape, mesh_name, option_path, sigma_layers)
20+
21+ !! Given the h_mesh and a z_mesh under each node of it combines these
22+ !! into a full horiz+vertic. mesh
23+ type(vector_field), intent(inout):: h_mesh
24+ type(vector_field), dimension(:), intent(in):: z_meshes
25+ type(vector_field), intent(out):: out_mesh
26+ type(element_type), intent(in):: full_shape
27+ !! the name of the topol. mesh to be created, not the coordinate field
28+ character(len=*), intent(in):: mesh_name, option_path
29+ logical, intent(in), optional :: sigma_layers
30+
31+ ! The sigma_layers logical input is optional so create another logical for use
32+ ! in this routine
33+ logical :: sl
34+ type(vector_field) :: dummy_column
35
36 type(csr_sparsity):: out_columns
37 type(mesh_type):: mesh
38 integer, dimension(:), allocatable:: no_hanging_nodes
39 integer:: column, total_out_nodes, total_out_elements, z_elements, last_seen
40
41- if (present(sl)) then
42- sigma_layers=sl
43+ if (present(sigma_layers)) then
44+ sl=sigma_layers
45 else
46- sigma_layers=.false.
47+ sl=.false.
48 end if
49
50 allocate(no_hanging_nodes(1:node_count(h_mesh)))
51@@ -95,14 +100,22 @@
52 out_mesh%option_path=""
53 out_mesh%mesh%periodic = mesh_periodic(h_mesh)
54
55+ ! If we have sigma layers we want to create a dummy chain in order to create a mesh
56+ ! with the desired topological properties. The nodal coordinates will then later
57+ ! be over written with the correct ones. Note that all chains have the same amount of
58+ ! layers so we will just use the first chain to create the dummy mesh.
59+ if (sl) then
60+ call create_dummy_column(z_meshes(1), dummy_column)
61+ end if
62+
63 last_seen = 0
64 do column=1,node_count(h_mesh)
65 if (node_owned(h_mesh, column)) then
66- if (sigma_layers) then
67+ if (sl) then
68 ! If we have sigma layers we will first use one chain to chain to create a dummy
69 ! 'mesh' that has the correct topological properties. We will later over write the
70 ! vector field with the correct one. We always have chain '1', so we'll use that now.
71- call append_to_structures(column, z_meshes(1), h_mesh, out_mesh, last_seen)
72+ call append_to_structures(column, dummy_column, h_mesh, out_mesh, last_seen)
73 else
74 call append_to_structures(column, z_meshes(column), h_mesh, out_mesh, last_seen)
75 end if
76@@ -115,6 +128,7 @@
77 last_seen = last_seen + no_hanging_nodes(column)+1
78 end if
79 end do
80+ if (sl) call deallocate(dummy_column)
81 assert(all(out_mesh%mesh%columns>0))
82
83 call create_columns_sparsity(out_columns, out_mesh%mesh)
84@@ -130,13 +144,23 @@
85
86 ! If we have sigma layers we now populate the vector field with the actual
87 ! node positions.
88- if (sigma_layers) then
89+ if (sl) then
90 last_seen = 0
91 do column=1,node_count(h_mesh)
92 if (node_owned(h_mesh, column)) then
93 call append_to_structures(column, z_meshes(column), h_mesh, out_mesh, last_seen)
94+ else
95+ ! for non-owned columns we reserve node numbers,
96+ ! but don't fill in out_mesh positions yet
97+ ! note that in this way out_mesh will obtain the same halo ordering
98+ ! convention as h_mesh
99+ out_mesh%mesh%columns(last_seen+1:last_seen+no_hanging_nodes(column)+1) = column
100+ last_seen = last_seen + no_hanging_nodes(column)+1
101 end if
102 end do
103+ if (associated(h_mesh%mesh%halos)) then
104+ call halo_update(out_mesh)
105+ end if
106 end if
107
108 call deallocate(out_columns)
109@@ -145,27 +169,32 @@
110
111
112 subroutine combine_r_meshes(shell_mesh, r_meshes, out_mesh, &
113- full_shape, mesh_name, option_path, sl)
114- !! Given the shell_mesh and a r_mesh under each node of it combines these
115- !! into a full layered mesh
116- type(vector_field), intent(inout):: shell_mesh
117- type(vector_field), dimension(:), intent(in):: r_meshes
118- type(vector_field), intent(out):: out_mesh
119- type(element_type), intent(in):: full_shape
120- !! the name of the topol. mesh to be created, not the coordinate field
121- character(len=*), intent(in):: mesh_name, option_path
122- logical, intent(in), optional :: sl
123- logical :: sigma_layers
124+ full_shape, mesh_name, option_path, sigma_layers)
125+
126+ !! Given the shell_mesh and a r_mesh under each node of it combines these
127+ !! into a full layered mesh
128+ type(vector_field), intent(inout):: shell_mesh
129+ type(vector_field), dimension(:), intent(in):: r_meshes
130+ type(vector_field), intent(out):: out_mesh
131+ type(element_type), intent(in):: full_shape
132+ !! the name of the topol. mesh to be created, not the coordinate field
133+ character(len=*), intent(in):: mesh_name, option_path
134+ logical, intent(in), optional :: sigma_layers
135+
136+ ! The sigma_layers logical input is optional so create another logical for use
137+ ! in this routine
138+ logical :: sl
139+ type(vector_field) :: dummy_column
140
141 type(csr_sparsity):: out_columns
142 type(mesh_type):: mesh
143 integer, dimension(:), allocatable:: no_hanging_nodes
144 integer:: column, total_out_nodes, total_out_elements, r_elements, last_seen
145
146- if (present(sl)) then
147- sigma_layers=sl
148+ if (present(sigma_layers)) then
149+ sl=sigma_layers
150 else
151- sigma_layers=.false.
152+ sl=.false.
153 end if
154
155 allocate(no_hanging_nodes(1:node_count(shell_mesh)))
156@@ -217,15 +246,23 @@
157 out_mesh%mesh%option_path=option_path
158 out_mesh%option_path=""
159 out_mesh%mesh%periodic = mesh_periodic(shell_mesh) ! Leave this here for now
160+
161+ ! If we have sigma layers we want to create a dummy chain in order to create a mesh
162+ ! with the desired topological properties. The nodal coordinates will then later
163+ ! be over written with the correct ones. Note that all chains have the same amount of
164+ ! layers so we will just use the first chain to create the dummy mesh.
165+ if (sl) then
166+ call create_dummy_column(r_meshes(1), dummy_column)
167+ end if
168
169 last_seen = 0
170 do column=1,node_count(shell_mesh)
171 if (node_owned(shell_mesh, column)) then
172- if (sigma_layers) then
173+ if (sl) then
174 ! If we have sigma layers we will first use one chain to chain to create a dummy
175 ! 'mesh' that has the correct topological properties. We will later over write the
176 ! vector field with the correct one. We always have chain '1', so we'll use that now.
177- call append_to_structures_radial(column, r_meshes(1), out_mesh, last_seen)
178+ call append_to_structures_radial(column, r_meshes(column), out_mesh, last_seen, dummy_column)
179 else
180 call append_to_structures_radial(column, r_meshes(column), out_mesh, last_seen)
181 end if
182@@ -238,6 +275,7 @@
183 last_seen = last_seen + no_hanging_nodes(column)+1
184 end if
185 end do
186+ if (sl) call deallocate(dummy_column)
187 assert(all(out_mesh%mesh%columns>0))
188
189 call create_columns_sparsity(out_columns, out_mesh%mesh)
190@@ -251,16 +289,25 @@
191
192 call generate_layered_mesh(out_mesh, shell_mesh)
193
194- if (sigma_layers) then
195+ ! If we have sigma layers we now populate the vector field with the actual
196+ ! node positions.
197+ if (sl) then
198 last_seen = 0
199 do column=1,node_count(shell_mesh)
200 if (node_owned(shell_mesh, column)) then
201- ! If we have sigma layers we will first use one chain to chain to create a dummy
202- ! 'mesh' that has the correct topological properties. We will later over write the
203- ! vector field with the correct one. We always have chain '1', so we'll use that now.
204 call append_to_structures_radial(column, r_meshes(column), out_mesh, last_seen)
205+ else
206+ ! for non-owned columns we reserve node numbers,
207+ ! but don't fill in out_mesh positions yet
208+ ! note that in this way out_mesh will obtain the same halo ordering
209+ ! convention as h_mesh
210+ out_mesh%mesh%columns(last_seen+1:last_seen+no_hanging_nodes(column)+1) = column
211+ last_seen = last_seen + no_hanging_nodes(column)+1
212 end if
213 end do
214+ if (associated(shell_mesh%mesh%halos)) then
215+ call halo_update(out_mesh)
216+ end if
217 end if
218
219 call deallocate(out_columns)
220@@ -291,25 +338,55 @@
221
222 end subroutine append_to_structures
223
224- subroutine append_to_structures_radial(column, r_mesh, out_mesh, last_seen)
225+ subroutine append_to_structures_radial(column, r_mesh, out_mesh, last_seen, dummy_column)
226 integer, intent(in) :: column
227 type(vector_field), intent(in) :: r_mesh
228 type(vector_field), intent(inout) :: out_mesh
229 integer, intent(inout) :: last_seen
230+ type(vector_field), intent(in), optional :: dummy_column
231
232 integer :: j
233 integer :: r_dim
234
235 real, dimension(mesh_dim(out_mesh)) :: pos
236
237+ logical :: sigma_layers
238+ real, dimension(3) :: r
239+ real :: mod_r, theta, phi, height
240+
241+ if (present(dummy_column)) then
242+ sigma_layers=.true.
243+ else
244+ sigma_layers=.false.
245+ end if
246+
247 r_dim = mesh_dim(out_mesh)
248
249- do j=1,node_count(r_mesh)
250- last_seen = last_seen + 1
251- out_mesh%mesh%columns(last_seen)=column
252- pos(1:r_dim) = node_val(r_mesh, j) ! note that in z-dir extrusion case only the z value was loaded into the out mesh from the z mesh. Here however,
253- call set(out_mesh, last_seen, pos)
254- end do
255+ if (sigma_layers) then
256+ assert(mesh_dim(out_mesh)==3)
257+ r=node_val(r_mesh, 1)
258+ mod_r=sqrt(dot_product(r,r))
259+
260+ theta=acos(r(3)/mod_r)
261+ phi=atan2(r(2),r(1))
262+
263+ do j=1,node_count(r_mesh)
264+ last_seen = last_seen + 1
265+ out_mesh%mesh%columns(last_seen)=column
266+ height=node_val(dummy_column,1,j)
267+ pos(1)=(mod_r+height)*sin(theta)*cos(phi)
268+ pos(2)=(mod_r+height)*sin(theta)*sin(phi)
269+ pos(3)=(mod_r+height)*cos(theta)
270+ call set(out_mesh, last_seen, pos)
271+ end do
272+ else
273+ do j=1,node_count(r_mesh)
274+ last_seen = last_seen + 1
275+ out_mesh%mesh%columns(last_seen)=column
276+ pos(1:r_dim) = node_val(r_mesh, j) ! note that in z-dir extrusion case only the z value was loaded into the out mesh from the z mesh. Here however,
277+ call set(out_mesh, last_seen, pos)
278+ end do
279+ end if
280
281 end subroutine append_to_structures_radial
282
283@@ -405,5 +482,48 @@
284
285 end subroutine derive_extruded_l2_node_halo
286
287+ subroutine create_dummy_column(z_mesh, dummy_column)
288+ ! Subroutine to create a dummy column when using sigma layers
289+
290+ type(vector_field), intent(in) :: z_mesh
291+ type(vector_field), intent(inout) :: dummy_column
292+
293+ integer :: node
294+
295+ type(mesh_type) :: mesh
296+ type(element_type) :: oned_shape
297+ type(quadrature_type) :: oned_quad
298+ integer :: quadrature_degree
299+ integer :: ele
300+ integer, parameter :: loc=2
301+
302+ integer :: elements
303+ type(rlist):: depths
304+
305+ call get_option("/geometry/quadrature/degree", quadrature_degree)
306+ oned_quad = make_quadrature(vertices=loc, dim=1, degree=quadrature_degree)
307+ oned_shape = make_element_shape(vertices=loc, dim=1, degree=1, quad=oned_quad)
308+ call deallocate(oned_quad)
309+
310+ do node=1,node_count(z_mesh)
311+ call insert(depths, float(node-1)*10.0)
312+ end do
313+ elements=depths%length-1
314+
315+ call allocate(mesh, elements+1, elements, oned_shape, "DummyMesh")
316+ call deallocate(oned_shape)
317+ do ele=1,elements
318+ mesh%ndglno((ele-1) * loc + 1: ele*loc) = (/ele, ele+1/)
319+ end do
320+
321+ call allocate(dummy_column, 1, mesh, "DummyMeshCoordinates")
322+ call deallocate(mesh)
323+
324+ call set(dummy_column, 1, (/0.0/))
325+ do node=1, elements+1
326+ call set(dummy_column, node, (/ pop(depths) /))
327+ end do
328+
329+ end subroutine create_dummy_column
330
331 end module hadapt_combine_meshes
332
333=== modified file 'horizontal_adaptivity/Extrude.F90'
334--- horizontal_adaptivity/Extrude.F90 2011-08-01 16:03:12 +0000
335+++ horizontal_adaptivity/Extrude.F90 2011-09-08 00:21:25 +0000
336@@ -155,7 +155,7 @@
337
338 ! combine the 1d vertical meshes into a full mesh
339 call combine_z_meshes(h_mesh, z_meshes, out_mesh, &
340- full_shape, mesh_name, option_path, sigma_layers)
341+ full_shape, mesh_name, option_path, sigma_layers=sigma_layers)
342
343 do column=1, node_count(h_mesh)
344 if (.not. node_owned(h_mesh, column)) cycle
345
346=== modified file 'horizontal_adaptivity/Extrude_radially.F90'
347--- horizontal_adaptivity/Extrude_radially.F90 2011-08-01 16:03:12 +0000
348+++ horizontal_adaptivity/Extrude_radially.F90 2011-09-08 00:21:25 +0000
349@@ -285,7 +285,7 @@
350
351 ! combine the 1d radial meshes into a full mesh
352 call combine_r_meshes(shell_mesh, r_meshes, out_mesh, &
353- full_shape, mesh_name, option_path, sigma_layers)
354+ full_shape, mesh_name, option_path, sigma_layers=sigma_layers)
355
356 ! vtk_write_state(filename, index, model, state, write_region_ids, stat)
357 ! call vtk_write_fields("extruded_mesh", 0, out_mesh, out_mesh%mesh, vfields=(/out_mesh/))