AArch64: correct constraint on Upl early clobber alternatives
[official-gcc.git] / gcc / testsuite / gfortran.dg / deallocate_error_2.f90
blobbda1adff514c8c21a65376c9b60b51e21d0084e6
1 ! { dg-do run }
2 ! { dg-shouldfail "runtime error" }
3 ! { dg-output "At line 15.*Attempt to DEALLOCATE unallocated 'ptr'" }
5 ! PR fortran/37507
6 ! Check that locus is printed for DEALLOCATE errors.
8 PROGRAM main
9 IMPLICIT NONE
10 INTEGER, POINTER :: ptr
11 INTEGER, ALLOCATABLE :: arr(:)
13 ALLOCATE (ptr, arr(5))
14 DEALLOCATE (ptr)
15 DEALLOCATE (arr, ptr)
16 END PROGRAM main