2 ! { dg-options "-fcheck=bounds" }
3 ! { dg-shouldfail "Array bounds mismatch" }
5 ! Test that pr72832 is fixed now.
6 ! Contributed by Daan van Vugt
8 program allocate_source
12 type, extends(t) :: tt
16 call test_class_correct()
17 call test_class_fail()
21 subroutine test_class_correct()
22 class(t), allocatable, dimension(:) :: a, b
25 if (size(a) /= 2) call abort()
26 if (any(a(:)%i /= [ 1,2])) call abort()
28 allocate(b(1:4), source=a(1))
29 if (size(b) /= 4) call abort()
30 if (any(b(:)%i /= [ 1,1,1,1])) call abort()
39 subroutine test_class_fail()
40 class(t), allocatable, dimension(:) :: a, b
43 if (size(a) /= 2) call abort()
44 if (any(a(:)%i /= [ 1,2])) call abort()
46 allocate(b(1:4), source=a) ! Fail expected: sizes do not conform
47 if (size(b) /= 4) call abort()
48 if (any(b(1:2)%i /= [ 1,2])) call abort()
57 subroutine test_type()
58 type(t), allocatable, dimension(:) :: a, b
60 if (size(a) /= 2) call abort()
62 allocate(b(1:4), source=a)
63 if (size(b) /= 4) call abort()
65 end program allocate_source