Skip to content

Commit

Permalink
update mpif.h to use mpi
Browse files Browse the repository at this point in the history
  • Loading branch information
Sebastian Beyer committed Sep 16, 2024
1 parent 59f9b2b commit 0e5bfdc
Show file tree
Hide file tree
Showing 6 changed files with 9 additions and 13 deletions.
4 changes: 2 additions & 2 deletions src/MOD_PARTIT.F90
Original file line number Diff line number Diff line change
Expand Up @@ -5,12 +5,12 @@ module MOD_PARTIT
USE, intrinsic :: ISO_FORTRAN_ENV, only : int32
USE MOD_WRITE_BINARY_ARRAYS
USE MOD_READ_BINARY_ARRAYS
USE mpi
#if defined(_OPENMP)
USE OMP_LIB
#endif
IMPLICIT NONE
SAVE
include 'mpif.h'
integer, parameter :: MAX_LAENDERECK=16
integer, parameter :: MAX_NEIGHBOR_PARTITIONS=32

Expand Down Expand Up @@ -217,4 +217,4 @@ subroutine READ_T_PARTIT(partit, unit, iostat, iomsg)
read(unit, iostat=iostat, iomsg=iomsg) partit%pe_status
end subroutine READ_T_PARTIT

end module MOD_PARTIT
end module MOD_PARTIT
2 changes: 1 addition & 1 deletion src/fortran_utils.F90
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
! synopsis: basic Fortran utilities, no MPI, dependencies only to INTRINSIC modules
module fortran_utils
use mpi
implicit none

contains
Expand Down Expand Up @@ -48,7 +49,6 @@ function mpirank_to_txt(mpicomm) result(txt)
integer mype
integer npes
integer mpierr
include 'mpif.h'

call MPI_Comm_Rank(mpicomm, mype, mpierr)
call MPI_Comm_Size(mpicomm, npes, mpierr)
Expand Down
3 changes: 1 addition & 2 deletions src/gen_modules_partitioning.F90
Original file line number Diff line number Diff line change
Expand Up @@ -113,7 +113,7 @@ subroutine par_ex(COMM, mype, abort) ! finalizes MPI
#ifndef __oasis
if (present(abort)) then
if (mype==0) write(*,*) 'Run finished unexpectedly!'
call MPI_ABORT(MPI_COMM_WORLD, 1 )
call MPI_ABORT(MPI_COMM_WORLD, 1, error)
else
! TODO: this is where fesom standalone, ifsinterface etc get to
!1. there no abort actually even when model calls abort, and barrier may hang
Expand Down Expand Up @@ -580,4 +580,3 @@ subroutine status_check(partit)
call par_ex(partit%MPI_COMM_FESOM, partit%mype, 1)
endif
end subroutine status_check

3 changes: 1 addition & 2 deletions src/ifs_interface/mpp_io.F90
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@
!-----------------------------------------------------

MODULE mpp_io
USE mpi
#if defined(__MULTIO)
USE iom, only : iom_enable_multio, iom_initialize, iom_init_server, iom_finalize
#endif
Expand All @@ -30,7 +31,6 @@ MODULE mpp_io

SUBROUTINE mpp_io_init( iicomm, lio, irequired, iprovided, lmpi1 )

INCLUDE "mpif.h"
INTEGER, INTENT(INOUT) :: iicomm
LOGICAL, INTENT(INOUT) :: lio
INTEGER, INTENT(INOUT) :: irequired, iprovided
Expand Down Expand Up @@ -126,7 +126,6 @@ SUBROUTINE mpp_io_init_2( iicomm )
INTEGER :: icode, ierr, icolor, iicommx, iicommm, iicommo
INTEGER :: ji,inum
LOGICAL :: lcompp
INCLUDE "mpif.h"

! Construct multio server communicator

Expand Down
6 changes: 2 additions & 4 deletions src/io_restart.F90
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@ MODULE io_RESTART
use MOD_PARTIT
use MOD_PARSUP
use fortran_utils
use mpi
#if defined(__recom)
use recom_glovar
use recom_config
Expand Down Expand Up @@ -771,7 +772,6 @@ subroutine read_all_raw_restarts(mpicomm, mype)
integer fileunit
integer status
integer mpierr
include 'mpif.h'

if(mype == RAW_RESTART_METADATA_RANK) then
! read metadata info for the raw restart
Expand Down Expand Up @@ -860,7 +860,6 @@ subroutine finalize_restart()
!
!_______________________________________________________________________________
subroutine read_restart(path, filegroup, mpicomm, mype)
include 'mpif.h'
character(len=*), intent(in) :: path
type(restart_file_group), intent(inout) :: filegroup
integer, intent(in) :: mpicomm
Expand Down Expand Up @@ -1004,12 +1003,11 @@ function is_due(unit, frequency, istep) result(d)
! integer mype
! integer npes
! integer mpierr
! include 'mpif.h'
!
! call MPI_Comm_Rank(mpicomm, mype, mpierr)
! call MPI_Comm_Size(mpicomm, npes, mpierr)
! txt = int_to_txt_pad(mype,int(log10(real(npes)))+1) ! pad to the width of the number of processes
! end function
!!PS --> move this function also to fortran_utils.F90

end module
end module
4 changes: 2 additions & 2 deletions src/temp/MOD_PARTIT.F90
Original file line number Diff line number Diff line change
Expand Up @@ -5,9 +5,9 @@ module MOD_PARTIT
USE, intrinsic :: ISO_FORTRAN_ENV
USE MOD_WRITE_BINARY_ARRAYS
USE MOD_READ_BINARY_ARRAYS
USE mpi
IMPLICIT NONE
SAVE
include 'mpif.h'
integer, parameter :: MAX_LAENDERECK=16
integer, parameter :: MAX_NEIGHBOR_PARTITIONS=32

Expand Down Expand Up @@ -186,4 +186,4 @@ subroutine READ_T_PARTIT(partit, unit, iostat, iomsg)
read(unit, iostat=iostat, iomsg=iomsg) partit%pe_status
end subroutine READ_T_PARTIT

end module MOD_PARTIT
end module MOD_PARTIT

0 comments on commit 0e5bfdc

Please sign in to comment.