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

ID 767251
Date 9/08/2022
Public

A newer version of this document is available. Customers should click here to go to the newest version.

Document Table of Contents

Variable-Definition Context

A variable can appear in different contexts that imply definition or undefinition of the variable. A reference to a function that returns a data pointer is permitted in such variable-definition contexts.

When a function returns a data pointer, that pointer is always associated with a variable that has the TARGET attribute, either by pointer assignment or by allocation. If a reference to a function that returns a data pointer appears in a variable-definition context, the definable target (with which the function result is associated) is the variable that becomes defined or undefined.

This section describes the different variable-definition contexts in which a function reference returning a data pointer can be used. It also describes the contexts in which data pointer function references are not allowed.

Assignment Statement

Function references returning a data pointer can be used on the left-hand side of an assignment statement. References to type bound and generic procedures are also permitted on the left-hand side of an intrinsic assignment. If the variable on the left-hand side is polymorphic, it must be an allocatable. Therefore, a function returning a polymorphic pointer cannot be used on the left-hand side.

In the following example, function STORAGE returns a data pointer to either the module variable OUTSIDE or to an element of VAR into which a value is stored:

MODULE TMOD
 PUBLIC

 INTEGER, PARAMETER :: N = 10
 INTEGER, TARGET    :: VAR(N)
 INTEGER, TARGET    :: OUTSIDE
 CONTAINS
 FUNCTION STORAGE(KEY) RESULT(LOC)
   INTEGER, INTENT(IN) :: KEY
   INTEGER, POINTER    :: LOC

   IF( KEY .LT. 1 .OR. KEY .GE. N ) THEN
     LOC=> OUTSIDE
   ELSE
     LOC => VAR(KEY)
   ENDIF
 END FUNCTION
END MODULE

PROGRAM MAIN
  USE TMOD
  OUTSIDE = -1
  STORAGE(1) = 11
  STORAGE(0) = 0
  PRINT *, VAR(1), OUTSIDE    ! prints 11, 0
END

The following example shows generic resolution on the left-hand side of an assignment statement:

MODULE MYMODULE
    TYPE :: VEC
        INTEGER :: X(3)
    CONTAINS        
        GENERIC   :: GET => GETELEMENT, GETARRAY
        PROCEDURE :: GETELEMENT
        PROCEDURE :: GETARRAY 
    END TYPE VEC
    CONTAINS
        FUNCTION GETELEMENT( THIS, EL ) RESULT( P )
            IMPLICIT NONE
            CLASS(VEC), TARGET :: THIS
            INTEGER, INTENT(IN) :: EL
            INTEGER, POINTER :: P
            P => THIS%X(EL)
        END FUNCTION GETELEMENT
        
        FUNCTION GETARRAY( THIS ) RESULT( P )
            IMPLICIT NONE
            CLASS(VEC), TARGET :: THIS            
            INTEGER, POINTER :: P(:) ! array pointer
            P => THIS%X
        END FUNCTION GETARRAY
END MODULE MYMODULE

PROGRAM TEST
   USE MYMODULE
   IMPLICIT NONE
   TYPE(VEC) :: MYVEC
   INTEGER   :: Y(3)
   MYVEC%X = [1,2,3]
   Y = [6,7,8]

   ! expected output 1 2 1 2 3
   WRITE(6,*) MYVEC%GET(1), MYVEC%GET(2), MYVEC%GET()

   ! change any array element 
   MYVEC%GET(1) = 4
   MYVEC%GET(2) = 5
   MYVEC%GET(3) = 6

   ! check modified values
   ! expected output 4 5 4 5 6
   WRITE(6,*) MYVEC%GET(1), MYVEC%GET(2), MYVEC%GET()

   MYVEC%GET() = Y          ! array pointer returned

   ! check modified values
   WRITE(6,*)  MYVEC%GET()  ! expected output 6 7 8
END PROGRAM TEST

Argument Association

A function reference returning a data pointer can be used as an actual argument in a reference to a procedure with an explicit interface. If the corresponding dummy argument has the INTENT (OUT) or INTENT (INOUT) attribute, then the pointer function is used in a variable definition context.

The following example uses the function STORAGE, which was defined in the above section "Assignment Statement":

FUNCTION STORAGE(KEY) RESULT(LOC)
   INTEGER, INTENT(IN) :: KEY
   INTEGER, POINTER    :: LOC
..
END FUNCTION
..
STORAGE(2) = 10  
CALL CHANGE_VAL(STORAGE(2)) ! pass storage(2) as actual argument 
PRINT *, VAR(2)             ! prints 50
..
SUBROUTINE CHANGE_VAL(X)
  INTEGER, INTENT(OUT) :: X
  X = X*5    
END SUBROUTINE CHANGE_VAL

The following example shows that the target of the function pointer can get modified inside the subroutine without using the dummy argument corresponding to the function reference:

  MODULE M200C2
    INTEGER, TARGET :: X = 42
  CONTAINS
    FUNCTION FX()
      INTEGER, POINTER :: FX
      FX => X
    END FUNCTION
  END MODULE

  PROGRAM Q1
    USE M200C2
    CALL TEST(X, FX())
    ! note that corresponding dummy is not INTENT (OUT) or INTENT(INOUT).  
    ! FX() is not used in a variable definition context but it still
    !   denotes a variable.
    CONTAINS
    SUBROUTINE TEST(A, B)
    INTEGER, TARGET :: B             
      A = A*10
      PRINT *, A, B                !  prints 420 420
    END SUBROUTINE
  END PROGRAM

SELECT RANK, SELECT TYPE, and ASSOCIATE Construct

A pointer function reference can appear as a variable that is the selector in a SELECT RANK, SELECT TYPE, or ASSOCIATE construct and the associate name of that construct can appear in a variable-definition context. For example:

PROGRAM MAIN 
    INTEGER, TARGET :: DATA = 123 

    ASSOCIATE (ALIAS => FX1()) 
        ALIAS = 456 
        PRINT *, ALIAS, DATA     ! prints 456 456
    END ASSOCIATE 

    SELECT TYPE (ALIAS =>FX2())
        TYPE IS (INTEGER)
          ALIAS = 789
          PRINT *, ALIAS, DATA   ! prints 789 789
    END SELECT

    CONTAINS 
    FUNCTION FX1() 
        INTEGER, POINTER :: FX1
        FX1 => DATA 
    END FUNCTION FX1 
    FUNCTION FX2()
        CLASS(*),POINTER :: FX2
        FX2 => DATA
    END FUNCTION FX2
END PROGRAM MAIN

In the following example, FX() in the ASSOCIATE is a variable and every reference to ALIAS is a reference to the associated variable, so the assignment also changes the value of ALIAS:

PROGRAM MAIN 
    INTEGER, TARGET :: DATA = 123 

    ASSOCIATE (ALIAS => FX1()) 
        DATA = 0 
        PRINT *, ALIAS, DATA     ! prints 0 0
    END ASSOCIATE 

    SELECT TYPE (ALIAS => FX2())
        TYPE IS (INTEGER)
          DATA = 1
          PRINT *, ALIAS, DATA   ! prints 1 1
    END SELECT

    CONTAINS 
    
    FUNCTION FX1 () 
        INTEGER, POINTER :: FX1 
        FX1 => DATA 
    END FUNCTION FX1 

    FUNCTION FX2()
        CLASS(*),POINTER :: FX2
        FX2 => DATA
    END FUNCTION FX2

END PROGRAM MAIN

Input/Output Statements

A pointer function reference can be used as an input item in a READ statement.

A function reference returning a character pointer can be used as an internal file variable in a WRITE statement.

A scalar integer pointer function reference can be an IOSTAT= or a SIZE= specifier in an input/output statement. A scalar character pointer function reference can be an IOMSG= specifier in an input/output statement.

A function returning a scalar pointer, whose datatype matches the specifier, can be specified in an INQUIRE statement except for the three specifiers FILE=, ID=, and UNIT=.

A function returning a scalar integer pointer can be a NEWUNIT= specifier in an OPEN statement.

Consider the following example:

...
    CHARACTER(50), TARGET :: V(33)
    INTEGER, TARGET :: I
    ..
    FUNCTION RET_CHAR(INDEX) RESULT (DCV)
      CHARACTER(50), POINTER :: DCV
      INTEGER :: INDEX
      DCV => V(INDEX)
    END FUNCTION
    FUNCTION RET_INT() RESULT (P)
      INTEGER, POINTER :: P
      P => I
    END FUNCTION
  ...
! an input item in a read stmt
    READ (6, *) RET_INT()
    READ  10, RET_INT()

! an internal file variable in a write stmt  
    WRITE  (RET_CHAR(10), FMT=*) 666

! an IOSTAT=, SIZE=, or IOMSG= specifier in an I/O statement
    READ (10, FMT=*, IOSTAT=RET_INT(), SIZE=RET_INT(), &   
          IOMSG=RET_CHAR(6) ) STR

! a specifier in an inquire statement except FILE=, ID=, and UNIT=
    OPEN(NEWUNIT = NUM, FILE = 'A.TXT', ACTION = 'READ')    
    INQUIRE(NUM,               &
    ACCESS = RET_CHAR(2),      &
    EXIST = RET_CHAR(10),      &
    ID = 13,                   &
    IOSTAT = RET_CHAR(14),     & 
    SIZE = RET_CHAR(30))      
    CLOSE(NUM, STATUS = 'DELETE')

! a NEWUNIT= SPECIFIER in an OPEN statement
    OPEN(NEWUNIT = RET_INT(1), STATUS = 'SCRATCH')
    CLOSE(RET_INT(1), STATUS = 'DELETE') ! allowed on CLOSE

STAT=, ERRMSG=, and ACQUIRED_LOCK= Specifiers and STAT and ERRMSG Arguments to Intrinsic Procedures

A scalar integer pointer function reference can be used as a STAT= variable. A scalar character pointer function reference can be used as an ERRMSG= variable.

STAT= and ERRMSG= are allowed in CHANGE TEAM, END TEAM, CRITICAL, EVENT POST, EVENT WAIT, FORM TEAM, SYNC ALL, SYNC IMAGES, SYNC MEMORY, SYNC TEAM, LOCK, UNLOCK, ALLOCATE, and DEALLOCATE statements.

A STAT= specifier is allowed in an image selector. Collective and atomic procedures have an optional STAT argument, and the MOVE_ALLOC intrinsic has optional STAT and ERRMSG arguments.

A scalar logical pointer function reference can be an ACQUIRED_LOCK= specifier in a LOCK statement.

The following example uses RET_CHAR and RET_INT, which were defined in the above section "Input/Output Statements":


    TYPE(EVENT_TYPE) :: ET[*] 
    TYPE(LOCK_TYPE) :: LT[*]    
    INTEGER, POINTER     :: AR(:)
    ALLOCATE(AR(2), STAT=RET_INT())   
    DEALLOCATE(AR, STAT=RET_INT())   
 
    EVENT POST (EV[THIS_IMAGE() + 1], STAT=RET_INT(), ERRMSG=RET_CHAR())
    EVENT WAIT(EV, STAT=RET_INT(), ERRMSG=RET_CHAR())
    LOCK(LT, ACQUIRED_LOCK=GET_LOGICAL(), STAT=RET_INT(), &
    ERRMSG=RET_CHAR()) 
    UNLOCK(LT, STAT=RET_INT(), ERRMSG=RET_CHAR())    
    SYNC IMAGES(*,STAT=RET_INT(), ERRMSG=RET_CHAR())    
    SYNC ALL(STAT=RET_INT(), ERRMSG=RET_CHAR())    
    SYNC MEMORY(STAT=RET_INT(), ERRMSG=RET_CHAR())    

Execution of EVENT POST and EVENT WAIT statements

An event variable of type EVENT_TYPE from the ISO_FORTRAN_ENV module becomes defined by the successful execution of an EVENT POST or an EVENT WAIT statement.

Execution of a FORM TEAM statement

A team variable of type TEAM_TYPE from the intrinsic module ISO_FORTRAN_ENV becomes defined by the successful execution of a FORM TEAM statement.

Execution of a LOCK or UNLOCK statement

A lock variable of LOCK_TYPE from the ISO_FORTRAN_ENV module becomes defined by the successful execution of an UNLOCK statement, or a LOCK statement without an ACQUIRED_LOCK= specifier. Successful execution of a LOCK statement with an ACQUIRED_LOCK= specifier causes the specified logical variable to become defined. If it is defined with the value true, the lock variable in the LOCK statement also becomes defined.

Disallowed Contexts

The Fortran Standard defines both a "variable" and a "variable name". For function F, F is a variable name; F(7) is a function. If F returns a data pointer, F(7) is a variable and can be used in a variable-definition context.

For the following variable-definition contexts, the Fortran Standard specifies that a "variable name" must be used and not a "variable":

  • The pointer object in a NULLIFY statement

  • A data pointer object or procedure pointer object in a pointer assignment statement

  • The DO variable in a DO statement or an implied DO construct

  • A variable name in a NAMELIST statement if the NAMELIST group name appears in a NML= specifier in a READ statement

  • The object in an ALLOCATE or DEALLOCATE statement

  • An event variable in an EVENT POST or EVENT WAIT statement

  • The lock variable in a LOCK or UNLOCK statement

A function reference can return a pointer to any data object, even one that cannot be stored into, for example, a USE associated PROTECTed object or a constant. This will not be caught at compile time. It is possible that the target of the pointer function is a local variable from a different subprogram or a private USE associated variable, in which case the pointer returned has an undefined association status.

A More Complex Example

The following example has pointer functions that return data pointers to parameterized derived type objects. The pointer function results are automatic objects whose length type parameters depend on the dummy arguments:

MODULE TMOD
  PUBLIC
  TYPE PDT(K, L)
    INTEGER, KIND :: K
    INTEGER, LEN :: L
    INTEGER :: FIELD(L)
  END TYPE PDT    
END MODULE
PROGRAM MAIN 
    USE TMOD
    IMPLICIT NONE     
    TYPE(PDT(4,2)), TARGET :: PDTOBJ1, OBJ
    TYPE(PDT(2,2)), POINTER :: ACTARG
    CHARACTER(10), TARGET :: C1
    
    BAR() = PDT(4,2)((/5,3/))
    PRINT *, PDTOBJ1%FIELD            ! prints 5 3
        
    AUTO_RES(ACTARG) = PDT(4,2)((/6,4/))
    PRINT *, PDTOBJ1%FIELD            ! prints 6 4
    
    AUTO_CHAR(10) = "TEST"
    PRINT *, C1                       ! prints TEST
    CONTAINS                   
    FUNCTION BAR() RESULT(LOC)
        TYPE(PDT(4,2)), POINTER :: LOC
        LOC => PDTOBJ1
    END FUNCTION
    FUNCTION AUTO_CHAR(DUM1) RESULT(LOC)
         INTEGER, INTENT(IN) :: DUM1
         CHARACTER(DUM1), POINTER :: LOC
         LOC => C1
    END FUNCTION
        
    FUNCTION AUTO_RES(DUM1) RESULT(LOC)
         TYPE(PDT(4,:)), POINTER, INTENT(IN) :: DUM1
         TYPE(PDT(4,DUM1%L)), POINTER :: LOC
         LOC => PDTOBJ1
    END FUNCTION
END PROGRAM