XL Fortran for AIX 8.1

Language Reference


Derived Types

You can create additional data types, known as derived types, from intrinsic data types and other derived types. You require a type definition to define the name of the derived type (type_name), as well as the data types and names of the components of the derived type.

+-------------------------------IBM Extension--------------------------------+

A record structure is a popular extension for manipulating aggregate non-array data. The record structure predates the introduction of derived types in Fortran 90.

The syntax used for record structures parallels that used for Fortran derived types in most cases. Also, in most cases, the semantics of the two features are parallel. For these reasons, record structures are supported in XL Fortran in a way that makes the two features almost completely interchangeable. Hence,

There are differences, however, as outlined here:

+----------------------------End of IBM Extension----------------------------+



>>-DERIVED_TYPE_statement--------------------------------------><
 
 
>>-+------------------------+----------------------------------><
   '-PRIVATE_SEQUENCE_block-'
 
 
>>-component_def_stmt_block------------------------------------><
 
 
>>-END_TYPE_statement------------------------------------------><
 
 

DERIVED_TYPE_statement
See Derived Type for syntax details.

PRIVATE_SEQUENCE_block
includes the PRIVATE statement (keyword only) and/or the SEQUENCE statement. Only one of each statement can be specified. See PRIVATE and SEQUENCE for details on syntax.

component_def_stmt_block
consists of one or more type declaration statements to define the components of the derived type. The type declaration statements can specify only the DIMENSION, POINTER and ALLOCATABLE attributes. See Type Declaration for detailed syntax and information.

+---------------------------------Fortran 95---------------------------------+

In addition, Fortran 95 allows you to specify a default initialization for each component in the definition of a derived type. See Type Declaration for detailed syntax and information.

+-----------------------------End of Fortran 95------------------------------+

END_TYPE_statement
See END TYPE.

+---------------------------------Fortran 95---------------------------------+

Direct components of a derived type in Fortran 95 are:

+-----------------------------End of Fortran 95------------------------------+

Each derived type is resolved into ultimate components of intrinsic data type, or are alloctable or pointers.

The type name is a local entity. It cannot be the same name as any of the intrinsic data types except BYTE and DOUBLE COMPLEX.

The END TYPE statement can optionally contain the same type_name as specified on the TYPE statement.

The components of a derived type can specify any of the intrinsic data types. Components can also be of a previously defined derived type. A pointer component can be of the same derived type that it is a component of. Within a derived type, the names of components must be unique, although they can be different from names outside the scope of the derived-type definition. Components that are declared to be of type CHARACTER must have length specifications that are constant specification expressions; asterisks are not allowed as length specifiers. Nonpointer array components must be declared with constant dimension declarators. Pointer array components must be declared with a deferred_shape_spec_list.

By default, no storage sequence is implied by the order of the component definitions. However, if you specify the SEQUENCE statement, the derived type becomes a sequence derived type. For a sequence derived type, the order of the components specifies a storage sequence for objects declared with this derived type. If a component of a sequence derived type is of a derived type, that derived type must also be a sequence derived type.

The size of a sequence derived type is equal to the number of bytes of storage needed to hold all of the components of that derived type.

Use of sequence derived types can lead to misaligned data, which can adversely affect the performance of the program.

The PRIVATE statement can only be specified if the derived-type definition is within the specification part of a module. If a component of a derived type is of a type declared to be private, either the derived-type definition must contain the PRIVATE statement or the derived type itself must be private.

If a type definition is private, the following are accessible only within the defining module:

If a derived-type definition contains a PRIVATE statement, its components are accessible only within the defining module, even if the derived type itself is public. Structure components can only be used in the defining module.

A component of a derived-type entity cannot appear as an input/output list item if any ultimate component of the object cannot be accessed by the scoping unit of the input/output statement. A derived-type object cannot appear in a data transfer statement if it has a component that is a pointer or allocatable.

A scalar entity of derived type is called a structure. A scalar entity of sequence derived type is called a sequence structure. The type specifier of a structure must include the TYPE keyword, followed by the name of the derived type in parentheses. See TYPE for details on declaring entities of a specified derived type. The components of a structure are called structure components. A structure component is one of the components of a structure or is an array whose elements are components of the elements of an array of derived type.

An object of a private derived type cannot be used outside the defining module.

Default initialization may be specified using an equal sign followed by an initialization expression, or by using an initial_value_list enclosed in slashes. This form of initialization is now supported for components declared using either a record structure declaration or a standard derived type declaration.

+---------------------------------Fortran 95---------------------------------+

In Fortran 95 a candidate data object for default initialization is a named data object that:

  1. is of derived type with default initialization specified for any of its direct components.
  2. has neither the POINTER, nor the ALLOCATABLE attribute.
  3. is not use or host associated.
  4. is not a pointee.

A default initialization for a non-pointer component will take precedence over any default initialization appearing for any direct component of its type.

If a dummy argument with INTENT(OUT) is of a derived type with default initialization, it must not be an assumed-size array. If a non-pointer object or subobject has been specified with default initialization in a type definition, it must not be initialized by a DATA statement.

+-----------------------------End of Fortran 95------------------------------+

A data object of derived type with default initialization may be specified in a common block as an IBM extension. In addition, default initialization does not imply the SAVE attribute in XL Fortran unless -qsave=defaultinit has been specified.

+---------------------------------Fortran 95---------------------------------+

Unlike explicit initialization, it is not necessary for a data object to have the SAVE attribute for component default initialization to have an impact. You can specify a default initialization for some components of a derived type, but it is not necessary for every component.

You can specify default initialization for a storage unit that is storage associated. However, the objects or subobjects supplying the default initialization must be of the same type. The objects or subobjects must also have the same type parameters and supply the same value for the storage unit.

A direct component will receive an initial value if you specify a default initialization on the corresponding component definition in the type definition, regardless of the accessibility of the component.

For candidate data objects for default initialization, their nonpointer components are either initially defined, or become defined by their corresponding default initialization expressions, and their pointer components are either initially disassociated, or become disassociated if one of the following conditions is met:

Allocation of an object of a derived type in which you specify a default initialization for a component will cause the component to:

In a subprogram with an ENTRY statement, default initialization only occurs for the dummy arguments that appear in the argument list of the procedure name referenced. If such a dummy argument has the OPTIONAL attribute, default initialization will only occur if the dummy argument is present.

Module data objects, which are of derived type with default initializations must have the SAVE attribute, if they are candidate data objects for default initialization.

+-----------------------------End of Fortran 95------------------------------+

The size of a sequence derived type declared using a standard derived type declaration is equal to the sum of the number of bytes required to hold all of its components.

The size of a sequence derived type declared using a record structure declaration is equal to the sum of the number of bytes required to hold all of its components and its padding.

Prior to the introduction of XL Fortran 7.1.0, a numeric sequence structure or character sequence structure that appeared in a common block was treated as if its components were enumerated directly in the common block. Now, that only applies to structures of a type declared using a standard derived type declaration.

Input/Output

In namelist input, a structure is expanded into a list of its non-filler ultimate components.

In namelist output, a structure is expanded into the values of its non-filler ultimate components.

In a formatted data transfer statement (READ, WRITE or PRINT), only components of entities of derived type that are not %FILL components are treated as if they appeared in the input-item-list or the output-item-list.

Any %FILL field in an entity of derived type is treated as padding in an unformatted data transfer statement.

Determining Type for Derived Types

Two data objects have the same derived type if they are declared with reference to the same derived-type definition.

If the data objects are in different scoping units, they can still have the same derived type. Either the derived-type definition is accessible via host or use association, or the data objects reference their own derived-type definitions with the following conditions:

A derived-type definition that specifies SEQUENCE is not the same as a definition declared to be private or that has components that are private.

Example of Determining Type with Derived Types

PROGRAM MYPROG
 
TYPE NAME                         ! Sequence derived type
   SEQUENCE
   CHARACTER(20) LASTNAME
   CHARACTER(10) FIRSTNAME
   CHARACTER(1)  INITIAL
END TYPE NAME
TYPE (NAME) PER1
 
CALL MYSUB(PER1)
PER1 = NAME('Smith','John','K')   ! Structure constructor
CALL MYPRINT(PER1)
 
CONTAINS
  SUBROUTINE MYSUB(STUDENT)       ! Internal subroutine MYSUB
     TYPE (NAME) STUDENT          ! NAME is accessible via host association
              
  ·
  ·
  ·
END SUBROUTINE MYSUB END SUBROUTINE MYPRINT(NAMES) ! External subroutine MYPRINT TYPE NAME ! Same type as data type in MYPROG SEQUENCE CHARACTER(20) LASTNAME CHARACTER(10) FIRSTNAME CHARACTER(1) INITIAL END TYPE NAME TYPE (NAME) NAMES ! NAMES and PER1 from MYPROG PRINT *, NAMES ! have the same data type END SUBROUTINE

An Eample with Different Component Names

        MODULE MOD
          STRUCTURE /S/
           INTEGER I
           INTEGER, POINTER :: P
          END STRUCTURE
          RECORD /S/ R
        END MODULE
        PROGRAM P
          USE MOD, ONLY: R
          STRUCTURE /S/
            INTEGER J
            INTEGER, POINTER :: Q
          END STRUCTURE
          RECORD /S/ R2
          R = R2 ! OK - same type name, components have same attributes and
                 ! type (but different names)
        END PROGRAM P

Structure Components

Structure components can be of any explicit type, including derived type.

Note:
The case in which a structure component has a subobject that is an array or array section requires some background information from Array Sections, and is explained in Array Sections and Structure Components. The following rules for scalar structure components apply also to structure components that have array subobjects.

You can refer to a specific structure component using a component designator. A scalar component designator has the following syntax:

scalar_struct_comp:



>>-name--+---------------------+-------------------------------->
         '-(--int_expr_list--)-'
 
>--+--------------------------------------------------+--------->
   | .----------------------------------------------. |
   | V                                              | |
   '---separator comp_name--+---------------------+-+-'
                            '-(--int_expr_list--)-'
 
>--separator comp_name-+---------------------+-----------------><
                       '-(--int_expr_list--)-'
 
 

name
is the name of an object of derived type

comp_name
is the name of a derived-type component

int_expr
is a scalar integer or real expression called a subscript expression

separator
is % or .
Note:
. (period) is an IBM extension.

The structure component has the same type, type parameters, and POINTER attribute (if any) as the right-most comp_name. It inherits any INTENT, TARGET, and PARAMETER attributes from the parent object.

Notes:

  1. Each comp_name must be a component of the immediately preceding name or comp_name.

  2. The name and each comp_name, except the right-most, must be of derived type.

  3. The number of subscript expressions in any int_expr_list must equal the rank of the preceding name or comp_name.

  4. If name or any comp_name is the name of an array, it must have an int_expr_list.

  5. The right-most comp_name must be scalar.

In namelist formatting, a separator must be a percent sign.

If an expression has a form that could be interpreted either as a structure component using periods as separators or as a binary operation, and an operator with that name is accessible in the scoping unit, XL Fortran will treat the expression as a binary operation. If that is not the interpretation you intended, you should use the percent sign to dereference the parts, or, in free source form, insert white space between the periods and the comp_name.

Examples of References to Structure Components

Example 1: Ambiguous use of a period as separator

        MODULE MOD
          STRUCTURE /S1/
            STRUCTURE /S2/ BLUE
              INTEGER I
            END STRUCTURE
          END STRUCTURE
          INTERFACE OPERATOR(.BLUE.)
            MODULE PROCEDURE BLUE
          END INTERFACE
        CONTAINS
          INTEGER FUNCTION BLUE(R1, I)
            RECORD /S1/ R1
            INTENT(IN) :: R1
            INTEGER, INTENT(IN) :: I
            BLUE = R1%BLUE%I + I
          END FUNCTION BLUE
        END MODULE MOD
 
        PROGRAM P
          USE MOD
          RECORD /S1/ R1
          R1%BLUE%I = 17
          I = 13
          PRINT *, R1.BLUE.I ! Calls BLUE(R1,I) - prints 30
          PRINT *, R1%BLUE%I ! Prints 17
        END PROGRAM P

Example 2: Mix of separators

        STRUCTURE /S1/
          INTEGER I
        END STRUCTURE
        STRUCTURE /S2/
          RECORD /S1/ C
        END STRUCTURE
        RECORD /S2/ R
        R.C%I = 17 ! OK
        R%C.I = 3 ! OK
        R1876I = 13 ! OK
        R.C.I = 19 ! OK
        END

Example 3: Percent and period work for any derived types

        STRUCTURE /S/
          INTEGER I, J
        END STRUCTURE
        TYPE DT
          INTEGER I, J
        END TYPE DT
        RECORD /S/ R1
        TYPE(DT) :: R2
        R1.I = 17; R1%J = 13
        R2.I = 19; R2%J = 11
        END

+-------------------------------IBM Extension--------------------------------+

Allocatable Components

Allocatable components are defined as ultimate components just as pointer components are. This is because the value (if any) is stored separately from the rest of the structure, and this storage does not exist (because the object is unallocated) when the structure is created. As with ultimate pointer components, variables containing ultimate allocatable components are forbidden from appearing directly in input/output lists: the user lists any allocatable or pointer component for input/output.

As is currently the case with allocatable arrays, allocatable components are forbidden from storage association contexts. So, any variable containing an ultimate, allocatable component cannot appear in COMMON or EQUIVALENCE. However, allocatable components are permitted in SEQUENCE types, which allows the same type to be defined separately in more than one scoping unit.

Deallocation of a variable containing an ultimate allocatable component automatically deallocates all such components of the variable that are currently allocated.

In a structure constructor for a derived type containing an allocatable component, the expression corresponding to the allocatable component must be one of the following:

For intrinsic assignment of those objects of a derived type containing an allocatable component, the allocatable component of the variable on the left-hand-side receives the allocation status and, if allocated, the bounds and value of the corresponding component of the expression. This occurs as if the following sequence of steps is carried out:

  1. If the component of the variable is currently allocated, it is deallocated.
  2. If the corresponding component of the expression is currently allocated, the component of the variable is allocated with the same bounds. The value of the component of the expression is then assigned to the corresponding component of the variable using intrinsic assignment.

An allocated ultimate allocatable component of an actual argument that is associated with an INTENT(OUT) dummy argument is deallocated on procedure entry so that the corresponding component of the dummy argument has an allocation status of not currently allocated.

This ensures that any pointers that point to the previous contents of the allocatable component of the variable become undefined.

Example
MODULE REAL_POLYNOMIAL_MODULE
  TYPE REAL_POLYNOMIAL
    REAL, ALLOCATABLE :: COEFF(:)
  END TYPE
  INTERFACE OPERATOR(+)
    MODULE PROCEDURE RP_ADD_RP, RP_ADD_R
  END INTERFACE
CONTAINS
  FUNCTION RP_ADD_R(P1,R)
    TYPE(REAL_POLYNOMIAL) RP_ADD_R, P1
    REAL R
    INTENT(IN) P1,R
    ALLOCATE(RP_ADD_R%COEFF(SIZE(P1%COEFF)))
    RP_ADD_R%COEFF = P1%COEFF
    RP_ADD_R%COEFF(1) = P1%COEFF(1) + R
  END FUNCTION
  FUNCTION RP_ADD_RP(P1,P2)
    TYPE(REAL_POLYNOMIAL) RP_ADD_RP, P1, P2
    INTENT(IN) P1, P2
    INTEGER M
    ALLOCATE(RP_ADD_RP%COEFF(MAX(SIZE(P1%COEFF), SIZE(P2%COEFF))))
    M = MIN(SIZE(P1%COEFF), SIZE(P2%COEFF))
    RP_ADD_RP%COEFF(:M) = P1%COEFF(:M) + P2%COEFF(:M)
    IF (SIZE(P1%COEFF)>M) THEN
      RP_ADD_RP%COEFF(M+1:) = P1%COEFF(M+1:)
    ELSE IF (SIZE(P2%COEFF)>M) THEN
      RP_ADD_RP%COEFF(M+1:) = P2%COEFF(M+1:)
    END IF
  END FUNCTION
END MODULE
 
PROGRAM EXAMPLE
  USE REAL_POLYNOMIAL_MODULE
  TYPE(REAL_POLYNOMIAL) P, Q, R
  P = REAL_POLYNOMIAL((/4,2,1/)) ! Set P to (X**2+2X+4)
  Q = REAL_POLYNOMIAL((/1,1/)) ! Set Q to (X+1)
  R = P + Q ! Polynomial addition
  PRINT *, 'Coefficients are: ', R%COEFF
END
 

+----------------------------End of IBM Extension----------------------------+

Structure Constructor



>>-type_name--(--expr_list--)----------------------------------><
 
 

type_name
is the name of the derived type

expr
is an expression. Expressions are defined under Chapter 5, Expressions and Assignment.

A structure constructor allows a scalar value of derived type to be constructed from an ordered list of values. A structure constructor must not appear before the definition of the referenced derived type.

expr_list contains one value for each component of the derived type. The sequence of expressions in the expr_list must agree in number and order with the components of the derived type. The type and type parameters of each expression must be assignment-compatible with the type and type parameters of the corresponding component. Data type conversion is performed if necessary.

A component that is a pointer can be declared with the same type that it is a component of. If a structure constructor is created for a derived type containing a pointer, the expression corresponding to the pointer component must evaluate to an object that would be an allowable target for such a pointer in a pointer assignment statement.

+-------------------------------IBM Extension--------------------------------+

If a component of a derived type is allocatable, the corresponding constructor expression will either be a reference to the intrinsic function NULL() with no arguments, an allocatable entity, or will evaluate to an entity of the same rank. If the expression is a reference to the intrinsic function NULL(), the corresponding component of the constructor has a status of not currently allocated. If the expression is an allocatable entity, the corresponding component of the constructor has the same allocation status as that of allocatable entity and, if it is allocated, it's same bounds (if any) and value. Otherwise, the corresponding component of the constructor has an allocation status of currently allocated, and has the same bounds (if any) and value as the expression.

If a component using a record structure declaration is %FILL, the structure constructor for that type cannot be used.

If a derived type is accessible in a scoping unit and there is a local entity of class 1 that is not a derived type with the same name accessible in the scoping unit, the structure constructor for that type cannot be used in that scope.

+----------------------------End of IBM Extension----------------------------+

Examples of Derived Types

Example 1:

MODULE PEOPLE
  TYPE NAME
     SEQUENCE                     ! Sequence derived type
     CHARACTER(20) LASTNAME
     CHARACTER(10) FIRSTNAME
     CHARACTER(1)  INITIAL
  END TYPE NAME
 
  TYPE PERSON                     ! Components accessible via use
                                  ! association
     INTEGER AGE
     INTEGER BIRTHDATE(3)         ! Array component
     TYPE (NAME) FULLNAME         ! Component of derived type
  END TYPE PERSON
END MODULE PEOPLE
 
PROGRAM TEST1
  USE PEOPLE
  TYPE (PERSON) SMITH, JONES
  SMITH = PERSON(30, (/6,30,63/), NAME('Smith','John','K'))
                                  ! Nested structure constructors
  JONES%AGE = SMITH%AGE           ! Component designator
  CALL TEST2
  CONTAINS
 
  SUBROUTINE TEST2
    TYPE T
      INTEGER EMP_NO
      CHARACTER, POINTER :: EMP_NAME(:)  ! Pointer component
    END TYPE T
    TYPE (T) EMP_REC
    CHARACTER, TARGET :: NAME(10)
    EMP_REC = T(24744,NAME)              ! Pointer assignment occurs
  END SUBROUTINE                         ! for EMP_REC%EMP_NAME
END PROGRAM

+---------------------------------Fortran 95---------------------------------+

Example 2:

PROGRAM LOCAL_VAR
   TYPE DT
      INTEGER A
      INTEGER :: B = 80
   END TYPE
 
   TYPE(DT) DT_VAR                      ! DT_VAR%B IS INITIALIZED
END PROGRAM LOCAL_VAR

Example 3:

MODULE MYMOD
   TYPE DT
      INTEGER :: A = 40
      INTEGER, POINTER :: B => NULL()
   END TYPE
END MODULE
 
PROGRAM DT_INIT
   USE MYMOD
   TYPE(DT), SAVE :: SAVED(8)            ! SAVED%A AND SAVED%B ARE INITIALIZED
   TYPE(DT) LOCAL(5)                     ! LOCAL%A LOCAL%B ARE INITIALIZED
END PROGRAM

+-----------------------------End of Fortran 95------------------------------+

+-------------------------------IBM Extension--------------------------------+

Record Structures

Declaring Record Structures

Declaring a record structure declares a user-defined type in the same way that a standard Fortran derived type definition declares a user-defined type. A type declared using a record structure declaration is a derived type. For the most part, rules that apply to derived types declared using the standard Fortran syntax apply to derived types declared using the record structure syntax. In those cases where there is a difference, the difference will be called out by referring to the two as derived types declared using a record structure declaration and derived types declared using a standard derived type declaration.

Record structure declarations follow this syntax:

record_structure_dcl:



>>-structure_stmt----------------------------------------------><
 
 
   .----------------------.
   V                      |
>>---struct_comp_dcl_item-+------------------------------------><
 
 
>>-end_structure_stmt------------------------------------------><
 
 

struct_comp_dcl_item:

>>-+-component_def_stmt---+------------------------------------><
   +-record_structure_dcl-+
   '-parameter_stmt-------'
 
 

where component_def_stmt is a type declaration statement used to define the components of the derived type.

structure_stmt:

>>-STRUCTURE--+------------------+--+--------------------+-----><
              '-/structure_name/-'  '-component_dcl_list-'
 
 

component_dcl:

>>-a--+----------------+---------------------------------------><
      '-(-array_spec-)-'
 
 

where a is an object name.

A structure statement declares the structure_name to be a derived type in the scoping unit of the nearest enclosing program unit, interface body or subprogram. The derived type is a local entity of class 1 in that scoping unit.

A structure statement may not specify a component_dcl_list unless it is nested in another record structure declaration. Likewise, the structure_name of a structure statement cannot be omitted unless it is part of a record_structure_dcl that is nested in another record structure declaration. A record_structure_dcl must have at least one component.

A derived type declared using a record structure declaration is a sequence derived type, and is subject to all rules that apply to sequence derived types. A component of a type declared using a record structure declaration cannot be of a nonsequence derived type, as is true of sequence derived types declared using standard derived type declarations. A record structure declaration cannot contain a PRIVATE or SEQUENCE statement.

A record structure declaration defines a scoping unit. All statements in the record_structure_dcl are part of the scoping unit of the record structure declaration, with the exception of any other record_structure_dcl contained in the record_structure_dcl. These rules are also true of standard derived type declarations, repeated here for clarity.

A parameter_stmt in a record_structure_dcl declares named constants in the scoping unit of the nearest enclosing program unit, interface body or subprogram. A named constant declared in such a parameter_stmt may have the same name as a component declared in the record_structure_dcl in which it is contained.

Any components declared on a structure_stmt are components of the enclosing derived type, and are local entities of the enclosing structure's scoping unit. The type of such a component is the derived type on whose structure_stmt it is declared.

Unlike derived types declared using a standard derived type declaration, a derived type name declared using a record structure declaration may be the same as the name of an intrinsic type.

In place of the name of a component, %FILL can be used in a component_def_stmt in a record structure declaration. A %FILL component is used as a place-holder to achieve desired alignment of data in a record structure declaration. Initialization cannot be specified for a %FILL component. Each instance of %FILL in a record structure declaration is treated as a unique component name, different from the names of all other components you specified for the type, and different from all other %FILL components. %FILL is a keyword and is not affected by the -qmixed compiler option.

Each instance of a nested structure that has no name is treated as if it had a unique name, different from the names of all other accessible entities.

As an extension to the rules described on derived types thus far, the direct components of a derived type declared using a record structure declaration are:

The non-filler ultimate components of a derived type are the ultimate components of the derived type that are also direct components.

Prior to the introduction of XL Fortran 7.1.0 an object of a derived type that had default initialization could not be in a common block. This is now permitted as an extension. You must still ensure that a common block is not initialized in more than one scoping unit.

Examples of Declaring Record Structures

Example 1: Nested record structure declarations - named and unnamed

        STRUCTURE /S1/
          STRUCTURE /S2/ A ! A is a component of S1 of type S2
            INTEGER I
          END STRUCTURE
          STRUCTURE B ! B is a component of S1 of unnamed type
            INTEGER J
          END STRUCTURE
        END STRUCTURE
        RECORD /S1/ R1
        RECORD /S2/ R2 ! Type S2 is accessible here.
        R2.I = 17
        R1.A = R2
        R1.B.J = 13
        END

Example 2: Parameter statement nested in a structure declaration

        INTEGER I
        STRUCTURE /S/
          INTEGER J
          PARAMETER(I=17, J=13) ! Declares I and J in scope of program unit to
                                ! be named constants
        END STRUCTURE
        INTEGER J ! Confirms implicit typing of named constant J
        RECORD /S/ R
        R.J = I + J
        PRINT *, R.J ! Prints 30
        END

Example 3: %FILL fields

        STRUCTURE /S/
          INTEGER I, %FILL, %FILL(2,2), J
          STRUCTURE /S2/ R1, %FILL, R2
            INTEGER I
          END STRUCTURE
        END STRUCTURE
        RECORD /S/ R
        PRINT *, LOC(R%J)-LOC(R%I)  ! Prints 24 with -qintsize=4
        PRINT *, LOC(R%R2)-LOC(R%R1) ! Prints 8 with -qintsize=4
        END

Storage Mapping

A derived type declared using a record structure declaration is a sequence derived type. In memory, objects of such a type will have the components stored in the order specified. The same is true of objects of a sequence derived type declared using a standard derived type declaration.

The -qalign option specifies the alignment of data objects in storage, which avoids performance problems with misaligned data. Both the [no]4k and struct suboptions can be specified and are not mutually exclusive. The default setting is -qalign=no4k:struct=natural. [no]4K is useful primarily in combination with logical volume I/O and disk striping.

+----------------------------End of IBM Extension----------------------------+

+-------------------------------IBM Extension--------------------------------+

Union and Map

A union declares a group of fields in the enclosing record structure that can share the data area in a program.

Unions and maps follow this syntax:

union_dcl:



          .----------------.
          V                |
>>-UNION----union_dcl_item-+-----------------------------------><
 
 
>>-END UNION---------------------------------------------------><
 
 

union_dcl_item:

>>-+-map_dcl--------+------------------------------------------><
   '-parameter_stmt-'
 
 

map_dcl:



        .--------------.
        V              |
>>-MAP----map_dcl_item-+---------------------------------------><
 
 
>>-END MAP-----------------------------------------------------><
 
 

map_dcl_item:

>>-+-struct_comp_dcl_item-+------------------------------------><
   '-record_stmt----------'
 
 

struct_comp_dcl_item:

>>-+-component_def_stmt---+------------------------------------><
   +-record_structure_dcl-+
   +-parameter_stmt-------+
   '-union_dcl------------'
 
 

A union declaration must be defined in a record structure, may be in a map declaration, and a map declaration must be in a union declaration. All declarations in a map_dcl_item within a union declaration must be of the same nesting level, regardless of which map_dcl they reside in. Therefore, no component name inside a map_dcl may appear in any other map_dcl on the same level.

A component declared within a map declaration must not have a POINTER or ALLOCATABLE attribute.

A record structure with union map must not appear in I/O statements.

The components declared in a map declaration share the same storage as the components declared in the other map declarations within a union construct. When you assign a value to one component in one map declaration, the components in other map declarations that share storage with this component may be affected.

The size of a map is the sum of the sizes of the components declared within it.

The size of the data area established for a union declaration is the size of the largest map defined for that union

A parameter_stmt in a map declaration or union construct declares entities in the scoping unit of the nearest enclosing program unit, interface body, or subprogram.

A %FILL field in a map declaration is used as a place-holder to achieve desired alignment of data in a record structure. Other non-filler components or part of the components in other map declarations that share the data area with a %FILL field are undefined.

If default initialization is specified in component_def_stmts in at least one map declaration in a union declaration, the last occurence of the initialization becomes the final initialization of the components.

If default initialization is specified in one of the union map declarations in a record structure, a variable of that type that will have its storage class assigned by default will be given

At any time, only one map is associated with the shared storage. If a component from another map is referenced, the associated map becomes unassociated and its components become undefined. The map referenced will then be associated with the storage.

If a component of map_dcl is entirely or partially mapped with the %FILL component of the other map_dcl in a union, the value of the overlap portion is undefined unless that component is initialized by default initialization or an assignment statement.

Examples of Union and Map

Example 1: The size of the union is equal to the size of the largest map in that union

     structure /S/
        union
          map
            integer*4  i, j, k
            real*8  r, s, t
          end map
          map
            integer*4  p, q
            real*4  u, v
          end map
        end union         ! Size of the union is 36 bytes.
      end structure
      record /S/ r

Example 2: The results of union map are different with different -qsave option and suboptions

      PROGRAM P
       CALL SUB
       CALL SUB
      END PROGRAM P
 
      SUBROUTINE SUB
        LOGICAL, SAVE :: FIRST_TIME = .TRUE.
        STRUCTURE /S/
          UNION
            MAP
              INTEGER I/17/
            END MAP
            MAP
              INTEGER J
            END MAP
          END UNION
        END STRUCTURE
        RECORD /S/ LOCAL_STRUCT
        INTEGER LOCAL_VAR
 
        IF (FIRST_TIME) THEN
          LOCAL_STRUCT.J = 13
          LOCAL_VAR = 19
          FIRST_TIME = .FALSE.
        ELSE
          ! Prints " 13" if compiled with -qsave or -qsave=all
          ! Prints " 13" if compiled with -qsave=defaultinit
          ! Prints " 17" if compiled with -qnosave
          PRINT *, LOCAL_STRUCT%j
          ! Prints " 19" if compiled with -qsave or -qsave=all
          ! Value of LOCAL_VAR is undefined otherwise
          PRINT *, LOCAL_VAR
        END IF
      END SUBROUTINE SUB

Example 3: The last occurrence of default initialization in a map declaration within a union structure becomes the final initialization of the component

        structure /st/
          union
            map
              integer  i /3/, j /4/
              union
                map
                  integer  k /8/, l /9/
                end map
              end union
            end map
            map
              integer  a, b
              union
                map
                  integer  c /21/
                end map
              end union
            end map
          end union
        end structure
        record /st/ R
        print *, R.i, R.j, R.k, R.l      ! Prints "3 4 21 9"
        print *, R.a, R.b, R.c           ! Prints "3 4 21"
        end

Example 4: The following program is compiled with -qintsize=4 and -qalign=struct=pack, the components in the union MAP are aligned and packed

        structure /s/
          union
            map
              integer*2  i /z'1a1a'/, %FILL, j /z'2b2b'/
            end map
            map
              integer  m, n
            end map
          end union
        end structure
        record /s/ r
 
        print '(2z6.4)', r.i, r.j      ! Prints "1A1A  2B2B"
        print '(2z10.8)', r.m, r.n     ! Prints "1A1A0000  2B2B0000" however
                                       ! the two bytes in the lower order are
                                       ! not guaranteed.
        r.m = z'abc00cba'              ! Components are initialized by
                                       ! assignment statements.
        r.n = z'02344320'
 
        print '(2z10.8)', r.m, r.n     ! Prints "ABC00CBA  02344320"
        print '(2z6.4)', r.i, r.j      ! Prints "ABC0  0234"
        end

+----------------------------End of IBM Extension----------------------------+


[ Top of Page | Previous Page | Next Page | Table of Contents | Index ]