view gcc/testsuite/gfortran.dg/interface_17.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 }
! Tests the fix for PR32727, which was a regression caused
! by the fix for PR32634
!
! Contributed by Joost VandeVondele <jv244@cam.ac.uk>
!
MODULE kinds
  INTEGER, PARAMETER :: dp = SELECTED_REAL_KIND ( 14, 200 )
END MODULE kinds

MODULE util
  USE kinds,                           ONLY: dp
  INTERFACE sort
     MODULE PROCEDURE sort2
  END INTERFACE
CONTAINS
  SUBROUTINE sort2 ( )
  END SUBROUTINE sort2
END MODULE util

MODULE graphcon
  USE util,                            ONLY: sort
END MODULE graphcon