aarch64: Add vector floating point extend pattern [PR113880, PR113869]
[official-gcc.git] / gcc / testsuite / gfortran.dg / typebound_generic_4.f03
bloba74cdae750896c3125d376aa46bdc06fb5b65053
1 ! { dg-do run }
3 ! PR fortran/37588
4 ! This test used to not resolve the GENERIC binding.
6 ! Contributed by Salvatore Filippone <sfilippone@uniroma2.it>
8 module bar_mod
10   type foo
11     integer :: i
12     
13   contains
14     procedure, pass(a) :: foo_v => foo_v_inner    
15     procedure, pass(a) :: foo_m => foo_m_inner    
16     generic, public    :: foo => foo_v, foo_m
17   end type foo
18   
19   private foo_v_inner, foo_m_inner
21 contains
22   
23   subroutine foo_v_inner(x,a)
24     real :: x(:)
25     class(foo) :: a
26     
27     a%i = int(x(1))
28     WRITE (*,*) "Vector"
29   end subroutine foo_v_inner
30   
31   subroutine foo_m_inner(x,a)
32     real :: x(:,:)
33     class(foo) :: a
34     
35     a%i = int(x(1,1))
36     WRITE (*,*) "Matrix"
37   end subroutine foo_m_inner
38 end module bar_mod
40 program foobar
41   use bar_mod
42   type(foo) :: dat
43   real :: x1(10), x2(10,10)
45   x1=1
46   x2=2
48   call dat%foo(x1)
49   call dat%foo(x2)
51 end program foobar
53 ! { dg-output "Vector.*Matrix" }