summaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/elemental_subroutine_4.f90
diff options
context:
space:
mode:
Diffstat (limited to 'gcc/testsuite/gfortran.dg/elemental_subroutine_4.f90')
-rw-r--r--gcc/testsuite/gfortran.dg/elemental_subroutine_4.f9038
1 files changed, 38 insertions, 0 deletions
diff --git a/gcc/testsuite/gfortran.dg/elemental_subroutine_4.f90 b/gcc/testsuite/gfortran.dg/elemental_subroutine_4.f90
new file mode 100644
index 000000000..9d2bc492f
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/elemental_subroutine_4.f90
@@ -0,0 +1,38 @@
+! { dg-do compile }
+! Test the fix for PR25099, in which conformance checking was not being
+! done for elemental subroutines and therefore for interface assignments.
+!
+! Contributed by Joost VandeVondele <jv244@cam.ac.uk>
+!
+module elem_assign
+ implicit none
+ type mytype
+ integer x
+ end type mytype
+ interface assignment(=)
+ module procedure myassign
+ end interface assignment(=)
+ contains
+ elemental subroutine myassign(x,y)
+ type(mytype), intent(out) :: x
+ type(mytype), intent(in) :: y
+ x%x = y%x
+ end subroutine myassign
+end module elem_assign
+
+ use elem_assign
+ integer :: I(2,2),J(2)
+ type (mytype) :: w(2,2), x(4), y(5), z(4)
+! The original PR
+ CALL S(I,J) ! { dg-error "Incompatible ranks in elemental procedure" }
+! Check interface assignments
+ x = w ! { dg-error "Incompatible ranks in elemental procedure" }
+ x = y ! { dg-error "Different shape for elemental procedure" }
+ x = z
+CONTAINS
+ ELEMENTAL SUBROUTINE S(I,J)
+ INTEGER, INTENT(IN) :: I,J
+ END SUBROUTINE S
+END
+
+! { dg-final { cleanup-modules "elem_assign" } }