[flang-commits] [flang] d07dc73 - [flang][debug] Support derived types. (#99476)

via flang-commits flang-commits at lists.llvm.org
Tue Aug 27 02:30:54 PDT 2024


Author: Abid Qadeer
Date: 2024-08-27T10:30:49+01:00
New Revision: d07dc73bcfcd4026b956eb08b770ff0c47546b66

URL: https://github.com/llvm/llvm-project/commit/d07dc73bcfcd4026b956eb08b770ff0c47546b66
DIFF: https://github.com/llvm/llvm-project/commit/d07dc73bcfcd4026b956eb08b770ff0c47546b66.diff

LOG: [flang][debug] Support derived types. (#99476)

This PR adds initial debug support for derived type. It handles
`RecordType` and generates appropriate `DICompositeTypeAttr`. The
`TypeInfoOp` is used to get information about the parent and location of
the derived type.

We use `getTypeSizeAndAlignment` to get the size and alignment of the
components of the derived types. This function needed a few changes to
be suitable to be used here:

1. The `getTypeSizeAndAlignment` errored out on unsupported type which
would not work with incremental way we are building debug support. A new
variant of this function has been that returns an std::optional. The original
function has been renamed to `getTypeSizeAndAlignmentOrCrash` as it
will call `TODO()` for unsupported types.

2. The Character type was returning size of just element and not the
whole string which has been fixed.

The testcase checks for offsets of the components which had to be
hardcoded in the test. So the testcase is currently enabled on x86_64.

With this PR in place, this is how the debugging of derived types look
like:

```
type :: t_date
    integer :: year, month, day
  end type

  type :: t_address
    integer :: house_number
  end type
  type, extends(t_address) :: t_person
    character(len=20) name
  end type
  type, extends(t_person)  :: t_employee
    type(t_date) :: hired_date
    real :: monthly_salary
  end type
  type(t_employee) :: employee

(gdb) p employee
$1 = ( t_person = ( t_address = ( house_number = 1 ), name = 'John', ' ' <repeats 16 times> ), hired_date = ( year = 2020, month = 1, day = 20 ), monthly_salary = 3.1400001 )
```

Added: 
    flang/test/Integration/debug-cyclic-derived-type.f90
    flang/test/Transforms/debug-derived-type-1.fir

Modified: 
    flang/include/flang/Optimizer/Dialect/FIRType.h
    flang/lib/Optimizer/CodeGen/Target.cpp
    flang/lib/Optimizer/Dialect/FIRType.cpp
    flang/lib/Optimizer/Transforms/AddDebugInfo.cpp
    flang/lib/Optimizer/Transforms/DebugTypeGenerator.cpp
    flang/lib/Optimizer/Transforms/DebugTypeGenerator.h
    flang/lib/Optimizer/Transforms/LoopVersioning.cpp

Removed: 
    


################################################################################
diff  --git a/flang/include/flang/Optimizer/Dialect/FIRType.h b/flang/include/flang/Optimizer/Dialect/FIRType.h
index 3498a329ced302..68e03eab7268b1 100644
--- a/flang/include/flang/Optimizer/Dialect/FIRType.h
+++ b/flang/include/flang/Optimizer/Dialect/FIRType.h
@@ -487,11 +487,18 @@ std::string getTypeAsString(mlir::Type ty, const KindMapping &kindMap,
 /// target dependent type size inquiries in lowering. It would also not be
 /// straightforward given the need for a kind map that would need to be
 /// converted in terms of mlir::DataLayoutEntryKey.
+
+/// This variant terminates the compilation if an unsupported type is passed.
 std::pair<std::uint64_t, unsigned short>
+getTypeSizeAndAlignmentOrCrash(mlir::Location loc, mlir::Type ty,
+                               const mlir::DataLayout &dl,
+                               const fir::KindMapping &kindMap);
+
+/// This variant returns std::nullopt if an unsupported type is passed.
+std::optional<std::pair<uint64_t, unsigned short>>
 getTypeSizeAndAlignment(mlir::Location loc, mlir::Type ty,
                         const mlir::DataLayout &dl,
                         const fir::KindMapping &kindMap);
-
 } // namespace fir
 
 #endif // FORTRAN_OPTIMIZER_DIALECT_FIRTYPE_H

diff  --git a/flang/lib/Optimizer/CodeGen/Target.cpp b/flang/lib/Optimizer/CodeGen/Target.cpp
index 25141102a8c432..7bc730bff76fe1 100644
--- a/flang/lib/Optimizer/CodeGen/Target.cpp
+++ b/flang/lib/Optimizer/CodeGen/Target.cpp
@@ -431,8 +431,8 @@ struct TargetX86_64 : public GenericTarget<TargetX86_64> {
         return byteOffset;
       }
       mlir::Type compType = component.second;
-      auto [compSize, compAlign] =
-          fir::getTypeSizeAndAlignment(loc, compType, getDataLayout(), kindMap);
+      auto [compSize, compAlign] = fir::getTypeSizeAndAlignmentOrCrash(
+          loc, compType, getDataLayout(), kindMap);
       byteOffset = llvm::alignTo(byteOffset, compAlign);
       ArgClass LoComp, HiComp;
       classify(loc, compType, byteOffset, LoComp, HiComp);
@@ -452,8 +452,8 @@ struct TargetX86_64 : public GenericTarget<TargetX86_64> {
                      ArgClass &Hi) const {
     mlir::Type eleTy = seqTy.getEleTy();
     const std::uint64_t arraySize = seqTy.getConstantArraySize();
-    auto [eleSize, eleAlign] =
-        fir::getTypeSizeAndAlignment(loc, eleTy, getDataLayout(), kindMap);
+    auto [eleSize, eleAlign] = fir::getTypeSizeAndAlignmentOrCrash(
+        loc, eleTy, getDataLayout(), kindMap);
     std::uint64_t eleStorageSize = llvm::alignTo(eleSize, eleAlign);
     for (std::uint64_t i = 0; i < arraySize; ++i) {
       byteOffset = llvm::alignTo(byteOffset, eleAlign);
@@ -641,7 +641,7 @@ struct TargetX86_64 : public GenericTarget<TargetX86_64> {
                                                mlir::Type ty) const {
     CodeGenSpecifics::Marshalling marshal;
     auto sizeAndAlign =
-        fir::getTypeSizeAndAlignment(loc, ty, getDataLayout(), kindMap);
+        fir::getTypeSizeAndAlignmentOrCrash(loc, ty, getDataLayout(), kindMap);
     // The stack is always 8 byte aligned (note 14 in 3.2.3).
     unsigned short align =
         std::max(sizeAndAlign.second, static_cast<unsigned short>(8));

diff  --git a/flang/lib/Optimizer/Dialect/FIRType.cpp b/flang/lib/Optimizer/Dialect/FIRType.cpp
index dbccacfa8be26a..c1debf28d00332 100644
--- a/flang/lib/Optimizer/Dialect/FIRType.cpp
+++ b/flang/lib/Optimizer/Dialect/FIRType.cpp
@@ -1393,43 +1393,50 @@ void FIROpsDialect::registerTypes() {
       OpenACCPointerLikeModel<fir::LLVMPointerType>>(*getContext());
 }
 
-std::pair<std::uint64_t, unsigned short>
+std::optional<std::pair<uint64_t, unsigned short>>
 fir::getTypeSizeAndAlignment(mlir::Location loc, mlir::Type ty,
                              const mlir::DataLayout &dl,
                              const fir::KindMapping &kindMap) {
   if (mlir::isa<mlir::IntegerType, mlir::FloatType, mlir::ComplexType>(ty)) {
     llvm::TypeSize size = dl.getTypeSize(ty);
     unsigned short alignment = dl.getTypeABIAlignment(ty);
-    return {size, alignment};
+    return std::pair{size, alignment};
   }
   if (auto firCmplx = mlir::dyn_cast<fir::ComplexType>(ty)) {
-    auto [floatSize, floatAlign] =
+    auto result =
         getTypeSizeAndAlignment(loc, firCmplx.getEleType(kindMap), dl, kindMap);
-    return {llvm::alignTo(floatSize, floatAlign) + floatSize, floatAlign};
+    if (!result)
+      return result;
+    auto [floatSize, floatAlign] = *result;
+    return std::pair{llvm::alignTo(floatSize, floatAlign) + floatSize,
+                     floatAlign};
   }
   if (auto real = mlir::dyn_cast<fir::RealType>(ty))
     return getTypeSizeAndAlignment(loc, real.getFloatType(kindMap), dl,
                                    kindMap);
 
   if (auto seqTy = mlir::dyn_cast<fir::SequenceType>(ty)) {
-    auto [eleSize, eleAlign] =
-        getTypeSizeAndAlignment(loc, seqTy.getEleTy(), dl, kindMap);
-
+    auto result = getTypeSizeAndAlignment(loc, seqTy.getEleTy(), dl, kindMap);
+    if (!result)
+      return result;
+    auto [eleSize, eleAlign] = *result;
     std::uint64_t size =
         llvm::alignTo(eleSize, eleAlign) * seqTy.getConstantArraySize();
-    return {size, eleAlign};
+    return std::pair{size, eleAlign};
   }
   if (auto recTy = mlir::dyn_cast<fir::RecordType>(ty)) {
     std::uint64_t size = 0;
     unsigned short align = 1;
     for (auto component : recTy.getTypeList()) {
-      auto [compSize, compAlign] =
-          getTypeSizeAndAlignment(loc, component.second, dl, kindMap);
+      auto result = getTypeSizeAndAlignment(loc, component.second, dl, kindMap);
+      if (!result)
+        return result;
+      auto [compSize, compAlign] = *result;
       size =
           llvm::alignTo(size, compAlign) + llvm::alignTo(compSize, compAlign);
       align = std::max(align, compAlign);
     }
-    return {size, align};
+    return std::pair{size, align};
   }
   if (auto logical = mlir::dyn_cast<fir::LogicalType>(ty)) {
     mlir::Type intTy = mlir::IntegerType::get(
@@ -1440,7 +1447,24 @@ fir::getTypeSizeAndAlignment(mlir::Location loc, mlir::Type ty,
     mlir::Type intTy = mlir::IntegerType::get(
         character.getContext(),
         kindMap.getCharacterBitsize(character.getFKind()));
-    return getTypeSizeAndAlignment(loc, intTy, dl, kindMap);
+    auto result = getTypeSizeAndAlignment(loc, intTy, dl, kindMap);
+    if (!result)
+      return result;
+    auto [compSize, compAlign] = *result;
+    if (character.hasConstantLen())
+      compSize *= character.getLen();
+    return std::pair{compSize, compAlign};
   }
-  TODO(loc, "computing size of a component");
+  return std::nullopt;
 }
+
+std::pair<std::uint64_t, unsigned short>
+fir::getTypeSizeAndAlignmentOrCrash(mlir::Location loc, mlir::Type ty,
+                                    const mlir::DataLayout &dl,
+                                    const fir::KindMapping &kindMap) {
+  std::optional<std::pair<uint64_t, unsigned short>> result =
+      getTypeSizeAndAlignment(loc, ty, dl, kindMap);
+  if (result)
+    return *result;
+  TODO(loc, "computing size of a component");
+}
\ No newline at end of file

diff  --git a/flang/lib/Optimizer/Transforms/AddDebugInfo.cpp b/flang/lib/Optimizer/Transforms/AddDebugInfo.cpp
index 30fc4185575e61..fb637684d374a5 100644
--- a/flang/lib/Optimizer/Transforms/AddDebugInfo.cpp
+++ b/flang/lib/Optimizer/Transforms/AddDebugInfo.cpp
@@ -65,20 +65,15 @@ class AddDebugInfoPass : public fir::impl::AddDebugInfoBase<AddDebugInfoPass> {
 
   void handleGlobalOp(fir::GlobalOp glocalOp, mlir::LLVM::DIFileAttr fileAttr,
                       mlir::LLVM::DIScopeAttr scope,
+                      fir::DebugTypeGenerator &typeGen,
                       mlir::SymbolTable *symbolTable,
                       fir::cg::XDeclareOp declOp);
   void handleFuncOp(mlir::func::FuncOp funcOp, mlir::LLVM::DIFileAttr fileAttr,
                     mlir::LLVM::DICompileUnitAttr cuAttr,
+                    fir::DebugTypeGenerator &typeGen,
                     mlir::SymbolTable *symbolTable);
 };
 
-static uint32_t getLineFromLoc(mlir::Location loc) {
-  uint32_t line = 1;
-  if (auto fileLoc = mlir::dyn_cast<mlir::FileLineColLoc>(loc))
-    line = fileLoc.getLine();
-  return line;
-}
-
 bool debugInfoIsAlreadySet(mlir::Location loc) {
   if (mlir::isa<mlir::FusedLoc>(loc)) {
     if (loc->findInstanceOf<mlir::FusedLocWith<fir::LocationKindAttr>>())
@@ -103,7 +98,7 @@ void AddDebugInfoPass::handleDeclareOp(fir::cg::XDeclareOp declOp,
     return;
   // If this DeclareOp actually represents a global then treat it as such.
   if (auto global = symbolTable->lookup<fir::GlobalOp>(declOp.getUniqName())) {
-    handleGlobalOp(global, fileAttr, scopeAttr, symbolTable, declOp);
+    handleGlobalOp(global, fileAttr, scopeAttr, typeGen, symbolTable, declOp);
     return;
   }
 
@@ -160,19 +155,24 @@ mlir::LLVM::DIModuleAttr AddDebugInfoPass::getOrCreateModuleAttr(
 void AddDebugInfoPass::handleGlobalOp(fir::GlobalOp globalOp,
                                       mlir::LLVM::DIFileAttr fileAttr,
                                       mlir::LLVM::DIScopeAttr scope,
+                                      fir::DebugTypeGenerator &typeGen,
                                       mlir::SymbolTable *symbolTable,
                                       fir::cg::XDeclareOp declOp) {
   if (debugInfoIsAlreadySet(globalOp.getLoc()))
     return;
-  mlir::ModuleOp module = getOperation();
   mlir::MLIRContext *context = &getContext();
-  fir::DebugTypeGenerator typeGen(module);
   mlir::OpBuilder builder(context);
 
   std::pair result = fir::NameUniquer::deconstruct(globalOp.getSymName());
   if (result.first != fir::NameUniquer::NameKind::VARIABLE)
     return;
 
+  // Discard entries that describe a derived type. Usually start with '.c.',
+  // '.dt.' or '.n.'. It would be better if result of the deconstruct had a flag
+  // for such values so that we dont have to look at string values.
+  if (!result.second.name.empty() && result.second.name[0] == '.')
+    return;
+
   unsigned line = getLineFromLoc(globalOp.getLoc());
 
   // DWARF5 says following about the fortran modules:
@@ -214,6 +214,7 @@ void AddDebugInfoPass::handleGlobalOp(fir::GlobalOp globalOp,
 void AddDebugInfoPass::handleFuncOp(mlir::func::FuncOp funcOp,
                                     mlir::LLVM::DIFileAttr fileAttr,
                                     mlir::LLVM::DICompileUnitAttr cuAttr,
+                                    fir::DebugTypeGenerator &typeGen,
                                     mlir::SymbolTable *symbolTable) {
   mlir::Location l = funcOp->getLoc();
   // If fused location has already been created then nothing to do
@@ -221,7 +222,6 @@ void AddDebugInfoPass::handleFuncOp(mlir::func::FuncOp funcOp,
   if (debugInfoIsAlreadySet(l))
     return;
 
-  mlir::ModuleOp module = getOperation();
   mlir::MLIRContext *context = &getContext();
   mlir::OpBuilder builder(context);
   llvm::StringRef fileName(fileAttr.getName());
@@ -245,7 +245,6 @@ void AddDebugInfoPass::handleFuncOp(mlir::func::FuncOp funcOp,
   funcName = mlir::StringAttr::get(context, result.second.name);
 
   llvm::SmallVector<mlir::LLVM::DITypeAttr> types;
-  fir::DebugTypeGenerator typeGen(module);
   for (auto resTy : funcOp.getResultTypes()) {
     auto tyAttr =
         typeGen.convertType(resTy, fileAttr, cuAttr, /*declOp=*/nullptr);
@@ -285,7 +284,7 @@ void AddDebugInfoPass::handleFuncOp(mlir::func::FuncOp funcOp,
       if (auto func =
               symbolTable->lookup<mlir::func::FuncOp>(sym.getLeafReference())) {
         // Make sure that parent is processed.
-        handleFuncOp(func, fileAttr, cuAttr, symbolTable);
+        handleFuncOp(func, fileAttr, cuAttr, typeGen, symbolTable);
         if (auto fusedLoc =
                 mlir::dyn_cast_if_present<mlir::FusedLoc>(func.getLoc())) {
           if (auto spAttr =
@@ -320,6 +319,14 @@ void AddDebugInfoPass::runOnOperation() {
   mlir::SymbolTable symbolTable(module);
   llvm::StringRef fileName;
   std::string filePath;
+  std::optional<mlir::DataLayout> dl =
+      fir::support::getOrSetDataLayout(module, /*allowDefaultLayout=*/true);
+  if (!dl) {
+    mlir::emitError(module.getLoc(), "Missing data layout attribute in module");
+    signalPassFailure();
+    return;
+  }
+  fir::DebugTypeGenerator typeGen(module, &symbolTable, *dl);
   // We need 2 type of file paths here.
   // 1. Name of the file as was presented to compiler. This can be absolute
   // or relative to 2.
@@ -354,13 +361,13 @@ void AddDebugInfoPass::runOnOperation() {
       isOptimized, debugLevel);
 
   module.walk([&](mlir::func::FuncOp funcOp) {
-    handleFuncOp(funcOp, fileAttr, cuAttr, &symbolTable);
+    handleFuncOp(funcOp, fileAttr, cuAttr, typeGen, &symbolTable);
   });
   // Process any global which was not processed through DeclareOp.
   if (debugLevel == mlir::LLVM::DIEmissionKind::Full) {
     // Process 'GlobalOp' only if full debug info is requested.
     for (auto globalOp : module.getOps<fir::GlobalOp>())
-      handleGlobalOp(globalOp, fileAttr, cuAttr, &symbolTable,
+      handleGlobalOp(globalOp, fileAttr, cuAttr, typeGen, &symbolTable,
                      /*declOp=*/nullptr);
   }
 }

diff  --git a/flang/lib/Optimizer/Transforms/DebugTypeGenerator.cpp b/flang/lib/Optimizer/Transforms/DebugTypeGenerator.cpp
index 860c16c9a13ce9..54f2a12d800085 100644
--- a/flang/lib/Optimizer/Transforms/DebugTypeGenerator.cpp
+++ b/flang/lib/Optimizer/Transforms/DebugTypeGenerator.cpp
@@ -15,7 +15,7 @@
 #include "DebugTypeGenerator.h"
 #include "flang/Optimizer/CodeGen/DescriptorModel.h"
 #include "flang/Optimizer/CodeGen/TypeConverter.h"
-#include "flang/Optimizer/Support/DataLayout.h"
+#include "flang/Optimizer/Support/InternalNames.h"
 #include "mlir/Pass/Pass.h"
 #include "llvm/ADT/ScopeExit.h"
 #include "llvm/BinaryFormat/Dwarf.h"
@@ -44,17 +44,13 @@ std::uint64_t getComponentOffset<0>(const mlir::DataLayout &dl,
   return 0;
 }
 
-DebugTypeGenerator::DebugTypeGenerator(mlir::ModuleOp m)
-    : module(m), kindMapping(getKindMapping(m)) {
+DebugTypeGenerator::DebugTypeGenerator(mlir::ModuleOp m,
+                                       mlir::SymbolTable *symbolTable_,
+                                       const mlir::DataLayout &dl)
+    : module(m), symbolTable(symbolTable_), dataLayout{&dl},
+      kindMapping(getKindMapping(m)) {
   LLVM_DEBUG(llvm::dbgs() << "DITypeAttr generator\n");
 
-  std::optional<mlir::DataLayout> dl =
-      fir::support::getOrSetDataLayout(module, /*allowDefaultLayout=*/true);
-  if (!dl) {
-    mlir::emitError(module.getLoc(), "Missing data layout attribute in module");
-    return;
-  }
-
   mlir::MLIRContext *context = module.getContext();
 
   // The debug information requires the offset of certain fields in the
@@ -62,10 +58,12 @@ DebugTypeGenerator::DebugTypeGenerator(mlir::ModuleOp m)
   mlir::Type llvmDimsType = getDescFieldTypeModel<kDimsPosInBox>()(context);
   mlir::Type llvmPtrType = getDescFieldTypeModel<kAddrPosInBox>()(context);
   mlir::Type llvmLenType = getDescFieldTypeModel<kElemLenPosInBox>()(context);
-  dimsOffset = getComponentOffset<kDimsPosInBox>(*dl, context, llvmDimsType);
-  dimsSize = dl->getTypeSize(llvmDimsType);
-  ptrSize = dl->getTypeSize(llvmPtrType);
-  lenOffset = getComponentOffset<kElemLenPosInBox>(*dl, context, llvmLenType);
+  dimsOffset =
+      getComponentOffset<kDimsPosInBox>(*dataLayout, context, llvmDimsType);
+  dimsSize = dataLayout->getTypeSize(llvmDimsType);
+  ptrSize = dataLayout->getTypeSize(llvmPtrType);
+  lenOffset =
+      getComponentOffset<kElemLenPosInBox>(*dataLayout, context, llvmLenType);
 }
 
 static mlir::LLVM::DITypeAttr genBasicType(mlir::MLIRContext *context,
@@ -154,6 +152,49 @@ mlir::LLVM::DITypeAttr DebugTypeGenerator::convertBoxedSequenceType(
       dataLocation, /*rank=*/nullptr, allocated, associated);
 }
 
+mlir::LLVM::DITypeAttr DebugTypeGenerator::convertRecordType(
+    fir::RecordType Ty, mlir::LLVM::DIFileAttr fileAttr,
+    mlir::LLVM::DIScopeAttr scope, fir::cg::XDeclareOp declOp) {
+  mlir::MLIRContext *context = module.getContext();
+  auto result = fir::NameUniquer::deconstruct(Ty.getName());
+  if (result.first != fir::NameUniquer::NameKind::DERIVED_TYPE)
+    return genPlaceholderType(context);
+
+  fir::TypeInfoOp tiOp = symbolTable->lookup<fir::TypeInfoOp>(Ty.getName());
+  unsigned line = (tiOp) ? getLineFromLoc(tiOp.getLoc()) : 1;
+
+  llvm::SmallVector<mlir::LLVM::DINodeAttr> elements;
+  std::uint64_t offset = 0;
+  for (auto [fieldName, fieldTy] : Ty.getTypeList()) {
+    auto result = fir::getTypeSizeAndAlignment(module.getLoc(), fieldTy,
+                                               *dataLayout, kindMapping);
+    // If we get a type whose size we can't determine, we will break the loop
+    // and generate the derived type with whatever components we have
+    // assembled thus far.
+    if (!result)
+      break;
+    auto [byteSize, byteAlign] = *result;
+    // FIXME: Handle non defaults array bound in derived types
+    mlir::LLVM::DITypeAttr elemTy =
+        convertType(fieldTy, fileAttr, scope, /*declOp=*/nullptr);
+    offset = llvm::alignTo(offset, byteAlign);
+    mlir::LLVM::DIDerivedTypeAttr tyAttr = mlir::LLVM::DIDerivedTypeAttr::get(
+        context, llvm::dwarf::DW_TAG_member,
+        mlir::StringAttr::get(context, fieldName), elemTy, byteSize * 8,
+        byteAlign * 8, offset * 8, /*optional<address space>=*/std::nullopt,
+        /*extra data=*/nullptr);
+    elements.push_back(tyAttr);
+    offset += llvm::alignTo(byteSize, byteAlign);
+  }
+
+  return mlir::LLVM::DICompositeTypeAttr::get(
+      context, llvm::dwarf::DW_TAG_structure_type, /*recursive_id=*/{},
+      mlir::StringAttr::get(context, result.second.name), fileAttr, line, scope,
+      /*baseType=*/nullptr, mlir::LLVM::DIFlags::Zero, offset * 8,
+      /*alignInBits=*/0, elements, /*dataLocation=*/nullptr, /*rank=*/nullptr,
+      /*allocated=*/nullptr, /*associated=*/nullptr);
+}
+
 mlir::LLVM::DITypeAttr DebugTypeGenerator::convertSequenceType(
     fir::SequenceType seqTy, mlir::LLVM::DIFileAttr fileAttr,
     mlir::LLVM::DIScopeAttr scope, fir::cg::XDeclareOp declOp) {
@@ -312,6 +353,8 @@ DebugTypeGenerator::convertType(mlir::Type Ty, mlir::LLVM::DIFileAttr fileAttr,
   } else if (auto charTy = mlir::dyn_cast_or_null<fir::CharacterType>(Ty)) {
     return convertCharacterType(charTy, fileAttr, scope, declOp,
                                 /*hasDescriptor=*/false);
+  } else if (auto recTy = mlir::dyn_cast_or_null<fir::RecordType>(Ty)) {
+    return convertRecordType(recTy, fileAttr, scope, declOp);
   } else if (auto boxTy = mlir::dyn_cast_or_null<fir::BoxType>(Ty)) {
     auto elTy = boxTy.getElementType();
     if (auto seqTy = mlir::dyn_cast_or_null<fir::SequenceType>(elTy))

diff  --git a/flang/lib/Optimizer/Transforms/DebugTypeGenerator.h b/flang/lib/Optimizer/Transforms/DebugTypeGenerator.h
index 5ab6ca5e9f880e..e3220f18958df2 100644
--- a/flang/lib/Optimizer/Transforms/DebugTypeGenerator.h
+++ b/flang/lib/Optimizer/Transforms/DebugTypeGenerator.h
@@ -17,6 +17,7 @@
 #include "flang/Optimizer/Dialect/FIRType.h"
 #include "flang/Optimizer/Dialect/Support/FIRContext.h"
 #include "flang/Optimizer/Dialect/Support/KindMapping.h"
+#include "flang/Optimizer/Support/DataLayout.h"
 #include "llvm/Support/Debug.h"
 
 namespace fir {
@@ -24,7 +25,8 @@ namespace fir {
 /// This converts FIR/mlir type to DITypeAttr.
 class DebugTypeGenerator {
 public:
-  DebugTypeGenerator(mlir::ModuleOp module);
+  DebugTypeGenerator(mlir::ModuleOp module, mlir::SymbolTable *symbolTable,
+                     const mlir::DataLayout &dl);
 
   mlir::LLVM::DITypeAttr convertType(mlir::Type Ty,
                                      mlir::LLVM::DIFileAttr fileAttr,
@@ -32,6 +34,10 @@ class DebugTypeGenerator {
                                      fir::cg::XDeclareOp declOp);
 
 private:
+  mlir::LLVM::DITypeAttr convertRecordType(fir::RecordType Ty,
+                                           mlir::LLVM::DIFileAttr fileAttr,
+                                           mlir::LLVM::DIScopeAttr scope,
+                                           fir::cg::XDeclareOp declOp);
   mlir::LLVM::DITypeAttr convertSequenceType(fir::SequenceType seqTy,
                                              mlir::LLVM::DIFileAttr fileAttr,
                                              mlir::LLVM::DIScopeAttr scope,
@@ -59,6 +65,8 @@ class DebugTypeGenerator {
                                                 bool genAssociated);
 
   mlir::ModuleOp module;
+  mlir::SymbolTable *symbolTable;
+  const mlir::DataLayout *dataLayout;
   KindMapping kindMapping;
   std::uint64_t dimsSize;
   std::uint64_t dimsOffset;
@@ -68,4 +76,11 @@ class DebugTypeGenerator {
 
 } // namespace fir
 
+static uint32_t getLineFromLoc(mlir::Location loc) {
+  uint32_t line = 1;
+  if (auto fileLoc = mlir::dyn_cast<mlir::FileLineColLoc>(loc))
+    line = fileLoc.getLine();
+  return line;
+}
+
 #endif // FORTRAN_OPTIMIZER_TRANSFORMS_DEBUGTYPEGENERATOR_H

diff  --git a/flang/lib/Optimizer/Transforms/LoopVersioning.cpp b/flang/lib/Optimizer/Transforms/LoopVersioning.cpp
index 38cdc2b1388d40..51dc48f0fcb129 100644
--- a/flang/lib/Optimizer/Transforms/LoopVersioning.cpp
+++ b/flang/lib/Optimizer/Transforms/LoopVersioning.cpp
@@ -266,7 +266,7 @@ void LoopVersioningPass::runOnOperation() {
         if (mlir::isa<mlir::FloatType>(elementType) ||
             mlir::isa<mlir::IntegerType>(elementType) ||
             mlir::isa<fir::ComplexType>(elementType)) {
-          auto [eleSize, eleAlign] = fir::getTypeSizeAndAlignment(
+          auto [eleSize, eleAlign] = fir::getTypeSizeAndAlignmentOrCrash(
               arg.getLoc(), elementType, *dl, kindMap);
           typeSize = llvm::alignTo(eleSize, eleAlign);
         }

diff  --git a/flang/test/Integration/debug-cyclic-derived-type.f90 b/flang/test/Integration/debug-cyclic-derived-type.f90
new file mode 100644
index 00000000000000..03e06336a6e084
--- /dev/null
+++ b/flang/test/Integration/debug-cyclic-derived-type.f90
@@ -0,0 +1,15 @@
+! RUN: %flang_fc1 -emit-llvm -debug-info-kind=standalone %s -o - | FileCheck  %s
+
+module m
+ type t1
+   type(t2), pointer :: p
+ end type
+ type t2
+   type(t1) :: v1
+ end type
+ type(t1) :: v2
+ type(t2) :: v3
+end module
+
+! CHECK-DAG: !DICompositeType(tag: DW_TAG_structure_type, name: "t1"{{.*}})
+! CHECK-DAG: !DICompositeType(tag: DW_TAG_structure_type, name: "t2"{{.*}})

diff  --git a/flang/test/Transforms/debug-derived-type-1.fir b/flang/test/Transforms/debug-derived-type-1.fir
new file mode 100644
index 00000000000000..e453db6ae6fbb7
--- /dev/null
+++ b/flang/test/Transforms/debug-derived-type-1.fir
@@ -0,0 +1,73 @@
+// RUN: fir-opt --add-debug-info --mlir-print-debuginfo %s | FileCheck %s
+
+// Only enabled on x86_64
+// REQUIRES: x86-registered-target
+
+module attributes {dlti.dl_spec = #dlti.dl_spec<#dlti.dl_entry<!llvm.ptr<272>, dense<64> : vector<4xi64>>, #dlti.dl_entry<!llvm.ptr<271>, dense<32> : vector<4xi64>>, #dlti.dl_entry<!llvm.ptr<270>, dense<32> : vector<4xi64>>, #dlti.dl_entry<f64, dense<64> : vector<2xi64>>, #dlti.dl_entry<f80, dense<128> : vector<2xi64>>, #dlti.dl_entry<f128, dense<128> : vector<2xi64>>, #dlti.dl_entry<i128, dense<128> : vector<2xi64>>, #dlti.dl_entry<i64, dense<64> : vector<2xi64>>, #dlti.dl_entry<i16, dense<16> : vector<2xi64>>, #dlti.dl_entry<i32, dense<32> : vector<2xi64>>, #dlti.dl_entry<f16, dense<16> : vector<2xi64>>, #dlti.dl_entry<!llvm.ptr, dense<64> : vector<4xi64>>, #dlti.dl_entry<i1, dense<8> : vector<2xi64>>, #dlti.dl_entry<i8, dense<8> : vector<2xi64>>, #dlti.dl_entry<"dlti.stack_alignment", 128 : i64>, #dlti.dl_entry<"dlti.endianness", "little">>, fir.defaultkind = "a1c4d8i4l4r4", fir.kindmap = "", llvm.data_layout = "e-m:e-p270:32:32-p271:32:32-p272:64:64-i64:64-i128:128-f80:128-n8:16:32:64-S128", llvm.target_triple = "x86_64-unknown-linux-gnu", omp.is_gpu = false, omp.is_target_device = false, omp.version = #omp.version<version = 11>} {
+  fir.global @_QMm_employeeEemployee : !fir.type<_QMm_employeeTt_employee{t_person:!fir.type<_QMm_employeeTt_person{t_address:!fir.type<_QMm_employeeTt_address{house_number:i32}>,name:!fir.char<1,20>}>,hired_date:!fir.type<_QMm_employeeTt_date{year:i32,month:i32,day:i32}>,monthly_salary:f32}> {
+    %0 = fir.zero_bits !fir.type<_QMm_employeeTt_employee{t_person:!fir.type<_QMm_employeeTt_person{t_address:!fir.type<_QMm_employeeTt_address{house_number:i32}>,name:!fir.char<1,20>}>,hired_date:!fir.type<_QMm_employeeTt_date{year:i32,month:i32,day:i32}>,monthly_salary:f32}>
+    fir.has_value %0 : !fir.type<_QMm_employeeTt_employee{t_person:!fir.type<_QMm_employeeTt_person{t_address:!fir.type<_QMm_employeeTt_address{house_number:i32}>,name:!fir.char<1,20>}>,hired_date:!fir.type<_QMm_employeeTt_date{year:i32,month:i32,day:i32}>,monthly_salary:f32}>
+  } loc(#loc5)
+  fir.global @_QMt1Evar : !fir.type<_QMt1Tt_t1{age:i32,points:!fir.array<3x!fir.complex<4>>,cond:!fir.logical<1>,name:!fir.char<1,20>,ratio:f64}> {
+    %0 = fir.zero_bits !fir.type<_QMt1Tt_t1{age:i32,points:!fir.array<3x!fir.complex<4>>,cond:!fir.logical<1>,name:!fir.char<1,20>,ratio:f64}>
+    fir.has_value %0 : !fir.type<_QMt1Tt_t1{age:i32,points:!fir.array<3x!fir.complex<4>>,cond:!fir.logical<1>,name:!fir.char<1,20>,ratio:f64}>
+  } loc(#loc6)
+  fir.type_info @_QMt1Tt_t1 noinit nodestroy nofinal : !fir.type<_QMt1Tt_t1{age:i32,points:!fir.array<3x!fir.complex<4>>,cond:!fir.logical<1>,name:!fir.char<1,20>,ratio:f64}> loc(#loc7)
+  fir.type_info @_QMm_employeeTt_address noinit nodestroy nofinal : !fir.type<_QMm_employeeTt_address{house_number:i32}> loc(#loc1)
+  fir.type_info @_QMm_employeeTt_person noinit nodestroy nofinal extends !fir.type<_QMm_employeeTt_address{house_number:i32}> : !fir.type<_QMm_employeeTt_person{t_address:!fir.type<_QMm_employeeTt_address{house_number:i32}>,name:!fir.char<1,20>}> loc(#loc2)
+  fir.type_info @_QMm_employeeTt_date noinit nodestroy nofinal : !fir.type<_QMm_employeeTt_date{year:i32,month:i32,day:i32}> loc(#loc3)
+  fir.type_info @_QMm_employeeTt_employee noinit nodestroy nofinal extends !fir.type<_QMm_employeeTt_person{t_address:!fir.type<_QMm_employeeTt_address{house_number:i32}>,name:!fir.char<1,20>}> : !fir.type<_QMm_employeeTt_employee{t_person:!fir.type<_QMm_employeeTt_person{t_address:!fir.type<_QMm_employeeTt_address{house_number:i32}>,name:!fir.char<1,20>}>,hired_date:!fir.type<_QMm_employeeTt_date{year:i32,month:i32,day:i32}>,monthly_salary:f32}> loc(#loc4)
+  fir.type_info @_QFTt_pair noinit nodestroy nofinal : !fir.type<_QFTt_pair{i:i64,x:f64}> loc(#loc8)
+  func.func @_QQmain() attributes {fir.bindc_name = "test"} {
+    %1 = fir.alloca !fir.type<_QFTt_pair{i:i64,x:f64}> {bindc_name = "pair", uniq_name = "_QFEpair"}
+    %2 = fircg.ext_declare %1 {uniq_name = "_QFEpair"} : (!fir.ref<!fir.type<_QFTt_pair{i:i64,x:f64}>>) -> !fir.ref<!fir.type<_QFTt_pair{i:i64,x:f64}>> loc(#loc9)
+    return
+  } loc(#loc10)
+}
+#loc1 = loc("derived1.f90":24:1)
+#loc2 = loc("derived1.f90":35:25)
+#loc3 = loc("derived1.f90":17:1)
+#loc4 = loc("derived1.f90":46:1)
+#loc5 = loc("derived1.f90":50:3)
+#loc6 = loc("derived1.f90":62:3)
+#loc7 = loc("derived1.f90":70:3)
+#loc8 = loc("derived1.f90":85:3)
+#loc9 = loc("derived1.f90":77:3)
+#loc10 = loc("derived1.f90":75:3)
+
+
+// CHECK-DAG: #[[INT_TY:.*]] = #llvm.di_basic_type<tag = DW_TAG_base_type, name = "integer", sizeInBits = 32, encoding = DW_ATE_signed>
+// CHECK-DAG: #[[INT8_TY:.*]] = #llvm.di_basic_type<tag = DW_TAG_base_type, name = "integer", sizeInBits = 64, encoding = DW_ATE_signed>
+// CHECK-DAG: #[[REAL4_TY:.*]] = #llvm.di_basic_type<tag = DW_TAG_base_type, name = "real", sizeInBits = 32, encoding = DW_ATE_float>
+// CHECK-DAG: #[[CMX8_TY:.*]] = #llvm.di_basic_type<tag = DW_TAG_base_type, name = "complex", sizeInBits = 64, encoding = DW_ATE_complex_float>
+// CHECK-DAG: #[[CMX_ARR:.*]] = #llvm.di_composite_type<tag = DW_TAG_array_type, baseType = #[[CMX8_TY:.*]]{{.*}}>
+// CHECK-DAG: #[[LOG_TY:.*]] = #llvm.di_basic_type<tag = DW_TAG_base_type, name = "logical", sizeInBits = 8, encoding = DW_ATE_boolean>
+// CHECK-DAG: #[[REAL8_TY:.*]] = #llvm.di_basic_type<tag = DW_TAG_base_type, name = "real", sizeInBits = 64, encoding = DW_ATE_float>
+// CHECK-DAG: #[[STR_TY:.*]] = #llvm.di_string_type
+// CHECK-DAG: #[[MOD:.*]] = #llvm.di_module<{{.*}}name = "m_employee"{{.*}}>
+// CHECK-DAG: #[[MOD1:.*]] = #llvm.di_module<{{.*}}name = "t1"{{.*}}>
+// CHECK-DAG: #[[ELMA1:.*]] = #llvm.di_derived_type<tag = DW_TAG_member, name = "house_number", baseType = #[[INT_TY]], sizeInBits = 32, alignInBits = 32>
+// CHECK-DAG: #[[ADDR:.*]] = #llvm.di_composite_type<tag = DW_TAG_structure_type, name = "t_address"{{.*}}line = 24, scope = #[[MOD]], sizeInBits = 32, elements = #[[ELMA1]]>
+// CHECK-DAG: #[[ELMD1:.*]] = #llvm.di_derived_type<tag = DW_TAG_member, name = "year", baseType = #[[INT_TY]], sizeInBits = 32, alignInBits = 32>
+// CHECK-DAG: #[[ELMD2:.*]] = #llvm.di_derived_type<tag = DW_TAG_member, name = "month", baseType = #[[INT_TY]], sizeInBits = 32, alignInBits = 32, offsetInBits = 32>
+// CHECK-DAG: #[[ELMD3:.*]] = #llvm.di_derived_type<tag = DW_TAG_member, name = "day", baseType = #[[INT_TY]], sizeInBits = 32, alignInBits = 32, offsetInBits = 64>
+// CHECK-DAG: #[[DATE:.*]] = #llvm.di_composite_type<tag = DW_TAG_structure_type, name = "t_date", file = #di_file, line = 17, scope = #[[MOD]], sizeInBits = 96, elements = #[[ELMD1]], #[[ELMD2]], #[[ELMD3]]>
+// CHECK-DAG: #[[ELMP1:.*]] = #llvm.di_derived_type<tag = DW_TAG_member, name = "t_address", baseType = #[[ADDR]], sizeInBits = 32, alignInBits = 32>
+// CHECK-DAG: #[[ELMP2:.*]] = #llvm.di_derived_type<tag = DW_TAG_member, name = "name", baseType = #[[STR_TY]], sizeInBits = 160, alignInBits = 8, offsetInBits = 32>
+// CHECK-DAG: #[[PERS:.*]] = #llvm.di_composite_type<tag = DW_TAG_structure_type, name = "t_person"{{.*}}line = 35, scope = #[[MOD]], sizeInBits = 192, elements = #[[ELMP1]], #[[ELMP2]]>
+// CHECK-DAG: #[[ELME1:.*]] = #llvm.di_derived_type<tag = DW_TAG_member, name = "t_person", baseType = #[[PERS]], sizeInBits = 192, alignInBits = 32>
+// CHECK-DAG: #[[ELME2:.*]] = #llvm.di_derived_type<tag = DW_TAG_member, name = "hired_date", baseType = #[[DATE]], sizeInBits = 96, alignInBits = 32, offsetInBits = 192>
+// CHECK-DAG: #[[ELME3:.*]] = #llvm.di_derived_type<tag = DW_TAG_member, name = "monthly_salary", baseType = #[[REAL4_TY]], sizeInBits = 32, alignInBits = 32, offsetInBits = 288>
+// CHECK-DAG: #[[EMP:.*]] = #llvm.di_composite_type<tag = DW_TAG_structure_type, name = "t_employee"{{.*}}line = 46, scope = #[[MOD]], sizeInBits = 320, elements = #[[ELME1]], #[[ELME2]], #[[ELME3]]>
+
+// CHECK-DAG: #[[ELM1:.*]] = #llvm.di_derived_type<tag = DW_TAG_member, name = "age", baseType = #[[INT_TY]], sizeInBits = 32, alignInBits = 32>
+// CHECK-DAG: #[[ELM2:.*]] = #llvm.di_derived_type<tag = DW_TAG_member, name = "points", baseType = #[[CMX_ARR]], sizeInBits = 192, alignInBits = 32, offsetInBits = 32>
+// CHECK-DAG: #[[ELM3:.*]] = #llvm.di_derived_type<tag = DW_TAG_member, name = "cond", baseType = #[[LOG_TY]], sizeInBits = 8, alignInBits = 8, offsetInBits = 224>
+// CHECK-DAG: #[[ELM4:.*]] = #llvm.di_derived_type<tag = DW_TAG_member, name = "name", baseType = #[[STR_TY]], sizeInBits = 160, alignInBits = 8, offsetInBits = 232>
+// CHECK-DAG: #[[ELM5:.*]] = #llvm.di_derived_type<tag = DW_TAG_member, name = "ratio", baseType = #[[REAL8_TY]], sizeInBits = 64, alignInBits = 64, offsetInBits = 448>
+// CHECK-DAG: #llvm.di_composite_type<tag = DW_TAG_structure_type, name = "t_t1"{{.*}}, line = 70, scope = #[[MOD1]], sizeInBits = 512, elements = #[[ELM1]], #[[ELM2]], #[[ELM3]], #[[ELM4]], #[[ELM5]]>
+
+// CHECK-DAG: #[[SP:.*]] = #llvm.di_subprogram
+// CHECK-DAG: #[[ELML1:.*]] = #llvm.di_derived_type<tag = DW_TAG_member, name = "i", baseType = #[[INT8_TY]], sizeInBits = 64, alignInBits = 64>
+// CHECK-DAG: #[[ELML2:.*]] = #llvm.di_derived_type<tag = DW_TAG_member, name = "x", baseType = #[[REAL8_TY]], sizeInBits = 64, alignInBits = 64, offsetInBits = 64>
+// CHECK-DAG: #llvm.di_composite_type<tag = DW_TAG_structure_type, name = "t_pair"{{.*}}line = 85, scope = #di_subprogram, sizeInBits = 128, elements = #[[ELML1]], #[[ELML2]]>


        


More information about the flang-commits mailing list