"implicit none" scoping error with header file

I am attempting to compile and run an old MPI parallel scientific code written in Fortran 77, using the “ftn” compiler command with intel compiler on a computer cluster, as in:

ftn main.f hb.f upd.f

and not shown is the header file, hb.h, which includes the following:
(col numbers)

      IMPLICIT NONE
      INTEGER n,m

and other variable declarations that get used repeatedly in modules, functions, and subroutines.
Within the subroutines, the header file is included with

      SUBROUTINE ROUTINENAME
      INCLUDE 'hb.h'
      INTEGER var1,var2,var3....

After compiling with ftn I get the error:

hb.h(1): error #6222: This IMPLICIT statement is not positioned correctly within the scoping unit.
      IMPLICIT NONE
------^

The error message implies that IMPLICIT NONE in hb.h is being placed incorrectly in each of the modules (yes I get an error message for each time hb.h is included in a subroutine,module,etc).

Help is appreciated

2 Likes

Welcome @jonthephysicist
you can put your Fortran codes between
```fortran
and
```
to get colored syntax with a monospace font.

2 Likes

Welcome to the forum. Now that you have formatted the code inserts, you may remove the “1234567” lines.

I suspect that you are describing what you think the source files contain, rather than what they actually contain, because the subroutine code that you show compiles without error.

1 Like

Could you clarify what you mean regarding actual and assumed contents of the source files?

I created an include file and a Fortran source file based on your post, as follows:

T:\lang\jon>cat hb.h
      implicit none
      integer n,m

T:\lang\jon>cat upd.f
      subroutine upd
      include 'hb.h'
      integer var1, var2
      end subroutine

T:\lang\jon>gfortran -c upd.f

T:\lang\jon>ls -l
total 32
-rw-r--r-- 1 Admin None  40 Aug 17 07:35 hb.h
-rw-r--r-- 1 Admin None  92 Aug 17 07:36 upd.f
-rw-r--r-- 1 Admin None 672 Aug 17 07:57 upd.o

As you can see, the compilation did not produce any error messages.

Ok, that’s helpful, however my concern is compiling on a cluster for MPI. I think your hint is pointing towards additional complications:

I am compiling with:

module swap PrgEnv-cray PrgEnv-intel
ftn main.f hb.f upd.f

This is at a supercomputer cluster, and the programs include various MPI commands as well as an mpi header file, mpif.h. So, the actual header file include statements are either just ‘hb.h’ or ‘mpif.h’ and ‘hb.h’:

      INCLUDE 'mpif.h'
      INCLUDE 'hb.h'

I counted the error messages from the compiler and it turns out there are 6 of them, corresponding to all the cases in which the above ‘mpif.h’ is included before ‘hb.h’.

How could ‘mpif.h’ cause problems for positioning of IMPLICIT NONE?

I’m going to try including hb.h before mpif.h to see if that changes it.

Ok so that resolves it.

Solution:

      SUBROUTINE ROUTINENAME
      INCLUDE 'mpif.h'
      INCLUDE 'hb.h'

keeps IMPLICIT NONE at the first line of the module. Apparently it needs to be the very first line of the module (please confirm?)

Just a suggestion, if you know what compiler was used to build MPI on your system and its the same as the one you are using, you might want to use the MPI module file instead of the include file. ie

use mpi

or

use mpi_f08

An included file may contain any text. The include '<filename>' line is replaced by the contents of the included file, and the resulting source code is passed to the compiler. Thus, the source file that the compiler parses is quite dependent on the order of the include statements as well as the contents of the included files. Naturally, the order in which multiple files are included may have major effects on the meaning of the program.

[I remember seeing the following lines in an include file, lenore.h, years ago:

c   A UNIX saleslady, Lenore,
c      Enjoys work, but she likes the beach more.
c   She found a good way
c      To combine work and play:
c   She sells C shells by the seashore.

]

IMPLICIT NONE (whether it be in the main program, a module, or a routine) must appear after the USE statements (if any) and before any declaration or statement (other than USE)

Sort of off topic but I’ve always wondered about the restriction on placing IMPLICIT NONE after a USE statement. To me it doesn’t make much sense. The same with having explicit interfaces as separate scoping units forcing you to either use IMPORT or a USE statement in each interface just to get KIND parameters.

My proposal to relax this restriction was discussed at Allow implicit none to appear before use statements · Issue #239 · j3-fortran/fortran_proposals · GitHub

1 Like