Why MPI_SIZEOF not working for Fortran complex type?

Deal all,

I have a similar question as the one posted by another person on SO,

The thing is, this MPI_SIZEOF not working for Fortran complex type is not only for intel Fortran and MPI, but also for gfortran mpich at least on Ubuntu.

As a minimal working example as below. You know, in MPI, I also want to mimic the selected_int_kind trick in Fortran to have portable MPI version of i4, i8, r8, complex(r8).

  module mympi
  use mpi
  implicit none
  integer, private, parameter :: i4=selected_int_kind(9)
  integer, private, parameter :: i8=selected_int_kind(15)
  integer, private, parameter :: r8=selected_real_kind(15,9)
  integer, private, save :: mpii4,mpii8,mpir8,mpic8
contains
   subroutine init0 ! define mpii4,mpii8,mpir8,mpic8 type as their Fortran brothers.
   integer :: ierror,isize
   integer(kind=i4) :: itest4
   integer(kind=i8) :: itest8
   real(kind=r8) :: rtest8
   complex(kind=r8) :: ctest8 !!!!!problem!!!!!!
   call mpi_sizeof(itest4,isize,ierror)
   call mpi_type_match_size(mpi_typeclass_integer,isize,mpii4,ierror)
   call mpi_sizeof(itest8,isize,ierror)
   call mpi_type_match_size(mpi_typeclass_integer,isize,mpii8,ierror)
   call mpi_sizeof(rtest8,isize,ierror)
   call mpi_type_match_size(mpi_typeclass_real,isize,mpir8,ierror)
   call mpi_sizeof(ctest8,isize,ierror) !!!problem!!!!
   call mpi_type_match_size(mpi_typeclass_complex,isize,mpic8,ierror)!!!!problem!!!!
   return
   end subroutine init0
  end module mympi

So far, I am successful for i4, i8, r8 as below, by using mpi_sizeof() intrinsic subroutine, I got mine mpii4, mpii8, and mpir8,

   call mpi_sizeof(itest4,isize,ierror)
   call mpi_type_match_size(mpi_typeclass_integer,isize,mpii4,ierror)
   call mpi_sizeof(itest8,isize,ierror)
   call mpi_type_match_size(mpi_typeclass_integer,isize,mpii8,ierror)
   call mpi_sizeof(rtest8,isize,ierror)
   call mpi_type_match_size(mpi_typeclass_real,isize,mpir8,ierror)

However the problem is to define mpic8 which is the MPI brother of complex(kind=r8) type. See below,

   call mpi_sizeof(ctest8,isize,ierror) !!!problem!!!!
   call mpi_type_match_size(mpi_typeclass_complex,isize,mpic8,ierror)!!!!problem!!!!

It shows an error for both Intel and gfortran’s mpi,

error #6285: There is no matching specific subroutine for this generic subroutine call.   [MPI_SIZEOF]

Just curious,
does anyone know how to have a portable mpic8 type which should be the same as complex(kind=r8) type?

Thank you very much in advance!

PS,
For now, I can use the intrinsic mpi_double_complex to transfer data for complex number. But I am not sure if mpi_double_complex is portable or not, but I guess mpi_double_complex should be just fine.