[to-be-committed] [RISC-V] Use Zbkb for general 64 bit constants when profitable
[official-gcc.git] / gcc / testsuite / gfortran.dg / pr92050.f90
blob64193878d8fd87a65ecf59896ae3e09d7238d1e2
1 ! { dg-do run }
2 ! { dg-options "-fcheck=all" }
3 ! { dg-shouldfail "above upper bound" }
5 ! PR fortran/92050
8 module buggy
9 implicit none (type, external)
11 type :: par
12 contains
13 procedure, public :: fun => fun_par
14 end type par
16 type comp
17 class(par), allocatable :: p
18 end type comp
20 type foo
21 type(comp), allocatable :: m(:)
22 end type foo
24 contains
26 function fun_par(this)
27 class(par) :: this
28 integer :: fun_par(1)
29 fun_par = 42
30 end function fun_par
32 subroutine update_foo(this)
33 class(foo) :: this
34 write(*,*) this%m(1)%p%fun()
35 end subroutine update_foo
37 subroutine bad_update_foo(this)
38 class(foo) :: this
39 write(*,*) this%m(2)%p%fun()
40 end subroutine bad_update_foo
41 end module buggy
43 program main
44 use buggy
45 implicit none (type, external)
46 type(foo) :: x
47 allocate(x%m(1))
48 allocate(x%m(1)%p)
49 call update_foo(x)
50 call bad_update_foo(x)
51 end program main
53 ! { dg-output "At line 39 of file .*pr92050.f90.*Fortran runtime error: Index '2' of dimension 1 of array 'this%m' above upper bound of 1" }