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

Subversion Repositories openrisc

[/] [openrisc/] [tags/] [gnu-src/] [gcc-4.5.1/] [gcc-4.5.1-or32-1.0rc3/] [gcc/] [testsuite/] [gfortran.dg/] [module_equivalence_5.f90] - Blame information for rev 516

Details | Compare with Previous | View Log

Line No. Rev Author Line
1 302 jeremybenn
! { dg-do run }
2
!
3
! Fixes PR37787 where the EQUIVALENCE between QLA1 and QLA2 wasn't recognized
4
! in the dependency checking because the compiler was looking in the wrong name
5
! space.
6
!
7
! Contributed by Dick Hendrickson 
8
!
9
module stuff
10
  integer, parameter :: r4_kv = 4
11
contains
12
 
13
  SUBROUTINE CF0004
14
!  COPYRIGHT 1999   SPACKMAN & HENDRICKSON, INC.
15
    REAL(R4_KV), dimension (10) :: QLA1, QLA2, QLA3, &
16
                                   QCA = (/(i, i= 1, 10)/)
17
    EQUIVALENCE (QLA1, QLA2)
18
    QLA1 = QCA
19
    QLA3 = QCA
20
    QLA3( 2:10:3) = QCA ( 1:5:2) + 1
21
    QLA1( 2:10:3) = QLA2( 1:5:2) + 1  !failed because of dependency
22
    if (any (qla1 .ne. qla3)) call abort
23
  END SUBROUTINE
24
end module
25
 
26
program try_cf004
27
  use stuff
28
  nf1 = 1
29
  nf2 = 2
30
  call cf0004
31
end
32
 
33
! { dg-final { cleanup-modules "stuff" } }
34
 

powered by: WebSVN 2.1.0

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