Idea Help: Simple code that demonstrates non-trivial, realistic bug

I’m going to be presenting to some colleagues of mine regarding debugging tools. Many of them are used to debugging with print statements, so I’ll be starting with a simple example to show how to navigate gdb.

I want to do this by demonstrating how to use it to fix a bug, but I’m having trouble coming up with an example program for this purpose. I want the bug to be non-trivial, meaning that you could have a hard time addressing it just with print statements, and ideally also it should be something that would not be caught simply by enabling runtime checks (so no e.g. array out of bounds accesses).

It would probably be easy to come up with a C function that could demonstrate this, but I’d prefer that the function be in Fortran.

I’m wondering if any of you have any ideas or examples of a program I could use for this demonstration.

Thanks very much in advance.

One thing that comes to mind is checking the contents of an array of derived types, where some of the fields are derived types themselves. While I love the print method for debugging (especially if you know something goes wrong in a large loop), writing useful print statements is a craft that can be painful to apply. Interactive debugging can be a pain when it comes to large loops, but then I usually try to combine the two.

To elaborate on loops:

do i = 1,100000
     ... calculate something ...
     if ( i == 2000 ) then
         ! Put a breakpoint here!
         write(*,*)  'Here is the iteration to be investigated'
    endif
    ... calculate another something ...

The idea is to skip to the iteration that is probably the culprit or near to it. The condition might be the curious value you are looking for instead of a particular value for the loop index.

1 Like

I think you are implying something that a lot of people do not do – compile with all the debug flags on, and do things to help the compiler find bad Fortran usage like combine the code into as few files as possible (ideally, one). I find debuggers best for finding human errors in logic. Code bugs like exceeding array bounds can not only go undetected by some debuggers, they can corrupt memory and cause the debugger to fail.

It sounds like you intend to tell them, but I always recommend trying the compiler flags first, as I have seen a lot of people spend a very long time in a debugger tracking down something that then have asked for help, and when I recompile with debug flags the problem shows up immediately.

So I am not sure how many of these your compiler(s) might catch, but the gotchas at
resources like https://www.cs.rpi.edu/~szymansk/OOF90/bugs.html provide some nice examples of bad usage. That might be useful. New users often have issues with inadvertent integer division, not specifying the kind of constants and getting unexpected values, overflow of integers in a lot of places. There are a few other “gotcha” references and FAQ lists that describe those available that can be searched for with those terms. There are a lot of hard-to-debug issues with initialization, especially using modern features. Would your users be familiar with some of the more complex new Fortran features or are you looking for something simpler like not initializing all the values in an array with DATA statements, not realizing initialization is not assignment and using a saved value that is changed between calls, or not understanding the scope of variables and changing things in a procedure via contained procedures because they were not declared in the contained routine? and so on … it is hard to do something short that the compilers will not detect that requires a debugger that is also not easy to spot by an experienced programmer. Although I have done something as simple as not notice a line is commented out that is needed at one time or another :>

But I think the “gotcha” reference might have what you need (?)

1 Like

@jdietz224 ,

TL;DR: almost anything with array arguments in subprograms and the typical problems encountered in Fortran programs requiring trouble-shooting are good cases for graphical debugging tools.

Please note in the present day and age if there are computational scientists/engineers/technicians hesitating to use graphical debugging facilities of integrated development environments (IDEs), it can be indicative of a significantly hesitant or a certain minimalist attitude toward adoption of certain good coding practices that have long (1970s and earlier) been recognized as leading to safe, productive, and efficient computations e.g., by Kernighan and Plauger in 1978.

Now, in the context of Fortran, a simple aspect to note where the issues pop up is with the supposed strength of Fortran i.e., arrays.where the importance of paying to the right attributes to choose with subprogram arguments and also explicit interfaces which tend to be overlooked and you will be surprised by the overlap of those who prefer to employ the debug-only-with-print approach and the practice to go with implicit interfaces.

So with this background, here’s a simple illustration:

  • consider an external procedure in file s1.f where the assumed-shape attribute was chosen for the received argument: note the PRINT statement
subroutine s1( x )
   integer, intent(in) :: x(:)
   print *, x
end subroutine 
  • consider another external procedure in s2.f that attempts to consume `s`` with an implicit interface
subroutine s2( y )
   integer :: y(*)
   call s1( y )
end subroutine 
  • and a main program that invokes s2
   integer :: n(3)
   n = [ 1, 2, 3 ]
   call s2( n )
end 
  • Try it with a Fortran processor and you will notice the PRINT statement does NOTHING:
C:\temp>gfortran -c -ffree-form s1.f

C:\temp>gfortran -c -ffree-form s2.f

C:\temp>gfortran -c -ffree-form p.f

C:\temp>gfortran p.o s1.o s2.o -o p.exe

C:\temp>p.exe


C:\temp>

You can extrapolate from this trivial case to a large code base where across various libraries and remote calls, the instruction arrives at something like s2 where the inadequateness of argument passing lead to PRINT being useless, the variable reference itself is garbage.

Whereas a basic familiarity with studying objects in memory and dereferencing their addresses, etc in a debugger would allow one to debug such a situation easily.

But now, note the above illustration is not conformant, but you may or may not be surprised by the large amount of Fortran codebases out there which do not conform and where their maintainers attempt support and development using PRINT statements!

1 Like

@jdietz224 , another case to consider is one involving a C-Fortran interoperating solution where a bug can lead to memory corruption and where the PRINT statement approach can become useless. Take a look at this thread (the first half of it) for an illustration.

1 Like

Print-based debugging becomes less convenient when there are derived types with allocatable components, since a list-directed print works for the components but not the whole derived type, as illustrated below:

module m
implicit none
type t
   real, allocatable :: x(:)
end type
end module m
!
program main
use m
type(t) :: z
z%x = [2.0, 4.0]
print*,z ! gfortran says Error: Data transfer element at (1) cannot have ALLOCATABLE components unless it is processed by a defined input/output procedure
end program main
1 Like

Attention @greenrongreen .

Readers may want to note there are posts online where a Fortran practitioner or other whinges and moans - yours truly among the worst culprits - about the Fortran “ecosystem” and how the inadequacies there curtail and inhibit the adoption of modern Fortran in many new computational projects and endeavors.

Note graphical debugging and support (or lack thereof) toward many new features introduced in the language starting Fortran 90 in one significant gap in the "ecosystem**.

Consider the following silly snippet conformant with the Fortran 90 standard from over 30 years ago:

   type :: a_t
      integer, allocatable :: x(:)
   end type
   type :: b_t
      type(a_t) :: a(2)
   end type
   type :: c_t
      type(b_t) :: b
   end type
   type(c_t) :: c
   allocate( c%b%a(1)%x(2) )
   allocate( c%b%a(2)%x(2) )
   c%b%a(1)%x = (/ 1, 2 /)
   c%b%a(2)%x = (/ 3, 4 /)
   print *, "Hello World!"
end

which can processed without any issues with a processor dated over 22 years ago:

C:\temp>f90 -free p.f
Compaq Visual Fortran Optimizing Compiler Version 6.6 (Update A)
Copyright 2001 Compaq Computer Corp. All rights reserved.

p.f
Microsoft (R) Incremental Linker Version 6.00.8447
Copyright (C) Microsoft Corp 1992-1998. All rights reserved.

/subsystem:console
/entry:mainCRTStartup
/ignore:505
/debugtype:cv
/debug:minimal
/pdb:none
dfor.lib
libc.lib
dfconsol.lib
dfport.lib
kernel32.lib
/out:p.exe

C:\temp>p.exe
 Hello World!

C:\temp>

Yet, if one works with it in the most widely IDE viz., Microsoft Visual Studio on Windows OS and uses the default approach to visually examine objects in the Fortran code, one encounters “undefined pointer/array” issue which does adversely affect the productive use of Fortran in industry:

For the Intel’s of this world, this can be seen as a business opportunity, if they so choose.

1 Like

“uses the default approach” suggests there is an alternative approach that works. Can you tell me more.

1 Like

Those with time and inclination can look into vendor (Microsoft) documentation and variety of disparate sources online on how to get one’s hands dirty with data inspection by viewing memory, etc. in a Visual Studio debugging session.

But in the context of Fortran and trying to keep it simple with the language syntax, a quick and (decidedly) dirty workaround is to use some “dead code” and employ the ASSOCIATE construct:

1 Like

Thanks. Looks good. I have done similar, but not as neatly and without the informative !DIR$ directive.

1 Like