aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/typebound_proc_13.f03
diff options
context:
space:
mode:
Diffstat (limited to 'gcc-4.9/gcc/testsuite/gfortran.dg/typebound_proc_13.f03')
-rw-r--r--gcc-4.9/gcc/testsuite/gfortran.dg/typebound_proc_13.f0346
1 files changed, 46 insertions, 0 deletions
diff --git a/gcc-4.9/gcc/testsuite/gfortran.dg/typebound_proc_13.f03 b/gcc-4.9/gcc/testsuite/gfortran.dg/typebound_proc_13.f03
new file mode 100644
index 000000000..98caac692
--- /dev/null
+++ b/gcc-4.9/gcc/testsuite/gfortran.dg/typebound_proc_13.f03
@@ -0,0 +1,46 @@
+! { dg-do compile }
+
+! PR fortran/41177
+! Test for additional errors with type-bound procedure bindings.
+! Namely that non-scalar base objects are rejected for TBP calls which are
+! NOPASS, and that passed-object dummy arguments must be scalar, non-POINTER
+! and non-ALLOCATABLE.
+
+MODULE m
+ IMPLICIT NONE
+
+ TYPE t
+ CONTAINS
+ PROCEDURE, NOPASS :: myproc
+ END TYPE t
+
+ TYPE t2
+ CONTAINS
+ PROCEDURE, PASS :: nonscalar ! { dg-error "must be scalar" }
+ PROCEDURE, PASS :: is_pointer ! { dg-error "must not be POINTER" }
+ PROCEDURE, PASS :: is_allocatable ! { dg-error "must not be ALLOCATABLE" }
+ END TYPE t2
+
+CONTAINS
+
+ SUBROUTINE myproc ()
+ END SUBROUTINE myproc
+
+ SUBROUTINE nonscalar (me)
+ CLASS(t2), INTENT(IN) :: me(:)
+ END SUBROUTINE nonscalar
+
+ SUBROUTINE is_pointer (me)
+ CLASS(t2), POINTER, INTENT(IN) :: me
+ END SUBROUTINE is_pointer
+
+ SUBROUTINE is_allocatable (me)
+ CLASS(t2), ALLOCATABLE, INTENT(IN) :: me
+ END SUBROUTINE is_allocatable
+
+ SUBROUTINE test ()
+ TYPE(t) :: arr(2)
+ CALL arr%myproc () ! { dg-error "must be scalar" }
+ END SUBROUTINE test
+
+END MODULE m