HP Fortran for OpenVMS
Language Reference Manual


Previous Contents Index


Chapter 5
Specification Statements

A specification statement is a nonexecutable statement that declares the attributes of data objects. In Fortran 95/90, many of the attributes that can be defined in specification statements can also be optionally specified in type declaration statements.

This chapter contains information on the following topics:

For more information on BLOCK DATA and PROGRAM statements, see Chapter 8.

5.1 Type Declaration Statements

A type declaration statement explicitly specifies the properties of data objects or functions.

The general form of a type declaration statement follows:

  • type [[,att]... ::] v [/c-list/] [,v [/c-list/]]...

type

Is one of the following data type specifiers:
BYTE DOUBLE COMPLEX
INTEGER[([KIND=]k)] CHARACTER[([LEN=]n)[,[KIND=]k]]
REAL[([KIND=]k)] LOGICAL[([KIND=]k)]
DOUBLE PRECISION TYPE (derived-type-name)
COMPLEX[([KIND=]k)]  

In the optional kind selector "([KIND=]k)", k is the kind parameter. It must be an acceptable kind parameter for that data type. If the kind selector is not present, entities declared are of default type. (For a list of the valid noncharacter data types, see Table 5-2.)

Kind parameters for intrinsic numeric and logical data types can also be specified using the *n format, where n is the length (in bytes) of the entity; for example, INTEGER*4.

att

Is one of the following attribute specifiers:
ALLOCATABLE (Section 5.2) POINTER (Section 5.15)
AUTOMATIC (Section 5.3) PRIVATE 1 (Section 5.16)
DIMENSION (Section 5.6) PUBLIC 1 (Section 5.16)
EXTERNAL (Section 5.8) SAVE (Section 5.17)
INTENT (Section 5.10) STATIC (Section 5.3)
INTRINSIC (Section 5.11) TARGET (Section 5.18)
OPTIONAL (Section 5.13) VOLATILE (Section 5.19)
PARAMETER (Section 5.14)    

1These are access specifiers.

v

Is the name of a data object or function. It can optionally be followed by:

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

c-list

Is a list of constants, as in a DATA statement. If v is the name of a constant or an initialization expression, the c-list cannot be present.

The c-list cannot specify more than one value unless it initializes an array. When initializing an array, the c-list must contain a value for every element in the array.

Rules and Behavior

Type declaration statements must precede all executable statements.

In most cases, a type declaration statement overrides (or confirms) the implicit type of an entity. However, a variable that appears in a DATA statement and is typed implicitly can appear in a subsequent type declaration only if that declaration confirms the implicit typing.

The double colon separator (::) is required only if the declaration contains an attribute specifier or initialization; otherwise it is optional.

If att appears, c-list cannot be specified. For example:


INTEGER I /2/                ! Valid 
INTEGER, SAVE :: I /2/       ! Invalid 

The same attribute must not appear more than once in a given type declaration statement, and an entity cannot be given the same attribute more than once in a scoping unit.

If the PARAMETER attribute is specified, the declaration must contain an initialization expression.

If => NULL() is specified for a pointer, its initial association status is disassociated.

A variable (or variable subobject) can only be initialized once in an executable program.

If a declaration contains an initialization expression, but no PARAMETER attribute is specified, the object is a variable whose value is initially defined. The object becomes defined with the value determined from the initialization expression according to the rules of intrinsic assignment.

The presence of initialization implies that the name of the object is saved, except for objects in named common blocks or objects with the PARAMETER attribute.

The following objects cannot be initialized in a type declaration statement:

An object can have more than one attribute. Table 5-1 shows compatible attributes.

Table 5-1 Compatible Attributes
Attribute Compatible with:
ALLOCATABLE AUTOMATIC, DIMENSION 1, PRIVATE, PUBLIC, SAVE, STATIC, TARGET, VOLATILE
AUTOMATIC ALLOCATABLE, DIMENSION, POINTER, TARGET, VOLATILE
DIMENSION ALLOCATABLE, AUTOMATIC, INTENT, OPTIONAL, PARAMETER, POINTER, PRIVATE, PUBLIC, SAVE, STATIC, TARGET, VOLATILE
EXTERNAL OPTIONAL, PRIVATE, PUBLIC
INTENT DIMENSION, OPTIONAL, TARGET, VOLATILE
INTRINSIC PRIVATE, PUBLIC
OPTIONAL DIMENSION, EXTERNAL, INTENT, POINTER, TARGET, VOLATILE
PARAMETER DIMENSION, PRIVATE, PUBLIC
POINTER AUTOMATIC, DIMENSION 1, OPTIONAL, PRIVATE, PUBLIC, SAVE, STATIC, VOLATILE
PRIVATE ALLOCATABLE, DIMENSION, EXTERNAL, INTRINSIC, PARAMETER, POINTER, SAVE, STATIC, TARGET, VOLATILE
PUBLIC ALLOCATABLE, DIMENSION, EXTERNAL, INTRINSIC, PARAMETER, POINTER, SAVE, STATIC, TARGET, VOLATILE
SAVE ALLOCATABLE, DIMENSION, POINTER, PRIVATE, PUBLIC, STATIC, TARGET, VOLATILE
STATIC ALLOCATABLE, DIMENSION, POINTER, PRIVATE, PUBLIC, SAVE, TARGET, VOLATILE
TARGET ALLOCATABLE, AUTOMATIC, DIMENSION, INTENT, OPTIONAL, PRIVATE, PUBLIC, SAVE, STATIC, VOLATILE
VOLATILE ALLOCATABLE, AUTOMATIC, DIMENSION, INTENT, OPTIONAL, POINTER, PRIVATE, PUBLIC, SAVE, STATIC, TARGET


1With deferred shape.

Examples

The following show valid type declaration statements:


DOUBLE PRECISION B(6) 
INTEGER(KIND=2) I 
REAL(KIND=4) X, Y 
REAL(4) X, Y 
LOGICAL, DIMENSION(10,10) :: ARRAY_A, ARRAY_B 
INTEGER, PARAMETER :: SMALLEST = SELECTED_REAL_KIND(6, 70) 
REAL(KIND (0.0)) M 
COMPLEX(KIND=8) :: D 
TYPE(EMPLOYEE) :: MANAGER 
REAL, INTRINSIC :: COS 
CHARACTER(15) PROMPT 
CHARACTER*12, SAVE :: HELLO_MSG 
INTEGER COUNT, MATRIX(4,4), SUM      
LOGICAL*2 SWITCH 
REAL :: X = 2.0 
TYPE (NUM), POINTER :: FIRST => NULL() 

For More Information:

5.1.1 Declaration Statements for Noncharacter Types

Table 5-2 shows the data types that can appear in noncharacter type declaration statements.

Table 5-2 Noncharacter Data Types
BYTE 1  
LOGICAL 2  
LOGICAL(1) (or LOGICAL*1)  
LOGICAL(2) (or LOGICAL*2)  
LOGICAL(4) (or LOGICAL*4)  
LOGICAL(8) (or LOGICAL*8)  
INTEGER 3  
INTEGER(1) (or INTEGER*1)  
INTEGER(2) (or INTEGER*2)  
INTEGER(4) (or INTEGER*4)  
INTEGER(8) (or INTEGER*8)  
REAL 4  
REAL(4) (or REAL*4)  
DOUBLE PRECISION (REAL(8)) (or REAL*8)  
REAL(16) (or REAL*16)  
COMPLEX 5  
COMPLEX(4) (or COMPLEX*8)  
DOUBLE COMPLEX (COMPLEX(8)) (or COMPLEX*16)  
COMPLEX(16) (or COMPLEX*32)  


1Same as INTEGER(1).
2This is treated as default logical.
3This is treated as default integer.
4This is treated as default real.
5This is treated as default complex.

In noncharacter type declaration statements, you can optionally specify the name of the data object or function as v*n, where n is the length (in bytes) of v. The length specified overrides the length implied by the data type.

The value for n must be a valid length for the type of v (see Table 15-2). The type specifiers BYTE, DOUBLE PRECISION, and DOUBLE COMPLEX have one valid length, so the n specifier is invalid for them.

For an array specification, the n must be placed immediately following the array name; for example, in an INTEGER declaration statement, IVEC*2(10) is an INTEGER(2) array of 10 elements.

Examples

In a noncharacter type declaration statement, a subsequent kind parameter overrides any initial kind parameter. For example, consider the following statements:


INTEGER(2) I, J, K, M12*4, Q, IVEC*4(10) 
REAL(8) WX1, WXZ, WX3*4, WX5, WX6*4 
REAL(8) PI/3.14159E0/, E/2.72E0/, QARRAY(10)/5*0.0,5*1.0/ 

In the first statement, M12*4 and IVEC*4 override the KIND=2 specification. In the second statement, WX3*4 and WX6*4 override the KIND=8 specification. In the third statement, QARRAY is initialized with implicit conversion of the REAL(4) constants to a REAL(8) data type.

For More Information:

5.1.2 Declaration Statements for Character Types

A CHARACTER type specifier can be immediately followed by the length of the character object or function. It takes one of the following forms:

Keyword Forms

  • CHARACTER [([LEN=]len)]
  • CHARACTER [([LEN=]len [,[KIND=]n])]
  • CHARACTER [(KIND=n [,LEN=len])]

Nonkeyword Form

  • CHARACTER*len[,]

len

Is one of the following:

The largest valid value for len in both forms is 65535. Negative values are treated as zero.

n

Is a scalar integer initialization expression specifying a valid kind parameter. Currently the only kind available is 1.

Rules and Behavior

An automatic object can appear in a character declaration. The object cannot be a dummy argument, and its length must be declared with a specification expression that is not a constant expression.

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

When an asterisk length specification *(*) is used for a function name or dummy argument, it assumes the length of the corresponding function reference or actual argument. Similarly, when an asterisk length specification is used for a named constant, the name assumes the length of the actual constant it represents. For example, STRING assumes a 9-byte length in the following statements:


CHARACTER*(*) STRING 
PARAMETER (STRING = 'VALUE IS:') 

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

The form CHARACTER*(*) is an obsolescent feature in Fortran 95.

Examples

The following example declares an array NAMES containing 100 32-character elements, an array SOCSEC containing 100 9-character elements, and a variable NAMETY that is 10 characters long and has an initial value of 'ABCDEFGHIJ' .


CHARACTER*32 NAMES(100),SOCSEC(100)*9,NAMETY*10 /'ABCDEFGHIJ'/ 

The following example includes a CHARACTER statement declaring two 8-character variables, LAST and FIRST.


INTEGER, PARAMETER :: LENGTH=4 
CHARACTER*(4+LENGTH) LAST, FIRST 

The following example shows a CHARACTER statement declaring an array LETTER containing 26 one-character elements. It also declares a dummy argument BUBBLE that has a passed length defined by the calling program.


SUBROUTINE S1(BUBBLE) 
CHARACTER LETTER(26), BUBBLE*(*) 

In the following example, NAME2 is an automatic object:


SUBROUTINE AUTO_NAME(NAME1) 
  CHARACTER(LEN = *)          NAME1 
  CHARACTER(LEN = LEN(NAME1)) NAME2 

For More Information:


Previous Next Contents Index