nvptx, libgfortran: Switch out of "minimal" mode
[official-gcc.git] / gcc / testsuite / gfortran.dg / ISO_Fortran_binding_19.f90
blob8cc1601d047ca89bec9d77f6e9734df52fbfcd34
1 ! { dg-do run }
2 ! This testcase failed before with optimization as
3 ! allocatef's CFI descriptor argument 'x' failed with -fstrict-alias due to
4 ! internally alising with the GFC descriptor
7 program testit
8 use iso_c_binding
9 implicit none (external, type)
10 type, bind (c) :: m
11 integer(C_INT) :: i, j
12 end type
13 type(m), allocatable :: a(:)
15 call testf (a)
17 contains
18 subroutine allocatef (x) bind (c)
19 type(m), allocatable :: x(:)
20 allocate (x(5:15))
21 end subroutine
23 subroutine testf (y)
24 type(m), allocatable, target :: y(:)
25 call allocatef (y)
26 if (.not. allocated (y)) stop 1
27 end subroutine
28 end program