AArch64: correct constraint on Upl early clobber alternatives
[official-gcc.git] / gcc / testsuite / gfortran.dg / elemental_function_5.f90
blob315ff9162b35782615f65be015fc33d222999211
1 ! { dg-do compile }
3 ! Test the fix for PR98472.
5 ! Contributed by Rui Coelho <ruicoelhopedro@hotmail.com>
7 module a
8 type, abstract :: base
9 contains
10 procedure(elem_func), deferred, nopass :: add
11 end type base
13 type, extends(base) :: derived
14 contains
15 procedure, nopass :: add => add_derived
16 end type derived
18 abstract interface
19 elemental function elem_func(x, y) result(out)
20 integer, intent(in) :: x, y
21 integer :: out
22 end function elem_func
23 end interface
25 contains
26 elemental function add_derived(x, y) result(out)
27 integer, intent(in) :: x, y
28 integer :: out
29 out = x + y
30 end function add_derived
31 end module a
33 program main
34 use a
35 call foo
36 contains
37 subroutine foo
38 integer, dimension(:), allocatable :: vec
39 class(base), allocatable :: instance
40 allocate(derived :: instance)
41 allocate(vec, source=instance%add([1, 2], [1, 2])) ! ICE here
42 if (any (vec .ne. [2, 4])) stop 1
43 end
44 end program main