c: Fix up pointer types to may_alias structures [PR114493]
[official-gcc.git] / gcc / testsuite / gfortran.dg / allocate_alloc_opt_1.f90
blob12005a6cc16cd5a3e0804772896a6e45206a10a3
1 ! { dg-do compile }
2 program a
4 implicit none
6 real x
7 integer j, k, n(4)
8 character(len=70) err
9 character(len=70), allocatable :: error(:)
11 integer, allocatable :: i(:)
13 type b
14 integer, allocatable :: c(:), d(:)
15 end type b
17 type(b) e, f(3)
19 allocate(i(2), stat=x) ! { dg-error "must be a scalar INTEGER" }
20 allocate(i(2), stat=j, stat=k) ! { dg-error "Redundant STAT" }
21 allocate(i(2))
22 allocate(i(2))) ! { dg-error "Syntax error in ALLOCATE" }
23 allocate(i(2), errmsg=err, errmsg=err) ! { dg-error "Redundant ERRMSG" }
24 allocate(i(2), errmsg=err) ! { dg-warning "useless without a STAT" }
25 allocate(i(2), stat=j, errmsg=x) ! { dg-error "shall be a scalar default CHARACTER" }
27 allocate(err) ! { dg-error "neither a data pointer nor an allocatable" }
29 allocate(error(2),stat=j,errmsg=error(1)) ! { dg-error "shall not be ALLOCATEd within" }
30 allocate(i(2), stat = i(1)) ! { dg-error "shall not be ALLOCATEd within" }
32 allocate(n) ! { dg-error "must be ALLOCATABLE or a POINTER" }
34 allocate(i(2), i(2)) ! { dg-error "Allocate-object at" }
36 ! These should not fail the check for duplicate alloc-objects.
37 allocate(f(1)%c(2), f(2)%d(2))
38 allocate(e%c(2), e%d(2))
40 end program a