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

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

PURE

Keyword: Asserts that a user-defined procedure has no side effects.

Description

This kind of procedure is specified by using the prefix PURE or the prefix ELEMENTAL without the prefix IMPURE in a FUNCTION or SUBROUTINE statement.

A pure procedure has no side effects. It has no effect on the state of the program, except for the following:

  • For functions: It returns a value.

  • For subroutines: It modifies INTENT(OUT) and INTENT(INOUT) parameters.

The following intrinsic and library procedures are implicitly pure:

  • All intrinsic functions

  • The elemental intrinsic subroutine MVBITS

  • The intrinsic subroutine MOVE_ALLOC

  • Intrinsic module procedures that are specified to be pure

A dummy argument or a procedure pointer may be specified to be pure. A type-bound procedure that is bound to a pure procedure is also pure.

A statement function is pure only if all functions that it references are pure and its definition does not reference any data object with the VOLATILE attribute.

Except for procedure arguments and pointer arguments, the following intent must be specified in the specification part of the procedure for all dummy arguments:

  • For functions: INTENT(IN) or the VALUE attribute

  • For subroutines: any INTENT (IN, OUT, or INOUT) or the VALUE attribute

A local variable declared in a pure procedure (including variables declared in any internal procedure) must not:

  • Specify the SAVE attribute

  • Specify the VOLATILE attribute

  • Be initialized in a type declaration statement or a DATA statement

The following variables have restricted use in pure procedures (and any internal procedures):

  • Global variables

  • Dummy arguments with INTENT(IN)

  • Dummy arguments with no declared intent that do not have the VALUE attribute

  • Objects that are storage associated with any part of a global variable

They must not be used in any context that does either of the following:

  • Causes their value to change. For example, they must not be used as:

    • The left side of an assignment statement or pointer assignment statement

    • An actual argument associated with a dummy argument with INTENT(OUT), INTENT(INOUT), or the POINTER attribute

    • An index variable in a DO or FORALL statement, or an implied-DO clause

    • The variable in an ASSIGN statement

    • An input item in a READ statement

    • An internal file unit in a WRITE statement

    • An object in an ALLOCATE, DEALLOCATE, or NULLIFY statement

    • An IOSTAT or SIZE specifier in an I/O statement, the STAT specifier in a ALLOCATE, DEALLOCATE, or image control statement, or as the STAT argument to the intrinsic MOVE_ALLOC or a collective or atomic intrinsic subroutine.

  • Creates a pointer to that variable. For example, they must not be used as:

    • The target in a pointer assignment statement

    • The right side of an assignment to a derived-type variable (including a pointer to a derived type) if the derived type has a pointer component at any level

    • The actual argument to the C_LOC function defined in the intrinsic module ISO_C_BINDING

A pure procedure must not contain the following:

  • Any external I/O statement (including a READ or WRITE statement whose I/O unit is an external file unit number or *)

  • A PAUSE statement

  • A STOP statement

  • An image control statement

  • An OpenMP* directive that is not a PURE directive

A pure procedure can be used in contexts where other procedures are restricted; for example:

  • It can be called directly in a FORALL statement or be used in the mask expression of a FORALL statement.

  • It can be called from a pure procedure. Pure procedures can only call other pure procedures, including one referenced by means of a defined operator, defined assignment, or finalization.

  • It can be passed as an actual argument to a pure procedure.

If a procedure is used in any of these contexts, its interface must be explicit and it must be declared pure in that interface.

Example

Consider the following:

PURE FUNCTION DOUBLE(X)
  REAL, INTENT(IN) :: X
  DOUBLE = 2 * X
END FUNCTION DOUBLE

The following shows another example:

PURE INTEGER FUNCTION MANDELBROT(X)
  COMPLEX, INTENT(IN) :: X
  COMPLEX__:: XTMP
  INTEGER__:: K
  ! Assume SHARED_DEFS includes the declaration
  ! INTEGER ITOL
  USE SHARED_DEFS

  K = 0
  XTMP = -X
  DO WHILE (ABS(XTMP) < 2.0 .AND. K < ITOL)
    XTMP = XTMP**2 - X
    K = K + 1
  END DO
  MANDELBROT = K
END FUNCTION

The following shows the preceding function used in an interface block:

INTERFACE
  PURE INTEGER FUNCTION MANDELBROT(X)
    COMPLEX, INTENT(IN) :: X
  END FUNCTION MANDELBROT
END INTERFACE

The following shows a FORALL construct calling the MANDELBROT function to update all the elements of an array:

FORALL (I = 1:N, J = 1:M)
  A(I,J) = MANDELBROT(COMPLX((I-1)*1.0/(N-1), (J-1)*1.0/(M-1))
END FORALL