view gcc/testsuite/gfortran.dg/extends_7.f03 @ 132:d34655255c78

update gcc-8.2
author mir3636
date Thu, 25 Oct 2018 10:21:07 +0900 (2018-10-25)
parents 04ced10e8804
children
line wrap: on
line source
! { dg-do compile }
! Check for re-definition of inherited components in the sub-type.

MODULE m1
  IMPLICIT NONE

  TYPE supert
    INTEGER :: c1
    INTEGER, PRIVATE :: c2
  END TYPE supert

END MODULE m1

MODULE m2
  USE m1 ! { dg-error "already in the parent type" }
  IMPLICIT NONE

  TYPE, EXTENDS(supert) :: subt
    INTEGER :: c1 ! { dg-error "already in the parent type" }
    INTEGER :: c2 ! { dg-error "already in the parent type" }
  END TYPE subt

END MODULE m2