Intel® Fortran Compiler Classic and Intel® Fortran Compiler Developer Guide and Reference

ID 767251
Date 3/22/2024
Public
Document Table of Contents

FUNCTION

Statement: The initial statement of a function subprogram. A function subprogram is invoked in an expression and returns a single value (a function result) that is used to evaluate the expression.

[prefix [prefix]] FUNCTION name [([d-arg-list])] [suffix]

   [specification-part]

   [execution-part]

[CONTAINS

   [internal-subprogram-part]]

END [FUNCTION [name]]

prefix

(Optional) Is any of the following:

  • A data type specifier

  • ELEMENTAL

    Acts on one array element at a time. This is a restricted form of pure procedure.

  • IMPURE

    Asserts that the procedure has side effects.

  • MODULE

    Indicates a separate module procedure. See separate module procedures.

  • NON_RECURSIVE

    Indicates the function is not recursive.

  • PURE

    Asserts that the procedure has no side effects.

  • RECURSIVE

    Permits direct and indirect recursion to occur. If a function is directly recursive and array valued, and RESULT is not specified, any reference to the function name in the executable part of the function is a reference to the function result variable.

At most one of each of the above can be specified. You cannot specify both NON_RECURSIVE and RECURSIVE. You cannot specify both PURE and IMPURE. You cannot specify ELEMENTAL if lang-binding is specified in suffix.

name

Is the name of the function. If RESULT is specified, the function name must not appear in any specification statement in the scoping unit of the function subprogram.

The function name can be followed by the length of the data type. The length is specified by an asterisk (*) followed by any unsigned, nonzero integer that is a valid length for the function's type. For example, REAL FUNCTION LGFUNC*8 (Y, Z) specifies the function result as REAL(8) (or REAL*8).

This optional length specification is not permitted if the length has already been specified following the keyword CHARACTER.

d-arg-list

(Optional) Is a list of one or more dummy arguments.

If there are no dummy arguments, no suffix, and no RESULT variable, the parentheses can be omitted. For example, the following is valid:

  FUNCTION F

suffix

(Optional) Takes one of the following forms:

[RESULT (r-name)] lang-binding

lang-binding [RESULT (r-name)]

r-name

(Optional) Is the name of the function result. This name must not be the same as the function name.

lang-binding

Takes the following form:

BIND (C [, NAME=ext-name])

ext-name

Is a character scalar constant expression that can be used to construct the external name.

specification-part

Is one or more specification statements.

execution-part

Is one or more executable constructs or statements.

internal-subprogram-part

Is one or more internal subprograms (defining internal procedures). The internal-subprogram-part is preceded by a CONTAINS statement.

Description

The type and kind parameters (if any) of the function's result can be defined in the FUNCTION statement or in a type declaration statement within the function subprogram, but not both. If no type is specified, the type is determined by implicit typing rules in effect for the function subprogram.

Execution begins with the first executable construct or statement following the FUNCTION statement. Control returns to the calling program unit once the END statement (or a RETURN statement) is executed.

If you specify CHARACTER(LEN=*) as the type of the function, the function assumes the length declared for it in the program unit that invokes it. This type of the resulting character function can have different lengths when it is invoked by different program units. An assumed-length character function cannot be directly recursive.

If the character length is specified as an integer constant, the value must agree with the length of the function specified in the program unit that invokes the function. If no length is specified, a length of 1 is assumed.

If the function is array-valued or a pointer, the declarations within the function must state these attributes for the function result name. The specification of the function result attributes, dummy argument attributes, and the information in the procedure heading collectively define the interface of the function.

The value of the result variable is returned by the function when it completes execution. Certain rules apply depending on whether the result is a pointer, as follows:

  • If the result is a pointer, its allocation status must be determined before the function completes execution. The function must associate a target with the pointer, or cause the pointer to be explicitly disassociated from a target.

    If the pointer result points to a TARGET with the INTENT(IN) attribute, the function can give the result a value but the caller is not allowed to change the value pointed to.

  • The shape of the value returned by the function is determined by the shape of the result variable when the function completes execution.

  • If the result is not a pointer, its value must be defined before the function completes execution. If the result is an array, all the elements must be defined. If the result is a derived-type structure, all the components must be defined.

A function subprogram cannot contain a BLOCK DATA statement, a PROGRAM statement, a MODULE statement, or a SUBMODULE statement. A function can contain SUBROUTINE and FUNCTION statements to define internal procedures. ENTRY statements can be included to provide multiple entry points to the subprogram.

Example

The following example uses the Newton-Raphson iteration method (F(X) = cosh(X) + cos(X) - A = 0) to get the root of the function:


  FUNCTION ROOT(A)
    IF (A >= 2.0) THEN
      X  = 1.0
      DO
        EX = EXP(X)
        EMINX = 1./EX
        ROOT  = X - ((EX+EMINX)*.5+COS(X)-A)/((EX-EMINX)*.5-SIN(X))
        IF (ABS((X-ROOT)/ROOT) .LT. 1E-6) RETURN
        X  = ROOT
      END DO
    ELSE
      STOP 'in FUNCTION ROOT, A must be >= 2.0'
    ENDIF
  END

In the preceding example, the following formula is calculated repeatedly until the difference between Xi and Xi+1 is less than 1.0E-6:

The following example shows an assumed-length character function:


  CHARACTER*(*) FUNCTION REDO(CARG)
    CHARACTER*1 CARG
    DO I=1,LEN(REDO)
      REDO(I:I) = CARG
    END DO
    RETURN
  END FUNCTION

This function returns the value of its argument, repeated to fill the length of the function.

Within any given program unit, all references to an assumed-length character function must have the same length. In the following example, the REDO function has a length of 1000:

  CHARACTER*1000 REDO, MANYAS, MANYZS
  MANYAS = REDO('A')
  MANYZS = REDO('Z')

Another program unit within the executable program can specify a different length. For example, the following REDO function has a length of 2:

  CHARACTER HOLD*6, REDO*2
  HOLD = REDO('A')//REDO('B')//REDO('C')

The following example shows a dynamic array-valued function:

  FUNCTION SUB (N)
    REAL, DIMENSION(N) :: SUB
    ...
  END FUNCTION

The following shows another example:

      INTEGER Divby2
10    PRINT *, 'Enter a number'
      READ *, i
      Print *, Divby2(i)
      GOTO 10
      END
C
C     This is the function definition
C
      INTEGER FUNCTION Divby2 (num)
      Divby2=num / 2
      END FUNCTION

The following example shows an allocatable function with allocatable arguments:

MODULE AP
CONTAINS

 FUNCTION ADD_VEC(P1,P2)
  ! Function to add two allocatable arrays of possibly differing lengths.
  ! The arrays may be thought of as polynomials (coefficients)
   REAL, ALLOCATABLE :: ADD_VEC(:), P1(:), P2(:)

  ! This function returns an allocatable array whose length is set to
  ! the length of the larger input array.
  ALLOCATE(ADD_VEC(MAX(SIZE(P1), SIZE(P2))))
  M = MIN(SIZE(P1), SIZE(P2))
  ! Add up to the shorter input array size
  ADD_VEC(:M) = P1(:M) + P2(:M)
  ! Use the larger input array elements afterwards (from P1 or P2)
  IF(SIZE(P1) > M) THEN
    ADD_VEC(M+1:) = P1(M+1:)
  ELSE IF(SIZE(P2) > M) THEN
    ADD_VEC(M+1:) = P2(M+1:)
  ENDIF
 END FUNCTION
END MODULE

PROGRAM TEST
 USE AP
 REAL, ALLOCATABLE :: P(:), Q(:), R(:), S(:)
 ALLOCATE(P(3))
 ALLOCATE(Q(2))
 ALLOCATE(R(3))
 ALLOCATE(S(3))

 ! Notice that P and Q differ in length
 P = (/4,2,1/)  ! P = X**2 + 2X + 4
 Q = (/-1,1/)   ! Q =         X - 1
 PRINT *,' Result should be:    3.000000       3.000000       1.000000'
 PRINT *,' Coefficients are: ', ADD_VEC(P, Q)  ! X**2 + 3X + 3

 P = (/1,1,1/)  ! P =  X**2 +  X + 1
 R = (/2,2,2/)  ! R = 2X**2 + 2X + 2
 S = (/3,3,3/)  ! S = 3X**2 + 3X + 3
 PRINT *,' Result should be:    6.000000       6.000000       6.000000'
 PRINT *,' Coefficients are: ', ADD_VEC(ADD_VEC(P,R), S)
END

Consider the following example:

module mymodule
type :: vec
  integer :: x(3) 
contains
  procedure :: at 
end type vec

contains
  function at( this, i ) result( p )
    implicit none
    class(vec), intent(in), target :: this
    integer, intent(in) :: i
    integer, pointer :: p

    p => this%x(i)
  end function at
end module mymodule

program test
use mymodule
implicit none
type(vec) :: myvec

myvec%x =  [1,2,3]

! pointer returned by function at gives the correct values: 1, 2, and 3
write(6,*) myvec%at(1), myvec%at(2), myvec%at(3)

! changing any array element is an error
myvec%at(1) = 4
myvec%at(2) = 5
myvec%at(3) = 6
…
end program test