[LoopReroll] Add an extra defensive check to avoid SCEV assertion.
[llvm-project.git] / flang / test / Semantics / label11.f90
blob6c45edc251f2dbd5a2b26d73d1a3e69af8b39c3a
1 ! RUN: %S/test_errors.sh %s %t %flang_fc1
2 ! REQUIRES: shell
3 ! C739 If END TYPE is followed by a type-name, the type-name shall be the
4 ! same as that in the corresponding derived-type-stmt.
5 ! C1401 The program-name shall not be included in the end-program-stmt unless
6 ! the optional program-stmt is used. If included, it shall be identical to the
7 ! program-name specified in the program-stmt.
8 ! C1402 If the module-name is specified in the end-module-stmt, it shall be
9 ! identical to the module-name specified in the module-stmt.
10 ! C1413 If a submodule-name appears in the end-submodule-stmt, it shall be
11 ! identical to the one in the submodule-stmt.
12 ! C1414 If a function-name appears in the end-function-stmt, it shall be
13 ! identical to the function-name specified in the function-stmt.
14 ! C1502 If the end-interface-stmt includes a generic-spec, the interface-stmt
15 ! shall specify the same generic-spec
16 ! C1564 If a function-name appears in the end-function-stmt, it shall be
17 ! identical to the function-name specified in the function-stmt.
18 ! C1567 If a submodule-name appears in the end-submodule-stmt, it shall be
19 ! identical to the one in the submodule-stmt.
20 ! C1569 If the module-name is specified in the end-module-stmt, it shall be
21 ! identical to the module-name specified in the module-stmt
23 block data t1
24 !ERROR: BLOCK DATA subprogram name mismatch
25 end block data t2
27 function t3
28 !ERROR: FUNCTION name mismatch
29 end function t4
31 subroutine t9
32 !ERROR: SUBROUTINE name mismatch
33 end subroutine t10
35 program t13
36 !ERROR: END PROGRAM name mismatch
37 end program t14
39 submodule (mod) t15
40 !ERROR: SUBMODULE name mismatch
41 end submodule t16
43 module t5
44 interface t7
45 !ERROR: INTERFACE generic-name (t7) mismatch
46 end interface t8
47 type t17
48 !ERROR: derived type definition name mismatch
49 end type t18
51 abstract interface
52 subroutine subrFront()
53 !ERROR: SUBROUTINE name mismatch
54 end subroutine subrBack
55 function funcFront(x)
56 real, intent(in) :: x
57 real funcFront
58 !ERROR: FUNCTION name mismatch
59 end function funcBack
60 end interface
62 contains
63 module procedure t11
64 !ERROR: MODULE PROCEDURE name mismatch
65 end procedure t12
66 !ERROR: MODULE name mismatch
67 end module mox