Chapter 5. Declarations

Declarations are used to specify the type and other attributes of program entities. The attributes that an entity possesses determine how the entity can be used in a program. Every variable and function has a type, which is the most important of the attributes; type is discussed in Chapter 4, “Data Types”. However, type is only one of a number of attributes that an entity may possess. Some entities, such as subroutines and namelist groups, do not have a type but may possess other attributes. In addition, there are relationships among objects that can be specified by EQUIVALENCE, COMMON, and NAMELIST statements. Declarations are used to specify these attributes and relationships.

Generally, Fortran keywords are used to declare the attributes for an entity. The following list summarizes these keywords:

Attribute 

Keyword

Type 

INTEGER, REAL (and DOUBLE PRECISION), COMPLEX, LOGICAL, CHARACTER, TYPE (user-defined name)

Array properties 

DIMENSION, ALLOCATABLE

Pointer properties 

POINTER, TARGET

Setting values 

DATA, PARAMETER

Object accessibility and use 

PUBLIC, PRIVATE, INTENT, OPTIONAL, SAVE, AUTOMATIC

Procedure properties 

EXTERNAL, INTRINSIC

The attributes are described and illustrated in turn using either of the two forms that attribute specifications can take: entity-oriented and attribute-oriented.

For objects that have a type, other attributes can be included in the type declaration statement. For example:

INTEGER, SAVE :: A, B, C

Collecting the attributes into a single statement is sometimes more convenient for readers of programs. It eliminates searching through many declaration statements to locate all attributes of a particular object. Emphasis can be placed on an object and its attributes (entity-oriented declaration) or on an attribute and the objects that possess the attribute (attribute-oriented declaration), whichever is preferred by a programmer. In both forms, dimensionality can be specified as an attribute or as an attachment to the object name.

The following are examples of entity-oriented declaration statements:

REAL, DIMENSION(20), SAVE :: X

or

REAL, SAVE :: X(20)

The following are examples of attribute-oriented declaration statements:

REAL X
DIMENSION X(20)
SAVE X

or

REAL X(20)
SAVE X

If attributes are not declared for a data object, defaults apply. Generally, if an attribute is not specified for an object, it is assumed that the object does not possess the attribute. However, each data object has a type, and if this is not explicitly specified, it is assumed from the first letter of its name. You can use the IMPLICIT statement to specify any intrinsic or user-defined type for an initial letter or a range of initial letters. The IMPLICIT NONE statement, on the other hand, removes implicit typing and thus requires explicit type declarations for every named data object in the scoping unit.

Fortran provides dynamic data objects that can be sized at the time a program is executed. These include allocatable arrays and objects with the POINTER attribute. They also include automatic data objects (arrays of any type and character strings) that are created on entry into a procedure. Only objects whose size may vary are called automatic.

Other declarations (NAMELIST, EQUIVALENCE, and COMMON) establish relationships among data objects. The NAMELIST statement is used to name a collection of objects so that they can be referenced by a single name in an input/output (I/O) statement. EQUIVALENCE provides references to storage by more than one name. COMMON provides a mechanism to share storage among the different units of a program.

Type Declaration Statements

A type declaration type statement begins with the name of the type, optionally lists other attributes, then ends with a list of variables that possess these attributes. In addition, a type declaration statement may include an initial value for a variable. If the PARAMETER attribute is specified on a type statement, the statement must include the value of the named constant.

The type_declaration_stmt is defined as follows:

 

type_declaration_stmt

is

type_spec[[, attr_spec]... ::]entity_decl_list

 

type_spec

is

INTEGER kind_selector

EXT

 

or

INTEGER* length_value

 

 

or

REAL kind_selector

EXT

 

or

REAL* length_value

 

 

or

DOUBLE PRECISION

EXT

 

or

DOUBLE PRECISION* length_value

 

 

or

COMPLEX kind_selector

EXT

 

or

COMPLEX* length_value

 

 

or

CHARACTER char_selector

 

 

or

LOGICAL kind_selector

EXT

 

or

LOGICAL* length_value

 

 

or

TYPE (type_name)

EXT

 

or

POINTER (pointer_name, pointee_name[ (array_spec) ])

 

 

 

[, (pointer_name, pointee_name[ (array_spec) ])] ...

 

attr_spec

is

PARAMETER

 

 

or

access_spec

 

 

or

ALLOCATABLE

EXT

 

or

AUTOMATIC

 

 

or

DIMENSION ( array_spec)

 

 

or

EXTERNAL

 

 

or

INTENT (intent_spec)

 

 

or

INTRINSIC

 

 

or

OPTIONAL

 

 

or

POINTER

 

 

or

SAVE

 

 

or

TARGET

 

access_spec

is

PUBLIC

 

 

or

PRIVATE

 

entity_decl

is

object_name[(array_spec)][ * char_length][initialization]

 

 

or

function_name[ * char_length]

 

kind_selector

is

([ KIND=]scalar_int_initialization_expr)

 

initialization_expr

is

=intialization_expr

 

 

or

=>NULL()

The double colon symbol (::) is required in a type declaration statement only when the type declaration statement contains two or more attributes or when it contains an initialization_expr.

If => appears in initialization, the object must have the POINTER attribute. If = appears in initialization, the object cannot have the POINTER attribute.

The type specification can override or confirm the implicit type indicated by the first letter of the entity name according to the implicit typing rules in effect.

The same attribute can appear more than once in a given type declaration statement.


Note: The Fortran standard permits an attribute to appear only once in a given type declaration. The CF90 and MIPSpro 7 Fortran 90 compilers relax this restriction.

An entity must not be assigned any attribute more than once in a scoping unit.

The value specified in a kind selector must be a kind type parameter allowed for that type by the CF90 and MIPSpro 7 Fortran 90 compilers.

The character length option can appear only when the type specification is CHARACTER.

An initialization expression must be included if the PARAMETER attribute is specified.

A function name must be the name of an external function, an intrinsic function, a function dummy procedure, or a statement function.

An array function result name must be specified as an explicit-shape array unless it has the POINTER attribute, in which case it must be specified as a deferred-shape array. For information on array properties, see “Array Properties”.

Other rules and restrictions pertain to particular attributes; these are covered in the sections describing those attributes. The attributes that can be used with the attribute being described are also listed. The simple forms that appear in the following sections to illustrate attribute specification in a type declaration statement show the attribute being described first in the attribute list, but attributes can appear in any order. If these simple forms are used to construct statements, the statements will be correct, but other variations are permitted.

The following examples show type declaration statements:

REAL A(10)
LOGICAL, DIMENSION(5,5) :: MASK_1, MASK_2
COMPLEX :: CUBE_ROOT = (-0.5, 0.867)
INTEGER, PARAMETER :: SHORT = SELECTED_INT_KIND(4)
INTEGER(SHORT) :: K           ! Range of -9999 to 9999
REAL, ALLOCATABLE :: A1(:, :), A2(:, :, :)
TYPE(PERSON) CHAIRMAN
TYPE(NODE), POINTER :: HEAD_OF_CHAIN, END_OF_CHAIN
REAL, INTENT(IN) :: ARG1
REAL, INTRINSIC :: SIN
REAL, POINTER, DIMENSION (:) :: S => NULL()

Integer

An INTEGER statement declares the names of entities to be of type integer. If a kind selector is present, it specifies the representation method. For more information on integer type, see “Integer Type” in Chapter 4.

The CF90 and MIPSpro 7 Fortran 90 compilers support the following formats for declaring objects of this type:

INTEGER [([ KIND = ]kind_param) ][[ , attribute_list] :: ]entity_list
INTEGER * length_value[[ , attribute_list] :: ]entity_list

For kind_param values, see “Integer Type” in Chapter 4. The length_value values correspond to the kind_param values and are as follows:

  • On UNICOS and UNICOS/mk systems, the values are as follows: 1, 2, 4, and 8 (default).

  • On IRIX systems, the values are as follows: 1, 2, 4 (default), and 8.

The following are examples of entity-oriented declaration statements:

INTEGER, DIMENSION(:), POINTER :: MILES, HOURS
INTEGER(SHORT), POINTER :: RATE, INDEX

The following are examples of attribute-oriented declaration statements:

INTEGER :: MILES, HOURS
INTEGER(SHORT) :: RATE, INDEX
DIMENSION :: MILES(:), HOURS(:)
POINTER :: MILES, HOURS, RATE, INDEX


Note: The Fortran standard does not specify the INTEGER*length_value syntax. It is recommended that this syntax not be used in any new code.


Real

A REAL statement declares the names of entities to be of type real. If a kind selector is present, it specifies the representation method. For more information on real type, see “Real Type” in Chapter 4.

The CF90 and MIPSpro 7 Fortran 90 compilers support the following formats for declaring objects of this type:

REAL [ ([ KIND = ]kind_param) ][[ , attribute_list] :: ]entity_list
REAL * length_value[[ , attribute_list] :: ]entity_list

For kind_param values, see “Real Type” in Chapter 4. The length_value values correspond to the kind_param values and are as follows:

  • On UNICOS systems, the values are as follows: 4, 8 (default), and 16.

  • On UNICOS/mk systems, the values are as follows: 4 and 8 (default).

  • On IRIX systems, the values are as follows: 4 (default), 8, and 16.

The following examples show entity-oriented declaration statements:

REAL(KIND = HIGH), OPTIONAL :: VARIANCE
REAL, SAVE :: A1(10, 10), A2(100, 10, 10)

The following examples show attribute-oriented declaration statements:

REAL(KIND = HIGH) VARIANCE
REAL A1(10, 10), A2(100, 10, 10)
OPTIONAL VARIANCE
SAVE A1, A2


Note: The Fortran standard does not specify the REAL*length_value syntax. It is recommended that this syntax not be used in any new code.


Double Precision

A DOUBLE PRECISION statement declares the names of entities to be of real type with a representation method that represents more precision than the default real representation. The DOUBLE PRECISION statement is outmoded because REAL with the appropriate kind parameter value is equivalent. A kind selector is not permitted in the DOUBLE PRECISION statement. For more information on the real data type, see “Real Type” in Chapter 4.

The CF90 and MIPSpro 7 Fortran 90 compilers support the following formats for declaring objects of this type:

DOUBLE PRECISION [[ , attribute_list] :: ]entity_list
DOUBLE PRECISION * 16 [[, attribute_list] :: ]entity_list

The following examples show entity-oriented declaration statements:

DOUBLE PRECISION, DIMENSION(N,N) :: MATRIX_A, MATRIX_B
DOUBLE PRECISION, POINTER :: C, D, E, F(:, :)

The following examples show attribute-oriented declaration statements:

DOUBLE PRECISION :: MATRIX_A, MATRIX_B, C, D, E, F
DIMENSION :: MATRIX_A(N, N), MATRIX_B(N, N), F(:, :)
POINTER :: C, D, E, F

If DOUBLE is a named integer constant that has the value of the kind parameter of the double-precision real type on the target platform, the preceding entity-oriented declaration statements could be written as follows:

REAL (DOUBLE), DIMENSION (N,N) :: MATRIX_A, MATRIX_B
REAL (DOUBLE), POINTER :: C, D, E, F(:,:)


Note: The Fortran standard does not specify the DOUBLE PRECISION*16 syntax. It is recommended that this syntax not be used in any new code.


Complex

A COMPLEX statement declares the names of entities to be of type complex. If a kind selector is present, it specifies the representation method. For more information on complex type, see “Complex Type” in Chapter 4.

The CF90 and MIPSpro 7 Fortran 90 compilers support the following formats for declaring objects of this type:

COMPLEX [([ KIND = ]kind_param)][[ , attribute_list] :: ]entity_list
COMPLEX * length_value[[, attribute_list] :: ]entity_list

For kind_param values, see “Complex Type” in Chapter 4. The length_value values correspond to the kind_param values in the following manner:

  • On UNICOS systems, the values are as follows:

    kind_param 

    length_value

    4 

    8

    8 (default) 

    16 (default)

    16 

    32

  • On UNICOS/mk systems, the values are as follows:

    kind_param 

    length_value

    4 

    8

    8 (default) 

    16 (default)

  • On IRIX systems, the values are as follows:

    kind_param 

    length_value

    4 (default) 

    8 (default)

    8 

    16

    16 

    32

The following examples show entity-oriented declaration statements:

COMPLEX(KIND = LOW), POINTER :: ROOTS(:)
COMPLEX, POINTER :: DISCRIMINANT, COEFFICIENTS(:)

The following examples show attribute-oriented declaration statements:

COMPLEX(KIND = LOW) :: ROOTS(:)
COMPLEX :: DISCRIMINANT, COEFFICIENTS(:)
POINTER :: ROOTS, DISCRIMINANT, COEFFICIENTS


Note: The Fortran standard does not specify the COMPLEX*length_value syntax. It is recommended that this syntax not be used in any new code.


Logical

A LOGICAL statement declares the names of entities to be of type logical. If a kind selector is present, it specifies the representation method. For more information on logical type, see “Logical Type” in Chapter 4.

The CF90 and MIPSpro 7 Fortran 90 compilers support the following formats for declaring objects of this type:

LOGICAL [ ([ KIND = ]kind_param)][[, attribute_list] :: ]entity_list
LOGICAL * length_value[[, attribute_list] :: ]entity_list

For kind_param values, see “Logical Type” in Chapter 4. The length_value values correspond to the kind_param values in the following manner:

  • On UNICOS systems and UNICOS/mk systems, the values are as follows:

    kind_param 

    length_value

    1 

    1

    2 

    2

    4 

    4

    8 (default) 

    8 (default)

  • On IRIX systems, the values are as follows:

    kind_param 

    length_value

    1 

    1

    2 

    2

    4 (default) 

    4 (default)

    8 

    8

     

The following examples show entity-oriented declaration statements:

LOGICAL, ALLOCATABLE :: MASK_1(:), MASK_2(:)
LOGICAL(KIND = WORD), SAVE :: INDICATOR, STATUS

The following examples show attribute-oriented declaration statements:

LOGICAL MASK_1(:), MASK_2(:)
LOGICAL (KIND = WORD) INDICATOR, STATUS
ALLOCATABLE MASK_1, MASK_2
SAVE INDICATOR, STATUS


Note: The Fortran standard does not specify the LOGICAL*length_value syntax. It is recommended that this syntax not be used in any new code.


Character

A CHARACTER statement declares the names of entities to be of type character. For more information on character type, see “Character Type” in Chapter 4.

The following is a format for declaring objects of this type:

CHARACTER [char_selector][[ , attribute_list] :: ]entity_list

The components of this format are defined as follows:

 

char_selector

is

length_selector

 

 

or

(LEN = type_param_value, KIND = kind_value)

 

 

or

(type_param_value, [ KIND = ]kind_value)

 

 

or

(KIND = kind_value[, LEN = type_param_value])

 

length_selector

is

([ LEN = ]type_param_value)

OBS

 

or

* char_length[ , ]

 

char_length

is

(type_param_value)

 

 

or

scalar_int_literal_constant

 

type_param_value

is

specification_expr

 

 

or

*

The optional comma in a length_selector is permitted only if no double colon separator appears in the type declaration statement.

A character type declaration can specify a character length that is a nonconstant expression if it appears in a procedure or a procedure interface if it is not a component declaration in a derived-type definition. The length is determined on entry into the procedure and is not affected by any changes in the values of variables in the expression during the execution of the procedure. A character object declared this way that is not a dummy argument is called an automatic data object.

The length of a named character entity or a character component in a type definition is specified by the character selector in the type specification unless there is a character length in an entity or component declaration; if so, the character length specifies an individual length and overrides the length in the character selector. If a length is not specified in either a character selector or a character length, the length is 1.

If the length parameter has a negative value, the length of the character entity is 0.

If a scalar integer literal constant is used to specify a character length, it must not include a kind parameter. (This could produce an ambiguity when fixed source form is used.)

A length parameter value of * can be used only in the following ways:

  • To declare a dummy argument of a procedure, in which case the dummy argument assumes the length of the associated actual argument when the procedure is invoked.

  • To declare a named constant, in which case the length is that of the constant value.

  • To declare the result variable for an external function. Any scoping unit that invokes the function must declare the function with a length other than *, or it must access such a declaration by host or use association. When the function is invoked, the length of the result is the value specified in the declaration in the program unit referencing the function. Note that an implication of this rule is that a length of * must not appear in an IMPLICIT statement.

  • To declare a character pointee.

A function name must not be declared with a length of * if the function is an internal or module function; or if it is array-valued, pointer-valued, or recursive; or if it is a PURE function.

An interface body can be specified for a dummy or external function whose result is of type CHAR*(*) only if the function is not invoked. This is because the characteristics must match in both places.

The length of a character-valued statement function or statement function dummy argument of type character must be an integer constant expression.

The following examples show entity-oriented character type declaration statements:

CHARACTER(LEN = 10, KIND = ASCII), SAVE :: GREETING(2)
CHARACTER(10) :: PROMPT = "PASSWORD?"
CHARACTER(*), INTENT(IN) :: HOME_TEAM, VISITORS
CHARACTER*(3), SAVE :: NORMAL_1, LONGER(9)*20, NORMAL_2
CHARACTER :: GRADE = "A"

The following examples show attribute-oriented character type declaration statements:

CHARACTER(LEN = 10, KIND = ASCII) :: GREETING
CHARACTER(10) :: PROMPT
CHARACTER(*) :: HOME_TEAM, VISITORS
CHARACTER*(3) :: NORMAL_1, LONGER*20, NORMAL_2
CHARACTER GRADE
SAVE :: GREETING, NORMAL_1, LONGER, NORMAL_2
DIMENSION GREETING(2), LONGER(9)
INTENT(IN) :: HOME_TEAM, VISITORS
DATA PROMPT / "PASSWORD?" /, GRADE / "A" /

Derived Type

A TYPE declaration statement declares the names of entities to be of the specified user-defined type. The type name appears in parentheses following the keyword TYPE. For more information on derived types, see “Derived Types” in Chapter 4.

The following is a format for declaring objects of user-defined type:

TYPE (type_name) [[ , attribute_list] :: ]entity_list

The following examples show entity-oriented derived type declaration statements:

TYPE(COLOR), DIMENSION(:), ALLOCATABLE :: HUES_OF_RED
TYPE(PERSON), SAVE :: CAR_POOL(3)
TYPE(PARAGRAPH), SAVE :: OVERVIEW, SUBSTANCE, SUMMARY

The following examples show attribute-oriented derived type declaration statements:

TYPE(COLOR) :: HUES_OF_RED
TYPE(PERSON) :: CAR_POOL(3)
TYPE(PARAGRAPH) :: OVERVIEW, SUBSTANCE, SUMMARY
DIMENSION :: HUES_OF_RED(:)
ALLOCATABLE :: HUES_OF_RED
SAVE :: CAR_POOL, OVERVIEW, SUBSTANCE, SUMMARY

An object of derived type (a structure) must not have the PUBLIC attribute if its type is private.

A structure constructor must be used to initialize an object of derived type. Each component of the structure constructor must be an initialization expression. For more information on structure constructors, see “Structure Constructors” in Chapter 4.


Note: : Variables declared to be Cray pointers and pointees through the Cray POINTER statement cannot be declared as components of derived types.


Cray Pointer (EXTENSION)

The Cray POINTER statement declares one variable to be a Cray pointer (that is, to have the Cray pointer data type) and another variable to be its pointee; that is, the value of the Cray pointer is the address of the pointee. This statement has the following format:

POINTER (pointer_name, pointee_name[ (array_spec) ])
[, (pointer_name, pointee_name [ (array_spec) ])] ...
pointer_name 

Pointer to the corresponding pointee_name. pointer_name contains the address of pointee_name. Only a scalar variable can be declared type Cray pointer; constants, arrays, statement functions, and external functions cannot.

pointee_name 

Pointee of corresponding pointer_name. Must be a variable name, array declarator, or array name. The value of pointer_name is used as the address for any reference to pointee_name; therefore, pointee_name is not assigned storage. If pointee_name is an array declarator, it can be explicit-shape (with either constant or nonconstant bounds) or assumed-size.

array_spec 

If present, this must be either an explicit_shape_spec_list, with either constant or nonconstant bounds) or an assumed_size_spec.

Example:

POINTER(P,B),(Q,C)

This statement declares Cray pointer P and its pointee B, and Cray pointer Q and pointee C; the pointer's current value is used as the address of the pointee whenever the pointee is referenced.

An array that is named as a pointee in a Cray POINTER statement is a pointee array. Its array declarator can appear in a separate type or DIMENSION statement or in the pointer list itself. In a subprogram, the dimension declarator can contain references to variables in a common block or to dummy arguments. As with nonconstant bound array arguments to subprograms, the size of each dimension is evaluated on entrance to the subprogram, not when the pointee is referenced. For example:

POINTER(IX, X(N,0:M))


Note: The Fortran standard does not specify the Cray POINTER statement or data type. Variables declared to be pointers and pointees through the Cray POINTER statement cannot be declared as components of derived types.

In addition, pointees must not be deferred-shape or assumed-shape arrays. An assumed-size pointee array is not allowed in a main program unit.

Cray Character Pointer (EXTENSION) (Implementation Deferred on IRIX Systems)

To define a character pointer, use the CLOC(3i) intrinsic function. (The LOC(3i) intrinsic function returns only the word address.)

The FCD(3i) function can also be used to construct a Cray character pointer. FCD(3i) has two integer arguments:

  • On UNICOS and UNICOS/mk systems, the first argument is the word address for the first character of the pointee.

  • On all systems, the second argument is the character length of the pointee.

On UNICOS and UNICOS/mk systems, if the pointee does not begin on a word boundary, the character offset can be added to the FCD(3i) result.


Note: : Intrinsic functions CLOC(3i) and FCD(3i) are not part of the Fortran standard.

The size of a Fortran Character Descriptor (FCD) and of a Cray character pointer depends on your platform, so Cray character pointers should not be equivalenced or storage-associated. For more information on FCDs, see FCD(3i).

Example:

CPTR = FCD(IADRS,ILEN) + IOFFSET

On UNICOS and UNICOS/mk systems, Cray character pointers are not optimized. Statements containing them are not vectorized or Autotasked.

The following operations are the only ones allowed with Cray character pointers, where cp is a character pointer and i is an integer. Arithmetic is in bytes (characters), not words or bits:

  • cp + i

  • cp - i

  • i + cp

  • cp = cp

  • cp relational_operator cp

Implicit Typing

Each variable, named constant, and function has a type and a name. If the type is not declared explicitly, it is assumed from the first letter of the name. This method of determining type is called implicit typing. In each scoping unit, there is in effect a mapping of each of the letters A, B, ..., Z (and corresponding lowercase letters) to one of the accessible types or to no type. IMPLICIT statements in a scoping unit can be used to specify a mapping different from the default mapping. If a new mapping for a letter is not specified in an IMPLICIT statement, the default mapping continues to apply for that letter.

An IMPLICIT NONE statement specifies that there is no mapping for any letter and thus all variables, named constants, and functions must be declared in type declaration statements. If the host of a scoping unit contains the IMPLICIT NONE statement and the scoping unit contains IMPLICIT statements for some letters, the other letters retain the null mapping. This is the only situation in which some initial letters specify an implied type and other initial letters require explicit declarations.

A program unit is treated as if it had a host with the mapping shown in Figure 5-1. That is, each undeclared variable or function whose name begins with any of the letters I, J, K, L, M, or N is of type integer and all others are of type real.

Figure 5-1. Default implicit mapping for a program unit

Default implicit mapping for a program unit

The IMPLICIT statement is defined as follows:

 

implicit_stmt

is

IMPLICIT implicit_spec_list

 

 

or

IMPLICIT NONE

EXT

 

or

IMPLICIT UNDEFINED

 

implicit_spec

is

type_spec (letter_spec_list)

 

letter_spec

is

letter[- letter]

If IMPLICIT NONE appears, it must precede any PARAMETER statements and there must be no other IMPLICIT statements in the scoping unit.

If the - letter option appears in a letter specification, the second letter must follow the first alphabetically.

The same letter must not appear as a single letter or be included in a range of letters more than once in all of the IMPLICIT statements in a scoping unit.


Note: The Fortran standard does not include the IMPLICIT UNDEFINED syntax. IMPLICIT UNDEFINED is equivalent to IMPLICIT NONE, but it is recommended that the IMPLICIT UNDEFINED syntax not be used in new code.

An IMPLICIT statement can be used to specify implicit mappings for user-defined types as well as for intrinsic types.

The IMPLICIT statement specifies that all variables, named constants, and functions beginning with the indicated letters are assigned the indicated data type (and type parameters) implicitly. For example, consider the following statement:

IMPLICIT COMPLEX (A-C, Z)

In this statement, all undeclared variables, named constants, and functions beginning with the letters A, B, C, and Z are of type default complex. If this is the only IMPLICIT statement, undeclared variables, named constants, and functions beginning with I through N will still be of type integer; undeclared variables, named constants, and functions beginning with D through H and O through Y will be of type real.

As another example, consider the following statement:

IMPLICIT NONE

In this statement, there is no implicit typing in the scoping unit. Each variable and named constant local to the scoping unit, and each external function used in the scoping unit, must be declared explicitly in a type statement. This statement is useful for detecting inadvertent misspellings in a program because misspelled names become undeclared rather than implicitly declared.

The following examples show IMPLICIT statements:

IMPLICIT INTEGER (A-G), LOGICAL(KIND = WORD) (M)
IMPLICIT CHARACTER*(10) (P, Q)
IMPLICIT TYPE(COLOR) (X-Z)

The additional complexity that implicit typing causes in determining the scope of an undeclared variable in a nested scope is explained in the Fortran Language Reference Manual, Volume 2.

Array Properties

An array object has the DIMENSION attribute. An array specification determines the array's rank, or number of dimensions. The extents of the dimensions may be declared or left unspecified. If they are left unspecified, the array must also have the ALLOCATABLE or POINTER attribute, or it must be a dummy argument.

Array Specifications

There are four formats that an array_spec can take:

 

array_spec

is

explicit_shape_spec_list

 

 

or

assumed_shape_spec_list

 

 

or

deferred_shape_spec_list

 

 

or

assumed_size_spec

The maximum rank of an array is 7. A scalar is considered to have rank 0.

An array with a deferred_shape_spec_list must have the POINTER or ALLOCATABLE attribute.

An array with an assumed_shape_spec_list or an assumed_size_spec must be a dummy argument.

Explicit-shape Arrays

An explicit-shape array has bounds specified in each dimension. Each dimension is specified by an explicit_shape_spec, which is defined as follows:

 

explicit_shape_spec

is

lower_bound : upper_bound

 

lower_bound

is

specification_expr

 

upper_bound

is

specification_expr

For more information on specification_exprs, see “Specification Expressions” in Chapter 7.

The number of sets of bounds specified is the number of dimensions (rank) of the array.

If the lower bound is omitted, the default value is 1.

The value of a lower bound or an upper bound can be positive, negative, or 0.

The subscript range of the array in a dimension is the set of integer values between and including the lower and upper bounds, provided the upper bound is not less than the lower bound. If the upper bound is less than the lower bound, the range is empty, the extent in that dimension is 0, and the size of the array is 0.

The expression for a bound could involve variables that cause the expression to have different values each time the procedure in which it is declared is executed. If so, the array must be a dummy argument, a function result, or an automatic array, in which case the actual bounds are determined when the procedure is entered. The bounds of such an array are unaffected by any redefinition or undefinition of the specification variables during the execution of the procedure.

The following are examples of entity-oriented explicit-shape array declarations:

REAL Q(-10:10, -10:10, 2)  ! in a main program

SUBROUTINE EX1(Z, I, J)             ! in a
  REAL, DIMENSION(2:I + 1, J) :: Z  ! subroutine

The following are examples of attribute-oriented explicit-shape array declarations:

REAL Q
DIMENSION Q(-10:10, -10:10, 2)  ! in a main program

SUBROUTINE EX1(Z, I, J)    ! in
   REAL Z                  ! a
   DIMENSION Z(2:I + 1, J) ! subroutine

Assumed-shape Arrays

An assumed-shape array is a dummy argument that takes the shape of the actual argument passed to it. An assumed_shape_spec has the following format:

 

assumed_shape_spec

is

[lower_bound] :

The lower_bound of the assumed-shape array is the specified lower bound, if present; otherwise it is 1.

The rank is equal to the number of colons in the assumed_shape_spec_list.

The upper bound is the extent of the corresponding dimension of the associated array plus the lower bound minus 1.

An assumed-shape array must not have the POINTER or ALLOCATABLE attribute.

The following example shows an entity-oriented, assumed-shape array declaration:

REAL, DIMENSION(2:, :) :: X

The following example shows an attribute-oriented, assume-shaped array declaration:

SUBROUTINE EX2(A, B, X)
   REAL A(:), B(0:), X
   DIMENSION X(2:, :)
   INTENT(IN) A, B
      . . .  

As another example, assume that EX2 is called by the following statement:

CALL EX2(U, V, W(4:9, 2:6))

Dummy argument X is an array with bounds (2:7, 1:5). The lower bound of the first dimension is 2 because X is declared to have a lower bound of 2. The upper bound is 7 because the dummy argument takes its shape from the actual argument W.

Deferred-shape Arrays

A deferred-shape array is either an array pointer or an allocatable array. An array pointer is an array that has the POINTER attribute. Its extent in each dimension is determined when the pointer is allocated or when a pointer assignment statement for the pointer is executed. An allocatable array is an array that has the ALLOCATABLE attribute. Its bounds, and thus its shape, are determined when the array is allocated. In both cases a colon specifies the declared bound; that is, the format of a deferred_shape_spec is defined as follows:

 

deferred_shape_spec

is

:

The rank is equal to the number of colons in the deferred_shape_spec_list.

The bounds of an allocatable array are specified in an ALLOCATE statement when the array is allocated.

The lower bound of each dimension of an array pointer is the result of the LBOUND(3i) intrinsic function applied to the corresponding dimension of the target. The upper bound of each dimension is the result of the UBOUND(3i) intrinsic function applied to the corresponding dimension of the target. This means that if the bounds are determined by allocation of the pointer, you can specify them. If the bounds are determined by pointer assignment, there are two possible interpretations:

  • If the pointer target is a named whole array, the bounds are those declared in the array declaration or those specified when the array was allocated.

  • If the pointer target is an array section, the lower bound is 1 and the upper bound is the extent in that dimension.

The bounds and shape of an array pointer or allocatable array are unaffected by any subsequent redefinition or undefinition of variables involved in determination of the bounds.

The following examples show entity-oriented, deferred-shape array declarations:

REAL, POINTER :: D(:, :), P(:) ! array pointers
REAL, ALLOCATABLE :: E(:)      ! allocatable array

The following examples show attribute-oriented, deferred-shaped array declarations:

REAL D
DIMENSION D(:, :), P(:), E(:)
POINTER D, P
ALLOCATABLE E

Assumed-size Arrays

An assumed-size array is a dummy argument array whose size is assumed from that of the associated actual argument. Only the size is assumed. The rank, extents, and bounds (except for the upper bound and extent in the last dimension) are determined by the declaration of the dummy array. The rules for argument association between an actual argument and an assumed-size array are as follows:

  • They must have the same initial array element.

  • Successive array elements are storage associated. For information on storage association, see “Storage Association”.

  • Declarations for the dummy argument determine the rank. They also determine lower bounds for all dimensions and the extents and upper bounds for all dimensions except the last.

  • The size of the actual argument determines the size of the dummy argument as explained in this section.

The format of an assumed_size_spec is defined as follows:

 

assumed_size_spec

is

[explicit_shape_spec_list, ][lower_bound : ] *

The rank of an assumed-size array is the number of explicit-shape specifications plus one.

The size of an assumed-size array is determined as follows:

  • If the actual argument associated with the assumed-size dummy argument is an array of any type other than character, the size is that of the actual array.

  • If the actual argument associated with the assumed-size dummy array is an array element of any type other than character with a subscript order value of v in an array of size x, the size of the dummy argument is x - v +1. For information on array element order, see “Array Element Order” in Chapter 6.

  • If the actual argument is a character array, character array element, or a character array element substring, and if it begins at character storage unit t of an array with c character storage units, the size of the dummy array is MAX(INT(( c - t +1)/ e ), 0) where e is the length of an element in the dummy character array.

If r is the rank of the array, the bounds of the first r-1 dimensions are those specified by the explicit-shape specification list, if present. The lower bound of the last dimension is the specified lower bound, if present; otherwise it is 1.

The expression for a bound may involve variables that cause the expression to have different values each time the procedure in which it is declared is executed. If so, the bounds are unaffected by any subsequent redefinition or undefinition of such variables involved in the determination of the bounds.

A function result must not be an assumed-size array.

An assumed-size array must not appear in a context where the shape of the array is required, such as a whole array reference.

The following examples show entity-oriented, assumed-size array declarations:

SUBROUTINE EX3(N, S, Y)
   REAL, DIMENSION(N, *) :: S
   REAL Y(10, 5, *)
      . . .  

The following examples show attribute-oriented, assumed size array declarations:

SUBROUTINE EX3(N, S, Y)
   REAL S, Y
   DIMENSION S(N, *), Y(10, 5, *)
      . . .  

DIMENSION Attribute and Statement

The dimensions of an array can be specified by the appearance of a DIMENSION attribute or by the appearance of an array specification following the name of the array in a type declaration statement. Both a DIMENSION attribute and an array specification following the name can appear in a declaration statement. In this case, the array specification following the name overrides the array specification following the DIMENSION attribute. A format for a type declaration statement with a DIMENSION attribute is as follows:

type, DIMENSION (array_spec) [, attribute_list] :: entity_decl_list

Subject to the rules governing combinations of these attributes, attribute_list can contain the following:

ALLOCATABLE
AUTOMATIC (EXTENSION)
INTENT
OPTIONAL
POINTER
PARAMETER
PRIVATE
PUBLIC
SAVE
TARGET
VOLATILE (EXTENSION)

The type declaration can also contain an initialization_expr. An array specification can also appear following a name in several different kinds of statements to declare an array. They are DIMENSION, ALLOCATABLE, POINTER, TARGET, and COMMON statements.

The DIMENSION statement is the statement form of the DIMENSION attribute and is defined as follows:

 

dimension_stmt

is

DIMENSION [ :: ]array_name (array_spec)
[, array_name (array_spec) ] ...

The DIMENSION statement also confers the DIMENSION attribute. It is subject to the same rules and restrictions as the DIMENSION attribute.

The following examples show entity-oriented declarations:

INTEGER, DIMENSION(10), TARGET, SAVE :: INDICES
INTEGER, ALLOCATABLE, TARGET :: LG(:, :, :)

The following examples show attribute-oriented declarations:

INTEGER INDICES, LG(:, :, :)
DIMENSION INDICES(10)
TARGET INDICES, LG
ALLOCATABLE LG
SAVE INDICES

The following examples show the array specification in other statements:

INTEGER INDICES, LG
TARGET INDICES(10), LG
ALLOCATABLE LG(:, :, :)
SAVE INDICES

The following example shows the array specification in a COMMON statement:

COMMON /UNIVERSAL/ TIME(80), SPACE(20, 20, 20, 20)

ALLOCATABLE Attribute and Statement

Arrays are the only objects that can have the ALLOCATABLE attribute. An allocatable array is one for which the bounds are determined when an ALLOCATE statement is executed for the array. These arrays must be deferred-shape arrays. The following is a format for a type declaration statement with an ALLOCATABLE attribute:

type, ALLOCATABLE [, attribute_list] :: entity_decl_list

Subject to the rules governing combinations of these attributes, attribute_list can contain the following:

DIMENSION (with deferred shape)
PRIVATE
PUBLIC
SAVE
TARGET
VOLATILE (EXTENSION)

The format of the ALLOCATABLE statement is defined as follows:

 

allocatable_stmt

is

ALLOCATABLE [::]array_name[ (deferred_shape_spec_list)]
[ ,array_name[ (deferred_shape_spec_list) ]] ...

The array must not be a dummy argument or function result.

If the array is given the DIMENSION attribute elsewhere, the bounds must be specified as colons (deferred shape).

The ALLOCATABLE statement also confers the ALLOCATABLE attribute. It is subject to the same rules and restrictions as the ALLOCATABLE attribute.

The following examples show entity-oriented declarations:

REAL, ALLOCATABLE :: A(:, :)
LOGICAL, ALLOCATABLE, DIMENSION(:) :: MASK1

The following examples show attribute-oriented declarations:

REAL A(:, :)
LOGICAL MASK1
DIMENSION MASK1(:)
ALLOCATABLE A, MASK1

POINTER Properties

Most attributes, when applied to an object, add characteristics that the object would not have otherwise. The POINTER attribute, in some sense, removes a characteristic that an object has. Ordinarily, an object has storage space set aside. If the object has the POINTER attribute, it has no space initially and must not be referenced until space is associated with it. An ALLOCATE statement creates new space for a pointer object. A pointer assignment statement permits the pointer to borrow the space from another object. The space that becomes associated with a pointer is called the pointer's target. The target can change during the execution of a program. A pointer target is either an object or part of an object declared to have the TARGET attribute; or it is an object or part of an object that was created by the allocation of a pointer. A pointer can be assigned the target (or part of the target) of another pointer.

Another way of thinking about a pointer is as a descriptor that contains information about the type, type parameters, rank, extents, and location of the pointer's target. Thus, a pointer to a scalar object of type real is different from a pointer to an array of user-defined type.

POINTER Attribute and Statement

The following is a format for a type declaration statement with a POINTER attribute:

type, POINTER [, attribute_list] :: entity_decl_list

Subject to the rules governing combinations of these attributes, attribute_list can contain the following:

AUTOMATIC (EXTENSION)
DIMENSION (with deferred shape)
OPTIONAL
PRIVATE
PUBLIC
SAVE
VOLATILE (EXTENSION)

The POINTER statement also provides a means for declaring pointers. Its format is defined as follows:

 

pointer_stmt

is

POINTER [ :: ]object_name[ (deferred_shape_spec_list) ]
[ , object_name[ (deferred_shape_spec_list) ]] ...

The target of a pointer can be a scalar or an array.

An array pointer must be declared as a deferred-shape array.

A pointer must not be referenced or defined unless it is associated with a target that can be referenced or defined. (A pointer on the right-hand side of a pointer assignment is not considered a pointer reference.)

The POINTER statement also confers the POINTER attribute. It is subject to the same rules and restrictions as the POINTER attribute.

The following example shows an entity-oriented declaration:

TYPE(NODE), POINTER :: CURRENT
REAL, POINTER :: X(:, :), Y(:)

The following example shows an attribute-oriented declaration:

TYPE(NODE) CURRENT
REAL X(:, :), Y(:)
POINTER CURRENT, X, Y

TARGET Attribute and Statement

Only an object with the TARGET attribute can become the target of a pointer during execution of a program. If an object does not have the TARGET attribute or has not been allocated, no part of it can be accessed through a pointer. The following is a format for a type declaration statement with a TARGET attribute:

type, TARGET [, attribute_list] :: entity_list

Subject to the rules governing combinations of these attributes, attribute_list can contain the following:

ALLOCATABLE
AUTOMATIC (EXTENSION)
DIMENSION
INTENT
OPTIONAL
PRIVATE
PUBLIC
SAVE
VOLATILE (EXTENSION)

The type declaration statement can also contain an initialization_expr.

The TARGET statement also provides a means for specifying pointer targets. It has the following format:

 

target_stmt

is

TARGET [ :: ]object_name[ (array_spec) ]
[, object_name[ (array_spec) ]] ...

The TARGET statement also confers the TARGET attribute. It is subject to the same rules and restrictions as the TARGET attribute.

The following examples show entity-oriented declarations:

TYPE(NODE), TARGET :: HEAD_OF_LIST
REAL, TARGET, DIMENSION(100, 100) :: V, W(100)

The following examples show attribute-oriented declarations:

TYPE(NODE) HEAD_OF_LIST
REAL V, W(100)
DIMENSION V(100, 100)
TARGET HEAD_OF_LIST, V, W

AUTOMATIC Attribute and Statement (EXTENSION)

The AUTOMATIC attribute specifies stack-based storage for a variable or array. Such variables and arrays are undefined upon entering and exiting the procedure. The following is the format for the AUTOMATIC specification:

type, AUTOMATIC [ , attribute_list] :: entity_list
attribute_list

For attribute_list, specify a variable name or an array declarator. If an attribute_list item is an array, it must be declared with an explicit_shape_spec with constant bounds. If an attribute_list item is a pointer, it must be declared with a deferred_shape_spec.

If an attribute_list item has the same name as the function in which it is declared, the attribute_list item must be scalar and of type integer, real, logical, complex, or double precision.

If the attribute_list item is a pointer, the AUTOMATIC attribute applies to the pointer itself and not to any target that may become associated with the pointer.

Subject to the rules governing combinations of attributes, attribute_list can contain the following:

DIMENSION
TARGET
POINTER
VOLATILE (EXTENSION)

The following entities cannot have the AUTOMATIC attribute:

  • Pointers or arrays used as function results

  • Dummy arguments

  • Statement functions

  • Automatic array or character data objects

An attribute_list item cannot have the following characteristics:

  • It cannot be defined in the scoping unit of a module.

  • It cannot be a common block item.

  • It cannot be specified more than once within the same scoping unit.

  • It cannot be initialized with a DATA statement or with a type declaration statement.

  • It cannot also have the SAVE attribute.

  • It cannot be specified as a Cray pointee.

  • It cannot be specified on an object that appears in an AUXILIARY or SYMMETRIC compiler directive.


Note: The Fortran standard does not specify the AUTOMATIC attribute or statement, nor does it provide a means to explicitly declare automatic variables as automatic. The Fortran standard does not specify compiler directives.


Data Initialization and the DATA Statement

An entity can be initialized in a type declaration statement. When an initialization expression appears in a declaration for an object that does not have the PARAMETER attribute, the object (which is a variable) is assigned the specified initial value. This object is a variable with explicit initialization. Alternatively, explicit initialization can be specified in a DATA statement unless the variable is of a derived type for which default initialization has been specified.


Note: The Fortran standard has declared that the placement of DATA statements amongst executable statements is obsolescent.


The same rules apply to the assignment of the initial value as apply when an assignment statement is executed. For example, if the variable is of type real but the value is an integer value, the variable will be assigned the real equivalent of the integer value. If the kind of the variable is different from the kind of the value, the value will be converted to the kind of the variable. Array constructors and broadcast values can be used to initialize arrays, and structure constructors can be used to initialize variables of user-defined type. The format of a type declaration statement that provides an initial value for a variable is as follows:

type[, attribute_list] :: object_name[ (array_spec) ]
[ * char_length] = initialization_expr

Subject to the rules governing combinations of these attributes, attribute_list can contain the following:

DIMENSION
POINTER
PRIVATE
PUBLIC
SAVE
TARGET
VOLATILE (EXTENSION)

For example:

INTEGER :: I = 0

The PARAMETER attribute can also appear in the attribute_list, but in this case, the object is declared to be a named constant.

The value associated with the name cannot be changed during the execution of the program. For example, PI or E can be associated with the familiar mathematical constants to provide more convenient access to these values. Named constants are also used to assign names to values (such as a sales tax rate) that could change at some later time. When a change is necessary, it can be made at one place in the program rather than every place where the value is used. The program can be recompiled to effect the change.

An array name that appears in a declaration statement that contains an initialization_expr must have its dimensionality declared in the same statement or a previous statement.

Initialization of a variable in a type declaration statement or any part of a variable in a DATA statement implies that the variable has the SAVE attribute unless the variable is in a named common block. The automatically acquired SAVE attribute may be reaffirmed by the appearance of SAVE as an attribute in its type declaration statement or by inclusion of the variable name in a separate SAVE statement.

The DATA statement is defined as follows:

 

data_stmt

is

DATAdata_stmt_set[[, ]data_stmt_set]...

 

data_stmt_set

is

data_stmt_object_list / data_stmt_value_list / [[, ]data_stmt_object_list / data_stmt_value_list / ] ...

 

data_stmt_object

is

variable

 

 

or

data_implied_do

 

data_stmt_value

is

[data_stmt_repeat * ]data_stmt_constant

 

data_stmt_constant

is

scalar_constant

 

 

or

scalar_constant_subobject

 

 

or

signed_int_literal_constant

 

 

or

signed_real_literal_constant

 

 

or

structure_constructor

 

 

or

boz_literal_constant

 

 

or

NULL()

EXT

 

or

typeless_constant

 

data_stmt_repeat

is

scalar_int_constant

 

 

or

scalar_int_constant_subobject

 

data_implied_do

is

(data_i_do_object_list, data_i_do_variable= scalar_int_expr, scalar_int_expr[, scalar_int_expr])

 

data_i_do_object

is

array_element

 

 

or

scalar_structure_component

 

 

or

data_implied_do

 

data_i_do_variable

is

scalar_int_variable

EXT

typeless_constant

is

octal_typeless_constant

 

 

or

hexadecimal_typeless_constant

 

 

or

binary_typeless_constant

EXT

octal_typeless_constant

is

digit[digit... ]B

 

 

or

O"digit[digit... ]"

 

 

or

O'digit[digit... ]'

 

 

or

"digit[digit... ]"O

 

 

or

'digit[digit... ]'O

EXT

hexadecimal_typeless_constant

is

X'hex_digit[hex_digit... ]

 

 

or

'X"hex_digit[hex_digit... ]"

 

 

or

'hex_digit[hex_digit... ]'X

 

 

or

"hex_digit[hex_digit... ]"X

 

 

or

Z'hex_digit[hex_digit... ]'

 

 

or

Z"hex_digit[hex_digit... ]"

EXT

binary_typeless_constant

is

B'bin_digit[bin_digit... ]

 

 

or

'B"bin_digit[bin_digit... ] "

The following notes pertain to the preceding format:

  • digit must have one of the values 0 through 7 in octal_typeless_constant

  • digit must have a value of 0 or 1 in binary_typeless_constant

  • The B, O, X, and Z characters can be in uppercase or lowercase.

  • The scalar_structure_component must contain at least one part_ref that contains a subscript_list.

Note that a constant value cannot be an array constructor. An array can be initialized by using the array name as the data_stmt_object and supplying values for all the elements of the array using a data_implied_do.


Note: The Fortran standard does not specify the typeless_constant. If an object is of type character or logical, the constant used for initialization must be of the same type.

If an object is of type real or complex, the corresponding constant must be of type integer, real, or complex. The CF90 and MIPSpro 7 Fortran 90 compilers permit a default real object to be initialized with a BOZ, typeless, or character (used as Hollerith) constant. No conversion of the BOZ value, typeless value, or character constant takes place.

The CF90 and MIPSpro 7 Fortran 90 compilers permit an integer object to be initialized with a BOZ, typeless, or character (used as Hollerith) constant in a type declaration statement. The CF90 and MIPSpro 7 Fortran 90 compilers also allow an integer object to be initialized with a typeless or character (used as Hollerith) constant in a DATA statement.


Note: The Fortran standard does not specify typeless or character (used as Hollerith) constants in initializations, nor does it allow BOZ constants to be used in type declaration statement initializations.

If an object is of derived type, the corresponding structure constructor must be of the same type.

The value of the constant, structure constructor (in a DATA statement), or initialization expression (in a type declaration statement) must be such that its value could be assigned to the corresponding variable using an intrinsic assignment statement. The variable becomes initially defined with the value of the constant.

A variable, or the same part of a variable, must not be initialized more than once in an executable program.


Note: If a variable is initialized more than once in a program, the order of initialization is not guaranteed. The compiler cannot enforce and does not adhere to an order for initialization when multiple initializations appear in source code. The load order can also affect the value of a variable that is initialized multiple times, which means that the final value can vary from loader to loader. Such code does not necessarily port from platform to platform, for example from UNICOS to IRIX.

An object declared to be of a type that has default initialization cannot be specified in a DATA statement. This object can be initialized in a type specification statement. The initialization in the type specification statement overrides the default initialization.

The following items cannot be initialized:

  • A dummy argument

  • An object made accessible by use or host association

  • A function result

  • An automatic object

  • An allocatable array

  • An external or intrinsic procedure


Note: The Fortran standard does not allow initialization of objects in named common blocks except from within a BLOCKDATA program unit. The Fortran standard does not allow initialization of objects in a blank common block.

For an object being initialized, any subscript, section subscript, substring starting point, or substring ending point must be an integer initialization expression.

Each component of a structure constructor used for initialization must be an initialization expression.

If the variable being initialized has the POINTER attribute, then data_stmt_constant must be NULL(). The pointer has an initial association status of disassociated.

A variable that appears in a DATA statement and is thereby declared and typed implicitly can appear in a subsequent type declaration statement only if that declaration confirms the implicit declaration. An array name, array section, or array element appearing in a DATA statement must have had its array properties established previously.

If a DATA statement constant value is a named constant or a structure constructor, the named constant or derived type must have been declared previously in the scoping unit or must have been made accessible by USE or HOST association.

An array element or structure component that appears in a DATA statement must not have a constant parent.

The DATA statement repeat factor value must be positive or zero. If it is a named constant, the value must have been specified in a prior statement in the scoping unit that contains the DATA statement or must have been made accessible by use or host association.

In a scalar_constant_subobject that is a data_stmt_repeat, any subscript must be an initialization expression.

In a scalar_constant_subobject that is a data_stmt_constant, any subscript, substring starting point, or substring ending point must be an initialization expression.

A subscript in an array element of an implied-DO list must contain as operands only constants or DO variables of the containing implied-DO s.

The scalar integer loop control expressions in an implied-DO must contain as operands only constants or DO variables of the containing implied-DO s. Each operation must be an intrinsic operation.

The data object list is expanded to form a sequence of scalar variables. An array or array section is equivalent to the sequence of its array elements in array element order. A data_implied_do is expanded to form a sequence of array elements and structure components, under the control of the implied-DO variable, as in the DO construct. A zero-sized array or an implied-DO with an iteration count of 0 contributes no variables to the expanded list, but a character variable declared to have zero length does contribute a variable to the list.

The data value list is expanded to form a sequence of scalar values. Each value must be a constant or constant expression (structure constructor). If a value is represented by a named constant, the named constant must be specified prior to the DATA statement. A DATA statement repeat factor indicates the number of times the following constant value is to be included in the sequence. If the repeat factor is 0, the following value is ignored.

If a data_stmt_constant is a boz_literal_constant, the corresponding object must be of type integer. A data_stmt_constant that is a boz_literal_constant is treated as if the constant were an int_literal_constant with a kind_param that specified the representation method with the largest decimal exponent range supported.

Scalar variables and values of the expanded sequence must be in one-to-one correspondence. Each value specifies the initial value for the corresponding variable. The lengths of the two expanded sequences must be the same.


Note: If the last item in the data_object_list is an array name, the value list can contain fewer values than the number of elements in the array. Any element that is not assigned a value is undefined.

The following examples show type declaration statement initializations:

CHARACTER(LEN = 10) :: NAME = "JOHN DOE"
INTEGER, DIMENSION(0:9) :: METERS = (/ (0, I = 1, 10) /)
TYPE(PERSON) :: ME = PERSON(21, "JOHN SMITH"), &
   YOU = PERSON(35, "FRED BROWN")
INTEGER :: BIRD(3) = 1
REAL :: SKEW(100,100) = RESHAPE ( (/((1.0, K = 1, J-1), &
       (0.0, K = J, 100), J = 1, 100)/), (/ 100, 100 /) )

The following are examples of DATA statement initializations:

CHARACTER*10 NAME
INTEGER METERS(0:9)
DATA NAME /"JOHN DOE"/, METERS /10*0/

TYPE(PERSON) ME, YOU
DATA ME /PERSON(21, "JOHN SMITH")/
DATA YOU%AGE, YOU%NAME /35, "FRED BROWN"/
INTEGER BIRD(3)
DATA BIRD /3*1/
REAL SKEW(100, 100)
DATA ((SKEW (K, J), K = 1, J-1), J = 1, 100) /4950 * 1.0/
DATA ((SKEW (K, J), K = J, 100), J = 1, 100) /5050 * 0.0/

In both forms, the character variable NAME is initialized with the value JOHN DOE with padding on the right because the length of the constant is less than the length of the variable. All ten elements of the integer array METERS are initialized to 0; an array constructor is used in the type declaration statement form; a repeat factor is used for the DATA statement form. ME and YOU are structures declared using the user-defined type PERSON defined in “Array Constructors” in Chapter 4. In both forms ME is initialized using a structure constructor. In the DATA statement form YOU is initialized by supplying a separate value for each component.

In the type declaration statement form, the value 1 is broadcast to all 3 elements of BIRD. In the DATA statement form, a value must be supplied for each element of BIRD.

In both forms, the two-dimensional array SKEW is initialized so that the lower triangle is 0 and the strict upper triangle is 1. The RESHAPE(3i) intrinsic function is required in the first form because SKEW is of rank 2. Repeat factors are used in the second form.

PARAMETER Attribute and Statement

A constant can be given a name in a type declaration statement with the PARAMETER attribute or in a PARAMETER statement. The following is a format for a type declaration statement with a PARAMETER attribute:

type, PARAMETER [, attribute_list] :: name = initialization_expression

Subject to the rules governing combinations of these attributes, attribute_list can contain the following:

DIMENSION
PRIVATE
PUBLIC

The initialization_expression must be present.

More than one named constant can be specified in a single type declaration statement; see the examples in this section.

The named constant becomes defined with the value determined from the initialization expression in accordance with the rules for intrinsic assignment. Any named constant that appears in the initialization expression must meet one of the following conditions:

  • Be defined previously in this type declaration statement or in a previous type declaration statement

  • Be accessible through host or use association

If the named constant is an array, it must have its array properties declared in this statement or in a previous statement in the same scoping unit.

The PARAMETER statement also provides a means of defining a named constant. Its format is defined as follows:

 

parameter_stmt

is

PARAMETER (named_constant_def_list)

 

named_constant_def

is

named_constant = initialization_expr

The PARAMETER statement also confers the PARAMETER attribute. It is subject to the same rules and restrictions as the PARAMETER attribute.

The PARAMETER attribute must not be specified for dummy arguments, functions, or objects in a common block.

A named constant that appears in a PARAMETER statement and is thereby declared and typed implicitly may appear in a subsequent type declaration statement only if that declaration confirms the implicit declaration.

A named array constant appearing in a PARAMETER statement must have had its array properties established previously.

A named constant must not appear in a format specification because of a possible ambiguity.

The following examples show entity-oriented declarations:

INTEGER, PARAMETER :: STATES = 50
INTEGER, PARAMETER :: M = MOD(28, 3),  &
       NUMBER_OF_SENATORS = 2 * STATES

The following examples show attribute-oriented declarations:

INTEGER STATES, M, NUMBER_OF_SENATORS
PARAMETER(STATES = 50)
PARAMETER(M = MOD(28, 3),  &
      NUMBER_OF_SENATORS = 2 * STATES)

Object Accessibility and Use

Several attributes indicate where an object can be accessed and how it can be used. Some of these attributes apply only to objects in a module and others apply only to dummy arguments or other variables that are declared in a subprogram.

PUBLIC and PRIVATE Attributes and Statements

The PUBLIC and PRIVATE attributes control access to type definitions, variables, functions, and named constants in a module. The PUBLIC attribute declares that entities in a module are available outside the module by use association; the PRIVATE attribute prevents access outside the module by use association. The default accessibility is PUBLIC, but it can be changed to PRIVATE.

The following formats are for type declaration statements with PUBLIC and PRIVATE attributes:

type, PUBLIC [, attribute_list] :: entity_decl_list
type, PRIVATE [, attribute_list] :: entity_decl_list

Subject to the rules governing combinations of these attributes, attribute_list can contain the following:

ALLOCATABLE
DIMENSION
EXTERNAL
INTRINSIC
PARAMETER
POINTER
SAVE
TARGET
VOLATILE (EXTENSION)

The type declaration statement can also contain an initialization_expr.

PUBLIC and PRIVATE specifications can also appear in the derived-type statement of a derived-type definition in a module to specify the accessibility of the type definition, as shown in the following:

TYPE, PUBLIC :: type_name
TYPE, PRIVATE :: type_name

If a PRIVATE statement appears inside a type definition, it specifies that, although the type may be accessible outside the module, its components are private.

For more information on derived-type definitions, see “Derived Type Definition” in Chapter 4.

PUBLIC and PRIVATE statements provide another means for controlling the accessibility of variables, functions, type definitions, and named constants. PUBLIC and PRIVATE statements can control the accessibility of some entities that do not have a type; these are subroutines, generic specifiers, and namelist groups. The formats for PUBLIC and PRIVATE statements are defined as follows:

 

access_stmt

is

access_spec[[ :: ]access_id_list]

 

access_spec

is

PUBLIC

 

 

or

PRIVATE

 

access_id

is

use_name

 

 

or

generic_spec

Specify one of the following for generic_spec:

  • generic_name

  • OPERATOR (defined_operator)

  • ASSIGNMENT (=)

PUBLIC and PRIVATE statements can appear only in a module.

The PUBLIC and PRIVATE statements also confer the PUBLIC or PRIVATE attribute. They are subject to the same rules and restrictions as the PUBLIC and PRIVATE attributes.

A use_name can be the name of a variable, procedure, derived type, named constant, or namelist group.

Generic specifications are explained further in the Fortran Language Reference Manual, Volume 2. The following are examples of PUBLIC and PRIVATE statements that might be used with generic specifications:

PUBLIC HYPERBOLIC_COS, HYPERBOLIC_SIN     ! generic names
PRIVATE MY_COS_RAT, MY_SIN_RAT            ! specific names
PRIVATE MY_COS_INF_PREC, MY_SIN_INF_PREC  ! specific names
PUBLIC :: OPERATOR ( .MYOP. ), OPERATOR (+), ASSIGNMENT (=)

Only one PUBLIC or PRIVATE statement with an omitted access_id list is permitted in the scoping unit of a module. It determines the default accessibility of the module.

The default accessibility of entities defined in a module is PUBLIC. A PUBLIC statement without an access_id list can appear in the module to confirm the default accessibility. A PRIVATE statement without an access_id list can appear in the module to change the default accessibility.

A procedure that has a generic identifier that is public is accessible through the generic identifier even if its specific name is private. The converse is also true. That is, a module procedure that is public, but whose generic identifier is private, is still accessible through its specific name.

A module procedure that has an argument of a private type or a function result of a private type must be private and must not have a generic identifier that is public.

The following examples show entity-oriented declarations:

REAL, PUBLIC :: GLOBAL_X
TYPE, PRIVATE :: LOCAL_DATA
   LOGICAL :: FLAG
   REAL, DIMENSION(100) :: DENSITY
END TYPE LOCAL_DATA

The following examples show attribute-oriented declarations:

REAL GLOBAL_X
PUBLIC GLOBAL_X
TYPE LOCAL_DATA
   LOGICAL FLAG
   REAL DENSITY
   DIMENSION DENSITY(100)
END TYPE LOCAL_DATA
PRIVATE LOCAL_DATA

The following example shows a public type declaration with private components:

TYPE LIST_ELEMENT
   PRIVATE
   REAL VALUE
   TYPE(LIST_ELEMENT), POINTER :: NEXT, FORMER
END TYPE LIST_ELEMENT

The following example shows how to override the default accessibility:

MODULE M
   PRIVATE
   REAL R, K, TEMP(100)           ! R, K, and TEMP are private
   REAL, PUBLIC :: A(100), B(100) ! A and B are public
END MODULE M

INTENT Attribute and Statement

The INTENT attribute specifies the intended use of a dummy argument. If specified, it can help detect errors, provide information for readers of the program, and give the compiler information that can be used to make the code more efficient. It is particularly valuable in creating software libraries.

Some dummy arguments are referenced but not redefined within the subprogram; some are defined before being referenced within the subprogram; others can be referenced before being redefined. INTENT has three forms: IN, OUT, and INOUT, which correspond respectively to the preceding three situations.

If the intent of an argument is IN, the subprogram must neither change the value of the argument nor must the argument become undefined during the course of the subprogram. If the intent is OUT, the subprogram must not use the argument before it is defined, and it must be definable. If the intent is INOUT, the argument can be used to communicate information to the subprogram and return information; it must be definable. If no intent is specified, the use of the argument is subject to the limitations of the associated actual argument. For example, the actual argument may be a constant (for example, 2) or a more complicated expression (for example, N+2), and in these cases the dummy argument can be referenced but not defined.

The following is a format for a type declaration statement with an INTENT attribute:

type, INTENT (intent_spec) [, attribute_list] :: decl_list

For intent_spec, specify one of the following arguments:

IN
OUT
INOUT

The attribute_list can contain the following attributes:

DIMENSION
OPTIONAL
TARGET
VOLATILE (EXTENSION)

The INTENT statement also provides a means of specifying an intent for an argument. Its format is defined as follows:

 

intent_stmt

is

INTENT (intent_spec) [ :: ]dummy_arg_name_list

 

intent_spec

is

IN

 

 

or

OUT

 

 

or

INOUT

The INTENT attribute can be specified only for dummy arguments.

An INTENT statement can appear only in the specification part of a subprogram or interface body.

An intent must not be specified for a dummy argument that is a dummy procedure because it is not possible to change the definition of a procedure. Intent for a dummy pointer must not be specified either.

The INTENT statement also confers the INTENT attribute. It is subject to the same rules and restrictions as the INTENT attribute.

If an argument is of a type that is default initialized when it is declared with INTENT(OUT), the components that are initialized are defined when the procedure is invoked.

An assumed-size array with INTENT(OUT) cannot be a type for which default initialization is specified.

The following examples show entity-oriented declarations:

SUBROUTINE MOVE(FROM, TO)
   USE PERSON_MODULE
   TYPE(PERSON), INTENT(IN) :: FROM
   TYPE(PERSON), INTENT(OUT) :: TO

SUBROUTINE SUB(X, Y)
   INTEGER, INTENT(INOUT) :: X, Y

The following examples show attribute-oriented declarations:

SUBROUTINE MOVE(FROM, TO)
   USE PERSON_MODULE
   TYPE(PERSON) FROM, TO
   INTENT(IN) FROM
   INTENT(OUT) TO

SUBROUTINE SUB(X, Y)
   INTEGER X, Y
   INTENT(INOUT) X, Y

OPTIONAL Attribute and Statement

The OPTIONAL attribute allows a procedure reference to omit arguments with this attribute. The PRESENT(3i) intrinsic function can be used to test the presence of an optional argument in a particular invocation and this test can be used to control the subsequent processing in the procedure. If the argument is not present, the subprogram can supply a default value or it can use an algorithm that is not based on the presence of the argument.

The following is a format for a type declaration statement with an OPTIONAL attribute:

type, OPTIONAL [, attribute_list] :: entity_decl_list

Subject to the rules governing combinations of these attributes, attribute_list can contain the following:

DIMENSION
EXTERNAL
INTENT
POINTER
TARGET
VOLATILE (EXTENSION)

The OPTIONAL statement also provides a means for specifying an argument that can be omitted. Its format is defined as follows:

 

optional_stmt

is

OPTIONAL [ :: ]dummy_arg_name_list

The OPTIONAL attribute can be specified only for dummy arguments.

An OPTIONAL statement can appear only in the scoping unit of a subprogram or interface body.

The OPTIONAL statement also confers the OPTIONAL attribute. It is subject to the same rules and restrictions as the OPTIONAL attribute.

The following examples show entity-oriented declarations in a program fragment:

CALL SORT_X(X = VECTOR_A)
   . . .
SUBROUTINE SORT_X(X, SIZEX, FAST)
   REAL, INTENT(INOUT) :: X (:)
   INTEGER, INTENT(IN), OPTIONAL :: SIZEX
   LOGICAL, INTENT(IN), OPTIONAL :: FAST
      . . .

   INTEGER TSIZE

      . . .
   IF (PRESENT(SIZEX)) THEN
      TSIZE = SIZEX
   ELSE
      TSIZE = SIZE(X)
   END IF

   IF (.NOT. PRESENT(FAST) .AND. TSIZE > 1000) THEN
      CALL QUICK_SORT(X)
   ELSE
      CALL BUBBLE_SORT(X)
   END IF
      . . .

The following examples show attribute-oriented declarations to be inserted in the same program fragment:

SUBROUTINE SORT_X(X, SIZEX, FAST)
   REAL X(:)
   INTENT(INOUT) X
   INTEGER SIZEX
   LOGICAL FAST
   INTENT(IN) SIZEX, FAST
   OPTIONAL SIZEX, FAST
      . . .
   INTEGER TSIZE
      . . .  

SAVE Attribute and Statement

Variables with the SAVE attribute retain their value and their definition, association, and allocation status after the subprogram in which they are declared completes execution. Variables without the SAVE attribute cannot be depended on to retain their value and status, although the CF90 and MIPSpro 7 Fortran 90 compilers treat named common blocks as if they had the SAVE attribute. The SAVE attribute should always be specified for an object or the object's common named block, if it is necessary for the object to retain its value and status.

Objects declared in a module can be given the SAVE attribute, in which case they always retain their value and status when a procedure that uses the module completes execution. Objects in modules must be in continual use in order to retain their values.

Objects declared in recursive subprograms can be given the SAVE attribute. Such objects are shared by all instances of the subprogram.

Any object that is data initialized (in a DATA statement or a type declaration statement) has the SAVE attribute by default.

The following is a format for a type declaration statement with a SAVE attribute:

type, SAVE [, attribute_list] :: entity_decl_list

Subject to the rules governing combinations of these attributes, attribute_list can contain the following:

ALLOCATABLE
DIMENSION
POINTER
PRIVATE
PUBLIC
TARGET
VOLATILE (EXTENSION)

The type declaration statement can also contain an initialization_expr, but it cannot have the PARAMETER attribute.

The SAVE statement provides a means for specifying the SAVE attribute for objects and also for named common blocks. Its format is defined as follows:

 

save_stmt

is

SAVE [[ :: ]saved_entity_list]

 

saved_entity

is

data_object_name

 

 

or

/ common_block_name /

A SAVE statement without a saved entity list is treated as though it contained the names of all items that could be saved in the scoping unit. The CF90 and MIPSpro 7 Fortran 90 compilers allow you to insert multiple SAVE statements without entity lists in a scoping unit.


Note: The Fortran standard permits only one SAVE statement without an entity list in a scoping unit.

If SAVE appears in a main program as an attribute or a statement, it has no effect.

The following objects must not be saved:

  • A procedure

  • A function result

  • A dummy argument

  • A named constant

  • An automatic data object

  • An object in a common block

  • A namelist group

A variable in a common block cannot be saved individually; the entire named common block must be saved if you want any variables in it to be saved.

A named common block saved in one scoping unit of a program is saved throughout the program.


Note: The Fortran standard states that if a named common block is saved in one scoping unit of a program, it must be saved in every scoping unit of the program in which it is defined (other than the main program).

If a named common block is specified in a main program, it is available to any scoping unit of the program that specifies the named common block; it does not need to be saved.

The SAVE statement also confers the SAVE attribute. It is subject to the same rules and restrictions as the SAVE attribute.

The following example shows an entity-oriented declaration:

CHARACTER(LEN = 12), SAVE :: NAME

The following example shows an attribute-oriented declaration:

CHARACTER*12 NAME
SAVE NAME

The following example shows saving objects and named common blocks:

SAVE A, B, /BLOCKA/, C, /BLOCKB/

VOLATILE Attribute and Statement (IRIX Systems Only)

The VOLATILE attribute and statement specifies that the value of an object is unpredictable. The object's value can change without visible assignment by the program, and it's value can be affected by external events. The presence of this statement prevents the compiler from optimizing references to specified variables, arrays, and common blocks of data.

The following format is for a type declaration statement with the VOLATILE attribute:

type, VOLATILE [, attribute_list] :: entity_decl_list

Subject to the rules governing combinations of these attributes, attribute_list can contain the following:

ALLOCATABLE
AUTOMATIC (EXTENSION)
DIMENSION
INTENT
OPTIONAL
POINTER
PRIVATE
PUBLIC
SAVE
TARGET

The entity_decl_list can include the name of a common block, enclosed in slash characters (for example, /common_block_name/).

The format for the VOLATILE statement is as follows:

EXT

volatile_stmt

is

VOLATILE  entity_decl_list

EXT

entity_decl_list

is

data_object_name

EXT

 

or

/common_block_name/

The following example shows a type declaration statement that specifies the VOLATILE attribute:

INTEGER, VOLATILE :: D, E

In the following example, the named common block, BLK1, and the variables D and E are volatile. Variables P1 and P4 become volatile because of the direct equivalence of P1 and the indirect equivalence of P4. The code that shows this is as follows:

PROGRAM TEST
LOGICAL(KIND=1) IPI(4)
INTEGER(KIND=4) A, B, C, D, E, ILOOK
INTEGER(KIND=4) P1, P2, P3, P4
COMMON /BLK1/A, B, C

VOLATILE /BLK1/, D, E
EQUIVALENCE(ILOOK, IPI)
EQUIVALENCE(A, P1)
EQUIVALENCE(P1, P4)

The presence of a VOLATILE attribute or statement can inhibit some optimizations because it asserts that the compiler must perform loads and stores from the specified objects. As an example, consider the following code fragment:

J = 1
DO I = 1,100000
  IF (J.EQ.2) PRINT 'FOO'
END DO

If the preceding code were included in a Fortran program, the compiler might remove the statement IF (J.EQ.2) PRINT 'FOO' because J is loop invariant and because J was previously assigned the value 1. If J were declared VOLATILE, the compiler would perform all loads of J because something else might affect the value of J.


Note: The Fortran standard does not describe the VOLATILE attribute or statement.

A variable or common block must be declared VOLATILE if it can be read or written to in a way that is not visible to the compiler. This would be the case in the following situations:

  • If an operating system feature is used to place a variable in shared memory so that it can be accessed by other programs, the variable must be declared VOLATILE.

  • If a variable is accessed or modified by a routine called by the operating system when an asynchronous event occurs, the variable must be declared VOLATILE.

  • If a variable might be written by one thread and then read by a different thread, it must be marked VOLATILE.

If an array is declared VOLATILE, each element in the array is VOLATILE. If a common block is declared VOLATILE, each variable in the common block is VOLATILE.

If an object of derived type is declared VOLATILE, its components are VOLATILE.

If a pointer is declared VOLATILE, the pointer itself is VOLATILE.

A VOLATILE statement must not specify a procedure, function result, or NAMELIST group name.

Procedure Properties

If an external or dummy procedure is to be an actual argument to a subprogram, the procedure name must be declared EXTERNAL. (A dummy procedure is a dummy argument that is a procedure.) If an external procedure has the same name as an intrinsic procedure, again the name must be declared EXTERNAL. When this occurs, the intrinsic procedure of that name is no longer accessible to that program unit. If an intrinsic procedure is to be an actual argument, the name of the procedure must be declared INTRINSIC. The Fortran Language Reference Manual, Volume 2, discusses further the usage of these attributes.

Because only functions, not subroutines, are declared to have a type (the type of the result), only function names can appear in type declaration statements. The EXTERNAL and INTRINSIC attributes in type declaration statements therefore apply only to functions. The EXTERNAL and INTRINSIC statements can be used to specify properties of subroutines, and the EXTERNAL statement can specify block data program units. For information on block data program units, see the Fortran Language Reference Manual, Volume 2.

EXTERNAL Attribute and Statement

The EXTERNAL attribute in a type declaration statement indicates that a name is the name of an external function or a dummy function and permits the name to be used as an actual argument.

The following is a format for a type declaration statement with an EXTERNAL attribute:

type, EXTERNAL [, attribute_list] :: function_name_list

Subject to the rules governing combinations of these attributes, attribute_list can contain the following:

OPTIONAL
PRIVATE
PUBLIC

An interface block can be used to describe the interface of an external function. A function described by an interface block has the EXTERNAL attribute by default, so the function name cannot also be given the EXTERNAL attribute by any other means. Note that an interface block specifies the EXTERNAL attribute for all procedures in the interface block, with the exception of module procedures specified in MODULE PROCEDURE statements within the block. For information on interface blocks, see the Fortran Language Reference Manual, Volume 2.

The EXTERNAL statement provides a means for declaring subroutines and block data program units, as well as functions, to be external. Its format is defined as follows:

 

external_stmt

is

EXTERNAL external_name_list

Each external name must be the name of an external procedure, a dummy argument, or a block data program unit.

If a dummy argument is specified to be EXTERNAL, the dummy argument is a dummy procedure.

The EXTERNAL statement also confers the EXTERNAL attribute. It is subject to the same rules and restrictions as the EXTERNAL attribute.

The following examples of entity-oriented declarations:

SUBROUTINE SUB(FOCUS)
   INTEGER, EXTERNAL :: FOCUS
   LOGICAL, EXTERNAL :: SIN

The following example shows an attribute-oriented declaration:

SUBROUTINE SUB (FOCUS)
   INTEGER FOCUS
   LOGICAL SIN
   EXTERNAL FOCUS, SIN

FOCUS is declared to be a dummy procedure. SIN is declared to be an external procedure. Both are functions. To declare an external subroutine, the EXTERNAL statement or an interface block must be used because a subroutine does not have a type, and thus its attributes cannot be specified in a type declaration statement. The specific and generic name SIN of the intrinsic function SIN is no longer available to subroutine SUB.

INTRINSIC Attribute and Statement

The INTRINSIC attribute in a type declaration statement indicates that a name is the name of an intrinsic function and permits the names of some intrinsic functions to be used as actual arguments.

The following is a format for a type declaration statement with an INTRINSIC attribute:

type, INTRINSIC [, attribute_list] :: intrinsic_function_name_list

For attribute_list, specify one of the following attributes:

PRIVATE
PUBLIC

The INTRINSIC statement provides a means for declaring intrinsic subroutines, as well as functions. Its format is defined as follows:

 

intrinsic_stmt

is

INTRINSIC intrinsic_procedure_name_list

Each intrinsic_procedure_name must be the name of an intrinsic procedure.

A name must not be declared to be both EXTERNAL and INTRINSIC in a scoping unit.

A type can be specified for an intrinsic function even though it has a type as specified in the Fortran Language Reference Manual, Volume 2. If a type is specified for the generic name of an intrinsic function, it does not remove the generic properties of the function name.

The INTRINSIC statement also confers the INTRINSIC attribute. It is subject to the same rules and restrictions as the INTRINSIC attribute.

The CF90 and MIPSpro 7 Fortran 90 compilers have implemented intrinsic procedures in addition to the ones required by the standard. These procedures have the status of intrinsic procedures, but programs that use them may not be portable. It is recommended that such procedures be declared INTRINSIC to allow other processors to diagnose whether or not they are intrinsic for those processors.

The following is an example of an entity-oriented declaration:

REAL, INTRINSIC :: SIN, COS

The following is an example of an attribute-oriented declaration:

REAL SIN, COS
INTRINSIC SIN, COS

Because the interfaces of intrinsic procedures are known to the compiler, it is not necessary to specify a type for them, but it is not incorrect to do so.

Automatic Data Objects

Automatic data objects are especially useful as working storage in a procedure. These objects can be declared only in procedures or procedure interfaces; they are created when the procedure is entered and disappear when the procedure completes execution. They can be created the same size as an argument to the procedure, so they can be tailored to each invocation.

The following are the three kinds of automatic data objects:

  • Automatic arrays of any type

  • Objects of type character

  • Local variables and arrays not in a common block or module and not declared with the SAVE attribute

An automatic array or character data object is one with a specification that depends on the value of a nonconstant expression and is not a dummy argument. Automatic arrays are those whose size depends on a variable used in a bound expression. The size of an automatic array or character data object is not known at compile time. The size is calculated at execution time, and storage is allocated upon entry into the procedure. Storage is freed upon exit from the procedure. Local variables and arrays may be declared with the AUTOMATIC attribute. For more information on the AUTOMATIC attribute, see “AUTOMATIC Attribute and Statement (EXTENSION)”.

The following are examples of automatic data objects:

SUBROUTINE SUB (N, DUMMY_ARRRAY)
COMMON /CB/ K
INTEGER AUTO_ARRAY(N)      ! Automatic array.
CHARACTER(LEN=K*2) CH      ! Automatic character variable.
INTEGER DUMMY_ARRAY(K,N)   ! Not an automatic array
                           ! because it is a dummy
                           ! argument, not a local array.. . .
END SUBROUTINE

An automatic array or character data object is one with a specification that depends on the value of a nonconstant expression and is not a dummy argument. Automatic arrays are those whose size depends on a value used in a bound expression.

An automatic array or character data object is similar to an object declared with the AUTOMATIC attribute. For both items, storage is allocated when the procedure is entered and deallocated when the procedure is exited. The differences between these types are as follows:

  • The size of an automatic array or character data object is not known at compile time. The size is calculated at execution time, and storage is allocated upon execution of the procedure. Automatic arrays and character data objects cannot be declared with the AUTOMATIC attribute.

  • The size of objects declared with the AUTOMATIC attribute must be known at compile time. Storage is allocated with the initial stack allocation upon entry to the procedure.

In Fortran, the term automatic array or character object does not include noncharacter scalar local variables or arrays with constant bounds. For an array, the extents in each dimension are determined when the procedure is entered. For a character object, the length is determined when the procedure is entered. Apart from dummy arguments, this is the only character object whose length can vary. For arrays, extents can vary for allocatable arrays and array pointers as well as dummy arguments. An automatic array or character object is not a dummy argument, but it is declared with a specification expression that is not a constant expression. The specification expression can be the length of the character object or the bounds of the array. For variables declared with the AUTOMATIC attribute, the variables must be scalar or array values with constant bounds, and they cannot be declared in a common block or module. These variables are allocated on the stack. Automatic objects cannot be saved or initialized.

In the following example, C is an automatic array and MESSAGE is an automatic character object:

SUBROUTINE SWAP_ARRAYS(A, B, A_NAME, B_NAME)
   REAL, DIMENSION(:), INTENT(INOUT) :: A, B
   CHARACTER(LEN = *), INTENT(IN)     :: A_NAME, B_NAME

   REAL C(SIZE (A))
   CHARACTER (LEN = LEN(A_NAME) + LEN(B_NAME) + 17) MESSAGE

   C = A
   A = B
   B = C

   MESSAGE = A_NAME // " and " // B_NAME // " are swapped"
   PRINT *,  MESSAGE
END SUBROUTINE SWAP_ARRAYS


Note: The Fortran standard does not provide a means to explicitly declare automatic variables as automatic.


NAMELIST Statement

A NAMELIST statement establishes the name for a collection of objects that can then be referenced by the group name in certain I/O statements. The NAMELIST statement is defined as follows:

 

namelist_stmt

is

NAMELIST / namelist_group_name / namelist_group_object_list
[[ , ] / namelist_group_name / namelist_group_object_list] ...

 

namelist_group_object

is

variable_name

A variable in the variable name list must not be an array dummy argument with nonconstant bounds, a variable with assumed character length, an automatic object, a pointer, a Cray pointer, an object of a type that has a pointer component at any level, an allocatable array, or a subobject of any of the preceding objects.


Note: The Fortran standard does not describe Cray pointers.

If a namelist group name has the PUBLIC attribute, no item in the namelist group object list can have the PRIVATE attribute or have private components.

The namelist group name cannot be a name made accessible by USE association.

The order in which the data objects (variables) are specified in the NAMELIST statement determines the order in which the values appear on output.

A namelist group name can occur in more than one NAMELIST statement in a scoping unit. The variable list following each successive appearance of the same namelist group name in a scoping unit is treated as a continuation of the list for that namelist group name.

A variable can be a member of more than one namelist group.

A variable must have its type, type parameters, and shape specified previously in the same scoping unit, or it must be determined by implicit typing rules. If a variable is typed by the implicit typing rules, its appearance in any subsequent type declaration statement must confirm the implicit type and type parameters. The following is an example of a NAMELIST statement:

NAMELIST /N_LIST/ A, B, C

Storage Association

Generally, the physical storage units or storage order for data objects cannot be specified. However, the COMMON, EQUIVALENCE, and SEQUENCE statements provide sufficient control over the order and layout of storage units to permit data to share storage units.

The COMMON statement provides a means of sharing data between program units. The EQUIVALENCE statement provides a means whereby two or more objects can share the same storage units.

Fortran modules, pointers, allocatable arrays, and automatic data objects provide additional tools for sharing data and managing storage. The SEQUENCE statement defines a storage order for structures. This permits structures to appear in common blocks and be equivalenced. The SEQUENCE statement can appear only in derived-type definitions to define sequence types. The components of a sequence type have an order in storage sequences that is the order of their appearance in the type definition.

Storage Units

Fortran includes numeric and character storage units for numeric and character data. The nondefault types (user-defined types and pointers), however, are stored in unspecified storage units. These unspecified storage units are used for pointers, objects of nondefault type, and structures that contain components that are of nondefault types or are pointers. This unit is different for each different sort of object. A pointer occupies a single unspecified storage unit that is different from that of any nonpointer object and can be different for each combination of type, type parameters, and rank.

There are two kinds of structures, sequence structures and nonsequence structures, depending on whether or not the type definition contains a SEQUENCE statement. A nonsequence structure occupies a single unspecified storage unit that is different for each type. The three kinds of sequence structures are as follows:

  • Numeric sequence structures (containing only numeric and logical entities of default kind)

  • Character sequence structures (containing only character entities)

  • Sequence structures (containing a mixture of components including objects that occupy numeric, character, and unspecified storage units)

Table 5-1, lists objects of various types and attributes and the storage units they occupy.

Table 5-1. Types, attributes, and storage

Types and attributes of object

Storage units

Default integer

1 numeric

Default real

1 numeric

Logical

1 numeric

Double precision

2 numeric

Default complex

2 numeric

Character of length 1

1 character

Character of length s

s characters

Nondefault integer

1 unspecified

Real other than default real or double precision

1 unspecified

Nondefault complex

1 unspecified

Nonsequence structure

1 unspecified

Numeric sequence structure

n numeric, where n is the number of numeric storage units the structure occupies

Character sequence structure

n characters, where n is the number of character storage units the structure occupies

Sequence structure

The sum of the storage sequences of all the ultimate components of the structure.

Any type with the POINTER attribute

1 unspecified

Any intrinsic or sequence type with the DIMENSION attribute

The size of the array times the number of storage units for the type (will appear in array element order)

Any nonintrinsic or nonsequence type with the DIMENSION attribute

One unspecified storage unit for each element of the array

Any type with the POINTER attribute and the DIMENSION attribute

1 unspecified


Storage Sequence

A storage sequence is an ordered sequence of storage units. The storage units can be elements in an array, characters in a character variable, components in a sequence structure, or variables in a common block. A sequence of storage sequences forms a composite storage sequence. The order of the storage units in such a composite sequence is the order of the units in each constituent taken in succession, ignoring any zero-sized sequences.

Storage is associated when the storage sequences of two different objects have some storage in common. This permits two or more variables to share the same storage. Two objects are totally associated if they have the same storage sequence; two objects are partially associated if they share some storage but are not totally associated.

EQUIVALENCE Statement

To indicate that two or more variables will share storage, they can be placed in an equivalence group in an EQUIVALENCE statement. If the objects in an equivalence group have different types or type parameters, no conversion or mathematical relationship is implied. If a scalar and an array are equivalenced, the scalar does not have array properties and the array does not have the properties of a scalar. The format of the EQUIVALENCE statement is defined as follows:

 

equivalence_stmt

is

EQUIVALENCE equivalence_set_list

 

equivalence_set

is

(equivalence_object, equivalence_object_list)

 

equivalence_object

is

variable_name

 

 

or

array_element

 

 

or

substring

An equivalence object must not be one of the following items:

  • A dummy argument

  • A Fortran pointer

  • An allocatable array

  • A structure containing a pointer at any level

  • An automatic data object

  • A function name, result name, or entry name

  • A named constant

  • A structure component

  • A Cray pointee

  • An object made accessible by USE association.

  • A subobject of any of the preceding

  • An object with the TARGET attribute.

An equivalence group list must contain at least two items.

Subscripts and substring ranges must be integer initialization expressions. A substring cannot have a length of zero.

If an equivalence object is of type default integer, default real, double-precision real, default complex, default logical, or numeric sequence type, all objects in the set must be of these types.

If an equivalence object is of type character or character sequence type, all objects in the set must be type character. The lengths do not need to be the same.

If an equivalence object is of sequence type other than numeric or character sequence type, all objects in the set must be of the same type.


Note: The CF90 and MIPSpro 7 Fortran 90 compilers allow equivalencing of character data with noncharacter data. The Fortran standard does not address this. It is recommended that you do not perform equivalencing in this manner, however, because alignment and padding differs across platforms, thus rendering your code less portable.

If an equivalence object is of intrinsic type other than default integer, default real, double-precision real, default complex, or default logical, all objects in the set must be of the same type with the same kind type parameter value.

The use of an array name unqualified by a subscript list in an equivalence set specifies the first element of the array; that is, A means the first element of A.

An EQUIVALENCE statement must not specify that the same storage unit is to occur more than once in a storage sequence. For example, the following is illegal because it would indicate that storage for X(2) and X(3) is shared:

EQUIVALENCE (A, X(2)), (A, X(3))

An EQUIVALENCE statement must not specify the sharing of storage units between objects declared in different scoping units.

An EQUIVALENCE statement specifies that the storage sequences of the data objects in an equivalence set are storage associated. Any nonzero-sized sequences in the set have the same first storage unit, and any zero-sized sequences are storage associated with one another and with the first storage unit of any nonzero-sized sequences. This causes storage association of the objects in the group and may cause storage association of other data objects.

Example 1: The following code causes the alignment illustrated in Figure 5-2:

CHARACTER(LEN = 4) :: A, B
CHARACTER(LEN = 3) :: C(2)
EQUIVALENCE (A, C(1)), (B, C(2))

Figure 5-2. Character alignment example

Character alignment example

As a result, the fourth character of A, the first character of B, and the first character of C(2) all share the same character storage unit.

Example 2: Figure 5-3, illustrates alignment of the following two numeric arrays:

REAL, DIMENSION(6) :: X, Y
EQUIVALENCE (X(5), Y(3))

Figure 5-3. Numeric array alignment example

Numeric array alignment example

COMMON Statement

The COMMON statement establishes blocks of storage called common blocks and specifies objects that are contained in the blocks. Two or more program units can share this space and thus share the values of variables stored in the space. Thus, the COMMON statement provides a global data facility based on storage association. Common blocks can be named, in which case they are called named common blocks, or they can be unnamed, in which case they are called blank common.

Common blocks can contain mixtures of storage units and can contain unspecified storage units; however, if a common block contains a mixture of storage units, every declaration of the common block in the program must contain the same sequence of storage units, thereby matching types, kind type parameters, and attributes (DIMENSION and POINTER). The format of the COMMON statement is defined as follows:

 

common_stmt

is

COMMON [ / [common_block_name] / ]common_block_object_list
[[ , ] / [common_block_name] / common_block_object_list] ...

 

common_block_object

is

variable_name[ (explicit_shape_spec_list) ]

A common_block_object must not be one of the following items:

  • A dummy argument

  • An allocatable array

  • An automatic object

  • A function name, result name, or entry name

  • A USE associated variable

  • A HOST associated variable

  • A sequence structure with default initialization

  • A nonsequence structure

The appearance of two slashes with no common block name between them declares that the objects that follow are in blank common.

A common block name or an indication of blank common can appear more than once in one or more COMMON statements in the same scoping unit. The object list following each successive block name or blank common indication is treated as a continuation of the previous object list.

A variable can appear in only one common block within a scoping unit.

If a variable appears with an explicit-shape specification list, it is an array, and each bound must be a constant specification expression.

Only a named common block can be saved. Individual variables in the common block cannot be saved.

For each common block, a common block storage sequence is formed. It consists of the sequence of storage units of all the variables listed for the common block in the order of their appearance in the common block list. The storage sequence may be extended (on the end) to include the storage units of any variable equivalenced to a variable in the common block. Data objects storage associated with a variable in a common block are considered to be in that common block. The size of a common block is the size of its storage sequence including any extensions of the sequence resulting from equivalence association.

Within an executable program, the common block storage sequences of all nonzero-sized common blocks with the same name have the same first storage unit. Zero-sized common blocks are permitted. All zero-sized common blocks with the same name are storage associated with one another. The same is true for all blank common blocks except that because they can be of different sizes, it is possible for a zero-sized blank common block in one scoping unit to be associated with the first storage unit of a nonzero-sized blank common block in another scoping unit. In this way, many subprograms can use the same storage. They can specify common blocks to communicate global values or to reuse and conserve storage. USE association or HOST association can cause these associated objects to be accessible in the same scoping unit.

A nonpointer object of type default integer, default real, double-precision real, default complex, default logical, or numeric sequence type must become associated with only nonpointer objects of these types.

A nonpointer object of type character or character sequence must become associated with only nonpointer objects of these types.

If an object of numeric sequence or character sequence type appears in a common block, it is as if the individual components were enumerated in order directly in the common block object list.

A nonpointer object of sequence type other than numeric or character sequence type must become associated only with nonpointer objects of the same type.

A nonpointer object of intrinsic type other than default integer, default real, double precision real, default complex, default logical, or character must become associated only with nonpointer objects of the same type with the same kind type parameter value.

A pointer must become associated only with pointers of the same type, type parameters, and rank.


Note: An object with the TARGET attribute can become storage associated only with another object that has the TARGET attribute and the same type and type parameters.

The CF90 and MIPSpro 7 Fortran 90 compilers treat named common blocks and blank common blocks identically, as follows:

  • Variables in blank common and variables in named common blocks can be initialized.

  • Named common blocks and blank common are always saved.

  • Named common blocks of the same name and blank common can be of different sizes in different scoping units.


    Note: The Fortran standard lists the following differences between blank common and named common blocks:
    • Variables in blank common must not be initially defined in type declaration statements or DATA statements.

    • A named common block is not saved unless it is named in a SAVE statement.

    • Named common blocks of the same name must be of the same size in all scoping units.



Consider the code in the following example:

SUBROUTINE FIRST
   REAL B(2)
   COMPLEX C
   LOGICAL FLAG
   TYPE COORDINATES
      SEQUENCE
      REAL X, Y
      LOGICAL Z_O      ! ZERO ORIGIN?
   END TYPE COORDINATES
   TYPE(COORDINATES) P
   COMMON /REUSE/ B, C, FLAG, P

   REAL MY_VALUES(100)
   CHARACTER(LEN = 20) EXPLANATION
   COMMON /SHARE/ MY_VALUES, EXPLANATION
   SAVE /SHARE/

   REAL, POINTER :: W(:, :)
   REAL, TARGET, DIMENSION(100, 100) :: EITHER, OR
   INTEGER(SHORT) :: M(2000)
   COMMON /MIXED/ W, EITHER, OR, M
      . . .
END SUBROUTINE
SUBROUTINE SECOND
   INTEGER, PARAMETER :: SHORT = 2
   INTEGER I(8)
   COMMON /REUSE/ I

   REAL MY_VALUES(100)
   CHARACTER(LEN = 20) EXPLANATION
   COMMON /SHARE/ MY_VALUES, EXPLANATION
   SAVE /SHARE/

   REAL, POINTER :: V(:)
   REAL, TARGET, DIMENSION(100000) :: ONE, ANOTHER
   INTEGER(SHORT) :: M(2000)
   COMMON /MIXED/ V, ONE, ANOTHER, M  ! ILLEGAL
   . . .
END SUBROUTINE

Common block REUSE has a storage sequence of 8 numeric storage units. It is used to conserve storage. The storage referenced in subroutine FIRST is associated with the storage referenced in subroutine SECOND, as follows:

Figure 5-4. Storage of REUSE in FIRST and SECOND

Storage of  REUSE in  FIRST and  SECOND

The Fortran standard does not guarantee that the storage is actually retained and reused because, in the absence of a SAVE attribute for REUSE, some compilers can release the storage when either of the subroutines completes execution. The CF90 and MIPSpro 7 Fortran 90 compilers treat named common blocks as entities that are contained in a SAVE statement.

Common block SHARE contains both numeric and character storage units and is used to share data between subroutines FIRST and SECOND.

The declaration of common block MIXED in subroutine SECOND is illegal because it does not have the same sequence of storage units as the declaration of MIXED in subroutine FIRST. The array pointer W in FIRST has two dimensions; the array pointer V in SECOND has only one. With common blocks, it is the sequence of storage units that must match, not the names of variables.

Restrictions on Common and Equivalence

An EQUIVALENCE statement must not cause two different common blocks to become associated and must not cause a common block to be extended by adding storage units preceding the first storage unit of the common block. For example, the following code is legal and results in the alignment illustrated in Figure 5-5:

COMMON A(5)
REAL B(5)
EQUIVALENCE (A(2), B(1))

Figure 5-5. Alignment resulting from correct code

Alignment resulting from correct code

On the other hand, the following code is not legal because it would place B(1) ahead of A(1), as is illustrated in Figure 5-6:

EQUIVALENCE (A(1), B(2))

Figure 5-6. Alignment resulting from incorrect code

Alignment resulting from incorrect code

COMMON and EQUIVALENCE statements can appear in a module. The name of a public data object from a module must not appear in a COMMON or EQUIVALENCE statement in any scoping unit that has access to the data object.

EQUIVALENCE association must not cause a derived-type object with default initialization to be associated with an object in a common block.