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

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

80 lines
1.7 KiB
Fortran
Raw Normal View History

! RUN: %S/test_errors.sh %s %t %f18
! Resolve generic based on number of arguments
subroutine s1
interface f
real function f1(x)
optional :: x
end
real function f2(x, y)
end
end interface
z = f(1.0)
z = f(1.0, 2.0)
!ERROR: No specific procedure of generic 'f' matches the actual arguments
z = f(1.0, 2.0, 3.0)
end
! Elemental and non-element function both match: non-elemental one should be used
subroutine s2
interface f
logical elemental function f1(x)
intent(in) :: x
end
real function f2(x)
real :: x(10)
end
end interface
real :: x, y(10), z
logical :: a
a = f(1.0)
!ERROR: No intrinsic or user-defined ASSIGNMENT(=) matches operand types LOGICAL(4) and REAL(4)
a = f(y)
end
[flang] Resolve defined operators to specifics Most of these changes involve moving code around so that it case be used for `DefinedUnary` and `DefinedBinary`. The functional changes are in the `Analyze` member functions for those cases where the arguments are now analyzed, the generic is resolved, and a `FunctionRef` is created. Add `ArgumentAnalyzer` to handling building of the `ActualArguments` of a call. This allows the code to be shared with the defined unary and defined binary cases. Move `AnalyzeActualArgument` and `AnalyzeActualArgument` into that class (renaming both to `Analyze`). Create an overload of `GetCalleeAndArguments` for the `Name` case so it can be used for defined ops where we don't have a `ProcedureDesignator`. Move `IsGenericDefinedOp` to `tools.h` to make it available to the new code. We were using `semantics::CheckExplicitInterface` to resolve a generic interface to a specific procedure based on actual arguments. The problem with that is that it performs too many checks. We just want to get the right specific; there may be errors reported later during call analysis. To fix this, add a new function, `CheckInterfaceForGeneric`, to perform this check. It shares code with `CheckExplicitInterface`, but it passes in a null scope to indicate that the full set of checks aren't necessary in `CheckExplicitInterfaceArg`. Instead we lift the call to `TypeAndShape::IsCompatibleWith` out of `CheckExplicitDataArg`, and skip the latter when there is no scope. Original-commit: flang-compiler/f18@fff2d1580f26719e0c384c66576aa6620d04faff Reviewed-on: https://github.com/flang-compiler/f18/pull/786
2019-10-23 00:31:33 +08:00
! Resolve named operator
subroutine s3
interface operator(.foo.)
pure integer(8) function f_real(x, y)
real, intent(in) :: x, y
end
pure integer(8) function f_integer(x, y)
integer, intent(in) :: x, y
end
end interface
logical :: a, b, c
x = y .foo. z ! OK: f_real
i = j .foo. k ! OK: f_integer
!ERROR: No intrinsic or user-defined .FOO. matches operand types LOGICAL(4) and LOGICAL(4)
[flang] Resolve defined operators to specifics Most of these changes involve moving code around so that it case be used for `DefinedUnary` and `DefinedBinary`. The functional changes are in the `Analyze` member functions for those cases where the arguments are now analyzed, the generic is resolved, and a `FunctionRef` is created. Add `ArgumentAnalyzer` to handling building of the `ActualArguments` of a call. This allows the code to be shared with the defined unary and defined binary cases. Move `AnalyzeActualArgument` and `AnalyzeActualArgument` into that class (renaming both to `Analyze`). Create an overload of `GetCalleeAndArguments` for the `Name` case so it can be used for defined ops where we don't have a `ProcedureDesignator`. Move `IsGenericDefinedOp` to `tools.h` to make it available to the new code. We were using `semantics::CheckExplicitInterface` to resolve a generic interface to a specific procedure based on actual arguments. The problem with that is that it performs too many checks. We just want to get the right specific; there may be errors reported later during call analysis. To fix this, add a new function, `CheckInterfaceForGeneric`, to perform this check. It shares code with `CheckExplicitInterface`, but it passes in a null scope to indicate that the full set of checks aren't necessary in `CheckExplicitInterfaceArg`. Instead we lift the call to `TypeAndShape::IsCompatibleWith` out of `CheckExplicitDataArg`, and skip the latter when there is no scope. Original-commit: flang-compiler/f18@fff2d1580f26719e0c384c66576aa6620d04faff Reviewed-on: https://github.com/flang-compiler/f18/pull/786
2019-10-23 00:31:33 +08:00
a = b .foo. c
end
! Generic resolves successfully but error analyzing call
module m4
real, protected :: x
real :: y
interface s
pure subroutine s1(x)
[flang] Resolve defined operators to specifics Most of these changes involve moving code around so that it case be used for `DefinedUnary` and `DefinedBinary`. The functional changes are in the `Analyze` member functions for those cases where the arguments are now analyzed, the generic is resolved, and a `FunctionRef` is created. Add `ArgumentAnalyzer` to handling building of the `ActualArguments` of a call. This allows the code to be shared with the defined unary and defined binary cases. Move `AnalyzeActualArgument` and `AnalyzeActualArgument` into that class (renaming both to `Analyze`). Create an overload of `GetCalleeAndArguments` for the `Name` case so it can be used for defined ops where we don't have a `ProcedureDesignator`. Move `IsGenericDefinedOp` to `tools.h` to make it available to the new code. We were using `semantics::CheckExplicitInterface` to resolve a generic interface to a specific procedure based on actual arguments. The problem with that is that it performs too many checks. We just want to get the right specific; there may be errors reported later during call analysis. To fix this, add a new function, `CheckInterfaceForGeneric`, to perform this check. It shares code with `CheckExplicitInterface`, but it passes in a null scope to indicate that the full set of checks aren't necessary in `CheckExplicitInterfaceArg`. Instead we lift the call to `TypeAndShape::IsCompatibleWith` out of `CheckExplicitDataArg`, and skip the latter when there is no scope. Original-commit: flang-compiler/f18@fff2d1580f26719e0c384c66576aa6620d04faff Reviewed-on: https://github.com/flang-compiler/f18/pull/786
2019-10-23 00:31:33 +08:00
real, intent(out) :: x
end
subroutine s2(x, y)
real :: x, y
end
end interface
end
subroutine s4a
use m4
real :: z
!OK
call s(z)
end
subroutine s4b
use m4
!ERROR: Actual argument associated with INTENT(OUT) dummy argument 'x=' must be definable
call s(x)
end
pure subroutine s4c
use m4
!ERROR: Actual argument associated with INTENT(OUT) dummy argument 'x=' must be definable
call s(y)
end