OSDN Git Service

2010-02-10 Joost VandeVondele <jv244@cam.ac.uk>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / typebound_operator_2.f03
index 71e8e4f..cae2cda 100644 (file)
@@ -1,6 +1,4 @@
 ! { dg-do compile }
-! { dg-options "-w" }
-! FIXME: Remove -w once CLASS is fully supported.
 
 ! Type-bound procedures
 ! Checks for correct errors with invalid OPERATOR/ASSIGNMENT usage.
@@ -16,7 +14,7 @@ MODULE m
     PROCEDURE, NOPASS :: nopassed => onearg
     PROCEDURE, PASS :: threearg
     PROCEDURE, PASS :: sub
-    PROCEDURE, PASS :: sub2 ! { dg-error "must be a FUNCTION" }
+    PROCEDURE, PASS :: sub2
     PROCEDURE, PASS :: func
 
     ! These give errors at the targets' definitions.
@@ -52,7 +50,6 @@ CONTAINS
   LOGICAL FUNCTION func (me, b) ! { dg-error "must be a SUBROUTINE" }
     CLASS(t), INTENT(OUT) :: me
     CLASS(t), INTENT(IN) :: b
-    me = t ()
     func = .TRUE.
   END FUNCTION func
 
@@ -60,7 +57,7 @@ CONTAINS
     CLASS(t), INTENT(IN) :: a
   END SUBROUTINE sub
 
-  SUBROUTINE sub2 (a, x)
+  SUBROUTINE sub2 (a, x) ! { dg-error "must be a FUNCTION" }
     CLASS(t), INTENT(IN) :: a
     INTEGER, INTENT(IN) :: x
   END SUBROUTINE sub2