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_dummy_types_5.f90] - Diff between revs 154 and 816

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

Rev 154 Rev 816
! { dg-do compile }
! { dg-do compile }
! This checks that the fix for PR19362 has not broken gfortran
! This checks that the fix for PR19362 has not broken gfortran
! in respect of.references allowed by 4.4.2.
! in respect of.references allowed by 4.4.2.
!
!
! Contributed by Paul Thomas  
! Contributed by Paul Thomas  
!==============
!==============
module global
module global
  TYPE :: seq_type1
  TYPE :: seq_type1
    sequence
    sequence
    integer :: i
    integer :: i
  end type seq_type1
  end type seq_type1
  TYPE :: nonseq_type1
  TYPE :: nonseq_type1
    integer :: i = 44
    integer :: i = 44
  end type nonseq_type1
  end type nonseq_type1
  type (nonseq_type1), save :: ns1
  type (nonseq_type1), save :: ns1
end module global
end module global
  use global, only: seq_type2=>seq_type1, nonseq_type1, ns1
  use global, only: seq_type2=>seq_type1, nonseq_type1, ns1
! Host non-sequence types
! Host non-sequence types
  type :: different_type
  type :: different_type
    integer :: i
    integer :: i
  end type different_type
  end type different_type
  type :: same_type
  type :: same_type
    sequence
    sequence
    integer :: i
    integer :: i
  end type same_type
  end type same_type
  type (seq_type2)  :: t1
  type (seq_type2)  :: t1
  type (different_type)  :: dt1
  type (different_type)  :: dt1
  type (nonseq_type1) :: ns2
  type (nonseq_type1) :: ns2
  type (same_type)  :: st1
  type (same_type)  :: st1
  real seq_type1
  real seq_type1
  t1 = seq_type2 (42)
  t1 = seq_type2 (42)
  dt1 = different_type (43)
  dt1 = different_type (43)
  ns2 = ns1
  ns2 = ns1
  seq_type1 =1.0e32
  seq_type1 =1.0e32
  st1%i = 45
  st1%i = 45
  call foo (t1)
  call foo (t1)
contains
contains
  subroutine foo (x)
  subroutine foo (x)
    use global, only: seq_type3=>seq_type1
    use global, only: seq_type3=>seq_type1
    TYPE :: seq_type1
    TYPE :: seq_type1
      sequence
      sequence
      integer :: i
      integer :: i
    end type seq_type1
    end type seq_type1
    type :: different_type
    type :: different_type
      complex :: z
      complex :: z
    end type different_type
    end type different_type
    type :: same_type
    type :: same_type
      sequence
      sequence
      integer :: i
      integer :: i
    end type same_type
    end type same_type
! Host association of renamed type.
! Host association of renamed type.
    type (seq_type2) :: x
    type (seq_type2) :: x
! Locally declared version of the same thing.
! Locally declared version of the same thing.
    type (seq_type1) :: y
    type (seq_type1) :: y
! USE associated renamed type.
! USE associated renamed type.
    type (seq_type3) :: z
    type (seq_type3) :: z
    type (different_type)  :: dt2
    type (different_type)  :: dt2
    type (same_type)  :: st2
    type (same_type)  :: st2
    dt2%z = (2.0,-1.0)
    dt2%z = (2.0,-1.0)
    y = seq_type2 (46)
    y = seq_type2 (46)
    z = seq_type3 (47)
    z = seq_type3 (47)
    st2 = st1
    st2 = st1
    print *, x, y, z, dt2, st2, ns2, ns1
    print *, x, y, z, dt2, st2, ns2, ns1
  end subroutine foo
  end subroutine foo
END
END
! { dg-final { cleanup-modules "global" } }
! { dg-final { cleanup-modules "global" } }
 
 

powered by: WebSVN 2.1.0

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