11558Srgrimes! { dg-do run }
21558Srgrimes! PR fortran/34133
31558Srgrimes! PR fortran/34162
41558Srgrimes!
51558Srgrimes! Test of using internal bind(C) procedures as
61558Srgrimes! actual argument. Bind(c) on internal procedures and
71558Srgrimes! internal procedures are actual argument are
81558Srgrimes! Fortran 2008 (draft) extension.
91558Srgrimes!
101558Srgrimesmodule test_mod
111558Srgrimes  use iso_c_binding
121558Srgrimes  implicit none
131558Srgrimescontains
141558Srgrimes  subroutine test_sub(a, arg, res)
151558Srgrimes    interface
161558Srgrimes      subroutine a(x) bind(C)
171558Srgrimes        import
181558Srgrimes        integer(c_int), intent(inout) :: x
191558Srgrimes      end subroutine a
201558Srgrimes    end interface
211558Srgrimes    integer(c_int), intent(inout) :: arg
221558Srgrimes    integer(c_int), intent(in) :: res
231558Srgrimes    call a(arg)
241558Srgrimes    if(arg /= res) call abort()
251558Srgrimes  end subroutine test_sub
261558Srgrimes  subroutine test_func(a, arg, res)
271558Srgrimes    interface
281558Srgrimes      integer(c_int) function a(x) bind(C)
291558Srgrimes        import
301558Srgrimes        integer(c_int), intent(in) :: x
311558Srgrimes      end function a
321558Srgrimes    end interface
331558Srgrimes    integer(c_int), intent(in) :: arg
341558Srgrimes    integer(c_int), intent(in) :: res
3523675Speter    if(a(arg) /= res) call abort()
361558Srgrimes  end subroutine test_func
371558Srgrimesend module test_mod
381558Srgrimes
3941474Sjulianprogram main
4023675Speter  use test_mod
411558Srgrimes  implicit none
4241474Sjulian  integer :: a
4341474Sjulian  a = 33
4423675Speter  call test_sub (one, a, 7*33)
4541474Sjulian  a = 23
4641474Sjulian  call test_func(two, a, -123*23)
471558Srgrimescontains
481558Srgrimes  subroutine one(x) bind(c)
497585Sbde     integer(c_int),intent(inout) :: x
501558Srgrimes     x = 7*x
511558Srgrimes  end subroutine one
5241474Sjulian  integer(c_int) function two(y) bind(c)
5341474Sjulian     integer(c_int),intent(in) :: y
541558Srgrimes     two = -123*y
5541474Sjulian  end function two
5641474Sjulianend program main
571558Srgrimes