From 554fd8c5195424bdbcabf5de30fdc183aba391bd Mon Sep 17 00:00:00 2001 From: upstream source tree Date: Sun, 15 Mar 2015 20:14:05 -0400 Subject: obtained gcc-4.6.4.tar.bz2 from upstream website; verified gcc-4.6.4.tar.bz2.sig; imported gcc-4.6.4 source tree from verified upstream tarball. downloading a git-generated archive based on the 'upstream' tag should provide you with a source tree that is binary identical to the one extracted from the above tarball. if you have obtained the source via the command 'git clone', however, do note that line-endings of files in your working directory might differ from line-endings of the respective files in the upstream repository. --- .../gfortran.dg/class_defined_operator_1.f03 | 102 +++++++++++++++++++++ 1 file changed, 102 insertions(+) create mode 100644 gcc/testsuite/gfortran.dg/class_defined_operator_1.f03 (limited to 'gcc/testsuite/gfortran.dg/class_defined_operator_1.f03') diff --git a/gcc/testsuite/gfortran.dg/class_defined_operator_1.f03 b/gcc/testsuite/gfortran.dg/class_defined_operator_1.f03 new file mode 100644 index 000000000..008739e3f --- /dev/null +++ b/gcc/testsuite/gfortran.dg/class_defined_operator_1.f03 @@ -0,0 +1,102 @@ +! { dg-do run } +! Test the fix for PR42385, in which CLASS defined operators +! compiled but were not correctly dynamically dispatched. +! +! Contributed by Janus Weil +! +module foo_module + implicit none + private + public :: foo + + type :: foo + integer :: foo_x + contains + procedure :: times => times_foo + procedure :: assign => assign_foo + generic :: operator(*) => times + generic :: assignment(=) => assign + end type + +contains + + function times_foo(this,factor) result(product) + class(foo) ,intent(in) :: this + class(foo) ,allocatable :: product + integer, intent(in) :: factor + allocate (product, source = this) + product%foo_x = -product%foo_x * factor + end function + + subroutine assign_foo(lhs,rhs) + class(foo) ,intent(inout) :: lhs + class(foo) ,intent(in) :: rhs + lhs%foo_x = -rhs%foo_x + end subroutine + +end module + +module bar_module + use foo_module ,only : foo + implicit none + private + public :: bar + + type ,extends(foo) :: bar + integer :: bar_x + contains + procedure :: times => times_bar + procedure :: assign => assign_bar + end type + +contains + subroutine assign_bar(lhs,rhs) + class(bar) ,intent(inout) :: lhs + class(foo) ,intent(in) :: rhs + select type(rhs) + type is (bar) + lhs%bar_x = rhs%bar_x + lhs%foo_x = -rhs%foo_x + end select + end subroutine + function times_bar(this,factor) result(product) + class(bar) ,intent(in) :: this + integer, intent(in) :: factor + class(foo), allocatable :: product + select type(this) + type is (bar) + allocate(product,source=this) + select type(product) + type is(bar) + product%bar_x = 2*this%bar_x*factor + end select + end select + end function +end module + +program main + use foo_module ,only : foo + use bar_module ,only : bar + implicit none + type(foo) :: unitf + type(bar) :: unitb + +! foo's assign negates, whilst its '*' negates and mutliplies. + unitf%foo_x = 1 + call rescale(unitf, 42) + if (unitf%foo_x .ne. 42) call abort + +! bar's assign negates foo_x, whilst its '*' copies foo_x +! and does a multiply by twice factor. + unitb%foo_x = 1 + unitb%bar_x = 2 + call rescale(unitb, 3) + if (unitb%bar_x .ne. 12) call abort + if (unitb%foo_x .ne. -1) call abort +contains + subroutine rescale(this,scale) + class(foo) ,intent(inout) :: this + integer, intent(in) :: scale + this = this*scale + end subroutine +end program -- cgit v1.2.3