<< >> Title Contents Index Home Help

2 Data Types


Every Fortran element and expression has a data type. The data type of an element may be implicit in its definition or explicitly attached to the element in a declaration statement. This chapter describes the Fortran data types and constants that pgf77 supports.

Table 2-1 lists the standard Fortran 77 data types. Table 2-2 shows additional data types that pgf77 Fortran supports.

Data Type
Value
INTEGER
An integer number.
REAL
A real number.
DOUBLE PRECISION
A double precision floating point number (real number) taking up two numeric storage units and whose precision is greater than REAL.
LOGICAL
A value which can be either true or false.
COMPLEX
A pair of real numbers used in complex arithmetic.
CHARACTER
A string consisting of one or more printable characters.
A symbolic name for a data type can be followed by a data type length specifier of the form *s, where s is one of the acceptable lengths for the data type being declared. Such a specification overrides the length attribute that the statement implies and assigns a specific length to the specified item, regardless of the compiler options specified. For example, REAL*8 is equivalent to DOUBLE PRECISION. Table 2-2 shows the lengths of data types, their meanings, and their sizes.

Type

Meaning

Size

LOGICAL*1
Small LOGICAL
1 byte
LOGICAL*2
Short LOGICAL
2 bytes
LOGICAL*4
LOGICAL
4 bytes
LOGICAL*8
LOGICAL (extended - this is not available for
all hardware.)
8 bytes
BYTE
Small INTEGER
1 byte
INTEGER*1
Same as BYTE
1 byte
INTEGER*2
Short INTEGER
2 bytes
INTEGER*4
INTEGER
4 bytes
INTEGER*8
INTEGER (extended - this is not available for
all hardware.)
8 bytes
REAL*4
REAL
4 bytes
REAL*8
DOUBLE PRECISION
8 bytes
COMPLEX*8
COMPLEX
8 bytes
COMPLEX*16
DOUBLE COMPLEX
16 bytes

The BYTE type is treated as a signed one-byte integer and is equivalent to LOGICAL*1.

Assignment of a value too big for the data type to which it is assigned is an undefined operation.

A specifier is allowed after a CHARACTER function name even if the CHARACTER type word has a specifier. For example:

CHARACTER*4 FUNCTION C*8 (VAR1)
Above, the function size specification C*8 overrides the CHARACTER*4 specification. Logical data items can be used with any operation where a similar sized integer data item is permissible and vice versa. The logical data item is treated as an integer or the integer data item is treated as a logical of the same size and no type conversion is performed.

@ Floating point data items of type REAL or DOUBLE PRECISION may be used as array subscripts, in computed GOTOs, in array bounds and in alternate returns. pgf77 converts the floating point number to an integer.

The data type of the result of an arithmetic expression corresponds to the type of its data. The type of an expression is determined by the rank of its elements. Table 2-3 shows the ranks of the various data types, from lowest to highest.

Data Type

Rank

LOGICAL
1 (lowest)
LOGICAL*8
2 (extended - this is not available for
all hardware.)
INTEGER*2
3
INTEGER*4
4
INTEGER*8
5 (extended - this is not available for
all hardware.)
REAL*4
6
REAL*8 (Double precision)
7
COMPLEX*8 (Complex)
8
COMPLEX*16 (Double complex)
9 (highest)

The data type of a value produced by an operation on two arithmetic elements of different data types is the data type of the highest-ranked element in the operation. The exception to this rule is that an operation involving a COMPLEX*8 element and a REAL*8 element produces a COMPLEX*16 result. In this operation, the COMPLEX*8 element is converted to a COMPLEX*16 element, which consists of two REAL*8 elements, before the operation is performed.

In most cases, a logical expression will have a LOGICAL*4 result. In cases where the hardware supports LOGICAL*8 and if the expression is LOGICAL*8, the result may be LOGICAL*8.

2.1 Constants

A constant is an unchanging value. It takes a form corresponding to one of the data types.

The compiler supports octal, hexadecimal and Hollerith constants. The use of character constants in a numeric context, for example, in the right-hand side of an arithmetic assignment statement, is supported. These constants assume a data type that conforms to the context in which they appear.

2.1.1 Integer Constants

The form of a decimal integer constant is:

[s]d1d2...dn
where di is a digit in the range 0 to 9 and where s is an optional sign. The value of an integer constant must be within the range -2147483648 to 2147483647 inclusive
(-231 to (231 - 1)). Integer constants assume a data type of INTEGER*4 and have a 32-bit storage requirement.

The range, data type and storage requirement change if the -i8 flag is specified (this flag is only available on systems where the hardware supports it). With the -i8 flag, the range for integer constants is -263 to (263 - 1)). The value of an integer constant must be within the range -9223372036854775808 to 9223372036854775807. If the constant does not fit in a INTEGER*4 range, the data type is INTEGER*8 and the storage requirement is 64 bits.

Below are several examples of integer constants.

+2
-36
437

2.1.2 Real Constants

Real constants have two forms, scaled and unscaled. An unscaled real constant consists of a signed or unsigned decimal number. A scaled real constant takes the same form as an unscaled constant, but is followed by a scaling factor using the form:

E+digits
Edigit
E-digits
where digits is the scaling factor (the power of ten) to be applied to the unscaled constant. The first two forms above are equivalent, that is, a scaling factor without a sign is assumed to be positive.

Constant
Value
1.0
unscaled single precision constant
1.
unscaled single precision constant
-1.0
signed unscaled single precision constant
6.1E2
is equivalent to 610.0
+2.3E3
is equivalent to 2300.0
-3.5E-1
is equivalent to -0.35

2.1.3 Double Precision Constants

A double precision constant has the same form as a scaled real constant except that the E is replaced by D. Table 2-5 shows several double precision constants.

6.1D2
is equivalent to 610.0
+2.3D3
is equivalent to 2300.0
-3.5D-1
is equivalent to -0.35
+4D4
is equivalent to 40000

2.1.4 Logical Constants

A logical constant is one of:

.TRUE.
.FALSE.
The logical constants .TRUE. and .FALSE. are defined to be the four-byte values -1 and 0 respectively. A logical expression is defined to be .TRUE. if its least significant bit is 1 and .FALSE. otherwise.[*]

The data type and storage requirements change with the -i8 or -i8storage flag to LOGICAL*8 , requiring 8-byte values (these flags are only available on hardware supporting 64 bit values).

The abbreviations T and F can be used in place of .TRUE. and .FALSE. in data initialization statements and in namelist input.

2.1.5 Complex Constants

A complex constant is held as two real constants separated by a comma and surrounded by parentheses. The first real number is the real part and the second real number is the imaginary part. Together these values represent a complex number. Below are several examples:

(3.5,-3.5)
(6.1E2,+2.3E3)

2.1.6 Character Constants

Character string constants may be delimited using either an apostrophe (') or a double quote ("). The apostrophe or double quote acts as a delimiter and is not part of the character constant. Use two apostrophes together to include an apostrophe as part of the expression. If a string begins with one variety of quote mark, the other may be embedded within it without using the repeated quote or backslash escape. Within character constants, blanks are significant. The length of the string must be at least one character. For further information on the use of the backslash character, refer to -Mbackslash in the pgf77 User's Guide.

Below are several examples of character constants.

'abc'
'abc '
'ab''c'
@ If a character constant is used in a numeric context, for example as the expression on the right side of an arithmetic assignment statement, it is treated as a Hollerith constant. The rules for typing and sizing character constants used in a numeric context are outlined later in the description of Hollerith constants.

2.1.7 Octal and Hexadecimal Constants

The form of an octal constant is:

'c1c2...cn'O
The form of a hexadecimal constant is:
'a1a2...an'X
or
@	    x'a1a2...an'
where ci is a digit in the range 0 to 7 and ai is a digit in the range 0 to 9 or a letter in the range A to F or a to f (case mixing is allowed). You can specify up to 64 bits (22 octal digits or 16 hexadecimal digits).

Octal and hexadecimal constants are stored as either 32-bit or 64-bit quantities. They are padded on the left with zeroes if needed and assume data types based on how they are used.

The following are the rules for converting these data types:

In the example below, the constant I (of type INTEGER*4) and the constant J (of type INTEGER*2) will have hex values 1234 and 4567, respectively. The variable D (of type REAL*8) will have the hex value x4000012345678954 after its second assignment:
	I = '1234'X       ! Leftmost Pad with zero.
J = '1234567'X ! Truncate Leftmost 3 hex digits
D = '40000123456789ab'X
D = NEQV(D,'ff'X) ! 64-bit Exclusive Or

2.1.8 Hollerith Constants

The form of a Hollerith constant is:

nHc1c2...cn
where n specifies the positive number of characters in the constant and cannot exceed 2000 characters. A Hollerith constant is stored as a byte string with four characters per 32-bit word. Hollerith constants are untyped arrays of INTEGER*4. The last word of the array is padded on the right with blanks if necessary. Hollerith constants cannot assume a character data type and cannot be used where a character value is expected. Hollerith constants are permitted with the %REF built-in function (for more information on the built-in VAX/VMS functions, see Appendix B, VAX System Subroutines and Built-in Functions.) The data type of a Hollerith constant used in a numeric expression is determined by the following rules: When the length of the Hollerith constant is less than the length implied by the data type, spaces are appended to the constant on the right. When the length of the constant is greater than the length implied by the data type, the constant is truncated on the right.

2.2 Arrays

An array is a group of consecutive, contiguous storage locations associated with a symbolic name which is the array name. Each individual element of storage, called the array element, is referenced by the array name modified by a list of subscripts. Arrays are declared with type declaration statements, DIMENSION statements and COMMON statements; they are not defined by implicit reference. These declarations will introduce an array name and establish the number of dimensions and the bound of each dimension. If a symbol, modified by a list of subscripts is not defined as an array, then it will be assumed to be a FUNCTION reference with an argument list.

2.2.1 An Array Declaration Element

An array declaration has the following form:

name([lb:]ub[,[lb:]ub]... )
where name is the symbolic name of the array, lb is the specification of the lower bound of the dimension and ub is the specification of the upper bound. The upper bound, ub must be greater than the lower bound lb. The values lb and ub may be negative. The bound lb is taken to be 1 if it is not specified. The difference (ub-lb+1) specifies the number of elements in that dimension. The number of lb,ub pairs specifies the dimension of the array. The total amount of storage of the array is:
(ub-lb+1)*(ub-lb+1)*...
However, the dimension specifiers of a subroutine argument may themselves be subroutine arguments or members of COMMON.

2.2.2 Deferred Shape Arrays

Deferred-shape arrays are those arrays whose shape can be changed by an executable statement. Deferred shape arrays are declared with a rank, but with no bounds information. They assume their shape when either an ALLOCATE statement or a REDIMENSION statement is encountered.

For example, the following statement declares a deferred shape REAL array A with two dimensions.

REAL A(:, :)

2.2.3 Subscripts

A subscript is used to locate an array element for access. An array name qualified by a subscript list has the following form:

name(sub[,sub]...)
where there must be one sub entry for each dimension in array name.

Each sub must be an integer expression yielding a value which is within the range of the lower and upper bounds. Arrays are stored as a linear sequence of values in memory and are held such that the first element is in the first store location and the last element is in the last store location. In a multi-dimensional array the first subscript varies more rapidly than the second, the second more rapidly than the third, and so on (column major order).

2.2.4 Character substring

A character substring is a contiguous portion of a character variable and is of type character. A character substring can be referenced, assigned values and named. It can take either of the following forms:

character_variable_name (x1 : x2)
character_array (subscripts) (x1 : x2)
where x1 and x2 are integers and x1 denotes the left-hand character position and x2 the right-hand one. These are known as substring expressions. In substring expressions x1 must be both greater than or equal to 1 and less than x2 and x2 must be less than or equal to the length of the character variable or array element.

For example:

J(2:4)
the characters in positions 2 to 4 of character variable J.
K(3,5)(1:4)
the characters in positions 1 to 4 of array element K(3,5).
A substring expression can be any valid integer expression and may contain array element or function references.

2.3 Structures@

A structure is a user-defined aggregate data type having the following form:

STRUCTURE [/structure_name/][field_namelist]
field_declaration
[field_declaration]
... [field_declaration]
END STRUCTURE
Where:
structure_name
is unique and is used both to identify the structure and to allow its use in subsequent RECORD statements.
field_namelist
is a list of fields having the structure of the associated structure declaration. A field_namelist is allowed only in nested structure declarations.
field_declaration
can consist of any combination of substructure declarations, typed data declarations, union declarations or unnamed field declarations.
Fields within structures conform to machine-dependent alignment requirements. Alignment of fields also provides a C-like "struct" building capability and allows convenient inter-language communications.

Field names within the same declaration nesting level must be unique, but an inner structure declaration can include field names used in an outer structure declaration without conflict. Also, because records use periods to separate fields, it is not legal to use relational operators (for example, .EQ., .XOR.), logical constants (.TRUE. or .FALSE.), or logical expressions (.AND., .NOT., .OR.) as field names in structure declarations.

Fields in a structure are aligned as required by hardware; therefore a structure's storage requirements are machine-dependent. Because explicit padding of records is not necessary, the compiler recognizes the %FILL intrinsic, but performs no action in response to it.

Data initialization can occur for the individual fields.

2.3.1 Records@

A record is a user-defined aggregate data item having the following form:

RECORD /structure_name/record_namelist
[,/structure_name/record_namelist]
... [,/structure_name/record_namelist]
Where:
structure_name
is the name of a previously declared structure.
record_namelist
is a list of one or more variable or array names separated by commas.
You create memory storage for a record by specifying a structure name in the RECORD statement. You define the field values in a record either by defining them in the structure declaration or by assigning them with executable code.

You can access individual fields in a record by combining the parent record name, a period (.), and the field name (for example, recordname.fieldname). For records, a scalar reference means a reference to a name that resolves to a single typed data item (for example, INTEGER), while an aggregate reference means a reference that resolves to a structured data item.

Scalar field references may appear wherever normal variable or array elements may appear with the exception of COMMON, SAVE, NAMELIST, DATA and EQUIVALENCE statements. Aggregate references may only appear in aggregate assignment statements, unformatted I/O statements, and as parameters to subprograms.

The following is an example of RECORD and STRUCTURE usage.

	STRUCTURE /person/    ! Declare a structure to define a person
INTEGER id
LOGICAL living
CHARACTER*5 first, last, middle
INTEGER age
END STRUCTURE
! Define population to be an array where each element is of
! type person. Also define a variable, me, of type person.
RECORD /person/ population(2), me
...
me.age = 34 ! Assign values for the variable me to
me.living = .TRUE. ! some of the fields.
me.first = 'Steve'
me.id = 542124822
...
population(1).last = 'Jones' ! Assign the "last" field of
! element 1 of array population.
population(2) = me ! Assign all the values of record
! "me" to the record population(2)

2.3.2 UNION and MAP Declarations@

A UNION declaration is a multi-statement declaration defining a data area that can be shared intermittently during program execution by one or more fields or groups of fields. It declares groups of fields that share a common location within a structure. Each group of fields within a union declaration is declared by a MAP declaration, with one or more fields per MAP declaration.

Union declarations are used when one wants to use the same area of memory to alternately contain two or more groups of fields. Whenever one of the fields declared by a union declaration is referenced in a program, that field and any other fields in its map declaration become defined. Then, when a field in one of the other map declarations in the union declaration is referenced, the fields in that map declaration become defined, superseding the fields that were previously defined.

A union declaration is initiated by a UNION statement and terminated by an END UNION statement. Enclosed within these statements are one or more map declarations, initiated and terminated by MAP and END MAP statements, respectively. Each unique field or group of fields is defined by a separate map declaration. The format of a UNION statement is as follows:

UNION
map_declaration
[map_declaration]
...
[map_declaration]
END UNION
The format of the map_declaration is as follows:
MAP
field_declaration
[field_declaration]
...
[field_declaration]
END MAP
where field_declaration is a structure declaration or RECORD statement contained within a union declaration, a union declaration contained within a union declaration, or the declaration of a typed data field within a union.

Data can be initialized in field declaration statements in union declarations. Note, however, it is illegal to initialize multiple map declarations in a single union.

Field alignment within multiple map declarations is performed as previously defined in structure declarations.

The size of the shared area for a union declaration is the size of the largest map defined for that union. The size of a map is the sum of the sizes of the field(s) declared within it plus the space reserved for alignment purposes.

Manipulating data using union declarations is similar to what happens using EQUIVALENCE statements. However, union declarations are probably more similar to union declarations for the language C. The main difference is that the language C requires one to associate a name with each "map" (union). Fortran field names must be unique within the same declaration nesting level of maps.

The following is an example of RECORD, STRUCTURE, MAP and UNION usage. The size of each element of the recarr array would be the size of typetag (4 bytes) plus the size of the largest MAP, the employee map (24 bytes).

        STRUCTURE /account/
INTEGER typetag ! Tag to determine defined map.
UNION
MAP ! Structure for an employee
CHARACTER*12 ssn ! Social Security Number
REAL*4 salary
CHARACTER*8 empdate ! Employment date
END MAP
MAP ! Structure for a customer
INTEGER*4 acct_cust
REAL*4 credit_amt
CHARACTER*8 due_date
END MAP
MAP ! Structure for a supplier
INTEGER*4 acct_supp
REAL*4 debit_amt
BYTE num_items
BYTE items(12) ! Items supplied
END MAP
END UNION
END STRUCTURE RECORD /account/ recarr(1000)

2.3.3 Data Initialization

@ Within data type declaration statements, data initialization is allowed. Data is initialized by placing values bounded by slashes immediately following the symbolic name (variable or array) to be initialized. Initialization of fields within structure declarations is allowed, but initialization of unnamed fields and records is not.

Hollerith, octal and hexadecimal constants can be used to initialize data in both data type declarations and in DATA statements. Truncation and padding occur for constants that differ in size from the declared data item (as specified in the discussion of constants above).

2.4 Pointer Variables @

The POINTER statement declares a scalar variable to be a pointer variable (of data type INTEGER), and another variable to be its pointer-based variable.

The syntax of the POINTER statement is:

POINTER (p1, v1) [, (p2, v2) ...]
v1 and v2
are pointer-based variables. A pointer-based variable can be of any type, including STRUCTURE. A pointer-based variable can be dimensioned in a separate type, in a DIMENSION statement, or in the POINTER statement. The dimension expression may be adjustable, where the rules for adjustable dummy arrays regarding any variables which appear in the dimension declarators apply.
p1 and p2
are the pointer variables corresponding to v1 and v2. A pointer variable may not be an array. The pointer is an integer variable containing the address of a pointer-based variable. The storage located by the pointer variable is defined by the pointer-based variable (for example, array, data type, etc.). A reference to a pointer-based variable appears in Fortran statements like a normal variable reference (for example, a local variable, a COMMON block variable, or a dummy variable). When the based variable is referenced, the address to which it refers is always taken from its associated pointer (that is, its pointer variable is dereferenced).
The pointer-based variable does not have an address until its corresponding pointer is defined. The pointer is defined in one of the following ways: The following code illustrates the use of pointers:
	REAL XC(10)
COMMON IC, XC
POINTER (P, I)
POINTER (Q, X(5))
P = LOC(IC)
I = 0 ! IC gets 0
P = LOC(XC)
Q = P + 20 ! same as LOC(XC(6))
X(1) = 0 ! XC(6) gets 0 ALLOCATE (X) ! Q locates an allocated memory area

2.4.1 Restrictions

The following restrictions apply to the POINTER statement:

[*] The option -Munixlogical defines a logical expression to be true if its value is non-zero and false otherwise; also, the internal value of .TRUE. is 1. Refer to the pgf77 User's Guide for details.


<< >> Title Contents Index Home Help