OpenCores
URL https://opencores.org/ocsvn/openrisc_me/openrisc_me/trunk

Subversion Repositories openrisc_me

[/] [openrisc/] [trunk/] [gnu-src/] [gcc-4.2.2/] [gcc/] [testsuite/] [gfortran.dg/] [used_types_6.f90] - Diff between revs 149 and 154

Only display areas with differences | Details | Blame | View Log

Rev 149 Rev 154
! { dg-do compile }
! { dg-do compile }
! Tests the fix for a further regression caused by the
! Tests the fix for a further regression caused by the
! fix for PR28788, as noted in reply #13 in the Bugzilla
! fix for PR28788, as noted in reply #13 in the Bugzilla
! entry by Martin Tee  .
! entry by Martin Tee  .
! The problem was caused by contained, use associated
! The problem was caused by contained, use associated
! derived types with pointer components of a derived type
! derived types with pointer components of a derived type
! use associated in a sibling procedure, where both are
! use associated in a sibling procedure, where both are
! associated by an ONLY clause. This is the reporter's
! associated by an ONLY clause. This is the reporter's
! test case.
! test case.
!
!
MODULE type_mod
MODULE type_mod
  TYPE a
  TYPE a
    INTEGER  :: n(10)
    INTEGER  :: n(10)
  END TYPE a
  END TYPE a
  TYPE b
  TYPE b
    TYPE (a), POINTER :: m(:) => NULL ()
    TYPE (a), POINTER :: m(:) => NULL ()
  END TYPE b
  END TYPE b
END MODULE type_mod
END MODULE type_mod
MODULE seg_mod
MODULE seg_mod
CONTAINS
CONTAINS
  SUBROUTINE foo (x)
  SUBROUTINE foo (x)
    USE type_mod, ONLY : a     ! failed
    USE type_mod, ONLY : a     ! failed
    IMPLICIT NONE
    IMPLICIT NONE
    TYPE (a)  :: x
    TYPE (a)  :: x
    RETURN
    RETURN
  END SUBROUTINE foo
  END SUBROUTINE foo
  SUBROUTINE bar (x)
  SUBROUTINE bar (x)
    USE type_mod, ONLY : b     ! failed
    USE type_mod, ONLY : b     ! failed
    IMPLICIT NONE
    IMPLICIT NONE
    TYPE (b)  :: x
    TYPE (b)  :: x
    RETURN
    RETURN
  END SUBROUTINE bar
  END SUBROUTINE bar
END MODULE seg_mod
END MODULE seg_mod
! { dg-final { cleanup-modules "type_mod seg_mod" } }
! { dg-final { cleanup-modules "type_mod seg_mod" } }
 
 

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.