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