[an error occurred while processing this directive]

HP OpenVMS Systems Documentation

Content starts here

HP Fortran for OpenVMS
Language Reference Manual


Previous Contents Index

5.1.3 Declaration Statements for Derived Types

The derived-type (TYPE) declaration statement specifies the properties of objects and functions of derived (user-defined) type.

The derived type must be defined before you can specify objects of that type in a TYPE type declaration statement.

An object of derived type must not have the PUBLIC attribute if its type is PRIVATE.

A structure constructor specifies values for derived-type objects.

Examples

The following are examples of derived-type declaration statements:


TYPE(EMPLOYEE) CONTRACT
...
TYPE(SETS), DIMENSION(:,:), ALLOCATABLE :: SUBSET_1

The following example shows a public type with private components:


TYPE LIST_ITEMS
  PRIVATE
  ...
  TYPE(LIST_ITEMS), POINTER :: NEXT, PREVIOUS
END TYPE LIST_ITEMS

For More Information:

5.1.4 Declaration Statements for Arrays

An array declaration (or array declarator) declares the shape of an array. It takes the following form:


  • (a-spec)

a-spec

Is one of the following array specifications:

The array specification can be appended to the name of the array when the array is declared.

Examples

The following examples show array declarations:


SUBROUTINE SUB(N, C, D, Z)
  REAL, DIMENSION(N, 15) :: IARRY       ! An explicit-shape array
  REAL C(:), D(0:)                      ! An assumed-shape array
  REAL, POINTER :: B(:,:)               ! A deferred-shape array pointer
  REAL, ALLOCATABLE, DIMENSION(:) :: K  ! A deferred-shape allocatable array
  REAL :: Z(N,*)                        ! An assumed-size array

For More Information:

On the general form and rules for type declaration statements, see Section 5.1.

5.1.4.1 Explicit-Shape Specifications

An explicit-shape array is declared with explicit values for the bounds in each dimension of the array. An explicit-shape specification takes the following form:


  • ([dl:] du[, [dl:] du]...)

dl

Is a specification expression indicating the lower bound of the dimension. The expression can have a positive, negative, or zero value. If necessary, the value is converted to integer type.

If the lower bound is not specified, it is assumed to be 1.

du

Is a specification expression indicating the upper bound of the dimension. The expression can have a positive, negative, or zero value. If necessary, the value is converted to integer type.

The bounds can be specified as constant or nonconstant expressions, as follows:

  • If the bounds are constant expressions, the subscript range of the array in a dimension is the set of integer values between and including the lower and upper bounds. If the lower bound is greater than the upper bound, the range is empty, the extent in that dimension is zero, and the array has a size of zero.
  • If the bounds are nonconstant expressions, the array must be declared in a procedure. The bounds can have different values each time the procedure is executed, since they are determined when the procedure is entered.
    The bounds are not affected by any redefinition or undefinition of the variables in the specification expression that occurs while the procedure is executing.
    The following explicit-shape arrays can specify nonconstant bounds:
    • An automatic array (the array is a local variable)
    • An adjustable array (the array is a dummy argument to a subprogram)

The following are examples of explicit-shape specifications:


INTEGER I(3:8, -2:5)         ! Rank-two array; range of dimension one is
...                          ! 3 to 8, range of dimension two is -2 to 5
SUBROUTINE SUB(A, B, C)
  INTEGER :: B, C
  REAL, DIMENSION(B:C) :: A  ! Rank-one array; range is B to C

Automatic Arrays

An automatic array is an explicit-shape array that is a local variable. Automatic arrays are only allowed in function and subroutine subprograms, and are declared in the specification part of the subprogram. At least one bound of an automatic array must be a nonconstant specification expression. The bounds are determined when the subprogram is called.

The following example shows automatic arrays:


SUBROUTINE SUB1 (A, B)
  INTEGER A, B, LOWER
  COMMON /BOUND/ LOWER
  ...
  INTEGER AUTO_ARRAY1(B)
  ...
  INTEGER AUTO_ARRAY2(LOWER:B)
  ...
  INTEGER AUTO_ARRAY3(20, B*A/2)
END SUBROUTINE

Adjustable Arrays

An adjustable array is an explicit-shape array that is a dummy argument to a subprogram. At least one bound of an adjustable array must be a nonconstant specification expression. The bounds are determined when the subprogram is called.

The array specification can contain integer variables that are either dummy arguments or variables in a common block.

When the subprogram is entered, each dummy argument specified in the bounds must be associated with an actual argument. If the specification includes a variable in a common block, the variable must have a defined value. The array specification is evaluated using the values of the actual arguments, as well as any constants or common block variables that appear in the specification.

The size of the adjustable array must be less than or equal to the size of the array that is its corresponding actual argument.

To avoid possible errors in subscript evaluation, make sure that the bounds expressions used to declare multidimensional adjustable arrays match the bounds as declared by the caller.

In the following example, the function computes the sum of the elements of a rank-two array. Notice how the dummy arguments M and N control the iteration:


  FUNCTION THE_SUM(A, M, N)
    DIMENSION A(M, N)
    SUMX = 0.0
    DO J = 1, N
      DO I = 1, M
        SUMX = SUMX + A(I, J)
      END DO
    END DO
    THE_SUM = SUMX
  END FUNCTION

The following are examples of calls on THE_SUM:


DIMENSION A1(10,35), A2(3,56)
SUM1 = THE_SUM(A1,10,35)
SUM2 = THE_SUM(A2,3,56)

The following example shows how the array bounds determined when the procedure is entered do not change during execution:


DIMENSION ARRAY(9,5)
L = 9
M = 5
CALL SUB(ARRAY,L,M)
END

SUBROUTINE SUB(X,I,J)
  DIMENSION X(-I/2:I/2,J)
  X(I/2,J) = 999
  J = 1
  I = 2
END

The assignments to I and J do not affect the declaration of adjustable array X as X(--4:4,5) on entry to subroutine SUB.

For More Information:

On specification expressions, see Section 4.1.7.2.

5.1.4.2 Assumed-Shape Specifications

An assumed-shape array is a dummy argument array that assumes the shape of its associated actual argument array. An assumed-shape specification takes the following form:


  • ([dl]:[, [dl]:]...)

dl

Is a specification expression indicating the lower bound of the dimension. The expression can have a positive, negative, or zero value. If necessary, the value is converted to integer type.

If the lower bound is not specified, it is assumed to be 1.

The rank of the array is the number of colons (:) specified.

The value of the upper bound is the extent of the corresponding dimension of the associated actual argument array + lower-bound - 1.

The following is an example of an assumed-shape specification:


INTERFACE
  SUBROUTINE SUB(M)
    INTEGER M(:, 1:, 5:)
  END SUBROUTINE
END INTERFACE
INTEGER L(20, 5:25, 10)
CALL SUB(L)

SUBROUTINE SUB(M)
  INTEGER M(:, 1:, 5:)
END SUBROUTINE

Array M has the same extents as array L, but array M has bounds (1:20, 1:21, 5:14).

Note that an explicit interface is required when calling a routine that expects an assumed-shape or pointer array.

5.1.4.3 Assumed-Size Specifications

An assumed-size array is a dummy argument array that assumes the size (only) of its associated actual argument array; the rank and extents can differ for the actual and dummy arrays. An assumed-size specification takes the following form:


  • ([expli-shape-spec,] [expli-shape-spec,]... [dl:] *)

expli-shape-spec

Is an explicit-shape specification (see Section 5.1.4.1).

dl

Is a specification expression indicating the lower bound of the dimension. The expression can have a positive, negative, or zero value. If necessary, the value is converted to integer type.

If the lower bound is not specified, it is assumed to be 1.

*

Is the upper bound of the last dimension.

The rank of the array is the number of explicit-shape specifications plus 1.

The size of the array is assumed from the actual argument associated with the assumed-size dummy array as follows:

  • If the actual argument is an array of type other than default character, the size of the dummy array is the size of the actual array.
  • If the actual argument is an array element of type other than default character, the size of the dummy array is a + 1 - s , where s is the subscript order value and a is the size of the actual array.
  • If the actual argument is a default character array, array element, or array element substring, and it begins at character storage unit b of an array with n character storage units, the size of the dummy array is as follows:
    MAX(INT((n + 1 - b) / y), 0)

    The y is the length of an element of the dummy array.

An assumed-size array can only be used as a whole array reference in the following cases:

  • When it is an actual argument in a procedure reference that does not require the shape
  • In the intrinsic function LBOUND

Because the actual size of an assumed-size array is unknown, an assumed-size array cannot be used as any of the following in an I/O statement:

  • An array name in the I/O list
  • A unit identifier for an internal file
  • A run-time format specifier

The following is an example of an assumed-size specification:


SUBROUTINE SUB(A, N)
  REAL A, N
  DIMENSION A(1:N, *)
  ...

For More Information:

On array element order, see Section 3.5.2.2.

5.1.4.4 Deferred-Shape Specifications

A deferred-shape array is an array pointer or an allocatable array.

The array specification contains a colon (:) for each dimension of the array. No bounds are specified. The bounds (and shape) of allocatable arrays and array pointers are determined when space is allocated for the array during program execution.

An array pointer is an array declared with the POINTER attribute. Its bounds and shape are determined when it is associated with a target by pointer assignment, or when the pointer is allocated by execution of an ALLOCATE statement.

In pointer assignment, the lower bound of each dimension of the array pointer is the result of the LBOUND intrinsic function applied to the corresponding dimension of the target. The upper bound of each dimension is the result of the UBOUND intrinsic function applied to the corresponding dimension of the target.

A pointer dummy argument can be associated only with a pointer actual argument. An actual argument that is a pointer can be associated with a nonpointer dummy argument.

A function result can be declared to have the pointer attribute.

An allocatable array is declared with the ALLOCATABLE attribute. Its bounds and shape are determined when the array is allocated by execution of an ALLOCATE statement.

The following are examples of deferred-shape specifications:


REAL, ALLOCATABLE :: A(:,:)       ! Allocatable array
REAL, POINTER :: C(:), D (:,:,:)  ! Array pointers

For More Information:

5.2 ALLOCATABLE Attribute and Statement

The ALLOCATABLE attribute specifies that an array is an allocatable array with a deferred shape. The shape of an allocatable array is determined when an ALLOCATE statement is executed, dynamically allocating space for the array.

The ALLOCATABLE attribute can be specified in a type declaration statement or an ALLOCATABLE statement, and takes one of the following forms:

Type Declaration Statement:


  • type, [att-ls,] ALLOCATABLE [,att-ls] :: a[(d-spec)] [,a[(d-spec)]]...

Statement:


  • ALLOCATABLE [::] a[(d-spec)] [,a[(d-spec)]]...

type

Is a data type specifier.

att-ls

Is an optional list of attribute specifiers.

a

Is the name of the allocatable array; it must not be a dummy argument or function result.

d-spec

Is a deferred-shape specification (: [,:]...). Each colon represents a dimension of the array.

Rules and Behavior

If the array is given the DIMENSION attribute elsewhere in the program, it must be declared as a deferred-shape array.

When the allocatable array is no longer needed, it can be deallocated by execution of a DEALLOCATE statement.

An allocatable array cannot be specified in a COMMON, EQUIVALENCE, DATA, or NAMELIST statement.

Allocatable arrays are not saved by default. If you want to retain the values of an allocatable array across procedure calls, you must specify the SAVE attribute for the array.

Examples

The following example shows a type declaration statement specifying the ALLOCATABLE attribute:


REAL, ALLOCATABLE :: Z(:, :, :)

The following is an example of the ALLOCATABLE statement:


REAL A, B(:)
ALLOCATABLE :: A(:,:), B

For More Information:

5.3 AUTOMATIC and STATIC Attributes and Statements

The AUTOMATIC and STATIC attributes control the storage allocation of variables in subprograms.

The AUTOMATIC and STATIC attributes can be specified in a type declaration statement or an AUTOMATIC or STATIC statement, and take one of the following forms:

Type Declaration Statement:


  • type, [att-ls,] AUTOMATIC [,att-ls] :: v [,v]...
  • type, [att-ls,] STATIC [,att-ls] :: v [,v]...

Statement:


  • AUTOMATIC v [,v]...
  • STATIC v [,v]...

type

Is a data type specifier.

att-ls

Is an optional list of attribute specifiers.

v

Is the name of a variable or an array specification. It can be of any type.

Rules and Behavior

AUTOMATIC and STATIC declarations only affect how data is allocated in storage, as follows:

  • A variable declared as AUTOMATIC and allocated in memory resides in the stack storage area.
  • A variable declared as STATIC and allocated in memory resides in the static storage area.

If you want to retain definitions of variables upon reentry to subprograms, you must use the SAVE attribute.

Automatic variables can reduce memory use because only the variables currently being used are allocated to memory.

Automatic variables allow possible recursion. With recursion, a subprogram can call itself (directly or indirectly), and resulting values are available upon a subsequent call or return to the subprogram. For recursion to occur, RECURSIVE must be specified as one of the following:

  • A keyword in a FUNCTION or SUBROUTINE statement
  • A compiler option
  • An option in an OPTIONS statement

By default, the compiler allocates local variables of non-recursive subprograms, except for allocatable arrays, in the static storage area. The compiler may choose to allocate a variable in temporary (stack or register) storage if it notices that the variable is always defined before use. Appropriate use of the SAVE attribute can prevent compiler warnings if a variable is used before it is defined.

To change the default for variables, specify them as AUTOMATIC or specify RECURSIVE (in one of the ways mentioned above).

To override any compiler option that may affect variables, explicitly specify the variables as AUTOMATIC or STATIC.

Note

Variables that are data-initialized, and variables in COMMON and SAVE statements are always static. This is regardless of whether a compiler option specifies recursion.

A variable cannot be specified as AUTOMATIC or STATIC more than once in the same scoping unit.

If the variable is a pointer, AUTOMATIC or STATIC apply only to the pointer itself, not to any associated target.

Some variables cannot be specified as AUTOMATIC or STATIC. The following table shows these restrictions:

Variable AUTOMATIC STATIC
Dummy argument No No
Automatic object No No
Common block item No Yes
Use-associated item No No
Function result No No
Component of a derived type No No

A variable can be specified with both the STATIC and SAVE attributes.

If a variable is in a module's outer scope, it can be specified as STATIC, but not as AUTOMATIC.

Examples

The following examples show type declaration statements specifying the AUTOMATIC and STATIC attributes:


REAL, AUTOMATIC :: A, B, C
INTEGER, STATIC :: ARRAY_A

The following example shows an AUTOMATIC AND STATIC statement:


...
CONTAINS
 INTEGER FUNCTION REDO_FUNC
   INTEGER I, J(10), K
   REAL C, D, E(30)
   AUTOMATIC I, J, K(20)
   STATIC C, D, E
   ...
 END FUNCTION
...

For More Information:


Previous Next Contents Index