File: forall01.f90

package info (click to toggle)
swiftlang 6.0.3-2
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 2,519,992 kB
  • sloc: cpp: 9,107,863; ansic: 2,040,022; asm: 1,135,751; python: 296,500; objc: 82,456; f90: 60,502; lisp: 34,951; pascal: 19,946; sh: 18,133; perl: 7,482; ml: 4,937; javascript: 4,117; makefile: 3,840; awk: 3,535; xml: 914; fortran: 619; cs: 573; ruby: 573
file content (134 lines) | stat: -rw-r--r-- 3,359 bytes parent folder | download | duplicates (4)
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: %python %S/test_errors.py %s %flang_fc1
subroutine forall1
  real :: a(9)
  !ERROR: 'i' is already declared in this scoping unit
  !ERROR: Cannot redefine FORALL variable 'i'
  forall (i=1:8, i=1:9)  a(i) = i
  !ERROR: 'i' is already declared in this scoping unit
  !ERROR: Cannot redefine FORALL variable 'i'
  forall (i=1:8, i=1:9)
    a(i) = i
  end forall
  forall (j=1:8)
    !ERROR: 'j' is already declared in this scoping unit
    !ERROR: Cannot redefine FORALL variable 'j'
    forall (j=1:9)
    end forall
  end forall
end

subroutine forall2
  integer, pointer :: a(:)
  integer, target :: b(10,10)
  forall (i=1:10)
    !ERROR: Impure procedure 'f_impure' may not be referenced in a FORALL
    a(f_impure(i):) => b(i,:)
  end forall
  !ERROR: FORALL mask expression may not reference impure procedure 'f_impure'
  forall (j=1:10, f_impure(1)>2)
  end forall
contains
  impure integer function f_impure(i)
    f_impure = i
  end
end

subroutine forall3
  real :: x
  forall(i=1:10)
    !ERROR: Cannot redefine FORALL variable 'i'
    i = 1
  end forall
  forall(i=1:10)
    forall(j=1:10)
      !ERROR: Cannot redefine FORALL variable 'i'
      !WARNING: FORALL index variable 'j' not used on left-hand side of assignment
      i = 1
    end forall
  end forall
  !ERROR: Cannot redefine FORALL variable 'i'
  forall(i=1:10) i = 1
end

subroutine forall4
  integer, parameter :: zero = 0
  integer :: a(10)

  !ERROR: FORALL limit expression may not reference index variable 'i'
  forall(i=1:i)
    a(i) = i
  end forall
  !ERROR: FORALL step expression may not reference index variable 'i'
  forall(i=1:10:i)
    a(i) = i
  end forall
  !ERROR: FORALL step expression may not be zero
  forall(i=1:10:zero)
    a(i) = i
  end forall

  !ERROR: FORALL limit expression may not reference index variable 'i'
  forall(i=1:i) a(i) = i
  !ERROR: FORALL step expression may not reference index variable 'i'
  forall(i=1:10:i) a(i) = i
  !ERROR: FORALL step expression may not be zero
  forall(i=1:10:zero) a(i) = i
end

! Note: this gets warnings but not errors
subroutine forall5
  real, target :: x(10), y(10)
  forall(i=1:10)
    x(i) = y(i)
  end forall
  forall(i=1:10)
    !WARNING: FORALL index variable 'i' not used on left-hand side of assignment
    x = y
    forall(j=1:10)
      !WARNING: FORALL index variable 'j' not used on left-hand side of assignment
      x(i) = y(i)
      !WARNING: FORALL index variable 'i' not used on left-hand side of assignment
      x(j) = y(j)
    endforall
  endforall
  do concurrent(i=1:10)
    x = y
    !WARNING: FORALL index variable 'i' not used on left-hand side of assignment
    forall(i=1:10) x = y
  end do
end

subroutine forall6
  type t
    real, pointer :: p
  end type
  type(t) :: a(10)
  real, target :: b(10)
  forall(i=1:10)
    a(i)%p => b(i)
    !WARNING: FORALL index variable 'i' not used on left-hand side of assignment
    a(1)%p => b(i)
  end forall
end

subroutine forall7(x)
  integer :: iarr(1)
  real :: a(10)
  class(*) :: x
  associate (j => iarr(1))
    forall (j=1:size(a))
      a(j) = a(j) + 1
    end forall
  end associate
  associate (j => iarr(1) + 1)
    forall (j=1:size(a))
      a(j) = a(j) + 1
    end forall
  end associate
  select type (j => x)
  type is (integer)
    forall (j=1:size(a))
      a(j) = a(j) + 1
    end forall
  end select
end subroutine