MOAB: Mesh Oriented datABase  (version 5.5.0)
imoab_ptest.F
Go to the documentation of this file.
1 C push parallel mesh into moab, using iMoab API, F77 version
2 C
3 C This program shows how to push a mesh into MOAB in parallel using iMoab, with sufficient
4 C information to resolve boundary sharing and exchange a layer of ghost information.
5 C
6 C After resolving the sharing, mesh is saved to a file, then read back again, in parallel
7 C the mesh is a quad mesh, 2x2 on each task,
8 C by default, this test is run on 2 processors
9 
10 C Test is similar to itaps/iMeshP_unit_tests.cpp
11 C
12 C
13 C Create a mesh:
14 C Groups of four quads will be arranged into parts as follows:
15 C +------+------+------+------+------+-----
16 C | | |
17 C | | |
18 C + Part 0 + Part 2 + Part 4
19 C | | |
20 C | | |
21 C +------+------+------+------+------+-----
22 C | | |
23 C | | |
24 C + Part 1 + Part 3 + Part 5
25 C | | |
26 C | | |
27 C +------+------+------+------+------+-----
28 C
29 C Vertices will be enumerated as follows:
30 C 1------6-----11-----16-----21-----26----- > x x from 0, 1, 2
31 C | | |
32 C | | |
33 C 2 7 12 17 22 27
34 C | | |
35 C | | |
36 C 3------8-----13-----18-----23-----28-----
37 C | | |
38 C | | |
39 C 4 9 14 19 24 29
40 C | | |
41 C | | |
42 C 5-----10-----15-----20-----25-----30-----
43 C |
44 C y varies from 0 to 4
45 C
46 C Processor 0 will have vertices 1, 2, 3, 6, 7, 8, 11, 12, 13
47 C and 4 quads, with ids from 1 to 4, and connectivity
48 C 1, 2, 7, 6; 2, 3, 8, 7; 6 ,7, 12, 11; 7, 8, 13, 12
49 C Processor 1 will have vertices 3, 4, 5, 8, 9, 10, 13, 14, 15
50 C and 4 quads, with ids from 5 to 8, and connectivity
51 C 3, 4, 8, 9; 4, 5, 10, 9; 8, 9, 14, 13; 9, 10, 15, 14,
52 C and so on
53 C
54 C Vertex Global IDs will be used to resolve sharing
55 C
56 C Element IDs will be [4*rank+1,4*rank+5]
57 C #define ERROR(rval) if (0 .ne. rval) call exit(1)
58 
59 
60  SUBROUTINE errorout(ierr, message)
61  integer ierr
62  character*(*) message
63  if (ierr.ne.0) then
64  print *, message
65  call exit (1)
66  end if
67  return
68  end
69 
70 #include "moab/MOABConfig.h"
71  program imoabpar_test
72 C implicit none
73 
74  use imoab
75 #include "mpif.h"
76 
77  integer ierr, my_id, num_procs, pid, i, ix, iy, numv, nume
78  integer dime, lco, mbtype, blockid, npe
79  integer compid
80  character :: appname*10
81  character :: outfile*100, wopts*100
82 C coordinates for 9 vertices
83  double precision coordinates(27) , coords_core(27), deltax, deltay
84  integer ids(9)
85  integer connec(16)
86 C used for ghosting
87  integer dimgh, bridge, num_layers
88 
89  data coords_core/ 0., 0., 0.,
90  & 0., 1., 0.,
91  & 0., 2., 0.,
92  & 1., 0., 0.,
93  & 1., 1., 0.,
94  & 1., 2., 0.,
95  & 2., 0., 0.,
96  & 2., 1., 0.,
97  & 2., 2., 0./
98  data ids/1, 2, 3, 6, 7, 8, 11, 12, 13/
99  data connec/ 1, 2, 5, 4,
100  & 2, 3, 6, 5,
101  & 4, 5, 8, 7,
102  & 5, 6, 9, 8/
103 
104  call mpi_init ( ierr )
105  call errorout(ierr, 'fail to initialize MPI')
106 
107  ierr = imoab_initialize()
108  call errorout(ierr, 'fail to initialize iMOAB')
109 
110  call mpi_comm_rank (mpi_comm_world, my_id, ierr)
111  call errorout(ierr, 'fail to get MPI rank')
112 
113  call mpi_comm_size (mpi_comm_world, num_procs, ierr)
114  call errorout(ierr, 'fail to get MPI size')
115 
116  ! find out MY process ID, and how many processes were started.
117  if (my_id .eq. 0) then
118  print *, " I'm process ", my_id, " out of ",
119  & num_procs, " processes."
120  end if
121 
122  ! give a component id
123  compid = 7
124  appname = 'IMTEST'//char(0)
125  ierr = imoab_registerapplication(appname, mpi_comm_world,
126  & compid, pid)
127  call errorout(ierr, 'fail to initialize fortran app')
128 
129  ! create first 9 vertices, in a square 3x3;
130  deltax=(my_id/2) * 2.
131  deltay = mod(my_id, 2) * 2.
132  ix = (my_id/2) * 10
133  iy = mod(my_id,2) * 2
134  do i=1,9
135  coordinates( 3*(i-1) + 1 ) = coords_core(3*(i-1)+1) + deltax
136  coordinates( 3*(i-1) + 2 ) = coords_core(3*(i-1)+2) + deltay
137  coordinates( 3*(i-1) + 3 ) = coords_core(3*(i-1)+3)
138 
139  ! translate the ids too, by multiples of 10 or add 2
140  ids(i) = ids(i) + ix+iy
141  enddo
142  numv = 9
143  nume = 4
144  lco = numv*3
145  dime = 3
146  ierr = imoab_createvertices(pid, lco, dime, coordinates);
147  call errorout(ierr, 'fail to create vertices')
148 
149  ! create now 4 quads with those 9 vertices
150  mbtype = 3
151  blockid = 100
152  npe = 4
153  ierr = imoab_createelements(pid, nume, mbtype, npe,
154  & connec, blockid)
155  call errorout(ierr, 'fail to create quads')
156 
157  ierr = imoab_resolvesharedentities( pid, numv, ids );
158  call errorout(ierr, 'fail to resolve shared entities')
159 
160  ! see ghost elements
161  dimgh = 2 ! will ghost quads, topological dim 2
162  bridge = 0 ! use vertex as bridge
163  num_layers = 1 ! so far, one layer only
164  ierr = imoab_determineghostentities( pid, dimgh, num_layers,
165  & bridge)
166  call errorout(ierr, 'fail to determine ghosts')
167 
168  ! write out the mesh file to disk, in parallel, if h5m
169 #ifdef MOAB_HAVE_HDF5
170  outfile = 'wholeF.h5m'//char(0)
171  wopts = 'PARALLEL=WRITE_PART'//char(0)
172  ierr = imoab_writemesh(pid, outfile, wopts)
173  call errorout(ierr, 'fail to write the mesh file')
174 #endif
175 
176  ! all done. de-register and finalize
177  ierr = imoab_deregisterapplication(pid)
178  call errorout(ierr, 'fail to deregister application')
179 
180  ierr = imoab_finalize()
181  call errorout(ierr, 'fail to finalize iMOAB')
182 
183 
184  call mpi_finalize ( ierr )
185  call errorout(ierr, 'fail to finalize MPI')
186 
187  end
188