llvm-project/flang/test/Semantics/resolve63.f90

Ignoring revisions in .git-blame-ignore-revs. Click here to bypass and see the normal blame view.

238 lines
6.2 KiB
Fortran
Raw Normal View History

[flang] A rework of the cmake build components for in and out of tree builds. In general all the basic functionality seems to work and removes some redundancy and more complicated features in favor of borrowing infrastructure from LLVM build configurations. Here's a quick summary of details and remaining issues: * Testing has spanned Ubuntu 18.04 & 19.10, CentOS 7, RHEL 8, and MacOS/darwin. Architectures include x86_64 and Arm. Without access to Window nothing has been tested there yet. * As we change file and directory naming schemes (i.e., capitalization) some odd things can occur on MacOS systems with case preserving but not case senstive file system configurations. Can be painful and certainly something to watch out for as any any such changes continue. * Testing infrastructure still needs to be tuned up and worked on. Note that there do appear to be cases of some tests hanging (on MacOS in particular). They appear unrelated to the build process. * Shared library configurations need testing (and probably fixing). * Tested both standalone and 'in-mono repo' builds. Changes for supporting the mono repo builds will require LLVM-level changes that are straightforward when the time comes. * The configuration contains a work-around for LLVM's C++ standard mode passing down into Flang/F18 builds (i.e., LLVM CMake configuration would force a -std=c++11 flag to show up in command line arguments. The current configuration removes that automatically and is more strict in following new CMake guidelines for enforcing C++17 mode across all the CMake files. * Cleaned up a lot of repetition in the command line arguments. It is likely that more work is still needed to both allow for customization and working around CMake defailts (or those inherited from LLVM's configuration files). On some platforms agressive optimization flags (e.g. -O3) can actually break builds due to the inlining of templates in .cpp source files that then no longer are available for use cases outside those source files (shows up as link errors). Sticking at -O2 appears to fix this. Currently this CMake configuration forces this in release mode but at the cost of stomping on any CMake, or user customized, settings for the release flags. * Made the lit tests non-source directory dependent where appropriate. This is done by configuring certain test shell files to refer to the correct paths whether an in or out of tree build is being performed. These configured files are output in the build directory. A %B substitution is introduced in lit to refer to the build directory, mirroring the %S substitution for the source directory, so that the tests can refer to the configured shell scripts. Co-authored-by: David Truby <david.truby@arm.com> Original-commit: flang-compiler/f18@d1c7184159b2d3c542a8f36c58a0c817e7506845 Reviewed-on: https://github.com/flang-compiler/f18/pull/1045
2020-02-26 07:22:14 +08:00
! RUN: %B/test/Semantics/test_errors.sh %s %flang %t
[flang] Resolve extended intrinsic operators Enhance `ArgumentAnalyzer` to do most of the work for this. For each kind of operator that might have a user-defined form we follow this process: - analyze the arguments - if the types and shapes match the intrinsic operator do the usual processing - otherwise attempt to interpret it as a user-defined operator with `TryDefinedOp` When we fail to resolve an operator, produce different errors depending on whether there is a user-defined operator available or not. If there is, report that neither user-defined nor intrinsic operator worked. If there is not, describe the rules for the intrinsic operator. In either case, include the type(s) of the operand(s). Most of the uses of `ArgumentAnalyzer` are in helper functions that apply to classes of operators. For consistency, rename `BinaryOperationHelper` to `NumericBinaryOperator` and `LogicalHelper` to `LogicalBinaryHelper` and introduce `NumericUnaryHelper` for unary `+` and `-`. `.NOT.` and `//` are not implemented in helpers. Replace `success_` with `fatalErrors_` in `ArgumentAnalyzer` for consistency with `ExpressionAnalyzer`. Add `NumericOperator` and `LogicalOperator` enums to `Fortran.h` to go with `RelationalOperator`. Add `AddFortran` functions to each to convert to a Fortran source string. `RelationalOperator` also has `AllFortranNames` because there are multiple names for each operator. This replaces `LogicalOperator` in `expression.h` and the string representation of the operators in `formatting.cc`. Original-commit: flang-compiler/f18@3bb9d664e86c931a67b3e78859d2108e53d23f80 Reviewed-on: https://github.com/flang-compiler/f18/pull/807
2019-11-03 00:56:46 +08:00
! Invalid operand types when user-defined operator is available
module m1
type :: t
end type
interface operator(==)
logical function eq_tt(x, y)
import :: t
type(t), intent(in) :: x, y
end
end interface
interface operator(+)
logical function add_tr(x, y)
import :: t
type(t), intent(in) :: x
real, intent(in) :: y
end
logical function plus_t(x)
import :: t
type(t), intent(in) :: x
end
logical function add_12(x, y)
real, intent(in) :: x(:), y(:,:)
end
end interface
interface operator(.and.)
logical function and_tr(x, y)
import :: t
type(t), intent(in) :: x
real, intent(in) :: y
end
end interface
interface operator(//)
logical function concat_tt(x, y)
import :: t
type(t), intent(in) :: x, y
end
end interface
interface operator(.not.)
logical function not_r(x)
real, intent(in) :: x
end
end interface
type(t) :: x, y
real :: r
logical :: l
contains
subroutine test_relational()
l = x == y !OK
l = x .eq. y !OK
!ERROR: No intrinsic or user-defined OPERATOR(==) matches operand types TYPE(t) and REAL(4)
[flang] Resolve extended intrinsic operators Enhance `ArgumentAnalyzer` to do most of the work for this. For each kind of operator that might have a user-defined form we follow this process: - analyze the arguments - if the types and shapes match the intrinsic operator do the usual processing - otherwise attempt to interpret it as a user-defined operator with `TryDefinedOp` When we fail to resolve an operator, produce different errors depending on whether there is a user-defined operator available or not. If there is, report that neither user-defined nor intrinsic operator worked. If there is not, describe the rules for the intrinsic operator. In either case, include the type(s) of the operand(s). Most of the uses of `ArgumentAnalyzer` are in helper functions that apply to classes of operators. For consistency, rename `BinaryOperationHelper` to `NumericBinaryOperator` and `LogicalHelper` to `LogicalBinaryHelper` and introduce `NumericUnaryHelper` for unary `+` and `-`. `.NOT.` and `//` are not implemented in helpers. Replace `success_` with `fatalErrors_` in `ArgumentAnalyzer` for consistency with `ExpressionAnalyzer`. Add `NumericOperator` and `LogicalOperator` enums to `Fortran.h` to go with `RelationalOperator`. Add `AddFortran` functions to each to convert to a Fortran source string. `RelationalOperator` also has `AllFortranNames` because there are multiple names for each operator. This replaces `LogicalOperator` in `expression.h` and the string representation of the operators in `formatting.cc`. Original-commit: flang-compiler/f18@3bb9d664e86c931a67b3e78859d2108e53d23f80 Reviewed-on: https://github.com/flang-compiler/f18/pull/807
2019-11-03 00:56:46 +08:00
l = x == r
end
subroutine test_numeric()
l = x + r !OK
!ERROR: No intrinsic or user-defined OPERATOR(+) matches operand types REAL(4) and TYPE(t)
[flang] Resolve extended intrinsic operators Enhance `ArgumentAnalyzer` to do most of the work for this. For each kind of operator that might have a user-defined form we follow this process: - analyze the arguments - if the types and shapes match the intrinsic operator do the usual processing - otherwise attempt to interpret it as a user-defined operator with `TryDefinedOp` When we fail to resolve an operator, produce different errors depending on whether there is a user-defined operator available or not. If there is, report that neither user-defined nor intrinsic operator worked. If there is not, describe the rules for the intrinsic operator. In either case, include the type(s) of the operand(s). Most of the uses of `ArgumentAnalyzer` are in helper functions that apply to classes of operators. For consistency, rename `BinaryOperationHelper` to `NumericBinaryOperator` and `LogicalHelper` to `LogicalBinaryHelper` and introduce `NumericUnaryHelper` for unary `+` and `-`. `.NOT.` and `//` are not implemented in helpers. Replace `success_` with `fatalErrors_` in `ArgumentAnalyzer` for consistency with `ExpressionAnalyzer`. Add `NumericOperator` and `LogicalOperator` enums to `Fortran.h` to go with `RelationalOperator`. Add `AddFortran` functions to each to convert to a Fortran source string. `RelationalOperator` also has `AllFortranNames` because there are multiple names for each operator. This replaces `LogicalOperator` in `expression.h` and the string representation of the operators in `formatting.cc`. Original-commit: flang-compiler/f18@3bb9d664e86c931a67b3e78859d2108e53d23f80 Reviewed-on: https://github.com/flang-compiler/f18/pull/807
2019-11-03 00:56:46 +08:00
l = r + x
end
subroutine test_logical()
l = x .and. r !OK
!ERROR: No intrinsic or user-defined OPERATOR(.AND.) matches operand types REAL(4) and TYPE(t)
[flang] Resolve extended intrinsic operators Enhance `ArgumentAnalyzer` to do most of the work for this. For each kind of operator that might have a user-defined form we follow this process: - analyze the arguments - if the types and shapes match the intrinsic operator do the usual processing - otherwise attempt to interpret it as a user-defined operator with `TryDefinedOp` When we fail to resolve an operator, produce different errors depending on whether there is a user-defined operator available or not. If there is, report that neither user-defined nor intrinsic operator worked. If there is not, describe the rules for the intrinsic operator. In either case, include the type(s) of the operand(s). Most of the uses of `ArgumentAnalyzer` are in helper functions that apply to classes of operators. For consistency, rename `BinaryOperationHelper` to `NumericBinaryOperator` and `LogicalHelper` to `LogicalBinaryHelper` and introduce `NumericUnaryHelper` for unary `+` and `-`. `.NOT.` and `//` are not implemented in helpers. Replace `success_` with `fatalErrors_` in `ArgumentAnalyzer` for consistency with `ExpressionAnalyzer`. Add `NumericOperator` and `LogicalOperator` enums to `Fortran.h` to go with `RelationalOperator`. Add `AddFortran` functions to each to convert to a Fortran source string. `RelationalOperator` also has `AllFortranNames` because there are multiple names for each operator. This replaces `LogicalOperator` in `expression.h` and the string representation of the operators in `formatting.cc`. Original-commit: flang-compiler/f18@3bb9d664e86c931a67b3e78859d2108e53d23f80 Reviewed-on: https://github.com/flang-compiler/f18/pull/807
2019-11-03 00:56:46 +08:00
l = r .and. x
end
subroutine test_unary()
l = +x !OK
!ERROR: No intrinsic or user-defined OPERATOR(+) matches operand type LOGICAL(4)
[flang] Resolve extended intrinsic operators Enhance `ArgumentAnalyzer` to do most of the work for this. For each kind of operator that might have a user-defined form we follow this process: - analyze the arguments - if the types and shapes match the intrinsic operator do the usual processing - otherwise attempt to interpret it as a user-defined operator with `TryDefinedOp` When we fail to resolve an operator, produce different errors depending on whether there is a user-defined operator available or not. If there is, report that neither user-defined nor intrinsic operator worked. If there is not, describe the rules for the intrinsic operator. In either case, include the type(s) of the operand(s). Most of the uses of `ArgumentAnalyzer` are in helper functions that apply to classes of operators. For consistency, rename `BinaryOperationHelper` to `NumericBinaryOperator` and `LogicalHelper` to `LogicalBinaryHelper` and introduce `NumericUnaryHelper` for unary `+` and `-`. `.NOT.` and `//` are not implemented in helpers. Replace `success_` with `fatalErrors_` in `ArgumentAnalyzer` for consistency with `ExpressionAnalyzer`. Add `NumericOperator` and `LogicalOperator` enums to `Fortran.h` to go with `RelationalOperator`. Add `AddFortran` functions to each to convert to a Fortran source string. `RelationalOperator` also has `AllFortranNames` because there are multiple names for each operator. This replaces `LogicalOperator` in `expression.h` and the string representation of the operators in `formatting.cc`. Original-commit: flang-compiler/f18@3bb9d664e86c931a67b3e78859d2108e53d23f80 Reviewed-on: https://github.com/flang-compiler/f18/pull/807
2019-11-03 00:56:46 +08:00
l = +l
l = .not. r !OK
!ERROR: No intrinsic or user-defined OPERATOR(.NOT.) matches operand type TYPE(t)
[flang] Resolve extended intrinsic operators Enhance `ArgumentAnalyzer` to do most of the work for this. For each kind of operator that might have a user-defined form we follow this process: - analyze the arguments - if the types and shapes match the intrinsic operator do the usual processing - otherwise attempt to interpret it as a user-defined operator with `TryDefinedOp` When we fail to resolve an operator, produce different errors depending on whether there is a user-defined operator available or not. If there is, report that neither user-defined nor intrinsic operator worked. If there is not, describe the rules for the intrinsic operator. In either case, include the type(s) of the operand(s). Most of the uses of `ArgumentAnalyzer` are in helper functions that apply to classes of operators. For consistency, rename `BinaryOperationHelper` to `NumericBinaryOperator` and `LogicalHelper` to `LogicalBinaryHelper` and introduce `NumericUnaryHelper` for unary `+` and `-`. `.NOT.` and `//` are not implemented in helpers. Replace `success_` with `fatalErrors_` in `ArgumentAnalyzer` for consistency with `ExpressionAnalyzer`. Add `NumericOperator` and `LogicalOperator` enums to `Fortran.h` to go with `RelationalOperator`. Add `AddFortran` functions to each to convert to a Fortran source string. `RelationalOperator` also has `AllFortranNames` because there are multiple names for each operator. This replaces `LogicalOperator` in `expression.h` and the string representation of the operators in `formatting.cc`. Original-commit: flang-compiler/f18@3bb9d664e86c931a67b3e78859d2108e53d23f80 Reviewed-on: https://github.com/flang-compiler/f18/pull/807
2019-11-03 00:56:46 +08:00
l = .not. x
end
subroutine test_concat()
l = x // y !OK
!ERROR: No intrinsic or user-defined OPERATOR(//) matches operand types TYPE(t) and REAL(4)
[flang] Resolve extended intrinsic operators Enhance `ArgumentAnalyzer` to do most of the work for this. For each kind of operator that might have a user-defined form we follow this process: - analyze the arguments - if the types and shapes match the intrinsic operator do the usual processing - otherwise attempt to interpret it as a user-defined operator with `TryDefinedOp` When we fail to resolve an operator, produce different errors depending on whether there is a user-defined operator available or not. If there is, report that neither user-defined nor intrinsic operator worked. If there is not, describe the rules for the intrinsic operator. In either case, include the type(s) of the operand(s). Most of the uses of `ArgumentAnalyzer` are in helper functions that apply to classes of operators. For consistency, rename `BinaryOperationHelper` to `NumericBinaryOperator` and `LogicalHelper` to `LogicalBinaryHelper` and introduce `NumericUnaryHelper` for unary `+` and `-`. `.NOT.` and `//` are not implemented in helpers. Replace `success_` with `fatalErrors_` in `ArgumentAnalyzer` for consistency with `ExpressionAnalyzer`. Add `NumericOperator` and `LogicalOperator` enums to `Fortran.h` to go with `RelationalOperator`. Add `AddFortran` functions to each to convert to a Fortran source string. `RelationalOperator` also has `AllFortranNames` because there are multiple names for each operator. This replaces `LogicalOperator` in `expression.h` and the string representation of the operators in `formatting.cc`. Original-commit: flang-compiler/f18@3bb9d664e86c931a67b3e78859d2108e53d23f80 Reviewed-on: https://github.com/flang-compiler/f18/pull/807
2019-11-03 00:56:46 +08:00
l = x // r
end
subroutine test_conformability(x, y)
real :: x(10), y(10,10)
l = x + y !OK
!ERROR: No intrinsic or user-defined OPERATOR(+) matches rank 2 array of REAL(4) and rank 1 array of REAL(4)
[flang] Resolve extended intrinsic operators Enhance `ArgumentAnalyzer` to do most of the work for this. For each kind of operator that might have a user-defined form we follow this process: - analyze the arguments - if the types and shapes match the intrinsic operator do the usual processing - otherwise attempt to interpret it as a user-defined operator with `TryDefinedOp` When we fail to resolve an operator, produce different errors depending on whether there is a user-defined operator available or not. If there is, report that neither user-defined nor intrinsic operator worked. If there is not, describe the rules for the intrinsic operator. In either case, include the type(s) of the operand(s). Most of the uses of `ArgumentAnalyzer` are in helper functions that apply to classes of operators. For consistency, rename `BinaryOperationHelper` to `NumericBinaryOperator` and `LogicalHelper` to `LogicalBinaryHelper` and introduce `NumericUnaryHelper` for unary `+` and `-`. `.NOT.` and `//` are not implemented in helpers. Replace `success_` with `fatalErrors_` in `ArgumentAnalyzer` for consistency with `ExpressionAnalyzer`. Add `NumericOperator` and `LogicalOperator` enums to `Fortran.h` to go with `RelationalOperator`. Add `AddFortran` functions to each to convert to a Fortran source string. `RelationalOperator` also has `AllFortranNames` because there are multiple names for each operator. This replaces `LogicalOperator` in `expression.h` and the string representation of the operators in `formatting.cc`. Original-commit: flang-compiler/f18@3bb9d664e86c931a67b3e78859d2108e53d23f80 Reviewed-on: https://github.com/flang-compiler/f18/pull/807
2019-11-03 00:56:46 +08:00
l = y + x
end
end
! Invalid operand types when user-defined operator is not available
module m2
type :: t
end type
type(t) :: x, y
real :: r
logical :: l
contains
subroutine test_relational()
!ERROR: Operands of .EQ. must have comparable types; have TYPE(t) and REAL(4)
[flang] Resolve extended intrinsic operators Enhance `ArgumentAnalyzer` to do most of the work for this. For each kind of operator that might have a user-defined form we follow this process: - analyze the arguments - if the types and shapes match the intrinsic operator do the usual processing - otherwise attempt to interpret it as a user-defined operator with `TryDefinedOp` When we fail to resolve an operator, produce different errors depending on whether there is a user-defined operator available or not. If there is, report that neither user-defined nor intrinsic operator worked. If there is not, describe the rules for the intrinsic operator. In either case, include the type(s) of the operand(s). Most of the uses of `ArgumentAnalyzer` are in helper functions that apply to classes of operators. For consistency, rename `BinaryOperationHelper` to `NumericBinaryOperator` and `LogicalHelper` to `LogicalBinaryHelper` and introduce `NumericUnaryHelper` for unary `+` and `-`. `.NOT.` and `//` are not implemented in helpers. Replace `success_` with `fatalErrors_` in `ArgumentAnalyzer` for consistency with `ExpressionAnalyzer`. Add `NumericOperator` and `LogicalOperator` enums to `Fortran.h` to go with `RelationalOperator`. Add `AddFortran` functions to each to convert to a Fortran source string. `RelationalOperator` also has `AllFortranNames` because there are multiple names for each operator. This replaces `LogicalOperator` in `expression.h` and the string representation of the operators in `formatting.cc`. Original-commit: flang-compiler/f18@3bb9d664e86c931a67b3e78859d2108e53d23f80 Reviewed-on: https://github.com/flang-compiler/f18/pull/807
2019-11-03 00:56:46 +08:00
l = x == r
end
subroutine test_numeric()
!ERROR: Operands of + must be numeric; have REAL(4) and TYPE(t)
l = r + x
end
subroutine test_logical()
!ERROR: Operands of .AND. must be LOGICAL; have REAL(4) and TYPE(t)
l = r .and. x
end
subroutine test_unary()
!ERROR: Operand of unary + must be numeric; have LOGICAL(4)
l = +l
!ERROR: Operand of .NOT. must be LOGICAL; have TYPE(t)
l = .not. x
end
subroutine test_concat(a, b)
character(4,kind=1) :: a
character(4,kind=2) :: b
character(4) :: c
!ERROR: Operands of // must be CHARACTER with the same kind; have CHARACTER(KIND=1) and CHARACTER(KIND=2)
c = a // b
!ERROR: Operands of // must be CHARACTER with the same kind; have TYPE(t) and REAL(4)
l = x // r
end
subroutine test_conformability(x, y)
real :: x(10), y(10,10)
!ERROR: Operands of + are not conformable; have rank 2 and rank 1
l = y + x
end
end
! Invalid untyped operands: user-defined operator doesn't affect errors
module m3
interface operator(+)
logical function add(x, y)
logical, intent(in) :: x
integer, value :: y
[flang] Resolve extended intrinsic operators Enhance `ArgumentAnalyzer` to do most of the work for this. For each kind of operator that might have a user-defined form we follow this process: - analyze the arguments - if the types and shapes match the intrinsic operator do the usual processing - otherwise attempt to interpret it as a user-defined operator with `TryDefinedOp` When we fail to resolve an operator, produce different errors depending on whether there is a user-defined operator available or not. If there is, report that neither user-defined nor intrinsic operator worked. If there is not, describe the rules for the intrinsic operator. In either case, include the type(s) of the operand(s). Most of the uses of `ArgumentAnalyzer` are in helper functions that apply to classes of operators. For consistency, rename `BinaryOperationHelper` to `NumericBinaryOperator` and `LogicalHelper` to `LogicalBinaryHelper` and introduce `NumericUnaryHelper` for unary `+` and `-`. `.NOT.` and `//` are not implemented in helpers. Replace `success_` with `fatalErrors_` in `ArgumentAnalyzer` for consistency with `ExpressionAnalyzer`. Add `NumericOperator` and `LogicalOperator` enums to `Fortran.h` to go with `RelationalOperator`. Add `AddFortran` functions to each to convert to a Fortran source string. `RelationalOperator` also has `AllFortranNames` because there are multiple names for each operator. This replaces `LogicalOperator` in `expression.h` and the string representation of the operators in `formatting.cc`. Original-commit: flang-compiler/f18@3bb9d664e86c931a67b3e78859d2108e53d23f80 Reviewed-on: https://github.com/flang-compiler/f18/pull/807
2019-11-03 00:56:46 +08:00
end
end interface
contains
subroutine s1(x, y)
logical :: x
integer :: y
logical :: l
complex :: z
y = y + z'1' !OK
!ERROR: Operands of + must be numeric; have untyped and COMPLEX(4)
z = z'1' + z
y = +z'1' !OK
!ERROR: Operand of unary - must be numeric; have untyped
y = -z'1'
[flang] Resolve extended intrinsic operators Enhance `ArgumentAnalyzer` to do most of the work for this. For each kind of operator that might have a user-defined form we follow this process: - analyze the arguments - if the types and shapes match the intrinsic operator do the usual processing - otherwise attempt to interpret it as a user-defined operator with `TryDefinedOp` When we fail to resolve an operator, produce different errors depending on whether there is a user-defined operator available or not. If there is, report that neither user-defined nor intrinsic operator worked. If there is not, describe the rules for the intrinsic operator. In either case, include the type(s) of the operand(s). Most of the uses of `ArgumentAnalyzer` are in helper functions that apply to classes of operators. For consistency, rename `BinaryOperationHelper` to `NumericBinaryOperator` and `LogicalHelper` to `LogicalBinaryHelper` and introduce `NumericUnaryHelper` for unary `+` and `-`. `.NOT.` and `//` are not implemented in helpers. Replace `success_` with `fatalErrors_` in `ArgumentAnalyzer` for consistency with `ExpressionAnalyzer`. Add `NumericOperator` and `LogicalOperator` enums to `Fortran.h` to go with `RelationalOperator`. Add `AddFortran` functions to each to convert to a Fortran source string. `RelationalOperator` also has `AllFortranNames` because there are multiple names for each operator. This replaces `LogicalOperator` in `expression.h` and the string representation of the operators in `formatting.cc`. Original-commit: flang-compiler/f18@3bb9d664e86c931a67b3e78859d2108e53d23f80 Reviewed-on: https://github.com/flang-compiler/f18/pull/807
2019-11-03 00:56:46 +08:00
!ERROR: Operands of + must be numeric; have LOGICAL(4) and untyped
y = x + z'1'
!ERROR: Operands of .NE. must have comparable types; have LOGICAL(4) and untyped
[flang] Resolve extended intrinsic operators Enhance `ArgumentAnalyzer` to do most of the work for this. For each kind of operator that might have a user-defined form we follow this process: - analyze the arguments - if the types and shapes match the intrinsic operator do the usual processing - otherwise attempt to interpret it as a user-defined operator with `TryDefinedOp` When we fail to resolve an operator, produce different errors depending on whether there is a user-defined operator available or not. If there is, report that neither user-defined nor intrinsic operator worked. If there is not, describe the rules for the intrinsic operator. In either case, include the type(s) of the operand(s). Most of the uses of `ArgumentAnalyzer` are in helper functions that apply to classes of operators. For consistency, rename `BinaryOperationHelper` to `NumericBinaryOperator` and `LogicalHelper` to `LogicalBinaryHelper` and introduce `NumericUnaryHelper` for unary `+` and `-`. `.NOT.` and `//` are not implemented in helpers. Replace `success_` with `fatalErrors_` in `ArgumentAnalyzer` for consistency with `ExpressionAnalyzer`. Add `NumericOperator` and `LogicalOperator` enums to `Fortran.h` to go with `RelationalOperator`. Add `AddFortran` functions to each to convert to a Fortran source string. `RelationalOperator` also has `AllFortranNames` because there are multiple names for each operator. This replaces `LogicalOperator` in `expression.h` and the string representation of the operators in `formatting.cc`. Original-commit: flang-compiler/f18@3bb9d664e86c931a67b3e78859d2108e53d23f80 Reviewed-on: https://github.com/flang-compiler/f18/pull/807
2019-11-03 00:56:46 +08:00
l = x /= null()
end
end
! Test alternate operators. They aren't enabled by default so should be
! treated as defined operators, not intrinsic ones.
module m4
contains
subroutine s1(x, y, z)
logical :: x
real :: y, z
!ERROR: No operator .A. defined for REAL(4) and REAL(4)
x = y .a. z
!ERROR: No operator .O. defined for REAL(4) and REAL(4)
x = y .o. z
!ERROR: No operator .N. defined for REAL(4)
x = .n. y
!ERROR: No operator .XOR. defined for REAL(4) and REAL(4)
x = y .xor. z
!ERROR: No operator .X. defined for REAL(4)
x = .x. y
end
end
! Like m4 in resolve63 but compiled with different options.
! .A. is a defined operator.
module m5
interface operator(.A.)
logical function f1(x, y)
integer, intent(in) :: x, y
end
end interface
interface operator(.and.)
logical function f2(x, y)
real, intent(in) :: x, y
end
end interface
contains
subroutine s1(x, y, z)
logical :: x
complex :: y, z
!ERROR: No intrinsic or user-defined OPERATOR(.AND.) matches operand types COMPLEX(4) and COMPLEX(4)
x = y .and. z
!ERROR: No intrinsic or user-defined .A. matches operand types COMPLEX(4) and COMPLEX(4)
x = y .a. z
end
end
! Type-bound operators
module m6
type :: t1
contains
procedure, pass(x) :: p1 => f1
generic :: operator(+) => p1
end type
type, extends(t1) :: t2
contains
procedure, pass(y) :: p2 => f2
generic :: operator(+) => p2
end type
type :: t3
contains
procedure, nopass :: p1 => f1
!ERROR: OPERATOR(+) procedure 'p1' may not have NOPASS attribute
generic :: operator(+) => p1
end type
contains
integer function f1(x, y)
class(t1), intent(in) :: x
integer, intent(in) :: y
end
integer function f2(x, y)
class(t1), intent(in) :: x
class(t2), intent(in) :: y
end
subroutine test(x, y, z)
class(t1) :: x
class(t2) :: y
integer :: i
i = x + y
i = x + i
i = y + i
!ERROR: No intrinsic or user-defined OPERATOR(+) matches operand types TYPE(t2) and TYPE(t1)
i = y + x
!ERROR: No intrinsic or user-defined OPERATOR(+) matches operand types INTEGER(4) and TYPE(t1)
i = i + x
end
end