better way of doing this. When ISO C binding is cleared up,
this can probably be removed. See PR 57048. */
- if (((ts1->type == BT_INTEGER && ts2->type == BT_DERIVED)
- || (ts1->type == BT_DERIVED && ts2->type == BT_INTEGER))
- && ts1->u.derived && ts2->u.derived
- && ts1->u.derived == ts2->u.derived)
+ if ((ts1->type == BT_INTEGER
+ && ts2->type == BT_DERIVED
+ && ts1->f90_type == BT_VOID
+ && ts2->u.derived->from_intmod == INTMOD_ISO_C_BINDING
+ && ts1->u.derived
+ && strcmp (ts1->u.derived->name, ts2->u.derived->name) == 0)
+ || (ts2->type == BT_INTEGER
+ && ts1->type == BT_DERIVED
+ && ts2->f90_type == BT_VOID
+ && ts1->u.derived->from_intmod == INTMOD_ISO_C_BINDING
+ && ts2->u.derived
+ && strcmp (ts1->u.derived->name, ts2->u.derived->name) == 0))
return true;
/* The _data component is not always present, therefore check for its
switch (ts->type)
{
case BT_INTEGER:
- sprintf (buffer, "INTEGER(%d)", ts->kind);
+ if (ts->f90_type == BT_VOID
+ && ts->u.derived
+ && ts->u.derived->from_intmod == INTMOD_ISO_C_BINDING)
+ sprintf (buffer, "TYPE(%s)", ts->u.derived->name);
+ else
+ sprintf (buffer, "INTEGER(%d)", ts->kind);
break;
case BT_REAL:
sprintf (buffer, "REAL(%d)", ts->kind);
--- /dev/null
+! { dg-do compile }
+! { dg-additional-options "-fopenmp" }
+!
+! This failed to compile the declare variant directive due to the C_PTR
+! arguments to foo being recognised as INTEGER(8)
+
+program adjust_args
+ use iso_c_binding, only: c_loc
+ implicit none
+
+ integer, parameter :: N = 1024
+ real, allocatable, target :: av(:), bv(:), cv(:)
+
+ call foo(c_loc(bv), c_loc(av), N)
+
+ !$omp target data map(to: av(:N)) map(from: cv(:N))
+ !$omp parallel
+ call foo(c_loc(cv), c_loc(av), N)
+ !$omp end parallel
+ !$omp end target data
+
+contains
+ subroutine foo_variant(c_d_bv, c_d_av, n)
+ use iso_c_binding, only: c_ptr, c_f_pointer
+ type(c_ptr), intent(in) :: c_d_bv, c_d_av
+ integer, intent(in) :: n
+ real, pointer :: f_d_bv(:)
+ real, pointer :: f_d_av(:)
+ integer :: i
+
+ call c_f_pointer(c_d_bv, f_d_bv, [n])
+ call c_f_pointer(c_d_av, f_d_av, [n])
+ !$omp target teams loop is_device_ptr(f_d_bv, f_d_av)
+ do i = 1, n
+ f_d_bv(i) = f_d_av(i) * i
+ end do
+ end subroutine
+
+
+ subroutine foo(c_bv, c_av, n)
+ use iso_c_binding, only: c_ptr, c_f_pointer
+ type(c_ptr), intent(in) :: c_bv, c_av
+ integer, intent(in) :: n
+ real, pointer :: f_bv(:)
+ real, pointer :: f_av(:)
+ integer :: i
+ !$omp declare variant(foo_variant) &
+ !$omp match(construct={parallel})
+
+ call c_f_pointer(c_bv, f_bv, [n])
+ call c_f_pointer(c_av, f_av, [n])
+ !$omp parallel loop
+ do i = 1, n
+ f_bv(i) = f_av(i) * i
+ end do
+ end subroutine
+end program
--- /dev/null
+! { dg-do compile }
+! { dg-additional-options "-fopenmp" }
+!
+! Ensure that C_PTR and C_FUNPTR are reported as incompatible types in variant
+! argument lists
+
+program adjust_args
+ use iso_c_binding, only: c_loc
+ implicit none
+
+ integer, parameter :: N = 1024
+ real, allocatable, target :: av(:), bv(:), cv(:)
+
+ call foo(c_loc(bv), c_loc(av), N)
+
+ !$omp target data map(to: av(:N)) map(from: cv(:N))
+ !$omp parallel
+ call foo(c_loc(cv), c_loc(av), N)
+ !$omp end parallel
+ !$omp end target data
+
+contains
+ subroutine foo_variant(c_d_bv, c_d_av, n)
+ use iso_c_binding, only: c_funptr, c_f_pointer
+ type(c_funptr), intent(in) :: c_d_bv, c_d_av
+ integer, intent(in) :: n
+ real, pointer :: f_d_bv(:)
+ real, pointer :: f_d_av(:)
+ integer :: i
+
+! call c_f_pointer(c_d_bv, f_d_bv, [n])
+! call c_f_pointer(c_d_av, f_d_av, [n])
+ !$omp target teams loop is_device_ptr(f_d_bv, f_d_av)
+ do i = 1, n
+ f_d_bv(i) = f_d_av(i) * i
+ end do
+ end subroutine
+
+
+ subroutine foo(c_bv, c_av, n)
+ use iso_c_binding, only: c_ptr, c_f_pointer
+ type(c_ptr), intent(in) :: c_bv, c_av
+ integer, intent(in) :: n
+ real, pointer :: f_bv(:)
+ real, pointer :: f_av(:)
+ integer :: i
+ !$omp declare variant(foo_variant) & ! { dg-error "variant 'foo_variant' and base 'foo' at .1. have incompatible types: Type mismatch in argument 'c_bv' .TYPE.c_ptr./TYPE.c_funptr.." }
+ !$omp match(construct={parallel})
+
+ call c_f_pointer(c_bv, f_bv, [n])
+ call c_f_pointer(c_av, f_av, [n])
+ !$omp parallel loop
+ do i = 1, n
+ f_bv(i) = f_av(i) * i
+ end do
+ end subroutine
+end program