Neko  0.8.1
A portable framework for high-order spectral element flow simulations
nmsh_file.f90
Go to the documentation of this file.
1 ! Copyright (c) 2019-2021, The Neko Authors
2 ! All rights reserved.
3 !
4 ! Redistribution and use in source and binary forms, with or without
5 ! modification, are permitted provided that the following conditions
6 ! are met:
7 !
8 ! * Redistributions of source code must retain the above copyright
9 ! notice, this list of conditions and the following disclaimer.
10 !
11 ! * Redistributions in binary form must reproduce the above
12 ! copyright notice, this list of conditions and the following
13 ! disclaimer in the documentation and/or other materials provided
14 ! with the distribution.
15 !
16 ! * Neither the name of the authors nor the names of its
17 ! contributors may be used to endorse or promote products derived
18 ! from this software without specific prior written permission.
19 !
20 ! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
21 ! "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
22 ! LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
23 ! FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
24 ! COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
25 ! INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
26 ! BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
27 ! LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
28 ! CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
29 ! LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
30 ! ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
31 ! POSSIBILITY OF SUCH DAMAGE.
32 !
34 module nmsh_file
35  use generic_file
36  use comm
37  use mesh
38  use utils
39  use point
40  use tuple
41  use nmsh
42  use element
43  use datadist
44  use neko_mpi_types
45  use mpi_f08
46  use logger
47  implicit none
48 
49  private
52  integer, parameter :: max_write_nel = 8000000
54  type, public, extends(generic_file_t) :: nmsh_file_t
55  contains
56  procedure :: read => nmsh_file_read
57  procedure :: write => nmsh_file_write
58  end type nmsh_file_t
59 
60 contains
61 
63  subroutine nmsh_file_read(this, data)
64  class(nmsh_file_t) :: this
65  class(*), target, intent(inout) :: data
66  type(nmsh_hex_t), allocatable :: nmsh_hex(:)
67  type(nmsh_quad_t), allocatable :: nmsh_quad(:)
68  type(nmsh_zone_t), allocatable :: nmsh_zone(:)
69  type(nmsh_curve_el_t), allocatable :: nmsh_curve(:)
70  type(mesh_t), pointer :: msh
71  type(mpi_status) :: status
72  type(mpi_file) :: fh
73  integer (kind=MPI_OFFSET_KIND) :: mpi_offset, mpi_el_offset
74  integer :: i, j, ierr, element_offset
75  integer :: nmsh_quad_size, nmsh_hex_size, nmsh_zone_size
76  integer :: nelv, gdim, nzones, ncurves
77  integer :: el_idx
78  type(point_t), target :: p(8)
79  type(linear_dist_t) :: dist
80  character(len=LOG_SIZE) :: log_buf
81 
82  call this%check_exists()
83 
84  select type(data)
85  type is(mesh_t)
86  msh => data
87  class default
88  call neko_error('Invalid output data')
89  end select
90 
91 
92  call neko_log%section("Mesh")
93  call neko_log%message('Reading a binary Neko file ' // this%fname)
94 
95  call mpi_type_size(mpi_nmsh_hex, nmsh_hex_size, ierr)
96  call mpi_type_size(mpi_nmsh_quad, nmsh_quad_size, ierr)
97  call mpi_type_size(mpi_nmsh_zone, nmsh_zone_size, ierr)
98 
99  call mpi_file_open(neko_comm, trim(this%fname), &
100  mpi_mode_rdonly, mpi_info_null, fh, ierr)
101 
102  if (ierr > 0) then
103  call neko_error('Could not open the mesh file ' // this%fname // &
104  'for reading!')
105  end if
106  call mpi_file_read_all(fh, nelv, 1, mpi_integer, status, ierr)
107  call mpi_file_read_all(fh, gdim, 1, mpi_integer, status, ierr)
108 
109  write(log_buf,1) gdim, nelv
110 1 format('gdim = ', i1, ', nelements =', i9)
111  call neko_log%message(log_buf)
112 
113  if (gdim .eq. 2) then
114  call mpi_file_close(fh, ierr)
115  call nmsh_file_read_2d(this, msh)
116  else
117 
118  dist = linear_dist_t(nelv, pe_rank, pe_size, neko_comm)
119  nelv = dist%num_local()
120  element_offset = dist%start_idx()
121 
122  call msh%init(gdim, nelv)
123 
124  call neko_log%message('Reading elements')
125 
126  if (msh%gdim .eq. 2) then
127  allocate(nmsh_quad(msh%nelv))
128  mpi_offset = int(2 * mpi_integer_size,i8) + int(element_offset,i8) * int(nmsh_quad_size,i8)
129  call mpi_file_read_at_all(fh, mpi_offset, &
130  nmsh_quad, msh%nelv, mpi_nmsh_quad, status, ierr)
131  do i = 1, nelv
132  do j = 1, 4
133  p(j) = point_t(nmsh_quad(i)%v(j)%v_xyz, nmsh_quad(i)%v(j)%v_idx)
134  end do
135  ! swap vertices to keep symmetric vertex numbering in neko
136  call msh%add_element(i, p(1), p(2), p(4), p(3))
137  end do
138  deallocate(nmsh_quad)
139  mpi_el_offset = int(2 * mpi_integer_size,i8) + int(dist%num_global(),i8) * int(nmsh_quad_size,i8)
140  else if (msh%gdim .eq. 3) then
141  allocate(nmsh_hex(msh%nelv))
142  mpi_offset = int(2 * mpi_integer_size,i8) + int(element_offset,i8) * int(nmsh_hex_size,i8)
143  call mpi_file_read_at_all(fh, mpi_offset, &
144  nmsh_hex, msh%nelv, mpi_nmsh_hex, status, ierr)
145  do i = 1, nelv
146  do j = 1, 8
147  p(j) = point_t(nmsh_hex(i)%v(j)%v_xyz, nmsh_hex(i)%v(j)%v_idx)
148  end do
149  ! swap vertices to keep symmetric vertex numbering in neko
150  call msh%add_element(i, &
151  p(1), p(2), p(4), p(3), p(5), p(6), p(8), p(7))
152  end do
153  deallocate(nmsh_hex)
154  mpi_el_offset = int(2 * mpi_integer_size,i8) + int(dist%num_global(),i8) * int(nmsh_hex_size,i8)
155  else
156  if (pe_rank .eq. 0) call neko_error('Invalid dimension of mesh')
157  end if
158  call neko_log%message('Reading BC/zone data')
159 
160  mpi_offset = mpi_el_offset
161  call mpi_file_read_at_all(fh, mpi_offset, &
162  nzones, 1, mpi_integer, status, ierr)
163  if (nzones .gt. 0) then
164  allocate(nmsh_zone(nzones))
165 
171  mpi_offset = mpi_el_offset + int(mpi_integer_size,i8)
172  call mpi_file_read_at_all(fh, mpi_offset, &
173  nmsh_zone, nzones, mpi_nmsh_zone, status, ierr)
174 
175  do i = 1, nzones
176  el_idx = nmsh_zone(i)%e
177  if (el_idx .gt. msh%offset_el .and. &
178  el_idx .le. msh%offset_el + msh%nelv) then
179  el_idx = el_idx - msh%offset_el
180  select case(nmsh_zone(i)%type)
181  case(1)
182  call msh%mark_wall_facet(nmsh_zone(i)%f, el_idx)
183  case(2)
184  call msh%mark_inlet_facet(nmsh_zone(i)%f, el_idx)
185  case(3)
186  call msh%mark_outlet_facet(nmsh_zone(i)%f, el_idx)
187  case(4)
188  call msh%mark_sympln_facet(nmsh_zone(i)%f, el_idx)
189  case(5)
190  call msh%mark_periodic_facet(nmsh_zone(i)%f, el_idx, &
191  nmsh_zone(i)%p_f, nmsh_zone(i)%p_e, nmsh_zone(i)%glb_pt_ids)
192  case(6)
193  call msh%mark_outlet_normal_facet(nmsh_zone(i)%f, el_idx)
194  case(7)
195  call msh%mark_labeled_facet(nmsh_zone(i)%f, el_idx,nmsh_zone(i)%p_f)
196  end select
197  end if
198  end do
199  !Apply facets, important that marking is finished
200  do i = 1, nzones
201  el_idx = nmsh_zone(i)%e
202  if (el_idx .gt. msh%offset_el .and. &
203  el_idx .le. msh%offset_el + msh%nelv) then
204  el_idx = el_idx - msh%offset_el
205  select case(nmsh_zone(i)%type)
206  case(5)
207  call msh%apply_periodic_facet(nmsh_zone(i)%f, el_idx, &
208  nmsh_zone(i)%p_f, nmsh_zone(i)%p_e, nmsh_zone(i)%glb_pt_ids)
209  end select
210  end if
211  end do
212 
213  deallocate(nmsh_zone)
214  end if
215  call neko_log%message('Reading deformation data')
216 
217  mpi_offset = mpi_el_offset + int(mpi_integer_size,i8) + int(nzones,i8)*int(nmsh_zone_size,i8)
218  call mpi_file_read_at_all(fh, mpi_offset, &
219  ncurves, 1, mpi_integer, status, ierr)
220 
221  if (ncurves .gt. 0) then
222 
223  allocate(nmsh_curve(ncurves))
224  mpi_offset = mpi_el_offset + int(2 * mpi_integer_size,i8) + int(nzones,i8)*int(nmsh_zone_size,i8)
225  call mpi_file_read_at_all(fh, mpi_offset, &
226  nmsh_curve, ncurves, mpi_nmsh_curve, status, ierr)
227 
228  do i = 1, ncurves
229  el_idx = nmsh_curve(i)%e - msh%offset_el
230  if (el_idx .gt. 0 .and. &
231  el_idx .le. msh%nelv) then
232  call msh%mark_curve_element(el_idx, &
233  nmsh_curve(i)%curve_data, nmsh_curve(i)%type)
234  end if
235 
236  end do
237 
238  deallocate(nmsh_curve)
239  end if
240 
241  call mpi_file_close(fh, ierr)
242  call neko_log%message('Mesh read, setting up connectivity')
243 
244  call msh%finalize()
245  call neko_log%message('Done setting up mesh and connectivity')
246 
247  call neko_log%end_section()
248  end if
249 
250  end subroutine nmsh_file_read
251 
253  subroutine nmsh_file_read_2d(this, msh)
254  class(nmsh_file_t) :: this
255  type(mesh_t), pointer, intent(inout) :: msh
256  type(nmsh_hex_t), allocatable :: nmsh_hex(:)
257  type(nmsh_quad_t), allocatable :: nmsh_quad(:)
258  type(nmsh_zone_t), allocatable :: nmsh_zone(:)
259  type(nmsh_curve_el_t), allocatable :: nmsh_curve(:)
260  type(mpi_status) :: status
261  type(mpi_file) :: fh
262  integer (kind=MPI_OFFSET_KIND) :: mpi_offset, mpi_el_offset
263  integer :: i, j, ierr, element_offset, id
264  integer :: nmsh_quad_size, nmsh_hex_size, nmsh_zone_size
265  integer :: nelv, gdim, nzones, ncurves, ids(4)
266  integer :: el_idx
267  type(point_t) :: p(8)
268  type(linear_dist_t) :: dist
269  character(len=LOG_SIZE) :: log_buf
270  real(kind=rp) :: depth = 1d0
271  real(kind=dp) :: coord(3)
272  type(tuple4_i4_t) :: glb_pt_ids
273 
274 
275  call mpi_type_size(mpi_nmsh_hex, nmsh_hex_size, ierr)
276  call mpi_type_size(mpi_nmsh_quad, nmsh_quad_size, ierr)
277  call mpi_type_size(mpi_nmsh_zone, nmsh_zone_size, ierr)
278 
279  call mpi_file_open(neko_comm, trim(this%fname), &
280  mpi_mode_rdonly, mpi_info_null, fh, ierr)
281  call mpi_file_read_all(fh, nelv, 1, mpi_integer, status, ierr)
282  call mpi_file_read_all(fh, gdim, 1, mpi_integer, status, ierr)
283 
284  write(log_buf,2) gdim
285 2 format('gdim = ', i1, ', no full 2d support, creating thin slab')
286  call neko_log%message(log_buf)
287  gdim = 3
288 
289  dist = linear_dist_t(nelv, pe_rank, pe_size, neko_comm)
290  nelv = dist%num_local()
291  element_offset = dist%start_idx()
292 
293  call msh%init(gdim, nelv)
294 
295  allocate(nmsh_quad(msh%nelv))
296  mpi_offset = int(2 * mpi_integer_size,i8) + int(element_offset,i8) * int(nmsh_quad_size,i8)
297  call mpi_file_read_at_all(fh, mpi_offset, &
298  nmsh_quad, msh%nelv, mpi_nmsh_quad, status, ierr)
299  do i = 1, nelv
300  do j = 1, 4
301  coord = nmsh_quad(i)%v(j)%v_xyz
302  coord(3) = 0_rp
303  p(j) = point_t(coord, nmsh_quad(i)%v(j)%v_idx)
304  end do
305  do j = 1, 4
306  coord = nmsh_quad(i)%v(j)%v_xyz
307  coord(3) = depth
308  id = nmsh_quad(i)%v(j)%v_idx+msh%glb_nelv*8
309  p(j+4) = point_t(coord, id)
310  end do
311  ! swap vertices to keep symmetric vertex numbering in neko
312  call msh%add_element(i, &
313  p(1), p(2), p(4), p(3), p(5), p(6), p(8), p(7))
314  end do
315  deallocate(nmsh_quad)
316  mpi_el_offset = int(2 * mpi_integer_size,i8) + int(dist%num_global(),i8) * int(nmsh_quad_size,i8)
317 
318  mpi_offset = mpi_el_offset
319  call mpi_file_read_at_all(fh, mpi_offset, &
320  nzones, 1, mpi_integer, status, ierr)
321  if (nzones .gt. 0) then
322  allocate(nmsh_zone(nzones))
323 
329  mpi_offset = mpi_el_offset + int(mpi_integer_size,i8)
330  call mpi_file_read_at_all(fh, mpi_offset, &
331  nmsh_zone, nzones, mpi_nmsh_zone, status, ierr)
332 
333  do i = 1, nzones
334  el_idx = nmsh_zone(i)%e
335  if (el_idx .gt. msh%offset_el .and. &
336  el_idx .le. msh%offset_el + msh%nelv) then
337  el_idx = el_idx - msh%offset_el
338  select case(nmsh_zone(i)%type)
339  case(1)
340  call msh%mark_wall_facet(nmsh_zone(i)%f, el_idx)
341  case(2)
342  call msh%mark_inlet_facet(nmsh_zone(i)%f, el_idx)
343  case(3)
344  call msh%mark_outlet_facet(nmsh_zone(i)%f, el_idx)
345  case(4)
346  call msh%mark_sympln_facet(nmsh_zone(i)%f, el_idx)
347  case(5)
348  nmsh_zone(i)%glb_pt_ids(3) = nmsh_zone(i)%glb_pt_ids(1)+msh%glb_nelv*8
349  nmsh_zone(i)%glb_pt_ids(4) = nmsh_zone(i)%glb_pt_ids(2)+msh%glb_nelv*8
350  if (nmsh_zone(i)%f .eq. 1 .or. nmsh_zone(i)%f .eq. 2) then
351  ids(1) = nmsh_zone(i)%glb_pt_ids(1)
352  ids(2) = nmsh_zone(i)%glb_pt_ids(3)
353  ids(3) = nmsh_zone(i)%glb_pt_ids(4)
354  ids(4) = nmsh_zone(i)%glb_pt_ids(2)
355  else
356  ids(1) = nmsh_zone(i)%glb_pt_ids(1)
357  ids(2) = nmsh_zone(i)%glb_pt_ids(2)
358  ids(3) = nmsh_zone(i)%glb_pt_ids(4)
359  ids(4) = nmsh_zone(i)%glb_pt_ids(3)
360  end if
361  nmsh_zone(i)%glb_pt_ids = ids
362  call msh%mark_periodic_facet(nmsh_zone(i)%f, el_idx, &
363  nmsh_zone(i)%p_f, nmsh_zone(i)%p_e, ids)
364  case(6)
365  call msh%mark_outlet_normal_facet(nmsh_zone(i)%f, el_idx)
366  case(7)
367  call msh%mark_labeled_facet(nmsh_zone(i)%f, el_idx,nmsh_zone(i)%p_f)
368  end select
369  end if
370  end do
371  !Apply facets, important that marking is finished
372  do i = 1, nzones
373  el_idx = nmsh_zone(i)%e
374  if (el_idx .gt. msh%offset_el .and. &
375  el_idx .le. msh%offset_el + msh%nelv) then
376  el_idx = el_idx - msh%offset_el
377  select case(nmsh_zone(i)%type)
378  case(5)
379  call msh%apply_periodic_facet(nmsh_zone(i)%f, el_idx, &
380  nmsh_zone(i)%p_f, nmsh_zone(i)%p_e, nmsh_zone(i)%glb_pt_ids)
381  end select
382  end if
383  end do
384  !Do the same for extruded 3d points
385  do el_idx = 1, nelv
386  call msh%elements(el_idx)%e%facet_order(glb_pt_ids,5)
387  call msh%mark_periodic_facet(6, el_idx, &
388  5, el_idx, glb_pt_ids%x)
389  call msh%elements(el_idx)%e%facet_order(glb_pt_ids,5)
390  call msh%mark_periodic_facet(5, el_idx, &
391  6, el_idx, glb_pt_ids%x)
392  end do
393  do el_idx = 1, nelv
394  call msh%elements(el_idx)%e%facet_order(glb_pt_ids,5)
395  call msh%apply_periodic_facet(6, el_idx, &
396  5, el_idx, glb_pt_ids%x)
397  call msh%elements(el_idx)%e%facet_order(glb_pt_ids,5)
398  call msh%apply_periodic_facet(5, el_idx, &
399  6, el_idx, glb_pt_ids%x)
400  end do
401 
402  deallocate(nmsh_zone)
403  end if
404 
405  mpi_offset = mpi_el_offset + &
406  int(mpi_integer_size,i8) + int(nzones,i8)*int(nmsh_zone_size,i8)
407  call mpi_file_read_at_all(fh, mpi_offset, &
408  ncurves, 1, mpi_integer, status, ierr)
409 
410  if (ncurves .gt. 0) then
411 
412  allocate(nmsh_curve(ncurves))
413  mpi_offset = mpi_el_offset + &
414  int(2*mpi_integer_size,i8) + int(nzones,i8)*int(nmsh_zone_size,i8)
415  call mpi_file_read_at_all(fh, mpi_offset, &
416  nmsh_curve, ncurves, mpi_nmsh_curve, status, ierr)
417 
418  do i = 1, ncurves
419  el_idx = nmsh_curve(i)%e - msh%offset_el
420  if (el_idx .gt. 0 .and. &
421  el_idx .le. msh%nelv) then
422  call msh%mark_curve_element(el_idx, &
423  nmsh_curve(i)%curve_data, nmsh_curve(i)%type)
424  end if
425 
426  end do
427 
428  deallocate(nmsh_curve)
429  end if
430 
431  call mpi_file_close(fh, ierr)
432 
433  call msh%finalize()
434 
435  call neko_log%end_section()
436 
437  end subroutine nmsh_file_read_2d
438 
439 
441  subroutine nmsh_file_write(this, data, t)
442  class(nmsh_file_t), intent(inout) :: this
443  class(*), target, intent(in) :: data
444  real(kind=rp), intent(in), optional :: t
445  type(nmsh_quad_t), allocatable :: nmsh_quad(:)
446  type(nmsh_hex_t), allocatable :: nmsh_hex(:)
447  type(nmsh_zone_t), allocatable :: nmsh_zone(:)
448  type(nmsh_curve_el_t), allocatable :: nmsh_curve(:)
449  type(mesh_t), pointer :: msh
450  type(mpi_status) :: status
451  type(mpi_file) :: fh
452  integer (kind=MPI_OFFSET_KIND) :: mpi_offset, mpi_el_offset
453  integer :: i, j, ierr, nelgv, element_offset, k
454  integer :: nmsh_quad_size, nmsh_hex_size, nmsh_zone_size, nmsh_curve_size
455  integer :: nzones, ncurves
456  class(element_t), pointer :: ep
457  integer(i4), dimension(8), parameter :: vcyc_to_sym = (/1, 2, 4, 3, 5, &
458  & 6, 8, 7/) ! cyclic to symmetric vertex mapping
459 
460  select type(data)
461  type is (mesh_t)
462  msh => data
463  class default
464  call neko_error('Invalid output data')
465  end select
466 
467  call mpi_type_size(mpi_nmsh_quad, nmsh_quad_size, ierr)
468  call mpi_type_size(mpi_nmsh_hex, nmsh_hex_size, ierr)
469  call mpi_type_size(mpi_nmsh_zone, nmsh_zone_size, ierr)
470  call mpi_type_size(mpi_nmsh_curve, nmsh_curve_size, ierr)
471 
472  call mpi_reduce(msh%nelv, nelgv, 1, mpi_integer, &
473  mpi_sum, 0, neko_comm, ierr)
474  element_offset = 0
475  call mpi_exscan(msh%nelv, element_offset, 1, &
476  mpi_integer, mpi_sum, neko_comm, ierr)
477 
478  call neko_log%message('Writing data as a binary Neko file ' // this%fname)
479 
480  call mpi_file_open(neko_comm, trim(this%fname), &
481  mpi_mode_wronly + mpi_mode_create, mpi_info_null, fh, ierr)
482 
483  call mpi_file_write_all(fh, nelgv, 1, mpi_integer, status, ierr)
484  call mpi_file_write_all(fh, msh%gdim, 1, mpi_integer, status, ierr)
485 
486  call msh%reset_periodic_ids()
487 
488  if (msh%gdim .eq. 2) then
489  allocate(nmsh_quad(msh%nelv))
490  do i = 1, msh%nelv
491  ep => msh%elements(i)%e
492  nmsh_quad(i)%el_idx = ep%id()
493  do j = 1, 4
494  nmsh_quad(i)%v(j)%v_idx = ep%pts(vcyc_to_sym(j))%p%id()
495  nmsh_quad(i)%v(j)%v_xyz = ep%pts(vcyc_to_sym(j))%p%x
496  end do
497  end do
498  mpi_offset = int(2 * mpi_integer_size,i8) + int(element_offset,i8) * int(nmsh_quad_size,i8)
499  call mpi_file_write_at_all(fh, mpi_offset, &
500  nmsh_quad, msh%nelv, mpi_nmsh_quad, status, ierr)
501  deallocate(nmsh_quad)
502  mpi_el_offset = int(2 * mpi_integer_size,i8) + int(nelgv,i8) * int(nmsh_quad_size,i8)
503  else if (msh%gdim .eq. 3) then
504  allocate(nmsh_hex(msh%nelv))
505  do i = 1, msh%nelv
506  ep => msh%elements(i)%e
507  nmsh_hex(i)%el_idx = ep%id()
508  do j = 1, 8
509  nmsh_hex(i)%v(j)%v_idx = ep%pts(vcyc_to_sym(j))%p%id()
510  nmsh_hex(i)%v(j)%v_xyz = ep%pts(vcyc_to_sym(j))%p%x
511  end do
512  end do
513  mpi_offset = int(2 * mpi_integer_size,i8) + int(element_offset,i8) * int(nmsh_hex_size,i8)
514  call mpi_file_write_at_all(fh, mpi_offset, &
515  nmsh_hex, min(msh%nelv,max_write_nel), mpi_nmsh_hex, status, ierr)
516  do i = 1, msh%nelv/max_write_nel
517  mpi_offset = int(2 * mpi_integer_size,i8) + int(element_offset+i*max_write_nel,i8) * int(nmsh_hex_size,i8)
518  call mpi_file_write_at_all(fh, mpi_offset, &
519  nmsh_hex(i*max_write_nel+1), min(msh%nelv-i*max_write_nel,max_write_nel), mpi_nmsh_hex, status, ierr)
520  end do
521  deallocate(nmsh_hex)
522  mpi_el_offset = int(2 * mpi_integer_size,i8) + int(nelgv,i8) * int(nmsh_hex_size,i8)
523  else
524  call neko_error('Invalid dimension of mesh')
525  end if
526 
527  nzones = msh%wall%size + msh%inlet%size + msh%outlet%size + &
528  msh%sympln%size + msh%periodic%size + msh%outlet_normal%size
529 
530  do i = 1, neko_msh_max_zlbls
531  nzones = nzones + msh%labeled_zones(i)%size
532  end do
533  mpi_offset = mpi_el_offset
534  call mpi_file_write_at_all(fh, mpi_offset, &
535  nzones, 1, mpi_integer, status, ierr)
536 
537  if (nzones .gt. 0) then
538  allocate(nmsh_zone(nzones))
539 
540  nmsh_zone(:)%type = 0
541 
542  j = 1
543  do i = 1, msh%wall%size
544  nmsh_zone(j)%e = msh%wall%facet_el(i)%x(2) + msh%offset_el
545  nmsh_zone(j)%f = msh%wall%facet_el(i)%x(1)
546  nmsh_zone(j)%type = 1
547  j = j + 1
548  end do
549 
550  do i = 1, msh%inlet%size
551  nmsh_zone(j)%e = msh%inlet%facet_el(i)%x(2) + msh%offset_el
552  nmsh_zone(j)%f = msh%inlet%facet_el(i)%x(1)
553  nmsh_zone(j)%type = 2
554  j = j + 1
555  end do
556 
557  do i = 1, msh%outlet%size
558  nmsh_zone(j)%e = msh%outlet%facet_el(i)%x(2) + msh%offset_el
559  nmsh_zone(j)%f = msh%outlet%facet_el(i)%x(1)
560  nmsh_zone(j)%type = 3
561  j = j + 1
562  end do
563 
564  do i = 1, msh%sympln%size
565  nmsh_zone(j)%e = msh%sympln%facet_el(i)%x(2) + msh%offset_el
566  nmsh_zone(j)%f = msh%sympln%facet_el(i)%x(1)
567  nmsh_zone(j)%type = 4
568  j = j + 1
569  end do
570 
571  do i = 1, msh%periodic%size
572  nmsh_zone(j)%e = msh%periodic%facet_el(i)%x(2) + msh%offset_el
573  nmsh_zone(j)%f = msh%periodic%facet_el(i)%x(1)
574  nmsh_zone(j)%p_e = msh%periodic%p_facet_el(i)%x(2)
575  nmsh_zone(j)%p_f = msh%periodic%p_facet_el(i)%x(1)
576  nmsh_zone(j)%glb_pt_ids = msh%periodic%p_ids(i)%x
577  nmsh_zone(j)%type = 5
578  j = j + 1
579  end do
580  do i = 1, msh%outlet_normal%size
581  nmsh_zone(j)%e = msh%outlet_normal%facet_el(i)%x(2) + msh%offset_el
582  nmsh_zone(j)%f = msh%outlet_normal%facet_el(i)%x(1)
583  nmsh_zone(j)%type = 6
584  j = j + 1
585  end do
586  do k = 1, neko_msh_max_zlbls
587  do i = 1, msh%labeled_zones(k)%size
588  nmsh_zone(j)%e = msh%labeled_zones(k)%facet_el(i)%x(2) + msh%offset_el
589  nmsh_zone(j)%f = msh%labeled_zones(k)%facet_el(i)%x(1)
590  nmsh_zone(j)%p_f = k
591  nmsh_zone(j)%type = 7
592  j = j + 1
593  end do
594  end do
595 
596 
597  mpi_offset = mpi_el_offset + int(mpi_integer_size,i8)
598  call mpi_file_write_at_all(fh, mpi_offset, &
599  nmsh_zone, nzones, mpi_nmsh_zone, status, ierr)
600 
601  deallocate(nmsh_zone)
602  end if
603 
604  ncurves = msh%curve%size
605  mpi_offset = mpi_el_offset + int(mpi_integer_size,i8) + int(nzones,i8)*int(nmsh_zone_size,i8)
606 
607  call mpi_file_write_at_all(fh, mpi_offset, &
608  ncurves, 1, mpi_integer, status, ierr)
609 
610  if (ncurves .gt. 0) then
611  allocate(nmsh_curve(ncurves))
612  do i = 1, ncurves
613  nmsh_curve(i)%type = 0
614  end do
615 
616  do i = 1, ncurves
617  nmsh_curve(i)%e = msh%curve%curve_el(i)%el_idx + msh%offset_el
618  nmsh_curve(i)%curve_data = msh%curve%curve_el(i)%curve_data
619  nmsh_curve(i)%type = msh%curve%curve_el(i)%curve_type
620  end do
621  mpi_offset = mpi_el_offset + int(2*mpi_integer_size,i8) + int(nzones,i8)*int(nmsh_zone_size,i8)
622  call mpi_file_write_at_all(fh, mpi_offset, &
623  nmsh_curve, ncurves, mpi_nmsh_curve, status, ierr)
624 
625  deallocate(nmsh_curve)
626  end if
627 
628  call mpi_file_sync(fh, ierr)
629  call mpi_file_close(fh, ierr)
630  call neko_log%message('Done')
631 
632  end subroutine nmsh_file_write
633 
634 end module nmsh_file
635 
Definition: comm.F90:1
integer pe_rank
MPI rank.
Definition: comm.F90:26
type(mpi_comm) neko_comm
MPI communicator.
Definition: comm.F90:16
integer pe_size
MPI size of communicator.
Definition: comm.F90:29
Defines practical data distributions.
Definition: datadist.f90:34
Logging routines.
Definition: log.f90:34
type(log_t), public neko_log
Global log stream.
Definition: log.f90:61
Defines a mesh.
Definition: mesh.f90:34
integer, parameter, public neko_msh_max_zlbls
Max num. zone labels.
Definition: mesh.f90:55
MPI derived types.
Definition: mpi_types.f90:34
type(mpi_datatype), public mpi_nmsh_hex
MPI derived type for 3D Neko nmsh data.
Definition: mpi_types.f90:42
type(mpi_datatype), public mpi_nmsh_quad
MPI derived type for 2D Neko nmsh data.
Definition: mpi_types.f90:43
type(mpi_datatype), public mpi_nmsh_curve
MPI derived type for Neko nmsh curved elements.
Definition: mpi_types.f90:45
integer, public mpi_integer_size
Size of MPI type integer.
Definition: mpi_types.f90:63
type(mpi_datatype), public mpi_nmsh_zone
MPI derived type for Neko nmsh zone data.
Definition: mpi_types.f90:44
Neko binary mesh data.
Definition: nmsh_file.f90:34
subroutine nmsh_file_write(this, data, t)
Write a mesh from to a binary Neko nmsh file.
Definition: nmsh_file.f90:442
subroutine nmsh_file_read(this, data)
Load a mesh from a binary Neko nmsh file.
Definition: nmsh_file.f90:64
integer, parameter max_write_nel
Specifices the maximum number of elements any rank is allowed to write (for nmsh)....
Definition: nmsh_file.f90:52
subroutine nmsh_file_read_2d(this, msh)
Load a mesh from a binary Neko nmsh file.
Definition: nmsh_file.f90:254
Neko binary mesh format.
Definition: nmsh.f90:2
Implements a point.
Definition: point.f90:35
Implements a n-tuple.
Definition: tuple.f90:34
Utilities.
Definition: utils.f90:35
Load-balanced linear distribution .
Definition: datadist.f90:50
Base type for an element.
Definition: element.f90:44
A generic file handler.
Neko curve data.
Definition: nmsh.f90:39
Neko hex element data.
Definition: nmsh.f90:24
Neko quad element data.
Definition: nmsh.f90:19
Neko zone data.
Definition: nmsh.f90:29
Interface for Neko nmsh files.
Definition: nmsh_file.f90:54
A point in with coordinates .
Definition: point.f90:43
Integer based 4-tuple.
Definition: tuple.f90:69