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

Recursive Defined I/O

A defined I/O procedure can invoke itself indirectly.

It can have an I/O statement that includes a derived-type object that results in the invocation of the same procedure. In this case, the defined I/O procedure must be declared RECURSIVE.

Consider the following:

! This prints a linked list by calling write on the children
! of the list. 

MODULE LIST_MODULE
  IMPLICIT NONE
  TYPE NODE
! This type declaration represents a singly-linked list that also
! contains a user-defined i/o procedure. The name of the procedure
! is arbitrary, but the order of arguments must conform to the
! standard definition.

     INTEGER :: VALUE = -1
     TYPE(NODE), POINTER :: NEXT_NODE => NULL()
   CONTAINS
     PROCEDURE :: PWF
GENERIC :: WRITE(FORMATTED) => PWF ! <=== GENERIC BINDING.
  END TYPE NODE
CONTAINS
RECURSIVE SUBROUTINE PWF( DTV, UNIT, IOTYPE, V_LIST, IOSTAT, IOMSG )
! These arguments are defined in the standard.
    CLASS(NODE), INTENT(IN) :: DTV
    INTEGER, INTENT(IN) :: UNIT
    CHARACTER(LEN=*), INTENT(IN) :: IOTYPE
    INTEGER, DIMENSION(:), INTENT(IN) :: V_LIST
    INTEGER :: IOSTAT
    CHARACTER(LEN=*), INTENT(INOUT) :: IOMSG 

! The following is a child i/o statement that is called when user-defined i/o
! statement is invoked.
    WRITE( UNIT=UNIT, FMT='(I9)', IOSTAT=IOSTAT ) DTV%VALUE
    PRINT *, ASSOCIATED(DTV%NEXT_NODE)
    IF(IOSTAT /= 0)RETURN 

! It is possible to recursively call the user-defined i/o routine.
    IF(ASSOCIATED(DTV%NEXT_NODE)
      WRITE(UNIT=UNIT, FMT='(/,DT)', IOSTAT=IOSTAT) DTV%NEXT_NODE
    END IF
  END SUBROUTINE PWF
END MODULE LIST_MODULE 

PROGRAM LISTE
  USE LIST_MODULE
  IMPLICIT NONE
  INTEGER :: UNIT, IOSTAT, I
  TYPE(NODE), POINTER :: CUR, TO_PRINT 

! Create the linked list
  ALLOCATE(CUR)
  CUR % VALUE = 999
  ALLOCATE(TO_PRINT)
  TO_PRINT => CUR   

  DO I = 1,10
     ALLOCATE(CUR%NEXT_NODE)
     CUR % VALUE = I
     CUR => CUR%NEXT_NODE
  END DO
  CUR % NEXT_NODE => NULL()
! END CREATION OF LINKED LIST 

  DO I = 1,15
     IF(ASSOCIATED(TO_PRINT)) THEN
        PRINT *, I, TO_PRINT%VALUE
        TO_PRINT => TO_PRINT % NEXT_NODE
     END IF
  END DO 

! Call the user-defined i/o routine with dt format descriptor.
  WRITE( UNIT=UNIT, FMT=’(DT)’, IOSTAT=IOSTAT ) CUR
END PROGRAM LISTE

See Also