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