File: resolve57.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,532 bytes parent folder | download | duplicates (14)
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
! Tests for the last sentence of C1128:
!A variable-name that is not permitted to appear in a variable definition
!context shall not appear in a LOCAL or LOCAL_INIT locality-spec.

subroutine s1(arg)
  real, intent(in) :: arg

  ! This is not OK because "arg" is "intent(in)"
!ERROR: INTENT IN argument 'arg' not allowed in a locality-spec
  do concurrent (i=1:5) local(arg)
  end do
end subroutine s1

subroutine s2(arg)
  real, value, intent(in) :: arg

  ! This is not OK even though "arg" has the "value" attribute.  C1128
  ! explicitly excludes dummy arguments of INTENT(IN)
!ERROR: INTENT IN argument 'arg' not allowed in a locality-spec
  do concurrent (i=1:5) local(arg)
  end do
end subroutine s2

module m3
  real, protected :: prot
  real var

  contains
    subroutine sub()
      ! C857 This is OK because of the "protected" attribute only applies to
      ! accesses outside the module
      do concurrent (i=1:5) local(prot)
      end do
    end subroutine sub
endmodule m3

subroutine s4()
  use m3

  ! C857 This is not OK because of the "protected" attribute
!ERROR: 'prot' may not appear in a locality-spec because it is not definable
!BECAUSE: 'prot' is protected in this scope
  do concurrent (i=1:5) local(prot)
  end do

  ! C857 This is OK because of there's no "protected" attribute
  do concurrent (i=1:5) local(var)
  end do
end subroutine s4

subroutine s5()
  real :: a, b, c, d, e

  associate (a => b + c, d => e)
    b = 3.0
    ! C1101 This is OK because 'd' is associated with a variable
    do concurrent (i=1:5) local(d)
    end do

    ! C1101 This is not OK because 'a' is not associated with a variable
!ERROR: 'a' may not appear in a locality-spec because it is not definable
!BECAUSE: 'a' is construct associated with an expression
    do concurrent (i=1:5) local(a)
    end do
  end associate
end subroutine s5

subroutine s6()
  type point
    real :: x, y
  end type point

  type, extends(point) :: color_point
    integer :: color
  end type color_point

  type(point), target :: c, d
  class(point), pointer :: p_or_c

  p_or_c => c
  select type ( a => p_or_c )
  type is ( point )
    ! C1158 This is OK because 'a' is associated with a variable
    do concurrent (i=1:5) local(a)
    end do
  end select

  select type ( a => func() )
  type is ( point )
    ! C1158 This is OK because 'a' is associated with a variable
    do concurrent (i=1:5) local(a)
    end do
  end select

  select type ( a => (func()) )
  type is ( point )
    ! C1158 This is not OK because 'a' is not associated with a variable
!ERROR: 'a' may not appear in a locality-spec because it is not definable
!BECAUSE: 'a' is construct associated with an expression
    do concurrent (i=1:5) local(a)
    end do
  end select

  contains
    function func()
      class(point), pointer :: func
      func => c
    end function func
end subroutine s6

module m4
  real, protected :: prot
  real var
endmodule m4

pure subroutine s7()
  use m4

  ! C1594 This is not OK because we're in a PURE subroutine
!ERROR: 'var' may not appear in a locality-spec because it is not definable
!BECAUSE: 'var' may not be defined in pure subprogram 's7' because it is USE-associated
  do concurrent (i=1:5) local(var)
  end do
end subroutine s7

subroutine s8()
  integer, parameter :: iconst = 343

!ERROR: 'iconst' may not appear in a locality-spec because it is not definable
!BECAUSE: 'iconst' is not a variable
  do concurrent (i=1:5) local(iconst)
  end do
end subroutine s8