summaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/interface_32.f90
diff options
context:
space:
mode:
authorupstream source tree <ports@midipix.org>2015-03-15 20:14:05 -0400
committerupstream source tree <ports@midipix.org>2015-03-15 20:14:05 -0400
commit554fd8c5195424bdbcabf5de30fdc183aba391bd (patch)
tree976dc5ab7fddf506dadce60ae936f43f58787092 /gcc/testsuite/gfortran.dg/interface_32.f90
downloadcbb-gcc-4.6.4-554fd8c5195424bdbcabf5de30fdc183aba391bd.tar.bz2
cbb-gcc-4.6.4-554fd8c5195424bdbcabf5de30fdc183aba391bd.tar.xz
obtained gcc-4.6.4.tar.bz2 from upstream website;upstream
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.
Diffstat (limited to 'gcc/testsuite/gfortran.dg/interface_32.f90')
-rw-r--r--gcc/testsuite/gfortran.dg/interface_32.f9081
1 files changed, 81 insertions, 0 deletions
diff --git a/gcc/testsuite/gfortran.dg/interface_32.f90 b/gcc/testsuite/gfortran.dg/interface_32.f90
new file mode 100644
index 000000000..6cdb091ae
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/interface_32.f90
@@ -0,0 +1,81 @@
+! { dg-do compile }
+module m1
+ implicit none
+
+ type, abstract :: vector_class
+ end type vector_class
+end module m1
+!---------------------------------------------------------------
+module m2
+ use m1
+ implicit none
+
+ type, abstract :: inner_product_class
+ contains
+ procedure(dot), deferred :: dot_v_v
+ procedure(dot), deferred :: dot_g_g
+ procedure(sub), deferred :: D_times_v
+ procedure(sub), deferred :: D_times_g
+ end type inner_product_class
+
+ abstract interface
+ function dot (this,a,b)
+ import :: inner_product_class
+ import :: vector_class
+ class(inner_product_class), intent(in) :: this
+ class(vector_class), intent(in) :: a,b
+ real :: dot
+ end function
+ subroutine sub (this,a)
+ import :: inner_product_class
+ import :: vector_class
+ class(inner_product_class), intent(in) :: this
+ class(vector_class), intent(inout) :: a
+ end subroutine
+ end interface
+end module m2
+!---------------------------------------------------------------
+module m3
+ use :: m1
+ use :: m2
+ implicit none
+ private
+ public :: gradient_class
+
+ type, abstract, extends(vector_class) :: gradient_class
+ class(inner_product_class), pointer :: my_inner_product => NULL()
+ contains
+ procedure, non_overridable :: inquire_inner_product
+ procedure(op_g_v), deferred :: to_vector
+ end type gradient_class
+
+ abstract interface
+ subroutine op_g_v(this,v)
+ import vector_class
+ import gradient_class
+ class(gradient_class), intent(in) :: this
+ class(vector_class), intent(inout) :: v
+ end subroutine
+ end interface
+contains
+ function inquire_inner_product (this)
+ class(gradient_class) :: this
+ class(inner_product_class), pointer :: inquire_inner_product
+
+ inquire_inner_product => this%my_inner_product
+ end function inquire_inner_product
+end module m3
+!---------------------------------------------------------------
+module m4
+ use m3
+ use m2
+ implicit none
+contains
+ subroutine cg (g_initial)
+ class(gradient_class), intent(in) :: g_initial
+
+ class(inner_product_class), pointer :: ip_save
+ ip_save => g_initial%inquire_inner_product()
+ end subroutine cg
+end module m4
+! { dg-final { cleanup-modules "m1 m2 m3 m4" } }