Variables not visible in debugger with the classic Intel compiler

Hello,

The Intel compiler has been our official for decades on x86, but I also have been struggling for years when debugging codes that use modern Fortran construct: many variables are not visible in the debugger when using BLOCK constructs, contained procedures, etc… See for instance this MRE, compiled with IFORT 21 (on Linux, with the options -g -O0) and debugged under DDT:

module foo

contains

	subroutine foo1()
		integer :: i
		i = 1   ! DDT does show the variable “i” here
		print*, i
	end subroutine foo1

	subroutine foo2()
		integer :: i
		i = 1   ! DDT doesn't show the variable “i” here
		call foo3()
	contains
		 subroutine foo3()
			print*, i   ! DDT doesn’t show the variable “i” here
		end subroutine foo3
	end subroutine foo2

	subroutine foo4()
		integer :: i
		i = 1   ! DDT doesn’t show the variable “i” here
		BLOCK
			integer :: j
			j = 0       ! DDT doe show the variable “j” here
			print*, i   ! DDT doesn’t show the variable “i” here
		END BLOCK
	end subroutine foo4

end module

program main
use foo

call foo1()
call foo2()
call foo4()

end

I submitted the issue to Linaro (the editor of DDT), and they confirmed that the issue comes from the compiler and not from the debugger: IFORT doesn’t generate all the needed debug information. They tried with the latest IFX compiler and most of the variables were visible (except one of them, and they reported the case to Intel).

IFORT is no longer maintained, so there’s no hope to have this fixed, but is there a compiler option (or a combination of options) that could force to the compiler to generate the missing debug information ?

1 Like

It might be that even with -O0 the symbol is optimized away and replaced with an unnamed constant 1 in the print statement, and the other variable that is never used just disappears. You might try looking at either the intermediate code or the assembler code to see. This is always a problem when debugging a high level language.

ifort and ifx have -debug all and -debug-parameters all (which seems to be the same as -debug-parameters used).

With those options, on Linux, most DWARF-4-compatible information is generated. Otherwise, only minimal information is generated.

ifort has more -debug <keyword> options available (e.g., -debug extended), but those didn’t make it to ifx.

1 Like

Thanks, but unfortunately it doesn’t make it…

Then maybe the issue is with the other tool and not with ifort? I noticed that, if a variable is declared but never used, then ifort doesn’t generate a DW_AT_location for it.

For the following code

module mod1
    implicit none
    private

    public proc
contains
    subroutine proc(res)
        integer, intent(out) :: res
        real :: dummy_at_proc
        print*,dummy_at_proc

        block
            integer :: a, b
            real :: dummy_at_block
            print*,dummy_at_block
            a = 1
            b = 2
            call subproc(res, a, b)
        end block

    contains
        subroutine subproc(z, x, y)
            integer, intent(out) :: z
            integer, intent(in) :: x, y
            real :: dummy_at_subproc
            print*,dummy_at_subproc
            z = x + y
        end subroutine
    end subroutine
end module mod1

use mod1

implicit none

integer :: i
real :: dummy_at_main

print*,dummy_at_main

call proc(i)
print*, 'i=',i
end

ifort generates all DW_AT_location blocks —I added print statements for the dummy_* variables to ensure that.


.debug_info

COMPILE_UNIT<header overall offset = 0x00000000>:
< 0><0x0000000b>  DW_TAG_compile_unit
                    DW_AT_comp_dir              /home/jwm/tests/charptr
                    DW_AT_name                  debug-visible.f90
                    DW_AT_producer              Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.13.1 Build 20240703_000000

                    <Unknown AT value 0x3b01>   -diag-disable=10448 -g -O0 -debug all -debug-parameters all -o debug-visible 
                    DW_AT_language              DW_LANG_Fortran95
                    DW_AT_use_UTF8              yes(1)
                    DW_AT_low_pc                0x00404178
                    DW_AT_high_pc               <offset-from-lowpc> 614 <highpc: 0x004043de>
                    DW_AT_main_subprogram       yes(1)
                    DW_AT_stmt_list             0x00000000

LOCAL_SYMBOLS:
< 1><0x00000033>    DW_TAG_module
                      DW_AT_decl_line             0x00000001
                      DW_AT_decl_file             0x00000001 /home/jwm/tests/charptr/debug-visible.f90
                      DW_AT_name                  mod1
< 2><0x0000003a>      DW_TAG_subprogram
                        DW_AT_decl_line             0x00000006
                        DW_AT_decl_file             0x00000001 /home/jwm/tests/charptr/debug-visible.f90
                        DW_AT_name                  MOD1
                        DW_AT_low_pc                0x00404178
                        DW_AT_high_pc               <offset-from-lowpc> 6 <highpc: 0x0040417e>
                        DW_AT_external              yes(1)
< 2><0x00000052>      DW_TAG_subprogram
                        DW_AT_decl_line             0x00000007
                        DW_AT_decl_file             0x00000001 /home/jwm/tests/charptr/debug-visible.f90
                        DW_AT_name                  proc
                        DW_AT_frame_base            len 0x0002: 0x7600: 
                            DW_OP_breg6+0
                        DW_AT_low_pc                0x0040417e
                        DW_AT_high_pc               <offset-from-lowpc> 232 <highpc: 0x00404266>
                        DW_AT_external              yes(1)
< 3><0x0000006d>        DW_TAG_formal_parameter
                          DW_AT_decl_line             0x00000007
                          DW_AT_decl_file             0x00000001 /home/jwm/tests/charptr/debug-visible.f90
                          DW_AT_type                  <0x00000120> Refers to: INTEGER(4)
                          DW_AT_name                  res
                          DW_AT_location              len 0x0004: 0x76907f06: 
                              DW_OP_breg6-112
                              DW_OP_deref
< 3><0x0000007d>        DW_TAG_variable
                          DW_AT_decl_line             0x00000009
                          DW_AT_decl_file             0x00000001 /home/jwm/tests/charptr/debug-visible.f90
                          DW_AT_name                  dummy_at_proc
                          DW_AT_type                  <0x00000127> Refers to: REAL(4)
                          DW_AT_location              len 0x0003: 0x76807f: 
                              DW_OP_breg6-128
< 3><0x0000008c>        DW_TAG_lexical_block
                          DW_AT_decl_line             0x0000000c
                          DW_AT_decl_file             0x00000001 /home/jwm/tests/charptr/debug-visible.f90
                          DW_AT_low_pc                0x004041df
                          DW_AT_high_pc               0x00404260
< 4><0x0000009f>          DW_TAG_variable
                            DW_AT_decl_line             0x0000000c
                            DW_AT_decl_file             0x00000001 /home/jwm/tests/charptr/debug-visible.f90
                            DW_AT_name                  dummy_at_block
                            DW_AT_type                  <0x00000127> Refers to: REAL(4)
                            DW_AT_location              len 0x0003: 0x76847f: 
                                DW_OP_breg6-124
< 4><0x000000ae>          DW_TAG_variable
                            DW_AT_decl_line             0x0000000c
                            DW_AT_decl_file             0x00000001 /home/jwm/tests/charptr/debug-visible.f90
                            DW_AT_name                  b
                            DW_AT_type                  <0x00000120> Refers to: INTEGER(4)
                            DW_AT_location              len 0x0003: 0x768c7f: 
                                DW_OP_breg6-116
< 4><0x000000bb>          DW_TAG_variable
                            DW_AT_decl_line             0x0000000c
                            DW_AT_decl_file             0x00000001 /home/jwm/tests/charptr/debug-visible.f90
                            DW_AT_name                  a
                            DW_AT_type                  <0x00000120> Refers to: INTEGER(4)
                            DW_AT_location              len 0x0003: 0x76887f: 
                                DW_OP_breg6-120
< 3><0x000000c9>        DW_TAG_subprogram
                          DW_AT_decl_line             0x00000016
                          DW_AT_decl_file             0x00000001 /home/jwm/tests/charptr/debug-visible.f90
                          DW_AT_name                  subproc
                          DW_AT_static_link           len 0x0003: 0x760006: 
                              DW_OP_breg6+0
                              DW_OP_deref
                          DW_AT_low_pc                0x00404266
                          DW_AT_high_pc               <offset-from-lowpc> 129 <highpc: 0x004042e7>
< 4><0x000000e4>          DW_TAG_formal_parameter
                            DW_AT_decl_line             0x00000016
                            DW_AT_decl_file             0x00000001 /home/jwm/tests/charptr/debug-visible.f90
                            DW_AT_type                  <0x00000120> Refers to: INTEGER(4)
                            DW_AT_name                  z
                            DW_AT_location              len 0x0004: 0x76887f06: 
                                DW_OP_breg6-120
                                DW_OP_deref
< 4><0x000000f2>          DW_TAG_formal_parameter
                            DW_AT_decl_line             0x00000016
                            DW_AT_decl_file             0x00000001 /home/jwm/tests/charptr/debug-visible.f90
                            DW_AT_type                  <0x00000120> Refers to: INTEGER(4)
                            DW_AT_name                  x
                            DW_AT_location              len 0x0004: 0x76907f06: 
                                DW_OP_breg6-112
                                DW_OP_deref
< 4><0x00000100>          DW_TAG_formal_parameter
                            DW_AT_decl_line             0x00000016
                            DW_AT_decl_file             0x00000001 /home/jwm/tests/charptr/debug-visible.f90
                            DW_AT_type                  <0x00000120> Refers to: INTEGER(4)
                            DW_AT_name                  y
                            DW_AT_location              len 0x0004: 0x76987f06: 
                                DW_OP_breg6-104
                                DW_OP_deref
< 4><0x0000010e>          DW_TAG_variable
                            DW_AT_decl_line             0x00000019
                            DW_AT_decl_file             0x00000001 /home/jwm/tests/charptr/debug-visible.f90
                            DW_AT_name                  dummy_at_subproc
                            DW_AT_type                  <0x00000127> Refers to: REAL(4)
                            DW_AT_location              len 0x0003: 0x76807f: 
                                DW_OP_breg6-128
< 1><0x00000120>    DW_TAG_base_type
                      DW_AT_byte_size             4
                      DW_AT_encoding              DW_ATE_signed
                      DW_AT_name                  INTEGER(4)
< 1><0x00000127>    DW_TAG_base_type
                      DW_AT_byte_size             4
                      DW_AT_encoding              DW_ATE_float
                      DW_AT_name                  REAL(4)
< 1><0x0000012e>    DW_TAG_subprogram
                      DW_AT_decl_line             0x00000020
                      DW_AT_decl_file             0x00000001 /home/jwm/tests/charptr/debug-visible.f90
                      DW_AT_name                  _unnamed_main$$
                      DW_AT_calling_convention    DW_CC_program
                      DW_AT_low_pc                0x004042e7
                      DW_AT_high_pc               <offset-from-lowpc> 247 <highpc: 0x004043de>
                      DW_AT_main_subprogram       yes(1)
                      DW_AT_external              yes(1)
< 2><0x00000148>      DW_TAG_variable
                        DW_AT_decl_line             0x00000025
                        DW_AT_decl_file             0x00000001 /home/jwm/tests/charptr/debug-visible.f90
                        DW_AT_name                  dummy_at_main
                        DW_AT_type                  <0x00000127> Refers to: REAL(4)
                        DW_AT_location              len 0x0003: 0x76807f: 
                            DW_OP_breg6-128
< 2><0x00000157>      DW_TAG_variable
                        DW_AT_decl_line             0x00000024
                        DW_AT_decl_file             0x00000001 /home/jwm/tests/charptr/debug-visible.f90
                        DW_AT_name                  i
                        DW_AT_type                  <0x00000120> Refers to: INTEGER(4)
                        DW_AT_location              len 0x0003: 0x76847f: 
                            DW_OP_breg6-124

.debug_line: line number info for a single cu
Source lines (from CU-DIE at .debug_info offset 0x0000000b):

            NS new statement, BB new basic block, ET end of text sequence
            PE prologue end, EB epilogue begin
            IS=val ISA number, DI=val discriminator value
<pc>        [lno,col] NS BB ET PE EB IS= DI= uri: "filepath"
0x00404178  [   1, 0] NS uri: "/home/jwm/tests/charptr/debug-visible.f90"
0x0040417c  [   1, 0] NS ET EB
0x0040417e  [   7, 0] NS
0x00404191  [  10, 0] NS PE
0x004041df  [  15, 0] NS
0x0040422d  [  16, 0] NS
0x00404234  [  17, 0] NS
0x0040423b  [  18, 0] NS
0x00404255  [  19, 0] NS
0x00404260  [  21, 0] NS
0x00404264  [  21, 0] NS ET EB
0x00404266  [  22, 0] NS
0x00404281  [  26, 0] NS PE
0x004042cf  [  27, 0] NS
0x004042e1  [  28, 0] NS
0x004042e5  [  28, 0] NS ET EB
0x004042e7  [  32, 0] NS
0x00404303  [  39, 0] NS PE
0x00404351  [  41, 0] NS
0x0040435d  [  42, 0] NS
0x004043d3  [  43, 0] NS
0x004043dc  [  43, 0] NS ET EB
0x004043de  [  43, 0] NS ET

.debug_str
name at offset 0x00000000, length   23 is '/home/jwm/tests/charptr'
name at offset 0x00000018, length   17 is 'debug-visible.f90'
name at offset 0x0000002a, length  127 is 'Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.13.1 Build 20240703_000000
'
name at offset 0x000000aa, length   77 is '-diag-disable=10448 -g -O0 -debug all -debug-parameters all -o debug-visible '
name at offset 0x000000f8, length    4 is 'mod1'
name at offset 0x000000fd, length    4 is 'MOD1'
name at offset 0x00000102, length   10 is 'INTEGER(4)'
name at offset 0x0000010d, length   13 is 'dummy_at_proc'
name at offset 0x0000011b, length    7 is 'REAL(4)'
name at offset 0x00000123, length   14 is 'dummy_at_block'
name at offset 0x00000132, length   16 is 'dummy_at_subproc'
name at offset 0x00000143, length   15 is '_unnamed_main$$'
name at offset 0x00000153, length   13 is 'dummy_at_main'

.debug_aranges

.debug_frame

fde:
<    0><0x00404178:0x0040417e><><cie offset 0x00000000::cie index     0><fde offset 0x00000018 length: 0x00000024><eh offset none>
        0x00404178: <off cfa=08(r7) > <off r16=-8(cfa) > 
        0x00404179: <off cfa=16(r7) > <off r16=-8(cfa) > 
        0x0040417c: <off cfa=16(r6) > <off r6=-16(cfa) > <off r16=-8(cfa) > 
        0x0040417d: <off cfa=16(r6) > <off r16=-8(cfa) > 
<    1><0x0040417e:0x00404266><><cie offset 0x00000000::cie index     0><fde offset 0x00000040 length: 0x0000002c><eh offset none>
        0x0040417e: <off cfa=08(r7) > <off r16=-8(cfa) > 
        0x0040417f: <off cfa=16(r7) > <off r16=-8(cfa) > 
        0x00404182: <off cfa=16(r6) > <off r6=-16(cfa) > <off r16=-8(cfa) > 
        0x004041b6: <off cfa=16(r6) > <off r3=-24(cfa) > <off r6=-16(cfa) > <off r16=-8(cfa) > 
        0x00404264: <off cfa=16(r6) > <off r6=-16(cfa) > <off r16=-8(cfa) > 
        0x00404265: <off cfa=16(r6) > <off r16=-8(cfa) > 
<    2><0x00404266:0x004042e7><><cie offset 0x00000000::cie index     0><fde offset 0x00000070 length: 0x00000024><eh offset none>
        0x00404266: <off cfa=08(r7) > <off r16=-8(cfa) > 
        0x00404267: <off cfa=16(r7) > <off r16=-8(cfa) > 
        0x0040426a: <off cfa=16(r6) > <off r6=-16(cfa) > <off r16=-8(cfa) > 
        0x004042a6: <off cfa=16(r6) > <off r3=-32(cfa) > <off r6=-16(cfa) > <off r16=-8(cfa) > 
        0x004042e5: <off cfa=16(r6) > <off r6=-16(cfa) > <off r16=-8(cfa) > 
        0x004042e6: <off cfa=16(r6) > <off r16=-8(cfa) > 
<    3><0x004042e7:0x004043de><_unnamed_main$$><cie offset 0x00000000::cie index     0><fde offset 0x00000098 length: 0x0000002c><eh offset none>
        0x004042e7: <off cfa=08(r7) > <off r16=-8(cfa) > 
        0x004042e8: <off cfa=16(r7) > <off r16=-8(cfa) > 
        0x004042eb: <off cfa=16(r6) > <off r6=-16(cfa) > <off r16=-8(cfa) > 
        0x00404303: <off cfa=16(r6) > <off r3=-24(cfa) > <off r6=-16(cfa) > <off r16=-8(cfa) > 
        0x004043dc: <off cfa=16(r6) > <off r6=-16(cfa) > <off r16=-8(cfa) > 
        0x004043dd: <off cfa=16(r6) > <off r16=-8(cfa) > 

cie:
<    0> version      4
  cie section offset    0 0x00000000
  augmentation                  
  code_alignment_factor         1
  data_alignment_factor         -8
  return_address_register       16
  bytes of initial instructions 9
  cie length                    20
  initial instructions
  [  ] offset name                 operands
  [ 0]   0 DW_CFA_def_cfa          r7 8
  [ 1]   3 DW_CFA_offset           r16 -8
  [ 2]   5 DW_CFA_nop              
  [ 3]   6 DW_CFA_nop              
  [ 4]   7 DW_CFA_nop              
  [ 5]   8 DW_CFA_nop              

In my example all the variables are printed, to ensure they are not ignored by the compiler. And the DDT client support did test this example with ifx and reported that the variables were visible in the debugger, so DDT doesn’t look as the problem here.

Edit: with the same example compiled with gfortran, all the variables are visible in DDT. Which shows that the problem is IFORT.

Hmm… I see that ifort generates DWARF v3 information, whereas ifx (v2025.2.1) uses DWARF v4. Maybe DDT cannot handle the older format well —and it’s already been superseded twice, since the current DWARF version is 5.

It’s interesting, though, that the dwarfdump for an executable generated using ifx actually contains less information.