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.0rc2/] [gcc/] [testsuite/] [gfortran.dg/] [elemental_dependency_1.f90] - Blame information for rev 384

Details | Compare with Previous | View Log

Line No. Rev Author Line
1 302 jeremybenn
! { dg-do run }
2
! { dg-options "-fdump-tree-original" }
3
!
4
! PR fortran/35681
5
! Test the use of temporaries in case of elemental subroutines.
6
 
7
PROGRAM main
8
  IMPLICIT NONE
9
  INTEGER, PARAMETER :: sz = 5
10
  INTEGER :: i
11
  INTEGER :: a(sz) = (/ (i, i=1,sz) /)
12
  INTEGER :: b(sz)
13
 
14
  b = a
15
  CALL double(a(sz-b+1), a) ! { dg-warning "might interfere with actual" }
16
  ! Don't check the result, as the above is invalid
17
  ! and might produce unexpected results (overlapping vector subscripts).
18
 
19
 
20
  b = a
21
  CALL double (a, a)               ! same range, no temporary
22
  IF (ANY(a /= 2*b)) CALL abort
23
 
24
 
25
  b = a
26
  CALL double (a+1, a)             ! same range, no temporary
27
  IF (ANY(a /= 2*b+2)) CALL abort
28
 
29
 
30
  b = a
31
  CALL double ((a(1:sz)), a(1:sz)) ! same range, no temporary
32
  IF (ANY(a /= 2*b)) CALL abort
33
 
34
 
35
  b = a
36
  CALL double(a(1:sz-1), a(2:sz)) ! { dg-warning "might interfere with actual" }
37
  ! Don't check the result, as the above is invalid,
38
  ! and might produce unexpected results (arguments overlap).
39
 
40
 
41
  b = a
42
  CALL double((a(1:sz-1)), a(2:sz))     ! paren expression, temporary created
43
! { dg-final { scan-tree-dump-times "A\.16\\\[4\\\]" 1 "original" } }
44
 
45
  IF (ANY(a /= (/ b(1), (2*b(i), i=1,sz-1) /))) CALL abort
46
 
47
 
48
  b = a
49
  CALL double(a(1:sz-1)+1, a(2:sz))     ! op expression, temporary created
50
! { dg-final { scan-tree-dump-times "A\.25\\\[4\\\]" 1 "original" } }
51
 
52
  IF (ANY(a /= (/ b(1), (2*b(i)+2, i=1,sz-1) /))) CALL abort
53
 
54
 
55
  b = a
56
  CALL double(self(a), a) ! same range, no temporary
57
  IF (ANY(a /= 2*b)) CALL abort
58
 
59
 
60
  b = a
61
  CALL double(self(a(1:sz-1)), a(2:sz))  ! function expr, temporary created
62
! { dg-final { scan-tree-dump-times "A\.37\\\[4\\\]" 1 "original" } }
63
 
64
  IF (ANY(a /= (/ b(1), (2*b(i), i=1,sz-1) /))) CALL abort
65
 
66
 
67
CONTAINS
68
  ELEMENTAL SUBROUTINE double(a, b)
69
    IMPLICIT NONE
70
    INTEGER, INTENT(IN) :: a
71
    INTEGER, INTENT(OUT) :: b
72
    b = 2 * a
73
  END SUBROUTINE double
74
  ELEMENTAL FUNCTION self(a)
75
    IMPLICIT NONE
76
    INTEGER, INTENT(IN) :: a
77
    INTEGER :: self
78
    self = a
79
  END FUNCTION self
80
END PROGRAM main
81
 
82
! { dg-final { scan-tree-dump-times "_gfortran_internal_unpack" 3 "original" } }
83
! { 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.