OpenCores
URL https://opencores.org/ocsvn/openrisc_2011-10-31/openrisc_2011-10-31/trunk

Subversion Repositories openrisc_2011-10-31

[/] [openrisc/] [trunk/] [gnu-src/] [gcc-4.5.1/] [gcc/] [testsuite/] [gfortran.dg/] [internal_pack_7.f90] - Blame information for rev 325

Go to most recent revision | Details | Compare with Previous | View Log

Line No. Rev Author Line
1 302 jeremybenn
! { dg-do compile }
2
! { dg-options "-fdump-tree-original" }
3
!
4
! Test the fix for PR43072, in which unnecessary calls to
5
! internal PACK/UNPACK were being generated.
6
!
7
! Contributed by Joost VandeVondele 
8
!
9
MODULE M1
10
  PRIVATE
11
  REAL, PARAMETER :: c(2)=(/(i,i=1,2)/)
12
CONTAINS
13
  ! WAS OK
14
  SUBROUTINE S0
15
    real :: r
16
     r=0
17
     r=S2(c)
18
     r=S2((/(real(i),i=1,2)/)) ! See comment #1 of the PR
19
  END SUBROUTINE S0
20
  ! WAS NOT OK
21
  SUBROUTINE S1
22
    real :: r
23
     r=0
24
     r=r+S2(c)
25
     r=r+S2((/(real(i),i=1,2)/)) ! See comment #1 of the PR
26
  END SUBROUTINE S1
27
 
28
  FUNCTION S2(c)
29
     REAL, INTENT(IN) :: c(2)
30
     s2=0
31
  END FUNCTION S2
32
END MODULE M1
33
! { dg-final { cleanup-modules "M1" } }
34
! { dg-final { scan-tree-dump-times "pack" 0 "original" } }
35
! { dg-final { cleanup-tree-dump "original" } }

powered by: WebSVN 2.1.0

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