Intel® Fortran Compiler Classic and Intel® Fortran Compiler Developer Guide and Reference

ID 767251
Date 3/22/2024
Public
Document Table of Contents

Type Declarations

Statement: Explicitly specifies the properties of data objects or functions.

A type declaration has the general form:

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

type-spec

Is one of the following:

intrin-type

TYPE (intrin-type)

TYPE (derived-type-name)

For information about parameterized derived types, see Parameterized Derived-Type Declarations.

TYPE (*)
This defines the entity as an assumed-type object.

CLASS (derived-type-name)

CLASS (*)

intrin-type

Is one of the following data type specifiers:

BYTE

INTEGER[([KIND=]k)]

REAL[([KIND=]k)]

DOUBLE PRECISION

COMPLEX[([KIND=]k)]

DOUBLE COMPLEX

CHARACTER[([KIND=]k)]

LOGICAL[([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.

When type-spec is intrin-type, 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. The *n format cannot be used when type-spec is TYPE (intrin-type).

See each data type for further information on that type.

att

Is one of the following attribute specifiers:

You can also declare any attribute separately as a statement.

v

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

  • An array specification, if the object is an array.

    In a function declaration, an array must be a deferred-shape array if it has the POINTER or ALLOCATABLE attribute; otherwise, it must be an explicit-shape array.

  • A coarray specification, if the object is a coarray

  • A character length, if the object is of type character.

  • A constant expression preceded by = or by one of the following for pointer objects:

    • => NULL( )

    • => target (pointer initialization)

  • A codimension

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 has the PARAMETER attribute, 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.

Description

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 or a double colon (::) appears, c-list cannot be specified; for example:

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

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 CLASS is specified, the entity must be a dummy argument or have the ALLOCATABLE or POINTER attribute.

If the PARAMETER attribute is specified, the declaration must contain an constant expression. The PARAMETER attribute must not be specified for a dummy argument, a pointer, an allocatable entity, a function, or an object in a common block.

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

If => target is specified for a pointer, the following rules apply:

  • The pointer must be type compatible with the target.

  • The pointer and target must have the same rank.

  • All nondeferred type parameters of the pointer must have the same values as the corresponding type parameters of the target.

  • If the pointer has the CONTIGUOUS attribute, the target must be contiguous.

A variable (or variable subobject) can only be initialized once in an executable program. If the variable is an array, it must have its shape specified in either the type declaration statement or a previous attribute specification statement in the same scoping unit.

The INTENT, VALUE, and OPTIONAL attributes can be specified only for dummy arguments.

The INTENT attribute must not be specified for a dummy procedure without the POINTER attribute.

If the VALUE attribute is specified, the length type parameter values must be omitted or specified by constant expressions. The VALUE attribute must not be specified for a dummy procedure.

An entity must not have both the EXTERNAL attribute and the INTRINSIC attribute. It can only have one of these attributes if it is a function.

The BIND attribute and the PROTECTED attribute can appear only in the specification part of a module.

A function result can be declared to have the POINTER or ALLOCATABLE attribute.

An automatic object cannot appear in a SAVE or DATA statement and it cannot be declared with a SAVE attribute nor be initially defined by an initialization.

The SAVE attribute must not be specified for:

  • An object that is in a common block

  • A procedure

  • A dummy argument

  • An automatic data object

  • A function result

  • An object with the PARAMETER attribute

The PROTECTED attribute is only allowed for a procedure pointer or named variable that is not in a common block. A pointer object that has the PROTECTED attribute and is accessed by use association must not appear as:

  • A pointer object in a NULLIFY statement

  • A data pointer object or procedure pointer object in a pointer assignment statement

  • An allocate object in an ALLOCATE statement or DEALLOCATE statement

  • An actual argument in a reference to a procedure if the associated dummy argument is a pointer with the INTENT(OUT) or INTENT(INOUT) attribute.

The following objects cannot be initialized in a type declaration:

  • A dummy argument

  • A function result

  • An object in a named common block (unless the type declaration is in a block data program unit)

  • An object in blank common

  • An allocatable variable

  • An external name

  • An intrinsic name

  • An automatic object

  • An object that has the AUTOMATIC attribute

If a declaration contains a constant 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 constant expression according to the rules of intrinsic assignment.

When type-spec is intrin-type, the interpretation is exactly the same as it would have been without the keyword type and the parentheses. The following declarations for integers K and L and complexes A and B have identical results:

TYPE (INTEGER) :: K, L

INTEGER :: K, L

TYPE (COMPLEX (KIND (0.0D0))) :: A, B

COMPLEX (KIND (0.0D0)) :: A, B

A derived-type-name cannot be the same as the name of any standard intrinsic type. The type names BYTE and DOUBLECOMPLEX are not standard type names; they are Intel Fortran extensions. If BYTE or DOUBLECOMPLEX is declared to be a derived-type-name, it overrides the intrinsic name BYTE or DOUBLECOMPLEX. For example:

TYPE (DOUBLECOMPLEX) :: X     ! if DOUBLEXCOMPLEX is a defined-type 
                              !    name, X is of that defined type
BYTE :: Y                     ! if BYTE is not a defined-type name,
                              !    Y is of intrinsic type BYTE, which 
                              !    is the same as INTEGER(KIND=1)

The presence of initialization gives the object the SAVE attribute, except for objects in named common blocks or objects with the PARAMETER attribute.

When the entity is an assumed-type object, the following rules apply:

  • The entity has no declared type and its dynamic type and type parameters are assumed from its effective argument. An assumed-type object is unlimited polymorphic.

  • An assumed-type object must be a dummy variable that does not have the ALLOCATABLE, CODIMENSION, INTENT(OUT), POINTER, or VALUE attribute and is not an explicit-shape array.

  • An assumed-type object that is not assumed-shape and not assumed-rank is intended to be passed as the C address of the object. A TYPE(*) explicit-shape array is not permitted because there is insufficient information passed for an assumed-type explicit-shape array that is an actual argument corresponding to an assumed-shape dummy argument to compute element offsets.

  • An assumed-type variable name must not appear in a designator or expression except as an actual argument corresponding to a dummy argument that is assumed-type, or as the first argument to any of the following intrinsic or intrinsic module functions: IS_CONTIGUOUS, LBOUND, PRESENT, RANK, SHAPE, SIZE, UBOUND, and C_LOC.

  • An assumed-type actual argument that corresponds to an assumed-rank dummy argument must be assumed-shape or assumed-rank.

An object can have more than one attribute. The following table lists the compatible attributes:

Compatible Attributes

Attribute

Compatible with:

ALLOCATABLE

AUTOMATIC, ASYNCHRONOUS, CODIMENSION, DIMENSION 1, PRIVATE, PROTECTED, PUBLIC, SAVE, STATIC, TARGET, VOLATILE

ASYNCHRONOUS

ALLOCATABLE, AUTOMATIC, BIND, DIMENSION, INTENT, OPTIONAL, POINTER, PROTECTED, PUBLIC, SAVE, STATIC, TARGET, VALUE, VOLATILE

AUTOMATIC

ALLOCATABLE, ASYNCHRONOUS, BIND, DIMENSION, POINTER, PROTECTED, TARGET, VOLATILE

BIND

ASYNCHRONOUS, AUTOMATIC, DIMENSION, EXTERNAL, PRIVATE, PROTECTED, PUBLIC, SAVE, STATIC, TARGET, VOLATILE

CODIMENSION

ALLOCATABLE, DIMENSION, INTENT, OPTIONAL, PRIVATE, PROTECTED, PUBLIC, SAVE, TARGET

CONTIGUOUS

DIMENSION, INTENT, OPTIONAL, POINTER, PRIVATE, PROTECTED, PUBLIC, TARGET

DIMENSION

ALLOCATABLE, ASYNCHRONOUS, AUTOMATIC, BIND, CODIMENSION, CONTIGUOUS, INTENT, OPTIONAL, PARAMETER, POINTER, PRIVATE, PROTECTED, PUBLIC, SAVE, STATIC, TARGET, VOLATILE

EXTERNAL

BIND, OPTIONAL, PRIVATE, PUBLIC

INTENT

ASYNCHRONOUS, CODIMENSION, CONTIGUOUS, DIMENSION, OPTIONAL, TARGET, VOLATILE

INTRINSIC

PRIVATE, PUBLIC

OPTIONAL

ASYNCHRONOUS, CODIMENSION, CONTIGUOUS, DIMENSION, EXTERNAL, INTENT, POINTER, TARGET, VALUE, VOLATILE

PARAMETER

DIMENSION, PRIVATE, PUBLIC

POINTER

ASYNCHRONOUS, AUTOMATIC, CONTIGUOUS, DIMENSION 1, OPTIONAL, PRIVATE, PROTECTED, PUBLIC, SAVE, STATIC, VOLATILE

PRIVATE

ASYNCHRONOUS, ALLOCATABLE, BIND, CODIMENSION, CONTIGUOUS, DIMENSION, EXTERNAL, INTRINSIC, PARAMETER, POINTER, PROTECTED, SAVE, STATIC, TARGET, VOLATILE

PROTECTED

ALLOCATABLE, ASYNCHRONOUS, BIND, CODIMENSION, CONTIGUOUS, DIMENSION, POINTER, PRIVATE, PUBLIC, SAVE, TARGET, VOLATILE

PUBLIC

ASYNCHRONOUS, ALLOCATABLE, BIND, CODIMENSION, CONTIGUOUS, DIMENSION, EXTERNAL, INTRINSIC, PARAMETER, POINTER, PROTECTED, SAVE, STATIC, TARGET, VOLATILE

SAVE

ALLOCATABLE, ASYNCHRONOUS, BIND, CODIMENSION, DIMENSION, POINTER, PRIVATE, PROTECTED, PUBLIC, STATIC, TARGET, VOLATILE

STATIC

ALLOCATABLE, ASYNCHRONOUS, BIND, DIMENSION, POINTER, PRIVATE, PROTECTED, PUBLIC, SAVE, TARGET, VOLATILE

TARGET

ALLOCATABLE, ASYNCHRONOUS, AUTOMATIC, BIND, CODIMENSION, CONTIGUOUS, DIMENSION, INTENT, OPTIONAL, PRIVATE, PROTECTED, PUBLIC, SAVE, STATIC,VALUE, VOLATILE

VALUE

ASYNCHRONOUS, INTENT (IN only), OPTIONAL, TARGET

VOLATILE

ALLOCATABLE, ASYNCHRONOUS, AUTOMATIC, BIND, DIMENSION, INTENT, OPTIONAL, POINTER, PRIVATE, PROTECTED, PUBLIC, SAVE, STATIC, TARGET

1With deferred shape

Example

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()

The following shows more examples:

 REAL a (10)
 LOGICAL, DIMENSION (5, 5) :: mask1, mask2
 TYPE (COMPLEX) :: cube_root = (-0.5, 0.867)
 INTEGER, PARAMETER :: short = SELECTED_INT_KIND (4)
 REAL (KIND (0.0D0)) a1
 TYPE (REAL (KIND = 4)) b
 COMPLEX (KIND = KIND (0.0D0)) :: c
 INTEGER (short) k ! Range at least -9999 to 9999
 TYPE (member) :: george

The following shows an example of pointer initialization:

integer, target :: v (5) = [1, 2, 3, 4, 5]
type entry
  integer, pointer :: p (5) => v     ! pointer component default initialization
end type entry

type (entry), target :: bottom
type (entry), pointer :: top => bottom     ! pointer initialization