view gcc/testsuite/gfortran.dg/use_rename_8.f90 @ 131:84e7813d76e9

gcc-8.2
author mir3636
date Thu, 25 Oct 2018 07:37:49 +0900
parents 04ced10e8804
children 1830386684a0
line wrap: on
line source

! { dg-do compile }
!
! PR fortran/63744
! duplicate use rename used to be rejected when the target name
! was that of the current program unit 
!
! Original testcase from Roger Ferrer Ibanez <roger.ferrer@bsc.es>

MODULE MOO
    INTEGER :: A, B, C, D, E, F, G, H, I
END MODULE MOO

SUBROUTINE S
    USE MOO, ONLY: X => A, X => A
END SUBROUTINE S

SUBROUTINE T
    USE MOO, ONLY: X => B
    USE MOO, ONLY: X => B
END SUBROUTINE T

SUBROUTINE C
    USE MOO, ONLY: C  ! { dg-error "is also the name of the current program unit" }
END SUBROUTINE C

SUBROUTINE D
    USE MOO, ONLY: X => D
END SUBROUTINE D

SUBROUTINE E
    USE MOO, ONLY: X => E, X => E
END SUBROUTINE E

SUBROUTINE F
    USE MOO, ONLY: X => F
    USE MOO, ONLY: X => F
END SUBROUTINE F

SUBROUTINE X
    USE MOO, ONLY: X => G ! { dg-error "is also the name of the current program unit" }
END SUBROUTINE X

SUBROUTINE Y
    USE MOO, ONLY: Y => H ! { dg-error "is also the name of the current program unit" }
END SUBROUTINE Y

SUBROUTINE Z
    USE MOO, ONLY: Z => I, Z => I ! { dg-error "is also the name of the current program unit" }
END SUBROUTINE Z