1!
2! Copyright (C) by Argonne National Laboratory
3!     See COPYRIGHT in top-level directory
4!
5
6subroutine MPI_Type_dup_f08(oldtype, newtype, ierror)
7    use, intrinsic :: iso_c_binding, only : c_int
8    use :: mpi_f08, only : MPI_Datatype
9    use :: mpi_c_interface, only : c_Datatype
10    use :: mpi_c_interface, only : MPIR_Type_dup_c
11
12    implicit none
13
14    type(MPI_Datatype), intent(in) :: oldtype
15    type(MPI_Datatype), intent(out) :: newtype
16    integer, optional, intent(out) :: ierror
17
18    integer(c_Datatype) :: oldtype_c
19    integer(c_Datatype) :: newtype_c
20    integer(c_int) :: ierror_c
21
22    if (c_int == kind(0)) then
23        ierror_c = MPIR_Type_dup_c(oldtype%MPI_VAL, newtype%MPI_VAL)
24    else
25        oldtype_c = oldtype%MPI_VAL
26        ierror_c = MPIR_Type_dup_c(oldtype_c, newtype_c)
27        newtype%MPI_VAL = newtype_c
28    end if
29
30    if (present(ierror)) ierror = ierror_c
31
32end subroutine MPI_Type_dup_f08
33