From e91c0a35e5d1af2018c379962cbe1008788aba72 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Thomas=20K=C3=B6nig?= <tkoenig@gcc.gnu.org>
Date: Sun, 19 Apr 2020 13:06:22 +0200
Subject: [PATCH] Commit test case for PR 57129.

2020-04-19  Thomas Koenig  <tkoenig@gcc.gnu.org>

	PR fortran/57129
	* gfortran.dg/subroutine_as_type.f90: New test.
---
 gcc/testsuite/ChangeLog                          | 7 ++++++-
 gcc/testsuite/gfortran.dg/subroutine_as_type.f90 | 7 +++++++
 2 files changed, 13 insertions(+), 1 deletion(-)
 create mode 100644 gcc/testsuite/gfortran.dg/subroutine_as_type.f90

diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index e8742902d12a..315a29bd05fc 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,7 +1,12 @@
+2020-04-19  Thomas Koenig  <tkoenig@gcc.gnu.org>
+
+	PR fortran/57129
+	* gfortran.dg/subroutine_as_type.f90: New test.
+
 2020-04-19  Thomas Koenig  <tkoenig@gcc.gnu.org>
 
 	PR fortran/93500
-	* arith_divide_3.f90: New test.
+	* gfortran.dg/arith_divide_3.f90: New test.
 
 2020-04-19  Jakub Jelinek  <jakub@redhat.com>
 
diff --git a/gcc/testsuite/gfortran.dg/subroutine_as_type.f90 b/gcc/testsuite/gfortran.dg/subroutine_as_type.f90
new file mode 100644
index 000000000000..eb8240fbb7bc
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/subroutine_as_type.f90
@@ -0,0 +1,7 @@
+
+subroutine t()
+  type t  ! { dg-error "FUNCTION attribute conflicts with SUBROUTINE attribute" }
+  end type t ! { dg-error "Expecting END SUBROUTINE statement" }
+  type, extends(t) :: t2   ! { dg-error "has not been previously defined" }
+  end type t2 ! { dg-error "Expecting END SUBROUTINE statement" }
+end
-- 
GitLab