Question about CONTAINS

Separately, please note the Fortran standard does not restrict the number of internal procedures in a host that can operate on or with the “data” in the host. So, for example, someone might conjure up a design like so:

   real :: a, b, c
   call sub(x=1.0)
contains
   subroutine sub( x )
      real, intent(in) :: x
      ! define the host "data" here
      a = 1.0 ; b = 2.0 ; c = 3.0
      print *, f(x)
   end subroutine
   real function f( x )
      real, intent(in) :: x
      ! consume the host "data" here
      f = (a*x + b)*x + c
   end function
end 

and this too can obviate the need for nested internal procedures in the language; the nesting being something that concerns some who work on processor implementations.

This demonstrates one of the workarounds I mentioned early in this thread. One artificially moves entities to places that they don’t belong, just to satisfy the limited levels of internal procedures. We’ve all been doing this kind of thing for decades. The reason for this discussion is to see if there is really a good reason that we are forced to do this, or if the language could be extended to allow the internal procedures, and their local data, to be nested in the natural way.

Well that certainly answers your question about the technical limitations. I suppose it’s feasible, even if the tracking of access to the host variables would be a burden for vendors and the writers of the standard would be faced with an even bigger document to maintain.

I gave some counter-reasons (testing, design) why I think allowing an infinite level of nesting is a bad idea. It permits you to fit lots of non-reusable code under a small “interface” area, meaning the abstractions are weak. The potential performance benefits due to inlining could probably be achieved also with link-time optimization (LTO).

More generally, whenever nesting is too deep (be it conditional clauses, loops, etc) one ends up with code that will have poor spatial locality and is hard to reason about, essentially a rat’s nest. If we take the loop example, and pass everything using host association:

   call p_loop()

contains
   subroutine p_loop()
      do p = 1, n
         call q_loop()
      enddo
   contains
      subroutine q_loop()
         do q = p, n
            call r_loop()
         enddo
      contains
         subroutine r_loop()
            do r = q, n
               call s_loop()
            enddo
         contains
            subroutine s_loop()
               do s = r, n
               enddo
            end subroutine s_loop
         end subroutine r_loop
      end subroutine q_loop
   end subroutine p_loop

the code looks even worse than the regular loop version. The nesting of do has been replaced with code that is even more obscure, whereas in

do p = 1, n
   do q = p, n
      do r = q, n
         do s = r, n
         enddo
      enddo
   enddo
enddo

it was immediately clear you are iterating across a hyper-pyramid (half of a 4-d hyper-cube).

Those claims have not been argued here. That was one of the reasons for my posting the original question. The only comments so far from a standards committee member is that there are always workarounds that exist to bypass any need for nested internal procedures, but even the simple examples he shows have involved moving declarations of entities from where they belong to places where they do not belong, so I consider those arguments unconvincing. I have seen no arguments from compiler writers that this is too difficult.

I also consider this argument unconvincing. Everyone tests internal procedures for correctness all the time. I cannot fathom how one would write code without testing it, and I do not see how code within an internal procedure somehow becomes immune to testing.

I can only say that beauty is in the eyes of the beholder. What you consider obscure, I considered simplifying and revealing.

Yes, that is what it does, but it is 1/8 of the 4D space, not just half. That is not hidden by the internal subroutines, that structure is still there in both cases.

Hi Ron, In the link of my first post, Peter Klausler indicates possible complication of the implementation. I think he is a compiler writer (of NVIDIA), so I guess you can ask him directly on the linked Github page (by just adding a comment), or possibly make a small thread in comp.lang.fortran that links this thread (because he may prefer c.l.f. more (just a guess…)).

Apart from that, I’ve come across this Wikipedia page, which seems interesting:

I’m not sure about details, but this part may be related (for compiler stuff):

Nested functions may in certain situations (and languages) lead to the creation of a closure. If it is possible for the nested function to escape the enclosing function, for example if functions are first class objects and a nested function is passed to another function or returned from the enclosing function, then a closure is created and calls to this function can access the environment of the original function. The frame of the immediately enclosing function must continue to be alive until the last referencing closure dies and non-local automatic variables referenced in closures can therefore not be stack allocated. This is known as the funarg problem and is a key reason why nested functions was not implemented in some simpler languages as it significantly complicates code generation and analysis, especially when functions are nested to various levels, sharing different parts of their environment.

RE statement functions, is it not an option to keep them as-is, if it needs to appear in an internal procedure? Though this may not be entirely satisfying for modernization (particularly because it is “deprecated”), personally I feel statement functions are a pretty nice feature (similar to one-liner macro or lambda)… Though I haven’t used them up to now (just saw them in old codes), I guess I could use them as a replacement of internal functions (if they are one-liner).

One more thing is that, I usually do not meet strong needs for nested functions, probably because I prefer a function object approach. Though internal functions “capture” environment variables implicitly, with function objects we handle them explicitly (by capturing by value or by reference, i.e. setting type components explicitly by value or pointers). The behavior of data is also explicit and clear (which is nice for multi-threading etc). So I guess in some cases, it might be useful to consider such an approach (using a derived type as a replacement of internal functions).

  • Function object - Wikipedia
    (But unfortunately, we cannot use the native call syntax for such an object, so
    cannot use internal procedures and function objects on the same footing…)

Internal procedures are of course much more general than statement functions. They can be subroutines, for example, and not just functions, and also they can be more complicated, they need not be written always as a single expression as is required of statement functions. I also have used statement functions as a substitute for macro expansion, particularly because fortran does not have an actual standard macro preprocessor, so one was historically faced with the choice of using a statement function, using a nonstandard macro preprocessor, duplicating the code inline manually, or making the function an external function. I have done all of those things in the past, depending on the situation.

One situation the comes to mind, is an integer function that I usually write as nndx(i)=(i*(i-1))/2. This occurs when storing symmetric matrices in triangular-packed form. A matrix element indexed by (i,j) with normal rectangular storage is referenced as a(nndx(i)+j) with i>=j with packed storage. In some of my codes from the 70s and 80s, you will see dozens of instances of that statement function scattered throughout. I didn’t want to make it an external function because I wanted the compiler to be able to expand and optimize it locally, so I just replicated it everywhere.

Now, statement functions are deprecated, so when I work on those legacy codes, I sometimes convert them to internal functions, sometimes I just leave them as-is, and sometimes I do convert them to external or module functions. The internal procedure nesting limit of fortran sometimes goes into making the decision of which to do.

Placing the declarations of entities in the host (which may be a module procedure or an external subprogram) instead of in an internal procedure that otherwise will try to invoke a hornet’s nest of internal procedures is not moving them to “places where they do no belong”!

Rather it is indeed placing the entities where they belong. Compilers starting with Fortran 90 are well set to handle such hosting scenarios, the design of MODULEs in Fortran with module entities is based on this.

In both statement functions and allocation by assignment the syntax does not immediately show what they do: the former looks like an assignment to an array element and the latter like assignment to a scalar. For that reason I usually put ! stmt function or ! alloc by assignment at the end of the relevant line; I find those comments useful on revisiting one of my programs after some time.

1 Like

Where is the example with the specific case of refactoring the obsolescent statement functions with internal procedures that indicate to you the need for nested internal procedures?

Following the Wikipedia sources in the link from @septc, provided a few interesting resources:

In the StackOverflow thread, one of the the respondees quotes Guido van Rossum (Python creator):

This is because nested function definitions don’t have access to the local variables of the surrounding block – only to the globals of the containing module. This is done so that lookup of globals doesn’t have to walk a chain of dictionaries – as in C, there are just two nested scopes: locals and globals (and beyond this, built-ins). Therefore, nested functions have only a limited use. This was a deliberate decision, based upon experience with languages allowing arbitraries nesting such as Pascal and both Algols – code with too many nested scopes is about as readable as code with too many GOTOs.

Ron Shephard remarked previously that beauty is in the eyes of the beholder; at least it appears I am not alone with my sense of beauty. I don’t object that a disciplined programmer can’t make effective use of nesting. The question is if the code will be readable to the person that comes after.

1 Like

The claim is that a code with too many nested scopes is about as readable as code with too many GOTOs. Can you show me an example of such actual code, in Pascal or Algol or some other language that allows such nesting, or even better in fortran syntax where one can imagine that the current 1- and 2-level nesting limits are removed. I’ve already shown such an example where the code, to my eye, was simple, clear, and unambiguous, and where the suggested alternatives have all been inferior.

I certainly believe that such code can be written (one can write bad code in any language), I just want to see what you have in mind that is serious enough to continue to preclude this feature from the language.