IBM Books

Language Reference


Attributes

Each attribute has a corresponding attribute specification statement, and the syntax diagram provided for the attribute illustrates this form. An entity can also acquire this attribute from a type declaration statement or, in some cases, through a default setting. For example, entity A, said to have the PRIVATE attribute, could have acquired the attribute in any of the following ways:

     REAL, PRIVATE :: A     ! Type declaration statement
 
     PRIVATE :: A           ! Attribute specification statement
 
     MODULE X
       PRIVATE              ! Default setting
       REAL :: A
     END MODULE

The following table maps out the compatibility of attributes. An "X" indicates whether an entity can have the attributes indicated both horizontally and vertically.

Figure 1.

attrtbl

ALLOCATABLE

Purpose

The ALLOCATABLE attribute declares allocatable arrays -- that is, arrays whose bounds are determined when space is dynamically allocated by execution of an ALLOCATE statement.

Format



>>-ALLOCATABLE--+-----+----------------------------------------->
                +-::--+
 
   +-,-----------------------------------------------+
   V                                                 |
>----array_name--+---------------------------------+-+---------><
                 +-(--deferred_shape_spec_list--)--+
 

array_name
is the name of an allocatable array

deferred_shape_spec
is a colon(:), where each colon represents a dimension

Rules

The array cannot be a pointee, dummy argument or function result. If the array is specified elsewhere in the scoping unit with the DIMENSION attribute, the array specification must be a deferred_shape_spec.
Attributes Compatible with the ALLOCATABLE Attribute

  • AUTOMATIC
  • DIMENSION
  • PRIVATE

  • PUBLIC
  • SAVE
  • STATIC

  • TARGET
  • VOLATILE

Examples

REAL, ALLOCATABLE :: A(:,:)  ! Two-dimensional array A declared
                             ! but no space yet allocated
READ (5,*) I,J
ALLOCATE (A(I,J))
END

Related Information

ALLOCATE

Purpose

The ALLOCATE statement dynamically provides storage for pointer targets and allocatable arrays.

Format




>>-ALLOCATE--(--allocation_list--+----------------------------+--)--><
                                 +-,-STAT-- = --stat_variable-+

stat_variable
is a scalar integer variable

allocation




>>-allocate_object--+--------------------------------------------+-><
                    |   +--,--------------------------------+    |
                    |   V                                   |    |
                    +-(---+-----------------+--upper_bound--+--)-+
                          +-lower_bound--:--+

allocate_object
is a variable name or structure component. It must be a pointer or an allocatable array.

lower_bound, upper_bound
are each scalar integer expressions

Rules

Execution of an ALLOCATE statement for a pointer causes the pointer to become associated with the target allocated. For an allocatable array, the array becomes definable.

The number of dimensions specified (i.e., the number of upper bounds in allocation) must be equal to the rank of allocate_object. When an ALLOCATE statement is executed for an array, the values of the bounds are determined at that time. Subsequent redefinition or undefinition of any entities in the bound expressions does not affect the array specification. Any lower bound, if omitted, is assigned a default value of 1. If any lower bound value exceeds the corresponding upper bound value, that dimension has an extent of 0 and allocate_object is zero-sized.

A specified bound must not be an expression that contains as a primary an array inquiry function whose argument is an allocate_object in the same ALLOCATE statement. The stat_variable must not be allocated within the ALLOCATE statement in which it appears; nor can it depend on the value, bounds, allocation status, or association status of any allocate_object or subobject of an allocate_object allocated in the same statement.

If the STAT= specifier is not present and an error condition occurs during execution of the statement, the program terminates. If the STAT= specifier is present, the stat_variable is assigned one of the following values:
Stat value Error condition
0 No error
1 Error in system routine attempting to do allocation
2 An invalid data object has been specified for allocation
3 Both error conditions 1 and 2 have occurred

Allocating an allocatable array that is already allocated causes an error condition in the ALLOCATE statement.

Pointer allocation creates an object that has the TARGET attribute. Additional pointers can be associated with this target (or a subobject of it) through pointer assignment. If you reallocate a pointer that is already associated with a target:

Use the ALLOCATED intrinsic function to determine if an allocatable array is currently allocated. Use the ASSOCIATED intrinsic function to determine the association status of a pointer or whether a pointer is currently associated with a specified target.

Examples

CHARACTER, POINTER :: P(:,:)
CHARACTER, TARGET :: C(4,4)
INTEGER, ALLOCATABLE, DIMENSION(:) :: A
P => C
N = 2; M = N
ALLOCATE (P(N,M),STAT=I)         ! P is no longer associated with C
N = 3                            ! Target array for P maintains 2X2 shape
IF (.NOT.ALLOCATED(A)) ALLOCATE (A(N**2))
END

Related Information

ASSIGN

Purpose

The ASSIGN statement assigns a statement label to an integer variable.

Format



>>-ASSIGN--stmt_label--TO--variable_name-----------------------><
 

stmt_label
specifies the statement label of an executable statement or a FORMAT statement in the scoping unit containing the ASSIGN statement

variable_name
is the name of a scalar INTEGER(4) or INTEGER(8) variable

Rules

A statement containing the designated statement label must appear in the same scoping unit as the ASSIGN statement. If the statement containing the statement label is an executable statement, you can use the label name in a assigned GO TO statement that is in the same scoping unit. If the statement containing the statement label is a FORMAT statement, you can use the label name as the format specifier in a READ, WRITE, or PRINT statement that is in the same scoping unit.

You can redefine an integer variable defined with a statement label value with the same or different statement label value or an integer value. However, you must define the variable with a statement label value before you reference it in an assigned GO TO statement or as a format identifier in an input/output statement.

The value of variable_name is not the integer constant represented by the label itself, and you cannot use it as such.

Examples

      ASSIGN 30 TO LABEL
      NUM = 40
      GO TO LABEL
      NUM = 50                ! This statement is not executed
30    ASSIGN 1000 TO IFMT
      PRINT IFMT, NUM         ! IFMT is the format specifier
1000  FORMAT(1X,I4)
      END

Related Information

AUTOMATIC

Purpose

The AUTOMATIC attribute specifies that a variable has a storage class of automatic; that is, the variable is not defined once the procedure ends.

Format



>>-AUTOMATIC-+----+---automatic_list---------------------------><
             +-::-+
 

automatic
is a variable name or an array declarator with an explicit-shape specification list or a deferred-shape specification list

Rules

If automatic has the same name as the name of the function in which it is declared, it must not be of type character nor of derived type.

Function results that are pointers or arrays, dummy arguments, statement functions, automatic objects, and pointees must not have the AUTOMATIC attribute. A variable with the AUTOMATIC attribute cannot be defined in the scoping unit of a module. A variable that is explicitly declared with the AUTOMATIC attribute cannot be a common block item.

A variable must not have the AUTOMATIC attribute specified more than once in the same scoping unit.

Any variable declared as AUTOMATIC within the scope of a thread's work will be local to that thread.

If the -qinitauto compiler option is not specified, a variable with the AUTOMATIC attribute cannot be initialized, either with a DATA statement or a type declaration statement. If the -qinitauto option is specified, all bytes of storage for variables with the AUTOMATIC attribute are initialized to a specified byte value or, if no value is specified, to zero.

If automatic is a pointer, the AUTOMATIC attribute applies to the pointer itself, not to any target that is (or may become) associated with the pointer.

Local variables have a default storage class of automatic. See "-qsave Option" in the User's Guide for details on the default settings with regard to the invocation commands.
Note:An object with the AUTOMATIC attribute should not be confused with an automatic object. See "Automatic Objects".
Attributes Compatible with the AUTOMATIC Attribute

  • ALLOCATABLE
  • DIMENSION

  • POINTER
  • TARGET

  • VOLATILE

Examples

CALL SUB
CONTAINS
  SUBROUTINE SUB
    INTEGER, AUTOMATIC :: VAR
    VAR = 12
  END SUBROUTINE                  ! VAR becomes undefined
END

Related Information

BACKSPACE

Purpose

The BACKSPACE statement positions an external file, connected for sequential access, before the preceding record.

Format



>>-BACKSPACE--+-u--------------------+-------------------------><
              +-(--position_list--)--+
 

u
is an external unit identifier. The value of u must not be an asterisk or a Hollerith constant.

position_list
is a list that must contain one unit specifier ([ UNIT=]u) and can also contain one of each of the other valid specifiers:

[UNIT=] u
is a unit specifier in which u must be an external unit identifier whose value is not an asterisk. An external unit identifier refers to an external file that is represented by a scalar integer expression, whose value is in the range 1 through 2147483647. If the optional characters UNIT= are omitted, u must be the first item in position_list.

IOSTAT= ios
is an input/output status specifier that specifies the status of the input/output operation. ios is a scalar variable of type INTEGER(4) or default integer. When the BACKSPACE statement finishes executing, ios is defined with:

ERR= stmt_label
is an error specifier that specifies the statement label of an executable statement in the same scoping unit to which control is to transfer in the case of an error. Coding the ERR= specifier suppresses error messages.

Rules

If there is no preceding record, the file position does not change. If the preceding record is the endfile record, the file is positioned before the endfile record. You cannot backspace over records that were written using list-directed or namelist formatting.

If the ERR= and IOSTAT= specifiers are set and an error is encountered, transfer is made to the statement specified by the ERR= specifier and a positive integer value is assigned to ios.

If IOSTAT= and ERR= are not specified,

Examples

   BACKSPACE 15
   BACKSPACE (UNIT=15,ERR=99)
      ·
99 PRINT *, "Unable to backspace file."
   END

Related Information

BLOCK DATA

Purpose

A BLOCK DATA statement is the first statement in a block data program unit, which provides initial values for variables in named common blocks.

Format



>>-BLOCK DATA-+-----------------+------------------------------><
              +-block_data_name-+
 

block_data_name
is the name of a block data program unit

Rules

You can have more than one block data program unit in an executable program, but only one can be unnamed.

The name of the block data program unit, if given, must not be the same as an external subprogram, entry, main program, module, or common block in the executable program. It also must not be the same as a local entity in this program unit.

Examples

BLOCK DATA ABC
  PARAMETER (I=10)
  DIMENSION Y(5)
  COMMON /L4/ Y
  DATA Y /5*I/
END BLOCK DATA ABC

Related Information

BYTE

Purpose

The BYTE type declaration statement specifies the attributes of objects and functions of type byte. Each scalar object has a length of 1. Initial values can be assigned to objects.

Format



>>-BYTE--+-+----+-----------------+-entity_decl_list-----------><
         | +-::-+                 |
         +-,--attr_spec_list--::--+
 

where:
attr_spec

ALLOCATABLE
AUTOMATIC
DIMENSION (array_spec)
EXTERNAL
INTENT (intent_spec)
INTRINSIC
OPTIONAL
PARAMETER
POINTER
PRIVATE
PUBLIC
SAVE
STATIC
TARGET
VOLATILE

attr_spec
For detailed information on rules about a particular attribute, refer to the statement of the same name.

intent_spec
is either IN, OUT, or INOUT

::
is the double colon separator. It is required if attributes are specified or if = initialization_expr is used.

array_spec
is a list of dimension bounds

entity_decl



>>-a--+-------------------+--+--------------------------------+-><
      +-(--array_spec--)--+  +--+-/--initial_value_list--/--+-+
                                +-=--initialization_expr----+
 

a
is an object name or function name. array_spec cannot be specified for a function name.

initial_value
provides an initial value for the entity specified by the immediately preceding name

initialization_expr
provides an initial value, by means of an initialization expression, for the entity specified by the immediately preceding name

Rules

Entities in type declaration statements are constrained by the rules of any attributes specified for the entities, as detailed in the corresponding attribute statements.

The type declaration statement overrides the implicit type rules in effect. You can use a type declaration statement that confirms the type of an intrinsic function. The appearance of a generic or specific intrinsic function name in a type declaration statement does not cause the name to lose its intrinsic property.

An object cannot be initialized in a type declaration statement if it is a dummy argument, an allocatable array, a pointer, a function result, an object in blank common, an integer pointer, an external name, an intrinsic name, or an automatic object. Nor can an object be initialized if it has the AUTOMATIC attribute. The object may be initialized if it appears in a named common block in a block data program unit or if it appears in a named common block in a module.

The specification expression of an array_spec can be a nonconstant expression if the specification expression appears in an interface body or in the specification part of a subprogram. Any object being declared that uses this nonconstant expression and is not a dummy argument or a pointee is called an automatic object.

An attribute cannot be repeated in a given type declaration statement, nor can an entity be explicitly given the same attribute more than once in a scoping unit.

initialization_expr must be specified if the statement contains the PARAMETER attribute. If initialization_expr is specified and PARAMETER is not, the object is a variable that is initially defined. a becomes defined with the value determined by initialization_expr, in accordance with the rules for intrinsic assignment. If the variable is an array, its shape must be specified either in the type declaration statement or in a previous specification statement in the same scoping unit. A variable or variable subobject cannot be initialized more than once. The presence of initialization_expr implies that a is a saved object, except for an object with the PARAMETER attribute or in a named common block. The initialization of an object could affect the fundamental storage class of an object.

An array_spec specified in the entity_decl takes precedence over the array_spec in the DIMENSION attribute.

An array function result that does not have the POINTER attribute must have an explicit-shape array specification.

If the entity declared is a function, it must not have an accessible explicit interface unless it is an intrinsic function.

If T or F, defined previously as the name of a constant, appears in a type declaration statement, it is no longer an abbreviated logical constant but the name of the named constant.

Examples

BYTE, DIMENSION(4) :: X=(/1,2,3,4/)

Related Information

CALL

Purpose

The CALL statement invokes a subroutine to be executed.

Format



>>-CALL--name--+--------------------------------------+--------><
               +-(-+---------------------------+---)--+
                   +-actual_argument_spec_list-+
 

name
is the name of an internal, external, or module subroutine, an entry in an external or module subroutine, an intrinsic subroutine, or a generic name.

Rules

Executing a CALL statement results in the following order of events:

  1. Actual arguments that are expressions are evaluated.
  2. Actual arguments are associated with their corresponding dummy arguments.
  3. Control transfers to the specified subroutine.
  4. The subroutine is executed.
  5. Control returns from the subroutine.

A subprogram can call itself recursively, directly or indirectly, if the subroutine statement specifies the RECURSIVE keyword.

An external subprogram can also refer to itself directly or indirectly if the -qrecur compiler option is specified.

If a CALL statement includes one or more alternate return specifiers among its arguments, control may be transferred to one of the statement labels indicated, depending on the action specified by the subroutine in the RETURN statement.

The argument list built-in functions %VAL and %REF are supplied to aid interlanguage calls by allowing arguments to be passed by value and by reference, respectively. They can only be specified in non-Fortran procedure references.

Examples

INTERFACE
  SUBROUTINE SUB3(D1,D2)
    REAL D1,D2
  END SUBROUTINE
END INTERFACE
ARG1=7 ; ARG2=8
CALL SUB3(D2=ARG2,D1=ARG1)    ! subroutine call with argument keywords
END
 
SUBROUTINE SUB3(F1,F2)
  REAL F1,F2,F3,F4
  F3 = F1/F2
  F4 = F1-F2
  PRINT *, F3, F4
END SUBROUTINE

Related Information

CASE

Purpose

The CASE statement initiates a CASE statement block in a CASE construct, which has a concise syntax for selecting, at most, one of a number of statement blocks for execution.

Format



>>-CASE--case_selector-+---------------------+-----------------><
                       +-case_construct_name-+
 

case_selector



>>-+-DEFAULT-------------------------------------------+-------><
   |    +-,--------------------------------------+     |
   |    V                                        |     |
   +-(----+-case_value--------------------------++--)--+
          +-low_case_value--:--high_case_value--+
          +-low_case_value--:-------------------+
          +-:--high_case_value------------------+
 

case_construct_name
is a name given to the CASE construct for identification

case_value
is a scalar initialization expression of type integer, character, or logical

low_case_value, high_case_value
are each scalar initialization expressions of type integer, character, or logical

Rules

The case index, determined by the SELECT CASE statement, is compared to each case_selector in a CASE statement. When a match occurs, the stmt_block associated with that CASE statement is executed. If no match occurs, no stmt_block is executed. No two case value ranges can overlap.

A match is determined as follows:

case_value
DATA TYPE:  integer, character or logical
MATCH for integer and character:  case index = case_value
MATCH for logical:  case index .EQV. case_value is true

low_case_value : high_case_value
DATA TYPE:  integer or character
MATCH:  low_case_value <= case index <= high_case_value

low_case_value :
DATA TYPE:  integer or character
MATCH:  low_case_value <= case index

: high_case_value
DATA TYPE:  integer or character
MATCH:  case index <= high_case_value

DEFAULT
DATA TYPE:  not applicable
MATCH:  if no other match occurs.

There must be only one match. If there is a match, the statement block associated with the matched case_selector is executed, completing execution of the case construct. If there is no match, execution of the case construct is complete.

If the case_construct_name is specified, it must match the name specified on the SELECT CASE and END SELECT statements.

DEFAULT is the default case_selector. Only one of the CASE statements may have DEFAULT as the case_selector.

Each case value must be of the same data type as the case_expr, as defined in the SELECT CASE statement. If any typeless constants or BYTE named constants are encountered in the case_selectors, they are converted to the data type of the case_expr.

When the case_expr and the case values are of type character, they can have different lengths. If you specify the -qctyplss compiler option, a character constant expression used as the case_expr remains as type character. The character constant expression will not be treated as a typeless constant.

Examples

ZERO: SELECT CASE(N)
 
  CASE DEFAULT ZERO          ! Default CASE statement for
                             ! CASE construct ZERO
       OTHER: SELECT CASE(N)
          CASE(:-1)          ! CASE statement for CASE
                             ! construct OTHER
             SIGNUM = -1
          CASE(1:) OTHER
              SIGNUM = 1
       END SELECT OTHER
  CASE (0)
    SIGNUM = 0
 
END SELECT ZERO

Related Information

CHARACTER

Purpose

A CHARACTER type declaration statement specifies the kind, length, and attributes of objects and functions of type character. Initial values can be assigned to objects.

Format



>>-CHARACTER--+----------------+--+-+----+-----------------+---->
              +-char_selector--+  | +-::-+                 |
                                  +-,--attr_spec_list--::--+
 
>-entity_decl_list---------------------------------------------><
 

where:
attr_spec

ALLOCATABLE
AUTOMATIC
DIMENSION (array_spec)
EXTERNAL
INTENT (intent_spec)
INTRINSIC
OPTIONAL
PARAMETER
POINTER
PRIVATE
PUBLIC
SAVE
STATIC
TARGET
VOLATILE

char_selector
specifies the character length (number of characters between 0 and 256 MB). Values exceeding 256 MB are set to 256 MB in 32 bit, while negative values result in a length of zero. If not specified, the default length is 1. The kind type parameter, if specified, must be 1, which specifies the ASCII character representation.




>>-+-(-+-LEN--=--type_param_value--,--KIND--=--int_init_expr-----+-)-+-><
   |   +-type_param_value--,--+----------+--int_init_expr--------+   |
   |   |                      +-KIND--=--+                       |   |
   |   +-KIND--=--int_init_expr--+-----------------------------+-+   |
   |   |                         +-,--LEN--=--type_param_value-+ |   |
   |   +-+---------+--type_param_value---------------------------+   |
   |     +-LEN--=--+                                                 |
   +-*-char_length-+---+---------------------------------------------+
                   +-,-+

 
 

type_param_value
is a specification expression or an asterisk (*)

int_init_expr
is a scalar integer initialization expression that must evaluate to 1

char_length
is either a scalar integer literal constant (which cannot specify a kind type parameter) or a type_param_value enclosed in parentheses

attr_spec
For detailed information on rules about a particular attribute, refer to the statement of the same name.

intent_spec
is either IN, OUT, or INOUT

::
is the double colon separator. It is required if attributes are specified or if = initialization_expr is used.

array_spec
is a list of dimension bounds

entity_decl



>>-a--+-+-------------------+--+-------------------+-+---------->
      | +- * --char_length--+  +-(--array_spec--)--+ |
      +-(--array_spec--)-- * --char_length-----------+
 
>--+--------------------------------+--------------------------><
   +--+-/--initial_value_list--/--+-+
      +- = --initialization_expr--+
 

 
 

a
is an object name or function name. array_spec cannot be specified for a function name.

initial_value
provides an initial value for the entity specified by the immediately preceding name

initialization_expr
provides an initial value, by means of an initialization expression, for the entity specified by the immediately preceding name

Rules

Entities in type declaration statements are constrained by the rules of any attributes specified for the entities, as detailed in the corresponding attribute statements.

The type declaration statement overrides the implicit type rules in effect. You can use a type declaration statement that confirms the type of an intrinsic function. The appearance of a generic or specific intrinsic function name in a type declaration statement does not cause the name to lose its intrinsic property.

An object cannot be initialized in a type declaration statement if it is a dummy argument, an allocatable array, a pointer, a function result, an object in blank common, an integer pointer, an external name, an intrinsic name, or an automatic object. Nor can an object be initialized if it has the AUTOMATIC attribute. The object may be initialized if it appears in a named common block in a block data program unit or if it appears in a named common block in a module.

The specification expression of a type_param_value or an array_spec can be a nonconstant expression if the specification expression appears in an interface body or in the specification part of a subprogram. Any object being declared that uses this nonconstant expression and is not a dummy argument or a pointee is called an automatic object.

An attribute cannot be repeated in a given type declaration statement, nor can an entity be explicitly given the same attribute more than once in a scoping unit.

initialization_expr must be specified if the statement contains the PARAMETER attribute. If initialization_expr is specified and PARAMETER is not, the object is a variable that is initially defined. a becomes defined with the value determined by initialization_expr, in accordance with the rules for intrinsic assignment. If the variable is an array, its shape must be specified either in the type declaration statement or in a previous specification statement in the same scoping unit. A variable or variable subobject cannot be initialized more than once. The presence of initialization_expr implies that a is a saved object, except for an object with the PARAMETER attribute or in a named common block. The initialization of an object could affect the fundamental storage class of an object.

An array_spec specified in an entity_decl takes precedence over the array_spec in the DIMENSION attribute. A char_length specified in an entity_decl takes precedence over any length specified in char_selector.

An array function result that does not have the POINTER attribute must have an explicit-shape array specification.

If the entity declared is a function, it must not have an accessible explicit interface unless it is an intrinsic function.

If T or F, defined previously as the name of a constant, appears in a type declaration statement, it is no longer an abbreviated logical constant but the name of the named constant.

The optional comma after char_length in a CHARACTER type declaration statement is permitted only if no double colon separator (::) appears in the statement.

If the CHARACTER type declaration statement is in the scope of a module, block data program unit, or main program, and you specify the length of the entity as inherited length, the entity must be the name of a named character constant. The character constant assumes the length of its corresponding expression defined by the PARAMETER attribute.

If the CHARACTER type declaration statement is in the scope of a procedure and the length of the entity is inherited, the entity name must be the name of a dummy argument or a named character constant. If the statement is in the scope of an external function, it can also be the function or entry name in a FUNCTION or ENTRY statement in the same program unit. If the entity name is the name of a dummy argument, the dummy argument assumes the length of the associated actual argument for each reference to the procedure. If the entity name is the name of a character constant, the character constant assumes the length of its corresponding expression defined by the PARAMETER attribute. If the entity name is a function or entry name, the entity assumes the length specified in the calling scoping unit.

The length of a character function is either a specification expression (which must be a constant expression if the function type is not declared in an interface block) or it is an asterisk, indicating the length of a dummy procedure name. The length cannot be an asterisk if the function is an internal or module function, recursive, or if the function returns array or pointer values.

Examples

I=7
CHARACTER(KIND=1,LEN=6) APPLES /'APPLES'/
CHARACTER(7), TARGET :: ORANGES = 'ORANGES'
CALL TEST(APPLES,I)
CONTAINS
  SUBROUTINE  TEST(VARBL,I)
    CHARACTER*(*), OPTIONAL :: VARBL   ! VARBL inherits a length of 6
    CHARACTER(I) :: RUNTIME            ! Automatic object with length of 7
  END SUBROUTINE
END

Related Information

CLOSE

Purpose

The CLOSE statement disconnects an external file from a unit.

Format



>>-CLOSE--(--close_list--)-------------------------------------><
 

close_list
is a list that must contain one unit specifier ( UNIT=u) and can also contain one of each of the other valid specifiers. The valid specifiers are:

[UNIT=] u
is a unit specifier in which u must be an external unit identifier whose value is not an asterisk. An external unit identifier refers to an external file that is represented by a scalar integer expression, whose value is in the range 1 through 2147483647. If the optional characters UNIT= are omitted, u must be the first item in close_list.

IOSTAT= ios
is an input/output status specifier that specifies the status of the input/output operation. ios is a scalar variable of type INTEGER(4) or default integer. When the input/output statement containing this specifier finishes executing, ios is defined with:

ERR= stmt_label
is an error specifier that specifies the statement label of an executable statement in the same scoping unit to which control is to transfer in the case of an error. Coding the ERR= specifier suppresses error messages.

STATUS= char_expr
specifies the status of the file after it is closed. char_expr is a scalar character expression whose value, when any trailing blanks are removed, is either KEEP or DELETE.

The default is DELETE if the file status is SCRATCH; otherwise, the default is KEEP.

Rules

A CLOSE statement that refers to a unit can occur in any program unit of an executable program and need not occur in the same scoping unit as the OPEN statement referring to that unit. You can specify a unit that does not exist or has no file connected; the CLOSE statement has no effect in this case.

Unit 0 cannot be closed.

When an executable program stops for reasons other than an error condition, all units that are connected are closed. Each unit is closed with the status KEEP unless the file status prior to completion was SCRATCH, in which case the unit is closed with the status DELETE. The effect is as though a CLOSE statement without a STATUS= specifier were executed on each connected unit.

If a preconnected unit is disconnected by a CLOSE statement, the rules of implicit opening apply if the unit is later specified in a WRITE statement (without having been explicitly opened).

Examples

CLOSE(15)
CLOSE(UNIT=16,STATUS='DELETE')

Related Information

COMMON

Purpose

The COMMON statement specifies common blocks and their contents. A common block is a storage area that two or more scoping units can share, allowing them to define and reference the same data and to share storage units.

Format



>>-COMMON--+------------------------------+--object_list-------->
           +-/-+-------------------+---/--+
               +-common_block_name-+
 
>--+--------------------------------------------------------+--><
   |  +--------------------------------------------------+  |
   |  V                                                  |  |
   +---+---+---/-+-------------------+---/--object_list--+--+
       +-,-+     +-common_block_name-+
 

object



>>-variable_name--+---------------------------------+----------><
                  +-(--explicit_shape_spec_list--)--+
 

Rules

object cannot refer to a dummy argument, automatic object, allocatable array, pointee, function, function result, or entry to a procedure. object cannot have the STATIC or AUTOMATIC attributes.

If an explicit_shape_spec_list is present, variable_name must not have the POINTER attribute. Each dimension bound must be a constant specification expression. This form specifies that variable_name has the DIMENSION attribute.

If object is of derived type, it must be a sequence derived type. Given a sequenced structure where all the components are nonpointers and are either all of noncharacter type (or double precision real) or all of character type, the structure is treated as if its components are enumerated directly in the common block.

A pointer object in a common block can only be storage associated with pointers of the same type, type parameters, and rank.

Pointers of type BYTE can be storage associated with pointers of type INTEGER(1) and LOGICAL(1). Integer and logical pointers of the same length can be storage associated if you specify the -qintlog compiler option.

If you specify common_block_name, all variables specified in the object_list that follows are declared to be in that named common block. If you omit common_block_name, all variables that you specify in the object_list that follows are in the blank common block.

Within a scoping unit, a common block name can appear more than once in the same or in different COMMON statements. Each successive appearance of the same common block name continues the common block specified by that name. Common block names are global entities.

The variables in a common block can have different data types. You can mix character and noncharacter data types within the same common block. Variable names in common blocks can appear in only one COMMON statement in a scoping unit, and you cannot duplicate them within the same COMMON statement.

By default, common blocks are shared across threads, and so the use of the COMMON statement is thread-unsafe if any storage unit in the common block needs to be updated by more than one thread, or is updated by one thread and referenced by another. To ensure your application uses COMMON in a thread-safe manner, you must either serialize access to the data using locks, or make certain that the common blocks are local to each thread. The Pthreads library module provides mutexes to allow you to serialize access to the data using locks. See Chapter 14. "Pthreads Library Module" for more information. The lock_name attribute on the CRITICAL directive also provides the ability to serialize access to data. See CRITICAL / END CRITICAL for more information. The THREADLOCAL directive ensures that common blocks are local to each thread. See THREADLOCAL for more information.

Common Association

Within an executable program, all nonzero-sized named common blocks with the same name have the same first storage unit. There can be one blank common block, and all scoping units that refer to nonzero-sized blank common refer to the same first storage unit.

All zero-sized common blocks with the same name are storage associated with one another. All zero-sized blank common blocks are associated with one another and with the first storage unit of any nonzero-sized blank common blocks. Use association or host association can cause these associated objects to be accessible in the same scoping unit.

Because association is by storage unit, variables in a common block can have different names and types in different scoping units.

Common Block Storage Sequence

Storage units for variables within a common block in a scoping unit are assigned in the order that their names appear within the COMMON statement.

You can extend a common block by using an EQUIVALENCE statement, but only by adding beyond the last entry, not before the first entry. For example, these statements specify X:

      COMMON /X/ A,B      ! common block named X
      REAL C(2)
      EQUIVALENCE (B,C)

The contents of common block X are as follows:

            |    |    |    |    |    |    |    |    |    |    |    |    |
Variable A: |         A         |
Variable B:                     |         B         |
Array C:                        |        C(1)       |       C(2)        |

Only COMMON and EQUIVALENCE statements that appear in a scoping unit contribute to the common block storage sequences formed in that unit, not including variables in common made accessible by use association or host association.

An EQUIVALENCE statement cannot cause the storage sequences of two different common blocks to become associated. While a common block can be declared in the scoping unit of a module, it must not be declared in another scoping unit that accesses entities from the module through use association.

Use of COMMON can lead to misaligned data. Any use of misaligned data can adversely affect the performance of the program.

Size of a Common Block

The size of a common block is equal to the number of bytes of storage needed to hold all the variables in the common block, including any extensions resulting from equivalence association.

Differences Between Named and Blank Common Blocks

Examples

INTEGER MONTH,DAY,YEAR
COMMON /DATE/ MONTH,DAY,YEAR
REAL          R4
REAL          R8
CHARACTER(1)  C1
COMMON /NOALIGN/ R8,C1,R4     ! R4 will not be aligned on a
                              ! full-word boundary

Related Information

COMPLEX

Purpose

A COMPLEX type declaration statement specifies the length and attributes of objects and functions of type complex. Initial values can be assigned to objects.

Format



>>-COMPLEX-+---------------+---+-+----+-----------------+------->
           +-kind_selector-+   | +-::-+                 |
                               +-,--attr_spec_list--::--+
 
>--entity_decl_list--------------------------------------------><
 

where:
attr_spec

ALLOCATABLE
AUTOMATIC
DIMENSION (array_spec)
EXTERNAL
INTENT (intent_spec)
INTRINSIC
OPTIONAL
PARAMETER
POINTER
PRIVATE
PUBLIC
SAVE
STATIC
TARGET
VOLATILE

kind_selector



>>-+-(--+------------+--int_initialization_expr--)--+----------><
   |    +-KIND-- = --+                              |
   +- * --int_literal_constant----------------------+
 

 
specifies the length of complex entities:

attr_spec
For detailed information on rules about a particular attribute, refer to the statement of the same name.

intent_spec
is either IN, OUT, or INOUT

::
is the double colon separator. It is required if attributes are specified or if = initialization_expr is used.

array_spec
is a list of dimension bounds

entity_decl



>>-a--+-+-----------+--+-------------------+-+------------------>
      | +- * --len--+  +-(--array_spec--)--+ |
      +-(--array_spec--)-- * --len-----------+
 
>--+--------------------------------+--------------------------><
   +--+-/--initial_value_list--/--+-+
      +- = --initialization_expr--+
 

 

a
is an object name or function name. array_spec cannot be specified for a function name.

len
overrides the length as specified in kind_selector, and cannot specify a kind type parameter. The entity length must be an integer literal constant that represents one of the permissible length specifications.

initial_value
provides an initial value for the entity specified by the immediately preceding name

initialization_expr
provides an initial value, by means of an initialization expression, for the entity specified by the immediately preceding name

Rules

Entities in type declaration statements are constrained by the rules of any attributes specified for the entities, as detailed in the corresponding attribute statements.

The type declaration statement overrides the implicit type rules in effect. You can use a type declaration statement that confirms the type of an intrinsic function. The appearance of a generic or specific intrinsic function name in a type declaration statement does not cause the name to lose its intrinsic property.

An object cannot be initialized in a type declaration statement if it is a dummy argument, an allocatable array, a pointer, a function result, an object in blank common, an integer pointer, an external name, an intrinsic name, or an automatic object. Nor can an object be initialized if it has the AUTOMATIC attribute. The object may be initialized if it appears in a named common block in a block data program unit or if it appears in a named common block in a module.

The specification expression of an array_spec can be a nonconstant expression if the specification expression appears in an interface body or in the specification part of a subprogram. Any object being declared that uses this nonconstant expression and is not a dummy argument or a pointee is called an automatic object.

An attribute cannot be repeated in a given type declaration statement, nor can an entity be explicitly given the same attribute more than once in a scoping unit.

initialization_expr must be specified if the statement contains the PARAMETER attribute. If initialization_expr is specified and PARAMETER is not, the object is a variable that is initially defined. a becomes defined with the value determined by initialization_expr, in accordance with the rules for intrinsic assignment. If the variable is an array, its shape must be specified either in the type declaration statement or in a previous specification statement in the same scoping unit. A variable or variable subobject cannot be initialized more than once. The presence of initialization_expr implies that a is a saved object, except for an object with the PARAMETER attribute or in a named common block. The initialization of an object could affect the fundamental storage class of an object.

An array_spec specified in the entity_decl takes precedence over the array_spec in the DIMENSION attribute.

An array function result that does not have the POINTER attribute must have an explicit-shape array specification.

If the entity declared is a function, it must not have an accessible explicit interface unless it is an intrinsic function.

If T or F, defined previously as the name of a constant, appears in a type declaration statement, it is no longer an abbreviated logical constant but the name of the named constant.

Examples

      COMPLEX, DIMENSION (2,3) :: ABC(3) ! ABC has 3 (not 6) array elements

Related Information

CONTAINS

Purpose

The CONTAINS statement separates the body of a main program, external subprogram, or module subprogram from any internal subprograms that it may contain. Similarly, it separates the specification part of a module from any module subprograms.

Format



>>-CONTAINS----------------------------------------------------><
 

Rules

When a CONTAINS statement exists, at least one subprogram must follow it.

The CONTAINS statement cannot appear in a block data program unit or in an internal subprogram.

Any label of a CONTAINS statement is considered part of the main program, subprogram, or module that contains the CONTAINS statement.

Examples

MODULE A
     ·
  CONTAINS               ! Module subprogram must follow
  SUBROUTINE B(X)
        ·
    CONTAINS             ! Internal subprogram must follow
    FUNCTION C(Y)
        ·
    END FUNCTION
  END SUBROUTINE
END MODULE

Related Information

"Program Units, Procedures and Subprograms"

CONTINUE

Purpose

The CONTINUE statement is an executable control statement that takes no action; it has no effect. This statement is often used as the terminal statement of a loop.

Format



>>-CONTINUE----------------------------------------------------><
 

Examples

     DO 100 I = 1,N
        X = X + N
100  CONTINUE

Related Information

Chapter 6. "Control"

CYCLE

Purpose

The CYCLE statement terminates the current execution cycle of a DO or DO WHILE construct.

Format



>>-CYCLE-+-------------------+---------------------------------><
         +-DO_construct_name-+
 

DO_construct_name
is the name of a DO or DO WHILE construct

Rules

The CYCLE statement is placed within a DO or DO WHILE construct and belongs to the particular DO or DO WHILE construct specified by DO_construct_name or, if not specified, to the DO or DO WHILE construct that immediately surrounds it. The statement terminates only the current cycle of the construct that it belongs to.

When the CYCLE statement is executed, the current execution cycle of the DO or DO WHILE construct is terminated. Any executable statements after the CYCLE statement, including any terminating labeled action statement, will not be executed. For DOconstructs, program execution continues with incrementation processing, if any. For DO WHILE constructs, program execution continues with loop control processing.

A CYCLE statement can have a statement label. However, it cannot be used as a labeled action statement that terminates a DO construct.

Examples

LOOP1: DO I = 1, 20
   N = N + 1
   IF (N > NMAX) CYCLE LOOP1          ! cycle to LOOP1
 
   LOOP2: DO WHILE (K==1)
      IF (K > KMAX) CYCLE             ! cycle to LOOP2
      K = K + 1
   END DO LOOP2
 
   LOOP3:  DO J = 1, 10
      N = N + 1
      IF (N > NMAX) CYCLE LOOP1       ! cycle to LOOP1
      CYCLE LOOP3                     ! cycle to LOOP3
   END DO LOOP3
 
END DO LOOP1
END

Related Information

DATA

Purpose

The DATA statement provides initial values for variables.

Format



         +-+---+---------------------------------------+
         | +-,-+                                       |
         V                                             |
>>-DATA----data_object_list--/--initial_value_list--/--+-------><
 

data_object
is a variable or an implied- DO list. Any subscript or substring expression must be an initialization expression.

implied- DO list



>>-(--do_object_list--,--do_variable-- = ----------------------->
 
>-integer_expr1--,--integer_expr2---+-------------------+-)----><
                                    +-,--integer_expr3--+
 

do_object
is an array element, scalar structure component, substring, or implied- DO list

do_variable
is a named scalar integer variable called the implied- DO variable. This variable is a statement entity.

integer_expr1, integer_expr2,  and  integer_expr3
are each scalar integer expressions. The primaries of an expression can only contain constants or implied- DO variables of other implied- DO lists that have this implied- DO list within their ranges. Each operation must be intrinsic.

initial_value



>>-+---------+--data_value-------------------------------------><
   +-r-- * --+
 

r
is a nonnegative scalar integer constant. If r is a named constant, it must have been declared previously in the scoping unit or made accessible by use or host association. If r is omitted, the default value is 1. The form r*data_value is equivalent tor successive appearances of the data value.

data_value
is a scalar constant, scalar subobject of a constant, signed integer literal constant, signed real literal constant, or structure constructor

Rules

Specifying an array object as a data_object is the same as specifying a list of all the elements in the array object in the order they are stored. Each data_object_list must specify the same number of items as its corresponding initial_value_list. There is a one-to-one correspondence between the items in these two lists. This correspondence establishes the initial value of each data_object.

The definition of each data_object by its corresponding initial_value must follow the rules for intrinsic assignment, except as noted under "Using Typeless Constants".

If initial_value is a structure constructor, each component must be an initialization expression. If data_object is a variable, any substring, subscript, or stride expressions must be initialization expressions.

If data_value is a named constant or structure constructor, the named constant or derived type must have been declared previously in the scoping unit or made accessible by use or host association.

Zero-sized arrays, implied- DO lists with iteration counts of zero, and values with a repeat factor of zero contribute no variables to the expanded initial_value_list, although a zero-length scalar character variable contributes one variable to the list.

You can use an implied- DO list in a DATA statement to initialize array elements, scalar structure components and substrings. The implied- DO list is expanded into a sequence of scalar structure components, array elements, or substrings, under the control of the implied- DO variable. Array elements and scalar structure components must not have constant parents. Each scalar structure component must contain at least one component reference that specifies a subscript list.

The range of an implied- DO list is the do_object_list. The iteration count and the values of the implied- DO variable are established from integer_expr1, integer_expr2, and integer_expr3, the same as for a DO statement. When the implied- DO list is executed, it specifies the items in the do_object_list once for each iteration of the implied- DO list, with the appropriate substitution of values for any occurrence of the implied- DO variables. If the implied- DO variable has an iteration count of 0, no variables are added to the expanded sequence.

Each subscript expression in a do_object can only contain constants or implied- DO variables of implied- DO lists that have the subscript expression within their ranges. Each operation must be intrinsic.

To initialize list items of type logical with logical constants, you can also use the abbreviated forms (T for .TRUE. and F for .FALSE.). If T or F is a constant name that was defined previously with the PARAMETER attribute, XL Fortran recognizes the string as the named constant and assigns its value to the corresponding list item in the DATA statement.

In a block data program unit, you can use a DATA statement or type declaration statement to provide an initial value for a variable in a named common block.

In an internal or module subprogram, if the data_object is the same name as an entity in the host, and the data_object is not declared in any other specification statement in the internal subprogram, the data_object must not be referenced or defined before the DATA statement.

A DATA statement cannot provide an initial value for:

You must not initialize a variable more than once in an executable program. If you associate two or more variables, you can only initialize one of the data objects.

Examples

      INTEGER Z(100),EVEN_ODD(0:9)
      LOGICAL FIRST_TIME
      CHARACTER*10 CHARARR(1)
      DATA    FIRST_TIME / .TRUE. /
      DATA    Z  / 100* 0 /
! Implied-DO list
      DATA  (EVEN_ODD(J),J=0,8,2) / 5 * 0 /  &
    &      ,(EVEN_ODD(J),J=1,9,2) / 5 * 1 /
! Nested example
      DIMENSION TDARR(3,4)  ! Initializes a two-dimensional array
      DATA ((TDARR(I,J),J=1,4),I=1,3) /12 * 0/
! Character substring example
      DATA (CHARARR(J)(1:3),J=1,1) /'aaa'/
      DATA (CHARARR(J)(4:7),J=1,1) /'bbbb'/
      DATA (CHARARR(J)(8:10),J=1,1) /'ccc'/
! CHARARR(1) contains 'aaabbbbccc'

Related Information

DEALLOCATE

Purpose

The DEALLOCATE statement dynamically deallocates allocatable arrays and pointer targets. A specified pointer becomes disassociated while any other pointers associated with the target become undefined.

Format




>>-DEALLOCATE-(--object_list--+------------------------------+-)-><
                              +-,--STAT-- = --stat_variable--+

object
is a pointer or an allocatable array

stat_variable
is a scalar integer variable

Rules

An allocatable array that appears in a DEALLOCATE statement must be currently allocated. An allocatable array with the TARGET attribute cannot be deallocated through an associated pointer. Deallocation of such an array causes the association status of any associated pointer to become undefined. An allocatable array that has an undefined allocation status cannot be subsequently referenced, defined, allocated, or deallocated. Successful execution of a DEALLOCATE statement causes the allocation status of an allocatable array to become not allocated.

A pointer that appears in a DEALLOCATE statement must be associated with a whole target that was created with an ALLOCATE statement. Deallocation of a pointer target causes the association status of any other pointer associated with all or part of the target to become undefined.
Tips

Use the DEALLOCATE statement instead of the NULLIFY statement if no other pointer is associated with the allocated memory.

Deallocate memory that a pointer function has allocated.

If the STAT= specifier is not present and an error condition occurs during execution of the statement, the program terminates. If the STAT= specifier is present, stat_variable is assigned one of the following values:
Stat value Error condition
0 No error
1 Error in system routine attempting to do deallocation
2 An invalid data object has been specified for deallocation
3 Both error conditions 1 and 2 have occurred

The stat_variable must not be deallocated within the DEALLOCATE statement in which it appears.

Examples

INTEGER, ALLOCATABLE :: A(:,:)
INTEGER X,Y
      ·
ALLOCATE (A(X,Y))
      ·
DEALLOCATE (A,STAT=I)
END

Related Information

Derived Type

Purpose

The Derived Type statement is the first statement of a derived-type definition.

Format



>>-TYPE--+--------------------------+--type_name---------------><
         +-+-----------------+--::--+
           +-,--access_spec--+
 

access_spec
is either PRIVATE or PUBLIC

type_name
is the name of the derived type

Rules

access_spec can only be specified if the derived-type definition is within the specification part of a module.

type_name cannot be the same as the name of any intrinsic type, except BYTE, or the name of any other accessible derived type.

If a label is specified on the Derived Type statement, the label belongs to the scoping unit of the derived-type definition.

If the corresponding END TYPE statement specifies a name, it must be the same as type_name.

Examples

MODULE ABC
  TYPE, PRIVATE :: SYSTEM      ! Derived type SYSTEM can only be accessed
    SEQUENCE                   !   within module ABC
    REAL :: PRIMARY
    REAL :: SECONDARY
    CHARACTER(20), DIMENSION(5) :: STAFF
  END TYPE
END MODULE

Related Information

DIMENSION

Purpose

The DIMENSION attribute specifies the name and dimensions of an array.

Format



>>-DIMENSION--+-----+--array_declarator_list-------------------><
              +-::--+
 

Rules

According to Fortran 90, you can specify an array with up to seven dimensions.

With XL Fortran, you can specify up to twenty dimensions.

Only one dimension specification for an array name can appear in a scoping unit.
Attributes Compatible with the DIMENSION Attribute

  • ALLOCATABLE
  • AUTOMATIC
  • INTENT
  • OPTIONAL

  • PARAMETER
  • POINTER
  • PRIVATE
  • PUBLIC

  • SAVE
  • STATIC
  • TARGET
  • VOLATILE

Examples

CALL SUB(5,6)
CONTAINS
SUBROUTINE SUB(I,M)
  DIMENSION LIST1(I,M)                         ! automatic array
  INTEGER, ALLOCATABLE, DIMENSION(:,:) :: A    ! deferred-shape array
       ·
END SUBROUTINE
END

Related Information

DO

Purpose

The DO statement controls the execution of the statements that follow it, up to and including a specified terminal statement. Together, these statements form a DO construct.

Format



>>-+-----------------------+--DO---+-------------+-------------->
   +-DO_construct_name--:--+       +-stmt_label--+
 
>--+----------------------------------------------------+------><
   +-+---+-var_name = a_expr1a_expr2--+------------+--+
     +-,-+                              +- , a_expr3-+
 

DO_construct_name
is a name given to the DO construct for identification

stmt_label
is the statement label of an executable statement appearing after the DO statement in the same scoping unit. This statement denotes the end of the DO construct.

var_name
is a scalar variable name of type integer or real, called the DO variable

a_expr1, a_expr2, and a_expr3
are each scalar expressions of type integer or real

Rules

If you specify a DO_construct_name on the DO statement, you must terminate the construct with an END DO and the same DO_construct_name. Conversely, if you do not specify a DO_construct_name on the DO statement, and you terminate the DO construct with an END DO statement, you must not have a DO_construct_name on the END DO statement.

If you specify a statement label in the DO statement, you must terminate the DO construct with a statement that is labeled with that statement label. You can terminate a labeled DOstatement with an END DO statement that is labeled with that statement label, but you cannot terminate it with an unlabeled END DO statement. If you do not specify a label in the DO statement, you must terminate the DO construct with an END DO statement.

If the control clause (the clause beginning with var_name) is absent, the statement is an infinite DO. The loop will iterate indefinitely until interrupted (for example, by the EXIT statement).

When compiling a DO loop using the XL Fortran compiler, you should consider whether inserting an INDEPENDENT directive immediately preceding each loop is valid. If the iterations of the DO loop cannot be executed in an arbitrary order, the INDEPENDENT directive is not valid. The directive specifies that each iteration in the DO loop can be executed in any order without affecting the semantics of the program. For more information on the INDEPENDENT directive, see INDEPENDENT.

Examples

INTEGER :: SUM=0
OUTER: DO
  INNER: DO M=1,10
    READ (5,*) J
    IF (J.LE.I) THEN
      PRINT *, 'VALUE MUST BE GREATER THAN ', I
      CYCLE INNER
    END IF
    SUM=SUM+J
    IF (SUM.GT.500) EXIT OUTER
    IF (SUM.GT.100) EXIT INNER
  END DO INNER
  SUM=SUM+I
  I=I+10
END DO OUTER
PRINT *, 'SUM =',SUM
END

Related Information

DO WHILE

Purpose

The DO WHILE statement is the first statement in the DO WHILE construct, which indicates that you want the following statement block, up to and including a specified terminal statement, to be repeatedly executed for as long as the logical expression specified in the statement continues to be true.

Format



>>-+-----------------------+--DO---+-------------+--+----+------>
   +-DO_construct_name--:--+       +-stmt_label--+  +-,--+
 
>--WHILE--(--logical_expr--)-----------------------------------><
 

DO_construct_name
is a name given to the DO WHILE construct for identification

stmt_label
is the statement label of an executable statement appearing after the DO WHILE statement in the same scoping unit. It denotes the end of the DO WHILE construct.

logical_expr
is a scalar logical expression

Rules

If you specify a DO_construct_name on the DO WHILE statement, you must terminate the construct with an END DO and the same DO_construct_name. Conversely, if you do not specify a DO_construct_name on the DO WHILE statement, and you terminate the DO WHILE construct with an END DO statement, you must not have a DO_construct_name on the END DO statement.

If you specify a statement label in the DO WHILE statement, you must terminate the DO WHILE construct with a statement that is labeled with that statement label. You can terminate a labeled DO WHILE statement with an END DO statement that is labeled with that statement label, but you cannot terminate it with an unlabeled END DO statement. If you do not specify a label in the DO WHILE statement, you must terminate the DO WHILE construct with an END DO statement.

Examples

 
      MYDO: DO 10 WHILE (I .LE. 5)  ! MYDO is the construct name
         SUM = SUM + INC
         I = I + 1
10    END DO MYDO
      END
 
      SUBROUTINE EXAMPLE2
        REAL X(10)
        LOGICAL FLAG1
        DATA    FLAG1 /.TRUE./
        DO 20 WHILE (I .LE. 10)
           X(I) = A
           I = I + 1
20      IF (.NOT. FLAG1) STOP
      END SUBROUTINE EXAMPLE2

Related Information

DOUBLE COMPLEX

Purpose

A DOUBLE COMPLEX type declaration statement specifies the attributes of objects and functions of type double complex. Initial values can be assigned to objects.

Format



>>-DOUBLE COMPLEX--+-+----+-----------------+-entity_decl_list--><
                   | +-::-+                 |
                   +-,--attr_spec_list--::--+
 

where:
attr_spec

ALLOCATABLE
AUTOMATIC
DIMENSION (array_spec)
EXTERNAL
INTENT (intent_spec)
INTRINSIC
OPTIONAL
PARAMETER
POINTER
PRIVATE
PUBLIC
SAVE
STATIC
TARGET
VOLATILE

attr_spec
For detailed information on rules about a particular attribute, refer to the statement of the same name.

intent_spec
is either IN, OUT, or INOUT

::
is the double colon separator. It is required if attributes are specified or if = initialization_expr is used.

array_spec
is a list of dimension bounds

entity_decl



>>-a--+-------------------+--+--------------------------------+-><
      +-(--array_spec--)--+  +--+-/--initial_value_list--/--+-+
                                +-=--initialization_expr----+
 

a
is an object name or function name. array_spec cannot be specified for a function name.

initial_value
provides an initial value for the entity specified by the immediately preceding name

initialization_expr
provides an initial value, by means of an initialization expression, for the entity specified by the immediately preceding name

Rules

Entities in type declaration statements are constrained by the rules of any attributes specified for the entities, as detailed in the corresponding attribute statements.

The type declaration statement overrides the implicit type rules in effect. You can use a type declaration statement that confirms the type of an intrinsic function. The appearance of a generic or specific intrinsic function name in a type declaration statement does not cause the name to lose its intrinsic property.

An object cannot be initialized in a type declaration statement if it is a dummy argument, an allocatable array, a pointer, a function result, an object in blank common, an integer pointer, an external name, an intrinsic name, or an automatic object. Nor can an object be initialized if it has the AUTOMATIC attribute. The object may be initialized if it appears in a named common block in a block data program unit or if it appears in a named common block in a module.

The specification expression of an array_spec can be a nonconstant expression if the specification expression appears in an interface body or in the specification part of a subprogram. Any object being declared that uses this nonconstant expression and is not a dummy argument or a pointee is called an automatic object.

An attribute cannot be repeated in a given type declaration statement, nor can an entity be explicitly given the same attribute more than once in a scoping unit.

initialization_expr must be specified if the statement contains the PARAMETER attribute. If initialization_expr is specified and PARAMETER is not, the object is a variable that is initially defined. a becomes defined with the value determined by initialization_expr, in accordance with the rules for intrinsic assignment. If the variable is an array, its shape must be specified either in the type declaration statement or in a previous specification statement in the same scoping unit. A variable or variable subobject cannot be initialized more than once. The presence of initialization_expr implies that a is a saved object, except for an object with the PARAMETER attribute or in a named common block. The initialization of an object could affect the fundamental storage class of an object.

An array_spec specified in the entity_decl takes precedence over the array_spec in the DIMENSION attribute.

An array function result that does not have the POINTER attribute must have an explicit-shape array specification.

If the entity declared is a function, it must not have an accessible explicit interface unless it is an intrinsic function.

If T or F, defined previously as the name of a constant, appears in a type declaration statement, it is no longer an abbreviated logical constant but the name of the named constant.

Examples

SUBROUTINE SUB
  DOUBLE COMPLEX, STATIC, DIMENSION(1) :: B
END SUBROUTINE

Related Information

DOUBLE PRECISION

Purpose

A DOUBLE PRECISION type declaration statement specifies the attributes of objects and functions of type double precision. Initial values can be assigned to objects.

Format




>>-DOUBLE PRECISION-+-+----+-----------------+-entity_decl_list-><
                    | +-::-+                 |
                    +-,--attr_spec_list--::--+

where:


attr_spec

ALLOCATABLE
AUTOMATIC
DIMENSION (array_spec)
EXTERNAL
INTENT (intent_spec)
INTRINSIC
OPTIONAL
PARAMETER
POINTER
PRIVATE
PUBLIC
SAVE
STATIC
TARGET
VOLATILE

attr_spec
For detailed information on rules about a particular attribute, refer to the statement of the same name.

intent_spec
is either IN, OUT, or INOUT

::
is the double colon separator. It is required if attributes are specified or if = initialization_expr is used.

array_spec
is a list of dimension bounds

entity_decl



>>-a--+-------------------+--+--------------------------------+-><
      +-(--array_spec--)--+  +--+-/--initial_value_list--/--+-+
                                +- = --initialization_expr--+
 

 

a
is an object name or function name. array_spec cannot be specified for a function name.

initial_value
provides an initial value for the entity specified by the immediately preceding name

initialization_expr
provides an initial value, by means of an initialization expression, for the entity specified by the immediately preceding name

Rules

Entities in type declaration statements are constrained by the rules of any attributes specified for the entities, as detailed in the corresponding attribute statements.

The type declaration statement overrides the implicit type rules in effect. You can use a type declaration statement that confirms the type of an intrinsic function. The appearance of a generic or specific intrinsic function name in a type declaration statement does not cause the name to lose its intrinsic property.

An object cannot be initialized in a type declaration statement if it is a dummy argument, an allocatable array, a pointer, a function result, an object in blank common, an integer pointer, an external name, an intrinsic name, or an automatic object. Nor can an object be initialized if it has the AUTOMATIC attribute. The object may be initialized if it appears in a named common block in a block data program unit or if it appears in a named common block in a module.

The specification expression of an array_spec can be a nonconstant expression if the specification expression appears in an interface body or in the specification part of a subprogram. Any object being declared that uses this nonconstant expression and is not a dummy argument or a pointee is called an automatic object.

An attribute cannot be repeated in a given type declaration statement, nor can an entity be explicitly given the same attribute more than once in a scoping unit.

initialization_expr must be specified if the statement contains the PARAMETER attribute. If initialization_expr is specified and PARAMETER is not, the object is a variable that is initially defined. a becomes defined with the value determined by initialization_expr, in accordance with the rules for intrinsic assignment. If the variable is an array, its shape must be specified either in the type declaration statement or in a previous specification statement in the same scoping unit. A variable or variable subobject cannot be initialized more than once. The presence of initialization_expr implies that a is a saved object, except for an object with the PARAMETER attribute or in a named common block. The initialization of an object could affect the fundamental storage class of an object.

An array_spec specified in the entity_decl takes precedence over the array_spec in the DIMENSION attribute.

An array function result that does not have the POINTER attribute must have an explicit-shape array specification.

If the entity declared is a function, it must not have an accessible explicit interface unless it is an intrinsic function.

If T or F, defined previously as the name of a constant, appears in a type declaration statement, it is no longer an abbreviated logical constant but the name of the named constant.

Examples

      DOUBLE PRECISION, POINTER :: PTR
      DOUBLE PRECISION, TARGET  :: TAR

Related Information

ELSE

Purpose

The ELSE statement is the first statement of the optional ELSE block within an IF construct.

Format



>>-ELSE--+--------------------+--------------------------------><
         +-IF_construct_name--+
 

IF_construct_name
is a name given to the IF construct for identification

Format

Control branches to the ELSE block if every previous logical expression in the IF construct evaluates as false. The statement block of the ELSE block is executed and the IF construct is complete.

If the IF_construct_name is specified, it must be the same name as specified in the block IF statement.

Examples

    IF (A.GT.0) THEN
      B = B-A
    ELSE            ! the next statement is executed if a<=0
      B = B+A
    END IF

Related Information

ELSE IF

Purpose

The ELSE IF statement is the first statement of an optional ELSE IF block within an IF construct.

Format




>>-ELSE IF--(--scalar_logical_expr--)--THEN-+-------------------+-><
                                            +-IF_construct_name-+

IF_construct_name
is a name given to the IF construct for identification

Rules

scalar_logical_expr is evaluated if no previous logical expressions in the IF construct are evaluated as true. If scalar_logical_expr is true, the statement block that follows is executed and the IF construct is complete.

If the IF_construct_name is specified, it must be the same name as specified in the block IF statement.

Examples

IF (I.EQ.1) THEN
    J=J-1
ELSE IF (I.EQ.2) THEN
    J=J-2
ELSE IF (I.EQ.3) THEN
    J=J-3
ELSE
    J=J-4
END IF

Related Information

ELSEWHERE

Purpose

The ELSEWHERE statement is the first statement of the optional ELSEWHERE block within a WHERE construct.

Format



>>-ELSEWHERE---------------------------------------------------><
 

Rules

The mask expression that applies to all assignment statements in the ELSEWHERE block is (.NOT. mask_expr), where mask_expr is defined in the construct's WHERE statement.

Examples

INTEGER A(10),B(10)
WHERE (A>=0)
  B = SIN(A)
ELSEWHERE       ! Mask expression evaluates for A<0
  B = COS(A)
END WHERE

Related Information

END

Purpose

An END statement indicates the end of a program unit or procedure.

Format



>>-END--+----------------------------------+-------------------><
        +-BLOCK DATA-+-----------------+---+
        |            +-BLOCK_DATA_name-+   |
        +-FUNCTION-+---------------+-------+
        |          +-FUNCTION_name-+       |
        +-MODULE-+-------------+-----------+
        |        +-MODULE_name-+           |
        +-PROGRAM-+--------------+---------+
        |         +-PROGRAM_name-+         |
        +-SUBROUTINE-+-----------------+---+
                     +-SUBROUTINE_name-+
 

Rules

The END statement is the only required statement in a program unit.

For an internal subprogram or module subprogram, you must specify the FUNCTION or SUBROUTINE keyword on the END statement. For block data program units, external subprograms, the main program, modules and interface bodies, the corresponding keyword is optional.

The program name can be included in the END PROGRAM statement only if the optional PROGRAM statement is used and if the name is identical to the program name specified in the PROGRAM statement.

The block data name can be included in the END BLOCK DATA statement only if it is provided in the BLOCK DATA statement and if the name is identical to the block data name specified in the BLOCK DATA statement.

If a name is specified in an END MODULE, END FUNCTION, or END SUBROUTINE statement, it must be identical to the name specified in the corresponding MODULE, FUNCTION, or SUBROUTINE statement, respectively.

The END, END FUNCTION, END PROGRAM, and END SUBROUTINE statements are executable statements that can be branched to. In both fixed source form and Fortran 90 free source form formats, no other statement may follow the END statement on the same line. In fixed source form format, you cannot continue a program unit END statement, nor can a statement whose initial line appears to be a program unit END statement be continued.

The END statement of a main program terminates execution of the program. The END statement of a function or subroutine has the same effect as a RETURN statement. An inline comment can appear on the same line as an END statement. Any comment line appearing after an END statement belongs to the next program unit.

Examples

PROGRAM TEST
  CALL SUB()
  CONTAINS
    SUBROUTINE SUB
        ·
    END SUBROUTINE    ! Reference to subroutine name SUB is optional
END PROGRAM TEST

Related Information

Chapter 7. "Program Units and Procedures"

END (Construct)

Purpose

The END DO, END FORALL, END IF, END SELECT, and END WHERE statements terminate DO (or DO WHILE), FORALL, IF, CASE, and WHERE constructs, respectively.

Format



>>-+-END DO-+-------------------+-----------+------------------><
   |        +-DO_construct_name-+           |
   +-END FORALL-+-----------------------+---+
   |            +-FORALL_construct_name-+   |
   +-END IF-+-------------------+-----------+
   |        +-IF_construct_name-+           |
   +-END SELECT-+---------------------+-----+
   |            +-CASE_construct_name-+     |
   +-END WHERE------------------------------+
 

DO_construct_name
is a name given to identify a DO or DO WHILE construct

FORALL_construct_name
is a name given to identify a FORALL construct

IF_construct_name
is a name given to identify an IF construct

CASE_construct_name
is a name given to identify a CASE construct

Rules

If you label the END DO statement, you can use it as the terminal statement of a labeled or unlabeled DO or DO WHILE construct. An END DO statement terminates the innermost DO or DO WHILE construct only. If a DO or DO WHILE statement does not specify a statement label, the terminal statement of the DO or DO WHILE construct must be an END DO statement.

You can branch to an END DO, END IF, or END SELECT statement from within the DO (or DO WHILE), IF, or CASE construct, respectively. An END IF statement can also be branched to from outside of the IF construct.

If you specify a construct name on the statement that begins the construct, the END statement that terminates the construct must have the same construct name. Conversely, if you do not specify a construct name on the statement that begins the construct, you must not specify a construct name on the END statement.

Examples

INTEGER X(100,100)
DECR: DO WHILE (I.GT.0)
     ·
  IF (J.LT.K) THEN
     ·
  END IF                 ! Cannot reference a construct name
  I=I-1
END DO DECR              ! Reference to construct name DECR mandatory
 
END

Related Information

END INTERFACE

Purpose

The END INTERFACE statement terminates a procedure interface block.

Format



>>-END INTERFACE-----------------------------------------------><
 

Rules

Each INTERFACE statement must have a corresponding END INTERFACE statement.

Examples

INTERFACE OPERATOR (.DETERMINANT.)
  FUNCTION DETERMINANT (X)
    INTENT(IN) X
    REAL X(50,50), DETERMINANT
  END FUNCTION
END INTERFACE

Related Information

END TYPE

Purpose

The END TYPE statement indicates the completion of a derived-type definition.

Format



>>-END TYPE-+-----------+--------------------------------------><
            +-type_name-+
 

Rules

If type_name is specified, it must match the type_name in the corresponding Derived Type statement.

If a label is specified on the END TYPE statement, the label belongs to the scoping unit of the derived-type definition.

Examples

TYPE A
  INTEGER :: B
  REAL :: C
END TYPE A

Related Information

ENDFILE

Purpose

The ENDFILE statement writes an endfile record as the next record of an external file connected for sequential access. This record becomes the last record in the file.

Format



>>-ENDFILE--+-u--------------------+---------------------------><
            +-(--position_list--)--+
 

u
is an external unit identifier. The value of u must not be an asterisk or a Hollerith constant.

position_list
is a list that must contain one unit specifier ([ UNIT=]u) and can also contain one of each of the other valid specifiers:

[UNIT=] u
is a unit specifier in which u must be an external unit identifier whose value is not an asterisk. An external unit identifier refers to an external file that is represented by a scalar integer expression, whose value is in the range 1 through 2147483647. If the optional characters UNIT= are omitted, u must be the first item in position_list.

IOSTAT= ios
is an input/output status specifier that specifies the status of the input/output operation. ios is a scalar variable of type INTEGER(4) or default integer. When the ENDFILE statement finishes executing, ios is defined with:

ERR= stmt_label
is an error specifier that specifies the statement label of an executable statement in the same scoping unit to which control is to transfer in the case of an error. Coding the ERR= specifier suppresses error messages.

Rules

If the unit is not connected, an implicit OPEN specifying sequential access is performed to a default file named fort.n, where n is the value of u with leading zeros removed.

If two ENDFILE statements are executed for the same file without an intervening REWIND or BACKSPACE statement, the second ENDFILE statement is ignored.

If the ERR= and IOSTAT= specifiers are set and an error is encountered, transfer is made to the statement specified by the ERR= specifier and a positive integer value is assigned to ios.

If IOSTAT= and ERR= are not specified,

Examples

      ENDFILE 12
      ENDFILE (IOSTAT=IOSS,UNIT=11)

Related Information

ENTRY

Purpose

A function subprogram or subroutine subprogram has a primary entry point that is established through the SUBROUTINE or FUNCTION statement. The ENTRY statement establishes an alternate entry point for an external subprogram or a module subprogram.

Format



>>-ENTRY--entry_name-------------------------------------------->
 
>--+-----------------------------------------------------------------+-><
   +-(--+----------------------+--)--+----------------------------+--+
        +-dummy_argument_list--+     +-RESULT--(--result_name--)--+
 

entry_name
is the name of an entry point in a function subprogram or subroutine subprogram

Rules

The ENTRY statement cannot appear in a main program, block data program unit, internal subprogram, IF construct, DO construct, CASE construct, derived-type definition or interface block.

The ENTRY statement cannot appear in a CRITICAL construct.

An ENTRY statement can appear anywhere after the FUNCTION or SUBROUTINE statement (and after any USE statements) of an external or module subprogram, except in a statement block within a control construct, in a derived-type definition, or in an interface block. ENTRY statements are nonexecutable and do not affect control sequencing during the execution of a subprogram.

The result variable is result_name, if specified; otherwise, it is entry_name. If the characteristics of the ENTRY statement's result variable are the same as those of the FUNCTION statement's result variable, the result variables identify the same variable, even though they can have different names. Otherwise, they are storage-associated and must be all nonpointer scalars of intrinsic (noncharacter) type. result_name can be the same as the result variable name specified for the FUNCTION statement or another ENTRY statement.

The result variable cannot be specified in a COMMON, DATA, integer POINTER, or EQUIVALENCE statement, nor can it have the ALLOCATABLE, PARAMETER, INTENT, OPTIONAL, SAVE, or VOLATILE attributes. The STATIC and AUTOMATIC attributes can be specified only if the result variable is not an array or a pointer and is not of character or derived type.

If the RESULT keyword is specified, the ENTRY statement must be within a function subprogram, entry_name must not appear in any specification statement in the scope of the function subprogram, and result_name cannot be the same as entry_name.

A result variable cannot be initialized in a type declaration statement.

The entry name in an external subprogram is a global entity; an entry name in a module subprogram is not a global entity. An interface for an entry can appear in an interface block only when the entry name is used as the procedure name in an interface body.

In a function subprogram, entry_name identifies an external or module function that can be referenced as a function from the calling procedure. In a subroutine subprogram, entry_name identifies a subroutine and can be referenced as a subroutine from the calling procedure. When the reference is made, execution begins with the first executable statement following the ENTRY statement.

The result variable must be defined prior to exiting from the function, when the function is invoked through that entry.

A name in the dummy_argument_list must not appear:

The order, number, type, and kind type parameters of the dummy arguments can differ from those of the FUNCTION or SUBROUTINE statement, or other ENTRY statements.

If a dummy argument is used in a specification expression to specify an array bound or character length of an object, you can only specify the object in a statement that is executed during a procedure reference if the dummy argument is present and appears in the dummy argument list of the procedure name referenced.

Recursion

An ENTRY statement can reference itself directly, only if the subprogram statement specifies RECURSIVE and the ENTRY statement specifies RESULT. The entry procedure then has an explicit interface within the subprogram. The RESULT clause is not required for an entry to reference itself indirectly.

If entry_name is of type character, its length cannot be an asterisk if the function is recursive.

You can also call external procedures recursively when you specify the -qrecur compiler option, although XL Fortran disregards this option if a procedure specifies either the RECURSIVE or RESULT keyword.

Examples

RECURSIVE FUNCTION FNC() RESULT (RES)
     ·
  ENTRY ENT () RESULT (RES)          ! The result variable name can be
                                     ! the same as for the function
       ·
END FUNCTION

Related Information

EQUIVALENCE

Purpose

The EQUIVALENCE statement specifies that two or more objects in a scoping unit are to share the same storage.

Format



                +-,-----------------------------------------+
                V                                           |
>>-EQUIVALENCE----(--equiv_object--,--equiv_object_list--)--+--><
 

equiv_object
is a variable name, array element, or substring. Any subscript or substring expression must be an integer initialization expression.

Rules

equiv_object must not be a target, pointer, dummy argument, function name, pointee, entry name, result name, structure component, named constant, automatic data object, allocatable array, object of nonsequence derived type, object of sequence derived type that contains a pointer in the structure, or subobject of any of these.

Because all items named within a pair of parentheses have the same first storage unit, they become associated. This is called equivalence association. It may cause the association of other items as well.

If you specify an array element in an EQUIVALENCE statement, the number of subscript quantities cannot exceed the number of dimensions in the array. If you specify a multidimensional array using an array element with a single subscript n, the nth element in the array's storage sequence is specified. In all other cases, XL Fortran replaces any missing subscript with the lower bound of the corresponding dimension of the array. A nonzero-sized array without a subscript refers to the first element of the array.

If equiv_object is of derived type, it must be of a sequence derived type.

You can equivalence an object of sequence derived type with any other object of sequence derived type or intrinsic data type provided that the object is allowed in an EQUIVALENCE statement.

In XL Fortran, associated items can be of any intrinsic type or of sequence derived type. If they are, the EQUIVALENCE statement does not cause type conversion.

The lengths of associated items do not have to be equal.

Any zero-sized items are storage-associated with one another and with the first storage unit of any nonzero-sized sequences.

An EQUIVALENCE statement cannot associate the storage sequences of two different common blocks. It must not specify that the same storage unit is to occur more than once in a storage sequence. An EQUIVALENCE statement must not contradict itself or any previously established associations caused by an EQUIVALENCE statement.

You can cause names not in common blocks to share storage with a name in a common block using the EQUIVALENCE statement.

You can extend a common block by using an EQUIVALENCE statement, but only by adding beyond the last entry, not before the first entry. For example, if the variable that you associate to a variable in a common block, using the EQUIVALENCE statement, is an element of an array, the implicit association of the rest of the elements of the array can extend the size of the common block.

Examples

      DOUBLE PRECISION A(3)
      REAL B(5)
      EQUIVALENCE (A,B(3))

Association of storage units:

          |      |      |      |      |      |      |      |      |
Array A:                |    A(1)     |    A(2)     |    A(3)     |
Array B:  | B(1) | B(2) | B(3) | B(4) | B(5) |

This example shows how association of two items can result in further association.

      AUTOMATIC A
      CHARACTER A*4,B*4,C(2)*3
      EQUIVALENCE (A,C(1)),(B,C(2))

Association of storage units:

             |      |      |      |      |      |      |      |
Variable A:  |             A             |
Variable B:                       |             B             |
Array C:     |        C(1)        |        C(2)        |

Because XL Fortran associates A and B with C, A and B become associated with each other, and they all have the automatic storage class.

      INTEGER(4)   G(2,-1:2,-3:2)
      REAL(4)      H(3,1:3,2:3)
      EQUIVALENCE  (G(2),H(1,1))   ! G(2) is G(2,-1,-3)
                                   ! H(1,1) is H(1,1,2)

Related Information

EXIT

Purpose

The EXIT statement terminates execution of a DO construct or DO WHILE construct before the construct completes all of its iterations.

Format



>>-EXIT-+-------------------+----------------------------------><
        +-DO_construct_name-+
 

DO_construct_name
is the name of the DO or DO WHILE construct

Rules

The EXIT statement is placed within a DO or DO WHILE construct and belongs to the DO or DO WHILE construct specified by DO_construct_name or, if not specified, by the DO or DO WHILE construct that immediately surrounds it. When a DO_construct_name is specified, the EXIT statement must be in the range of that construct.

When the EXIT statement is executed, the DO or DO WHILE construct that the EXIT statement belongs to becomes inactive. If the EXIT statement is nested in any other DO or DO WHILE constructs, they also become inactive. Any DO variable present retains its last defined value. If the DO construct has no construct control, it will iterate infinitely unless it becomes inactive. The EXIT statement can be used to make the construct inactive.

An EXIT statement can have a statement label; it cannot be used as the labeled action statement which terminates a DOor DO WHILE construct.

Examples

      LOOP1: DO I = 1, 20
         N = N + 1
10       IF (N > NMAX) EXIT LOOP1           ! EXIT from LOOP1
 
         LOOP2: DO WHILE (K==1)
            KMAX = KMAX - 1
20          IF (K > KMAX) EXIT              ! EXIT from LOOP2
         END DO LOOP2
         LOOP3:  DO J = 1, 10
             N = N + 1
30           IF (N > NMAX) EXIT LOOP1       ! EXIT from LOOP1
             EXIT LOOP3                     ! EXIT from LOOP3
         END DO LOOP3
 
      END DO LOOP1

Related Information

EXTERNAL

Purpose

The EXTERNAL attribute specifies that a name represents an external procedure, a dummy procedure, or a block data program unit. A procedure name with the EXTERNAL attribute can be used as an actual argument.

Format



>>-EXTERNAL--name_list-----------------------------------------><
 

name
is the name of an external procedure, dummy procedure, or BLOCK DATA program unit

Rules

If an external procedure name or dummy argument name is used as an actual argument, it must be declared with the EXTERNAL attribute or by an interface block in the scoping unit, but may not appear in both.

If an intrinsic procedure name is specified with the EXTERNAL attribute in a scoping unit, the name becomes the name of a user-defined external procedure. Therefore, you cannot invoke that intrinsic procedure by that name from that scoping unit.

You can specify a name to have the EXTERNAL attribute only once in a scoping unit.

A name in an EXTERNAL statement must not also be specified as a specific procedure name in an interface block in the scoping unit.
Attributes Compatible with the EXTERNAL Attribute

  • OPTIONAL

  • PRIVATE

  • PUBLIC

Examples

      PROGRAM MAIN
        EXTERNAL AAA
        CALL SUB(AAA)         ! Procedure AAA is passed to SUB
      END
 
      SUBROUTINE SUB(ARG)
        CALL ARG()            ! This results in a call to AAA
      END SUBROUTINE

Related Information

FORALL

Purpose

The FORALL statement performs assignment to groups of subobjects, especially array elements. Unlike the WHERE statement, assignment can be performed on an elemental level rather than on an array level. The FORALL statement also allows pointer assignment.

Format



>>-FORALL--forall_header--forall_assignment--------------------><
 

forall_header



>>-(--forall_triplet_spec_list--+----------------------+--)----><
                                +-,--scalar_mask_expr--+
 

forall_triplet_spec



>>-index_name-- = --subscript-- : --subscript-- : --subscript--->
 
>--+--------------+--------------------------------------------><
   +- : --stride--+
 

forall_assignment
is either assignment_statement or pointer_assignment_statement

scalar_mask_expr
is a scalar logical expression

subscript, stride
are each scalar integer expressions

Rules

Only pure procedures can be referenced in the mask expression of forall_header and in a forall_assignment (including one referenced by a defined operation or assignment).

index_name must be a scalar integer variable. It is also a statement entity; that is, it does not affect and is not affected by other entities in the scoping unit.

In forall_triplet_spec_list, neither a subscript nor a stride can contain a reference to any index_name in the forall_triplet_spec_list. Evaluation of any expression in forall_header must not affect evaluation of any other expression in forall_header.

Given the forall_triplet_spec

     index1 = s1:s2:s3
the maximum number of index values is determined by:
     max = INT((s2-s1+s3)/s3)
If the stride (s3 above) is not specified, a value of 1 is assumed. If max <= 0 for any index, forall_assignment is not executed. For example,
     index1 = 2:10:3    !  The index values are 2,5,8.
                           max = INT((10-2+3)/3) = 3.
 
     index2 = 6:2:-1    !  The index values are 6,5,4,3,2.
     index2 = 6:2       !  No index values.

If the mask expression is omitted, a value of .TRUE. is assumed.

No atomic object can be assigned to more than once. Assignment to a nonatomic object assigns to all subobjects or associates targets with all subobjects.

Interpreting the FORALL Statement

  1. Evaluate the subscript and stride expressions for each forall_triplet_spec in any order. All possible pairings of index_name values form the set of combinations. For example, given the following statement:
    FORALL (I=1:3,J=4:5) A(I,J) = A(J,I)
    
    The set of combinations of I and J is:
        {(1,4),(1,5),(2,4),(2,5),(3,4),(3,5)}
    

    The -1 and -qnozerosize compiler options do not affect this step.

  2. Evaluate the scalar_mask_expr for the set of combinations, in any order, producing a set of active combinations (those for which scalar_mask_expr evaluated to .TRUE.). For example, if the mask (I+J.NE.6) is applied to the above set, the set of active combinations is:
        {(1,4),(2,5),(3,4),(3,5)}
    

  3. For assignment_statement, evaluate, in any order, all values in the right-hand side expression and all subscripts, strides, and substring bounds in the left-hand side variable for all active combinations of index_name values.

    For pointer_assignment, determine, in any order, what will be the targets of the pointer assignment and evaluate all subscripts, strides, and substring bounds in the pointer for all active combinations of index_name values. Whether or not the target is a pointer, the determination of the target does not include evaluation of its value.

  4. For assignment_statement, assign, in any order, the computed expression values to the corresponding variable entities for all active combinations of index_name values.

    For pointer_assignment, associate, in any order, all targets with the corresponding pointer entities for all active combinations of index_name values.

Loop Parallelization

The FORALL statement and FORALL construct are designed to allow for parallelization of assignment statements. When executing an assignment statement in a FORALL, the assignment of an object will not interfere with the assignment of another object. In the next example, the assignments to elements of A can be executed in any order without changing the results:

  FORALL (I=1:3,J=1:3) A(I,J)=A(J,I)

The INDEPENDENT directive asserts that each iteration of a DO loop or each operation in a FORALL statement or FORALL construct can be executed in any order without affecting the semantics of the program. The operations in a FORALL statement or FORALL construct are defined as:

Thus, the following loop,

         INTEGER, DIMENSION(2000) :: A,B,C
!IBM*  INDEPENDENT
         DO I = 1, 1999, 2
           A(I) = A(I+1)
         END DO
is semantically equivalent to the following array assignment:
         INTEGER, DIMENSION(2000) :: A,B,C
         A(1:1999:2) = A(2:2000:2)
Tip

If it is possible and beneficial to parallelize a specific loop, specify the INDEPENDENT directive before the loop. Because XL Fortran may not always be able to determine whether it is legal to parallelize a loop, the INDEPENDENT directive provides an assertion that it is legal.

Examples

INTEGER A(1000,1000), B(200)
I=17
FORALL (I=1:1000,J=1:1000,I.NE.J) A(I,J)=A(J,I)
PRINT *, I    ! The value 17 is printed because the I
              ! in the FORALL has statement scope.
FORALL (N=1:200:2) B(N)=B(N+1)
END

Related Information

FORALL (Construct)

Purpose

The FORALL (Construct) statement is the first statement of the FORALL construct.

Format



>>-+-----------------------------+--FORALL--+----------------+-><
   +-FORALL_construct_name-- : --+          +-forall_header--+
 

forall_header



>>-(--forall_triplet_spec_list---+----------------------+--)---><
                                 +-,--scalar_mask_expr--+
 

forall_triplet_spec



>>-index_name-- = --subscript-- : --subscript---+--------------+-><
                                                +- : --stride--+
 

scalar_mask_expr
is a scalar logical expression

subscript, stride
are each scalar integer expressions

Rules

Any procedures that are referenced in the mask expression of forall_header (including one referenced by a defined operation or assignment) must be pure.

The index_name must be a scalar integer variable. The scope of index_name is the whole FORALL construct.

In forall_triplet_spec_list, neither a subscript nor a stride can contain a reference to any index_name in the forall_triplet_spec_list. Evaluation of any expression in forall_header must not affect evaluation of any other expression in forall_header.

Given the following forall_triplet_spec:

     index1 = s1:s2:s3
The maximum number of index values is determined by:
     max = INT((s2-s1+s3)/s3)
If the stride (s3 above) is not specified, a value of 1 is assumed. If max <= 0 for any index, forall_assignment is not executed. For example:
     index1 = 2:10:3    !  The index values are 2,5,8.
                        !  max = floor(((10-2)/3)+1) = 3.
 
     index2 = 6:2:-1    !  The index values are 6,5,4,3,2.
     index2 = 6:2       !  No index values.

If the mask expression is omitted, a value of .TRUE. is assumed.

Examples

POSITIVE: FORALL (X=1:100,A(X)>0)
  I(X)=I(X)+J(X)
  J(X)=J(X)-I(X+1)
END FORALL POSITIVE

Related Information

FORMAT

Purpose

The FORMAT statement provides format specifications for input/output statements.

Format



>>-FORMAT--(-+------------------+---)--------------------------><
             +-format_item_list-+
 

format_item



>>-+-+---+---data_edit_desc----------+-------------------------><
   | +-r-+                           |
   +-control_edit_desc---------------+
   +-+---+---(--format_item_list--)--+
   | +-r-+                           |
   +-char_string_edit_desc-----------+
 

r
is an unsigned, positive, integer literal constant that cannot specify a kind type parameter, or a scalar integer expression enclosed by angle brackets (< and >). It is called a repeat specification. It specifies the number of times to repeat the format_item_list or the data_edit_desc. The default is 1.

data_edit_desc
is a data edit descriptor

control_edit_desc
is a control edit descriptor

char_string_edit_desc
is a character string edit descriptor

Data Edit Descriptors


Forms Use Page
A
Aw

Edits character values "A (Character) Editing"
Bw
Bw.m

Edits binary values "B (Binary) Editing"
Ew.d
Ew.dEe
Ew.dDe
Ew.dQe
Dw.d
ENw.d
ENw.dEe
ESw.d
ESw.dEe
Qw.d

Edits real and complex numbers with exponents "E, D, and Q (Extended Precision) Editing"
Fw.d
Edits real and complex numbers without exponents "F (Real without Exponent) Editing"
Gw.d
Gw.dEe
Gw.dDe
Gw.dQe

Edits data fields of any intrinsic type, with the output format adapting to the type of the data and, if the data is of type real, the magnitude of the data "G (General) Editing"
Iw
Iw.m

Edits integer numbers "I (Integer) Editing"
Lw
Edits logical values "L (Logical) Editing"
Ow
Ow.m

Edits octal values "O (Octal) Editing"
Q
Returns the count of characters remaining in an input record "Q (Character Count) Editing"
Zw
Zw.m

Edits hexadecimal values "Z (Hexadecimal) Editing"

where:

w
specifies the width of a field, including all blanks

m
specifies the number of digits to be printed

d
specifies the number of digits to the right of the decimal point

e
specifies the number of digits in the exponent field

w, m, d, and e can be:

You cannot specify kind parameters for w, m, d, or e.
Note:

There are two types of Q data edit descriptor ( Qw.d and Q):

extended precision Q
is the Q edit descriptor whose syntax is Qw .d

character count Q
is the Q edit descriptor whose syntax is Q

Control Edit Descriptors


Forms Use Page
/
 
r /

Specifies the end of data transfer on the current record "/ (Slash) Editing"
: Specifies the end of format control if there are no more items in the input/output list ": (Colon) Editing"
$
Suppresses end-of-record in output "$ (Dollar) Editing"
BN
Ignores nonleading blanks in numeric input fields "BN (Blank Null) and BZ (Blank Zero) Editing"
BZ
Interprets nonleading blanks in numeric input fields as zeros "BN (Blank Null) and BZ (Blank Zero) Editing"
k P Specifies a scale factor for real and complex items "P (Scale Factor) Editing"
S SS

Specifies plus signs are not to be written "S, SP, and SS (Sign Control) Editing"
SP
Specifies plus signs are to be written "S, SP, and SS (Sign Control) Editing"
Tc
Specifies the absolute position in a record from which, or to which, the next character is transferred "T, TL, TR, and X (Positional) Editing"
TLc
Specifies the relative position (backward from the current position in a record) from which, or to which, the next character is transferred "T, TL, TR, and X (Positional) Editing"
TRc
Specifies the relative position (forward from the current position in a record) from which, or to which, the next character is transferred "T, TL, TR, and X (Positional) Editing"
o X Specifies the relative position (forward from the current position in a record) from which, or to which, the next character is transferred "T, TL, TR, and X (Positional) Editing"

where:

r
is a repeat specifier. It is an unsigned, positive, integer literal constant.

k
specifies the scale factor to be used. It is an optionally signed, integer literal constant.

c
specifies the character position in a record. It is an unsigned, nonzero, integer literal constant.

o
is the relative character position in a record. It is an unsigned, nonzero, integer literal constant.

r, k, c, and o can also be expressed as an arithmetic expression enclosed by < and > that evaluates into an integer value.

Kind type parameters cannot be specified for r, k, c, or o.

Character String Edit Descriptors


Forms Use Page
n Hstr Outputs a character string (str) "H Editing"
'
str'
"str"

Outputs a character string (str) "Apostrophe/Double Quotation Mark Editing (Character-String Edit Descriptor)"

n
is the number of characters in a literal field. It is an unsigned, positive, integer literal constant. Blanks are included in character count. A kind type parameter cannot be specified.

Rules

When a format identifier in a formatted READ, WRITE, or PRINT statement is a statement label or a variable that is assigned a statement label, the statement label identifies a FORMAT statement.

The FORMAT statement must have a statement label. FORMAT statements cannot appear in block data program units, interface blocks, the scope of a module, or derived-type definitions.

Commas separate edit descriptors. You can omit the comma between a P edit descriptor and an F, E, EN, ES, D, G, or Q (both extended precision and character count) edit descriptor immediately following it, before a slash edit descriptor when the optional repeat specification is not present, after a slash edit descriptor, and before or after a colon edit descriptor.

FORMAT specifications can also be given as character expressions in input/output statements.

XL Fortran treats upper and lowercase characters in format specifications the same, except in character string edit descriptors.

Character Format Specification

When a format identifier (see READ) in a formatted READ, WRITE, or PRINT statement is a character array name or character expression, the value of the array or expression is a character format specification.

If the format identifier is a character array element name, the format specification must be completely contained within the array element. If the format identifier is a character array name, the format specification can continue beyond the first element into following consecutive elements.

Blanks can precede the format specification. Character data can follow the right parenthesis that ends the format specification without affecting the format specification.

Variable Format Expressions

Wherever an integer constant is required by an edit descriptor, you can specify an integer expression in a FORMAT statement. The integer expression must be enclosed by angle brackets ( < and >). You cannot use a sign outside of a variable format expression. The following are valid format specifications:

      WRITE(6,20) INT1
20    FORMAT(I<MAX(20,5)>)
 
      WRITE(6,FMT=30) INT2, INT3
30    FORMAT(I<J+K>,I<2*M>)

The integer expression can be any valid Fortran expression, including function calls and references to dummy arguments, with the following restrictions:

The value of the expression is reevaluated each time an input/output item is processed during the execution of the READ, WRITE, or PRINT statement.

Examples

      CHARACTER*32 CHARVAR
      CHARVAR="('integer: ',I2,'  binary: ',B8)"  ! Character format specification
      M = 56
      J = 1                                       !     OUTPUT:
      X = 2355.95843                              !
      WRITE (6,770) M,X                           !  56   2355.96
      WRITE (6,CHARVAR) M,M                       ! integer: 56  binary: 00111000
      WRITE (6,880) J,M                           !  1
                                                  ! 56
770   FORMAT(I3, 2F10.2)
880   FORMAT(I<J+1>)
      END

Related Information

FUNCTION

Purpose

The FUNCTION statement is the first statement of a function subprogram.

Format



   +-------------+
   V             |
>>---+---------+-+-FUNCTION--name--+---------+------------------>
     +-prefix--+                   +-*--len--+
 
>--(-+---------------------+---)--+----------------------------+-><
     +-dummy_argument_list-+      +-RESULT--(--result_name--)--+
 

prefix
is one of the following:
type_spec
RECURSIVE
PURE

type_spec
specifies the type and type parameters of the function result. See Type Declaration for details about type_spec.

name
is the name of the function subprogram

len
is an unsigned, positive, integer literal constant that cannot specify a kind type parameter. It represents the permissible length specifications for its associated type. It can be included only when the type is specified. The type cannot be DOUBLE PRECISION, DOUBLE COMPLEX, BYTE, or a derived type.

Rules

At most one of each kind of prefix can be specified.

The type and type parameters of the function result can be specified by either type_spec or by declaring the result variable in the declaration part of the function subprogram, but not by both. If not specified at all, the implicit typing rules are in effect. A length specifier cannot be specified by both type_spec and len.

If RESULT is specified, result_name becomes the function result variable. name must not be declared in any specification statement in the subprogram, although it can be referenced. result_name must not be the same as name. If RESULT is not specified, name becomes the function result variable.

If the result variable is an array or pointer, the DIMENSION or POINTER attributes, respectively, must be specified within the function body.

If the function result is a pointer, the shape of the result variable determines the shape of the value returned by the function. If the result variable is a pointer, the function must either associate a target with the pointer or define the association status of the pointer as disassociated.

If the result variable is not a pointer, the function must define its value.

If the name of an external function is of derived type, the derived type must be a sequence derived type if the type is not use-associated or host-associated.

The function result variable must not appear within a variable format expression, nor can it be specified in a COMMON, DATA, integer POINTER, or EQUIVALENCE statement, nor can it have the ALLOCATABLE, PARAMETER, INTENT, OPTIONAL, or SAVE attributes. The AUTOMATIC or STATIC attributes can be specified if it is not an array or pointer, or if it is not of character or derived type.

The function result variable is associated with any entry procedure result variables. This is called entry association. The definition of any of these result variables becomes the definition of all the associated variables having that same type, and is the value of the function regardless of the entry point.

If the function subprogram contains entry procedures, the result variables are not required to be of the same type unless the type is of character or derived type, if the variables have the POINTER attribute, or if they are not scalars. The variable whose name is used to reference the function must be in a defined state when a RETURN or END statement is executed in the subprogram. An associated variable of a different type must not become defined during the execution of the function reference, unless an associated variable of the same type redefines it later during execution of the subprogram.

Recursion

The RECURSIVE keyword must be specified if, directly or indirectly:

A function that directly invokes itself requires that both the RECURSIVE and RESULT keywords be specified. The presence of both keywords makes the procedure interface explicit within the subprogram.

If name is of type character, its length cannot be an asterisk if the function is recursive.

If RECURSIVE is specified, the result variable has a default storage class of automatic.

You can also call external procedures recursively when you specify the -qrecur compiler option, although XL Fortran disregards this option if the FUNCTION statement specifies either RECURSIVE or RESULT.

Examples

RECURSIVE FUNCTION FACTORIAL (N) RESULT (RES)
  INTEGER RES
  IF (N.EQ.0) THEN
    RES=1
  ELSE
    RES=N*FACTORIAL(N-1)
  END IF
END FUNCTION FACTORIAL

Related Information

GO TO (Assigned)

Purpose

The assigned GO TO statement transfers program control to an executable statement, whose statement label is designated in an ASSIGN statement.

Format



>>-GO TO--variable_name--+--------------------------------+----><
                         +-+---+---(--stmt_label_list--)--+
                           +-,-+
 

variable_name
is a scalar variable name of type INTEGER(4) or INTEGER(8) that you have assigned a statement label to in an ASSIGN statement.

stmt_label
is the statement label of an executable statement in the same scoping unit as the assigned GO TO. The same statement label can appear more than once in stmt_label_list.

Rules

When the assigned GO TO statement is executed, the variable you specify by variable_name with the value of a statement label must be defined. You must establish this definition with an ASSIGN statement in the same scoping unit as the assigned GO TO statement. If the integer variable is a dummy argument in a subprogram, you must assign it a statement label in the subprogram in order to use it in an assigned GO TO in that subprogram. Execution of the assigned GO TO statement transfers control to the statement identified by that statement label.

If stmt_label_list is present, the statement label assigned to the variable specified by variable_name must be one of the statement labels in the list.

The assigned GO TO cannot be the terminal statement of a DO or DO WHILE construct.

Examples

      INTEGER RETURN_LABEL
         ·
!  Simulate a call to a local procedure
      ASSIGN 100 TO RETURN_LABEL
      GOTO 9000
100   CONTINUE
         ·
9000  CONTINUE
!  A "local" procedure
         ·
      GOTO RETURN_LABEL

Related Information

GO TO (Computed)

Purpose

The computed GO TO statement transfers program control to one of possibly several executable statements.

Format



>>-GO TO--(--stmt_label_list--)-+---+---arith_expr-------------><
                                +-,-+
 

stmt_label
is the statement label of an executable statement in the same scoping unit as the computed GO TO. The same statement label can appear more than once in stmt_label_list.

arith_expr
is a scalar integer, real, or complex expression. If the value of the expression is noninteger, XL Fortran converts it to INTEGER(4) before using it.

Rules

When a computed GO TO statement is executed, the arith_expr is evaluated. The resulting value is used as an index into stmt_label_list. Control then transfers to the statement whose statement label you identify by the index. For example, if the value of arith_expr is 4, control transfers to the statement whose statement label is fourth in the stmt_label_list, provided there are at least four labels in the list.

If the value of arith_expr is less than 1 or greater than the number of statement labels in the list, the GO TO statement has no effect (like a CONTINUE statement), and the next statement is executed.

Examples

 
      INTEGER NEXT
         ·
      GO TO (100,200) NEXT
10    PRINT *,'Control transfers here if NEXT does not equal 1 or 2'
         ·
100   PRINT *,'Control transfers here if NEXT = 1'
         ·
200   PRINT *,'Control transfers here if NEXT = 2'

Related Information

GO TO (Unconditional)

Purpose

The unconditional GO TO statement transfers program control to a specified executable statement.

Format



>>-GO TO--stmt_label-------------------------------------------><
 

stmt_label
is the statement label of an executable statement in the same scoping unit as the unconditional GO TO

Rules

The unconditional GO TO statement transfers control to the statement identified by stmt_label.

The unconditional GO TO statement cannot be the terminal statement of a DO or DO WHILE construct.

Examples

   REAL(8) :: X,Y
   GO TO 10
      ·
10 PRINT *, X,Y
   END

Related Information

IF (Arithmetic)

Purpose

The arithmetic IF statement transfers program control to one of three executable statements, depending on the evaluation of an arithmetic expression.

Format



>>-IF--(--arith_expr--)--stmt_label1--,--stmt_label2--,--------->
 
>-stmt_label3--------------------------------------------------><
 

arith_expr
is a scalar arithmetic expression of type integer or real

stmt_label1, stmt_label2,  and  stmt_label3
are statement labels of executable statements within the same scoping unit as the IF statement. The same statement label can appear more than once among the three statement labels.

Rules

The arithmetic IF statement evaluates arith_expr and transfers control to the statement identified by stmt_label1, stmt_label2, or stmt_label3, depending on whether the value of arith_expr is less than zero, zero, or greater than zero, respectively.

Examples

      IF (K-100) 10,20,30
10    PRINT *,'K is less than 100.'
      GO TO 40
20    PRINT *,'K equals 100.'
      GO TO 40
30    PRINT *,'K is greater than 100.'
40    CONTINUE

Related Information

IF (Block)

Purpose

The block IF statement is the first statement in an IF construct.

Format



>>-+-----------------------+------------------------------------>
   +-IF_construct_name--:--+
 
>--IF--(--scalar_logical_expr--)--THEN-------------------------><
 

IF_construct_name
is a name given to the IF construct for identification

Rules

The block IF statement evaluates a logical expression and executes at most one of the blocks contained within the IF construct.

If the IF_construct_name is specified, it must appear on the END IF statement, and optionally on any ELSE IF or ELSE statements in the IF construct.

Examples

WHICHC: IF (CMD .EQ. 'RETRY') THEN
     IF (LIMIT .GT. FIVE) THEN          ! Nested IF constructs
         ·
         CALL STOP
     ELSE
         CALL RETRY
     END IF
ELSE IF (CMD .EQ. 'STOP') THEN WHICHC
     CALL STOP
ELSE IF (CMD .EQ. 'ABORT') THEN
     CALL ABORT
ELSE WHICHC
     GO TO 100
END IF WHICHC

Related Information

IF (Logical)

Purpose

The logical IF statement evaluates a logical expression and, if true, executes a specified statement.

Format



>>-IF--(--logical_expr--)--stmt--------------------------------><
 

logical_expr
is a scalar logical expression

stmt
is an unlabeled executable statement

Rules

When a logical IF statement is executed, the logical_expr is evaluated. If the value of logical_expr is true, stmt is executed. If the value of logical_expr is false, stmt does not execute and the IF statement has no effect (like a CONTINUE statement).

Execution of a function reference in logical_expr can change the values of variables that appear in stmt.

stmt cannot be a SELECT CASE, CASE, END SELECT, DO, DO WHILE, END DO, block IF, ELSE IF, ELSE, END IF, another logical IF, WHERE (for construct), ELSEWHERE, END WHERE, END, END FUNCTION, or END SUBROUTINE statement.

Examples

      IF (ERR.NE.0) CALL ERROR(ERR)

Related Information

Chapter 6. "Control"

IMPLICIT

Purpose

The IMPLICIT statement changes or confirms the default implicit typing or the default storage class for local entities or, with the form IMPLICIT NONE specified, voids the implicit type rules altogether.

Format



>>-IMPLICIT--+-NONE--------------------------------+-----------><
             | +-,-------------------------------+ |
             | V                                 | |
             +---+-type_spec-+-(--range_list--)--+-+
                 +-STATIC----+
                 +-AUTOMATIC-+
                 +-UNDEFINED-+
 

type_spec
specifies a data type. See Type Declaration.

range
is either a single letter or range of letters. A range of letters has the form letter1-letter2, where letter1 is the first letter in the range and letter2, which follows letter1 alphabetically, is the last letter in the range. Dollar sign ($) and underscore (_) are also permitted in a range. The underscore (_) follows the dollar sign ($), which follows the Z. Thus, the range Y - _ is the same as Y, Z, $, _.

Rules

Letter ranges cannot overlap; that is, no more than one type can be specified for a given letter.

In a given scoping unit, if a character has not been specified in an IMPLICIT statement, the implicit type for entities in a program unit or interface body is default integer for entities that begin with the characters I-N, and default real otherwise. The default for an internal or module procedure is the same as the implicit type used by the host scoping unit.

For any data entity name that begins with the character specified by range_list, and for which you do not explicitly specify a type, the type specified by the immediately preceding type_spec is provided. Note that implicit typing can be to a derived type that is inaccessible in the local scope if the derived type is accessible to the host scope.

A character or a range of characters that you specify as STATIC or AUTOMATIC can also appear in an IMPLICIT statement for any data type. A letter in a range_list cannot have both type_spec and UNDEFINED specified for it in the scoping unit. Neither can both STATIC and AUTOMATIC be specified for the same letter.

If you specify the form IMPLICIT NONE in a scoping unit, you must use type declaration statements to specify data types for names local to that scoping unit. You cannot refer to a name that does not have an explicitly defined data type; this lets you control all names that are inadvertently referenced. When IMPLICIT NONE is specified, you cannot specify any other IMPLICIT statement in the same scoping unit, except ones that contain STATIC or AUTOMATIC. You can compile your program with the -qundef compiler option to achieve the same effect as an IMPLICIT NONE statement appearing in each scoping unit where an IMPLICIT statement is allowed.

IMPLICIT UNDEFINED turns off the implicit data typing defaults for the character or range of characters specified. When you specify IMPLICIT UNDEFINED, you must declare the data types of all symbolic names in the scoping unit that start with a specified character. The compiler issues a diagnostic message for each symbolic name local to the scoping unit that does not have an explicitly defined data type.

An IMPLICIT statement does not change the data type of an intrinsic function.

Using the -qsave/ -qnosave compiler option modifies the predefined conventions for storage class:


-qsave compiler option
makes the predefined convention IMPLICIT STATIC( a - _ )
-qnosave compiler option
makes the predefined convention IMPLICIT AUTOMATIC( a - _ )

Even if you specified the -qmixed compiler option, the range list items are not case sensitive. For example, with -qmixed specified, IMPLICIT INTEGER(A) affects the implicit typing of data objects that begin with A as well as those that begin with a.

Examples

      IMPLICIT INTEGER (B), COMPLEX (D, K-M), REAL (R-Z,A)
!  This IMPLICIT statement establishes the following
!  implicit typing:
!
!        A: real
!        B: integer
!        C: real
!        D: complex
!   E to H: real
!     I, J: integer
!  K, L, M: complex
!        N: integer
!   O to Z: real
!        $: real
!        _: real

Related Information

INQUIRE

Purpose

The INQUIRE statement obtains information about the properties of a named file or the connection to a particular unit.

There are three forms of the INQUIRE statement:

Format



>>-INQUIRE--+-(--inquiry_list--)------------------------+------><
            +-(--IOLENGTH--=--iol--)--output_item_list--+
 

iol
indicates the number of bytes of data that would result from the use of the output list in an unformatted output statement. iol is a scalar integer variable.

output_item
See the PRINT or WRITE statement

inquiry_list
is a list of inquiry specifiers for the inquire-by-file and inquire-by-unit forms of the INQUIRE statement. The inquire-by-file form cannot contain a unit specifier, and the inquire-by-unit form cannot contain a file specifier. No specifier can appear more than once in any INQUIRE statement. The inquiry specifiers are:

[UNIT=] u
is a unit specifier. It specifies the unit about which the inquire-by-unit form of the statement is inquiring. u must be an external unit identifier whose value is not an asterisk. An external unit identifier refers to an external file that is represented by a scalar integer expression, whose value is in the range 0 through 2147483647. If the optional characters UNIT= are omitted, u must be the first item in inquiry_list.

IOSTAT= ios
is an input/output status specifier that specifies the status of the input/output operation. ios is a scalar variable of type INTEGER(4) or default integer. When the input/output statement containing this specifier is finished executing, ios is defined with:

Coding the IOSTAT= specifier suppresses error messages.

ERR= stmt_label
is an error specifier that specifies the statement label of an executable statement in the same scoping unit to which control is to transfer in the case of an error. Coding the ERR= specifier suppresses error messages.

FILE= char_expr
is a file specifier. It specifies the name of the file about which the inquire-by-file form of the statement is inquiring. char_expr is a scalar character expression whose value, when any trailing blanks are removed, is a valid AIX operating system file name. The named file does not have to exist, nor does it have to be associated with a unit.
Note:A valid AIX operating system file name must have a full path name of total length <= 1023 characters, with each file name <= 255 characters long (though the full path name need not be specified).

ACCESS= char_var
indicates whether the file is connected for sequential access or direct access. char_var is a scalar character variable that is assigned the value SEQUENTIAL if the file is connected for sequential access. The value assigned is DIRECT if the file is connected for direct access. If there is no connection, char_var is assigned the value UNDEFINED.

FORM= char_var
indicates whether the file is connected for formatted or unformatted input/output. char_var is a scalar default character variable that is assigned the value FORMATTED if the file is connected for formatted input/output. The value assigned is UNFORMATTED if the file is connected for unformatted input/output. If there is no connection, char_var is assigned the value UNDEFINED.

ASYNCH= char_variable
indicates whether the unit is connected for asynchronous access.

char_variable is a character variable that returns the value:

TRANSFER= char_variable
is an asynchronous I/O specifier that indicates whether synchronous and/or asynchronous data transfer are permissible transfer methods for the file.

char_variable is a scalar character variable. If char_variable is assigned the value BOTH, then both synchronous and asynchronous data transfer are permitted. If char_variable is assigned the value SYNCH then only synchronous data transfer is permitted. If char_variable is assigned the value UNKNOWN then the processor is unable to determine the permissible transfer methods for this file.

RECL= rcl
indicates the value of the record length of a file connected for direct access, or the value of the maximum record length of a file connected for sequential access. rcl is a scalar variable of type INTEGER(4), type INTEGER(8) in 64-bit, or type default integer that is assigned the value of the record length. If the file is connected for formatted input/output, the length is the number of characters for all records that contain character data. If the file is connected for unformatted input/output, the length is the number of bytes of data. If there is no connection, rcl becomes undefined.

BLANK= char_var
indicates the default treatment of blanks for a file connected for formatted input/output. char_var is a scalar character variable that is assigned the value NULL if all blanks in numeric input fields are ignored, or the value ZERO if all nonleading blanks are interpreted as zeros. If there is no connection, or if the connection is not for formatted input/output, char_var is assigned the value UNDEFINED.

EXIST= ex
indicates if a file or unit exists. ex is a scalar variable of type LOGICAL(4) or default logical that is assigned the value true or false. For the inquire-by-file form of the statement, the value true is assigned if the file specified by the FILE= specifier exists. The value false is assigned if the file does not exist. For the inquire-by-unit form of the statement, the value true is assigned if the unit specified by UNIT= exists. The value false is assigned if it is an invalid unit.

OPENED= od
indicates if a file or unit is connected. od is a scalar variable of type LOGICAL(4) or default logical that is assigned the value true or false. For the inquire-by-file form of the statement, the value true is assigned if the file specified by FILE=char_var is connected to a unit. The value false is assigned if the file is not connected to a unit. For the inquire-by-unit form of the statement, the value true is assigned if the unit specified by UNIT= is connected to a file. The value false is assigned if the unit is not connected to a file. For preconnected files that have not been closed, the value is true both before and after the first input/output operation.

NUMBER= num
indicates the external unit identifier currently associated with the file. num is a scalar variable of type INTEGER(4) or default integer that is assigned the value of the external unit identifier of the unit that is currently connected to the file. If there is no unit connected to the file, num is assigned the value -1.

NAMED= nmd
indicates if the file has a name. nmd is a scalar variable of type LOGICAL(4) or default logical that is assigned the value true if the file has a name. The value assigned is false if the file does not have a name.

NAME= fn
indicates the name of the file. fn is a scalar character variable that is assigned the name of the file to which the unit is connected.

SEQUENTIAL= seq
indicates if the file is connected for sequential access. seq is a scalar character variable that is assigned the value YES if the file can be accessed sequentially. The value assigned is NO if the file cannot be accessed sequentially. The value assigned is UNKNOWN if access cannot be determined.

DIRECT= dir
indicates if the file is connected for direct access. dir is a scalar character variable that is assigned the value YES if the file can be accessed directly. The value assigned is NO if the file cannot be accessed directly. The value assigned is UNKNOWN if it cannot be determined.

FORMATTED= fmt
indicates if the file can be connected for formatted input/output. fmt is a scalar character variable that is assigned the value YES if the file can be connected for formatted input/output. The value assigned is NO if the file cannot be connected for formatted input/output. The value assigned is UNKNOWN if formatting cannot be determined.

UNFORMATTED= unf
indicates if the file can be connected for unformatted input/output. fmt is a scalar character variable that is assigned the value YES if the file can be connected for unformatted input/output, the value NO if the file cannot be connected for unformatted input/output, or the value UNKNOWN if formatting cannot be determined.

NEXTREC= nr
indicates where the next record can be read or written on a file connected for direct access. nr is a scalar variable of type INTEGER(4), INTEGER(8), or default integer that is assigned the value n + 1, where n is the record number of the last record read or written on the file connected for direct access. If the file is connected but no records were read or written since the connection, nr is assigned the value 1. If the file is not connected for direct access or if the position of the file cannot be determined because of a previous error, nr becomes undefined.

Because record numbers can be greater than 2**31-1, you may choose to make the scalar variable specified with the NEXTREC= specifier of type INTEGER(8). This could be accomplished in many ways, two examples include:

POSITION= pos
indicates the position of the file. pos is a scalar character variable that is assigned the value REWIND if the file is connected by an OPEN statement for positioning at its initial point, APPEND if the file is connected for positioning before its endfile record or at its terminal point, ASIS if the file is connected without changing its position, or UNDEFINED if there is no connection or if the file is connected for direct access.

If the file has been repositioned to its initial point since it was opened, pos is assigned the value REWIND. If the file has been repositioned just before its endfile record since it was opened (or, if there is no endfile record, at its terminal point), pos is assigned the value APPEND. If both of the above are true and the file is empty, pos is assigned the value APPEND. If the file is positioned after the endfile record, pos is assigned the value ASIS.

ACTION= act
indicates if the file is connected for read and/or write access. act is a scalar character variable that is assigned the value READ if the file is connected for input only, WRITE if the file is connected for output only, READWRITE if the file is connected for both input and output, and UNDEFINED if there is no connection.

READ= rd
indicates if the file can be read. rd is a scalar character variable that is assigned the value YES if the file can be read, NO if the file cannot be read, and UNKNOWN if it cannot be determined if the file can be read.

WRITE= wrt
indicates if the file can be written to. wrt is a scalar character variable that is assigned the value YES if the file can be written to, NO if the file cannot be written to, and UNKNOWN if it cannot be determined if the file can be written to.

READWRITE= rw
indicates if the file can be both read from and written to. rw is a scalar character variable that is assigned the value YES if the file can be both read from and written to, NO if the file cannot be both read from and written to, and UNKNOWN if it cannot be determined if the file can be both read from and written to.

DELIM= del
indicates the form, if any, that is used to delimit character data that is written by list-directed or namelist formatting. del is a scalar character variable that is assigned the value APOSTROPHE if apostrophes are used to delimit data, QUOTE if quotation marks are used to delimit data, NONE if neither apostrophes nor quotation marks are used to delimit data, and UNDEFINED if there is no file connection or no connection to formatted data.

PAD= pd
indicates if the connection of the file had specified PAD=NO. pd is a scalar character variable that is assigned the value NO if the connection of the file had specified PAD=NO, and YES for all other cases.

Rules

An INQUIRE statement can be executed before, while, or after a file is associated with a unit. Any values assigned as the result of an INQUIRE statement are values that are current at the time the statement is executed.

If the unit or file is connected, the values returned for the ACCESS=, SEQUENTIAL=, DIRECT=, ACTION=, READ=, WRITE=, READWRITE=, FORM=, FORMATTED=, UNFORMATTED=, BLANK=, DELIM=, PAD=, RECL=, POSITION=, NEXTREC=, NUMBER=, NAME= and NAMED= specifiers are properties of the connection, and not of that file. Note that the EXIST= and OPENED= specifiers return true in these situations.

If a unit or file is not connected or does not exist, the ACCESS=, ACTION=, FORM=, BLANK=, DELIM=, POSITION= specifiers return the value UNDEFINED, the DIRECT=, SEQUENTIAL=, FORMATTED=, UNFORMATTED=, READ=, WRITE= and READWRITE= specifiers return the value UNKNOWN, the RECL= and NEXTREC= specifier variables are not defined, the PAD= specifier returns the value YES, and the OPENED specifier returns the value false.

If a unit or file does not exist, the EXIST= and NAMED= specifiers return the value false, the NUMBER= specifier returns the value -1, and the NAME= specifier variable is not defined.

If a unit or file exists but is not connected, the EXIST= specifier returns the value true. For the inquire-by-unit form of the statement, the NAMED= specifier returns the value false, the NUMBER= specifier returns the unit number, and the NAME= specifier variable is undefined. For the inquire-by-file form of the statement, the NAMED= specifier returns the value true, the NUMBER= specifier returns -1, and the NAME= specifier returns the file name.

The same variable name must not be specified for more than one specifier in the same INQUIRE statement, and must not be associated with any other variable in the list of specifiers.

Examples

SUBROUTINE SUB(N)
  CHARACTER(N) A(5)
  INQUIRE (IOLENGTH=IOL) A(1)  ! Inquire by output list
  OPEN (7,RECL=IOL)
      ·
END SUBROUTINE

Related Information

INTEGER

Purpose

An INTEGER type declaration statement specifies the length and attributes of objects and functions of type integer. Initial values can be assigned to objects.

Format



>>-INTEGER-+---------------+---+-+----+-----------------+------->
           +-kind_selector-+   | +-::-+                 |
                               +-,--attr_spec_list--::--+
 
>--entity_decl_list--------------------------------------------><
 

where:
attr_spec

ALLOCATABLE
AUTOMATIC
DIMENSION (array_spec)
EXTERNAL
INTENT (intent_spec)
INTRINSIC
OPTIONAL
PARAMETER
POINTER
PRIVATE
PUBLIC
SAVE
STATIC
TARGET
VOLATILE

kind_selector



>>-+-(--+------------+--int_initialization_expr--)--+----------><
   |    +-KIND-- = --+                              |
   +- * --int_literal_constant----------------------+
 

 
specifies the length of integer entities: 1, 2, 4 or 8. int_literal_constant cannot specify a kind type parameter.

attr_spec
For detailed information on rules about a particular attribute, refer to the statement of the same name.

intent_spec
is either IN, OUT, or INOUT

::
is the double colon separator. It is required if attributes are specified or if = initialization_expr is used.

array_spec
is a list of dimension bounds

entity_decl



>>-a--+-+-----------+--+-------------------+-+------------------>
      | +- * --len--+  +-(--array_spec--)--+ |
      +-(--array_spec--)-- * --len-----------+
 
>--+--------------------------------+--------------------------><
   +--+-/--initial_value_list--/--+-+
      +- = --initialization_expr--+
 

 

a
is an object name or function name. array_spec cannot be specified for a function name.

len
overrides the length as specified in kind_selector, and cannot specify a kind type parameter. The entity length must be an integer literal constant that represents one of the permissible length specifications.

initial_value
provides an initial value for the entity specified by the immediately preceding name

initialization_expr
provides an initial value, by means of an initialization expression, for the entity specified by the immediately preceding name

Rules

Entities in type declaration statements are constrained by the rules of any attributes specified for the entities, as detailed in the corresponding attribute statements.

The type declaration statement overrides the implicit type rules in effect. You can use a type declaration statement that confirms the type of an intrinsic function. The appearance of a generic or specific intrinsic function name in a type declaration statement does not cause the name to lose its intrinsic property.

An object cannot be initialized in a type declaration statement if it is a dummy argument, an allocatable array, a pointer, a function result, an object in blank common, an integer pointer, an external name, an intrinsic name, or an automatic object. Nor can an object be initialized if it has the AUTOMATIC attribute. The object may be initialized if it appears in a named common block in a block data program unit or if it appears in a named common block in a module.

The specification expression of an array_spec can be a nonconstant expression if the specification expression appears in an interface body or in the specification part of a subprogram. Any object being declared that uses this nonconstant expression and is not a dummy argument or a pointee is called an automatic object.

An attribute cannot be repeated in a given type declaration statement, nor can an entity be explicitly given the same attribute more than once in a scoping unit.

initialization_expr must be specified if the statement contains the PARAMETER attribute. If initialization_expr is specified and PARAMETER is not, the object is a variable that is initially defined. a becomes defined with the value determined by initialization_expr, in accordance with the rules for intrinsic assignment. If the variable is an array, its shape must be specified either in the type declaration statement or in a previous specification statement in the same scoping unit. A variable or variable subobject cannot be initialized more than once. The presence of initialization_expr implies that a is a saved object, except for an object with the PARAMETER attribute or in a named common block. The initialization of an object could affect the fundamental storage class of an object.

An array_spec specified in the entity_decl takes precedence over the array_spec in the DIMENSION attribute.

An array function result that does not have the POINTER attribute must have an explicit-shape array specification.

If the entity declared is a function, it must not have an accessible explicit interface unless it is an intrinsic function.

If T or F, defined previously as the name of a constant, appears in a type declaration statement, it is no longer an abbreviated logical constant but the name of the named constant.

Examples

MODULE INT
  INTEGER, DIMENSION(3) :: A,B,C
  INTEGER :: X=234,Y=678
END MODULE INT

Related Information

INTENT

Purpose

The INTENT attribute specifies the intended use of dummy arguments.

Format



>>-INTENT--(--+-IN----+-)-+----+---dummy_arg_name_list---------><
              +-OUT---+   +-::-+
              +-INOUT-+
 

dummy_arg_name
is the name of a dummy argument, which cannot be a dummy procedure or a dummy pointer

Rules

The INTENT attribute can take three forms:

An actual argument that becomes associated with a dummy argument with an intent of OUT or INOUT must be definable. Hence, a dummy argument with an intent of IN, or an actual argument that is a constant, a subobject of a constant, or an expression, cannot be passed as an actual argument to a subprogram expecting an argument with an intent of OUT or INOUT.

An actual argument that is an array section with a vector subscript cannot be associated with a dummy array that is defined or redefined (i.e., with an intent of OUT or INOUT).

A dummy argument with an intent of IN cannot be used as an actual argument for the LOC intrinsic function.

The %VAL built-in function, used for interlanguage calls, can only be used for an actual argument that corresponds to a dummy argument with an intent of IN, or no intent specified. This constraint does not apply to the %REF built-in function.
Attributes Compatible with the INTENT Attribute

  • DIMENSION
  • OPTIONAL

  • TARGET
  • VOLATILE

Examples

      PROGRAM MAIN
        DATA R,S /12.34,56.78/
        CALL SUB(R+S,R,S)
      END PROGRAM
 
      SUBROUTINE SUB (A,B,C)
        INTENT(IN) A
        INTENT(OUT) B
        INTENT(INOUT) C
        C=C+A+ABS(A)            ! Valid references to A and C
                                ! Valid redefinition of C
        B=C**2                  ! Valid redefinition of B
      END SUBROUTINE

Related Information

INTERFACE

Purpose

The INTERFACE statement is the first statement of an interface block, which can specify an explicit interface for an external or dummy procedure.

Format



>>-INTERFACE-+--------------+----------------------------------><
             +-generic_spec-+
 

generic_spec



>>-+-generic_name----------------------+-----------------------><
   +-OPERATOR--(--defined_operator--)--+
   +-ASSIGNMENT--(-- = --)-------------+
 

defined_operator
is a defined unary operator, defined binary operator, or extended intrinsic operator

Rules

If generic_spec is present, the interface block is generic. If generic_spec is absent, the interface block is nongeneric. generic_name specifies a single name to reference all procedures in the interface block. At most, one specific procedure is invoked each time there is a procedure reference with a generic name.

A specific procedure must not have more than one explicit interface in a given scoping unit.

You can always reference a procedure through its specific interface, if accessible. If a generic interface exists for a procedure, the procedure can also be referenced through the generic interface.

If generic_spec is OPERATOR(defined_operator), the interface block can define a defined operator or extend an intrinsic operator.

If generic_spec is ASSIGNMENT(=), the interface block can extend intrinsic assignment.

Examples

INTERFACE                            ! Nongeneric interface block
  FUNCTION VOL(RDS,HGT)
    REAL VOL, RDS, HGT
  END FUNCTION VOL
  FUNCTION AREA (RDS)
    REAL AREA, RDS
  END FUNCTION AREA
END INTERFACE
 
INTERFACE OPERATOR (.DETERMINANT.)   ! Defined operator interface
  FUNCTION DETERMINANT(X)
    INTENT(IN) X
    REAL X(50,50), DETERMINANT
  END FUNCTION
END INTERFACE
 
INTERFACE ASSIGNMENT(=)              ! Defined assignment interface
  SUBROUTINE BIT_TO_NUMERIC (N,B)
    INTEGER, INTENT(OUT) :: N
    LOGICAL, INTENT(IN)  :: B(:)
  END SUBROUTINE
END INTERFACE

Related Information

INTRINSIC

Purpose

The INTRINSIC attribute identifies a name as an intrinsic procedure and allows you to use specific names of intrinsic procedures as actual arguments.

Format



>>-INTRINSIC--name_list----------------------------------------><
 

name
is the name of an intrinsic procedure

Rules

If you use a specific intrinsic procedure name as an actual argument in a scoping unit, it must have the INTRINSIC attribute. Generic names can have the INTRINSIC attribute, but you cannot pass them as arguments unless they are also specific names.

A generic or specific procedure that has the INTRINSIC attribute keeps its generic or specific properties.

A generic intrinsic procedure that has the INTRINSIC attribute can also be the name of a generic interface block. The generic interface block defines extensions to the generic intrinsic procedure.
Attributes Compatible with the INTRINSIC Attribute

  • PRIVATE

  • PUBLIC

Examples

PROGRAM MAIN
  INTRINSIC SIN, ABS
  INTERFACE ABS
    LOGICAL FUNCTION MYABS(ARG)
      LOGICAL ARG
    END FUNCTION
  END INTERFACE
  LOGICAL LANS,LVAR
  REAL(8) DANS,DVAR
  DANS = ABS(DVAR)            ! Calls the DABS intrinsic procedure
  LANS = ABS(LVAR)            ! Calls the MYABS external procedure
 
! Pass intrinsic procedure name to subroutine
  CALL DOIT(0.5,SIN,X)        ! Passes the SIN specific intrinsic
END PROGRAM
 
SUBROUTINE DOIT(RIN,OPER,RESULT)
  RESULT = OPER(RIN)
END SUBROUTINE

Related Information

LOGICAL

Purpose

A LOGICAL type declaration statement specifies the length and attributes of objects and functions of type logical. Initial values can be assigned to objects.

Format



>>-LOGICAL-+---------------+---+-+----+-----------------+------->
           +-kind_selector-+   | +-::-+                 |
                               +-,--attr_spec_list--::--+
 
>-entity_decl_list---------------------------------------------><
 

where:
attr_spec

ALLOCATABLE
AUTOMATIC
DIMENSION (array_spec)
EXTERNAL
INTENT (intent_spec)
INTRINSIC
OPTIONAL
PARAMETER
POINTER
PRIVATE
PUBLIC
SAVE
STATIC
TARGET
VOLATILE

kind_selector



>>-+-(--+------------+--int_initialization_expr--)--+----------><
   |    +-KIND-- = --+                              |
   +- * --int_literal_constant----------------------+
 

 
specifies the length of logical entities: 1, 2, 4 or 8. int_literal_constant cannot specify a kind type parameter.

attr_spec
For detailed information on rules about a particular attribute, refer to the statement of the same name.

intent_spec
is either IN, OUT, or INOUT

::
is the double colon separator. It is required if attributes are specified or if = initialization_expr is used.

array_spec
is a list of dimension bounds

entity_decl



>>-a--+-+-----------+--+-------------------+-+------------------>
      | +- * --len--+  +-(--array_spec--)--+ |
      +-(--array_spec--)-- * --len-----------+
 
>--+--------------------------------+--------------------------><
   +--+-/--initial_value_list--/--+-+
      +- = --initialization_expr--+
 

 

a
is an object name or function name. array_spec cannot be specified for a function name.

len
overrides the length as specified in kind_selector, and cannot specify a kind type parameter. The entity length must be an integer literal constant that represents one of the permissible length specifications.

initial_value
provides an initial value for the entity specified by the immediately preceding name

initialization_expr
provides an initial value, by means of an initialization expression, for the entity specified by the immediately preceding name

Rules

Entities in type declaration statements are constrained by the rules of any attributes specified for the entities, as detailed in the corresponding attribute statements.

The type declaration statement overrides the implicit type rules in effect. You can use a type declaration statement that confirms the type of an intrinsic function. The appearance of a generic or specific intrinsic function name in a type declaration statement does not cause the name to lose its intrinsic property.

An object cannot be initialized in a type declaration statement if it is a dummy argument, an allocatable array, a pointer, a function result, an object in blank common, an integer pointer, an external name, an intrinsic name, or an automatic object. Nor can an object be initialized if it has the AUTOMATIC attribute. The object may be initialized if it appears in a named common block in a block data program unit or if it appears in a named common block in a module.

The specification expression of an array_spec can be a nonconstant expression if the specification expression appears in an interface body or in the specification part of a subprogram. Any object being declared that uses this nonconstant expression and is not a dummy argument or a pointee is called an automatic object.

An attribute cannot be repeated in a given type declaration statement, nor can an entity be explicitly given the same attribute more than once in a scoping unit.

initialization_expr must be specified if the statement contains the PARAMETER attribute. If initialization_expr is specified and PARAMETER is not, the object is a variable that is initially defined. a becomes defined with the value determined by initialization_expr, in accordance with the rules for intrinsic assignment. If the variable is an array, its shape must be specified either in the type declaration statement or in a previous specification statement in the same scoping unit. A variable or variable subobject cannot be initialized more than once. The presence of initialization_expr implies that a is a saved object, except for an object with the PARAMETER attribute or in a named common block. The initialization of an object could affect the fundamental storage class of an object.

An array_spec specified in the entity_decl takes precedence over the array_spec in the DIMENSION attribute.

An array function result that does not have the POINTER attribute must have an explicit-shape array specification.

If the entity declared is a function, it must not have an accessible explicit interface unless it is an intrinsic function.

If T or F, defined previously as the name of a constant, appears in a type declaration statement, it is no longer an abbreviated logical constant but the name of the named constant.

Examples

LOGICAL, ALLOCATABLE :: L(:,:)
LOGICAL :: Z=.TRUE.

Related Information

MODULE

Purpose

The MODULE statement is the first statement of a module program unit, which contains specifications and definitions that can be made accessible to other program units.

Format



>>-MODULE--module_name-----------------------------------------><
 

Rules

The module name is a global entity that is referenced by the USE statement in other program units to access the public entities of the module. The module name must not have the same name as any other program unit, external procedure or common block in the program, nor can it be the same as any local name in the module.

If the END statement that completes the module specifies a module name, the name must be the same as that specified in the MODULE statement.

Examples

MODULE MM
   CONTAINS
     REAL FUNCTION SUM(CARG)
       COMPLEX CARG
       SUM_FNC(CARG) = IMAG(CARG) + REAL(CARG)
       SUM = SUM_FNC(CARG)
       RETURN
     ENTRY AVERAGE(CARG)
       AVERAGE = SUM_FNC(CARG) / 2.0
     END FUNCTION SUM
     SUBROUTINE SHOW_SUM(SARG)
       COMPLEX SARG
       REAL SUM_TMP
  10   FORMAT('SUM:',E10.3,' REAL:',E10.3,' IMAG',E10.3)
       SUM_TMP = SUM(CARG=SARG)
       WRITE(10,10) SUM_TMP, SARG
     END SUBROUTINE SHOW_SUM
END MODULE MM

Related Information

MODULE PROCEDURE

Purpose

The MODULE PROCEDURE statement lists those module procedures that have a generic interface.

Format



>>-MODULE PROCEDURE--procedure_name_list-----------------------><
 

Rules

The MODULE PROCEDURE statement must appear in an interface block that has a generic specification. MODULE PROCEDURE statements must be listed after any interface bodies in the interface block, which is contained in a scoping unit where procedure_name can be accessed as a module procedure.

procedure_name must be the name of a module procedure that is accessible in this scope. procedure_name must not have been previously associated with the generic specification of the interface block in which it appears, either by a previous appearance in an interface block or by use or host association.

The characteristics of module procedures are determined by module procedure definitions, not their interface bodies.

Examples

MODULE M
  CONTAINS
  SUBROUTINE S1(IARG)
    IARG=1
  END SUBROUTINE
  SUBROUTINE S2(RARG)
    RARG=1.1
  END SUBROUTINE
END MODULE
 
USE M
INTERFACE SS
  SUBROUTINE SS1(IARG,JARG)
  END SUBROUTINE
  MODULE PROCEDURE S1, S2
END INTERFACE
CALL SS(N)                   ! Calls subroutine S1 from M
CALL SS(I,J)                 ! Calls subroutine SS1
END

Related Information

NAMELIST

Purpose

The NAMELIST statement specifies one or more lists of names for use in READ, WRITE, and PRINT statements.

Format



             +-+---+----------------------------+
             | +-,-+                            |
             V                                  |
>>-NAMELIST----/--Nname--/--variable_name_list--+--------------><
 

Nname
is a namelist group name

variable_name
must not be an array dummy argument with a nonconstant bound, a variable with nonconstant character length, an automatic object, a pointer, a variable of a type that has an ultimate component that is a pointer, an allocatable array, or a pointee.

Rules

The list of names belonging to a namelist group name ends with the appearance of another namelist group name or the end of the NAMELIST statement.

variable_name must either be accessed via use or host association, or have its type and type parameters specified by previous specification statements in the same scoping unit or by the implicit typing rules. If typed implicitly, any appearance of the object in a subsequent type declaration statement must confirm the implied type and type parameters. A derived-type object must not appear as a list item if any component ultimately contained within the object is not accessible within the scoping unit containing the namelist input/output statement on which its containing namelist group name is specified.

variable_name can belong to one or more namelist lists. If the namelist group name has the PUBLIC attribute, no item in the list can have the PRIVATE attribute or private components.

Nname can be specified in more than one NAMELIST statement in the scoping unit. The variable_name_list following each successive appearance of the same Nname in a scoping unit is treated as the continuation of the list for that Nname.

A namelist name can appear only in input/output statements. The rules for input/output conversion of namelist data are the same as the rules for data conversion.

Examples

DIMENSION X(5), Y(10)
NAMELIST /NAME1/ I,J,K
NAMELIST /NAME2/ A,B,C /NAME3/ X,Y
WRITE (10, NAME1)
PRINT NAME2

Related Information

NULLIFY

Purpose

The NULLIFY statement causes pointers to become disassociated.

Format



>>-NULLIFY--(--pointer_object_list--)--------------------------><
 

pointer_object
is a pointer variable name or structure component

Rules

A pointer_object must have the POINTER attribute.
Tip

Always initialize a pointer with the NULLIFY statement or with pointer assignment.

Examples

TYPE T
  INTEGER CELL
  TYPE(T), POINTER :: NEXT
ENDTYPE T
TYPE(T) HEAD, TAIL
TARGET :: TAIL
HEAD%NEXT => TAIL
NULLIFY (TAIL%NEXT)
END

Related Information

OPEN

Purpose

The OPEN statement can be used to connect an existing external file to a unit, create an external file that is preconnected, create an external file and connect it to a unit, or change certain specifiers of a connection between an external file and a unit.

Format



>>-OPEN--(--open_list--)---------------------------------------><
 

open_list
is a list that must contain one unit specifier ( UNIT=u) and can also contain one of each of the other valid specifiers. The valid specifiers are:

[UNIT=] u
is a unit specifier in which u must be an external unit identifier whose value is not an asterisk. An external unit identifier refers to an external file that is represented by a scalar integer expression, whose value is in the range 0 through 2,147,483,647. If the optional characters UNIT= are omitted, u must be the first item in open_list.

ASYNCH= char_expr
is an asynchronous I/O specifier that indicates whether an explicitly connected unit is to be used for asynchronous I/O.

char_expr is a scalar character expression whose value is either YES or NO. YES specifies that asynchronous data transfer statements are permitted for this connection. NO specifies that asynchronous data transfer statements are not permitted for this connection. The value specified will be in the set of transfer methods permitted for the file. If this specifier is omitted, the default value is NO.

Preconnected units are connected with an ASYNCH= value of NO.

The ASYNCH= value of an implicitly connected unit is determined by the first data transfer statement performed on the unit. If the first statement performs an asynchronous data transfer and the file being implicitly connected permits asynchronous data transfers, the ASYNCH= value is YES. Otherwise, the ASYNCH= value is NO.

IOSTAT= ios
is an input/output status specifier that specifies the status of the input/output operation. ios is a scalar variable of type INTEGER(4) or default integer. When the input/output statement containing this specifier finishes execution, ios is defined with:

ERR= stmt_label
is an error specifier that specifies the statement label of an executable statement in the same scoping unit to which control is to transfer in the case of an error. Coding the ERR= specifier suppresses error messages.

FILE= char_expr
is a file specifier that specifies the name of the file to be connected to the specified unit.

char_expr is a scalar character expression whose value, when any trailing blanks are removed, is a valid AIX operating system file name. If the file specifier is omitted and is required, the unit becomes implicitly connected (by default) to fort.u, where u is the unit specified with any leading zeros removed. Use the UNIT_VARS run-time option to allow alternative files names to be used for files that are implicitly connected.
Note:A valid AIX operating system file name must have a full path name of total length <=1023 characters, with each file name <=255 characters long (although the full path name need not be specified).

STATUS= char_expr
specifies the status of the file when it is opened. char_expr is a scalar character expression whose value, when any trailing blanks are removed, is one of the following:

UNKNOWN is the default.

ACCESS= char_expr
specifies the access method for the connection of the file. char_expr is a scalar character expression whose value, when any trailing blanks are removed, is either SEQUENTIAL or DIRECT. SEQUENTIAL is the default. If ACCESS is DIRECT, RECL= must be specified. If ACCESS is SEQUENTIAL, RECL= is optional.

FORM= char_expr
specifies whether the file is connected for formatted or unformatted input/output. char_expr is a scalar character expression whose value, when any trailing blanks are removed, is either FORMATTED or UNFORMATTED. If the file is being connected for sequential access, FORMATTED is the default. If the file is being connected for direct access, UNFORMATTED is the default.

RECL= integer_expr
specifies the length of each record in a file being connected for direct access or the maximum length of a record in a file being connected for sequential access. integer_expr is a scalar integer expression whose value must be positive. This specifier must be present when a file is being connected for direct access. For formatted input/output, the length is the number of characters for all records that contain character data. For unformatted input/output, the length is the number of bytes required for the internal form of the data. The length of an unformatted sequential record does not count the four-byte fields surrounding the data.

If RECL= is omitted when a file is being connected for sequential access in 32-bit, the length is 2,147,483,647 minus the record terminator. For a formatted sequential file in 32-bit, the default record length is 2,147,483,646 (which is 2,147,483,647 minus 1 byte for the record terminator surrounding the data). For an unformatted file in 32-bit, the default record length is 2,147,483,639 (which is 2,147,483,647 minus 8 bytes for the record terminators surrounding the data). For a file that cannot be accessed randomly in 32-bit, the default length is 32,768.

If RECL= is omitted when a file is being connected for sequential access in 64-bit, the length is 9,223,372,036,854,775,807 minus the record terminator. For a formatted sequential file in 64-bit, the default record length is 9,223,372,036,854,775,806 (which is 9,223,372,036,854,775,807 minus 1 byte for the record terminator surrounding the data). For an unformatted file in 64-bit, the default record length is 9,223,372,036,854,775,791 (which is 9,223,372,036,854,775,807 minus 16 bytes for the record terminators surrounding the data) when the UWIDTH run-time option is set to 64.

BLANK= char_expr
controls the default interpretation of blanks when you are using a format specification. char_expr is a scalar character expression whose value, when any trailing blanks are removed, is either NULL or ZERO. If BLANK= is specified, you must use FORM='FORMATTED'. If BLANK= is not specified and you specify FORM='FORMATTED', NULL is the default.

POSITION= char_expr
specifies the file position for a file connected for sequential access. A file that did not exist previously is positioned at its initial point. char_expr is a scalar character expression whose value, when any trailing blanks are removed, is either ASIS, REWIND, or APPEND. REWIND positions the file at its initial point. APPEND positions the file before the endfile record or, if there is no endfile record, at the terminal point. ASIS leaves the position unchanged. The default value is ASIS except under the following conditions:

In such cases, the default value for the POSITION= specifier is APPEND at the time the WRITE statement is executed.

ACTION= char_expr
specifies the allowed input/output operations. char_expr is a scalar character expression whose value evaluates to READ, WRITE or READWRITE. If READ is specified, WRITE and ENDFILE statements cannot refer to this connection. If WRITE is specified, READ statements cannot refer to this connection. The value READWRITE permits any input/output statement to refer to this connection. If the ACTION= specifier is omitted, the default value depends on the actual file permissions:

DELIM= char_expr
specifies what delimiter, if any, is used to delimit character constants written with list-directed or namelist formatting. char_expr is a scalar character expression whose value must evaluate to APOSTROPHE, QUOTE or NONE. If the value is APOSTROPHE, apostrophes delimit character constants and all apostrophes within character constants are doubled. If the value is QUOTE, double quotation marks delimit character constants and all double quotation marks within character constants are doubled. If the value is NONE, character constants are not delimited and no characters are doubled. The default value is NONE. The DELIM= specifier is permitted only for files being connected for formatted input/output, although it is ignored during input of a formatted record.

PAD= char_expr
specifies if input records are padded with blanks. char_expr is a scalar character expression that must evaluate to YES or NO. If the value is YES, a formatted input record is padded with blanks if an input list is specified and the format specification requires more data from a record than the record contains. If NO is specified, the input list and format specification must not require more characters from a record than the record contains. The default value is YES. The PAD= specifier is permitted only for files being connected for formatted input/output, although it is ignored during output of a formatted record.

If the -qxlf77 compiler option specifies the noblankpad suboption and the file is being connected for formatted direct input/output, the default value is NO when the PAD= specifier is omitted.

Rules

If a unit is connected to a file that exists, an OPEN statement for that unit can be performed. If the FILE= specifier is not included in the OPEN statement, the file to be connected to the unit is the same as the file to which the unit is connected.

If the file to be connected to the unit is not the same as the file to which the unit is connected, the effect is as if a CLOSE statement without a STATUS= specifier had been executed for the unit immediately prior to the execution of the OPEN statement.

If the file to be connected to the unit is the same as the file to which the unit is connected, only the BLANK=, DELIM=, PAD=, ERR=, and IOSTAT= specifiers can have a value different from the one currently in effect. Execution of the OPEN statement causes any new value for the BLANK=, DELIM= or PAD= specifiers to be in effect, but does not cause any change in any of the unspecified specifiers or the position of the file. Any ERR= and IOSTAT= specifiers from OPEN statements previously executed have no effect on the current OPEN statement. To specify the same file as the one currently connected to the unit, you can specify the same file name, omit the FILE= specifier, or specify a file symbolically linked to the same file.

If a file is connected to a unit, an OPEN statement on that file and a different unit cannot be performed.

If the STATUS= specifier has the value OLD, NEW or REPLACE, the FILE= specifier is optional.

Unit 0 cannot be specified to connect to a file other than the preconnected file, the standard error device, although you can change the values for the BLANK=, DELIM= and PAD= specifiers.

If the ERR= and IOSTAT= specifiers are set and an error is encountered, transfer is made to the statement specified by the ERR= specifier and a positive integer value is assigned to ios.

If IOSTAT= and ERR= are not specified,

Examples

!   Open a new file with name fname
 
CHARACTER*20 FNAME
FNAME = 'INPUT.DAT'
OPEN(UNIT=8,FILE=FNAME,STATUS='NEW',FORM='FORMATTED')
 
OPEN (4,FILE="myfile")
OPEN (4,FILE="myfile", PAD="NO")  ! Changing PAD= value to NO
 
!   Connects unit 2 to a tape device for unformatted, sequential
!   write-only access:
 
OPEN (2, FILE="/dev/rmt0",ACTION="WRITE",POSITION="REWIND", &
&   FORM="UNFORMATTED",ACCESS="SEQUENTIAL",RECL=32767)

Related Information

OPTIONAL

Purpose

The OPTIONAL attribute specifies that a dummy argument need not be associated with an actual argument in a reference to the procedure.

Format



>>-OPTIONAL-+----+---dummy_arg_name_list-----------------------><
            +-::-+
 

Rules

A reference to a procedure that has an optional dummy argument specified must have an explicit interface.

Use the PRESENT intrinsic function to determine if an actual argument has been associated with an optional dummy argument. Avoid referencing an optional dummy argument without first verifying that the dummy argument is present.

A dummy argument is considered present in a subprogram if it is associated with an actual argument, which itself can also be a dummy argument that is present (an instance of propagation). A dummy argument that is not optional must be present; that is, it must be associated with an actual argument.

An optional dummy argument that is not present may be used as an actual argument corresponding to an optional dummy argument, which is then also considered not to be associated with an actual argument. An optional dummy argument that is not present is subject to the following restrictions:

The OPTIONAL attribute cannot be specified for dummy arguments in an interface body that specifies an explicit interface for a defined operator or defined assignment.
Attributes Compatible with the OPTIONAL Attribute

  • DIMENSION
  • EXTERNAL

  • INTENT
  • POINTER

  • TARGET
  • VOLATILE

Examples

      SUBROUTINE SUB (X,Y)
        INTERFACE
          SUBROUTINE SUB2 (A,B)
            OPTIONAL :: B
          END SUBROUTINE
        END INTERFACE
        OPTIONAL :: Y
        IF (PRESENT(Y)) THEN          ! Reference to Y conditional
          X = X + Y                   ! on its presence
        ENDIF
        CALL SUB2(X,Y)
      END SUBROUTINE
 
      SUBROUTINE SUB2 (A,B)
        OPTIONAL :: B                 ! B and Y are argument associated,
        IF (PRESENT(B)) THEN          ! even if Y is not present, in
          B = B * A                   ! which case, B is also not present
          PRINT*, B
        ELSE
          A = A**2
          PRINT*, A
        ENDIF
      END SUBROUTINE

Related Information

PARAMETER

Purpose

The PARAMETER attribute specifies names for constants.

Format



                 +-,------------------------------+
                 V                                |
>>-PARAMETER--(----constant_name-- = --init_expr--+--)---------><
 

init_expr
is an initialization expression

Rules

A named constant must have its type, shape, and parameters specified in a previous specification statement in the same scoping unit or be declared implicitly. If a named constant is implicitly typed, its appearance in any subsequent type declaration statement or attribute specification statement must confirm the implied type and any parameter values.

You can define constant_name only once with a PARAMETER attribute in a scoping unit.

A named constant that is specified in the initialization expression must have been previously defined (possibly in the same PARAMETER or type declaration statement, if not in a previous statement) or made accessible through use or host association.

The initialization expression is assigned to the named constant using the rules for intrinsic assignment. If the named constant is of type character and it has inherited length, it takes on the length of the initialization expression.
Attributes Compatible with the PARAMETER Attribute

  • DIMENSION

  • PRIVATE

  • PUBLIC

Examples

REAL, PARAMETER :: TWO=2.0
 
COMPLEX      XCONST
REAL         RPART,IPART
PARAMETER    (RPART=1.1,IPART=2.2)
PARAMETER    (XCONST = (RPART,IPART+3.3))
 
CHARACTER*2, PARAMETER :: BB='   '
    ·
END

Related Information

PAUSE

Purpose

The PAUSE statement temporarily suspends the execution of a program and prints the keyword PAUSE and, if specified, a character constant or digit string to unit 0.

Format



>>-PAUSE--+---------------+------------------------------------><
          +-char_constant-+
          +-digit_string--+
 

char_constant
is a scalar character constant that is not a Hollerith constant

digit_string
is a string of one through five digits

Rules

After execution of a PAUSE statement, processing continues when you press the Enter key. If unit 5 is not connected to the terminal, the PAUSE statement does not suspend execution.

Examples

      PAUSE 'Ensure backup tape is in tape drive'
      PAUSE 10             ! Output:  PAUSE 10

POINTER (Fortran 90)

Purpose

The POINTER attribute designates objects as pointer variables.

The term pointer refers to objects with the Fortran 90 POINTER attribute. The integer POINTER statement provides details on what was documented in previous versions of XL Fortran as the POINTER statement; these pointers are now referred to as integer pointers.

Format



>>-POINTER-+----+----------------------------------------------->
           +-::-+
 
   +-,------------------------------------------------+
   V                                                  |
>----object_name--+---------------------------------+-+--------><
                  +-(--deferred_shape_spec_list--)--+
 

deferred_shape_spec
is a colon (:), where each colon represents a dimension

Rules

object_name refers to a data object or function result. If object_name is declared elsewhere in the scoping unit with the DIMENSION attribute, the array specification must be a deferred_shape_spec_list.

object_name must not appear in a DATA, integer POINTER, NAMELIST, or EQUIVALENCE statement. If object_name is a component of a derived-type definition, any variables declared with that type cannot be specified in an EQUIVALENCE, DATA, or NAMELIST statement.

Pointer variables can appear in common blocks and block data program units.

To ensure that Fortran 90 pointers are thread-specific, do not specify either the SAVE or STATIC attribute for the pointer. These attributes are either specified explicitly by the user, or implicitly through the use of the -qsave compiler option. Note, however, that if a non-static pointer is used in a pointer assignment statement where the target is static, all references to the pointer are, in fact, references to the static, shared target.

An object having a component with the POINTER attribute can itself have the TARGET, INTENT, or ALLOCATABLE attributes, although it cannot appear in a data transfer statement.
Attributes Compatible with the POINTER Attribute

  • AUTOMATIC
  • DIMENSION
  • OPTIONAL

  • PRIVATE
  • PUBLIC
  • SAVE

  • STATIC
  • VOLATILE

These attributes apply only to the pointer itself, not to any associated targets, except for the DIMENSION attribute, which applies to associated targets.

Examples

Example1:

INTEGER, POINTER :: PTR(:)
INTEGER, TARGET :: TARG(5)
PTR => TARG                  ! PTR is associated with TARG and is
                             !   assigned an array specification of (5)
 
PTR(1) = 5                   ! TARG(1) has value of 5
PRINT *, FUNC()
CONTAINS
  REAL FUNCTION FUNC()
    POINTER :: FUNC          ! Function result is a pointer
 
       ·
  END FUNCTION
END

Example 2: Fortran 90 pointers and threadsafing

FUNCTION MYFUNC(ARG)                ! MYPTR is thread-specific.
INTEGER, POINTER :: MYPTR           !  every thread that invokes
                                    !  'MYFUNC' will allocate a
ALLOCATE(MYPTR)                     !  new piece of storage that
MYPTR = ARG                         !  is only accessible within
·                                    !  that thread.
ANYVAR = MYPTR
END FUNCTION

Related Information

POINTER (integer)

Purpose

The integer POINTER statement specifies that the value of the variable int_pointer is to be used as the address for any reference to pointee.

The name of this statement has been changed from POINTER to integer POINTER to distinguish it from the Fortran 90 POINTER statement. The functionality and syntax for this statement remain the same as in previous releases of XL Fortran; only the name has changed.

Format



            +-,------------------------------+
            V                                |
>>-POINTER----(--int_pointer--,--pointee--)--+-----------------><
 

int_pointer
is the name of an integer pointer variable

pointee
is a variable name or array declarator

Rules

The compiler does not allocate storage for the pointee. Storage is associated with the pointee at execution time by the assignment of the address of a block of storage to the pointer. The pointee can become associated with either static or dynamic storage. A reference to a pointee requires that the associated pointer be defined.

An integer pointer is a scalar variable of type INTEGER(4) in 32-bit mode and type INTEGER(8) in 64-bit mode that cannot have a type explicitly assigned to it. You can use integer pointers in any expression or statement in which a variable of the same type as the integer pointer can be used. You can assign any data type to a pointee, but you cannot assign a storage class or initial value to a pointee.

An actual array that appears as a pointee in an integer POINTER statement is called a pointee array. You can dimension a pointee array in a type declaration statement, a DIMENSION statement, or in the integer POINTER statement itself.

If you specify the -qddim compiler option, a pointee array that appears in a main program can also have an adjustable array specification. In main programs and subprograms, the dimension size is evaluated when the pointee is referenced (dynamic dimensioning).

If you do not specify the -qddim compiler option, a pointee array that appears in a subprogram can have an adjustable array specification, and the dimension size is evaluated on entrance to the subprogram, not when the pointee is evaluated.

The following constraints apply to the definition and use of pointees and integer pointers:

Examples

     INTEGER A,B
     POINTER (P,I)
     IF (A<>0) THEN
       P=LOC(A)
     ELSE
       P=LOC(B)
     ENDIF
     I=0         ! Assigns 0 to either A or B, depending on A's value
     END

Related Information

PRINT

Purpose

The PRINT statement is a data transfer output statement.

Format



>>-PRINT--+-name-----------------------------+-----------------><
          +-format--+----------------------+-+
                    +-,--output_item_list--+
 

name
is a namelist group name

output_item
is an output list item. An output list specifies the data to be transferred. An output list item can be:

format
is a format specifier that specifies the format to be used in the output operation. format is a format identifier that can be:

Implied-DO List



>>-(--do_object_list-- , --------------------------------------->
 
>--do_variable = arith_expr1arith_expr2----------------------->
 
>-+---+--+-------------+---)-----------------------------------><
  +-,-+  +-arith_expr3-+
 

do_object
is an output list item

do_variable
is a named scalar variable of type integer or real

arith_expr1, arith_expr2,  and  arith_expr3
are scalar numeric expressions

The range of an implied- DO list is the list do_object_list. The iteration count and the values of the DO variable are established from arith_expr1, arith_expr2, and arith_expr3, the same as for a DO statement. When the implied- DO list is executed, the items in the do_object_list are specified once for each iteration of the implied- DO list, with the appropriate substitution of values for any occurrence of the DO variable.

Examples

   PRINT 10, A,B,C
10 FORMAT (E4.2,G3.2E1,B3)

Related Information

PRIVATE

Purpose

The PRIVATE attribute specifies that a module entity is not accessible outside the module through use association.

Format



>>-PRIVATE--+--------------------------+-----------------------><
            +-+----+---access_id_list--+
              +-::-+
 

access_id
is a generic specification or the name of a variable, procedure, derived type, constant, or namelist group

Rules

The PRIVATE attribute can appear only in the scope of a module.

Although multiple PRIVATE statements may appear in a module, only one statement that omits an access_id_list is permitted. A PRIVATE statement without an access_id_list sets the default accessibility to private for all potentially accessible entities in the module. If the module contains such a statement, it cannot also include a PUBLIC statement without an access_id_list. If the module does not contain such a statement, the default accessibility is public. Entities whose accessibility is not explicitly specified have default accessibility.

A procedure that has a generic identifier that is public is accessible through that identifier, even if its specific identifier is private. If a module procedure contains a private dummy argument or function result whose type has private accessibility, the module procedure must be declared to have private accessibility and must not have a generic identifier that has public accessibility.

If a PRIVATE statement is specified within a derived-type definition, all the components of the derived type become private.

A structure must be private if its derived type is private. A namelist group must be private if it contains any object that is private or contains private components. A derived type that has a component of derived type that is private must itself be private or have private components. A subprogram must be private if any of its arguments are of a derived type that is private. A function must be private if its result variable is of a derived type that is private.
Attributes Compatible with the PRIVATE Attribute

  • ALLOCATABLE
  • DIMENSION
  • EXTERNAL
  • INTRINSIC

  • PARAMETER
  • POINTER
  • SAVE

  • STATIC
  • TARGET
  • VOLATILE

Examples

MODULE MC
   PUBLIC                     ! Default accessibility declared as public
   INTERFACE GEN
      MODULE PROCEDURE SUB1, SUB2
   END INTERFACE
   PRIVATE SUB1               ! SUB1 declared as private
   CONTAINS
      SUBROUTINE SUB1(I)
         INTEGER I
         I = I + 1
      END SUBROUTINE SUB1
      SUBROUTINE SUB2(I,J)
         I = I + J
      END SUBROUTINE
END MODULE MC
 
PROGRAM ABC
   USE MC
   K = 5
   CALL GEN(K)                ! SUB1 referenced because GEN has public
                              ! accessibility and appropriate argument
                              ! is passed
   CALL SUB2(K,4)
   PRINT *, K                 ! Value printed is 10
END PROGRAM

Related Information

PROGRAM

Purpose

The PROGRAM statement specifies that a program unit is a main program, the program unit that receives control from the system when the executable program is invoked at run time.

Format



>>-PROGRAM--name-----------------------------------------------><
 

name
is the name of the main program in which this statement appears

Rules

The PROGRAM statement is optional.

If specified, the PROGRAM statement must be the first statement of the main program.

If a program name is specified in the corresponding END statement, it must match name.

The program name is global to the executable program. The program must not have a name that is the same as the name of any common block, external procedure, or any other program unit in that executable program. The program name cannot be the same as any name local to the main program.

The name has no type and must not appear in any type declaration or specification statements. You cannot refer to a main program from a subprogram or from itself.

Examples

      PROGRAM DISPLAY_NUMBER_2
         INTEGER A
         A = 2
         PRINT *, A
      END PROGRAM DISPLAY_NUMBER_2

Related Information

"Main Program"

PUBLIC

Purpose

The PUBLIC attribute specifies that a module entity can be accessed by other program units through use association.

Format



>>-PUBLIC--+--------------------------+------------------------><
           +-+----+---access_id_list--+
             +-::-+
 

access_id
is a generic specification or the name of a variable, procedure, derived type, constant, or namelist group

Rules

The PUBLIC attribute can appear only in the scope of a module.

Although multiple PUBLIC statements can appear in a module, only one statement that omits an access_id_list is permitted. A PUBLIC statement without an access_id_list sets the default accessibility to public for all potentially accessible entities in the module. If the module contains such a statement, it cannot also include a PRIVATE statement without an access_id_list. If the module does not contain such a statement, the default accessibility is public. Entities whose accessibility is not explicitly specified have default accessibility.

A procedure that has a generic identifier that is public is accessible through that identifier, even if its specific identifier is private. If a module procedure contains a private dummy argument or function result whose type has private accessibility, the module procedure must be declared to have private accessibility and must not have a generic identifier that has public accessibility.

Although an entity with public accessibility cannot have the STATIC attribute, public entities in a module are unaffected by IMPLICIT STATIC statements in the module.
Attributes Compatible with the PUBLIC Attribute

  • ALLOCATABLE
  • DIMENSION
  • EXTERNAL

  • INTRINSIC
  • PARAMETER
  • POINTER

  • SAVE
  • TARGET
  • VOLATILE

Examples

MODULE MC
   PRIVATE                    ! Default accessibility declared as private
   PUBLIC GEN                 ! GEN declared as public
   INTERFACE GEN
      MODULE PROCEDURE SUB1
   END INTERFACE
   CONTAINS
      SUBROUTINE SUB1(I)
         INTEGER I
         I = I + 1
      END SUBROUTINE SUB1
END MODULE MC
PROGRAM ABC
   USE MC
   K = 5
   CALL GEN(K)                ! SUB1 referenced because GEN has public
                              !   accessibility and appropriate argument
                              !   is passed
   PRINT *, K                 ! Value printed is 6
END PROGRAM

Related Information

READ

Purpose

The READ statement is the data transfer input statement.

Format



>>-READ--+-name----------------------------------------+-------><
         +-format--+---------------------+-------------+
         |         +-,--input_item_list--+             |
         +-(--io_control_list--)-+-----------------+---+
                                 +-input_item_list-+
 

format
is a format identifier, described below under FMT=format. In addition, it cannot be a Hollerith constant.

name
is a namelist group name

input_item
is an input list item. An input list specifies the data to be transferred. An input list item can be:

io_control
is a list that must contain one unit specifier ( UNIT=), and can also contain one of each of the other valid specifiers:

[UNIT=] u
is a unit specifier that specifies the unit to be used in the input operation. u is an external unit identifier or internal file identifier.

An external unit identifier refers to an external file. It is one of the following:

An internal file identifier refers to an internal file. It is the name of a character variable that cannot be an array section with a vector subscript.

If the optional characters UNIT= are omitted, u must be the first item in io_control_list. If the optional characters UNIT= are specified, either the optional characters FMT= or the optional characters NML= must also be present.

[FMT=] format
is a format specifier that specifies the format to be used in the input operation. format is a format identifier that can be:

If the optional characters FMT= are omitted, format must be the second item in io_control_list and the first item must be the unit specifier with the optional characters UNIT= omitted. Both NML= and FMT= cannot be specified in the same input statement.

REC= integer_expr
is a record specifier that specifies the number of the record to be read in a file connected for direct access. The REC= specifier is only permitted for direct input. integer_expr is an integer expression whose value is positive. A record specifier is not valid if list-directed or namelist formatting is used and if the unit specifier specifies an internal file. The END= specifier can appear concurrently. The record specifier represents the relative position of a record within a file. The relative position number of the first record is 1.

ID= integer_variable
indicates that the data transfer is to be done asynchronously. The integer_variable is a scalar of type INTEGER(4) or default integer. If no error is encountered, the integer_variable is defined with a value after executing the asynchronous data transfer statement. This value must be used in the matching WAIT statement.

Asynchronous data transfer must either be direct unformatted or sequential unformatted. Asynchronous I/O to internal files is prohibited. Asynchronous I/O to raw character devices (for example, to tapes or raw logical volumes) is prohibited. The integer_variable must not be associated with any entity in the data transfer I/O list, nor with a do_variable of an io_implied_do in the data transfer I/O list. If the integer_variable is an array element reference, its subscript values must not be affected by the data transfer, the io_implied_do processing, or the definition or evaluation of any other specifier in the io_control_spec.

IOSTAT= ios
is an input/output status specifier that specifies the status of the input/output operation. ios is a variable of type INTEGER(4) or default integer. Coding the IOSTAT= specifier suppresses error messages. When the statement finishes execution, ios is defined with:

ERR= stmt_label
is an error specifier that specifies the statement label of an executable statement to which control is to transfer in the case of an error. Coding the ERR= specifier suppresses error messages.

END= stmt_label
is an end-of-file specifier that specifies a statement label at which the program is to continue if an endfile record is encountered and no error occurs. An external file is positioned after the endfile record, the IOSTAT= specifier, if present, is assigned a negative value, and the NUM= specifier, if present, is assigned an integer value. If an error occurs and the statement contains the SIZE= specifier, the specified variable becomes defined with an integer value. Coding the END= specifier suppresses the error message for end-of-file. This specifier can be specified for a unit connected for either sequential or direct access.

NUM= integer_variable
is a number specifier that specifies the number of bytes of data transmitted between the I/O list and the file. integer_variable is a scalar variable name of type INTEGER(4), type INTEGER(8) in 64-bit, or type default integer. The NUM= specifier is only permitted for unformatted output. Coding the NUM parameter suppresses the indication of an error that would occur if the number of bytes represented by the output list is greater than the number of bytes that can be written into the record. In this case, integer_variable is set to a value that is the maximum length record that can be written. Data from remaining output list items is not written into subsequent records.

[NML=] name
is a namelist specifier that specifies the name of a namelist list that you have previously defined. If the optional characters NML=are not specified, the namelist name must appear as the second parameter in the list and the first item must be the unit specifier with UNIT= omitted. If both NML=and UNIT=are specified, all the parameters can appear in any order. The NML= specifier is an alternative to FMT=; both NML= and FMT= cannot be specified in the same input statement.

ADVANCE=char_expr
is an advance specifier that determines whether nonadvancing input occurs for this statement. char_expr is a scalar character expression that must evaluate to YES or NO. If NO is specified, nonadvancing input occurs. If YES is specified, advancing, formatted sequential input occurs. The default value is YES. ADVANCE= can be specified only in a formatted sequential READ statement with an explicit format specification that does not specify an internal file unit specifier.

SIZE=count
is a character count specifier that determines how many characters are transferred by data edit descriptors during execution of the current input statement. count is a scalar variable of type INTEGER(4), type INTEGER(8) in 64-bit, or type default integer. Blanks that are inserted as padding are not included in the count.

EOR=stmt_label
is an end-of-record specifier. If the specifier is present, an end-of-record condition occurs, and no error condition occurs during execution of the statement:
  1. If the PAD= specifier has the value YES, the record is padded with blanks to satisfy the input list item and the corresponding data edit descriptor that requires more characters than the record contains.
  2. Execution of the READ statement terminates.
  3. The file specified in the READ statement is positioned after the current record.
  4. If the IOSTAT= specifier is present, the specified variable becomes defined with a negative value different from an end-of-file value.
  5. If the SIZE= specifier is present, the specified variable becomes defined with an integer value.
  6. Execution continues with the statement containing the statement label specified by the EOR= specifier.
  7. End-of-record messages are suppressed.

Implied-DO List



>>-(--do_object_list-- , --------------------------------------->
 
>--do_variable = arith_expr1arith_expr2----------------------->
 
>-+---+--+-------------+---)-----------------------------------><
  +-,-+  +-arith_expr3-+
 

do_object
is an output list item

do_variable
is a named scalar variable of type integer or real

arith_expr1, arith_expr2,  and  arith_expr3
are scalar numeric expressions

The range of an implied- DO list is the list do_object_list. The iteration count and the values of the DO variable are established from arith_expr1, arith_expr2, and arith_expr3, the same as for a DO statement. When the implied- DO list is executed, the items in the do_object_list are specified once for each iteration of the implied- DO list, with the appropriate substitution of values for any occurrence of the DO variable.

The DO variable or an associated data item must not appear as an input list item in the do_object_list, but can be read in the same READ statement outside of the implied- DO list.

Rules

Any statement label specified by the ERR=, EOR= and END= specifiers must refer to a branch target statement that appears in the same scoping unit as the READ statement.

If either the EOR= specifier or the SIZE= specifier is present, the ADVANCE= specifier must also be present and must have the value NO.

If a NUM= specifier is present, neither a format specifier nor a namelist specifier can be present.

Variables specified for the IOSTAT=, SIZE= and NUM= specifiers must not be associated with any input list item, namelist list item, or the DO variable of an implied- DO list. If such a specifier variable is an array element, its subscript values must not be affected by the data transfer, any implied- DO processing, or the definition or evaluation of any other specifier.

A READ statement without io_control_list specified specifies the same unit as a READ statement with io_control_list specified in which the external unit identifier is an asterisk.

If the ERR= and IOSTAT= specifiers are set and an error is encountered during a synchronous data transfer, transfer is made to the statement specified by the ERR= specifier and a positive integer value is assigned to ios.

If the ERR= or IOSTAT= specifiers are set and an error is encountered during an asynchronous data transfer, execution of the matching WAIT statement is not required.

If the END= or IOSTAT= specifiers are set and an end-of-file condition is encountered during an asynchronous data transfer, execution of the matching WAIT statement is not required.

If a conversion error is encountered and the CNVERR run-time option is set to NO, ERR= is not branched to, although IOSTAT= may be set.

If IOSTAT= and ERR= are not specified,

Examples

INTEGER A(100)
CHARACTER*4 B
READ *, A(LBOUND(A,1):UBOUND(A,1))
READ (7,FMT='(A3)',ADVANCE='NO',EOR=100) B
     ·
100 PRINT *, 'end of record reached'
END

Related Information

REAL

Purpose

A REAL type declaration statement specifies the length and attributes of objects and functions of type real. Initial values can be assigned to objects.

Format



>>-REAL-+---------------+---+-+----+-----------------+---------->
        +-kind_selector-+   | +-::-+                 |
                            +-,--attr_spec_list--::--+
 
>-entity_decl_list---------------------------------------------><
 

where:
attr_spec

ALLOCATABLE
AUTOMATIC
DIMENSION (array_spec)
EXTERNAL
INTENT (intent_spec)
INTRINSIC
OPTIONAL
PARAMETER
POINTER
PRIVATE
PUBLIC
SAVE
STATIC
TARGET
VOLATILE

kind_selector



>>-+-(--+------------+--int_initialization_expr--)--+----------><
   |    +-KIND-- = --+                              |
   +- * --int_literal_constant----------------------+
 

 
specifies the length of real entities: 4, 8 or 16. int_literal_constant cannot specify a kind type parameter.

attr_spec
For detailed information on rules about a particular attribute, refer to the statement of the same name.

intent_spec
is either IN, OUT, or INOUT

::
is the double colon separator. It is required if attributes are specified or if = initialization_expr is used.

array_spec
is a list of dimension bounds

entity_decl



>>-a--+-+-----------+--+-------------------+-+------------------>
      | +- * --len--+  +-(--array_spec--)--+ |
      +-(--array_spec--)-- * --len-----------+
 
>--+--------------------------------+--------------------------><
   +--+-/--initial_value_list--/--+-+
      +- = --initialization_expr--+
 

 

a
is an object name or function name. array_spec cannot be specified for a function name.

len
overrides the length as specified in kind_selector, and cannot specify a kind type parameter. The entity length must be an integer literal constant that represents one of the permissible length specifications.

initial_value
provides an initial value for the entity specified by the immediately preceding name

initialization_expr
provides an initial value, by means of an initialization expression, for the entity specified by the immediately preceding name

Rules

Entities in type declaration statements are constrained by the rules of any attributes specified for the entities, as detailed in the corresponding attribute statements.

The type declaration statement overrides the implicit type rules in effect. You can use a type declaration statement that confirms the type of an intrinsic function. The appearance of a generic or specific intrinsic function name in a type declaration statement does not cause the name to lose its intrinsic property.

An object cannot be initialized in a type declaration statement if it is a dummy argument, an allocatable array, a pointer, a function result, an object in blank common, an integer pointer, an external name, an intrinsic name, or an automatic object. Nor can an object be initialized if it has the AUTOMATIC attribute. The object may be initialized if it appears in a named common block in a block data program unit or if it appears in a named common block in a module.

The specification expression of an array_spec can be a nonconstant expression if the specification expression appears in an interface body or in the specification part of a subprogram. Any object being declared that uses this nonconstant expression and is not a dummy argument or a pointee is called an automatic object.

An attribute cannot be repeated in a given type declaration statement, nor can an entity be explicitly given the same attribute more than once in a scoping unit.

initialization_expr must be specified if the statement contains the PARAMETER attribute. If initialization_expr is specified and PARAMETER is not, the object is a variable that is initially defined. a becomes defined with the value determined by initialization_expr, in accordance with the rules for intrinsic assignment. If the variable is an array, its shape must be specified either in the type declaration statement or in a previous specification statement in the same scoping unit. A variable or variable subobject cannot be initialized more than once. The presence of initialization_expr implies that a is a saved object, except for an object with the PARAMETER attribute or in a named common block. The initialization of an object could affect the fundamental storage class of an object.

An array_spec specified in the entity_decl takes precedence over the array_spec in the DIMENSION attribute.

An array function result that does not have the POINTER attribute must have an explicit-shape array specification.

If the entity declared is a function, it must not have an accessible explicit interface unless it is an intrinsic function.

If T or F, defined previously as the name of a constant, appears in a type declaration statement, it is no longer an abbreviated logical constant but the name of the named constant.

Examples

      REAL(8), POINTER :: RPTR
      REAL(8), TARGET  :: RTAR

Related Information

RETURN

Purpose

The RETURN statement:

Format



>>-RETURN-+------------+---------------------------------------><
          +-arith_expr-+
 

arith_expr
is a scalar integer, real, or complex expression. If the value of the expression is noninteger, it is converted to INTEGER(4) before use. arith_expr cannot be a Hollerith constant.

Rules

arith_expr can be specified in a subroutine subprogram only, and it specifies an alternate return point. Letting m be the value of arith_expr, if 1 <= m <= the number of asterisks in the SUBROUTINE or ENTRY statement, the mth asterisk in the dummy argument list is selected. Control then returns to the invoking procedure at the statement whose statement label is specified as the mth alternate return specifier in the CALL statement. For example, if the value of m is 5, control returns to the statement whose statement label is specified as the fifth alternate return specifier in the CALL statement.

If arith_expr is omitted or if its value (m) is not in the range 1 through the number of asterisks in the SUBROUTINE or ENTRY statement, a normal return is executed. Control returns to the invoking procedure at the statement following the CALL statement.

Executing a RETURN statement terminates the association between the dummy arguments of the subprogram and the actual arguments supplied to that instance of the subprogram. All entities local to the subprogram become undefined, except as noted under "Events Causing Undefinition".

A subprogram can contain more than one RETURN statement, but it does not require one. An END statement in a function or subroutine subprogram has the same effect as a RETURN statement.

Examples

CALL SUB(A,B)
CONTAINS
  SUBROUTINE SUB(A,B)
    INTEGER :: A,B
    IF (A.LT.B)
      RETURN            ! Control returns to the calling procedure
    ELSE
      ·
    END IF
  END SUBROUTINE
END

Related Information

REWIND

Purpose

The REWIND statement positions an external file connected for sequential access at the beginning of the first record of the file.

Format



>>-REWIND--+-u--------------------+----------------------------><
           +-(--position_list--)--+
 

u
is an external unit identifier. The value of u must not be an asterisk or a Hollerith constant.

position_list
is a list that must contain one unit specifier ([ UNIT=]u) and can also contain one of each of the other valid specifiers. The valid specifiers are:

[UNIT=] u
is a unit specifier in which u must be an external unit identifier whose value is not an asterisk. An external unit identifier refers to an external file that is represented by a scalar integer expression, whose value is in the range 1 through 2,147,483,647. If the optional characters UNIT= are omitted, u must be the first item in position_list.

IOSTAT= ios
is an input/output status specifier that specifies the status of the input/output operation. ios is a scalar variable of type INTEGER(4) or default integer. When the REWIND statement finishes executing, ios is defined with:

ERR= stmt_label
is an error specifier that specifies the statement label of an executable statement in the same scoping unit to which control is to transfer in the case of an error. Coding the ERR= specifier suppresses error messages.

Rules

If the unit is not connected, an implicit OPEN specifying sequential access is performed to a default file named fort.n, where n is the value of u with leading zeros removed. If the external file connected to the specified unit does not exist, the REWIND statement has no effect. If it exists, an end-of-file marker is created, if necessary, and the file is positioned at the beginning of the first record. If the file is already positioned at its initial point, the REWIND statement has no effect. The REWIND statement causes a subsequent READ or WRITE statement referring to u to read data from or write data to the first record of the external file associated with u.

If the ERR= and IOSTAT= specifiers are set and an error is encountered, transfer is made to the statement specified by the ERR= specifier and a positive integer value is assigned to ios.

If IOSTAT= and ERR= are not specified,

Examples

      REWIND (9, IOSTAT=IOSS)

Related Information

SAVE

Purpose

The SAVE attribute specifies the names of objects and named common blocks whose definition status you want to retain after control returns from the subprogram where you define the variables and named common blocks.

Format



>>-SAVE--+-------------------------------------------+---------><
         |          +-,---------------------------+  |
         |          V                             |  |
         +-+----+-----+-object_name--------------++--+
           +-::-+     +-/--common_block_name--/--+
 

Rules

A SAVE statement without a list is treated as though it contains the names of all common items and local variables in the scoping unit. A common block name having the SAVE attribute has the effect of specifying all the entities in that named common block.

Within a function or subroutine subprogram, a variable whose name you specify with the SAVE attribute does not become undefined as a result of a RETURN or END statement in the subprogram.

object_name cannot be the name of a dummy argument, pointee, procedure, automatic object, or common block entity.

If a local entity specified with the SAVE attribute (and not in a common block) is in a defined state at the time a RETURN or END statement is encountered in a subprogram, that entity is defined with the same value at the next reference of that subprogram. Saved objects are shared by all instances of the subprogram.

XL Fortran permits function results to have the SAVE attribute. To indicate that a function result is to have the SAVE attribute, the function result name must be explicitly specified with the SAVE attribute. That is, a SAVE statement without a list does not provide the SAVE attribute for the function result.

Variables declared as SAVE are shared amongst threads. To thread-safe an application which contains shared variables, you must either serialize access to the static data using locks, or make the data thread-specific. One method of making the data thread-specific is to move the static data into a named COMMON block that has been declared THREADLOCAL. The Pthreads library module provides mutexes to allow you to serialize access to the data using locks. See Chapter 14. "Pthreads Library Module" for more information. The lock_name attribute on the CRITICAL directive also provides the ability to serialize access to data. See CRITICAL / END CRITICAL for more information. The THREADLOCAL directive ensures that common blocks are local to each thread. See THREADLOCAL for more information.
Attributes Compatible with the SAVE Attribute

  • ALLOCATABLE
  • DIMENSION
  • POINTER

  • PRIVATE
  • PUBLIC
  • STATIC

  • TARGET
  • VOLATILE

Examples

LOGICAL :: CALLED=.FALSE.
CALL SUB(CALLED)
CALLED=.TRUE.
CALL SUB(CALLED)
CONTAINS
  SUBROUTINE SUB(CALLED)
    INTEGER, SAVE :: J
    LOGICAL :: CALLED
    IF (CALLED.EQV..FALSE.) THEN
      J=2
    ELSE
      J=J+1
    ENDIF
    PRINT *, J                  ! Output on first call is 2
                                ! Output on second call is 3
  END SUBROUTINE
END

Related Information

SELECT CASE

Purpose

The SELECT CASE statement is the first statement of a CASE construct, which provides a concise syntax for selecting, at most, one of a number of statement blocks for execution.

Format



>>-+-------------------------+--SELECT CASE--(--case_expr--)---><
   +-case_construct_name--:--+
 

case_construct_name
is a name given to the CASE construct for identification

case_expr
is a scalar expression of type integer, character or logical

Rules

When a SELECT CASE statement is executed, the case_expr is evaluated. The resulting value is called the case index, which is used for evaluating control flow within the case construct.

If the case_construct_name is specified, it must appear on the END CASE statement and optionally on any CASE statements within the construct.

The case_expr must not be a typeless constant nor a BYTE data object.

Examples

      ZERO: SELECT CASE(N)         ! start of CASE construct ZERO
 
        CASE DEFAULT ZERO
             OTHER: SELECT CASE(N) ! start of CASE construct OTHER
                CASE(:-1)
                   SIGNUM = -1
                CASE(1:) OTHER
                    SIGNUM = 1
             END SELECT OTHER
        CASE (0)
          SIGNUM = 0
 
      END SELECT ZERO

Related Information

SEQUENCE

Purpose

The SEQUENCE statement specifies that the order of the components in a derived-type definition establishes the storage sequence for objects of that type. Such a type becomes a sequence derived type.

Format



>>-SEQUENCE----------------------------------------------------><
 

Rules

The SEQUENCE statement can be specified only once in a derived-type definition.

If a component of a sequence derived type is of derived type, that derived type must also be a sequence derived type.

The size of a sequence derived type is equal to the number of bytes of storage needed to hold all of the components of that derived type.

Use of sequence derived types can lead to misaligned data, which can adversely affect the performance of a program.

Examples

TYPE PERSON
  SEQUENCE
  CHARACTER*1 GENDER     ! Offset 0
  INTEGER(4) AGE         ! Offset 1
  CHARACTER(30) NAME     ! Offset 5
END TYPE PERSON

Related Information

Statement Function

Purpose

A statement function defines a function in a single statement.

Format



>>-name--(-+---------------------+---)-- = --scalar_expression--><
           +-dummy_argument_list-+
 

name
is the name of the statement function. It must not be supplied as a procedure argument.

dummy_argument
can only appear once in the dummy argument list of any statement function. The dummy arguments have the scope of the statement function statement, and the same types and type parameters as the entities of the same names in the scoping unit containing the statement function.

Rules

A statement function is local to the scoping unit in which it is defined. It must not be defined in the scope of a module.

name determines the data type of the value returned from the statement function. If the data type of name does not match that of the scalar expression, the value of the scalar expression is converted to the type of name in accordance with the rules for assignment statements.

The names of the function and all the dummy arguments must be specified, explicitly or implicitly, to be scalar data objects.

The scalar expression can be composed of constants, references to variables, references to functions and function dummy procedures, and intrinsic operations. If the expression contains a reference to a function or function dummy procedure, the reference must not require an explicit interface, the function must not require an explicit interface or be a transformational intrinsic, and the result must be scalar. If an argument to a function or function dummy procedure is array-valued, it must be an array name.

With XL Fortran, the scalar expression can also reference a structure constructor.

The scalar expression can reference another statement function that is either:

Named constants and arrays whose elements are referenced in the expression must be declared earlier in the scoping unit or be made accessible by use or host association.

Variables that are referenced in the expression must be either:

If an entity in the expression is typed by the implicit typing rules, its type must agree with the type and type parameters given in any subsequent type declaration statement.

An external function reference in the scalar expression must not cause any dummy arguments of the statement function to become undefined or redefined.

If the statement function is defined in an internal subprogram and if it has the same name as an accessible entity from the host, precede the statement function definition with an explicit declaration of the statement function name. For example, use a type declaration statement.

The length specification for a statement function of type character or a statement function dummy argument of type character must be a constant specification expression.

Examples

PARAMETER (PI = 3.14159)
REAL AREA,CIRCUM,R,RADIUS
AREA(R) = PI * (R**2)            ! Define statement functions
CIRCUM(R) = 2 * PI * R           !   AREA and CIRCUM
 
! Reference the statement functions
PRINT *,'The area is: ',AREA(RADIUS)
PRINT *,'The circumference is: ',CIRCUM(RADIUS)

Related Information

STATIC

Purpose

The STATIC attribute specifies that a variable has a storage class of static; that is, the variable remains in memory for the duration of the program and its value is retained between calls to the procedure.

Format




                 +-,-------------------------------------------+ 
                 V                                             |
>>-STATIC-+----+---stat_variable--+--------------------------+-+-><
          +-::-+                  +-/--initial_value_list--/-+

stat_variable
is a variable name or an array declarator that can specify an explicit_shape_spec_list or a deferred_shape_spec_list.

initial_value
provides an initial value for the variable specified by the immediately preceding name. Initialization occurs as described in DATA.

Rules

If stat_variable is a result variable, it must not be of type character nor of derived type. Dummy arguments, automatic objects and pointees must not have the STATIC attribute. A variable that is explicitly declared with the STATIC attribute cannot be a common block item.

A variable must not have the STATIC attribute specified more than once in the same scoping unit.

Local variables have a default storage class of automatic. See the " -qsave Option" in the User's Guide for details on the default settings with regard to the invocation commands.

Variables declared as STATIC are shared amongst threads. To thread-safe an application which contains shared variables, you must either serialize access to the static data using locks, or make the data thread-specific. One method of making the data thread-specific is to move the static data into a COMMON block that has been declared THREADLOCAL. The Pthreads library module provides mutexes to allow you to serialize access to the data using locks. See Chapter 14. "Pthreads Library Module" for more information. The lock_name attribute on the CRITICAL directive also provides the ability to serialize access to data. See CRITICAL / END CRITICAL for more information. The THREADLOCAL directive ensures that common blocks are local to each thread. See THREADLOCAL for more information.
Attributes Compatible with the STATIC Attribute

  • ALLOCATABLE
  • DIMENSION
  • POINTER

  • PRIVATE
  • SAVE

  • TARGET
  • VOLATILE

Examples

LOGICAL :: CALLED=.FALSE.
CALL SUB(CALLED)
CALLED=.TRUE.
CALL SUB(CALLED)
CONTAINS
  SUBROUTINE SUB(CALLED)
    INTEGER, STATIC :: J
    LOGICAL :: CALLED
    IF (CALLED.EQV..FALSE.) THEN
      J=2
    ELSE
      J=J+1
    ENDIF
    PRINT *, J                  ! Output on first call is 2
                                ! Output on second call is 3
  END SUBROUTINE
END

Related Information

STOP

Purpose

When the STOP statement is executed, the program stops executing and, if a character constant or digit string is specified, prints the keyword STOP followed by the constant or digit string to unit 0.

Format



>>-STOP--+---------------+-------------------------------------><
         +-char_constant-+
         +-digit_string--+
 

char_constant
is a scalar character constant that is not a Hollerith constant

digit_string
is a string of one through five digits

Rules

If neither char_constant nor digit_string are specified, nothing is printed to standard error (unit 0).

A STOP statement cannot terminate the range of a DO or DO WHILE construct.

If you specify digit_string, XL Fortran sets the system return code to MOD (digit_string,256). The system return code is available in the Korn shell command variable $?.

Examples

STOP 'Abnormal Termination'    ! Output:  STOP Abnormal Termination
END
 
STOP                           ! No output
END

SUBROUTINE

Purpose

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

Format



    +------------+
    V            |
>>---+---------+-+--SUBROUTINE--name---------------------------->
     +-prefix--+
 
>--+--------------------------------+--------------------------><
   +-(-+---------------------+---)--+
       +-dummy_argument_list-+
 

prefix
is one of the following:
RECURSIVE
PURE
Note:type_spec is not permitted as a prefix in a subroutine.

name
is the name of the subroutine subprogram

Rules

At most one of each kind of prefix can be specified.

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,

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

Using the PURE prefix indicates that the subroutine may be invoked by the compiler in any order as it is free of side-effects. However, with regard to PURE subroutines, there are three exceptions:

You 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.

Examples

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

Related Information

TARGET

Purpose

Variables with the TARGET attribute can become pointer targets.

Format



                   +-,------------------------------------+
                   V                                      |
>>-TARGET-+----+-----variable_name--+-------------------+-+----><
          +-::-+                    +-(--array_spec--)--+
 

Rules

Although the target of a pointer can also be a pointer, this target cannot have the TARGET attribute.

A target cannot appear in an EQUIVALENCE statement.

A target cannot be an integer pointer or a pointee.
Attributes Compatible with the TARGET Attribute

  • ALLOCATABLE
  • AUTOMATIC
  • DIMENSION
  • INTENT

  • OPTIONAL
  • PRIVATE
  • PUBLIC

  • SAVE
  • STATIC
  • VOLATILE

Examples

REAL, POINTER :: A,B
REAL, TARGET  :: C = 3.14
B => C
A => B       ! A points to C

Related Information

TYPE

Purpose

A TYPE type declaration statement specifies the type and attributes of objects and functions of derived type. Initial values can be assigned to objects.

Format



>>-TYPE--(--type_name--)--+-+----+-----------------+------------>
                          | +-::-+                 |
                          +-,--attr_spec_list--::--+
 
>--entity_decl_list--------------------------------------------><
 

where:
attr_spec

ALLOCATABLE
AUTOMATIC
DIMENSION (array_spec)
EXTERNAL
INTENT (intent_spec)
INTRINSIC
OPTIONAL
PARAMETER
POINTER
PRIVATE
PUBLIC
SAVE
STATIC
TARGET
VOLATILE

type_name
is the name of a derived type

attr_spec
For detailed information on rules about a particular attribute, refer to the statement of the same name.

intent_spec
is either IN, OUT, or INOUT

::
is the double colon separator. It is required if attributes are specified or if = initialization_expr is used.

array_spec
is a list of dimension bounds

entity_decl



>>-a--+-------------------+--+--------------------------------+-><
      +-(--array_spec--)--+  +--+-/--initial_value_list--/--+-+
                                +- = --initialization_expr--+
 

a
is an object name or function name. array_spec cannot be specified for a function name.

initial_value
provides an initial value for the entity specified by the immediately preceding name

initialization_expr
provides an initial value, by means of an initialization expression, for the entity specified by the immediately preceding name

Rules

Entities in type declaration statements are constrained by the rules of any attributes specified for the entities, as detailed in the corresponding attribute statements.

Once a derived type has been defined, you can use it to define your data items using the TYPE type declaration statement. When an entity is explicitly declared to be of a derived type, that derived type must have been previously defined in the scoping unit or is accessible by use or host association.

The data object becomes an object of derived type or a structure. Each structure component is a subobject of the object of derived type.

If you specify the DIMENSION attribute, you are creating an array whose elements have a data type of that derived type.

Other than in specification statements, you can use objects of derived type as actual and dummy arguments, and they can also appear as items in input/output lists (unless the object has a component with the POINTER attribute), assignment statements, structure constructors, and the right side of a statement function definition. If a structure component is not accessible, a derived-type object cannot be used in an input/output list or as a structure constructor.

Objects of nonsequence derived type cannot be used as data items in EQUIVALENCE and COMMON statements. Objects of nonsequence data types cannot be integer pointees.

A nonsequence derived-type dummy argument must specify a derived type that is accessible through use or host association to ensure that the same derived-type definition defines both the actual and dummy arguments.

The type declaration statement overrides the implicit type rules in effect.

An object cannot be initialized in a type declaration statement if it is a dummy argument, allocatable array, pointer, function result, object in blank common, integer pointer, external name, intrinsic name, or automatic object. Nor can an object be initialized if it has the AUTOMATIC attribute. The object may be initialized if it appears in a named common block in a block data program unit or if it appears in a named common block in a module.

The specification expression of an array_spec can be a nonconstant expression if the specification expression appears in an interface body or in the specification part of a subprogram. Any object being declared that uses this nonconstant expression and is not a dummy argument or a pointee is called an automatic object.

An attribute cannot be repeated in a given type declaration statement, nor can an entity be explicitly given the same attribute more than once in a scoping unit.

initialization_expr must be specified if the statement contains the PARAMETER attribute. If initialization_expr is specified and PARAMETER is not, the object is a variable that is initially defined. a becomes defined with the value determined by initialization_expr, in accordance with the rules for intrinsic assignment. If the variable is an array, its shape must be specified either in the type declaration statement or in a previous specification statement in the same scoping unit. A variable or variable subobject cannot be initialized more than once. The presence of initialization_expr implies that a is a saved object, except for an object with the PARAMETER attribute or in a named common block. The initialization of an object could affect the fundamental storage class of an object.

An array_spec specified in the entity_decl takes precedence over the array_spec in the DIMENSION attribute.

An array function result that does not have the POINTER attribute must have an explicit-shape array specification.

If the entity declared is a function, it must not have an accessible explicit interface unless it is an intrinsic function. The derived type can be specified on the FUNCTION statement, provided the derived type is defined within the body of the function or is accessible via host or use association.

If T or F, defined previously as the name of a constant, appears in a type declaration statement, it is no longer an abbreviated logical constant but the name of the named constant.

Examples

TYPE PEOPLE                      ! Defining derived type PEOPLE
  INTEGER AGE
  CHARACTER*20 NAME
END TYPE PEOPLE
TYPE(PEOPLE) :: SMITH = PEOPLE(25,'John Smith')
END

Related Information

Type Declaration

Purpose

A type declaration statement specifies the type, length, and attributes of objects and functions. Initial values can be assigned to objects.

Format



>>-type_spec--+-+----+-----------------+-entity_decl_list------><
              | +-::-+                 |
              +-,--attr_spec_list--::--+
 

where:
type_spec

attr_spec

BYTE
CHARACTER [char_selector]
COMPLEX [ kind_selector]
DOUBLE COMPLEX
DOUBLE PRECISION
INTEGER [ kind_selector]
LOGICAL [ kind_selector]
REAL [ kind_selector]
TYPE ( type_name)

ALLOCATABLE
AUTOMATIC
DIMENSION (array_spec)
EXTERNAL
INTENT (intent_spec)
INTRINSIC
OPTIONAL
PARAMETER
POINTER
PRIVATE
PUBLIC
SAVE
STATIC
TARGET
VOLATILE

type_name
is the name of a derived type

kind_selector



>>-+-(--+------------+--int_initialization_expr--)--+----------><
   |    +-KIND-- = --+                              |
   +- * --int_literal_constant----------------------+
 

 
represents one of the permissible length specifications for its associated type. int_literal_constant cannot specify a kind type parameter.

char_selector
specifies the character length (number of characters between 0 and 256 MB). Values exceeding 256 MB are set to 256 MB, while negative values result in a length of zero. If not specified, the default length is 1. The kind type parameter, if specified, must be 1, which specifies the ASCII character representation.




>>-+-(-+-LEN--=--type_param_value--,--KIND--=--int_init_expr-----+-)-+-><
   |   +-type_param_value--,--+----------+--int_init_expr--------+   |
   |   |                      +-KIND--=--+                       |   |
   |   +-KIND--=--int_init_expr--+-----------------------------+-+   |
   |   |                         +-,--LEN--=--type_param_value-+ |   |
   |   +-+---------+--type_param_value---------------------------+   |
   |     +-LEN--=--+                                                 |
   +-*-char_length-+---+---------------------------------------------+
                   +-,-+

 

type_param_value
is a specification expression or an asterisk (*)

int_init_expr
is a scalar integer initialization expression that must evaluate to 1

char_length
is either a scalar integer literal constant (which cannot specify a kind type parameter) or a type_param_value enclosed in parentheses

attr_spec
For detailed information on rules about a particular attribute, refer to the statement of the same name.

intent_spec
is either IN, OUT, or INOUT

::
is the double colon separator. It is required if attributes are specified or if = initialization_expr is used.

array_spec
is a list of dimension bounds

entity_decl



>>-a--+-+-------------------+--+-------------------+-+---------->
      | +- * --char_length--+  +-(--array_spec--)--+ |
      +-(--array_spec--)-- * --char_length-----------+
 
>--+--------------------------------+--------------------------><
   +--+-/--initial_value_list--/--+-+
      +- = --initialization_expr--+
 

 

a
is an object name or function name. array_spec cannot be specified for a function name.

char_length
overrides the length as specified in kind_selector and char_selector, and is only permitted in statements where the length can be specified with the initial keyword. A character entity can specify char_length, as defined above. A noncharacter entity can only specify an integer literal constant that represents one of the permissible length specifications for its associated type.

initial_value
provides an initial value for the entity specified by the immediately preceding name

initialization_expr
provides an initial value, by mean of an initialization expression, for the entity specified by the immediately preceding name

Rules

Entities in type declaration statements are constrained by the rules of any attributes specified for the entities, as detailed in the corresponding attribute statements.

The type declaration statement overrides the implicit type rules in effect. You can use a type declaration statement that confirms the type of an intrinsic function. The appearance of a generic or specific intrinsic function name in a type declaration statement does not cause the name to lose its intrinsic property.

An object cannot be initialized in a type declaration statement if it is a dummy argument, allocatable array, pointer, function result, object in blank common, integer pointer, external name, intrinsic name, or automatic object. Nor can an object be initialized if it has the AUTOMATIC attribute. The object may be initialized if it appears in a named common block in a block data program unit or if it appears in a named common block in a module.

The specification expression of a type_param_value or an array_spec can be a nonconstant expression if the specification expression appears in an interface body or in the specification part of a subprogram. Any object being declared that uses this nonconstant expression and is not a dummy argument or a pointee is called an automatic object.

An attribute cannot be repeated in a given type declaration statement, nor can an entity be explicitly given the same attribute more than once in a scoping unit.

initialization_expr must be specified if the statement contains the PARAMETER attribute. If initialization_expr is specified and PARAMETER is not, the object is a variable that is initially defined. a becomes defined with the value determined by initialization_expr, in accordance with the rules for intrinsic assignment. If the variable is an array, its shape must be specified either in the type declaration statement or in a previous specification statement in the same scoping unit. A variable or variable subobject cannot be initialized more than once. The presence of initialization_expr implies that a is a saved object, except for an object with the PARAMETER attribute or in a named common block. The initialization of an object could affect the fundamental storage class of an object.

An array_spec specified in an entity_decl takes precedence over the array_spec in the DIMENSION attribute.

An array function result that does not have the POINTER attribute must have an explicit-shape array specification.

If the entity declared is a function, it must not have an accessible explicit interface unless it is an intrinsic function.

If T or F, defined previously as the name of a constant, appears in a type declaration statement, it is no longer an abbreviated logical constant but the name of the named constant.

The optional comma after char_length in a CHARACTER type declaration statement is permitted only if no double colon separator (::) appears in the statement.

If the CHARACTER type declaration statement is in the scope of a module, block data program unit, or main program, and you specify the length of the entity as inherited length, the entity must be the name of a named character constant. The character constant assumes the length of its corresponding expression defined by the PARAMETER attribute.

If the CHARACTER type declaration statement is in the scope of a procedure and the length of the entity is inherited, the entity name must be the name of a dummy argument or a named character constant. If the statement is in the scope of an external function, it can also be the function or entry name in a FUNCTION or ENTRY statement in the same program unit. If the entity name is the name of a dummy argument, the dummy argument assumes the length of the associated actual argument for each reference to the procedure. If the entity name is the name of a character constant, the character constant assumes the length of its corresponding expression defined by the PARAMETER attribute. If the entity name is a function or entry name, the entity assumes the length specified in the calling scoping unit.

The length of a character function is either a specification expression (which must be a constant expression if the function type is not declared in an interface block) or it is an asterisk, indicating the length of a dummy procedure name. The length cannot be an asterisk if the function is an internal or module function, recursive, or if the function returns array or pointer values.

Examples

      CHARACTER(KIND=1,LEN=6) APPLES /'APPLES'/
      CHARACTER*7, TARGET :: ORANGES = 'ORANGES'
      CALL TEST(APPLES)
      END
 
      SUBROUTINE  TEST(VARBL)
        CHARACTER*(*), OPTIONAL :: VARBL   ! VARBL inherits a length of 6
 
        COMPLEX, DIMENSION (2,3) :: ABC(3) ! ABC has 3 (not 6) array elements
        REAL, POINTER :: XCONST
 
        TYPE PEOPLE                        ! Defining derived type PEOPLE
          INTEGER AGE
          CHARACTER*20 NAME
        END TYPE PEOPLE
        TYPE(PEOPLE) :: SMITH = PEOPLE(25,'John Smith')
      END

Related Information

USE

Purpose

The USE statement is a module reference that provides local access to the public entities of a module.

Format



>>-USE--module_name--+----------------------------+------------><
                     +-,--rename_list-------------+
                     +-,--ONLY--:-+-----------+---+
                                  +-only_list-+
 

rename
is the assignment of a local name to an accessible data entity: local_name => use_name

only
is a rename, a generic specification, or the name of a variable, procedure, derived type, named constant, or namelist group

Rules

The USE statement can only appear prior to all other statements in specification_part. Multiple USE statements may appear within a scoping unit.

At the time the file containing the USE statement is being compiled, the specified module must precede the USE statement in the file or the module must have been already compiled in another file. Each referenced entity must be the name of a public entity in the module.

Entities in the scoping unit become use-associated with the module entities, and the local entities have the attributes of the corresponding module entities.

In addition to the PRIVATE attribute, the ONLY clause of the USE statement provides further constraint on which module entities can be accessed. If the ONLY clause is specified, only entities named in the only_list are accessible. If no list follows the keyword, no module entities are accessible. If the ONLY clause is absent, all public entities are accessible.

If a scoping unit contains multiple USE statements, all specifying the same module, and one of the statements does not include the ONLY clause, all public entities are accessible. If each USE statement includes the ONLY clause, only those entities named in one or more of the only_lists are accessible.

You can rename an accessible entity for local use. A module entity can be accessed by more than one local name. If no renaming is specified, the name of the use-associated entity becomes the local name. The local name of a use-associated entity cannot be redeclared. However, if the USE statement appears in the scoping unit of a module, the local name can appear in a PUBLIC or PRIVATE statement.

If multiple generic interfaces that are accessible to a scoping unit have the same local name, operator, or assignment, they are treated as a single generic interface. In such a case, one of the generic interfaces can contain an interface body to an accessible procedure with the same name. Otherwise, any two different use-associated entities can only have the same name if the name is not used to refer to an entity in the scoping unit. If a use-associated entity and host entity share the same name, the host entity becomes inaccessible through host association by that name.

A module must not reference itself, either directly or indirectly. For example, module X cannot reference module Y if module Y references module X.

Consider the situation where a module (for example, module B) has access through use association to the public entities of another module (for example, module A). The accessibility of module B's local entities (which includes those entities that are use-associated with entities from module A) to other program units is determined by the PRIVATE and PUBLIC attributes, or, if absent, through the default accessibility of module B. Of course, other program units can access the public entities of module A directly.

Examples

   MODULE A
     REAL :: X=5.0
   END MODULE A
   MODULE B
     USE A
     PRIVATE :: X               !  X cannot be accessed through module B
     REAL :: C=80, D=50
   END MODULE B
   PROGRAM TEST
     INTEGER :: TX=7
     CALL SUB
     CONTAINS
 
     SUBROUTINE SUB
     USE B, ONLY : C
     USE B, T1 => C
     USE B, TX => C             !  C is given another local name
     USE A
     PRINT *, TX                !  Value written is 80 because use-associated
                                !  entity overrides host entity
     END SUBROUTINE
   END

Related Information

VIRTUAL

Purpose

The VIRTUAL statement specifies the name and dimensions of an array. The VIRTUAL statement is an alternative form of the DIMENSION statement, although there is no VIRTUAL attribute.

Format



>>-VIRTUAL--array_declarator_list------------------------------><
 

Rules

You can specify arrays with a maximum of 20 dimensions.

Only one array specification for an array name can appear in a scoping unit.

Examples

VIRTUAL A(10), ARRAY(5,5,5), LIST(10,100)
VIRTUAL ARRAY2(1:5,1:5,1:5), LIST2(I,M)       ! adjustable array
VIRTUAL B(0:24), C(-4:2), DATA(0:9,-5:4,10)
VIRTUAL ARRAY (M*N*J,*)                       ! assumed-size array

Related Information

VOLATILE

Purpose

The VOLATILE attribute is used to designate a data object as being mapped to memory that can be accessed by independent input/output processes and independent, asynchronously interrupting processes. Code that manipulates volatile data objects is not optimized.

Format



                     +-,----------------------------+
                     V                              |
>>-VOLATILE-+----+------+-variable_name------------++----------><
            +-::-+      +-/--common_block_name--/--+
                        +-derived_type_name--------+
 

Rules

If an array name is declared volatile, each element of the array is considered volatile. If a common block is declared volatile, each variable in the common block is considered volatile. An element of a common block can be declared volatile without affecting the status of the other elements in the common block.

If a common block is declared in multiple scopes, and if it (or one or more of its elements) is declared volatile in one of those scopes, you must specify the VOLATILE attribute in each scope where you require the common block (or one or more of its elements) to be considered volatile.

If a derived type name is declared volatile, all variables declared with that type are considered volatile. When an object of derived type is declared volatile, all of its components are considered volatile. If a component of a derived type is itself derived, the component does not inherit the volatile attribute from its type. A derived type name that is declared volatile must have had the VOLATILE attribute prior to any use of the type name in a type declaration statement.

If a pointer is declared volatile, the storage of the pointer itself is considered volatile. The VOLATILE attribute has no affect on any associated pointer targets.

If you declare an object to be volatile and then use it in an EQUIVALENCE statement, all of the objects that are associated with the volatile object through equivalence association are considered volatile.

Any data object which is shared across threads and is stored and read by multiple threads must be declared as VOLATILE. If, however, your program only uses the automatic or directive-based parallelization facilities of the compiler, variables that have the SHARED attribute need not be declared VOLATILE.

If the actual argument associated with a dummy argument is a variable that is declared volatile, you must declare the dummy argument volatile if you require the dummy argument to be considered volatile. If a dummy argument is declared volatile, and you require the associated actual argument to be considered volatile, you must declare the actual argument as volatile.

Declaring a statement function as volatile has no effect on the statement function.

Within a function subprogram, the function result variable can be declared volatile. Any entry result variables will be considered volatile. An ENTRY name must not be specified with the VOLATILE attribute.
Attributes Compatible with the VOLATILE Attribute

  • ALLOCATABLE
  • AUTOMATIC
  • DIMENSION
  • INTENT

  • OPTIONAL
  • POINTER
  • PRIVATE
  • PUBLIC

  • SAVE
  • STATIC
  • TARGET

Examples

      FUNCTION TEST ()
        REAL ONE, TWO, THREE
        COMMON /BLOCK1/A, B, C
        ...
        VOLATILE /BLOCK1/, ONE, TEST
! Common block elements A, B and C are considered volatile
! since common block BLOCK1 is declared volatile.
        ...
        EQUIVALENCE (ONE, TWO), (TWO, THREE)
! Variables TWO and THREE are volatile as they are equivalenced
! with variable ONE which is declared volatile.
      END FUNCTION

Related Information

Chapter 11. "Directives"

WAIT

Purpose

The WAIT statement may be used to wait for an asynchronous data transfer to complete or it may be used to detect the completion status of an asynchronous data transfer statement.

Format



>>-WAIT--(--wait_list--)---------------------------------------><
 

wait_list
is a list that must contain one ID= specifier and at most one of each of the other valid specifiers. The valid specifiers are:

ID= integer_expr
indicates the data transfer with which this WAIT statement is identified. The integer_expr is a scalar of type INTEGER(4) or default integer. To initiate an asynchronous data transfer, the ID= specifier is used on a READ or WRITE statement.

IOSTAT= ios
is an input/output status specifier that specifies the status of the input/output operation. ios is a scalar variable of type INTEGER(4) or default integer. When the input/output statement containing this specifier finishes execution, ios is defined with:

The ios defined for the IOSTAT= specifier of the asynchronous data transfer statement need not be identical to the ios defined for the IOSTAT= specifier of the matching WAIT statement.

ERR= stmt_label
is an error specifier that specifies the statement label of an executable statement in the same scoping unit to which control is to transfer in the case of an error. Coding the ERR= specifier suppresses error messages.

The stmt_label defined for the ERR= specifier of the asynchronous data transfer statement need not be identical to the stmt_label defined for the ERR= specifier of the matching WAIT statement.

END= stmt_label
is an end-of-file specifier that specifies a statement label at which the program is to continue if an endfile record is encountered and no error occurs. If an external file is positioned after the endfile record, the IOSTAT= specifier, if present, is assigned a negative value, and the NUM= specifier, if present, is assigned an integer value. Coding the END= specifier suppresses the error message for end-of-file. This specifier can be specified for a unit connected for either sequential or direct access.

The stmt_label defined for the END= specifier of the asynchronous data transfer statement need not be identical to the stmt_label defined for the END= specifier of the matching WAIT statement.

DONE= logical_variable
specifies whether or not the asynchronous I/O statement is complete. If the DONE= specifier is present, the logical_variable is set to true if the asynchronous I/O is complete and is set to false if it is not complete. If the returned value is false, then one or more WAIT statements must be executed until either the DONE= specifier is not present, or its returned value is true. A WAIT statement without the DONE= specifier, or a WAIT statement that sets the logical_variable value to true, is the matching WAIT statement to the data transfer statement identified by the same ID= value.

Rules

The matching WAIT statement must be in the same scoping unit as the corresponding asynchronous data transfer statement. Within the instance of that scoping unit, the program must not execute a RETURN, END, or STOP statement before the matching WAIT statement is executed.

Related Information

"Executing Data Transfer Statements Asynchronously"
"AIX Implementation Details of XL Fortran Input/Output" in the User's Guide

WHERE

Purpose

The WHERE statement masks the evaluation of array expressions and array assignment. The WHERE statement can be the initial statement of the WHERE construct.

Format



>>-WHERE--(--mask_expr--)-+-----------------+------------------><
                          +-assignment_stmt-+
 

mask_expr
is a logical array expression

Rules

If assignment_stmt is present, the WHERE statement is not part of a WHERE construct. If assignment_stmt is absent, the WHERE statement is the first statement of the WHERE construct and an END WHERE statement must follow.

The logical array expression determines the mask.

In each assignment_stmt, the mask_expr and the variable being defined must be arrays of the same shape. assignment_stmt must not be a defined assignment.

When an assignment statement in a WHERE statement is executed, the expression of the assignment statement is evaluated for all the elements where mask_expr is true and the result is assigned to the corresponding elements of the variable according to the rules of intrinsic assignment.

If a nonelemental function reference occurs in the expression or variable of an assignment statement, the function is evaluated without any masked control by mask_expr; that is, all of its argument expressions are fully evaluated and the function is fully evaluated. If the result is an array and the reference is not within the argument list of a nonelemental function, elements corresponding to true values in mask_expr are selected for use in evaluating each expression.

If an elemental intrinsic operation or function reference occurs in the expression or variable of an assignment statement and is not within the argument list of a nonelemental function reference, the operation is performed or the function is evaluated only for the elements corresponding to true values in mask_expr.

If an array constructor appears in an assignment statement, the array constructor is evaluated without any masked control by mask_expr and then the assignment statement is evaluated.

If the WHERE statement is not the first statement of a WHERE construct, it can be used as the terminal statement of a DO or DO WHILE construct.

Examples

REAL, DIMENSION(10) :: A,B,C
 
!   In the following WHERE statement, the LOG of an element of A
!   is assigned to the corresponding element of B only if that
!   element of A is a positive value.
 
WHERE (A>0.0) B = LOG(A)
       ·
END

Related Information

WRITE

Purpose

The WRITE statement is a data transfer output statement.

Format



>>-WRITE--(--io_control_list--)-+------------------+-----------><
                                +-output_item_list-+
 

output_item
is an output list item. An output list specifies the data to be transferred. An output list item can be:

io_control
is a list that must contain one unit specifier ( UNIT=), and can also contain one of each of the other valid specifiers:

[UNIT=] u
is a unit specifier that specifies the unit to be used in the output operation. u is an external unit identifier or internal file identifier.

An external unit identifier refers to an external file. It is one of the following:

An internal file identifier refers to an internal file. It is the name of a character variable, which cannot be an array section with a vector subscript.

If the optional characters UNIT= are omitted, u must be the first item in io_control_list. If UNIT= is specified, FMT= must also be specified.

[FMT=] format
is a format specifier that specifies the format to be used in the output operation. format is a format identifier that can be:

If the optional characters FMT= are omitted, format must be the second item in io_control_list, and the first item must be the unit specifier with UNIT= omitted. Both NML= and FMT= cannot be specified in the same output statement.

REC= integer_expr
is a record specifier that specifies the number of the record to be written in a file connected for direct access. The REC= specifier is only permitted for direct output. integer_expr is an integer expression whose value is positive. A record specifier is not valid if formatting is list-directed or if the unit specifier specifies an internal file. The record specifier represents the relative position of a record within a file. The relative position number of the first record is 1.

IOSTAT= ios
is an input/output status specifier that specifies the status of the input/output operation. ios is a scalar variable of type INTEGER(4) or default integer. Coding the IOSTAT= specifier suppresses error messages. When the statement finishes execution, ios is defined with:

ID= integer_variable
indicates that the data transfer is to be done asynchronously. The integer_variable is a scalar of type INTEGER(4) or default integer. If no error is encountered, the integer_variable is defined with a value after executing the asynchronous data transfer statement. This value must be used in the matching WAIT statement.

Asynchronous data transfer must either be direct unformatted or sequential unformatted. Asynchronous I/O to internal files is prohibited. Asynchronous I/O to raw character devices (for example, to tapes or raw logical volumes) is prohibited. The integer_variable must not be associated with any entity in the data transfer I/O list, nor with a do_variable of an io_implied_do in the data transfer I/O list. If the integer_variable is an array element reference, its subscript values must not be affected by the data transfer, the io_implied_do processing, or the definition or evaluation of any other specifier in the io_control_spec.

ERR= stmt_label
is an error specifier that specifies the statement label of an executable statement in the same scoping unit to which control is to transfer in the case of an error. Coding the ERR= specifier suppresses error messages.

NUM= integer_variable
is a number specifier that specifies the number of bytes of data transmitted between the I/O list and the file. integer_variable is a variable name of type INTEGER(4), type INTEGER(8) in 64-bit, or type default integer. The NUM= specifier is only permitted for unformatted output. Coding the NUM parameter suppresses the indication of an error that would occur if the number of bytes represented by the output list is greater than the number of bytes that can be written into the record. In this case, integer_variable is set to a value that is the maximum length record that can be written. Data from remaining output list items is not written into subsequent records. In the portion of the program which executes between the asynchronous data transfer statement and the matching WAIT statement, the integer_variable in the NUM= specifier or any variable associated with it must not be referenced, become defined, or become undefined.

[NML=] name
is a namelist specifier that specifies the name of a namelist list that you have previously defined. If the optional characters NML= are not specified, the namelist name must appear as the second parameter in the list, and the first item must be the unit specifier with UNIT= omitted. If both NML= and UNIT= are specified, all the parameters can appear in any order. The NML= specifier is an alternative to FMT=. Both NML= and FMT= cannot be specified in the same output statement.

ADVANCE=char_expr
is an advance specifier that determines whether nonadvancing output occurs for this statement. char_expr is a character expression that must evaluate to YES or NO. If NO is specified, nonadvancing output occurs. If YES is specified, advancing, formatted sequential output occurs. The default value is YES. ADVANCE= can be specified only in a formatted sequential WRITE statement with an explicit format specification that does not specify an internal file unit specifier.

Implied-DO List



>>-(--do_object_list-- , --------------------------------------->
 
>--do_variable = arith_expr1arith_expr2----------------------->
 
>-+---+--+-------------+---)-----------------------------------><
  +-,-+  +-arith_expr3-+
 

do_object
is an output list item

do_variable
is a named scalar variable of type integer or real

arith_expr1, arith_expr2,  and  arith_expr3
are scalar numeric expressions

The range of an implied- DO list is the list do_object_list. The iteration count and values of the DO variable are established from arith_expr1, arith_expr2, and arith_expr3, the same as for a DO statement. When the implied- DO list is executed, the items in the do_object_list are specified once for each iteration of the implied- DO list, with the appropriate substitution of values for any occurrence of the DO variable.

Rules

If a NUM= specifier is present, neither a format specifier nor a namelist specifier can be present.

Variables specified for the IOSTAT= and NUM= specifiers must not be associated with any output list item, namelist list item, or DO variable of an implied- DO list. If such a specifier variable is an array element, its subscript values must not be affected by the data transfer, any implied- DO processing, or the definition or evaluation of any other specifier.

If the ERR= and IOSTAT= specifiers are set and an error is encountered during a synchronous data transfer, transfer is made to the statement specified by the ERR= specifier and a positive integer value is assigned to ios.

If the ERR= or IOSTAT= specifiers are set and an error is encountered during an asynchronous data transfer, execution of the matching WAIT statement is not required.

If a conversion error is encountered and the CNVERR run-time option is set to NO, ERR= is not branched to, although IOSTAT= may be set.

If IOSTAT= and ERR= are not specified,

PRINT format has the same effect as WRITE(*,format).

Examples

WRITE (6,FMT='(10F8.2)') (LOG(A(I)),I=1,N+9,K),G

Related Information


[ Top of Page | Previous Page | Next Page | Table of Contents | Index ]