File: resolve35.f90

package info (click to toggle)
llvm-toolchain-11 1%3A11.0.1-2
  • links: PTS, VCS
  • area: main
  • in suites: bullseye
  • size: 995,808 kB
  • sloc: cpp: 4,767,656; ansic: 760,916; asm: 477,436; python: 170,940; objc: 69,804; lisp: 29,914; sh: 23,855; f90: 18,173; pascal: 7,551; perl: 7,471; ml: 5,603; awk: 3,489; makefile: 2,573; xml: 915; cs: 573; fortran: 503; javascript: 452
file content (134 lines) | stat: -rw-r--r-- 3,374 bytes parent folder | download | duplicates (2)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
! RUN: %S/test_errors.sh %s %t %f18
! Construct names

subroutine s1
  real :: foo
  !ERROR: 'foo' is already declared in this scoping unit
  foo: block
  end block foo
end

subroutine s2(x)
  logical :: x
  foo: if (x) then
  end if foo
  !ERROR: 'foo' is already declared in this scoping unit
  foo: do i = 1, 10
  end do foo
end

subroutine s3
  real :: a(10,10), b(10,10)
  type y; end type
  integer(8) :: x
  !ERROR: Index name 'y' conflicts with existing identifier
  forall(x=1:10, y=1:10)
    a(x, y) = b(x, y)
  end forall
  !ERROR: Index name 'y' conflicts with existing identifier
  forall(x=1:10, y=1:10) a(x, y) = b(x, y)
end

subroutine s4
  real :: a(10), b(10)
  complex :: x
  integer :: i(2)
  !ERROR: Must have INTEGER type, but is COMPLEX(4)
  forall(x=1:10)
    !ERROR: Must have INTEGER type, but is COMPLEX(4)
    !ERROR: Must have INTEGER type, but is COMPLEX(4)
    a(x) = b(x)
  end forall
  !ERROR: Must have INTEGER type, but is REAL(4)
  forall(y=1:10)
    !ERROR: Must have INTEGER type, but is REAL(4)
    !ERROR: Must have INTEGER type, but is REAL(4)
    a(y) = b(y)
  end forall
  !ERROR: Index variable 'i' is not scalar
  forall(i=1:10)
    a(i) = b(i)
  end forall
end

subroutine s6
  integer, parameter :: n = 4
  real, dimension(n) :: x
  data(x(i), i=1, n) / n * 0.0 /
  !ERROR: Index name 't' conflicts with existing identifier
  forall(t=1:n) x(t) = 0.0
contains
  subroutine t
  end
end

subroutine s6b
  integer, parameter :: k = 4
  integer :: l = 4
  forall(integer(k) :: i = 1:10)
  end forall
  ! C713 A scalar-int-constant-name shall be a named constant of type integer.
  !ERROR: Must be a constant value
  forall(integer(l) :: i = 1:10)
  end forall
end

subroutine s7
  !ERROR: 'i' is already declared in this scoping unit
  do concurrent(integer::i=1:5) local(j, i) &
      !ERROR: 'j' is already declared in this scoping unit
      local_init(k, j) &
      shared(a)
    a = j + 1
  end do
end

subroutine s8
  implicit none
  !ERROR: No explicit type declared for 'i'
  do concurrent(i=1:5) &
    !ERROR: No explicit type declared for 'j'
    local(j) &
    !ERROR: No explicit type declared for 'k'
    local_init(k)
  end do
end

subroutine s9
  integer :: j
  !ERROR: 'i' is already declared in this scoping unit
  do concurrent(integer::i=1:5) shared(i) &
      shared(j) &
      !ERROR: 'j' is already declared in this scoping unit
      shared(j)
  end do
end

subroutine s10
  external bad1
  real, parameter :: bad2 = 1.0
  x = cos(0.)
  do concurrent(i=1:2) &
    !ERROR: 'bad1' may not appear in a locality-spec because it is not definable
    local(bad1) &
    !ERROR: 'bad2' may not appear in a locality-spec because it is not definable
    local(bad2) &
    !ERROR: 'bad3' may not appear in a locality-spec because it is not definable
    local(bad3) &
    !ERROR: 'cos' may not appear in a locality-spec because it is not definable
    local(cos)
  end do
  do concurrent(i=1:2) &
    !ERROR: The name 'bad1' must be a variable to appear in a locality-spec
    shared(bad1) &
    !ERROR: The name 'bad2' must be a variable to appear in a locality-spec
    shared(bad2) &
    !ERROR: The name 'bad3' must be a variable to appear in a locality-spec
    shared(bad3) &
    !ERROR: The name 'cos' must be a variable to appear in a locality-spec
    shared(cos)
  end do
contains
  subroutine bad3
  end
end