3 ! Test functionality of allocatable class arrays:
4 ! ALLOCATE with source, ALLOCATED, DEALLOCATE, passing as arguments for
5 ! ELEMENTAL and non-ELEMENTAL procedures, SELECT TYPE and LOWER/UPPER.
10 type, extends(type1) :: type2
13 class(type1), allocatable, dimension (:) :: x
15 allocate(x(2), source = type2(42,42.0))
16 call display(x, [1], [2], t2 = [type2(42,42.0),type2(42,42.0)])
17 call display(x, [1], [2], t2 = [type2(111,99.0),type2(111,99.0)])
18 if (allocated (x)) deallocate (x)
20 allocate(x(1:4), source = [(type2(i,42.0 + float (i)), i = 1, 4)])
21 call display(x, [1], [4], t2 = [(type2(i,42.0 + float (i)), i = 1, 4)])
22 call display(x, [1], [4], t2 = [(type2(111,99.0), i = 1, 4)])
24 if (any (disp (x) .ne. [99.0,99.0,99.0,99.0])) call abort
26 if (allocated (x)) deallocate (x)
28 allocate(x(1:4), source = type1(42))
29 call display(x, [1], [4], t1 = [(type1(42), i = 1, 4)])
30 call display(x, [1], [4], t1 = [type1(42),type1(99),type1(42),type1(42)])
31 if (any (disp (x) .ne. [0.0,0.0,0.0,0.0])) call abort
34 subroutine display(x, lower, upper, t1, t2)
35 class(type1), allocatable, dimension (:) :: x
36 integer, dimension (:) :: lower, upper
37 type(type1), optional, dimension(:) :: t1
38 type(type2), optional, dimension(:) :: t2
41 if (present (t1)) then
42 if (any (x%i .ne. t1%i)) call abort
48 if (present (t2)) then
49 if (any (x%i .ne. t2%i)) call abort
50 if (any (x%r .ne. t2%r)) call abort
57 call bounds (x, lower, upper)
59 subroutine bounds (x, lower, upper)
60 class(type1), allocatable, dimension (:) :: x
61 integer, dimension (:) :: lower, upper
62 if (any (lower .ne. lbound (x))) call abort
63 if (any (upper .ne. ubound (x))) call abort
65 elemental function disp(y) result(ans)
66 class(type1), intent(in) :: y