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

Subversion Repositories openrisc

[/] [openrisc/] [trunk/] [gnu-old/] [gcc-4.2.2/] [gcc/] [testsuite/] [gfortran.dg/] [used_types_3.f90] - Diff between revs 154 and 816

Go to most recent revision | Only display areas with differences | Details | Blame | View Log

Rev 154 Rev 816
! { dg-do compile }
! { dg-do compile }
! Test the fix for PR28601 in which line 55 would produce an ICE
! Test the fix for PR28601 in which line 55 would produce an ICE
! because the rhs and lhs derived times were not identically
! because the rhs and lhs derived times were not identically
! associated and so could not be cast.
! associated and so could not be cast.
!
!
! Contributed by Francois-Xavier Coudert  
! Contributed by Francois-Xavier Coudert  
!
!
module modA
module modA
implicit none
implicit none
save
save
private
private
type, public :: typA
type, public :: typA
integer :: i
integer :: i
end type typA
end type typA
type, public :: atom
type, public :: atom
type(typA), pointer :: ofTypA(:,:)
type(typA), pointer :: ofTypA(:,:)
end type atom
end type atom
end module modA
end module modA
!!! re-name and re-export typA as typB:
!!! re-name and re-export typA as typB:
module modB
module modB
use modA, only: typB => typA
use modA, only: typB => typA
implicit none
implicit none
save
save
private
private
public typB
public typB
end module modB
end module modB
!!! mixed used of typA and typeB:
!!! mixed used of typA and typeB:
module modC
module modC
use modB
use modB
implicit none
implicit none
save
save
private
private
contains
contains
subroutine buggy(a)
subroutine buggy(a)
use modA, only: atom
use modA, only: atom
! use modB, only: typB
! use modB, only: typB
! use modA, only: typA
! use modA, only: typA
implicit none
implicit none
type(atom),intent(inout) :: a
type(atom),intent(inout) :: a
target :: a
target :: a
! *** end of interface ***
! *** end of interface ***
type(typB), pointer :: ofTypB(:,:)
type(typB), pointer :: ofTypB(:,:)
! type(typA), pointer :: ofTypB(:,:)
! type(typA), pointer :: ofTypB(:,:)
integer :: i,j,k
integer :: i,j,k
ofTypB => a%ofTypA
ofTypB => a%ofTypA
a%ofTypA(i,j) = ofTypB(k,j)
a%ofTypA(i,j) = ofTypB(k,j)
end subroutine buggy
end subroutine buggy
end module modC
end module modC
! { dg-final { cleanup-modules "modA modB modC" } }
! { dg-final { cleanup-modules "modA modB modC" } }
 
 

powered by: WebSVN 2.1.0

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