llvm/flang/test/semantics/resolve35.f90
Tim Keith ed94af4c47 [flang] More name resolution for construct entities
Push a new scope for constructs and statements that require one
(DataStmt, DO CONCURRENT, ForallConstruct, ForallStmt -- there are more
to do). Currently we use the Block kind of scope because there is no
difference. Perhaps that kind should be renamed to Construct, though it
does apply to statements as well as constructs.

Add DeclareConstructEntity to create a construct or statement entity.
When the type is not specified it can come from the type of a symbol in
the enclosing scope with the same name. Change DeclareObjectEntity et al.
to return the symbol declared, for the benefit of DeclareConstructEntity.

Use DeclareConstructEntity for DO CONCURRENT index-name, LOCAL, and
LOCAL_INIT variables and the data-i-do-variable in DataImpliedDo

Names in SHARED locality spec need special handling: create a new kinds
of symbol with HostAssocDetails to represent the host-association of the
shared variables within the construct scope. That symbol gets the
LocalityShared flag without affecting the symbol in the outer scope.
HostAssoc symbols may be useful in other contexts, e.g. up-level
references to local variables.

Add parser::DoConstruct::IsDoConcurrent() because DO CONCURRENT loops
introduce a construct scope while other DO loops do not.

Move CanonicalizeDo to before name resolution so that name resolution
doesn't have to deal with labeled DO CONCURRENT loops.

Allow for type of index name to be specified in ConcurrentHeader.

Resolve the derived type name in an AllocateStmt, StructureConstructor

Original-commit: flang-compiler/f18@bc7b989136
Reviewed-on: https://github.com/flang-compiler/f18/pull/214
2018-10-18 09:06:11 -07:00

97 lines
2.3 KiB
Fortran

! Copyright (c) 2018, NVIDIA CORPORATION. All rights reserved.
!
! Licensed under the Apache License, Version 2.0 (the "License");
! you may not use this file except in compliance with the License.
! You may obtain a copy of the License at
!
! http://www.apache.org/licenses/LICENSE-2.0
!
! Unless required by applicable law or agreed to in writing, software
! distributed under the License is distributed on an "AS IS" BASIS,
! WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
! See the License for the specific language governing permissions and
! limitations under the License.
! 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
!ERROR: Variable 'x' is not scalar integer
forall(x=1:10)
a(x) = b(x)
end forall
!ERROR: Variable 'y' is not scalar integer
forall(y=1:10)
a(y) = b(y)
end forall
end
subroutine s5
real :: a(10), b(10)
!ERROR: 'i' is already declared in this scoping unit
forall(i=1:10, 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
data(x(t), t=1, n) / n * 0.0 /
contains
subroutine t
end
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) &
!ERROR: Variable 'a' not found
shared(a)
a(i) = 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