view gcc/testsuite/gfortran.dg/proc_ptr_13.f90 @ 152:2b5abeee2509

update gcc11
author anatofuz
date Mon, 25 May 2020 07:50:57 +0900
parents 04ced10e8804
children
line wrap: on
line source

! { dg-do compile }
! { dg-options "-g" }
!
! PR 38152: Procedure pointers as module variables.
!
! Contributed by Daniel Kraft <domob@gcc.gnu.org>

MODULE myfortran_binding

  IMPLICIT NONE
  PROCEDURE(error_stop), POINTER :: error_handler

CONTAINS

  LOGICAL FUNCTION myfortran_shutdown ()
    CALL error_handler ()
  END FUNCTION myfortran_shutdown

  SUBROUTINE error_stop ()
  END SUBROUTINE error_stop

END MODULE myfortran_binding


use myfortran_binding
error_handler => error_stop
end