Skip to content

Commit

Permalink
Merge pull request #54 from jubich/update_mpi_import
Browse files Browse the repository at this point in the history
Update all module imports
  • Loading branch information
bhourahine authored Dec 13, 2023
2 parents ab77b43 + 17e157f commit 9d3b1de
Show file tree
Hide file tree
Showing 22 changed files with 94 additions and 80 deletions.
1 change: 0 additions & 1 deletion lib/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,6 @@ set(sources-fpp
mpifx_barrier.fpp
mpifx_bcast.fpp
mpifx_comm.fpp
mpifx_common.fpp
mpifx_constants.fpp
mpifx_finalize.fpp
mpifx_gather.fpp
Expand Down
1 change: 0 additions & 1 deletion lib/meson.build
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,6 @@ sources_fpp = files(
'mpifx_barrier.fpp',
'mpifx_bcast.fpp',
'mpifx_comm.fpp',
'mpifx_common.fpp',
'mpifx_constants.fpp',
'mpifx_finalize.fpp',
'mpifx_gather.fpp',
Expand Down
4 changes: 3 additions & 1 deletion lib/mpifx_abort.fpp
Original file line number Diff line number Diff line change
@@ -1,6 +1,8 @@
!> Contains wrapper for \c MPI_ABORT.
module mpifx_abort_module
use mpifx_common_module
use mpi
use mpifx_comm_module, only : mpifx_comm
use mpifx_helper_module, only : handle_errorflag
implicit none
private

Expand Down
4 changes: 3 additions & 1 deletion lib/mpifx_allgather.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,9 @@

!> Contains wrapper for \c MPI_ALLGATHER
module mpifx_allgather_module
use mpifx_common_module
use mpi
use mpifx_comm_module, only : mpifx_comm
use mpifx_helper_module, only : dp, handle_errorflag, sp
implicit none
private

Expand Down
4 changes: 3 additions & 1 deletion lib/mpifx_allgatherv.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -106,7 +106,9 @@

!> Contains wrapper for \c MPI_allgatherv
module mpifx_allgatherv_module
use mpifx_common_module
use mpi
use mpifx_comm_module, only : mpifx_comm
use mpifx_helper_module, only : dp, handle_errorflag, sp
implicit none
private

Expand Down
6 changes: 4 additions & 2 deletions lib/mpifx_allreduce.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,9 @@

!> Contains wrapper for \c MPI_ALLREDUCE.
module mpifx_allreduce_module
use mpifx_common_module
use mpi
use mpifx_comm_module, only : mpifx_comm
use mpifx_helper_module, only : dp, handle_errorflag, sp
implicit none
private

Expand Down Expand Up @@ -86,7 +88,7 @@ module mpifx_allreduce_module
!! write(*, "(I2.2,'-',I3.3,'|',1X,A,3F8.2)") 4, mycomm%rank, &
!! & "Obtained result (prod):", resvalr(:)
!! call mpifx_finalize()
!!
!!
!! end program test_allreduceip
!!
interface mpifx_allreduceip
Expand Down
12 changes: 7 additions & 5 deletions lib/mpifx_barrier.fpp
Original file line number Diff line number Diff line change
@@ -1,8 +1,10 @@
#:include 'mpifx.fypp'

!> Contains wrapper for \c MPI_BARRIER.
!> Contains wrapper for \c MPI_BARRIER.
module mpifx_barrier_module
use mpifx_common_module
use mpi
use mpifx_comm_module, only : mpifx_comm
use mpifx_helper_module, only : handle_errorflag
implicit none
private

Expand Down Expand Up @@ -35,12 +37,12 @@ contains
subroutine mpifx_barrier(mycomm, error)
type(mpifx_comm), intent(in) :: mycomm
integer, intent(out), optional :: error

integer :: error0

call mpi_barrier(mycomm%id, error0)
call handle_errorflag(error0, "MPI_BARRIER in mpifx_barrier", error)

end subroutine mpifx_barrier


Expand Down
6 changes: 4 additions & 2 deletions lib/mpifx_bcast.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,9 @@

!> Contains wrapper for \c MPI_BCAST.
module mpifx_bcast_module
use mpifx_common_module
use mpi
use mpifx_comm_module, only : mpifx_comm
use mpifx_helper_module, only : dp, getoptarg, handle_errorflag, sp
implicit none
private

Expand Down Expand Up @@ -80,7 +82,7 @@ contains

#:enddef mpifx_bcast_template


#:for TYPE in TYPES
#:for RANK in RANKS

Expand Down
2 changes: 1 addition & 1 deletion lib/mpifx_comm.fpp
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
!> Contains the extended MPI communicator.
module mpifx_comm_module
use mpi
use mpifx_helper_module
use mpifx_helper_module, only : getoptarg, handle_errorflag
implicit none
private

Expand Down
13 changes: 0 additions & 13 deletions lib/mpifx_common.fpp

This file was deleted.

8 changes: 5 additions & 3 deletions lib/mpifx_finalize.fpp
Original file line number Diff line number Diff line change
@@ -1,6 +1,8 @@
!> Contains wrapper for \c MPI_FINALIZE.
!> Contains wrapper for \c MPI_FINALIZE.
module mpifx_finalize_module
use mpifx_common_module
use mpi
use mpifx_comm_module, only : mpifx_comm
use mpifx_helper_module, only : handle_errorflag
implicit none
private

Expand Down Expand Up @@ -39,5 +41,5 @@ contains
call handle_errorflag(error0, "Error: mpi_finalize() in mpifx_finalize()", error)

end subroutine mpifx_finalize

end module mpifx_finalize_module
22 changes: 12 additions & 10 deletions lib/mpifx_gather.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,9 @@

!> Contains wrapper for \c MPI_GATHER
module mpifx_gather_module
use mpifx_common_module
use mpi
use mpifx_comm_module, only : mpifx_comm
use mpifx_helper_module, only : dp, getoptarg, handle_errorflag, sp
implicit none
private

Expand All @@ -30,17 +32,17 @@ module mpifx_gather_module
!! program test_gather
!! use libmpifx_module
!! implicit none
!!
!!
!! type(mpifx_comm) :: mycomm
!! integer :: send0
!! integer, allocatable :: send1(:)
!! integer, allocatable :: recv1(:), recv2(:,:)
!! character(100) :: formstr
!! character(*), parameter :: label = "(I2.2,'-',I3.3,'|',1X"
!!
!!
!! call mpifx_init()
!! call mycomm%init()
!!
!!
!! ! I0 -> I1
!! send0 = mycomm%rank * 2 ! Arbitrary number to send
!! if (mycomm%lead) then
Expand All @@ -55,7 +57,7 @@ module mpifx_gather_module
!! write(*, *) mycomm%rank, "Recv1 buffer:", recv1(:)
!! end if
!! deallocate(recv1)
!!
!!
!! ! I1 -> I1
!! allocate(send1(2))
!! send1(:) = [ mycomm%rank, mycomm%rank + 1 ] ! Arbitrary numbers
Expand All @@ -70,7 +72,7 @@ module mpifx_gather_module
!! if (mycomm%lead) then
!! write(*, *) mycomm%rank, "Recv1 buffer:", recv1
!! end if
!!
!!
!! ! I1 -> I2
!! send1(:) = [ mycomm%rank, mycomm%rank + 1 ]
!! if (mycomm%lead) then
Expand All @@ -82,9 +84,9 @@ module mpifx_gather_module
!! if (mycomm%lead) then
!! write(*, *) mycomm%rank, "Recv2 buffer:", recv2
!! end if
!!
!!
!! call mpifx_finalize()
!!
!!
!! end program test_gather
!!
interface mpifx_gather
Expand All @@ -100,7 +102,7 @@ module mpifx_gather_module
#:endfor
#:endfor
end interface mpifx_gather

contains

#:def mpifx_gather_dr0_template(SUFFIX, TYPE, MPITYPE, RANK, HASLENGTH)
Expand Down Expand Up @@ -135,7 +137,7 @@ contains
call mpi_gather(send, ${COUNT}$, ${MPITYPE}$, recv, ${COUNT}$, ${MPITYPE}$, root0,&
& mycomm%id, error0)
call handle_errorflag(error0, "MPI_GATHER in mpifx_gather_${SUFFIX}$", error)

end subroutine mpifx_gather_${SUFFIX}$

#:enddef mpifx_gather_dr0_template
Expand Down
4 changes: 3 additions & 1 deletion lib/mpifx_gatherv.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -131,7 +131,9 @@

!> Contains wrapper for \c MPI_gatherv
module mpifx_gatherv_module
use mpifx_common_module
use mpi
use mpifx_comm_module, only : mpifx_comm
use mpifx_helper_module, only : dp, handle_errorflag, sp
implicit none
private

Expand Down
1 change: 0 additions & 1 deletion lib/mpifx_get_processor_name.fpp
Original file line number Diff line number Diff line change
@@ -1,6 +1,5 @@
!> Contains the extended MPI communicator.
module mpifx_get_processor_name_module
use mpifx_helper_module
use mpi
implicit none
private
Expand Down
2 changes: 1 addition & 1 deletion lib/mpifx_helper.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@
module mpifx_helper_module
use mpi
use, intrinsic :: iso_fortran_env, only : stderr => error_unit
use mpifx_constants_module
use mpifx_constants_module, only : MPIFX_ASSERT_FAILED, MPIFX_UNHANDLED_ERROR
implicit none
private

Expand Down
6 changes: 4 additions & 2 deletions lib/mpifx_init.fpp
Original file line number Diff line number Diff line change
@@ -1,7 +1,9 @@
!> Contains wrapper for \c MPI_INIT.
module mpifx_init_module
use mpifx_common_module
use mpifx_constants_module
use mpi
use mpifx_comm_module, only : mpifx_comm
use mpifx_constants_module, only : MPIFX_UNHANDLED_ERROR
use mpifx_helper_module, only : handle_errorflag
implicit none
private

Expand Down
12 changes: 7 additions & 5 deletions lib/mpifx_recv.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,9 @@

!> Contains wrapper for \c MPI_RECV
module mpifx_recv_module
use mpifx_common_module
use mpi
use mpifx_comm_module, only : mpifx_comm
use mpifx_helper_module, only : dp, sp
implicit none
private

Expand All @@ -15,7 +17,7 @@ module mpifx_recv_module
!!
!! \details All functions have the same argument list only differing in the
!! type and rank of the second argument. The second argument can be of
!! type integer (i), real (s), double precision (d), complex (c),
!! type integer (i), real (s), double precision (d), complex (c),
!! double complex (z), logical (b) and character (h). Its rank can vary from
!! zero (scalar) up to the maximum rank.
!!
Expand Down Expand Up @@ -60,7 +62,7 @@ contains
#:def mpifx_recv_template(SUFFIX, TYPE, MPITYPE, RANK, HASLENGTH)

#:assert RANK >= 0

!> Receives a message from a given process.
!! \param mycomm MPI descriptor.
!! \param msg Msg to be received.
Expand Down Expand Up @@ -105,6 +107,6 @@ contains
$:mpifx_recv_template(SUFFIX, FTYPE, MPITYPE, RANK, HASLENGTH)

#:endfor
#:endfor
#:endfor

end module mpifx_recv_module
24 changes: 13 additions & 11 deletions lib/mpifx_reduce.fpp
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,9 @@

!> Contains wrapper for \c MPI_REDUCE.
module mpifx_reduce_module
use mpifx_common_module
use mpi
use mpifx_comm_module, only : mpifx_comm
use mpifx_helper_module, only : dp, getoptarg, handle_errorflag, sp
implicit none
private

Expand All @@ -13,8 +15,8 @@ module mpifx_reduce_module
!> Reduces a scalar/array on a given node.
!!
!! \details All functions have the same argument list only differing in the
!! type and rank of the second and third arguments. The second and third
!! arguments can be of type integer (i), real (s), double precision (d),
!! type and rank of the second and third arguments. The second and third
!! arguments can be of type integer (i), real (s), double precision (d),
!! complex (c), double complex (z) or logical (l). Their rank can vary from
!! zero (scalars) up to the maximum rank. Both arguments must be of same
!! type and rank.
Expand Down Expand Up @@ -42,7 +44,7 @@ module mpifx_reduce_module
!! write(*, "(I2.2,'-',I3.3,'|',1X,A,3F8.2)") 4, mycomm%rank, &
!! & "Obtained result (prod):", resvalr(:)
!! call mpifx_finalize()
!!
!!
!! end program test_reduce
!!
interface mpifx_reduce
Expand Down Expand Up @@ -86,9 +88,9 @@ module mpifx_reduce_module
!! write(*, "(I2.2,'-',I3.3,'|',1X,A,3F8.2)") 4, mycomm%rank, &
!! & "Obtained result (prod):", resvalr(:)
!! call mpifx_finalize()
!!
!!
!! end program test_reduceip
!!
!!
interface mpifx_reduceip
#:for TYPE in TYPES
#:for RANK in RANKS
Expand Down Expand Up @@ -129,16 +131,16 @@ contains

call mpi_reduce(orig, reduced, ${COUNT}$, ${MPITYPE}$, reduceop, root0, mycomm%id, error0)
call handle_errorflag(error0, "MPI_REDUCE in mpifx_reduce_${SUFFIX}$", error)

end subroutine mpifx_reduce_${SUFFIX}$

#:enddef mpifx_reduce_template


#:def mpifx_reduceip_template(SUFFIX, TYPE, MPITYPE, RANK)

#:assert RANK >= 0

!> Reduces results on one process (type ${SUFFIX}$).
!!
!! \param mycomm MPI communicator.
Expand Down Expand Up @@ -170,12 +172,12 @@ contains
& error0)
end if
call handle_errorflag(error0, "MPI_REDUCE in mpifx_reduce_${SUFFIX}$", error)

end subroutine mpifx_reduceip_${SUFFIX}$

#:enddef mpifx_reduceip_template


#:for TYPE in TYPES
#:for RANK in RANKS

Expand Down
Loading

0 comments on commit 9d3b1de

Please sign in to comment.