xref: /llvm-project/flang/test/Semantics/resolve30.f90 (revision df111658a2535d273a4d7d1edf7c412e090ac97e)
1! RUN: %python %S/test_errors.py %s %flang_fc1 -pedantic
2subroutine s1
3  integer x
4  block
5    import, none
6    !ERROR: 'x' from host scoping unit is not accessible due to IMPORT
7    x = 1
8  end block
9end
10
11subroutine s2
12  block
13    import, none
14    !ERROR: 'y' from host scoping unit is not accessible due to IMPORT
15    y = 1
16  end block
17end
18
19subroutine s3
20  implicit none
21  integer :: i, j
22  block
23    import, none
24    !ERROR: No explicit type declared for 'i'
25    real :: a(16) = [(i, i=1, 16)]
26    real :: b(16)
27    !ERROR: No explicit type declared for 'j'
28    data(b(j), j=1, 16) / 16 * 0.0 /
29  end block
30end
31
32subroutine s4
33  real :: j
34  !ERROR: Must have INTEGER type, but is REAL(4)
35  real :: a(16) = [(x, x=1, 16)]
36  real :: b(16)
37  !ERROR: Must have INTEGER type, but is REAL(4)
38  data(b(j), j=1, 16) / 16 * 0.0 /
39end
40
41subroutine s5
42  implicit none
43  data x/1./
44  !PORTABILITY: 'x' appeared in a DATA statement before its type was declared under IMPLICIT NONE(TYPE)
45  real x
46end
47