1!
2! Copyright (C) by Argonne National Laboratory
3!     See COPYRIGHT in top-level directory
4!
5
6subroutine PMPIR_File_read_shared_f08ts(fh, buf, count, datatype, status, ierror)
7    use, intrinsic :: iso_c_binding, only : c_loc, c_associated
8    use, intrinsic :: iso_c_binding, only : c_int, c_ptr
9    use :: mpi_f08, only : MPI_File, MPI_Datatype, MPI_Status
10    use :: mpi_f08, only : MPI_STATUS_IGNORE, MPIR_C_MPI_STATUS_IGNORE, assignment(=)
11    use :: mpi_f08, only : MPI_File_f2c, MPI_File_c2f
12    use :: mpi_c_interface, only : c_File, c_Datatype
13    use :: mpi_c_interface, only : c_Status
14    use :: mpi_c_interface, only : MPIR_File_read_shared_cdesc
15
16    implicit none
17
18    type(MPI_File), intent(in) :: fh
19    type(*), dimension(..) :: buf
20    integer, intent(in) :: count
21    type(MPI_Datatype), intent(in) :: datatype
22    type(MPI_Status), target :: status
23    integer, optional, intent(out) :: ierror
24
25    integer(c_File) :: fh_c
26    integer(c_int) :: count_c
27    integer(c_Datatype) :: datatype_c
28    type(c_Status), target :: status_c
29    integer(c_int) :: ierror_c
30
31    fh_c = MPI_File_f2c(fh%MPI_VAL)
32    if (c_int == kind(0)) then
33        if (c_associated(c_loc(status), c_loc(MPI_STATUS_IGNORE))) then
34            ierror_c = MPIR_File_read_shared_cdesc(fh_c, buf, count, datatype%MPI_VAL, MPIR_C_MPI_STATUS_IGNORE)
35        else
36            ierror_c = MPIR_File_read_shared_cdesc(fh_c, buf, count, datatype%MPI_VAL, c_loc(status))
37        end if
38    else
39        count_c = count
40        datatype_c = datatype%MPI_VAL
41        if (c_associated(c_loc(status), c_loc(MPI_STATUS_IGNORE))) then
42            ierror_c = MPIR_File_read_shared_cdesc(fh_c, buf, count_c, datatype_c, MPIR_C_MPI_STATUS_IGNORE)
43        else
44            ierror_c = MPIR_File_read_shared_cdesc(fh_c, buf, count_c, datatype_c, c_loc(status_c))
45            status = status_c
46        end if
47    end if
48
49    if (present(ierror)) ierror = ierror_c
50
51end subroutine PMPIR_File_read_shared_f08ts
52