SUBROUTINE

Purpose

The SUBROUTINE statement is the first statement of a subroutine subprogram.

Syntax

Read syntax diagramSkip visual syntax diagram
   .------------.                     
   V            |                     
>>---+--------+-+--SUBROUTINE--name----------------------------->
     '-prefix-'                       

>--+-------------------------------+---------------------------->
   '-(--+---------------------+--)-'   
        '-dummy_argument_list-'        

>--+----------------------------------------------------+------><
   |      (1)                                           |   
   '-BIND------(--C--+-----------------------------+--)-'   
                     '-, -NAME-- = --binding_label-'        

Notes:
  1. Fortran 2003
prefix
is one of the following:
  • ELEMENTAL
  • Fortran 2008 beginsIMPUREFortran 2008 ends
  • Fortran 2008 beginsMODULEFortran 2008 ends
  • PURE
  • RECURSIVE
    Note: type_spec is not permitted as a prefix in a subroutine.
name
The name of the subroutine subprogram.

Fortran 2003 begins

binding_label A scalar character constant expression. Fortran 2003 ends

Rules

At most one of each kind of prefix can be specified. You cannot specify both the RECURSIVE and ELEMENTAL prefix specifiers. Fortran 2008 beginsYou cannot specify both the PURE and IMPURE prefix specifiers.Fortran 2008 ends

The subroutine name cannot appear in any other statement in the scope of the subroutine, unless recursion has been specified.

The RECURSIVE keyword must be specified if, directly or indirectly,
  • The subroutine invokes itself.
  • The subroutine invokes a procedure defined by an ENTRY statement in the same subprogram.
  • An entry procedure in the same subprogram invokes itself.
  • An entry procedure in the same subprogram invokes another entry procedure in the same subprogram.
  • An entry procedure in the same subprogram invokes the subprogram defined by the SUBROUTINE statement.

If the RECURSIVE keyword is specified, the procedure interface is explicit within the subprogram.

Using the PURE or ELEMENTAL prefix indicates that the subroutine may be invoked by the compiler in any order as it is free of side effects. For elemental procedures, the keyword ELEMENTAL must be specified. If the ELEMENTAL keyword is specified, the RECURSIVE keyword cannot be specified.

IBM extension beginsYou can also call external procedures recursively when you specify the -qrecur compiler option, although XL Fortran disregards this option if the SUBROUTINE statement specifies the RECURSIVE keyword. IBM extension ends

Fortran 2003 begins The BIND keyword implicitly or explicitly defines a binding label by which a procedure is accessed from the C programming language. A dummy argument cannot be zero-sized. A dummy argument for a procedure with the BIND attribute must have interoperable types and type parameters, and cannot have the ALLOCATABLE or POINTER attribute.

If the SUBROUTINE statement appears as part of an interface body that describes a dummy procedure, the NAME= specifier must not appear. An elemental procedure cannot have the BIND attribute. Fortran 2003 ends

Fortran 2008 begins
You can specify the MODULE prefix specifier for the SUBROUTINE statement of a module subprogram or of a nonabstract interface body that is declared in the scoping unit of a module or submodule. See Example 2.
  • When you specify the MODULE prefix specifier for the SUBROUTINE statement of a module subprogram, the module subprogram is a separate module procedure.
  • When you specify the MODULE prefix specifier for the SUBROUTINE statement of a nonabstract interface body, the interface body is a module procedure interface body.

The BIND attribute with the NAME= specifier is not allowed on an internal procedure.

Fortran 2008 ends

Example 1

RECURSIVE SUBROUTINE SUB(X,Y)
  INTEGER X,Y
  IF (X.LT.Y) THEN
    RETURN
  ELSE
    CALL SUB(X,Y+1)
  END IF
END SUBROUTINE SUB

Example 2 (Fortran 2008)

MODULE m
  ! The MODULE prefix specifier is specified for the SUBROUTINE
  ! statement of a module procedure interface body.
  INTERFACE
    MODULE SUBROUTINE sub(arg)
      INTEGER :: arg
    END SUBROUTINE
  END INTERFACE
END MODULE

SUBMODULE (m) n
  
  CONTAINS
    ! The MODULE prefix specifier is specified for the SUBROUTINE
    ! statement of a separate module procedure.
    MODULE SUBROUTINE sub(arg) 
      INTEGER :: arg
      arg = 1
    END SUBROUTINE
END SUBMODULE


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