[LoopReroll] Add an extra defensive check to avoid SCEV assertion.
[llvm-project.git] / flang / test / Semantics / resolve20.f90
blob6908aeb575a582fbddc9cf8ea866cd3854f5823e
1 ! RUN: %S/test_errors.sh %s %t %flang_fc1
2 ! REQUIRES: shell
3 module m
4 abstract interface
5 subroutine foo
6 end subroutine
7 end interface
9 procedure() :: a
10 procedure(integer) :: b
11 procedure(foo) :: c
12 procedure(bar) :: d
13 !ERROR: 'missing' must be an abstract interface or a procedure with an explicit interface
14 procedure(missing) :: e
15 !ERROR: 'b' must be an abstract interface or a procedure with an explicit interface
16 procedure(b) :: f
17 procedure(c) :: g
18 external :: h
19 !ERROR: 'h' must be an abstract interface or a procedure with an explicit interface
20 procedure(h) :: i
21 procedure(forward) :: j
22 !ERROR: 'bad1' must be an abstract interface or a procedure with an explicit interface
23 procedure(bad1) :: k1
24 !ERROR: 'bad2' must be an abstract interface or a procedure with an explicit interface
25 procedure(bad2) :: k2
26 !ERROR: 'bad3' must be an abstract interface or a procedure with an explicit interface
27 procedure(bad3) :: k3
29 abstract interface
30 subroutine forward
31 end subroutine
32 end interface
34 real :: bad1(1)
35 real :: bad2
36 type :: bad3
37 end type
39 type :: m ! the name of a module can be used as a local identifier
40 end type m
42 external :: a, b, c, d
43 !ERROR: EXTERNAL attribute not allowed on 'm'
44 external :: m
45 !ERROR: EXTERNAL attribute not allowed on 'foo'
46 external :: foo
47 !ERROR: EXTERNAL attribute not allowed on 'bar'
48 external :: bar
50 !ERROR: PARAMETER attribute not allowed on 'm'
51 parameter(m=2)
52 !ERROR: PARAMETER attribute not allowed on 'foo'
53 parameter(foo=2)
54 !ERROR: PARAMETER attribute not allowed on 'bar'
55 parameter(bar=2)
57 type, abstract :: t1
58 integer :: i
59 contains
60 !ERROR: 'proc' must be an abstract interface or a procedure with an explicit interface
61 !ERROR: Procedure component 'p1' has invalid interface 'proc'
62 procedure(proc), deferred :: p1
63 end type t1
65 abstract interface
66 function f()
67 end function
68 end interface
70 contains
71 subroutine bar
72 end subroutine
73 subroutine test
74 !ERROR: Abstract interface 'foo' may not be called
75 call foo()
76 !ERROR: Abstract interface 'f' may not be called
77 x = f()
78 end subroutine
79 end module