Elemental procedures

An elemental procedure is an elemental intrinsic procedure or an elemental subprogram that has the ELEMENTAL prefix specifier. If the ELEMENTAL prefix specifier is used, the RECURSIVE specifier cannot be used.

You cannot use the -qrecur option when you specify elemental procedures.

An elemental subprogram is a pure subprogram unless it has the Fortran 2008 beginsIMPUREFortran 2008 ends prefix specifier.

Elemental procedures must conform to the following rules:
  • The result of an elemental function must be a scalar, and must not have the Fortran 2003 beginsALLOCATABLE or Fortran 2003 ends POINTER attribute.
  • The following apply to dummy arguments used in elemental subprograms:
    • All dummy arguments must be scalar data objects and must not have the Fortran 2003 beginsALLOCATABLE or Fortran 2003 ends POINTER attribute.
    • The result of an elemental function must be scalar and must not have the Fortran 2003 beginsALLOCATABLE or Fortran 2003 ends POINTER attribute.
    • If a dummy argument is the base object of an object designator that appears in the specification expression that specifies a type parameter value of the result of the elemental function, the object designator must appear only as the subject of a specification inquiry, and the inquiry must not depend on a property that is deferred.
    • A dummy argument cannot be an asterisk.
    • Fortran 2008 beginsA dummy argument that does not have the VALUE attribute must have the INTENT attribute specified.Fortran 2008 ends
  • Elemental subprograms can have ENTRY statements, but the ENTRY statement cannot have the ELEMENTAL prefix. The procedure defined by the ENTRY statement is elemental if the ELEMENTAL prefix is specified in the SUBROUTINE or FUNCTION statement.
  • Elemental procedures can be used as defined operators in elemental expressions, but they must follow the rules for elemental expressions as described in Operators and expressions.
In a reference to an elemental procedure, the following rules apply:
  • If any actual argument is an array, every actual argument that corresponds to an INTENT(OUT) or INTENT(INOUT) dummy argument must be an array.
  • All actual arguments must be conformable.
In a reference to an elemental function, the following rules apply:
  • The shape of the result is the same as the shape of the actual argument with the greatest rank.
  • If there are no actual arguments or all the actual arguments are scalars, the result is scalar.

If any actual argument of an elemental procedure is an array, the value of the elements, if any, of the results are the same as would be obtained if the procedure had been applied separately, in the element order, to the corresponding elements of each array actual argument.

Examples

Example 1:

! Example of an elemental function
PROGRAM P
INTERFACE
  ELEMENTAL REAL FUNCTION LOGN(X,N)
     REAL, INTENT(IN) :: X
     INTEGER, INTENT(IN) :: N
  END FUNCTION LOGN
END INTERFACE

REAL RES(100), VAL(100,100)
  ...
DO I=1,100
   RES(I) = MAXVAL( LOGN(VAL(I,:),2) )
END DO
    ...
END PROGRAM P

Example 2:

! Elemental procedure declared with a generic interface
INTERFACE RAND
   ELEMENTAL FUNCTION SCALAR_RAND(x)
     REAL, INTENT(IN) :: X
   END FUNCTION SCALAR_RAND

   FUNCTION VECTOR_RANDOM(x)
     REAL X(:)
     REAL VECTOR_RANDOM(SIZE(x))
   END FUNCTION VECTOR_RANDOM
END INTERFACE RAND

REAL A(10,10), AA(10,10)

! The actual argument AA is a two-dimensional array. The procedure
! taking AA as an argument is not declared in the interface block.
! The specific procedure SCALAR_RAND is then called.

A = RAND(AA)


! The actual argument is a one-dimensional array section. The procedure
! taking a one-dimensional array as an argument is declared in the
! interface block. The specific procedure VECTOR_RANDOM is then called.
! This is a non-elemental reference since VECTOR_RANDOM is not elemental.

A(:,1) = RAND(AA(6:10,2))
END 


Voice your opinion on getting help information Ask IBM compiler experts a technical question in the IBM XL compilers forum Reach out to us