annotate gcc/testsuite/gfortran.dg/class_array_2.f03 @ 131:84e7813d76e9

gcc-8.2
author mir3636
date Thu, 25 Oct 2018 07:37:49 +0900
parents 04ced10e8804
children
Ignore whitespace changes - Everywhere: Within whitespace: At end of lines:
rev   line source
111
kono
parents:
diff changeset
1 ! { dg-do run }
kono
parents:
diff changeset
2 !
kono
parents:
diff changeset
3 ! Test functionality of pointer class arrays:
kono
parents:
diff changeset
4 ! ALLOCATE with source, ASSOCIATED, DEALLOCATE, passing as arguments for
kono
parents:
diff changeset
5 ! ELEMENTAL and non-ELEMENTAL procedures, SELECT TYPE and LOWER/UPPER.
kono
parents:
diff changeset
6 !
kono
parents:
diff changeset
7 type :: type1
kono
parents:
diff changeset
8 integer :: i
kono
parents:
diff changeset
9 end type
kono
parents:
diff changeset
10 type, extends(type1) :: type2
kono
parents:
diff changeset
11 real :: r
kono
parents:
diff changeset
12 end type
kono
parents:
diff changeset
13 class(type1), pointer, dimension (:) :: x
kono
parents:
diff changeset
14
kono
parents:
diff changeset
15 allocate(x(2), source = type2(42,42.0))
kono
parents:
diff changeset
16 call display(x, [1], [2], t2 = [type2(42,42.0),type2(42,42.0)])
kono
parents:
diff changeset
17 call display(x, [1], [2], t2 = [type2(111,99.0),type2(111,99.0)])
kono
parents:
diff changeset
18 if (associated (x)) deallocate (x)
kono
parents:
diff changeset
19
kono
parents:
diff changeset
20 allocate(x(1:4), source = [(type2(i,42.0 + float (i)), i = 1, 4)])
kono
parents:
diff changeset
21 call display(x, [1], [4], t2 = [(type2(i,42.0 + float (i)), i = 1, 4)])
kono
parents:
diff changeset
22 call display(x, [1], [4], t2 = [(type2(111,99.0), i = 1, 4)])
kono
parents:
diff changeset
23
131
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
24 if (any (disp (x) .ne. [99.0,99.0,99.0,99.0])) STOP 1
111
kono
parents:
diff changeset
25
kono
parents:
diff changeset
26 if (associated (x)) deallocate (x)
kono
parents:
diff changeset
27
kono
parents:
diff changeset
28 allocate(x(1:4), source = type1(42))
kono
parents:
diff changeset
29 call display(x, [1], [4], t1 = [(type1(42), i = 1, 4)])
kono
parents:
diff changeset
30 call display(x, [1], [4], t1 = [type1(42),type1(99),type1(42),type1(42)])
131
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
31 if (any (disp (x) .ne. [0.0,0.0,0.0,0.0])) STOP 2
111
kono
parents:
diff changeset
32
kono
parents:
diff changeset
33 if (associated (x)) deallocate (x)
kono
parents:
diff changeset
34
kono
parents:
diff changeset
35 contains
kono
parents:
diff changeset
36 subroutine display(x, lower, upper, t1, t2)
kono
parents:
diff changeset
37 class(type1), pointer, dimension (:) :: x
kono
parents:
diff changeset
38 integer, dimension (:) :: lower, upper
kono
parents:
diff changeset
39 type(type1), optional, dimension(:) :: t1
kono
parents:
diff changeset
40 type(type2), optional, dimension(:) :: t2
kono
parents:
diff changeset
41 select type (x)
kono
parents:
diff changeset
42 type is (type1)
kono
parents:
diff changeset
43 if (present (t1)) then
131
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
44 if (any (x%i .ne. t1%i)) STOP 3
111
kono
parents:
diff changeset
45 else
131
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
46 STOP 4
111
kono
parents:
diff changeset
47 end if
kono
parents:
diff changeset
48 x(2)%i = 99
kono
parents:
diff changeset
49 type is (type2)
kono
parents:
diff changeset
50 if (present (t2)) then
131
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
51 if (any (x%i .ne. t2%i)) STOP 5
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
52 if (any (x%r .ne. t2%r)) STOP 6
111
kono
parents:
diff changeset
53 else
131
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
54 STOP 7
111
kono
parents:
diff changeset
55 end if
kono
parents:
diff changeset
56 x%i = 111
kono
parents:
diff changeset
57 x%r = 99.0
kono
parents:
diff changeset
58 end select
kono
parents:
diff changeset
59 call bounds (x, lower, upper)
kono
parents:
diff changeset
60 end subroutine
kono
parents:
diff changeset
61 subroutine bounds (x, lower, upper)
kono
parents:
diff changeset
62 class(type1), pointer, dimension (:) :: x
kono
parents:
diff changeset
63 integer, dimension (:) :: lower, upper
131
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
64 if (any (lower .ne. lbound (x))) STOP 8
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
65 if (any (upper .ne. ubound (x))) STOP 9
111
kono
parents:
diff changeset
66 end subroutine
kono
parents:
diff changeset
67 elemental function disp(y) result(ans)
kono
parents:
diff changeset
68 class(type1), intent(in) :: y
kono
parents:
diff changeset
69 real :: ans
kono
parents:
diff changeset
70 select type (y)
kono
parents:
diff changeset
71 type is (type1)
kono
parents:
diff changeset
72 ans = 0.0
kono
parents:
diff changeset
73 type is (type2)
kono
parents:
diff changeset
74 ans = y%r
kono
parents:
diff changeset
75 end select
kono
parents:
diff changeset
76 end function
kono
parents:
diff changeset
77 end
kono
parents:
diff changeset
78