Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.

The IMPLICIT NONE issue drags on

Andrew_Smith
New Contributor III
2,703 Views

It is good practice to use IMPLICIT NONE but it is hard to enforce because one has to pepper code with IMPLICIT NONE and when you miss one, there is nothing to tell you unless you use a non-standard compiler directive.

The standard should make life easier for us by making good things the default when it does not break old code. Module procedures is new so the standard could have been better in this area.

This code raises no errors. You can add IMPLICIT NONE to all the module procedure interfaces but it can be an onerous task.

We dont need an IMPORT statement in the module procedure interface because this special type of interface picks up the scope of the module. Since the parent module has IMPLICIT NONE, the module interfaces should see this.

Is this a correct interpretation of the standard and if not why was the standard lacking in this area?

module A

   implicit none
   
   interface
      module subroutine foo(X)
      end
   end interface

end module

 

45 Replies
andrew_4619
Honored Contributor II
1,852 Views

I believe that is correct to the standard and Yes I personally think this is a bit strange. I am sure there was a discussion of this in the forum withing the last year or so. I will see if I can find it.

0 Kudos
andrew_4619
Honored Contributor II
1,852 Views

The discussion goes along the lines that the interface is a separate  scoping unit and the implicit/explicitness is whatever you actually specify within the scoping  unit. Clearly it must match the corresponding procedure. For a submodule you can have a global implicit none in the submodule and that is enough because if the interfaces do not match a compile error is produced. 

From a personal point of view I put implicit none absolutely everywhere often in a redundant way and that way I feel happy that my trousers will not fall down as I have both belt and braces.

0 Kudos
Steve_Lionel
Honored Contributor III
1,852 Views

An interface block is a window into the procedure, so having things flow by default from the host scope into the block would cause other issues. Of course, the preferable course is to not use interface blocks at all for Fortran code except where needed for submodules.

But, yeah, it would be nice to go back 50 years and do away with implicit declarations. At least most if not all compilers allow you to disable implicit with a command option.

 

0 Kudos
mecej4
Honored Contributor III
1,852 Views

Andrew S.:

1. The /warn:declarations compiler option will give you the same diagnostics as introducing IMPLICIT NONE in every relevant place. This may not help you if you have a habit of ignoring warnings.

2. With old code, whether you add IMPLICIT NONE by hand or using a tool, or you use a compiler option with the effect of adding IMPLICIT NONE, you will have decide what to do with the lots of error messages that result from an attempt to compile. the modified source.

3. Faced with a big job of writing hundreds of declarations, you may find IMPLICIT REAL(A-H,O-Z) a compromise that may serve you better. If, after you select this compromise, the modified code can be compiled and the program passes tests, you can use a tool to add explicit variable declarations and remove the IMPLICIT statements. Examples of such third party tools: Vast79 and Plusfort/SPAG.

Just to clarify, in your sample code the dummy variable X is implicitly typed, and the IMPLICIT NONE of the module containing the interface does not apply to it.

0 Kudos
Andrew_Smith
New Contributor III
1,853 Views

". Of course, the preferable course is to not use interface blocks at all for Fortran code except where needed for submodules"

I put almost all routines I write in submodules because of a huge reduction in compile time. When I have to touch old code the first task I do is to put all the procedures into a new submodule file. I only write an interface for the exposed procedures. Writting the interface block is the biggest time consumer but it can be done easily by copy and paste from the routine entry code apart from having to insert IMPLICIT NONE into each one. We did not need it before because IMPLICIT NONE in a module extends into its procedures. This is a step back beyond 50 years.

It is a viral growth of submodules. Is this unexpected to you Steve?

Is there no Intel option to dissable implicit type in visual studio? I only found one to warn of undeclared symbols which is not quite hard enough. It is easy to miss a warning.

0 Kudos
Steve_Lionel
Honored Contributor III
1,853 Views

The option to "warn for undeclared symbols" is the equivalent of IMPLICIT NONE.

If you have existing routines for which you're copying the declarations into submodule interfaces, the compiler will complain if they don't match. If you already have IMPLICIT NONE, then you know you have everything declared.

Yes, there are some warts on the language that hindsight tells us should not have been there. But a tremendous strength of Fortran is that old, correct code still works, and having the language change the default for such a fundamental aspect would be immediately rejected by users and vendors. I will note that F2015 adds the ability to disable implicit interfaces for externals, which is welcome. Compilers will also add command line options for this. I would like to see Intel Fortran support this as soon as possible.

0 Kudos
andrew_4619
Honored Contributor II
1,853 Views

Andrew Smith wrote:
...easily by copy and paste from the routine entry code apart from having to insert IMPLICIT NONE into each one. 

But as  pointed out in #3 and Steve also in the previous post the IMPLICIT NONE you are adding is redundant in this case, as the IMPLICIT NONE of the procedure will be enforced by the compiler when checking that the interface and implimentation match. 

0 Kudos
FortranFan
Honored Contributor II
1,853 Views

Steve Lionel (Ret.) wrote:

.. Yes, there are some warts on the language that hindsight tells us should not have been there. ..

 A close second to IMPLICIT NONE in terms of investment in better code is the INTENT declarations of dummy arguments in procedures.  One thing I have long wished is for the standard to have made compulsory the INTENT declarations in MODULE subprograms.  I don't think this would have caused any backward compatibility issues with earlier standards.  But a little bit of such pain for coders would have alleviated a lot of subsequent agony in the teams I have worked with. 

0 Kudos
Steve_Lionel
Honored Contributor III
1,853 Views

There's a problem with mandatory INTENT in that there is no way to say with INTENT the same thing as omitting INTENT. In particular, INTENT(INOUT), which you might think is the same, requires that the associated actual argument be definable, whereas with omitted INTENT "its use is subject to the limitations of its effective argument (12.5.2)." So if you have a dummy where in some cases you pass a variable that can be written and in other cases a constant (and the procedure flow makes sure that a constant is never modified), there is no form of INTENT that corresponds.

0 Kudos
JVanB
Valued Contributor II
1,853 Views

Compared to all the other boilerplate, IMPLICIT NONE doesn't seem like such a big deal.

   public glGetError
   interface
      function glGetError() bind(C,name='glGetError')
         import
         implicit none
!DEC$ ATTRIBUTES STDCALL :: glGetError
!GCC$ ATTRIBUTES STDCALL :: glGetError
         integer(glEnum) glGetError
      end function glGetError
   end interface

Besides, IMPLICIT NONE is not possible in some codes.

If a compiler implemented a switch enforcing INTENT it would probably have to also have an extension INTENT(F77).

 

0 Kudos
FortranFan
Honored Contributor II
1,853 Views

Steve Lionel (Ret.) wrote:

There's a problem with mandatory INTENT in that there is no way to say with INTENT the same thing as omitting INTENT...

".. no way to say with INTENT the same thing as omitting INTENT.." is why omitting the INTENT is such a concern; the situation can actually turn out worse than the "warts" mentioned by Steve as there are many coders who are still under the wrong impression not including the INTENT is the same as INTENT(INOUT).  It would have been really useful if such a situation was disallowed starting with Fortran 90 standard, at least in certain forward-looking circumstances such when it's NOT an external subprogram e.g., a MODULE subprogram.  Backward compatibility with all the FORTRAN 77 and older codes out would still have been maintained even if coders were to write INTERFACEs for them and the netherworld scenario would have remained confined to those old codes.  Unfortunately coders are writing new code in so-called 'modern' ways using MODULEs and SUBMODULEs but without including the dummy argument INTENTs and thereby propagating a serious problem ad infinitum.  For example, I think it's dangerous compilers do not throw any warning for the code shown below where the dummy argument has the ALLOCATABLE attribute but the INTENT is missing that can have a different behavior compared to INTENT(INOUT) which is then separate from INTENT(OUT):

module m

   implicit none

   interface
      module subroutine foo(x)
         implicit none
         integer, allocatable :: x
      end subroutine foo
   end interface

end module m

 

0 Kudos
Steve_Lionel
Honored Contributor III
1,853 Views

I don't see the problem. If the programmer really means INTENT(OUT) then there is a specific meaning for that in that the dummy argument becomes undefined on routine entry (and for allocatable it becomes deallocated). I do think that there should be a fourth INTENT option, maybe UNKNOWN or OMITTED or something like that, to allow the programmer to specify the semantics of omitted intent. (Then again, I would urge programmers who want that option to rearchitect the application to not need it.)

0 Kudos
jimdempseyatthecove
Honored Contributor III
1,853 Views

Why would a programmer .NOT. want to have a lack of INTENT equivalent to (you pick)

INTENT UNKNOWN
INTENT OMITTED
INTENT NONE (on par with IMPLICIT NONE)
...

Cannot a programmer (and compiler optimization) implicitly understand arguments specified without INTENT (they do now).

I do agree with FortranFan that INTENT should be specified as a strong preference. However, with the amount of legacy code around, there may be unintended consequences in forcing INTENT in the API.

Jim Dempsey

0 Kudos
Steve_Lionel
Honored Contributor III
1,853 Views

Here's an example where there's no value of INTENT that works:

subroutine noclue (flag, val)
logical flag
integer val
if (flag) then
   val = val + 1
else
  print *, val
end subroutine noclue
!
program test
integer var
var = 42
call noclue (.true., var)
call noclue(.false., var+13)
end program test

Here, the expression var+13 is not definable, so INTENT(INOUT) is not allowed. 

FortranFan
Honored Contributor II
1,853 Views

I read this thread in a somewhat larger context focusing on a point in the original post regarding IMPLICIT NONE which is that "when you miss one, there is nothing to tell you".

Fortran standard clearly ties the IMPLICIT statement with a scoping unit.  And I would think a processor (compiler) knows whether an IMPLICIT statement is in effect for a scoping unit or not.

So why can't some /warn:xx (say /warn:missing-implicit-none) compile-time option be introduced that can alert the programmer when no IMPLICIT statement is applicable for a particular scoping unit and when the default mapping of letters to types are going to be used for a program unit?

Similarly a processor has to know when the INTENT for dummy arguments (either via the attribute option or as an explicit INTENT statement) is missing, so why can't some /warn:yy (/warn:missing-dummyargs-intent) option be introduced to alert the programmer?

andrew_4619
Honored Contributor II
1,853 Views

FortranFan wrote:
 /warn:xx (say /warn:missing-implicit-none) .... /warn:yy (/warn:missing-dummyargs-intent) option be introduced to alert the programmer?

Both of these would be useful IMO. You could argue that existing warn undeclared  cover the first item but belt and braces is always a safe strategy and options that force me to "do it correctly" are always good.

0 Kudos
FortranFan
Honored Contributor II
1,853 Views

Steve Lionel (Ret.) wrote:

Here's an example where there's no value of INTENT that works: ..

Issue is one of a "contract" between the party that develops and delivers "noclue" and the one that consumes it.  Per this example by Steve, the implementation is incomplete or ill-defined with respect to whatever contract might exist between the two parties.  If the contract calls for val dummy argument to be defined in the noclue procedure and to otherwise meet the terms as defined by INTENT(INOUT) attribute, then the caller is departing from the contract, perhaps unknowingly in which case can legimately hope to get warned about it.  On the other hand, say if the contract calls for the val dummy argument to meets the terms of "pass by value" (the VALUE atttibute) then in this case the caller will have reason to be upset with the first invocation of noclue even if the second call is ok.

Now the example as shown by Message #15 is effectively that from the FORTRAN 77 (and prior revisions) days of external subprograms and implicit interfaces.  In order to support legacy code and provide backward compatibility, the standard can best let such sleeping dogs lie.

But why should all the risk associated with such scenarios be allowed to propagate when external subprograms are not involved, as shown below?

module m

   private

   public :: noclue

contains

   subroutine noclue (flag, val)

      logical :: flag
      integer :: val

      if (flag) then
         val = val + 1
      else
         print *, val
      end if

      return

   end subroutine noclue

end module m
program test

   use m, only : noclue

   integer :: var

   var = 42

   call noclue(.true., var)
   call noclue(.false., var+13)

   stop

end program test

Or this:

module m

   private

   public :: noclue

   interface

      module subroutine noclue (flag, val)

         logical :: flag
         integer :: val

      end subroutine noclue

   end interface

end module m

submodule(m) sm

contains

   module subroutine noclue (flag, val)

      logical :: flag
      integer :: val

      if (flag) then
         val = val + 1
      else
         print *, val
      end if

      return

   end subroutine noclue

end submodule sm

Say the implementer who has generally attempted to follow all "modern" ways, as shown above, has simply missed out on the dummy argument INTENTs and IMPLICIT NONE, why can't the compiler help out and warn about this, at least when called out for such help, say with /warn:all or some other option?  In either of these cases, I think there is enough information available to the processor to be aware of such omissions, all that's being asked of it is to speak up.

This is one of the things I mean when I bring up the aspect of willingness to improve the customer experience.

0 Kudos
jimdempseyatthecove
Honored Contributor III
1,853 Views

With the somewhat recent versions of Fortran, when the argument INTENT is not seen (known) at point of compilation .AND. if a literal or expression is used for the actual argument, the calling convention is by reference, however, a temporary copy (of literal or expression) is placed on the stack. Although this appears to be meaningless, I am quite sure there is legacy code that would break by making a change.

I think there is a Fortran "lint" program, that would be a nice feature for IVF to include (or include link in documentation).

Also note, that the reference to copy of literal or expression though "fixes" most cases, there may have been a few bizarre situations were it broke code. I know of an instance in a very old FORTRAN II program where a literal was purposely changed. The intention was to obfuscate proprietary code. (I didn't write that code).

Jim Dempsey

0 Kudos
Steve_Lionel
Honored Contributor III
1,853 Views

Intel's implementation is to NOT create a stack copy of constant actual arguments by default. You can ask for that with /assume:noprotect_constants. The default is to pass the address of read-only storage, so you'll get an access violation on write. Expressions are passed as a writable copy, but the standard still insists that they are not "definable".

I'm afraid that I don't quite understand what is being expressed in post 18, but I will say that one of the primary strengths of Fortran is that old "dusty deck" code generally continues to work, and the committee is extremely reluctant to make breaking changes for situations where the standard clearly specified some behavior. Yes, this does mean passing on changes that enforce better programming practices. It's certainly possible for implementations to add such "guidance" through compiler options.

0 Kudos
FortranFan
Honored Contributor II
1,603 Views

Steve Lionel (Ret.) wrote:

.. I'm afraid that I don't quite understand what is being expressed in post 18 ..

What's so confusing about post 18?  It only suggests implementations try to provide some addiitonal warnings under 2 very specific circumstances, that too only when programmers ask for them via compiler options.  What part of it does one not understand?  That post didn't express anything about any change to the standard.  So how does the question of the standards committee getting involved or breaking any old dusty decks even arise?

0 Kudos
Reply