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/] [dependency_26.f90] - Blame information for rev 302

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 PR36932 and PR36933, in which unnecessary
5
! temporaries were being generated.  The module m2 tests the
6
! additional testcase in comment #3 of PR36932.
7
!
8
! Contributed by Joost VandeVondele 
9
!
10
MODULE M2
11
  IMPLICIT NONE
12
  TYPE particle
13
   REAL :: r(3)
14
  END TYPE
15
CONTAINS
16
  SUBROUTINE S1(p)
17
     TYPE(particle), POINTER, DIMENSION(:) :: p
18
     REAL :: b(3)
19
     INTEGER :: i
20
     b=pbc(p(i)%r)
21
  END SUBROUTINE S1
22
  FUNCTION pbc(b)
23
     REAL :: b(3)
24
     REAL :: pbc(3)
25
     pbc=b
26
  END FUNCTION
27
END MODULE M2
28
 
29
MODULE M1
30
  IMPLICIT NONE
31
  TYPE cell_type
32
     REAL :: h(3,3)
33
  END TYPE
34
CONTAINS
35
  SUBROUTINE S1(cell)
36
     TYPE(cell_type), POINTER :: cell
37
     REAL :: a(3)
38
     REAL :: b(3) = [1, 2, 3]
39
     a=MATMUL(cell%h,b)
40
     if (ANY (INT (a) .ne. [30, 36, 42])) call abort
41
  END SUBROUTINE S1
42
END MODULE M1
43
 
44
  use M1
45
  TYPE(cell_type), POINTER :: cell
46
  allocate (cell)
47
  cell%h = reshape ([(real(i), i = 1, 9)], [3, 3])
48
  call s1 (cell)
49
end
50
! { dg-final { cleanup-modules "M1" } }
51
! { dg-final { scan-tree-dump-times "&a" 1 "original" } }
52
! { dg-final { scan-tree-dump-times "pack" 0 "original" } }
53
! { 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.