Silverfrost Forums

Welcome to our forums

MODULE and EXTERNAL query

22 Jul 2014 7:11 #14350

I've recently been trying to get my head around MODULES and have even stopped using COMMON blocks. However I'm puzzled by some of the concepts associated with MODULES.

Here we have a function, subroutine and main routine, written in F77 as I was taught 30+ years ago. This does what I expect it to do.

FUNCTION F(X)
IMPLICIT NONE
DOUBLE PRECISION F, X
 F = SIN(X)
RETURN
END

SUBROUTINE SIMPSON(F,A,B,INTEGRAL,N)
IMPLICIT NONE
DOUBLE PRECISION F, A, B, INTEGRAL,S
DOUBLE PRECISION H, X
INTEGER NINT
INTEGER N, I

IF((N/2)*2.NE.N) N=N+1

S = 0.0
H = (B-A)/DFLOAT(N)
DO I=2, N-2, 2
   X   = A+DFLOAT(I)*H
   S = S + 2.0*F(X) + 4.0*F(X+H)
END DO
INTEGRAL = (S + F(A) + F(B) + 4.0*F(A+H))*H/3.0
RETURN
END SUBROUTINE SIMPSON


PROGRAM MAIN
IMPLICIT NONE
DOUBLE PRECISION F, A, B, INTEGRAL
INTEGER N
EXTERNAL F

A = 0.0
B = 3.1415926
N = 64

WRITE(*,100)
CALL SIMPSON(F,A,B,INTEGRAL,N)
WRITE (*,101) N, INTEGRAL

100   format('     nint   Simpson')
101   format(i9,1pe15.6)
end

Now moving the function and subroutine to a module we get:

MODULE M1
IMPLICIT NONE
CONTAINS

FUNCTION F(X)
DOUBLE PRECISION F, X
 F = SIN(X)
RETURN
END FUNCTION F

SUBROUTINE SIMPSON(F,A,B,INTEGRAL,N)
DOUBLE PRECISION F, A, B, INTEGRAL,S
DOUBLE PRECISION H, X
INTEGER NINT
INTEGER N, I

IF((N/2)*2.NE.N) N=N+1

S = 0.0
H = (B-A)/DFLOAT(N)
DO I=2, N-2, 2
   X   = A+DFLOAT(I)*H
   S = S + 2.0*F(X) + 4.0*F(X+H)
END DO
INTEGRAL = (S + F(A) + F(B) + 4.0*F(A+H))*H/3.0
RETURN
END SUBROUTINE SIMPSON

END MODULE M1

PROGRAM MAIN
USE M1
IMPLICIT NONE
DOUBLE PRECISION  A, B, INTEGRAL
INTEGER N
EXTERNAL F

A = 0.0
B = 3.1415926
N = 64

WRITE(*,100)
CALL SIMPSON(F,A,B,INTEGRAL,N)
WRITE (*,101) N, INTEGRAL

100   FORMAT('     NINT   SIMPSON')
101   FORMAT(I9,1PE15.6)
END

This also works, but looking at the main program I think the function F is defined in the module M1, so because of the USE M1 statement the EXTERNAL F statement is not required. But when I delete this, I get an error. Can somebody give me a (simple) explanation of why the EXTERNAL statement is still required?

Thanks Ken

23 Jul 2014 1:32 #14351

Ken,

I am not an expert in the use of CONTAINS or EXTERNAL but I would be inclined to use EXTERNAL, even though it is not always required. It appears that if you do not use EXTERNAL in the program, then F becomes a local real*8 variable. (what about implicit none ??) This might say something about the use of contained functions. It also indicates that in some circumstances there can be both local and contained variables of the same name, which is confusing and bad coding if allowed. My recommendation is to use EXTERNAL, even if the compiler sometimes guesses it is the case, as in SUBROUTINE SIMPSON. Another point is that although the function F is contained in M1, this has no linkage to the external function F referenced in SIMPSON. Modules don't override the argument list.

It is interesting, that although FTN95 identifies F in Subroutine simpson as implied external, it does not for the contained function F referenced in the Program. I do not know if this is standard complying or not. Again, the use of EXTERNAL statements does provide clearer documentation of what you intended. I changed to the following code to test what was happening.

MODULE M1 
 IMPLICIT NONE 
 CONTAINS 

 FUNCTION F(X) 
 DOUBLE PRECISION F, X 
  F = SIN(X) 
 RETURN 
 END FUNCTION F 

 FUNCTION C(X) 
 DOUBLE PRECISION C, X 
  C = 1.0
 RETURN 
 END FUNCTION C 

 FUNCTION U(X) 
 DOUBLE PRECISION U, X 
  U = X
 RETURN 
 END FUNCTION U

 SUBROUTINE SIMPSON (F,A,B,INTEGRAL,N) 
 DOUBLE PRECISION F, A, B, INTEGRAL 
 INTEGER N
 EXTERNAL F 
!
 DOUBLE PRECISION H, X,S
 INTEGER I 

 IF ((N/2)*2.NE.N) N=N+1 

 S = 0.0 
 H = (B-A)/DFLOAT(N) 
 DO I=2, N-2, 2 
    X = A+DFLOAT(I)*H 
    S = S + 2.0*F(X) + 4.0*F(X+H) 
 END DO 
 INTEGRAL = (S + F(A) + F(B) + 4.0*F(A+H))*H/3.0 
 RETURN 
 END SUBROUTINE SIMPSON 

 END MODULE M1 

 PROGRAM MAIN 
 USE M1 
 IMPLICIT NONE 
 DOUBLE PRECISION  A, B, INTEGRAL 
 INTEGER N, i 
 EXTERNAL F,C,U

 A = 0.0 
 B = 4 * atan (1.0d0) ! 3.1415926 
 do i = 3,6
   N = 2**i 
  
   WRITE(*,*) '     NINT   SINE SIMPSON'
   CALL SIMPSON (F,A,B,INTEGRAL,N) 
   WRITE (*,101) N, INTEGRAL, (INTEGRAL-2)
  
   WRITE(*,*) '     NINT   CONST SIMPSON'
   CALL SIMPSON (C,A,B,INTEGRAL,N) 
   WRITE (*,101) N, INTEGRAL, (INTEGRAL-B) 
  
   WRITE(*,*) '     NINT   LINEAR SIMPSON'
   CALL SIMPSON (U,A,B,INTEGRAL,N) 
   WRITE (*,101) N, INTEGRAL, (INTEGRAL - b**2/2) 
 end do
 101   FORMAT(I9,' Int',ES15.6,' err',ES15.6) 
 END 
23 Jul 2014 3:54 #14354

For me the trick is to ask a question along the lines of 'How does such-and-such a routine know what type variable <whatever> is?' which is an anthropomorphised version of the somewhat longer question 'How does the compiler know ...'

In the case of F in the list of parameters to SUBROUTINE SIMPSON, SIMPSON cannot know that F is a FUNCTION unless it is declared EXTERNAL within SIMPSON (Old-style Fortran), but SIMPSON can guess that F is a FUNCTION when calculating INTEGRAL because of the way it is invoked. Indeed, F might be a FUNCTION here or simply an undeclared array - no-one can tell until you LINK it and see if there is a FUNCTION F.

FTN95 is pretty clever, but it has two choices and one of them must be wrong, mustn't it? I suppose as A is REAL, then you could guess that F is an external function, but it is easier and completely unambiguous if you declare it to be so.

I don't use he later facilities in Fortran, but perhaps if F(X) was defined in one module, and that module was USEd inside SUBROUTINE SIMPSON, then that might do the trick, as the compiler could look inside the MODULE for the definition of F - but my guess is that it is also done at LINK time.

Eddie

23 Jul 2014 4:51 #14355

John is right: the problem is in SUBROUTINE simpson, where you should declare F as EXTERNAL. But you do not need to declare it as EXTERNAL in the main program because of the USE statement.

23 Jul 2014 6:48 #14356

Thanks for your suggestions/insights on this - very much appreciated.

Looking at this again, I've now found that the following version of the code, without any EXTERNAL references, fails with Checkmate Win 32 but runs fine with Release Win 32. Again not exactly as expected. I will stick to using EXTERNAL references from now on.

Cheers

Ken

      MODULE M1 
      IMPLICIT NONE 
      CONTAINS 

      FUNCTION F(X) 
      DOUBLE PRECISION F, X 
      F = SIN(X) 
      RETURN 
      END FUNCTION F 

      SUBROUTINE SIMPSON(F,A,B,INTEGRAL,N) 
      DOUBLE PRECISION F, A, B, INTEGRAL,S 
      DOUBLE PRECISION H, X 
      INTEGER NINT 
      INTEGER N, I

      IF((N/2)*2.NE.N) N=N+1 

      S = 0.0 
      H = (B-A)/DFLOAT(N) 
      DO I=2, N-2, 2 
        X   = A+DFLOAT(I)*H 
        S = S + 2.0*F(X) + 4.0*F(X+H) 
      END DO 
      INTEGRAL = (S + F(A) + F(B) + 4.0*F(A+H))*H/3.0 
      RETURN 
      END SUBROUTINE SIMPSON 

      END MODULE M1 

      PROGRAM MAIN 
      USE M1 
      IMPLICIT NONE 
      DOUBLE PRECISION  A, B, INTEGRAL 
      INTEGER N  

      A = 0.0 
      B = 3.1415926 
      N = 64 

      WRITE(*,100) 
      CALL SIMPSON(F,A,B,INTEGRAL,N) 
      WRITE (*,101) N, INTEGRAL 

 100  FORMAT('     NINT   SIMPSON') 
 101  FORMAT(I9,1PE15.6) 
      END 
23 Jul 2014 9:12 #14357

For situations such as this, what you need is the ability to declare an Abstract Interface to a subprogram, so that any subroutine/function with that interface can be used as an actual argument to a subroutine that applies an algorithm (such as quadrature) to the specific argument function passed to it as an argument. Fortran 2003 and above allow abstract interfaces, and here is a version of your program that uses this feature. FTN95 does not allow this feature, but other Fortran compilers such as Gfortran do. Note the complete absence of variables with the attribute EXTERNAL.

MODULE FNI
   ABSTRACT INTERFACE
      DOUBLE PRECISION FUNCTION FUN(X)
      implicit NONE
      double precision, intent(in) :: x
      end function
   END INTERFACE
END MODULE FNI

MODULE SIMP
CONTAINS
SUBROUTINE SIMPSON(F,A,B,INTEGRAL,N)
USE FNI
DOUBLE PRECISION, INTENT(IN) :: A, B
DOUBLE PRECISION, INTENT(OUT) :: INTEGRAL
DOUBLE PRECISION S,H,X
PROCEDURE (FUN) :: F
INTEGER N, I

IF((N/2)*2.NE.N) N=N+1

S = 0.0
H = (B-A)/N
DO I=2, N-2, 2
   X   = A+I*H
   S = S + 2.0*F(X) + 4.0*F(X+H)
END DO
INTEGRAL = (S + F(A) + F(B) + 4.0*F(A+H))*H/3.0
RETURN
END SUBROUTINE SIMPSON

END MODULE SIMP

PROGRAM MAIN
USE FNI
USE SIMP
IMPLICIT NONE
DOUBLE PRECISION  A, B, INTEGRAL
INTEGER N
PROCEDURE(FUN), POINTER :: FPTR

A = 0d0
B = 4*atan(1d0)
N = 64
FPTR=>F

WRITE(*,100)
CALL SIMPSON(FPTR,A,B,INTEGRAL,N)
WRITE (*,101) N, INTEGRAL

100   FORMAT('     NINT   SIMPSON')
101   FORMAT(I9,1PE15.6)

CONTAINS
  DOUBLE PRECISION FUNCTION F(X)
     DOUBLE PRECISION, INTENT(IN) :: X
     F=SIN(X)
     return
  END FUNCTION F
END PROGRAM
24 Jul 2014 2:15 #14358

Mecej4, Thanks very much for the example of a F2003 approach, as I would not have known this could be done without your post. Unfortunately this more scares me, as I find this general change to verbosity and complexity in Fortran to be a sign of extinction. How many new programmers could code that ? Isn't using EXTERNAL a better solution.

I looked more at the problem of what FTN95 is doing, as I think there is a bug for the/check option to fail. I placed an EXTERNAL F statement in Subroutine SIMPSON, but no EXTERNAL in Program main. I compiled with /check /lgo and this initiated SDBG. I then hovered the mouse over the arguments of SIMPSON, which identified that variables A, B INTEGRAL and N were scalar variables, BUT F had no debug information.

Clearly FTN95 identifiers F as something different but why didn't it associate F with the included function for the /check test ? What else could it be as IMPLICIT NONE has been used (twice?) FTN95 did associate the included function F for the release mode.

The error message appears ambiguous as SDBG does identify F to be a procedure in the Program Main, if not a procedure then at least not a variable.

For the alternative of EXTERNAL in Program main and no EXTERNAL in Subroutine Simpson, /check finds no problem, indicating that FTN95 can guess the status of F in the subroutine.

The simple solution is to place an EXTERNAL statement in Program main, (which I think is required even though a contained function of the same name is available ? EXTERNAL would definitely be required if function F was not included). I would also place an EXTERNAL statement in Subroutine Simpson, although I am not sure that this is required. ( I must admit that by the end of this post I am less certain of what the standard requires. )

John

24 Jul 2014 4:25 #14359

John, the F2003 approach using Abstract interfaces really shows its worth when the type of a function used as an actual argument, or the argument list of the function itself, is incorrect. This type of error in Fortran 9X code cannot be detected at compile time, although compilers such as FTN95 and Fujitsu/Lahey are able to emit extra code to catch such errors at run time.

Try the Simpson example again, but this time deliberately declare the type or the argument of F(X) REAL instead of DOUBLE PRECISION. A Fortran 2003 compiler will flag the error at compile time. In our example, F is a simple function of a single variable. When F is a user-defined type, or its argument list is long and complicated, using an abstract interface will save you a lot of grief. EXTERNAL cannot do this, as the attribute simply tells the compiler 'Don't worry about this symbol, let the linker take care of it!' Furthermore, EXTERNAL only declares the procedure name to be global in scope, and is completely ignorant of the number, type and sequence of the list of arguments to that procedure. EXTERNAL is not needed for procedures whose declarations are within the active scope, such as module procedures or contained procedures.

I am sure you have spent more time debugging mismatched subroutine argument lists than you planned to, as have most experienced programmers. Abstract interfaces can save us a lot of time, if we learn about this feature. It does take time to learn to code abstract interfaces, but the ability to catch errors at compile time rather than during run time makes the effort worthwhile.

Those who use C may remember the progression from old 'K&R C' to ANSI C in the 1980s, with function prototype declarations enabling checking for correct function calls at compile time. Abstract interfaces provide more or less the same facility for Fortran, but came a couple of decades later.

24 Jul 2014 5:11 #14360

mecej4,

Thanks for your explanation. For many years my solution to the argument list problem was to use included COMMON then used MODULE, although recently I am returning to libraries of routines with argument lists for data structure flexibility. I always wanted the linker to be able to do an argument count check for routines, although optional arguments can change that. Unfortunately, the linker has never been part of the Fortran Standard.

You said:

EXTERNAL is not needed for procedures whose declarations are within the active scope, such as module procedures or contained procedures.

Doesn't this describe the case we have in this post ? This should imply that EXTERNAL is not required for function F in Program main, as the function is contained in the used module.

John

24 Jul 2014 1:51 #14361

Quoted from JohnCampbell

I always wanted the linker to be able to do an argument count check for routines, although optional arguments can change that.

The STDCALL linkage convention used by Microsoft Fortran, CVF/DVF and others allowed limited checking on the number of arguments. It could not, however, detect errors such as 'call sub(m,n,X)' being written when 'call sub(X,m,n)' should have been used. If, within 'sub' one had 'DIMENSION X(m,n)', you can imagine what can happen at run time.

As you noted, STDCALL could not handle optional arguments, and its usage gave false confidence that subroutine calls had correct argument lists if the linker did not give error messages such as 'XYZ@12 not found'.

24 Jul 2014 5:05 #14362

As well as putting 'EXTERNAL F' in subroutine SIMPSON you can add an interface block. This is the 'pure' Fortran 95 way of doing things.

This has the virtue that the arguments of F (type and intent) will be checked by the compiler.

If 'EXTERNAL F' is used the compiler has no way of knowing whether the arguments expected of F match the calls made in SIMPSON or not.

Note that you can also put 'DOUBLE PRECISION, EXTERNAL :: F' instead of using a separate 'EXTERNAL F'.

Here is the interface block approach (note you need to remove EXTERNAL F from the main program because it is an error).

BTW B = 3.1415926 in the main program should be B = 3.1415926d0 to get the double precision representation of the literal constant 3.1415926.

MODULE M1
IMPLICIT NONE
CONTAINS

FUNCTION F(X)
DOUBLE PRECISION F, X
 F = SIN(X)
RETURN
END FUNCTION F

SUBROUTINE SIMPSON(F,A,B,INTEGRAL,N)
DOUBLE PRECISION F, A, B, INTEGRAL,S
DOUBLE PRECISION H, X
INTEGER NINT
INTEGER N, I

INTERFACE
   FUNCTION F(X)
   DOUBLE PRECISION F, X
   END FUNCTION F
END INTERFACE

IF((N/2)*2.NE.N) N=N+1

S = 0.0
H = (B-A)/DFLOAT(N)
DO I=2, N-2, 2
   X   = A+DFLOAT(I)*H
   S = S + 2.0*F(X) + 4.0*F(X+H)
END DO
INTEGRAL = (S + F(A) + F(B) + 4.0*F(A+H))*H/3.0
RETURN
END SUBROUTINE SIMPSON

END MODULE M1

PROGRAM MAIN
USE M1
IMPLICIT NONE
DOUBLE PRECISION  A, B, INTEGRAL
INTEGER N

A = 0.0
B = 3.1415926
N = 64

WRITE(*,100)
CALL SIMPSON(F,A,B,INTEGRAL,N)
WRITE (*,101) N, INTEGRAL

100   FORMAT('     NINT   SIMPSON')
101   FORMAT(I9,1PE15.6)
END 
24 Jul 2014 7:27 #14363

DavidB: don't you always need the D0 to make constants DOUBLE PRECISION? (FTN95 has a default real type option to do it). I always define PI with 4.0D0*DATAN(1.0D0) in an assignment statement but then I know what that means.

Interface blocks (whether Fortran 2003 [mecej4] abstract ones or plain old Fortran 95 [DavidB] ones) look to me to be a wonderful solution to a problem that I don't have but I can see that other people are likely to have, especially large teams of mixed ability programmers working on the same problem or code. I don't have it because I make strenuous efforts to avoid passing function names as subprogram parameters - although Clearwin+ forces you to do it and is a reason why I didn't use it for years. In fact I never used EXTERNAL until I used Clearwin+ and don't use it for anything else.

Indeed, the original poster didn't need to pass the subprogram name as a parameter, in which case, the compiler would have assumed that F was a function. He only needed to pass the function name if SIMPSON needed to run with other functions, and they could be selected by passing an integer or other code from a predefined list.

Les Hatton and others used to recommend giving named BLOCK DATA routines an EXTERNAL reference somewhere in the program to make sure the linker picks it up, but BLOCK DATA is eschewed now, and using multiple named BLOCK DATA routines is one of those things I always thought was plain weird.

Eddie

24 Jul 2014 7:58 #14364

Quoted from LitusSaxonicum I make strenuous efforts to avoid passing function names as subprogram parameters....

Indeed, the original poster didn't need to pass the subprogram name as a parameter, in which case, the compiler would have assumed that F was a function. He only needed to pass the function name if SIMPSON needed to run with other functions, and they could be selected by passing an integer or other code from a predefined list. Eddie Would you pay for a compiler that restricted you to compiling one selected source code from a repertoire of, say 100, based on an integer between 1 and 100 that you are allowed to choose? Would you pay for a library such as NAG or IMSl if they supplied a library routine that you wanted to use for quadrature, if they restricted you to using one of fifty integrands?

When writing a routine that implements a standard algorithm, we want the implementation to be usable on any problem of the user's choosing as long as that problem fits within the specifications of the problem class. Because these library routines are written and maintained by experts, the typical user should not be required/allowed to use the source code of the library. In such situations, one needs a clean separation between algorithm code and user function code. Subroutine arguments of procedure type allow this separation to be made. We gain breadth in applicability, but there is a small price to pay to make the linkage work correctly.

24 Jul 2014 10:01 #14365

Quoted from LitusSaxonicum DavidB: don't you always need the D0 to make constants DOUBLE PRECISION? (FTN95 has a default real type option to do it). I always define PI with 4.0D0*DATAN(1.0D0) in an assignment statement but then I know what that means. Eddie

Absolutely you do! In this case the other constants are all whole numbers 0.0, 2.0, 3.0, 4.0 so there is no loss of precision converting the REAL values to DOUBLE PRECISION. But as a general rule I would always write 4.0d0 etc if I am programming double precision expressions. You don't need DATAN(1.0D0) of course, you can just used ATAN(1.0D0).

Quoted from LitusSaxonicum

Interface blocks (whether Fortran 2003 [mecej4] abstract ones or plain old Fortran 95 [DavidB] ones) look to me to be a wonderful solution to a problem that I don't have but I can see that other people are likely to have, especially large teams of mixed ability programmers working on the same problem or code.

Sometimes I am writing the code that calls the subroutine or function provided as an argument and 'someone else' is writing the function and the call to my code. By putting my code in a module and using an interface block to define what the function must look like, I can ensure the other person will get a compiler error if they make a mistake (rather than have them pester me about their call not working). Its a form of programming by contract. I make the contract and they have to follow it.

Like you I rarely make a mistake using EXTERNAL when I am programming all parts of the problem, but the extra protection afforded by the interface does no harm and I find provides valuable code documentation when reviewing things months or years on.

24 Jul 2014 10:06 #14366

Quoted from mecej4

When writing a routine that implements a standard algorithm, we want the implementation to be usable on any problem of the user's choosing as long as that problem fits within the specifications of the problem class. Because these library routines are written and maintained by experts, the typical user should not be required/allowed to use the source code of the library. In such situations, one needs a clean separation between algorithm code and user function code. Subroutine arguments of procedure type allow this separation to be made. We gain breadth in applicability, but there is a small price to pay to make the linkage work correctly.

Very true. And having a mechanism to control/check the consistency of arguments passed to the subroutine, including a definition of what the 'user function' must look like, is an important part of this.

1 Aug 2014 3:22 #14382

I think there is a bug in FTN95 when using /check, that needs to be reviewed. With the USE of the module, the CONTAINS function F should not require an EXTERNAL, but the program fails with /check compilation option.

John

1 Aug 2014 9:04 #14383

Can you give an example of the bug you are referring to John?

2 Aug 2014 6:25 #14384

Davidb,

If you take the example I posted : Wed Jul 23, 2014 11:32 am (could be GMT +10hr) and remove the line 50 as : ! EXTERNAL F,C,U ; then you have an example where EXTERNAL should not be required as F, C and U are defined by being contained in M1 ( IMPLICIT NONE confirms this ) I interpreted Mecej4's comments as confirming this.

FTN95 simp.f90 /lgo and FTN95 simp.f90 /debug /lgo both run successfully, but FTN95 simp.f90 /check /lgo fails with an error report that I would suggest is wrong.

Using SDBG and hovering over the function names in 'CALL SIMPSON (' does suggest that these functions are not real variables.

Also, the other use of EXTERNAL at line 26 also does not appear to be required for FTN95, as the use of F is interpreted as a function.

While I would consider the use of EXTERNAL in both cases to be unnecessary, I would still use it as it provides some clarity of definition of the use of these functions, as is my continued use of IMPLICIT NONE.

John

2 Aug 2014 1:27 #14389

John,

You are correct. If there is a use statement which defines a function or subroutine, it is non-standard conforming to also use an external statement. It would be good if FTN95 could provide an error or warning about such cases but I would suggest there are other more important bugs to squash.

Please login to reply.