next up previous contents
Next: Required Interfaces Up: Procedure Interfaces Previous: Explicit Interfaces for Internal   Contents

Explicit Interfaces for External Procedures

In F90 ``it is possible, often essential and wholly desirable'' to provide explicit block interfaces whenever external procedures are used.

An interface declaration of an external procedure is initiated by INTERFACE statement and terminated by END INTERFACE. The declaration specifies the attributes of the dummy arguments and the procedure - it is in fact the whole procedure, without the local declarations and the executable code. An interface that is part of the declarations sequence is called ``explicit''.

For example, consider the sorting function. If the function is internal to the main program we have an explicit interface, but we lose modularity. With block interface, the routine can be in a different place (different file, or different library) and still have explicit interface.

PROGRAM impint SUBROUTINE sort(iv,n,how)
IMPLICIT NONE INTEGER, DIMENSION(:), &
INTERFACE INTENT(IN) :: iv(:)
  SUBROUTINE sort(iv,n,how) INTEGER, INTENT(IN) :: n
  INTEGER, DIMENSION(:), & INTEGER, INTENT(INOUT) :: how
  INTENT(IN) :: iv(:) INTEGER :: i, j, tmp, iperm
  INTEGER, INTENT(IN) :: n iperm = 0
  INTEGER, INTENT(INOUT) :: how DO i=1,n
  END SUBROUTINE sort DO j=i,n
END INTERFACE   IF (how.EQ.-1.AND.iv(i).LT.iv(j).OR.&
INTEGER, PARAMETER :: n=4   how.EQ.1.AND.iv(i).GT.iv(j)) THEN
INTEGER, DIMENSION(n) :: iv   tmp = iv(i); iv(i) = iv(j)
INTEGER :: iw, how   iv(j) = tmp; iperm=iperm+1
iv=(/3,1,4,2/)   END IF
how = -1 END DO
CALL sort(iv, n, how) END DO
PRINT *, iv(1:n), how how = iperm
END PROGRAM impint END SUBROUTINE sort

If the subroutine sort is called from different program units, then a copy of the bloc interface should be included in the declaration sequence of each caller. If at a later time we decide to modify the interface, all these copies need to be updated. A way to circumvent these drawbacks is to write the block interface once, in a module, then to USE the module in all units that call the subroutine. For example, we may have

PROGRAM impint MODULE sort_interf
USE sort_interf INTERFACE
IMPLICIT NONE  SUBROUTINE sort(iv,n,how)
INTEGER, PARAMETER :: n=4  INTEGER, DIMENSION(:), &
INTEGER, DIMENSION(n) :: iv  INTENT(IN):: iv(:)
INTEGER :: iw, how  INTEGER, INTENT(IN) :: n
iv=(/3,1,4,2/); how = -1  INTEGER, INTENT(INOUT):: how
CALL sort(iv, n, how)  END SUBROUTINE sort
PRINT *, iv(1:n), how END INTERFACE
END PROGRAM impint END MODULE sort_interf

When the compiler performs the consistency checks for the argument list, it verifies that the actual arguments match (in number, type and order) the dummy arguments provided by the block interface declaration (and not the dummy arguments of the procedure itself!). Therefore, if there is a mismatch between the interface arguments and the procedure arguments, the compiler is fed wrong information, and a run time error may occur.

A direct way to provide an explicit interface for a procedure, without writing a block interface, is to write a module which hosts the procedure itself, then USE this module in all the program units that call the procedure. For our example, this can be achieved as follows.

PROGRAM impint MODULE sort_code
USE sort_code CONTAINS
IMPLICIT NONE  SUBROUTINE sort(iv,n,how)
INTEGER, PARAMETER :: n=4  INTEGER, DIMENSION(:), &
INTEGER, DIMENSION(n) :: iv  INTENT(IN):: iv(:)
INTEGER :: iw, how  INTEGER, INTENT(IN) :: n
iv=(/3,1,4,2/); how = -1  INTEGER, INTENT(INOUT):: how
CALL sort(iv, n, how)
PRINT *, iv(1:n), how  END SUBROUTINE sort
END PROGRAM impint END MODULE sort_code

Consider the TEST_SCOPE program, but now with MY_SUM an explicit procedure. We declare the interface as follows:
program test_scope
implicit none
interface
subroutine my_sum(a,b,c)
integer, intent(in) :: a,b
integer, intent(out) :: c
end subroutine my_sum
end interface
integer :: i=1, j=2, k=3, glb=4, loc=5
call my_sum(i,j,k)
end program test_scope

Since

we need to write explicit interfaces for external procedures only.

Note that an explicit interface and the EXTERNAL attribute cannot be used simultaneously; this is no problem, since INTERFACEd procedures can be used as actual arguments.


next up previous contents
Next: Required Interfaces Up: Procedure Interfaces Previous: Explicit Interfaces for Internal   Contents
Adrian Sandu 2001-08-26