1!
2! Copyright (C) by Argonne National Laboratory
3!     See COPYRIGHT in top-level directory
4!
5
6subroutine PMPIR_File_set_info_f08(fh, info, ierror)
7    use, intrinsic :: iso_c_binding, only : c_int
8    use :: mpi_f08, only : MPI_File, MPI_Info
9    use :: mpi_f08, only : MPI_File_f2c, MPI_File_c2f
10    use :: mpi_c_interface, only : c_File, c_Info
11    use :: mpi_c_interface, only : MPIR_File_set_info_c
12
13    implicit none
14
15    type(MPI_File), intent(in) :: fh
16    type(MPI_Info), intent(in) :: info
17    integer, optional, intent(out) :: ierror
18
19    integer(c_File) :: fh_c
20    integer(c_Info) :: info_c
21    integer(c_int) :: ierror_c
22
23    fh_c = MPI_File_f2c(fh%MPI_VAL)
24    if (c_int == kind(0)) then
25        ierror_c = MPIR_File_set_info_c(fh_c, info%MPI_VAL)
26    else
27        info_c = info%MPI_VAL
28        ierror_c = MPIR_File_set_info_c(fh_c, info_c)
29    end if
30
31    if (present(ierror)) ierror = ierror_c
32
33end subroutine PMPIR_File_set_info_f08
34