summaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/exit_2.f08
diff options
context:
space:
mode:
Diffstat (limited to 'gcc/testsuite/gfortran.dg/exit_2.f08')
-rw-r--r--gcc/testsuite/gfortran.dg/exit_2.f0831
1 files changed, 31 insertions, 0 deletions
diff --git a/gcc/testsuite/gfortran.dg/exit_2.f08 b/gcc/testsuite/gfortran.dg/exit_2.f08
new file mode 100644
index 00000000000..23e7009cbf8
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/exit_2.f08
@@ -0,0 +1,31 @@
+! { dg-do compile }
+! { dg-options "-std=f2008" }
+
+! PR fortran/44709
+! Check that the resolving of loop names in parent namespaces introduced to
+! handle intermediate BLOCK's does not go too far and other sanity checks.
+
+! Contributed by Daniel Kraft, d@domob.eu.
+
+PROGRAM main
+ IMPLICIT NONE
+
+ EXIT ! { dg-error "is not within a loop" }
+ EXIT foobar ! { dg-error "is unknown" }
+ EXIT main ! { dg-error "is not a loop name" }
+
+ mainLoop: DO
+ CALL test ()
+ END DO mainLoop
+
+ otherLoop: DO
+ EXIT mainLoop ! { dg-error "is not within loop 'mainloop'" }
+ END DO otherLoop
+
+CONTAINS
+
+ SUBROUTINE test ()
+ EXIT mainLoop ! { dg-error "is unknown" }
+ END SUBROUTINE test
+
+END PROGRAM main