tree-optimization/113385 - wrong loop father with early exit vectorization
[official-gcc.git] / gcc / testsuite / gfortran.dg / class_result_10.f90
blobacfb7c35cfb23ca557c020e9828b31c76dc96248
1 ! { dg-do run }
4 ! PR fortran/99585
6 module m2
7 type t
8 class(*), pointer :: bar(:)
9 end type
10 type t2
11 class(t), allocatable :: my(:)
12 end type t2
13 contains
14 function f (x, y) result(z)
15 class(t) :: x(:)
16 class(t) :: y(size(x(1)%bar))
17 type(t) :: z(size(x(1)%bar))
18 end
19 function g (x) result(z)
20 class(t) :: x(:)
21 type(t) :: z(size(x(1)%bar))
22 end
23 subroutine s ()
24 class(t2), allocatable :: a(:), b(:), c(:), d(:)
25 class(t2), pointer :: p(:)
26 c(1)%my = f (a(1)%my, b(1)%my)
27 d(1)%my = g (p(1)%my)
28 end
29 end
31 ! Contributed by G. Steinmetz:
32 ! PR fortran/104430
34 module m
35 type t
36 integer :: a
37 end type
38 contains
39 function f(x) result(z)
40 class(t) :: x(:)
41 type(t) :: z(size(x%a))
42 z%a = 42
43 end
44 end
45 program p
46 use m
47 class(t), allocatable :: y(:), z(:)
48 allocate (y(32))
49 z = f(y)
50 if (size(z) /= 32) stop 1
51 if (any (z%a /= 42)) stop 2
52 end