• Home
  • Line#
  • Scopes#
  • Navigate#
  • Raw
  • Download
1! RUN: %S/test_errors.sh %s %t %f18
2! Check for semantic errors in ALLOCATE statements
3
4
5subroutine C935(l, ac1, ac2, ac3, dc1, dc2, ec1, ec2, aa, ab, ab2, ea, eb, da, db, whatever, something, something_else)
6! A type-param-value in a type-spec shall be an asterisk if and only if each
7! allocate-object is a dummy argument for which the corresponding type parameter
8! is assumed.
9
10  type A(la)
11    integer, len :: la
12    integer vector(la)
13  end type
14
15  type, extends(A) :: B(lb)
16    integer, len :: lb
17    integer matrix(lb, lb)
18  end type
19
20  type, extends(B) :: C(lc1, lc2, lc3)
21    integer, len :: lc1, lc2, lc3
22    integer array(lc1, lc2, lc3)
23  end type
24
25  integer l
26  character(len=*), pointer :: ac1, ac2(:)
27  character*(*), allocatable :: ac3(:)
28  character*(:), allocatable :: dc1
29  character(len=:), pointer :: dc2(:)
30  character(len=l), pointer :: ec1
31  character*5, allocatable :: ec2(:)
32
33  class(A(*)), pointer :: aa
34  type(B(* , 5)), allocatable :: ab(:)
35  type(B(* , *)), pointer :: ab2(:)
36  class(A(l)), allocatable :: ea
37  type(B(5 , 5)), pointer :: eb(:)
38  class(A(:)), allocatable :: da
39  type(B(: , 5)), pointer :: db(:)
40  class(*), allocatable :: whatever
41  type(C(la=*, lb=:, lc1=*, lc2=5, lc3=*)), pointer :: something(:)
42  type(C(la=*, lb=:, lc1=5, lc2=5, lc3=*)), pointer :: something_else(:)
43
44  ! OK
45  allocate(character(len=*):: ac1, ac3(3))
46  allocate(character*(*):: ac2(5))
47  allocate(B(*, 5):: aa, ab(2)) !OK but segfault GCC
48  allocate(B(*, *):: ab2(2))
49  allocate(C(la=*, lb=10, lc1=*, lc2=5, lc3=*):: something(5))
50  allocate(C(la=*, lb=10, lc1=2, lc2=5, lc3=3):: aa)
51  allocate(character(5):: whatever)
52
53  ! Not OK
54
55  ! Should be * or no type-spec
56  !ERROR: Type parameters in type-spec must be assumed if and only if they are assumed for allocatable object in ALLOCATE
57  allocate(character(len=5):: ac1)
58  !ERROR: Type parameters in type-spec must be assumed if and only if they are assumed for allocatable object in ALLOCATE
59  !ERROR: Type parameters in type-spec must be assumed if and only if they are assumed for allocatable object in ALLOCATE
60  allocate(character(len=5):: ac2(3), ac3)
61  !ERROR: Type parameters in type-spec must be assumed if and only if they are assumed for allocatable object in ALLOCATE
62  allocate(character(len=l):: ac1)
63  !ERROR: Type parameters in type-spec must be assumed if and only if they are assumed for allocatable object in ALLOCATE
64  !ERROR: Type parameters in type-spec must be assumed if and only if they are assumed for allocatable object in ALLOCATE
65  allocate(character(len=l):: ac2(3), ac3)
66  !ERROR: Type parameters in type-spec must be assumed if and only if they are assumed for allocatable object in ALLOCATE
67  allocate(A(5):: aa)
68  !ERROR: Type parameters in type-spec must be assumed if and only if they are assumed for allocatable object in ALLOCATE
69  allocate(B(5, 5):: ab(5))
70  !ERROR: Type parameters in type-spec must be assumed if and only if they are assumed for allocatable object in ALLOCATE
71  !ERROR: Type parameters in type-spec must be assumed if and only if they are assumed for allocatable object in ALLOCATE
72  allocate(B(l, 5):: aa, ab(5))
73
74  ! Must not be *
75  !ERROR: Type parameters in type-spec must be assumed if and only if they are assumed for allocatable object in ALLOCATE
76  allocate(character(len=*):: ac1, dc1, ac3(2))
77  !ERROR: Type parameters in type-spec must be assumed if and only if they are assumed for allocatable object in ALLOCATE
78  allocate(character*(*):: dc2(5))
79  !ERROR: Type parameters in type-spec must be assumed if and only if they are assumed for allocatable object in ALLOCATE
80  allocate(character*(*):: ec1)
81  !ERROR: Type parameters in type-spec must be assumed if and only if they are assumed for allocatable object in ALLOCATE
82  allocate(character(*):: whatever)
83  !ERROR: Type parameters in type-spec must be assumed if and only if they are assumed for allocatable object in ALLOCATE
84  allocate(character(len=*):: ac2(5), ec2(5))
85  !ERROR: Type parameters in type-spec must be assumed if and only if they are assumed for allocatable object in ALLOCATE
86  allocate(A(*):: ea) !segfault gfortran
87  !ERROR: Type parameters in type-spec must be assumed if and only if they are assumed for allocatable object in ALLOCATE
88  allocate(B(*, 5):: eb(2)) !segfault gfortran
89  !ERROR: Type parameters in type-spec must be assumed if and only if they are assumed for allocatable object in ALLOCATE
90  allocate(A(*):: da) !segfault gfortran
91  !ERROR: Type parameters in type-spec must be assumed if and only if they are assumed for allocatable object in ALLOCATE
92  allocate(B(*, 5):: db(2)) !segfault gfortran
93  !ERROR: Type parameters in type-spec must be assumed if and only if they are assumed for allocatable object in ALLOCATE
94  allocate(A(*):: aa, whatever)
95  !ERROR: Type parameters in type-spec must be assumed if and only if they are assumed for allocatable object in ALLOCATE
96  allocate(B(*, *):: aa)
97  !ERROR: Type parameters in type-spec must be assumed if and only if they are assumed for allocatable object in ALLOCATE
98  allocate(C(la=*, lb=10, lc1=*, lc2=5, lc3=*):: something_else(5))
99  !ERROR: Type parameters in type-spec must be assumed if and only if they are assumed for allocatable object in ALLOCATE
100  allocate(C(la=5, lb=10, lc1=4, lc2=5, lc3=3):: aa)
101  !ERROR: Type parameters in type-spec must be assumed if and only if they are assumed for allocatable object in ALLOCATE
102  allocate(C(la=*, lb=10, lc1=*, lc2=5, lc3=*):: aa)
103end subroutine
104