AArch64: correct constraint on Upl early clobber alternatives
[official-gcc.git] / gcc / testsuite / gfortran.dg / c_f_pointer_tests_4.f90
blobd70b91dc29e5d8c65e80c95fbc72838d6e728b43
1 ! { dg-do run }
2 program main
3 use iso_c_binding, only: c_ptr, c_loc, c_f_pointer
4 implicit none
5 integer, dimension(2,1,2), target :: table
6 table = reshape ( (/ 1,2,-1,-2/), (/2,1,2/))
7 call set_table (c_loc (table))
8 contains
9 subroutine set_table (cptr)
10 type(c_ptr), intent(in) :: cptr
11 integer, dimension(:,:,:), pointer :: table_tmp
12 call c_f_pointer (cptr, table_tmp, (/2,1,2/))
13 if (any(table_tmp /= table)) STOP 1
14 end subroutine set_table
15 end program main