flang-compiler / f18-llvm-project

Fork of llvm/llvm-project for f18. In sync with f18-mlir and f18.
http://llvm.org
28 stars 16 forks source link

tco segfaults: ExtractValueOpConversion::doRewrite #827

Closed oroppas closed 3 years ago

oroppas commented 3 years ago

tco crashes on the following mlir

func @_QPzlctes(%arg0: !fir.ref<!fir.complex<8>>, %arg1: !fir.ref<!fir.complex<8>>) -> !fir.logical<4> {
  %cst = constant 1.000000e+00 : f64
  %c0 = constant 0 : index
  %c1 = constant 1 : index
  %cst_0 = constant 0.000000e+00 : f64
  %0 = fir.alloca !fir.logical<4> {bindc_name = "zlctes", uniq_name = "_QFzlctesEzlctes"}
  %1 = fir.alloca f64 {bindc_name = "zmax", uniq_name = "_QFzlctesEzmax"}
  %2 = fir.load %arg1 : !fir.ref<!fir.complex<8>>
  %3 = fir.undefined !fir.complex<8>
  %4 = fir.insert_value %3, %cst_0, %c0 : (!fir.complex<8>, f64, index) -> !fir.complex<8>
  %5 = fir.insert_value %4, %cst_0, %c1 : (!fir.complex<8>, f64, index) -> !fir.complex<8>
  %6 = fir.cmpc "oeq", %2, %5 : !fir.complex<8>
  cond_br %6, ^bb1, ^bb2
^bb1:  // pred: ^bb0
  %7 = fir.load %arg0 : !fir.ref<!fir.complex<8>>
  %8 = fir.extract_value %7, %c0 : (!fir.complex<8>, index) -> f64
  %9 = cmpf olt, %8, %cst_0 : f64
  %10 = fir.no_reassoc %9 : i1
  %11 = fir.convert %10 : (i1) -> !fir.logical<4>
  fir.store %11 to %0 : !fir.ref<!fir.logical<4>>
  br ^bb6
^bb2:  // pred: ^bb0
  %12 = fir.load %arg0 : !fir.ref<!fir.complex<8>>
  %13 = fir.extract_value %12, %c0 : (!fir.complex<8>, index) -> f64
  %14 = cmpf oeq, %13, %cst_0 : f64
  %15 = fir.load %arg1 : !fir.ref<!fir.complex<8>>
  %16 = fir.extract_value %15, %c0 : (!fir.complex<8>, index) -> f64
  %17 = cmpf oeq, %16, %cst_0 : f64
  %18 = or %14, %17 : i1
  cond_br %18, ^bb3(%c1, %c1 : index, index), ^bb4
^bb3(%19: index, %20: index):  // 2 preds: ^bb2, ^bb4
  %21 = fir.load %arg0 : !fir.ref<!fir.complex<8>>
  %22 = fir.extract_value %21, %19 : (!fir.complex<8>, index) -> f64
  %23 = fir.call @llvm.fabs.f64(%cst) : (f64) -> f64
  %24 = fir.negf %23 : f64
  %25 = cmpf olt, %22, %cst_0 : f64
  %26 = select %25, %24, %23 : f64
  %27 = fir.load %arg1 : !fir.ref<!fir.complex<8>>
  %28 = fir.extract_value %27, %20 : (!fir.complex<8>, index) -> f64
  %29 = fir.call @llvm.fabs.f64(%cst) : (f64) -> f64
  %30 = fir.negf %29 : f64
  %31 = cmpf olt, %28, %cst_0 : f64
  %32 = select %31, %30, %29 : f64
  %33 = cmpf une, %26, %32 : f64
  %34 = fir.no_reassoc %33 : i1
  %35 = fir.convert %34 : (i1) -> !fir.logical<4>
  fir.store %35 to %0 : !fir.ref<!fir.logical<4>>
  br ^bb6
^bb4:  // pred: ^bb2
  %36 = fir.load %arg0 : !fir.ref<!fir.complex<8>>
  %37 = fir.extract_value %36, %c1 : (!fir.complex<8>, index) -> f64
  %38 = cmpf oeq, %37, %cst_0 : f64
  %39 = fir.load %arg1 : !fir.ref<!fir.complex<8>>
  %40 = fir.extract_value %39, %c1 : (!fir.complex<8>, index) -> f64
  %41 = cmpf oeq, %40, %cst_0 : f64
  %42 = or %38, %41 : i1
  cond_br %42, ^bb3(%c0, %c0 : index, index), ^bb5
^bb5:  // pred: ^bb4
  %43 = fir.load %arg0 : !fir.ref<!fir.complex<8>>
  %44 = fir.extract_value %43, %c0 : (!fir.complex<8>, index) -> f64
  %45 = fir.call @llvm.fabs.f64(%44) : (f64) -> f64
  %46 = fir.load %arg0 : !fir.ref<!fir.complex<8>>
  %47 = fir.extract_value %46, %c1 : (!fir.complex<8>, index) -> f64
  %48 = fir.call @llvm.fabs.f64(%47) : (f64) -> f64
  %49 = cmpf ogt, %45, %48 : f64
  %50 = select %49, %45, %48 : f64
  fir.store %50 to %1 : !fir.ref<f64>
  %51 = fir.load %arg0 : !fir.ref<!fir.complex<8>>
  %52 = fir.extract_value %51, %c0 : (!fir.complex<8>, index) -> f64
  %53 = fir.load %1 : !fir.ref<f64>
  %54 = divf %52, %53 : f64
  %55 = fir.no_reassoc %54 : f64
  %56 = fir.load %arg1 : !fir.ref<!fir.complex<8>>
  %57 = fir.extract_value %56, %c0 : (!fir.complex<8>, index) -> f64
  %58 = mulf %55, %57 : f64
  %59 = fir.extract_value %51, %c1 : (!fir.complex<8>, index) -> f64
  %60 = divf %59, %53 : f64
  %61 = fir.no_reassoc %60 : f64
  %62 = fir.extract_value %56, %c1 : (!fir.complex<8>, index) -> f64
  %63 = mulf %61, %62 : f64
  %64 = addf %58, %63 : f64
  %65 = cmpf olt, %64, %cst_0 : f64
  %66 = fir.no_reassoc %65 : i1
  %67 = fir.convert %66 : (i1) -> !fir.logical<4>
  fir.store %67 to %0 : !fir.ref<!fir.logical<4>>
  br ^bb6
^bb6:  // 3 preds: ^bb1, ^bb3, ^bb5
  %68 = fir.load %0 : !fir.ref<!fir.logical<4>>
  return %68 : !fir.logical<4>
}
fir.global internal @_QFzlctesECczero constant : !fir.complex<8> {
  %cst = constant 0.000000e+00 : f64
  %c0 = constant 0 : index
  %c1 = constant 1 : index
  %0 = fir.undefined !fir.complex<8>
  %1 = fir.insert_value %0, %cst, %c0 : (!fir.complex<8>, f64, index) -> !fir.complex<8>
  %2 = fir.insert_value %1, %cst, %c1 : (!fir.complex<8>, f64, index) -> !fir.complex<8>
  fir.has_value %2 : !fir.complex<8>
}
fir.global internal @_QFzlctesECone constant : f64 {
  %cst = constant 1.000000e+00 : f64
  fir.has_value %cst : f64
}
fir.global internal @_QFzlctesECzero constant : f64 {
  %cst = constant 0.000000e+00 : f64
  fir.has_value %cst : f64
}
func private @llvm.fabs.f64(f64) -> f64 attributes {fir.runtime}

Here's stack dump

Stack dump:
0.      Program arguments: /home/ryuta/packages/llvm/flang/build/bin/tco zlctes.mlir
 #0 0x00007f09b5443923 llvm::sys::PrintStackTrace(llvm::raw_ostream&, int) (/home/ryuta/packages/llvm/flang/build/lib/libLLVMSupport.so.13git+0x205923)
 #1 0x00007f09b544110e llvm::sys::RunSignalHandlers() (/home/ryuta/packages/llvm/flang/build/lib/libLLVMSupport.so.13git+0x20310e)
 #2 0x00007f09b54441bf SignalHandler(int) Signals.cpp:0:0
 #3 0x00007f09b7977630 __restore_rt sigaction.c:0:0
 #4 0x00007f09b7d42cf2 (anonymous namespace)::ExtractValueOpConversion::doRewrite(fir::ExtractValueOp, mlir::Type, llvm::ArrayRef<mlir::Value>, mlir::ConversionPatternRewriter&) const CodeGen.cpp:0:0
 #5 0x00007f09b602aecb mlir::ConversionPattern::matchAndRewrite(mlir::Operation*, mlir::PatternRewriter&) const (/home/ryuta/packages/llvm/flang/build/lib/libMLIRTransformUtils.so.13git+0x1eecb)
 #6 0x00007f09b5fad0ca mlir::PatternApplicator::matchAndRewrite(mlir::Operation*, mlir::PatternRewriter&, llvm::function_ref<bool (mlir::Pattern const&)>, llvm::function_ref<void (mlir::Pattern const&)>, llvm::function_ref<mlir::LogicalResult (mlir::Pattern const&)>) (/home/ryuta/packages/llvm/flang/build/lib/libMLIRRewrite.so.13git+0x220ca)
 #7 0x00007f09b6035ff5 (anonymous namespace)::OperationLegalizer::legalize(mlir::Operation*, mlir::ConversionPatternRewriter&) DialectConversion.cpp:0:0
 #8 0x00007f09b602e863 (anonymous namespace)::OperationConverter::convertOperations(llvm::ArrayRef<mlir::Operation*>) DialectConversion.cpp:0:0
 #9 0x00007f09b6031a61 mlir::applyFullConversion(mlir::Operation*, mlir::ConversionTarget&, mlir::FrozenRewritePatternSet const&) (/home/ryuta/packages/llvm/flang/build/lib/libMLIRTransformUtils.so.13git+0x25a61)
#10 0x00007f09b7d22ec8 (anonymous namespace)::FIRToLLVMLowering::runOnOperation() CodeGen.cpp:0:0
#11 0x00007f09b5eb06da mlir::detail::OpToOpPassAdaptor::run(mlir::Pass*, mlir::Operation*, mlir::AnalysisManager, bool, unsigned int) (/home/ryuta/packages/llvm/flang/build/lib/libMLIRPass.so.13git+0x186da)
#12 0x00007f09b5eb23b8 mlir::PassManager::run(mlir::Operation*) (/home/ryuta/packages/llvm/flang/build/lib/libMLIRPass.so.13git+0x1a3b8)
#13 0x0000000000210ca5 main (/home/ryuta/packages/llvm/flang/build/bin/tco+0x210ca5)
#14 0x00007f09b4a5d555 __libc_start_main (/lib64/libc.so.6+0x22555)
#15 0x000000000020ecf9 _start (/home/ryuta/packages/llvm/flang/build/bin/tco+0x20ecf9)
jeanPerier commented 3 years ago

The FIR generated here is wrong, I think a transformation/optimization pass moved the fir.extract_op positional argument as a block argument of ^bb3 that does not play well with the fact code generation is then trying to get a constant value from the argument.

^bb3(%19: index, %20: index):  // 2 preds: ^bb2, ^bb4
  %21 = fir.load %arg0 : !fir.ref<!fir.complex<8>>
  %22 = fir.extract_value %21, %19 : (!fir.complex<8>, index) -> f64

@oroppas , do you have the original Fortran source to investigate which pass is doing this rewrite and why ?

@schweitzpgi, should ExtractValueOp/InsertValueOp take the positional arguments as attributes instead of values to ensure by construction they are constants and prevent this kind of obfuscation during transformation passes ?

oroppas commented 3 years ago

@jeanPerier

This is the original code lapack-3.9.1/TESTING/EIG/zlctes.f

*> \brief \b ZLCTES
*
*  =========== DOCUMENTATION ===========
*
* Online html documentation available at
*            http://www.netlib.org/lapack/explore-html/
*
*  Definition:
*  ===========
*
*       LOGICAL          FUNCTION ZLCTES( Z, D )
*
*       .. Scalar Arguments ..
*       COMPLEX*16         D, Z
*       ..
*
*
*> \par Purpose:
*  =============
*>
*> \verbatim
*>
*> ZLCTES returns .TRUE. if the eigenvalue Z/D is to be selected
*> (specifically, in this subroutine, if the real part of the
*> eigenvalue is negative), and otherwise it returns .FALSE..
*>
*> It is used by the test routine ZDRGES to test whether the driver
*> routine ZGGES successfully sorts eigenvalues.
*> \endverbatim
*
*  Arguments:
*  ==========
*
*> \param[in] Z
*> \verbatim
*>          Z is COMPLEX*16
*>          The numerator part of a complex eigenvalue Z/D.
*> \endverbatim
*>
*> \param[in] D
*> \verbatim
*>          D is COMPLEX*16
*>          The denominator part of a complex eigenvalue Z/D.
*> \endverbatim
*
*  Authors:
*  ========
*
*> \author Univ. of Tennessee
*> \author Univ. of California Berkeley
*> \author Univ. of Colorado Denver
*> \author NAG Ltd.
*
*> \ingroup complex16_eig
*
*  =====================================================================
      LOGICAL          FUNCTION ZLCTES( Z, D )
*
*  -- LAPACK test routine --
*  -- LAPACK is a software package provided by Univ. of Tennessee,    --
*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
*
*     .. Scalar Arguments ..
      COMPLEX*16         D, Z
*     ..
*
*  =====================================================================
*
*     .. Parameters ..
*
      DOUBLE PRECISION   ZERO, ONE
      PARAMETER          ( ZERO = 0.0D+0, ONE = 1.0D+0 )
      COMPLEX*16         CZERO
      PARAMETER          ( CZERO = ( 0.0D+0, 0.0D+0 ) )
*     ..
*     .. Local Scalars ..
      DOUBLE PRECISION   ZMAX
*     ..
*     .. Intrinsic Functions ..
      INTRINSIC          ABS, DBLE, DIMAG, MAX, SIGN
*     ..
*     .. Executable Statements ..
*
      IF( D.EQ.CZERO ) THEN
         ZLCTES = ( DBLE( Z ).LT.ZERO )
      ELSE
         IF( DBLE( Z ).EQ.ZERO .OR. DBLE( D ).EQ.ZERO ) THEN
            ZLCTES = ( SIGN( ONE, DIMAG( Z ) ).NE.
     $               SIGN( ONE, DIMAG( D ) ) )
         ELSE IF( DIMAG( Z ).EQ.ZERO .OR. DIMAG( D ).EQ.ZERO ) THEN
            ZLCTES = ( SIGN( ONE, DBLE( Z ) ).NE.
     $               SIGN( ONE, DBLE( D ) ) )
         ELSE
            ZMAX = MAX( ABS( DBLE( Z ) ), ABS( DIMAG( Z ) ) )
            ZLCTES = ( ( DBLE( Z ) / ZMAX )*DBLE( D )+
     $               ( DIMAG( Z ) / ZMAX )*DIMAG( D ).LT.ZERO )
         END IF
      END IF
*
      RETURN
*
*     End of ZLCTES
*
      END
schweitzpgi commented 3 years ago

@schweitzpgi, should ExtractValueOp/InsertValueOp take the positional arguments as attributes instead of values to ensure by construction they are constants and prevent this kind of obfuscation during transformation passes ?

Yes, that sounds like the right approach here.

schweitzpgi commented 3 years ago

See #841

schweitzpgi commented 3 years ago

@oroppas Can you try this again and see if the issue is resolved? Thanks.

oroppas commented 3 years ago

Yes, it's resolved. Thanks!