aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/typebound_generic_4.f03
blob: a74cdae750896c3125d376aa46bdc06fb5b65053 (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
! { dg-do run }

! PR fortran/37588
! This test used to not resolve the GENERIC binding.

! Contributed by Salvatore Filippone <sfilippone@uniroma2.it>

module bar_mod

  type foo
    integer :: i
    
  contains
    procedure, pass(a) :: foo_v => foo_v_inner    
    procedure, pass(a) :: foo_m => foo_m_inner    
    generic, public    :: foo => foo_v, foo_m
  end type foo
  
  private foo_v_inner, foo_m_inner

contains
  
  subroutine foo_v_inner(x,a)
    real :: x(:)
    class(foo) :: a
    
    a%i = int(x(1))
    WRITE (*,*) "Vector"
  end subroutine foo_v_inner
  
  subroutine foo_m_inner(x,a)
    real :: x(:,:)
    class(foo) :: a
    
    a%i = int(x(1,1))
    WRITE (*,*) "Matrix"
  end subroutine foo_m_inner
end module bar_mod

program foobar
  use bar_mod
  type(foo) :: dat
  real :: x1(10), x2(10,10)

  x1=1
  x2=2
 
  call dat%foo(x1)
  call dat%foo(x2)

end program foobar

! { dg-output "Vector.*Matrix" }