lto: Remove random_seed from section name.
[official-gcc.git] / gcc / testsuite / gfortran.dg / associate_54.f90
blob8eb95a710b60320d2a542c4867a2d3f4bd828d7f
1 ! { dg-do compile }
3 ! Test the fix for PR93701.
5 ! Contributed by Simon Brass <simon.brass@desy.de>
7 module test
8 implicit none
10 integer, parameter :: N_STATE = 1, &
11 TEST_STATE = 1
13 type :: test_t
14 integer, dimension(:), allocatable :: state
15 end type test_t
17 contains
19 subroutine test_allocate (obj)
20 class(test_t), intent(out) :: obj
21 allocate (obj%state(N_STATE))
22 end subroutine test_allocate
24 subroutine test_alter_state1 (obj, a)
25 class(test_t), intent(inout) :: obj
26 integer, intent(in) :: a
27 associate (state => obj%state(TEST_STATES)) ! { dg-error "as array|no IMPLICIT type" }
28 ! state = a
29 state(TEST_STATE) = a ! { dg-error "array reference of a non-array" }
30 end associate
31 end subroutine test_alter_state1
33 end module test