PR tree-optimization/86415 - strlen() not folded for substrings within constant arrays
[official-gcc.git] / gcc / testsuite / gfortran.dg / extends_type_of_1.f03
blobf9ac08086d91a8391ba4e19b19136c9048e20fa7
1 ! { dg-do run }
3 ! Verifying the runtime behavior of the intrinsic function EXTENDS_TYPE_OF.
5 ! Contributed by Janus Weil <janus@gcc.gnu.org>
7  implicit none
9  intrinsic :: extends_type_of
11  type :: t1
12    integer :: i = 42
13  end type
15  type, extends(t1) :: t2
16    integer :: j = 43
17  end type
19  type, extends(t2) :: t3
20    class(t1),pointer :: cc
21  end type
23  class(t1), pointer :: c1,c2
24  type(t1), target :: x
25  type(t2), target :: y
26  type(t3), target :: z
28  c1 => x
29  c2 => y
30  z%cc => y
32  if (.not. extends_type_of (c1, c1)) STOP 1
33  if (      extends_type_of (c1, c2)) STOP 2
34  if (.not. extends_type_of (c2, c1)) STOP 3
36  if (.not. extends_type_of (x, x)) STOP 4
37  if (      extends_type_of (x, y)) STOP 5
38  if (.not. extends_type_of (y, x)) STOP 6
40  if (.not. extends_type_of (c1, x)) STOP 7
41  if (      extends_type_of (c1, y)) STOP 8
42  if (.not. extends_type_of (x, c1)) STOP 9
43  if (.not. extends_type_of (y, c1)) STOP 10
45  if (.not. extends_type_of (z,   c1)) STOP 11
46  if (      extends_type_of (z%cc, z)) STOP 12
48 end