Plugins: Add label-text.h to CPPLIB_H so it will be installed [PR115288]
[official-gcc.git] / gcc / testsuite / gfortran.dg / pr69739.f90
blob50fd57aeebf731aa2b9f2a09376caadb051fe436
1 ! { dg-do run }
3 ! Test the fix for PR69739 in which the statement
4 ! R = operate(A, X) caused an ICE.
6 ! Contributed by John <jwmwalrus@gmail.com>
8 module test
10 implicit none
11 type, public :: sometype
12 real :: a = 0.
13 end type
14 contains
16 function dosomething(A) result(r)
17 type(sometype), intent(IN) :: A(:,:,:)
18 integer :: N
19 real, allocatable :: R(:), X(:)
21 N = PRODUCT(UBOUND(A))
22 allocate (R(N),X(N))
23 X = [(real(N), N = 1, size(X, 1))]
24 R = operate(A, X)
25 end function
27 function operate(A, X)
28 type(sometype), intent(IN) :: A(:,:,:)
29 real, intent(IN) :: X(:)
30 real :: operate(1:PRODUCT(UBOUND(A)))
32 operate = x
33 end function
34 end module test
36 use test
37 type(sometype) :: a(2, 2, 2)
38 if (any(int (dosomething(a)) .ne. [1,2,3,4,5,6])) STOP 1
39 end