aarch64: Add vector floating point extend pattern [PR113880, PR113869]
[official-gcc.git] / gcc / testsuite / gfortran.dg / elemental_result_2.f90
blob490c2ef68de0ef6159eee6531b3d54f456c5192d
1 ! { dg-do compile }
3 ! Test part of the fix for PR99124 which adds errors for class results
4 ! That violate F2018, C15100.
6 ! Contributed by Gerhard Steinmetz <gscfq@t-online.de>
8 module m
9 type t
10 integer :: i
11 contains
12 procedure :: f
13 generic :: operator(+) => f
14 end type
15 contains
16 elemental function f(a, b) &
17 result(c) ! { dg-error "shall not have an ALLOCATABLE or POINTER attribute" }
18 class(t), intent(in) :: a, b
19 class(t), allocatable :: c
20 c = t(a%i + b%i)
21 end
22 elemental function g(a, b) &
23 result(c) ! { dg-error "shall not have an ALLOCATABLE or POINTER attribute" }
24 class(t), intent(in) :: a, b
25 class(t), pointer :: c
26 c => null ()
27 end
28 elemental function h(a, b) & ! { dg-error "must have a scalar result" }
29 result(c) ! { dg-error "must be dummy, allocatable or pointer" }
30 class(t), intent(in) :: a, b
31 class(t) :: c(2)
32 end
33 end