How to detect uninitialized arguments?

I’m modernizing odrpack. As part of the conversion process, I’ve added intent(in/out) to all procedure arguments. Not being my code, I’ve struggled quite a bit trying to figure out what should be out or inout. Inevitably, I mislabeled a few arguments as just out, which led to hard-find problems. Unbelievable as it may seem (at least for me), the buggy code worked just fine in linux+gcc+debug/release and windows+gcc+debug, but failed in windows+gcc+release.

Anyway, this got me wondering how to detect this type of issues. IMO, the following code has an obvious problem in the first executable statement (y = x), but I can’t seem to make the compiler tell me about it.
How do you address these issues?

subroutine foo(x, y)
    implicit none
    integer, intent(out) :: x
    integer, intent(out) :: y
    integer :: i
    real :: a, b, c
    y = x
    i = i + 1
    a = a + 1.
    b = c
end subroutine
PS C:\Code\odrpack95\src> gfortran -c test.f90 -Wuninitialized
test.f90:8:13:

    8 |     i = i + 1
      |             ^
Warning: 'i' is used uninitialized [-Wuninitialized]
test.f90:5:16:

    5 |     integer :: i
      |                ^
note: 'i' was declared here
test.f90:9:14:

    9 |     a = a + 1.
      |              ^
Warning: 'a' is used uninitialized [-Wuninitialized]
test.f90:6:13:

    6 |     real :: a, b, c
      |             ^
note: 'a' was declared here
test.f90:10:9:

   10 |     b = c
      |         ^
Warning: 'c' is used uninitialized [-Wuninitialized]
test.f90:6:19:

    6 |     real :: a, b, c
      |                   ^
note: 'c' was declared here
1 Like

Using multiple compilers helps, because their error detection capabilities vary.

Intel Fortran Compiler: ifx -warn all

/app/example.f90(1): warning #6843: A dummy argument with an explicit INTENT(OUT) declaration is not given an explicit value.   [X]
subroutine foo(x, y)
---------------^

NAG Fortran:

~/discourse> nagfor example.f90 
NAG Fortran Compiler Release 7.1(Hanzomon) Build 7101
Questionable: example.f90, line 11: Variable B set but never referenced
Warning: example.f90, line 11: Symbol C referenced but never set
Warning: example.f90, line 11: INTENT(OUT) dummy argument X never set
[NAG Fortran Compiler normal termination, 3 warnings]
2 Likes

OK, I see… it’s possible, but not with gcc. Pitty, because I do like gcc. I tried installing Intel OneAPI on my Windows PC a while back, but it was not an enjoyable experience… I could never make it work… too many install options/packages, zillions of Gb… I gave up.

1 Like

The easiest way for me, has been to use the online or offline installer packages, e.g. if you visit: https://www.intel.com/content/www/us/en/developer/articles/tool/oneapi-standalone-components.html#fortran

With the online installer, you can select later if you need other components (say the C++ compiler or the MKL package). The whole oneAPI toolkit is big indeed. :elephant:


It looks like the gfortran unused argument detection is a bit faulty. If you remove all the statements entirely, you will see that gfortran does provide warnings:

/app/example.f90:1:16:

    1 | subroutine foo(x, y)
      |                1
Warning: Dummy argument 'x' at (1) was declared INTENT(OUT) but was not set [-Wunused-dummy-argument]
/app/example.f90:1:19:

    1 | subroutine foo(x, y)
      |                   1
Warning: Dummy argument 'y' at (1) was declared INTENT(OUT) but was not set [-Wunused-dummy-argument]

So it looks like y = x makes the compiler think that both arguments are used, despite the use of x being in violation of the intent(out) argument. The name of warning flag would imply it checks if a dummy argument appears in the executable section of a procedure, but not if it is actually used correctly. If not found it prints a message.

That said, one possibility with gfortran would be to initialize integers to some strange value, -finit-integer=-999999. Hopefully this would trigger some other error you could detect (for instance a runtime bound violation).

1 Like

Some error messages and warnings are better from ifx than gfortran; others are better from gfortran. So I always use both (and sometimes flang and g95 as well). Lfortran has not yet implemented all the Fortran 95 and Fortran 2003 features I use. NAG was very good until it was priced beyond what my employers were willing to pay. All of them got bug reports from me that were admitted to be bugs. Over 80% of those bugs have been fixed.

The following are helpful flags for ifort

  • /Qinit:snan: initialize variables to signaling NaN.
  • /Qinit:arrays: Initialize arrays as well as scalars.
  • /Qtrapuv: Initialize stack variables to unsafe variables.
  • /fpe:1: Underflow gives 0.0; Other exceptions produce NaN, signed infinity
  • /Qfp-stack-check: Check floating point stack.
1 Like

The compilers mentioned above can detect uninitialized real variables at compile and runtime. and some integer variables at compile time. Silverfrost makes the only Fortran compiler I am aware of that can detect uninitialized integer variables at runtime. It is Fortran-95 only, though. I understand compiler writers are reluctant to introduce runtime checking, for fear peopole will publish benchmarks with runtime checking turned on. That is unfortunate, as there are many applications where the overhead is not significant to the user even if left on for production. In particular, ordinary Fortran optimization techniques may move the checks out of loops, so the runtime cost can be trivial.

Lots of good suggestions here - run your tests with all the compilers you can lay your hands on, with all debugging options turned on. Each may find problems the other didn’t.

Also look at tools like valgrind. Running your tests under valgrind is really helpful for finding things others may miss.

I don’t recommend using /Qtrapuv with the Intel compilers - it doesn’t do anything useful.

1 Like

Thank you all, for the various suggestions. This is a hobby project, so I am intrinsically limited to compilers that are free to use. In practice, in terms of mature compilers, that means I can only use gcc or ifort/ifx.

I decided to give Intel a try, and this time all went fine with the installation. However, as far as I can see, ifx is not better than gcc at detecting the problem raised in this post. On the test code below, this is what happens:

  • the intel compiler (with flag /warn:all) does not detect any of the 5 issues!
  • gcc can at least detect issues #3 to #5.

I confess I was surprised/disappointed by this lack of error detection…

I tried ifix with /Qinit:snan, but I confess I don’t know how to make the compiler tell me where the NaN is coming from. Skill issue.

Note: The warning shown in @ivanpribec’s post is not about the the use of an uninitialized dummy argument in a statement, rather just that an intent(out) argument was not assigned a (return) value.

program test
    implicit none
    integer :: r, s
    r = 1
    s = 2
    call foo(r, s)

contains
    subroutine foo(x, y)
        integer, intent(out) :: x
        integer, intent(out) :: y
        integer :: i
        real :: a, b, c
        print *, x, y
        y = x      ! issue #1
        x = x + 1  ! issue #2
        i = i + 1  ! issue #3
        a = a + 1. ! issue #4
        b = c      ! issue #5
        print *, x, y
    end subroutine
end program
C:\Code\odrpack95\example>ifx test.f90 /warn:all
Intel(R) Fortran Compiler for applications running on Intel(R) 64, Version 2024.2.0 Build 20240602
Copyright (C) 1985-2024 Intel Corporation. All rights reserved.

Microsoft (R) Incremental Linker Version 14.36.32535.0
Copyright (C) Microsoft Corporation.  All rights reserved.

-out:test.exe
-subsystem:console
test.obj

@HugoMVale ,

If I recall correctly with current Intel Fortran and gfortran, certain scenarios around what you show are left up to the program author to sort out, the compiler provides little to no assistance. For example, the following will likely get no help from the processor:

   subroutine foo( x, y )
      integer, intent(out) :: x
      integer, intent(out) :: y
      y = x
      x = 1
   end subroutine

where the first instruction y = x fails to conform. I don’t know if other processors can help here.

Regular use of a graphical debugger in an integrated development environment during code development - e.g., Visual Studio IDE with Intel Fortran - is another workflow that can help in such situations.

I realize that it is so, but I can’t understand why.

intent is a feature of Fortran 90, which is around for 3 decades… Detecting this type of non-conformity is, IMO, something one has the right to expect from “production-grade” compilers, no?

I think the problem lies in when the error is detected. While gfortran is able to detect some of the issues at compile time, ifx/ifort seems to consider them runtime checks.

The version of oneAPI you installed still ships with ifort, and with that you can do something like

$ ifort -g -O0 -C -standard-semantics -traceback -diag-disable=10448  uninit.f90 && ./a.out 
 1 2
forrtl: severe (194): Run-Time Check Failure. The variable 'foo$I$_1' is being used in 'uninit.f90(17,9)' without being defined
Image              PC                Routine            Line        Source             
a.out              00000000004041C6  MAIN__                      6  uninit.f90
a.out              000000000040416D  Unknown               Unknown  Unknown
libc.so.6          00007F16F1378C8A  Unknown               Unknown  Unknown
libc.so.6          00007F16F1378D45  __libc_start_main     Unknown  Unknown
a.out              0000000000404081  Unknown               Unknown  Unknown

That covers issues 3, 4 and 5.

(I know some versions of ifx have LLVM-related problems with -check uninit (included with -C). That’s why I used ifort instead.)

So, you might consider building a test suite around the issues, rather than relying on compiler flags.

Back in the DEC days, the compiler could give you compile-time warnings of many uses of uninitialized variables, powered by DEC’s common-language GEM back-end. When we moved to Intel, GEM was discarded in favor of Intel’s IL0 back-end, which had no ability to do uninitialized variable checking, and the IL0 team rejected requests by the Fortran team to add it.

This left the Intel Fortran team to kludge-in a form of run-time detection that worked some of the time. Now with the move to LLVM, there is still no compile-time detection, but a fairly robust run-time detection. Again sadly, this works only on Linux and not on Windows - I don’t know why, nor if Windows support will be added later.

2 Likes

@sblionel is there some information about the GEM backend? I did a quick web search and found more information about it here: community.intel.com/t5/Intel-Fortran-Compiler/ifx-compiler-options/m-p/1552671#M169890, it turns out it’s your own post. :slight_smile: I’ll quote it here, if I may:

The ifort code generator has always been a terrible design (I’ve heard it likened to someone’s college project), and is difficult to maintain. (I could say that Intel would have been far better off to ditch IL0 for the DEC GEM backend, when the DEC compiler team moved to Intel, but that ship has sailed.) That most of the industry is converging on LLVM, a more modern design, means quick improvement. LLVM suffers in that it was (and is still largely) C-focused, so making Fortran work well with it requires more effort.

From your response, it seems LLVM is better than the IL0 backend. But how does the GEM backend compare to LLVM? LLVM is newer, so presumably it’s better, but are there some good lessons to learn from the GEM design?

1 Like

Not being a backend person, I can’t comment on this knowledgeably. I do know that GEM was designed from the start to support multiple languages, and provided many common tools that could be used by compilers (virtual memory management, listing files, cross-language oprtimization) whereas LLVM started as C/C++ only, and I’ve heard developers complain about the difficulty shoehorning Fortran into it. GEM was very, very good for its time and it took several years after we moved to Intel for Intel Fortran to outperform CVF. Intel had the rights to GEM but chose to put it on a shelf. At this point it’s not worth discussing - GEM hasn’t been developed since 2003.

3 Likes

Awesome thanks. My interest stems from trying to figure out a good compiler design, and these lessons from other compilers are invaluable. Something like learning from history.

The goals of GEM were similar to what LLVM claims to be now (but isn’t really) - a common toolkit to support compilers from a dozen or more languages that was easily retargetable and portable. When it was designed, DEC’s VAX compilers were built from a variety of home-grown back-ends; in fact, I think every language’s compiler had its own, with the exception of VAX C and VAX PL/I which shared a “VAX Code Generator” backend (not very good.)

GEM needed to satisfy the needs of languages as diverse as Fortran, Ada, BASIC, COBOL, Pascal, C, PL/I, and BLISS (the systems programming language used within DEC.) The goal was that if two compilers needed some function, it was better to add it to GEM than to have duplicated functionality. The engineers who designed GEM were top-notch and I had a great deal of respect for them. (Two were Rich Grove, who had been VAX FORTRAN project leader when I joined DEC, and Bill Noyce, son of one of Intel’s cofounders.)

I don’t doubt that there were some clever optimization techniques within GEM, but they’ve probably been duplicated and improved in the years since. For me, the value of GEM was like a lot of VMS - it worked for all programming languages. It made its debut with compilers for RISC ULTRIX, the short-lived MIPS-based systems that were a placeholder until Alpha was ready. When Alpha did launch, GEM enabled there to be a full suite of compilers ready to go. GEM also made it straightforward to retarget Fortran to x86 for DIGITAL Visual Fortran, and then for x64.

So, I don’t think GEM has much value today to developers of individual compilers. It could have been a useful inspiration to LLVM, and as LLVM matures it comes closer to what GEM set out to be.

4 Likes

https://vmssoftware.com – Seems to be the DEC compilers!

1 Like

It looks like fortran up through f95 is supported.