summaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/interface_35.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_35.f90
downloadcbb-gcc-4.6.4-15d2061ac0796199866debe9ac87130894b0cdd3.tar.bz2
cbb-gcc-4.6.4-15d2061ac0796199866debe9ac87130894b0cdd3.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_35.f90')
-rw-r--r--gcc/testsuite/gfortran.dg/interface_35.f9079
1 files changed, 79 insertions, 0 deletions
diff --git a/gcc/testsuite/gfortran.dg/interface_35.f90 b/gcc/testsuite/gfortran.dg/interface_35.f90
new file mode 100644
index 000000000..20aa4af78
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/interface_35.f90
@@ -0,0 +1,79 @@
+! { dg-do compile }
+! { dg-options "-std=f2008" }
+!
+! PR fortran/48112 (module_m)
+! PR fortran/48279 (sidl_string_array, s_Hard)
+!
+! Contributed by mhp77@gmx.at (module_m)
+! and Adrian Prantl (sidl_string_array, s_Hard)
+!
+
+module module_m
+ interface test
+ function test1( ) result( test )
+ integer :: test
+ end function test1
+ end interface test
+end module module_m
+
+! -----
+
+module sidl_string_array
+ type sidl_string_1d
+ end type sidl_string_1d
+ interface set
+ module procedure &
+ setg1_p
+ end interface
+contains
+ subroutine setg1_p(array, index, val)
+ type(sidl_string_1d), intent(inout) :: array
+ end subroutine setg1_p
+end module sidl_string_array
+
+module s_Hard
+ use sidl_string_array
+ type :: s_Hard_t
+ integer(8) :: dummy
+ end type s_Hard_t
+ interface set_d_interface
+ end interface
+ interface get_d_string
+ module procedure get_d_string_p
+ end interface
+ contains ! Derived type member access functions
+ type(sidl_string_1d) function get_d_string_p(s)
+ type(s_Hard_t), intent(in) :: s
+ end function get_d_string_p
+ subroutine set_d_objectArray_p(s, d_objectArray)
+ end subroutine set_d_objectArray_p
+end module s_Hard
+
+subroutine initHard(h, ex)
+ use s_Hard
+ type(s_Hard_t), intent(inout) :: h
+ call set(get_d_string(h), 0, 'Three') ! { dg-error "There is no specific subroutine for the generic" }
+end subroutine initHard
+
+! -----
+
+ interface get
+ procedure get1
+ end interface
+
+ integer :: h
+ call set1 (get (h))
+
+contains
+
+ subroutine set1 (a)
+ integer, intent(in) :: a
+ end subroutine
+
+ integer function get1 (s) ! { dg-error "Extension: Internal procedure .get1. in generic interface .get." }
+ integer :: s
+ end function
+
+end
+
+! { dg-final { cleanup-modules "module_m module_m2 s_hard sidl_string_array" } }