aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/internal_dummy_4.f08
blob: 8ade99efb88f624e20b1851fbf652d19ecd420bb (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
! { dg-do run }
! PR fortran/34133
! PR fortran/34162
!
! Test of using internal bind(C) procedures as
! actual argument. Bind(c) on internal procedures and
! internal procedures are actual argument are
! Fortran 2008 (draft) extension.
!
module test_mod
  use iso_c_binding
  implicit none
contains
  subroutine test_sub(a, arg, res)
    interface
      subroutine a(x) bind(C)
        import
        integer(c_int), intent(inout) :: x
      end subroutine a
    end interface
    integer(c_int), intent(inout) :: arg
    integer(c_int), intent(in) :: res
    call a(arg)
    if(arg /= res) call abort()
  end subroutine test_sub
  subroutine test_func(a, arg, res)
    interface
      integer(c_int) function a(x) bind(C)
        import
        integer(c_int), intent(in) :: x
      end function a
    end interface
    integer(c_int), intent(in) :: arg
    integer(c_int), intent(in) :: res
    if(a(arg) /= res) call abort()
  end subroutine test_func
end module test_mod

program main
  use test_mod
  implicit none
  integer :: a
  a = 33
  call test_sub (one, a, 7*33)
  a = 23
  call test_func(two, a, -123*23)
contains
  subroutine one(x) bind(c)
     integer(c_int),intent(inout) :: x
     x = 7*x
  end subroutine one
  integer(c_int) function two(y) bind(c)
     integer(c_int),intent(in) :: y
     two = -123*y
  end function two
end program main