AArch64: correct constraint on Upl early clobber alternatives
[official-gcc.git] / gcc / testsuite / gfortran.dg / ISO_Fortran_binding_5.f90
blob97c2c5202bb278d06ed13e90cf3d65e4c710018b
1 ! { dg-do run }
2 ! { dg-additional-sources ISO_Fortran_binding_5.c }
4 ! Test fix of PR89385.
6 ! Contributed by Reinhold Bader <Bader@lrz.de>
8 program allocatable_01
9 use, intrinsic :: iso_c_binding
10 implicit none
11 type, bind(c) :: cstruct
12 integer(c_int) :: i
13 real(c_float) :: r(2)
14 end type cstruct
15 interface
16 subroutine psub(this, that, ierr) bind(c, name='Psub')
17 import :: c_float, cstruct, c_int
18 real(c_float), allocatable :: this(:,:)
19 type(cstruct), allocatable :: that(:)
20 integer(c_int), intent(inout) :: ierr
21 end subroutine psub
22 end interface
24 real(c_float), allocatable :: t(:,:)
25 type(cstruct), allocatable :: u(:)
26 integer(c_int) :: ierr
28 allocate(t(3:6,5))
29 t = 0.0
30 t(4,2) = -2.0
31 allocate(u(1), source=[ cstruct( 4, [1.1,2.2] ) ] )
32 call psub(t, u, ierr)
34 deallocate(t,u)
35 if (ierr .ne. 0) stop ierr
36 end program allocatable_01