Emil Kieri 93dca9fbee [flang][test] Fix semantics tests with respect to warnings
Make tests expect the (correctly) emitted warnings using the WARNING
directive. This directive is non-functional now, but will be recognised
by test_errors.py when D125804 is landed. This patch is a preparation
for D125804.

For most tests, we add missing WARNING directives for emitted warnings,
but there are exceptions:

 - for int-literals.f90 and resolve31.f90 we pass -pedantic to the
   frontend driver, so that the expected warnings are actually emitted.

 - for block-data01.f90 and resolve42.f90 we change the tests so that
   warnings, which appear unintentional, are not emitted. While testing
   the warning in question (padding added for alignment in common block)
   would be desired, that is beyond the scope of this patch. This
   warning is target-dependent.

Reviewed By: PeteSteinfeld

Differential Revision: https://reviews.llvm.org/D131987
2022-08-18 19:16:20 +02:00

115 lines
2.5 KiB
Fortran

! RUN: %python %S/test_errors.py %s %flang_fc1
subroutine s1
!ERROR: Array 'x' without ALLOCATABLE or POINTER attribute must have explicit shape
common x(:), y(4), z
end
subroutine s2
common /c1/ x, y, z
!ERROR: 'y' is already in a COMMON block
common y
end
subroutine s3
!ERROR: 'x' may not be a procedure as it is in a COMMON block
procedure(real) :: x
common x
common y
!ERROR: 'y' may not be a procedure as it is in a COMMON block
procedure(real) :: y
end
subroutine s5
integer x(2)
!ERROR: The dimensions of 'x' have already been declared
common x(4), y(4)
!ERROR: The dimensions of 'y' have already been declared
real y(2)
end
function f6(x) result(r)
!ERROR: ALLOCATABLE object 'y' may not appear in a COMMON block
!ERROR: Dummy argument 'x' may not appear in a COMMON block
common y,x,z
allocatable y
!ERROR: Function result 'r' may not appear in a COMMON block
common r
end
module m7
!ERROR: Variable 'w' with BIND attribute may not appear in a COMMON block
!ERROR: Variable 'z' with BIND attribute may not appear in a COMMON block
common w,z
integer, bind(c) :: z
integer, bind(c,name="w") :: w
end
module m8
type t
end type
class(*), pointer :: x
!ERROR: Unlimited polymorphic pointer 'x' may not appear in a COMMON block
!ERROR: Unlimited polymorphic pointer 'y' may not appear in a COMMON block
common x, y
class(*), pointer :: y
end
module m9
integer x
end
subroutine s9
use m9
!ERROR: 'x' is use-associated from module 'm9' and cannot be re-declared
common x
end
module m10
type t
end type
type(t) :: x
!ERROR: Derived type 'x' in COMMON block must have the BIND or SEQUENCE attribute
common x
end
module m11
type t1
sequence
integer, allocatable :: a
end type
type t2
sequence
type(t1) :: b
integer:: c
end type
type(t2) :: x2
!ERROR: Derived type variable 'x2' may not appear in a COMMON block due to ALLOCATABLE component
common /c2/ x2
end
module m12
type t1
sequence
integer :: a = 123
end type
type t2
sequence
type(t1) :: b
integer:: c
end type
type(t2) :: x2
!ERROR: Derived type variable 'x2' may not appear in a COMMON block due to component with default initialization
common /c3/ x2
end
subroutine s13
block
!ERROR: COMMON statement is not allowed in a BLOCK construct
common x
end block
end
subroutine s14
!ERROR: 'c' appears as a COMMON block in a BIND statement but not in a COMMON statement
bind(c) :: /c/
end