view gcc/testsuite/gfortran.dg/warn_unused_function_2.f90 @ 128:fe568345ddd5

fix CbC-example
author mir3636
date Wed, 11 Apr 2018 19:32:28 +0900
parents 04ced10e8804
children
line wrap: on
line source

! { dg-do compile }
! { dg-options "-Wall" }
!
! [4.8 Regression] PR 54997: -Wunused-function gives false warnings
! PR 54224: missing warnings with -Wunused-function
!
! Contributed by Janus Weil <janus@gcc.gnu.org>

module m

  implicit none
  private :: s1,s2,s3

contains

  subroutine s1            ! { dg-warning "defined but not used" }
    call s2(s3)
    contains
      subroutine s4        ! { dg-warning "defined but not used" }
      end subroutine
  end subroutine

  subroutine s2(dummy)     ! { dg-warning "Unused dummy argument" }
    procedure() :: dummy
  end subroutine

  subroutine s3()
  end subroutine

end module


subroutine sub
entry en
end subroutine

program test
contains
  subroutine s5            ! { dg-warning "defined but not used" }
  end subroutine
end