[to-be-committed] [RISC-V] Use Zbkb for general 64 bit constants when profitable
[official-gcc.git] / gcc / testsuite / gfortran.dg / pr48958.f90
blob2b109374f4014067310f2248223952ea4ad2195a
1 ! { dg-do run }
2 ! { dg-options "-fcheck=pointer -fdump-tree-original" }
3 ! { dg-shouldfail "Fortran runtime error: Allocatable argument 'a' is not allocated" }
4 ! { dg-output "At line 13 .*" }
5 ! PR48958 - Add runtime diagnostics for SIZE intrinsic function
7 program p
8 integer :: n
9 integer, allocatable :: a(:)
10 integer, pointer :: b(:)
11 class(*), allocatable :: c(:)
12 integer :: d(10)
13 print *, size (a)
14 print *, size (b)
15 print *, size (c)
16 print *, size (d)
17 print *, size (f(n))
18 contains
19 function f (n)
20 integer, intent(in) :: n
21 real, allocatable :: f(:)
22 end function f
23 end
25 ! { dg-final { scan-tree-dump-times "_gfortran_runtime_error_at" 4 "original" } }