1!
2! Copyright (C) by Argonne National Laboratory
3!     See COPYRIGHT in top-level directory
4!
5
6subroutine MPI_File_write_at_all_begin_f08ts(fh, offset, buf, count, datatype, ierror)
7    use, intrinsic :: iso_c_binding, only : c_int
8    use :: mpi_f08, only : MPI_File, MPI_Datatype
9    use :: mpi_f08, only : MPI_OFFSET_KIND
10    use :: mpi_f08, only : MPI_File_f2c, MPI_File_c2f
11    use :: mpi_c_interface, only : c_File, c_Datatype
12    use :: mpi_c_interface, only : MPIR_File_write_at_all_begin_cdesc
13
14    implicit none
15
16    type(MPI_File), intent(in) :: fh
17    integer(MPI_OFFSET_KIND), intent(in) :: offset
18    type(*), dimension(..), intent(in) :: buf
19    integer, intent(in) :: count
20    type(MPI_Datatype), intent(in) :: datatype
21    integer, optional, intent(out) :: ierror
22
23    integer(c_File) :: fh_c
24    integer(MPI_OFFSET_KIND) :: offset_c
25    integer(c_int) :: count_c
26    integer(c_Datatype) :: datatype_c
27    integer(c_int) :: ierror_c
28
29    fh_c = MPI_File_f2c(fh%MPI_VAL)
30    if (c_int == kind(0)) then
31        ierror_c = MPIR_File_write_at_all_begin_cdesc(fh_c, offset, buf, count, datatype%MPI_VAL)
32    else
33        offset_c = offset
34        count_c = count
35        datatype_c = datatype%MPI_VAL
36        ierror_c = MPIR_File_write_at_all_begin_cdesc(fh_c, offset_c, buf, count_c, datatype_c)
37    end if
38
39    if (present(ierror)) ierror = ierror_c
40
41end subroutine MPI_File_write_at_all_begin_f08ts
42