Chapter 6. Outmoded Features

This chapter describes outmoded Fortran features that the CF90 and MIPSpro 7 Fortran 90 compilers support. These features have been replaced by alternatives that enhance the portability of CF90 and MIPSpro 7 Fortran 90 programs. None of the outmoded features described in this chapter were part of any Fortran standard; they were extensions supported in older Cray Research compilers. The outmoded features and their preferred alternatives are listed in Table 6-1.

Table 6-1. Outmoded features and preferred alternatives

Outmoded feature

Preferred alternative

Hollerith data

Character data.

ENCODE and DECODE

Internal files.

Asterisk character constant delimiters in formats

Apostrophe or quotation mark delimiters.

[-b]X edit descriptor

TL edit descriptor, 1X.

A descriptor used for noncharacter data and R descriptor

Character type and other conventional matchings of data with descriptors.

EOF, IEOF, and IOSTAT functions

End-of-file specifier (END=) or status specifier (IOSTAT=).

Initialization using long strings

Replace the numeric target with a character item. Replace a Hollerith constant with a character constant.

IMPLICIT UNDEFINED

IMPLICIT NONE

Type statements with *n

Standard type statements (KIND=).

Two-branch arithmetic IF

IF construct or IF statement.

TASK COMMON statement

TASKCOMMON compiler directive.

Indirect logical IF

IF construct or IF statement.

Nested loops ending with a single, labeled END DO

One END DO statement for each loop.

DOUBLE COMPLEX statement and related specific intrinsic function names

COMPLEX (KIND=) statement and standard intrinsic functions. See “DOUBLE COMPLEX Statement (UNICOS Systems Only)”, for more information.

Bitwise intrinsic functions

Standard intrinsic functions. See “Bitwise Logical Expressions”, for more information.

CLOCK(3i), DATE(3i), and JDATE(3i) intrinsic functions

DATE_AND_TIME(3i) intrinsic subroutine.

DCOT(3m) intrinsic function

COT(3m) intrinsic function.

DFLOAT(3m) and DREAL(3m) intrinsic functions

REAL(3m) intrinsic function.

NUMARG(3i) intrinsic function

PRESENT(3i) intrinsic function for optional arguments.

RANF(3i) and RANGET(3i) intrinsic functions

RANDOM_NUMBER(3i) intrinsic subroutine.

RANSET(3i) intrinsic function

RANDOM_SEED(3i) intrinsic subroutine.

RTC(3i) intrinsic function

SYSTEM_CLOCK(3i) intrinsic subroutine.


Hollerith Type

Hollerith data is a sequence of any characters capable of internal representation as specified in Table 3-1. Its length is the number of characters in the sequence, including blank characters. Each character occupies a position within the storage sequence identified by one of the numbers 1, 2, 3, . . . indicating its placement from the left (position 1). Hollerith data must contain at least one character.

Hollerith Constants

A Hollerith constant is expressed in one of three forms. The first of these is specified as a nonzero integer constant followed by the letter H, L, or R and as many characters as equal the value of the integer constant. The second form of Hollerith constant specification delimits the character sequence between a pair of apostrophes followed by the letter H, L, or R. The third form is like the second, except that quotation marks replace apostrophes. For example:

Character sequence:     ABC 12
Form 1:                 6HABC 12
Form 2:                 'ABC 12'H
Form 3:                 "ABC 12"H 

Two adjacent apostrophes or quotation marks appearing between delimiting apostrophes or quotation marks are interpreted and counted by the compiler as a single apostrophe or quotation mark within the sequence. Thus, the sequence DON'T USE "*" would be specified with apostrophe delimiters as 'DON''T USE "*"'H, and with quotation mark delimiters as "DON'T USE ""*"""H.

Each character of a Hollerith constant is represented internally by an 8-bit code, with up to 32 such codes allowed. This limit corresponds to the size of the largest numeric type, COMPLEX(KIND = 16). The ultimate size and makeup of the Hollerith data depends on the context. If the Hollerith constant is larger than the size of the type implied by context, the constant is truncated to the appropriate size. If the Hollerith constant is smaller than the size of the type implied by context, the constant is padded with a character dependent on the Hollerith indicator. When an H Hollerith indicator is used, the truncation and padding is done on the right end of the constant. The pad character is the blank character code (20).

Null codes can be produced in place of blank codes by substituting the letter L for the letter H in the Hollerith forms described above. The truncation and padding is also done on the right end of the constant, with the null character code (00) as the pad character.

Using the letter R instead of the letter H as the Hollerith indicator means truncation and padding is done on the left end of the constant with the null character code (00) used as the pad character.

All of the following Hollerith constants yield the same Hollerith constant and differ only in specifying the content and placement of the unused portion of the single 64-bit entity containing the constant:

Hollerith

Internal byte, beginning on bit:

constant

0

8

16

24

32

40

48

56

6HABCDEF

A

B

C

D

E

F

2016

2016

'ABCDEF'H

A

B

C

D

E

F

2016

2016

"ABCDEF" H

A

B

C

D

E

F

2016

2016

6LABCDEF

A

B

C

D

E

F

00

00

'ABCDEF'L

A

B

C

D

E

F

00

00

"ABCDEF"L

A

B

C

D

E

F

00

00

6RABCDEF

00

00

A

B

C

D

E

F

'ABCDEF'R

00

00

A

B

C

D

E

F

"ABCDEF"R

00

00

A

B

C

D

E

F

A Hollerith constant is limited to 32 characters except when specified in a CALL statement, a function argument list, or a DATA statement. An all-zero computer word follows the last word containing a Hollerith constant specified as an actual argument in an argument list.

A character constant of 32 or fewer characters is treated as if it were a Hollerith constant in situations where a character constant is not allowed by the standard but a Hollerith constant is allowed by the CF90 and MIPSpro 7 Fortran 90 compilers. If the character constant appears in a DATA statement value list, it can be longer than 32 characters.

Hollerith Values

A Hollerith value is a Hollerith constant or a variable that contains Hollerith data. A Hollerith value is limited to 32 characters.

A Hollerith value can be used in any operation in which a numeric constant can be used. It can also appear on the right-hand side of an assignment statement in which a numeric constant can be used. It is truncated or padded to be the correct size for the type implied by the context.

Hollerith Relational Expressions

Used with a relational operator, the Hollerith value e1 is less than e2 if its value precedes the value of e2 in the collating sequence and is greater if its value follows the value of e2 in the collating sequence.

The following examples are evaluated as true if the integer variable LOCK contains the Hollerith characters K, E, and Y in that order and left-justified with five trailing blank character codes:

3HKEY.EQ.LOCK
'KEY'.EQ.LOCK
LOCK.EQ.LOCK
'KEY1'.GT.LOCK
'KEY0'H.GT.LOCK

Formatted I/O and Internal Files

A formatted I/O operation defines entities by transferring data between I/O list items and records of a file. The file can be on an external media or in internal storage.

The Fortran standard provides READ and WRITE statements for both formatted external and internal file I/O. This is the preferred method for formatted internal file I/O. It is the only method for list-directed internal file I/O.

The ENCODE and DECODE statements are an alternative to standard Fortran READ and WRITE statements for formatted internal file I/O.

An internal file in standard Fortran I/O must be declared as character, while the internal file in ENCODE and DECODE statements can be any data type. A record in an internal file in standard Fortran I/O is either a scalar character variable or an array element of a character array. The record size in an internal file in an ENCODE or DECODE statement is independent of the storage size of the variable used as the internal file. If the internal file is a character array in standard Fortran I/O, multiple records can be read or written with internal file I/O. The alternative form does not provide the multiple record capability.

ENCODE Statement

The ENCODE statement provides a method of converting or encoding the internal representation of the entities in the output list to a character representation. The format of the ENCODE statement is as follows:

ENCODE ( n, f, dest ) [elist]
n

Number of characters to be processed. Nonzero integer expression not to exceed the maximum record length for formatted records. This is the record size for the internal file.

f

Format identifier. It cannot be an asterisk.

dest

Name of internal file. It can be a variable or array of any data type. It cannot be an array section, a zero-sized array, or a zero-sized character variable.

elist

Output list to be converted to character during the ENCODE statement.

The output list items are converted using format f to produce a sequence of n characters that are stored in the internal file dest. The n characters are packed 8 characters per word on UNICOS and UNICOS/mk systems. The n characters are packed 4 characters per word on IRIX systems.

An ENCODE statement transfers one record of length n to the internal file dest. If format f attempts to write a second record, ENCODE processing repositions the current record position to the beginning of the internal file and begins writing at that position.

An error is issued when the ENCODE statement attempts to write more than n characters to the record of the internal file. If dest is a noncharacter entity and n is not a multiple of 8 (for UNICOS and UNICOS/mk systems) or 4 (for IRIX systems), the last word of the record is padded with blanks to a word boundary. If dest is a character entity, the last word of the record is not padded with blanks to a word boundary.

Example 1: The following example assumes a machine word length of 64 bits and uses the underscore character (_) as a blank:

      INTEGER ZD(5), ZE(3)
      ZD(1)='THIS____'
      ZD(2)='MUST____'
      ZD(3)='HAVE____'
      ZD(4)='FOUR____'
      ZD(5)='CHAR____'
1     FORMAT(5A4)
      ENCODE(20,1,ZE)ZD
      DO 10 I=1,3
        PRINT 2,'ZE(',I,')="',ZE(I),'"'
10    CONTINUE
2     FORMAT(A,I2,A,A8,A)
      END

On UNICOS systems, the output is as follows:

>ZE( 1)="THISMUST"
>ZE( 2)="HAVEFOUR"
>ZE( 3)="CHAR____"

Example 2: On IRIX systems, the comparable example would be as follows:

      INTEGER ZD(5), ZE(3)
      ZD(1)='TH__'
      ZD(2)='IS__'
      ZD(3)='=4__'
      ZD(4)='CH__'
      ZD(5)='AR__'
1     FORMAT(5A2)
      ENCODE(10,1,ZE)ZD
      DO 10 I=1,3
      PRINT 2,'ZE(',I,')="',ZE(I),'"'
10    CONTINUE
2     FORMAT(A,I2,A,A4,A)
      END

The output is as follows:

>ZE( 1)="THIS"
>ZE( 2)="=4CH"
>ZE( 3)="AR__"

DECODE Statement

The DECODE statement provides a method of converting or decoding from a character representation to the internal representation of the entities in the input list. The format of the DECODE statement is as follows:

DECODE ( n, f, source ) [dlist]
n

Number of characters to be processed. Nonzero integer expression not to exceed the maximum record length for formatted records. This is the record size for the internal file.

f

Format identifier. It cannot be an asterisk.

source

Name of internal file. It can be a variable or array of any data type. It cannot be an array section or a zero-sized array or a zero-sized character variable.

dlist

Input list to be converted from character during the DECODE statement.

The input list items are converted using format f from a sequence of n characters in the internal file source to an internal representation and stored in the input list entities. If the internal file source is noncharacter, the internal file is assumed to be a multiple of 8 characters (for UNICOS and UNICOS/mk systems) or 4 characters (for IRIX systems).

Example 1: On UNICOS systems, an example of a DECODE statement is as follows:

      INTEGER ZD(4), ZE(3)
      ZE(1)='WHILETHI'
      ZE(2)='S HAS  F'
      ZE(3)='IVE     '
3     FORMAT(4A5)
      DECODE(20,3,ZE)ZD
      DO 10 I=1,4
         PRINT 2,'ZD(',I,')="',ZD(I),'"'
10    CONTINUE
2     FORMAT(A,I2,A,A8,A)
      END

The output is as follows:

>ZD( 1)="WHILE   "
>ZD( 2)="THIS    "
>ZD( 3)="HAS     "
>ZD( 4)="FIVE    "

Example 2: On IRIX systems, an example of a DECODE statement is as follows:

      INTEGER ZD(5), ZE(4)
      ZE(1)='WHIL'
      ZE(2)='E_IT'
      ZE(3)='=4CH'
      ZE(4)='ARS_'
      ZE(5)='RS.+'
3     FORMAT(5A3)
      DECODE(16,3,ZE)ZD
      DO 10 I=1,4
         PRINT 2,'ZD(',I,')="',ZD(I),'"'
10    CONTINUE
2     FORMAT(A,I2,A,A4,A)
      END

The output is as follows:

>ZD( 1)="WHI_"
>ZD( 2)="LE__"
>ZD( 3)="IT=_"
>ZD( 4)="4CH_"
>ZD( 5)="ARS_"

Edit Descriptors

The following sections show obsolete edit descriptors and outmoded uses of current descriptors.

Asterisk Delimiters

The asterisk was allowed to delimit a literal character constant. It has been replaced by the apostrophe and quotation mark.

*h1 h2 ... hn*
*

Delimiter for a literal character string

h

Any ASCII character indicated by a C in Table 3-1 (that is, capable of internal representation)

Example:

*AN ASTERISK EDIT DESCRIPTOR* 

Negative-valued X Descriptor

A negative value could be used with the X descriptor to indicate a move to the left. This has been replaced by the TL descriptor.

[-b]X
b

Any nonzero, unsigned integer constant

X

Indicates a move of as many positions as indicated by b

Example:

-55X   ! Moves current position 55 spaces left 

A and R Descriptors for Noncharacter Types

The Rw descriptor and the use of the Aw descriptor for noncharacter data are available primarily for programs that were written before a true character type was available. Other uses include adding labels to binary files and the transfer of data whose type is not known in advance.

List items can be of type real, integer, complex, or logical. For character use, the binary form of the data is converted to or from ASCII codes. The numeric list item is assumed to contain ASCII characters when used with these edit descriptors.

Complex items use two storage units and require two A descriptors, for the first and second storage units respectively.

The Aw descriptor works with noncharacter list items containing character data in essentially the same way as described in the Fortran Language Reference Manual, Volume 1. The Rw descriptor works like Aw with the following exceptions:

  • Characters in an incompletely filled input list item are right-justified with the remainder of that list item containing binary zeros.

  • Partial output of an output list item is from its rightmost character positions.

The following example shows the Aw and Rw edit descriptors for noncharacter data types:

      INTEGER IA
      LOGICAL LA
      REAL RA
      DOUBLE PRECISION DA
      COMPLEX CA
      CHARACTER*52 CHC
      CHC='ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz'
      READ(CHC,3) IA, LA, RA, DA, CA
3     FORMAT(A4,A8,A10,A17,A7,A6)
      PRINT 4, IA, LA, RA, DA, CA
4     FORMAT(1x,3(A8,'-'),A16,'-',2A8)
      READ(CHC,5) IA, LA, RA
5     FORMAT(R2,R8,R9)
      PRINT 4, IA, LA, RA
      END

On UNICOS and UNICOS/mk systems, the output of this program would be as follows:

> ABCD    -EFGHIJKL-OPQRSTUV-XYZabcdefghijklm-nopqrst uvwxyz
      ^^^^
> ooooooAB-CDEFGHIJ-LMNOPQRS-

The carat (^) indicates leading blanks in the use of the A edit descriptor. The lowercase letter o is used to indicate where binary zeros have been written with the R edit descriptor.

On IRIX systems, the output of this program would be as follows:

>     ABCD-    IJKL-    STUV-        fghijklm-    qrst    wxyz
 ^^^^^     ^^^^     ^^^^     ^^^^^^^^         ^^^^    ^^^^
>     AB-    GHIJ-    PQRS-
 ^^^^^         ^^^^     ^^^^

The binary zeros are not printable characters, so the printed output simply contains the characters without the binary zeros.

Type Declaration with Data Length

Data type declarations that include the data length are outmoded. The CF90 and MIPSpro 7 Fortran 90 compilers recognize this usage in type statements, IMPLICIT statements, and FUNCTION statements, mapping these numbers onto lengths appropriate for the target machine.

Format:

type[ *n]v[ , v] ...
IMPLICIT type[ *n] ( a1[ -a2][ , a1[ -a2]] ... )
[ , type ... ] ...
[type[ *n]] FUNCTION fun ([d[ , d] ... ])
type

Can be INTEGER, REAL, DOUBLE PRECISION, COMPLEX, or LOGICAL.

*n

Data length as shown in Table 6-2, Table 6-3, and Table 6-4. Any other data length generates an error.

v

Name of a constant, variable, or array declarator.

an

A letter. A range of letters is denoted by the first and last letters of the range separated by a hyphen. A range (a1 - an) has the same effect as a list of the letters (a1, a2, ... an).

fun

Name of the function subprogram.

d

Dummy argument representing a variable, array, or dummy procedure name.

The following tables show the data lengths for UNICOS, UNICOS/mk, and IRIX systems.


Note: : On UNICOS systems, a 32-bit item or a 46-bit item is contained in a 64-bit word.


Table 6-2. Data length (UNICOS systems)

type

n:

*1

*2

*4

*8

*16

*32

INTEGER

 

64-bit

64-bit

64-bit

64-bit

Error

Error

REAL

 

Error

Error

64-bit single precision

64-bit single precision

128-bit double precision

Error

COMPLEX

 

Error

Error

Error

128-bit single precision

128-bit single precision

256-bit double precision

LOGICAL

 

64-bit

64-bit

64-bit

64-bit

Error

Error

DOUBLE PRECISION

 

Error

Error

Error

Error

128-bit double precision

Error


Table 6-3. Data length (UNICOS/mk systems)

type

n:

*1

*2

*4

*8

*16

*32

INTEGER

 

32-bit

32-bit

32-bit

64-bit

Error

Error

REAL

 

Error

Error

32-bit single precision[a]

64-bit double precision[b]

64-bit double precision[c]

Error

COMPLEX

 

Error

Error

Error

64-bit single precision[d]

64-bit single precision[e]

64-bit single precision[f]

LOGICAL

 

32-bit

32-bit

32-bit

64-bit

Error

Error

DOUBLE PRECISION

 

Error

Error

Error

Error

64-bit single precision[g]

Error

[a] This is an additional precision on a UNICOS/mk system.

[b] This is a single precision on a UNICOS/mk system.

[c] 128-bit precision is not supported on UNICOS/mk systems.

[d] This is an additional precision on a UNICOS/mk system.

[e] 128-bit precision is not supported on UNICOS/mk systems.

[f] 128-bit precision is not supported on UNICOS/mk systems.

[g] 128-bit precision is not supported on UNICOS/mk systems.


Table 6-4. Data length (IRIX systems)

type

n:

*1

*2

*4

*8

*16

*32

INTEGER

 

8-bit

16-bit

32-bit

64-bit

Error

Error

LOGICAL

 

8-bit

16-bit

32-bit

64-bit

Error

Error

REAL

 

Error

Error

32-bit

64-bit

128-bit

Error

COMPLEX

 

Error

Error

32-bit

64-bit

128-bit

Error

DOUBLE PRECISION

 

Error

Error

Error

64-bit

Error

Error


DATA Statement Features

The DATA statement has the following outmoded features:

  • A constant need not exist for each element of a whole array named in a data_stmt_object_list if the array is the last item in the list.

  • A Hollerith or character constant can initialize more than one element of an integer or single-precision real array if the array is specified without subscripts.

    Example 1: On a machine with 64-bit words, if an array is declared by INTEGER A(2), the following DATA statements have the same effect:

    DATA A /'1234567890123456'/
    DATA A /'12345678','90123456'/

    Example 2: On a machine with 32-bit words, if an array is declared by INTEGER A(2), the following DATA statements have the same effect:

    DATA A /'12345678'/
    DATA A /'1234','5678'/

    An integer or single-precision real array can be defined in the same way in a DATA implied-DO statement.

IF Statements

Outmoded IF statements are the two-branch arithmetic IF and the indirect logical IF.

Two-branch Arithmetic IF

A two-branch arithmetic IF statement transfers control to statement s1 if expression e is evaluated as nonzero or to statement s2 if e is zero. The arithmetic expression should be replaced with a relational expression, and the statement should be changed to an IF statement or an IF construct. This format is as follows:

IF ( e ) s1, s2
e

Integer, real, or double-precision expression

s

Label of an executable statement in the same program unit

Example:

IF (I+J*K) 100,101 

Indirect Logical IF

An indirect logical IF statement transfers control to statement st if logical expression le is true and to statement sf if le is false. An IF construct or an IF statement should be used in place of this outmoded statement. This format is as follows:

IF ( le ) st,  sf
le

Logical expression

st, sf

Labels of executable statements in the same program unit

Example:

IF(X.GE.Y)148,9999 

TASK COMMON Statement (UNICOS Systems Only)

When multitasking is used, some common blocks might need to be local to a task. The TASK COMMON statement declares all variables in a common block to be local to a task. If multiple tasks execute code containing the same task common block, each task will have a separate copy of the block. A common block cannot be declared both local common and task common. If a common block is declared local common in one routine and task common in another routine, the loader will generate an error.

A task common block can also be declared by the use of a COMMON statement with the TASKCOMMON compiler directive. The compiler directives are described in CF90 Commands and Directives Reference Manual. The directive is recommended over the TASK COMMON statement for better portability.

The keyword TASK must precede the keyword COMMON to establish a task common block. Task common blocks must be named. A task common block is allocated at task invocation.

The TASK COMMON statement has the following format:

TASK COMMON / cb / member_list[ , / cb / member_list ] ...
cb 

Task common block name.

member_list 

A variable name, array name, or array declarator. A member name must not be a subprogram dummy argument name.

Variables in member_list may appear in a DATA statement.

For information on using the -a alloc option to allocate storage from the f90(1) command line, see the f90(1) man page or the CF90 Commands and Directives Reference Manual.

Nested Loop Termination

Older Cray Research Fortran compilers allowed nested DO loops to terminate on a single END DO statement if the END DO statement had a statement label. The END DO statement is included in the Fortran standard. The Fortran standard specifies that a separate END DO statement must be used to terminate each DO loop, so allowing nested DO loops to end on a single, labeled END DO statement is an outmoded feature.

DOUBLE COMPLEX Statement (UNICOS Systems Only)

The DOUBLE COMPLEX statement is used to declare an item to be of type double complex. The format for the DOUBLE COMPLEX statement is as follows:

DOUBLE COMPLEX [ , attribute_list :: ]entity_list

Items declared as DOUBLE COMPLEX contain two double-precision entities.

When the -d p option is in effect, double complex entities are affected as follows:

  • The nonstandard DOUBLE COMPLEX declaration is treated as a single-precision complex type.

  • Double-precision intrinsic procedures are changed to the corresponding single-precision intrinsic procedures.

The -e p or -d p specification is used for all source files compiled with a single invocation of the f90(1) command. If a module is compiled separately from a program unit that uses the module, they both must be compiled with the same -e p or -d p specification.

Table 6-5 shows the CF90 double complex intrinsic functions and the preferred standard alternatives:

Table 6-5. Standard alternatives to CF90 double-complex functions

Double complex function

Fortran 90 standard alternative

CDABS

ABS(3)

CDCOS

COS(3)

CDEXP

EXP(3)

CDLOG

LOG(3)

CDSIN

SIN(3)

CDSQRT

SQRT(3)


Bitwise Logical Expressions

A bitwise logical expression (also called a masking expression) is an expression in which a logical operator operates on individual bits within integer, real, Cray pointer, or Boolean operands, giving a result of type Boolean. Each operand is treated as a single storage unit. This storage unit is a 64-bit word on UNICOS and UNICOS/mk systems; it is a 32-bit word on IRIX systems. The result is a single storage unit. Boolean values and bitwise logical expressions are contrasted to logical values and expressions.

Bitwise logical operators can also be written as functions; for example A.AND.B can be written as AND(A,B) and .NOT.A can be written as COMPL(A).

The CF90 and MIPSpro 7 Fortran 90 compiler intrinsic functions that operate on Boolean values in bitwise fashion, such as shifting, parity count, and tallying 1s or leading 0s, are extensions to the Fortran standard. Generally, these bitwise functions have equivalent Fortran standard intrinsic procedures. Table 6-6 shows the bitwise functions and, where possible, their equivalent Fortran standard intrinsic procedures:

Table 6-6. Standard alternatives to CF90 and MIPSpro 7 Fortran 90 bitwise functions

Bitwise function

Fortran standard alternative

AND(3m)

IAND(3i)

COMPL(3i)

NOT(3i)

CSMG(3i)

MERGE(3i)

EQV(3m)

IEOR(3i)

MASK(3i)

IBSET(3i)

OR(3m)

IOR(3i)

NEQV(3m)

IEOR(3i)

SHIFT(3i)

ISHFT(3i), ISHFTC(3i)

SHIFTL(3i), LSHIFT(3i)

ISHFT(3i), ISHFTC(3i)

SHIFTR(3i), , RSHIFT(3i)

ISHFT(3i), ISHFTC(3i)

XOR(3m)

IEOR(3i)

If one operand is of type logical, then both operands must be of type logical; the operation performed, then, is a logical operation (not a masking operation). In a logical or masking operation, neither operand can be of type double precision or of type double complex.

Table 6-7, shows which data types can be used together in bitwise logical operations.

Table 6-7. Data types in bitwise logical operations

x1x2

Integer

Real

Boolean

Pointer

Logical

Character

Integer

Masking operation, Boolean result.

Masking operation, Boolean result.

Masking operation, Boolean result.

Masking operation, Boolean result.

Not valid

Not valid1

Real

Masking operation, Boolean result.

Masking operation, Boolean result.

Masking operation, Boolean result.

Masking operation, Boolean result.

Not valid

Not valid1

Boolean

Masking operation, Boolean result.

Masking operation, Boolean result.

Masking operation, Boolean result.

Masking operation, Boolean result.

Not valid

Not valid1

Pointer

Masking operation, Boolean result.

Masking operation, Boolean result.

Masking operation, Boolean result.

Masking operation, Boolean result.

Not valid

Not valid1

Logical

Not valid

Not valid

Not valid

Not valid

Logical operation logical result

Not valid

Character

Not valid1

Not valid1

Not valid1

Not valid1

Not valid

Not valid

Notes:

  1. x1 and x2 represent operands for a logical or bitwise expression, using operators .NOT., .AND., .OR., .XOR., .NEQV., and .EQV..

  2. The entry "Not valid1" indicates that if the operand is a character operand of 32 or fewer characters, the operand is treated as a Hollerith constant and is allowed.

Bitwise logical expressions can be combined with expressions of Boolean or other types by using arithmetic, relational, and logical operators. Evaluation of an arithmetic or relational operator processes a bitwise logical expression with no type conversion. Boolean data is never automatically converted to another type.

A bitwise logical expression performs the indicated logical operation separately on each bit. The interpretation of individual bits in bitwise multiplication_exprs, summation_exprs, and general expressions is the same as for logical expressions. The results of binary 1 and 0 correspond to the logical results TRUE and FALSE, respectively, in each of the bit positions. These values are summarized as follows:

.NOT. 1100            1100           1100           1100           1100
     =0011      .AND. 1010      .OR. 1010     .XOR. 1010     .EQV. 1010
                      ----           ----           ----           ----
                      1000           1110           0110           1001