[flang] Enable polymorphic lowering by default (#83285)

Polymorphic entity lowering status is good. The main remaining TODO is
to allow lowering of vector subscripted polymorphic entity, but this
does not deserve blocking all application using polymorphism.

Remove experimental option and enable lowering of polymorphic entity by
default.
This commit is contained in:
jeanPerier 2024-03-19 11:45:31 +01:00 committed by GitHub
parent d1c3795968
commit d0829fbded
No known key found for this signature in database
GPG Key ID: B5690EEEBB952194
68 changed files with 63 additions and 107 deletions

View File

@ -6441,11 +6441,6 @@ def flang_deprecated_no_hlfir : Flag<["-"], "flang-deprecated-no-hlfir">,
Flags<[HelpHidden]>, Visibility<[FlangOption, FC1Option]>,
HelpText<"Do not use HLFIR lowering (deprecated)">;
def flang_experimental_polymorphism : Flag<["-"], "flang-experimental-polymorphism">,
Flags<[HelpHidden]>, Visibility<[FlangOption, FC1Option]>,
HelpText<"Enable Fortran 2003 polymorphism (experimental)">;
//===----------------------------------------------------------------------===//
// FLangOption + CoreOption + NoXarchOption
//===----------------------------------------------------------------------===//

View File

@ -148,7 +148,6 @@ void Flang::addCodegenOptions(const ArgList &Args,
Args.addAllArgs(CmdArgs, {options::OPT_flang_experimental_hlfir,
options::OPT_flang_deprecated_no_hlfir,
options::OPT_flang_experimental_polymorphism,
options::OPT_fno_ppc_native_vec_elem_order,
options::OPT_fppc_native_vec_elem_order});
}

View File

@ -24,9 +24,6 @@ LOWERINGOPT(Name, Bits, Default)
/// If true, lower transpose without a runtime call.
ENUM_LOWERINGOPT(OptimizeTranspose, unsigned, 1, 1)
/// If true, enable polymorphic type lowering feature. On by default.
ENUM_LOWERINGOPT(PolymorphicTypeImpl, unsigned, 1, 1)
/// If true, lower to High level FIR before lowering to FIR. On by default.
ENUM_LOWERINGOPT(LowerToHighLevelFIR, unsigned, 1, 1)

View File

@ -1191,11 +1191,6 @@ bool CompilerInvocation::createFromArgs(
invoc.loweringOpts.setLowerToHighLevelFIR(false);
}
if (args.hasArg(
clang::driver::options::OPT_flang_experimental_polymorphism)) {
invoc.loweringOpts.setPolymorphicTypeImpl(true);
}
// -fno-ppc-native-vector-element-order
if (args.hasArg(clang::driver::options::OPT_fno_ppc_native_vec_elem_order)) {
invoc.loweringOpts.setNoPPCNativeVecElemOrder(true);

View File

@ -1050,12 +1050,6 @@ private:
Fortran::common::TypeCategory cat = dynamicType.category();
// DERIVED
if (cat == Fortran::common::TypeCategory::Derived) {
// TODO is kept under experimental flag until feature is complete.
if (dynamicType.IsPolymorphic() &&
!getConverter().getLoweringOptions().getPolymorphicTypeImpl())
TODO(interface.converter.getCurrentLocation(),
"support for polymorphic types");
if (dynamicType.IsUnlimitedPolymorphic())
return mlir::NoneType::get(&mlirContext);
return getConverter().genType(dynamicType.GetDerivedTypeSpec());

View File

@ -263,10 +263,6 @@ struct TypeBuilderImpl {
llvm::SmallVector<Fortran::lower::LenParameterTy> params;
translateLenParameters(params, tySpec->category(), ultimate);
ty = genFIRType(context, tySpec->category(), kind, params);
} else if (type->IsPolymorphic() &&
!converter.getLoweringOptions().getPolymorphicTypeImpl()) {
// TODO is kept under experimental flag until feature is complete.
TODO(loc, "support for polymorphic types");
} else if (type->IsUnlimitedPolymorphic()) {
ty = mlir::NoneType::get(context);
} else if (const Fortran::semantics::DerivedTypeSpec *tySpec =

View File

@ -52,8 +52,6 @@
! CHECK-NEXT: Do not use HLFIR lowering (deprecated)
! CHECK-NEXT: -flang-experimental-hlfir
! CHECK-NEXT: Use HLFIR lowering (experimental)
! CHECK-NEXT: -flang-experimental-polymorphism
! CHECK-NEXT: Enable Fortran 2003 polymorphism (experimental)
! CHECK-NEXT: -flarge-sizes Use INTEGER(KIND=8) for the result type in size-related intrinsics
! CHECK-NEXT: -flogical-abbreviations Enable logical abbreviations
! CHECK-NEXT: -flto=auto Enable LTO in 'full' mode

View File

@ -1,10 +0,0 @@
! Test -flang-experimental-hlfir flag
! RUN: %flang_fc1 -flang-experimental-polymorphism -emit-fir -o - %s | FileCheck %s
! RUN: %flang_fc1 -emit-fir -o - %s 2>&1 | FileCheck %s --check-prefix NO-POLYMORPHISM
! CHECK: func.func @_QPtest(%{{.*}}: !fir.class<none> {fir.bindc_name = "poly"})
subroutine test(poly)
class(*) :: poly
end subroutine test
! NO-POLYMORPHISM: func.func @_QPtest

View File

@ -17,7 +17,6 @@
! RUN: -fomit-frame-pointer \
! RUN: -fpass-plugin=Bye%pluginext \
! RUN: -fversion-loops-for-stride \
! RUN: -flang-experimental-polymorphism \
! RUN: -flang-experimental-hlfir \
! RUN: -flang-deprecated-no-hlfir \
! RUN: -fno-ppc-native-vector-element-order \
@ -49,7 +48,6 @@
! CHECK: "-fconvert=little-endian"
! CHECK: "-fpass-plugin=Bye
! CHECK: "-fversion-loops-for-stride"
! CHECK: "-flang-experimental-polymorphism"
! CHECK: "-flang-experimental-hlfir"
! CHECK: "-flang-deprecated-no-hlfir"
! CHECK: "-fno-ppc-native-vector-element-order"

View File

@ -1,5 +1,5 @@
! RUN: bbc -polymorphic-type -emit-hlfir %s -o - | fir-opt --fir-polymorphic-op | FileCheck %s
! RUN: bbc -polymorphic-type -emit-hlfir %s -o - | FileCheck %s --check-prefix=BT
! RUN: bbc -emit-hlfir %s -o - | fir-opt --fir-polymorphic-op | FileCheck %s
! RUN: bbc -emit-hlfir %s -o - | FileCheck %s --check-prefix=BT
! Tests codegen of fir.dispatch operation. This test is intentionally run from
! Fortran through bbc and tco so we have all the binding tables lowered to FIR

View File

@ -1,6 +1,6 @@
! Test lowering to FIR of actual arguments that are assumed type
! variables (Fortran 2018 7.3.2.2 point 3).
! RUN: bbc --polymorphic-type -emit-hlfir -o - %s | FileCheck %s
! RUN: bbc -emit-hlfir -o - %s | FileCheck %s
subroutine test1(x)
interface

View File

@ -1,4 +1,4 @@
! RUN: bbc -polymorphic-type -emit-hlfir %s -o - | FileCheck %s
! RUN: bbc -emit-hlfir %s -o - | FileCheck %s
! CHECK-LABEL: func.func @_QPtest1(
! CHECK-SAME: %[[VAL_0:.*]]: !fir.class<none> {fir.bindc_name = "x"}) {

View File

@ -1,4 +1,4 @@
! RUN: bbc -polymorphic-type -emit-hlfir %s -o - | FileCheck %s
! RUN: bbc -emit-hlfir %s -o - | FileCheck %s
! Test passing arguments to subprograms with polymorphic dummy arguments.

View File

@ -1,5 +1,5 @@
! Test actual TARGET argument association to dummy POINTER:
! RUN: bbc -emit-hlfir --polymorphic-type -o - -I nowhere %s 2>&1 | FileCheck %s
! RUN: bbc -emit-hlfir -o - -I nowhere %s 2>&1 | FileCheck %s
module target_to_pointer_types
type t1

View File

@ -1,4 +1,4 @@
! RUN: bbc -emit-hlfir --polymorphic-type -I nowhere %s -o - | FileCheck %s
! RUN: bbc -emit-hlfir -I nowhere %s -o - | FileCheck %s
! Test allocatable return.
! Allocatable arrays must have default runtime lbounds after the return.

View File

@ -1,5 +1,5 @@
! Test lowering of derived type array constructors to HLFIR.
! RUN: bbc -emit-hlfir --polymorphic-type -o - %s | FileCheck %s
! RUN: bbc -emit-hlfir -o - %s | FileCheck %s
module types
type simple

View File

@ -1,7 +1,7 @@
! Test lowering of sequence associated arguments (F'2023 15.5.2.12) passed
! by descriptor. The descriptor on the caller side is prepared according to
! the dummy argument shape.
! RUN: bbc -emit-hlfir -polymorphic-type -o - %s | FileCheck %s
! RUN: bbc -emit-hlfir -o - %s | FileCheck %s
module bindc_seq_assoc
interface

View File

@ -1,6 +1,6 @@
! Test lowering of calls involving assumed shape arrays or arrays with
! VALUE attribute.
! RUN: bbc -emit-hlfir -polymorphic-type -o - %s | FileCheck %s
! RUN: bbc -emit-hlfir -o - %s | FileCheck %s
subroutine test_assumed_to_assumed(x)
interface

View File

@ -1,4 +1,4 @@
! RUN: bbc -emit-hlfir --polymorphic-type -o - %s | FileCheck %s
! RUN: bbc -emit-hlfir -o - %s | FileCheck %s
! Test when constant argument are copied in memory
! and passed to polymorphic arguments.

View File

@ -2,7 +2,7 @@
! that is syntactically present, but may be absent at runtime (is
! an optional or a pointer/allocatable).
!
! RUN: bbc -emit-hlfir -polymorphic-type -o - %s | FileCheck %s
! RUN: bbc -emit-hlfir -o - %s | FileCheck %s
subroutine optional_copy_in_out(x)
interface

View File

@ -1,6 +1,6 @@
! Test passing rank 2 CLASS(*) deferred shape to assumed size assumed type
! This requires copy-in/copy-out logic.
! RUN: bbc -emit-hlfir -polymorphic-type -o - %s | FileCheck %s
! RUN: bbc -emit-hlfir -o - %s | FileCheck %s
subroutine pass_poly_to_assumed_type_assumed_size(x)
class(*), target :: x(:,:)

View File

@ -1,5 +1,5 @@
! Test conversion of MutableBoxValue to value.
! RUN: bbc -emit-hlfir -polymorphic-type -I nowhere %s -o - | FileCheck %s
! RUN: bbc -emit-hlfir -I nowhere %s -o - | FileCheck %s
subroutine test_int_allocatable(a)
integer, allocatable :: a

View File

@ -1,5 +1,5 @@
! Test lowering of component reference to HLFIR
! RUN: bbc -emit-hlfir --polymorphic-type -o - %s | FileCheck %s
! RUN: bbc -emit-hlfir -o - %s | FileCheck %s
module comp_ref
type t1
integer :: scalar_i

View File

@ -1,5 +1,5 @@
! Test non-contiguous slice of parameter array.
! RUN: bbc -emit-hlfir --polymorphic-type -o - %s | FileCheck %s
! RUN: bbc -emit-hlfir -o - %s | FileCheck %s
subroutine test2(i)
integer, parameter :: a(*,*) = reshape( [ 1,2,3,4 ], [ 2,2 ])
integer :: x(2)

View File

@ -1,5 +1,5 @@
! Test lowering of elemental intrinsic operations with array arguments to HLFIR
! RUN: bbc -emit-hlfir --polymorphic-type -I nowhere -o - %s 2>&1 | FileCheck %s
! RUN: bbc -emit-hlfir -I nowhere -o - %s 2>&1 | FileCheck %s
subroutine binary(x, y)
integer :: x(100), y(100)

View File

@ -1,5 +1,5 @@
! Test that the produced hlfir.elemental had proper result type and the mold.
! RUN: bbc --emit-hlfir --polymorphic-type -I nowhere -o - %s | FileCheck %s
! RUN: bbc --emit-hlfir -I nowhere -o - %s | FileCheck %s
subroutine test_polymorphic_merge(x, y, r, m)
type t

View File

@ -1,6 +1,6 @@
! Test lowering of user defined elemental procedure reference to HLFIR
! With polymorphic arguments.
! RUN: bbc -emit-hlfir -I nw -polymorphic-type -o - %s 2>&1 | FileCheck %s
! RUN: bbc -emit-hlfir -I nw -o - %s 2>&1 | FileCheck %s
module def_some_types
type :: t
integer :: i

View File

@ -1,4 +1,4 @@
! RUN: bbc -emit-hlfir --polymorphic-type -o - %s -I nowhere 2>&1 | FileCheck %s
! RUN: bbc -emit-hlfir -o - %s -I nowhere 2>&1 | FileCheck %s
module types
type t1

View File

@ -1,4 +1,4 @@
! RUN: bbc -emit-hlfir -polymorphic-type %s -o - -I nowhere | FileCheck %s
! RUN: bbc -emit-hlfir %s -o - -I nowhere | FileCheck %s
module types
type t1

View File

@ -1,6 +1,6 @@
! Test passing mismatching rank arguments to unlimited polymorphic
! dummy with IGNORE_TKR(R).
! RUN: bbc -emit-hlfir -polymorphic-type -o - -I nowhere %s 2>&1 | FileCheck %s
! RUN: bbc -emit-hlfir -o - -I nowhere %s 2>&1 | FileCheck %s
module m
interface

View File

@ -2,7 +2,7 @@
! dummy has IGNORE_TKR(t). The descriptor should be prepared
! according to the actual argument type, but its bounds and
! attributes should still be set as expected for the dummy.
! RUN: bbc -emit-hlfir --polymorphic-type -o - %s | FileCheck %s
! RUN: bbc -emit-hlfir -o - %s | FileCheck %s
module tkr_ifaces
interface

View File

@ -1,6 +1,6 @@
! Test that allocatable components of non pointer/non allocatable INTENT(OUT)
! dummy arguments are deallocated.
! RUN: bbc -emit-hlfir -polymorphic-type %s -o - -I nowhere | FileCheck %s
! RUN: bbc -emit-hlfir %s -o - -I nowhere | FileCheck %s
subroutine test_intentout_component_deallocate(a)
type :: t

View File

@ -1,6 +1,6 @@
! Test lowering of internal procedure capturing OPTIONAL polymorphic
! objects.
! RUN: bbc -emit-hlfir --polymorphic-type -o - %s -I nw | FileCheck %s
! RUN: bbc -emit-hlfir -o - %s -I nw | FileCheck %s
module captured_optional_polymorphic

View File

@ -2,7 +2,7 @@
! arguments. These are a bit special because semantics do not represent
! assumed types actual arguments with an evaluate::Expr like for usual
! arguments.
! RUN: bbc -emit-hlfir --polymorphic-type -o - %s | FileCheck %s
! RUN: bbc -emit-hlfir -o - %s | FileCheck %s
subroutine assumed_type_to_intrinsic(a)
type(*) :: a(:)

View File

@ -1,5 +1,5 @@
! Test lowering of parent component references to HLFIR.
! RUN: bbc -emit-hlfir -polymorphic-type -o - %s -I nw | FileCheck %s
! RUN: bbc -emit-hlfir -o - %s -I nw | FileCheck %s
module pc_types
type t

View File

@ -1,6 +1,6 @@
! Test passing polymorphic expression for non-polymorphic contiguous
! dummy argument:
! RUN: bbc -emit-hlfir --polymorphic-type -o - -I nowhere %s | FileCheck %s
! RUN: bbc -emit-hlfir -o - -I nowhere %s | FileCheck %s
module types
type t

View File

@ -1,4 +1,4 @@
! RUN: bbc -emit-hlfir --polymorphic-type -o - %s -I nowhere | FileCheck %s
! RUN: bbc -emit-hlfir -o - %s -I nowhere | FileCheck %s
module polymorphic_expressions_types
type t

View File

@ -1,5 +1,5 @@
! Test lowering of NOPASS procedure pointers components.
! RUN: bbc -emit-hlfir -polymorphic-type -o - %s | FileCheck %s
! RUN: bbc -emit-hlfir -o - %s | FileCheck %s
module proc_comp_defs
interface

View File

@ -1,5 +1,5 @@
! Test lowering of PASS procedure pointers components.
! RUN: bbc -emit-hlfir -polymorphic-type -o - %s | FileCheck %s
! RUN: bbc -emit-hlfir -o - %s | FileCheck %s
module m
type t

View File

@ -14,7 +14,7 @@
! (16.9.109) applied to the corresponding dimension of selector. The upper bound of each dimension is one less
! than the sum of the lower bound and the extent.
! RUN: bbc -emit-hlfir -polymorphic-type -I nowhere -o - %s | FileCheck %s
! RUN: bbc -emit-hlfir -I nowhere -o - %s | FileCheck %s
subroutine test()
type t

View File

@ -1,5 +1,5 @@
! Test lowering of TRANSPOSE intrinsic to HLFIR
! RUN: bbc -emit-hlfir --polymorphic-type -o - %s 2>&1 | FileCheck %s
! RUN: bbc -emit-hlfir -o - %s 2>&1 | FileCheck %s
subroutine transpose1(m, res)
integer :: m(1,2), res(2, 1)

View File

@ -1,6 +1,6 @@
! Test interface that lowering handles small interface mismatch with
! type bound procedures.
! RUN: bbc -emit-hlfir --polymorphic-type %s -o - -I nw | FileCheck %s
! RUN: bbc -emit-hlfir %s -o - -I nw | FileCheck %s
module dispatch_mismatch
type t

View File

@ -1,6 +1,6 @@
! Test lowering of vector subscript designators outside of the
! assignment left-and side and input IO context.
! RUN: bbc -emit-hlfir -o - -I nw %s --polymorphic-type 2>&1 | FileCheck %s
! RUN: bbc -emit-hlfir -o - -I nw %s 2>&1 | FileCheck %s
subroutine foo(x, y)
integer :: x(100)

View File

@ -1,4 +1,4 @@
! RUN: bbc -emit-fir -hlfir=false -polymorphic-type %s -o - | FileCheck %s
! RUN: bbc -emit-fir -hlfir=false %s -o - | FileCheck %s
module extends_type_of_mod

View File

@ -1,4 +1,4 @@
! RUN: bbc -emit-fir -hlfir=false -polymorphic-type %s -o - | FileCheck %s
! RUN: bbc -emit-fir -hlfir=false %s -o - | FileCheck %s
module same_type_as_mod

View File

@ -1,5 +1,5 @@
! Test SIZEOF lowering for polymorphic entities.
! RUN: bbc -emit-hlfir --polymorphic-type -o - %s | FileCheck %s
! RUN: bbc -emit-hlfir -o - %s | FileCheck %s
integer(8) function test1(x)
class(*) :: x

View File

@ -1,4 +1,4 @@
! RUN: bbc -emit-fir -hlfir=false -polymorphic-type %s -o - | FileCheck %s
! RUN: bbc -emit-fir -hlfir=false %s -o - | FileCheck %s
module spread_mod

View File

@ -1,4 +1,4 @@
! RUN: bbc -emit-fir -hlfir=false -polymorphic-type %s -o - | FileCheck %s
! RUN: bbc -emit-fir -hlfir=false %s -o - | FileCheck %s
module storage_size_test
type :: p1

View File

@ -1,5 +1,5 @@
! RUN: bbc --use-desc-for-alloc=false -polymorphic-type -emit-hlfir %s -o - | FileCheck %s
! RUN: bbc --use-desc-for-alloc=false -polymorphic-type -emit-hlfir %s -o - | tco | FileCheck %s --check-prefix=LLVM
! RUN: bbc --use-desc-for-alloc=false -emit-hlfir %s -o - | FileCheck %s
! RUN: bbc --use-desc-for-alloc=false -emit-hlfir %s -o - | tco | FileCheck %s --check-prefix=LLVM
module poly
type p1

View File

@ -1,4 +1,4 @@
! RUN: bbc -emit-fir -hlfir=false --polymorphic-type -I nowhere %s -o - | FileCheck %s
! RUN: bbc -emit-fir -hlfir=false -I nowhere %s -o - | FileCheck %s
! Test allocatable return.
! Allocatable arrays must have default runtime lbounds after the return.

View File

@ -1,4 +1,4 @@
! RUN: bbc -polymorphic-type -emit-fir -hlfir=false %s -o - | FileCheck %s
! RUN: bbc -emit-fir -hlfir=false %s -o - | FileCheck %s
module assumed_type_test

View File

@ -1,5 +1,5 @@
! Test default initialization of local and dummy variables (dynamic initialization)
! RUN: bbc -emit-fir -hlfir=false -polymorphic-type %s -o - | FileCheck %s
! RUN: bbc -emit-fir -hlfir=false %s -o - | FileCheck %s
module test_dinit
type t

View File

@ -1,5 +1,5 @@
! Test derived type finalization
! RUN: bbc --use-desc-for-alloc=false -polymorphic-type -emit-fir -hlfir=false %s -o - | FileCheck %s
! RUN: bbc --use-desc-for-alloc=false -emit-fir -hlfir=false %s -o - | FileCheck %s
! Missing tests:
! - finalization within BLOCK construct

View File

@ -1,4 +1,4 @@
! RUN: bbc -polymorphic-type -emit-fir %s -o - | FileCheck %s
! RUN: bbc -emit-fir %s -o - | FileCheck %s
! Tests the generation of fir.type_info operations.

View File

@ -1,4 +1,4 @@
! RUN: bbc -polymorphic-type -emit-hlfir %s -o - | FileCheck %s
! RUN: bbc -emit-hlfir %s -o - | FileCheck %s
! Tests the different possible type involving polymorphic entities.

View File

@ -1,6 +1,6 @@
! Test correct deallocation of intent(out) allocatables.
! RUN: bbc --use-desc-for-alloc=false -emit-fir -hlfir=false -polymorphic-type %s -o - | FileCheck %s --check-prefixes=CHECK,FIR
! RUN: bbc -emit-hlfir -polymorphic-type %s -o - -I nw | FileCheck %s --check-prefixes=CHECK,HLFIR
! RUN: bbc --use-desc-for-alloc=false -emit-fir -hlfir=false %s -o - | FileCheck %s --check-prefixes=CHECK,FIR
! RUN: bbc -emit-hlfir %s -o - -I nw | FileCheck %s --check-prefixes=CHECK,HLFIR
module mod1
type, bind(c) :: t1

View File

@ -1,6 +1,6 @@
! Check that InputDerivedType/OutputDeriverType APIs are used
! for io of derived types.
! RUN: bbc -polymorphic-type -emit-fir -o - %s | FileCheck %s
! RUN: bbc -emit-fir -o - %s | FileCheck %s
module p
type :: person

View File

@ -1,4 +1,4 @@
! RUN: bbc -polymorphic-type -emit-fir -hlfir=false -o - %s | FileCheck %s
! RUN: bbc -emit-fir -hlfir=false -o - %s | FileCheck %s
module m
type t

View File

@ -1,4 +1,4 @@
! RUN: bbc -polymorphic-type -emit-hlfir %s -o - | FileCheck %s
! RUN: bbc -emit-hlfir %s -o - | FileCheck %s
module poly
type p1

View File

@ -1,5 +1,5 @@
! RUN: bbc -emit-fir -polymorphic-type %s -o - | FileCheck %s --check-prefix=FIR
! RUN: bbc -emit-fir -polymorphic-type -hlfir %s -o - | FileCheck %s --check-prefix=HLFIR
! RUN: bbc -emit-fir %s -o - | FileCheck %s --check-prefix=FIR
! RUN: bbc -emit-fir -hlfir %s -o - | FileCheck %s --check-prefix=HLFIR
subroutine test
interface

View File

@ -1,4 +1,4 @@
! RUN: bbc -polymorphic-type -emit-fir -hlfir=false %s -o - | FileCheck %s
! RUN: bbc -emit-fir -hlfir=false %s -o - | FileCheck %s
module poly
type p1

View File

@ -1,5 +1,5 @@
! Test lowering of pointer disassociation
! RUN: bbc -emit-fir -hlfir=false --polymorphic-type %s -o - | FileCheck %s
! RUN: bbc -emit-fir -hlfir=false %s -o - | FileCheck %s
! -----------------------------------------------------------------------------

View File

@ -1,5 +1,5 @@
! Test creation of temporary from polymorphic enities
! RUN: bbc -polymorphic-type -emit-fir -hlfir=false %s -o - | FileCheck %s
! RUN: bbc -emit-fir -hlfir=false %s -o - | FileCheck %s
module poly_tmp
type p1

View File

@ -1,4 +1,4 @@
! RUN: bbc -polymorphic-type -emit-fir -hlfir=false %s -o - | FileCheck %s
! RUN: bbc -emit-fir -hlfir=false %s -o - | FileCheck %s
! Tests the different possible type involving polymorphic entities.

View File

@ -1,4 +1,4 @@
! RUN: bbc --use-desc-for-alloc=false -polymorphic-type -emit-fir -hlfir=false %s -o - | FileCheck %s
! RUN: bbc --use-desc-for-alloc=false -emit-fir -hlfir=false %s -o - | FileCheck %s
! Tests various aspect of the lowering of polymorphic entities.

View File

@ -1,4 +1,4 @@
! RUN: bbc -polymorphic-type -emit-fir -hlfir=false %s -o - | fir-opt --fir-polymorphic-op | FileCheck %s
! RUN: bbc -emit-fir -hlfir=false %s -o - | fir-opt --fir-polymorphic-op | FileCheck %s
module select_type_2
type p1
integer :: a

View File

@ -1,5 +1,5 @@
! RUN: bbc -polymorphic-type -emit-fir -hlfir=false %s -o - | FileCheck %s
! RUN: bbc -polymorphic-type -emit-fir -hlfir=false %s -o - | fir-opt --fir-polymorphic-op | FileCheck --check-prefix=CFG %s
! RUN: bbc -emit-fir -hlfir=false %s -o - | FileCheck %s
! RUN: bbc -emit-fir -hlfir=false %s -o - | fir-opt --fir-polymorphic-op | FileCheck --check-prefix=CFG %s
module select_type_lower_test
type p1
integer :: a

View File

@ -191,11 +191,6 @@ static llvm::cl::opt<bool> enableOpenACC("fopenacc",
llvm::cl::desc("enable openacc"),
llvm::cl::init(false));
static llvm::cl::opt<bool> enablePolymorphic(
"polymorphic-type",
llvm::cl::desc("enable polymorphic type lowering (experimental)"),
llvm::cl::init(false));
static llvm::cl::opt<bool> enableNoPPCNativeVecElemOrder(
"fno-ppc-native-vector-element-order",
llvm::cl::desc("no PowerPC native vector element order."),
@ -351,7 +346,6 @@ static mlir::LogicalResult convertFortranSourceToMLIR(
std::string targetTriple = targetMachine.getTargetTriple().normalize();
// Use default lowering options for bbc.
Fortran::lower::LoweringOptions loweringOptions{};
loweringOptions.setPolymorphicTypeImpl(enablePolymorphic);
loweringOptions.setNoPPCNativeVecElemOrder(enableNoPPCNativeVecElemOrder);
loweringOptions.setLowerToHighLevelFIR(useHLFIR || emitHLFIR);
std::vector<Fortran::lower::EnvironmentDefault> envDefaults = {};