1!
2! Copyright (C) by Argonne National Laboratory
3!     See COPYRIGHT in top-level directory
4!
5
6subroutine PMPIR_Type_match_size_f08(typeclass, size, datatype, 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_match_size_c
11
12    implicit none
13
14    integer, intent(in) :: typeclass
15    integer, intent(in) :: size
16    type(MPI_Datatype), intent(out) :: datatype
17    integer, optional, intent(out) :: ierror
18
19    integer(c_int) :: typeclass_c
20    integer(c_int) :: size_c
21    integer(c_Datatype) :: datatype_c
22    integer(c_int) :: ierror_c
23
24    if (c_int == kind(0)) then
25        ierror_c = MPIR_Type_match_size_c(typeclass, size, datatype%MPI_VAL)
26    else
27        typeclass_c = typeclass
28        size_c = size
29        ierror_c = MPIR_Type_match_size_c(typeclass_c, size_c, datatype_c)
30        datatype%MPI_VAL = datatype_c
31    end if
32
33    if (present(ierror)) ierror = ierror_c
34
35end subroutine PMPIR_Type_match_size_f08
36