Files
clang-p2996/flang/test/Semantics/defined-ops.f90
Andrzej Warzynski 96d229c9ab [flang][driver] Add options for unparsing
This patch adds the following compiler frontend driver options:
  * -fdebug-unparse (f18 spelling: -funparse)
  * -fdebug-unparse-with-symbols (f18 spelling: -funparse-with-symbols)
The new driver will only accept the new spelling. `f18` will accept both
the original and the new spelling.

A new base class for frontend actions is added: `PrescanAndSemaAction`.
This is added to reduce code duplication that otherwise these new
options would lead to. Implementation from
  * `ParseSyntaxOnlyAction::ExecutionAction`
is moved to:
  * `PrescanAndSemaAction::BeginSourceFileAction`
This implementation is now shared between:
  * PrescanAndSemaAction
  * ParseSyntaxOnlyAction
  * DebugUnparseAction
  * DebugUnparseWithSymbolsAction

All tests that don't require other yet unimplemented options are
updated. This way `flang-new -fc1` is used instead of `f18` when
`FLANG_BUILD_NEW_DRIVER` is set to `On`. In order to facilitate this,
`%flang_fc1` is added in the LIT configuration (lit.cfg.py).

`asFortran` from f18.cpp is duplicated as `getBasicAsFortran` in
FrontendOptions.cpp. At this stage it's hard to find a good place to
share this method. I suggest that we revisit this once a switch from
`f18` to `flang-new` is complete.

Differential Revision: https://reviews.llvm.org/D96483
2021-02-16 09:32:51 +00:00

89 lines
1.6 KiB
Fortran

! RUN: %flang_fc1 -fdebug-unparse %s 2>&1 | FileCheck %s
! Check the analyzed form of a defined operator or assignment.
! Type-bound defined assignment
module m1
type :: t
contains
procedure :: b1 => s1
procedure, pass(y) :: b2 => s2
generic :: assignment(=) => b1, b2
end type
contains
subroutine s1(x, y)
class(t), intent(out) :: x
integer, intent(in) :: y
end
subroutine s2(x, y)
real, intent(out) :: x
class(t), intent(in) :: y
end
subroutine test1(x)
type(t) :: x
real :: a
!CHECK: CALL s1(x,1_4)
x = 1
!CHECK: CALL s2(a,x)
a = x
end
subroutine test2(x)
class(t) :: x
real :: a
!CHECK: CALL x%b1(1_4)
x = 1
!CHECK: CALL x%b2(a)
a = x
end
end
! Type-bound operator
module m2
type :: t2
contains
procedure, pass(x2) :: b2 => f
generic :: operator(+) => b2
end type
contains
integer pure function f(x1, x2)
class(t2), intent(in) :: x1
class(t2), intent(in) :: x2
end
subroutine test2(x, y)
class(t2) :: x
type(t2) :: y
!CHECK: i=f(x,y)
i = x + y
!CHECK: i=x%b2(y)
i = y + x
end
end module
! Non-type-bound assignment and operator
module m3
type t
end type
interface assignment(=)
subroutine s1(x, y)
import
class(t), intent(out) :: x
integer, intent(in) :: y
end
end interface
interface operator(+)
integer function f(x, y)
import
class(t), intent(in) :: x, y
end
end interface
contains
subroutine test(x, y)
class(t) :: x, y
!CHECK: CALL s1(x,2_4)
x = 2
!CHECK: i=f(x,y)
i = x + y
end
end