Skip to content

Commit 8a09731

Browse files
committed
fix ierr
1 parent 32f8c09 commit 8a09731

File tree

9 files changed

+63
-26
lines changed

9 files changed

+63
-26
lines changed

src/common/m_mpi_common.fpp

Lines changed: 26 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -24,7 +24,7 @@ module m_mpi_common
2424
2525
implicit none
2626
27-
integer, private :: ierr, v_size !<
27+
integer, private :: v_size
2828
$:GPU_DECLARE(create='[v_size]')
2929
!! Generic flags used to identify and report MPI errors
3030
@@ -88,6 +88,10 @@ contains
8888
!! available for the job and the local processor rank.
8989
impure subroutine s_mpi_initialize
9090
91+
#ifdef MFC_MPI
92+
integer :: ierr !< Generic flag used to identify and report MPI errors
93+
#endif
94+
9195
#ifndef MFC_MPI
9296
9397
! Serial run only has 1 processor
@@ -136,6 +140,7 @@ contains
136140
137141
! Generic loop iterator
138142
integer :: i, j
143+
integer :: ierr !< Generic flag used to identify and report MPI errors
139144
140145
!Altered system size for the lagrangian subgrid bubble model
141146
integer :: alt_sys
@@ -284,15 +289,16 @@ contains
284289
integer, intent(in) :: root ! Rank of the root process
285290
real(wp), allocatable, intent(out) :: gathered_vector(:) ! Gathered vector on the root process
286291
287-
integer :: i, local_ierr
292+
integer :: i
293+
integer :: ierr !< Generic flag used to identify and report MPI errors
288294
integer, allocatable :: recounts(:), displs(:)
289295
290296
#ifdef MFC_MPI
291297
292298
allocate (recounts(num_procs))
293299
294300
call MPI_GATHER(counts, 1, MPI_INTEGER, recounts, 1, MPI_INTEGER, root, &
295-
MPI_COMM_WORLD, local_ierr)
301+
MPI_COMM_WORLD, ierr)
296302
297303
allocate (displs(size(recounts)))
298304
@@ -304,7 +310,7 @@ contains
304310
305311
allocate (gathered_vector(sum(recounts)))
306312
call MPI_GATHERV(my_vector, counts, mpi_p, gathered_vector, recounts, displs, mpi_p, &
307-
root, MPI_COMM_WORLD, local_ierr)
313+
root, MPI_COMM_WORLD, ierr)
308314
#endif
309315
end subroutine s_mpi_gather_data
310316
@@ -314,6 +320,7 @@ contains
314320
real(wp), intent(inout) :: time_avg
315321
316322
#ifdef MFC_MPI
323+
integer :: ierr !< Generic flag used to identify and report MPI errors
317324
318325
call MPI_GATHER(time_avg, 1, mpi_p, proc_time(0), 1, mpi_p, 0, MPI_COMM_WORLD, ierr)
319326
@@ -365,6 +372,7 @@ contains
365372
366373
#ifdef MFC_SIMULATION
367374
#ifdef MFC_MPI
375+
integer :: ierr !< Generic flag used to identify and report MPI errors
368376
369377
! Reducing local extrema of ICFL, VCFL, CCFL and Rc numbers to their
370378
! global extrema and bookkeeping the results on the rank 0 processor
@@ -408,6 +416,7 @@ contains
408416
real(wp), intent(out) :: var_glb
409417
410418
#ifdef MFC_MPI
419+
integer :: ierr !< Generic flag used to identify and report MPI errors
411420
412421
! Performing the reduction procedure
413422
call MPI_ALLREDUCE(var_loc, var_glb, 1, mpi_p, &
@@ -430,6 +439,7 @@ contains
430439
real(wp), intent(out) :: var_glb
431440
432441
#ifdef MFC_MPI
442+
integer :: ierr !< Generic flag used to identify and report MPI errors
433443
434444
! Performing the reduction procedure
435445
call MPI_ALLREDUCE(var_loc, var_glb, 1, mpi_p, &
@@ -452,6 +462,7 @@ contains
452462
real(wp), intent(out) :: var_glb
453463
454464
#ifdef MFC_MPI
465+
integer :: ierr !< Generic flag used to identify and report MPI errors
455466
456467
! Performing the reduction procedure
457468
call MPI_ALLREDUCE(var_loc, var_glb, 1, mpi_p, &
@@ -472,6 +483,7 @@ contains
472483
real(wp), intent(inout) :: var_loc
473484
474485
#ifdef MFC_MPI
486+
integer :: ierr !< Generic flag used to identify and report MPI errors
475487
476488
! Temporary storage variable that holds the reduced minimum value
477489
real(wp) :: var_glb
@@ -507,6 +519,7 @@ contains
507519
real(wp), dimension(2), intent(inout) :: var_loc
508520
509521
#ifdef MFC_MPI
522+
integer :: ierr !< Generic flag used to identify and report MPI errors
510523
511524
real(wp), dimension(2) :: var_glb !<
512525
!! Temporary storage variable that holds the reduced maximum value
@@ -533,6 +546,10 @@ contains
533546
character(len=*), intent(in), optional :: prnt
534547
integer, intent(in), optional :: code
535548
549+
#ifdef MFC_MPI
550+
integer :: ierr !< Generic flag used to identify and report MPI errors
551+
#endif
552+
536553
if (present(prnt)) then
537554
print *, prnt
538555
call flush (6)
@@ -560,6 +577,7 @@ contains
560577
impure subroutine s_mpi_barrier
561578
562579
#ifdef MFC_MPI
580+
integer :: ierr !< Generic flag used to identify and report MPI errors
563581
564582
! Calling MPI_BARRIER
565583
call MPI_BARRIER(MPI_COMM_WORLD, ierr)
@@ -572,6 +590,7 @@ contains
572590
impure subroutine s_mpi_finalize
573591
574592
#ifdef MFC_MPI
593+
integer :: ierr !< Generic flag used to identify and report MPI errors
575594
576595
! Finalizing the MPI environment
577596
call MPI_FINALIZE(ierr)
@@ -609,6 +628,7 @@ contains
609628
integer :: pack_offset, unpack_offset
610629
611630
#ifdef MFC_MPI
631+
integer :: ierr !< Generic flag used to identify and report MPI errors
612632
613633
call nvtxStartRange("RHS-COMM-PACKBUF")
614634
@@ -1058,6 +1078,7 @@ contains
10581078
integer :: recon_order !< reconstruction order
10591079
10601080
integer :: i, j !< Generic loop iterators
1081+
integer :: ierr !< Generic flag used to identify and report MPI errors
10611082
10621083
if (num_procs == 1 .and. parallel_io) then
10631084
do i = 1, num_dims
@@ -1532,6 +1553,7 @@ contains
15321553
integer, intent(in) :: pbc_loc
15331554
15341555
#ifdef MFC_MPI
1556+
integer :: ierr !< Generic flag used to identify and report MPI errors
15351557
15361558
! MPI Communication in x-direction
15371559
if (mpi_dir == 1) then

src/post_process/m_data_output.fpp

Lines changed: 11 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -105,7 +105,7 @@ module m_data_output
105105
106106
! Generic error flags utilized in the handling, checking and the reporting
107107
! of the input and output operations errors with a formatted database file
108-
integer, private :: err, ierr
108+
integer, private :: err
109109
110110
contains
111111
@@ -477,6 +477,8 @@ contains
477477
! Generic string used to store the location of a particular file
478478
character(LEN=len_trim(case_dir) + 3*name_len) :: file_loc
479479
480+
integer :: ierr !< Generic flag used to identify and report database errors
481+
480482
! Silo-HDF5 Database Format
481483
482484
if (format == 1) then
@@ -650,6 +652,8 @@ contains
650652
! Generic loop iterator
651653
integer :: i
652654
655+
integer :: ierr !< Generic flag used to identify and report database errors
656+
653657
! Silo-HDF5 Database Format
654658
655659
if (format == 1 .and. n > 0) then
@@ -860,6 +864,8 @@ contains
860864
! Generic loop iterator
861865
integer :: i, j, k
862866
867+
integer :: ierr !< Generic flag used to identify and report database errors
868+
863869
! Silo-HDF5 Database Format
864870
865871
if (format == 1) then
@@ -1106,7 +1112,8 @@ contains
11061112
logical :: lg_bub_file, file_exist
11071113
11081114
integer, dimension(2) :: gsizes, lsizes, start_idx_part
1109-
integer :: ifile, ierr, tot_data
1115+
integer :: ifile, tot_data
1116+
integer :: ierr !< Generic flag used to identify and report MPI errors
11101117
integer :: i
11111118
11121119
write (file_loc, '(A,I0,A)') 'lag_bubbles_mpi_io_', t_step, '.dat'
@@ -1392,6 +1399,8 @@ contains
13921399
! domain, because one associated with the entire domain is
13931400
! not generated.
13941401
1402+
integer :: ierr !< Generic flag used to identify and report database errors
1403+
13951404
! Silo-HDF5 database format
13961405
if (format == 1) then
13971406
ierr = DBCLOSE(dbfile)

src/post_process/m_global_parameters.fpp

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -197,8 +197,6 @@ module m_global_parameters
197197
integer :: mpi_info_int
198198
!> @}
199199

200-
integer, private :: ierr
201-
202200
type(physical_parameters), dimension(num_fluids_max) :: fluid_pp !<
203201
!! Database of the physical parameters of each of the fluids that is present
204202
!! in the flow. These include the stiffened gas equation of state parameters,
@@ -904,6 +902,10 @@ contains
904902
!> Subroutine to initialize parallel infrastructure
905903
impure subroutine s_initialize_parallel_io
906904

905+
#ifdef MFC_MPI
906+
integer :: ierr !< Generic flag used to identify and report MPI errors
907+
#endif
908+
907909
num_dims = 1 + min(1, n) + min(1, p)
908910

909911
if (mhd) then

src/post_process/m_mpi_proxy.fpp

Lines changed: 6 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -31,11 +31,6 @@ module m_mpi_proxy
3131
integer, allocatable, dimension(:) :: displs
3232
!> @}
3333
34-
!> @name Generic flags used to identify and report MPI errors
35-
!> @{
36-
integer, private :: ierr
37-
!> @}
38-
3934
contains
4035
4136
!> Computation of parameters, allocation procedures, and/or
@@ -45,6 +40,7 @@ contains
4540
#ifdef MFC_MPI
4641
4742
integer :: i !< Generic loop iterator
43+
integer :: ierr !< Generic flag used to identify and report MPI errors
4844
4945
! Allocating and configuring the receive counts and the displacement
5046
! vector variables used in variable-gather communication procedures.
@@ -85,6 +81,7 @@ contains
8581
8682
#ifdef MFC_MPI
8783
integer :: i !< Generic loop iterator
84+
integer :: ierr !< Generic flag used to identify and report MPI errors
8885
8986
! Logistics
9087
call MPI_BCAST(case_dir, len(case_dir), MPI_CHARACTER, 0, MPI_COMM_WORLD, ierr)
@@ -150,6 +147,7 @@ contains
150147
real(wp), dimension(1:, 0:), intent(INOUT) :: spatial_extents
151148

152149
#ifdef MFC_MPI
150+
integer :: ierr !< Generic flag used to identify and report MPI errors
153151

154152
! Simulation is 3D
155153
if (p > 0) then
@@ -267,6 +265,7 @@ contains
267265
impure subroutine s_mpi_defragment_1d_grid_variable
268266

269267
#ifdef MFC_MPI
268+
integer :: ierr !< Generic flag used to identify and report MPI errors
270269

271270
! Silo-HDF5 database format
272271
if (format == 1) then
@@ -306,6 +305,7 @@ contains
306305
real(wp), dimension(1:2, 0:num_procs - 1), intent(inout) :: data_extents
307306

308307
#ifdef MFC_MPI
308+
integer :: ierr !< Generic flag used to identify and report MPI errors
309309

310310
! Minimum flow variable extent
311311
call MPI_GATHERV(minval(q_sf), 1, mpi_p, &
@@ -333,6 +333,7 @@ contains
333333
real(wp), dimension(0:m), intent(inout) :: q_root_sf
334334

335335
#ifdef MFC_MPI
336+
integer :: ierr !< Generic flag used to identify and report MPI errors
336337

337338
! Gathering the sub-domain flow variable data from all the processes
338339
! and putting it back together for the entire computational domain

src/pre_process/m_global_parameters.fpp

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -188,8 +188,6 @@ module m_global_parameters
188188

189189
#endif
190190

191-
integer, private :: ierr
192-
193191
! Initial Condition Parameters
194192
integer :: num_patches !< Number of patches composing initial condition
195193

@@ -931,6 +929,10 @@ contains
931929

932930
impure subroutine s_initialize_parallel_io
933931

932+
#ifdef MFC_MPI
933+
integer :: ierr !< Generic flag used to identify and report MPI errors
934+
#endif
935+
934936
num_dims = 1 + min(1, n) + min(1, p)
935937

936938
if (mhd) then

src/pre_process/m_mpi_proxy.fpp

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -23,9 +23,6 @@ module m_mpi_proxy
2323
2424
implicit none
2525
26-
integer, private :: ierr !<
27-
!! Generic flag used to identify and report MPI errors
28-
2926
contains
3027
!> Since only processor with rank 0 is in charge of reading
3128
!! and checking the consistency of the user provided inputs,
@@ -38,6 +35,8 @@ contains
3835
3936
! Generic loop iterator
4037
integer :: i
38+
! Generic flag used to identify and report MPI errors
39+
integer :: ierr
4140
4241
! Logistics
4342
call MPI_BCAST(case_dir, len(case_dir), MPI_CHARACTER, 0, MPI_COMM_WORLD, ierr)

src/simulation/m_fftw.fpp

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -58,7 +58,6 @@ module m_fftw
5858
#else
5959
type(c_ptr) :: fwd_plan_gpu, bwd_plan_gpu
6060
#endif
61-
integer :: ierr
6261

6362
integer, allocatable :: gpu_fft_size(:), iembed(:), oembed(:)
6463

@@ -82,6 +81,7 @@ contains
8281
batch_size = x_size*sys_size
8382

8483
#if defined(MFC_OpenACC)
84+
integer :: ierr !< Generic flag used to identify and report GPU errors
8585
rank = 1; istride = 1; ostride = 1
8686

8787
allocate (gpu_fft_size(1:rank), iembed(1:rank), oembed(1:rank))
@@ -138,6 +138,7 @@ contains
138138
! Restrict filter to processors that have cells adjacent to axis
139139
if (bc_y%beg >= 0) return
140140
#if defined(MFC_OpenACC)
141+
integer :: ierr !< Generic flag used to identify and report GPU errors
141142

142143
$:GPU_PARALLEL_LOOP(collapse=3)
143144
do k = 1, sys_size
@@ -302,6 +303,7 @@ contains
302303
impure subroutine s_finalize_fftw_module
303304

304305
#if defined(MFC_OpenACC)
306+
integer :: ierr !< Generic flag used to identify and report GPU errors
305307
@:DEALLOCATE(data_real_gpu, data_fltr_cmplx_gpu, data_cmplx_gpu)
306308
#if defined(__PGI)
307309

src/simulation/m_global_parameters.fpp

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -244,8 +244,6 @@ module m_global_parameters
244244
integer :: mpi_info_int
245245
!> @}
246246

247-
integer, private :: ierr
248-
249247
!> @name Annotations of the structure of the state and flux vectors in terms of the
250248
!! size and the configuration of the system of equations to which they belong
251249
!> @{
@@ -1318,6 +1316,10 @@ contains
13181316
!> Initializes parallel infrastructure
13191317
impure subroutine s_initialize_parallel_io
13201318
1319+
#ifdef MFC_MPI
1320+
integer :: ierr !< Generic flag used to identify and report MPI errors
1321+
#endif
1322+
13211323
#:if not MFC_CASE_OPTIMIZATION
13221324
num_dims = 1 + min(1, n) + min(1, p)
13231325

0 commit comments

Comments
 (0)