aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/typebound_call_9.f03
blob: c40850610e1654c466a6ef68b91253da3cff8af5 (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
57
58
! { dg-do compile }

! PR fortran/37638
! If a PASS(arg) is invalid, a call to this routine later would ICE in
! resolving.  Check that this also works for GENERIC, in addition to the
! PR's original test.

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

module foo_mod
  implicit none 

  type base_foo_type 
    integer           :: nr,nc
    integer, allocatable :: iv1(:), iv2(:)

  contains

    procedure, pass(a) :: makenull ! { dg-error "has no argument 'a'" }
    generic :: null2 => makenull   ! { dg-error "Undefined specific binding" }

  end type base_foo_type

contains

  subroutine makenull(m)
    implicit none
    type(base_foo_type), intent(inout) :: m

    m%nr=0
    m%nc=0

  end subroutine makenull

  subroutine foo_free(a,info)
    implicit none
    Type(base_foo_type), intent(inout)  :: A
    Integer, intent(out)        :: info
    integer             :: iret
    info  = 0


    if (allocated(a%iv1)) then
      deallocate(a%iv1,stat=iret)
      if (iret /= 0) info = max(info,2)
    endif
    if (allocated(a%iv2)) then
      deallocate(a%iv2,stat=iret)
      if (iret /= 0) info = max(info,3)
    endif

    call a%makenull()
    call a%null2 () ! { dg-error "should be a SUBROUTINE" }

    Return
  End Subroutine foo_free

end module foo_mod