Compaq Fortran
User Manual for
OpenVMS Alpha Systems


Previous Contents Index

RMS does not allow multiple instances of the same type XAB. To be compatible with future releases of the Run-Time Library, your procedure should scan the XAB chain for XABs of the type to be inserted. If one is found, it should be used instead.

11.4 Example of Block Mode I/O

The following example shows a complete application that calls the RMS block I/O services SYS$WRITE and SYS$READ directly from Compaq Fortran. A complete program called BIO.F90 writes out an array of REAL*8 values to a file using SYS$WRITE, closes the file, and then reads the data back in using SYS$READ operations with a different I/O transfer size. This program consists of five routines:
BIO Main control program
BIOCREATE USEROPEN routine to create the file
BIOREAD USEROPEN routine to open the file for READ access
OUTPUT Function that actually outputs the array
INPUT Function that actually reads the array and checks it

11.4.1 Main Block Mode I/O Program---BIO

The following main program specifies the USEROPEN specifier in its OPEN statements.


!  File: BIO.F90 
! 
!       Program to demonstrate the use of RMS Block I/O operations 
!       from Compaq Fortran 
 
   PROGRAM BIO 
 
!  Declare the Useropen routines as external 
 
   EXTERNAL BIOCREATE, BIOREAD 
 
!  Declare status variable, functions, and unit number 
 
   LOGICAL (KIND=4)  STATUS, OUTPUT, INPUT 
   INTEGER (KIND=4) IUN/1/ 
 
!       Open the file                                   (1)
 
   OPEN(UNIT=IUN, FILE='BIODEMO.DAT', FORM='UNFORMATTED', & 
     STATUS='NEW', RECL=128, BLOCKSIZE=512, ORGANIZATION='SEQUENTIAL', & 
     IOSTAT=IOS,  ACCESS='SEQUENTIAL', RECORDTYPE='FIXED',  & 
     USEROPEN=BIOCREATE, INITIALSIZE=100) 
 
   IF (IOS .NE. 0) STOP 'Create failed'                 (2)
 
!       Now perform the output 
 
   STATUS = OUTPUT(%VAL(FOR$RAB(IUN)))                  (3)
   IF (.NOT. STATUS) STOP 'Output failed'               (2)
 
!       Close the file for output 
 
   CLOSE (UNIT=IUN) 
 
!  Confirm output complete 
 
   TYPE *, 'Output complete, file closed' 
 
!  Now open the file for input                          (2)
 
   OPEN(UNIT=IUN, FILE='BIODEMO.DAT', FORM='UNFORMATTED',  & 
     STATUS='OLD', IOSTAT=IOS, USEROPEN=BIOREAD, DISP='DELETE') 
  
   IF (IOS .NE. 0) STOP 'Open for read failed'          (2)
 
!       Now read the file back 
 
   STATUS = INPUT(%VAL(FOR$RAB(IUN)))                   (3)
   IF (.NOT. STATUS) STOP 'Input failed'                (2)
 
!       Success, output that all is well 
 
   STOP 'Correct completion of Block I/O demo' 
   END PROGRAM BIO 
 

  1. Most of the necessary OPEN options for the file are specified with OPEN statement parameters. This is recommended whenever an OPEN statement qualifier exists to perform the desired function because it allows the Compaq Fortran RTL I/O processing routines to issue appropriate error messages when an RMS routine returns an error status.
    Note the discrepancy between RECL and BLOCKSIZE in the first OPEN statement. Both keywords specify 512 bytes, but the number given for RECL is 128. This is because the unit implied in the RECL keyword is longwords for unformatted files.
    When using Block I/O mode, the blocksize used in the I/O operations is determined by the routine that actually does the operation. The OUTPUT routine actually transfers two 512-byte blocks at a time; the INPUT routine actually transfers four 512-byte blocks at once (see Section 11.4.2).
    In general, the larger the transfers, the more efficiently the I/O is performed. The maximum I/O transfer size allowed by RMS is 65535 bytes.
  2. The error processing in this example routine is very crude; the program simply stops with an indicator of where the problem occurred. In real programs, you should provide more extensive error processing and reporting functions.
  3. The intrinsic function FOR$RAB is used to supply the appropriate RAB address to the OUTPUT and INPUT routines. The %VAL function is used to transform the address returned by the FOR$RAB intrinsic function to the proper argument passing mechanism. This allows the dummy argument RAB in INPUT and OUTPUT to be addressed properly.

11.4.2 Block Mode I/O USEROPEN Functions---BIOCREATE and BIOREAD

The only condition required for block I/O is the setting of the BIO bit in the File Access field of the FAB, using the normal declarations needed to define the symbols properly. If you wish to perform both block and record I/O on the file without closing it, you need to set the BRO bit as well. For more information on mixing block and record mode I/O, see the OpenVMS Record Management Services Reference Manual. Note that the only difference between BIOCREATE and BIOREAD is the use of SYS$CREATE and SYS$OPEN services, respectively.


! Procedure name: BIOCREATE 
 
! USEROPEN routine to set the Block I/O bit and create the BLOCK I/O file. 
 
  INTEGER FUNCTION BIOCREATE(FAB, RAB, LUN) 
  INTEGER LUN 
 
!       Declare the necessary interface names 
 
  INCLUDE '($FABDEF)' 
  INCLUDE '($RABDEF)' 
  INCLUDE '($SYSSRVNAM)' 
 
!       Declare the FAB and RAB blocks 
 
  RECORD /FABDEF/ FAB, /RABDEF/ RAB 
 
! Set the Block I/O bit in the FAC (GET and PUT bits set by RTL) 
 
      FAB.FAB$B_FAC = FAB.FAB$B_FAC .OR. FAB$M_BIO 
 
! Now do the Create and Connect 
 
  BIOCREATE = SYS$CREATE(FAB) 
  IF (.NOT. BIOCREATE) RETURN 
  BIOCREATE = SYS$CONNECT(RAB) 
  IF (.NOT. BIOCREATE) RETURN 
 
! Nothing more to do at this point, just return 
 
  RETURN 
  END FUNCTION BIOCREATE 
 
 
! Procedure name: BIOREAD 
 
! USEROPEN routine to set the Block I/O bit and open the Block I/O demo 
! file for reading 
 
  INTEGER FUNCTION BIOREAD(FAB, RAB, LUN) 
  INTEGER LUN 
 
! Declare the necessary interface names 
 
  INCLUDE '($FABDEF)' 
  INCLUDE '($RABDEF)' 
  INCLUDE '($SYSSRVNAM)' 
 
! Declare the FAB and RAB blocks 
 
      RECORD /FABDEF/ FAB, /RABDEF/ RAB 
 
! Set the Block I/O bit in the FAC (GET and PUT bits set by RTL) 
 
      FAB.FAB$B_FAC = FAB.FAB$B_FAC .OR. FAB$M_BIO 
 
! Now do the Open and Connect 
 
  BIOREAD = SYS$OPEN(FAB) 
  IF (.NOT. BIOREAD) RETURN 
  BIOREAD = SYS$CONNECT(RAB) 
  IF (.NOT. BIOREAD) RETURN 
 
!       Nothing more to do at this point, just return 
 
  RETURN 
  END FUNCTION BIOREAD 

11.4.2.1 OUTPUT Routine

The following routine initializes the array A and performs the SYS$WRITE operations. Beyond the normal RTL initialization, only the RSZ and RBF fields in the RAB need to be initialized in order to perform the SYS$WRITE operations. The %LOC function is used to create the address value required in the RBF field.

One of the main reasons that block mode I/O is so efficient is that it avoids copy operations by using the data areas of the program directly for the output buffer. When writing to a disk device, the program must specify a value for RSZ that is a multiple of 512 or else the final block would be only partly filled.


! Procedure name: OUTPUT 
 
! Function to output records in block I/O mode 
 
  LOGICAL FUNCTION OUTPUT(RAB) 
 
!       Declare RMS names 
 
  INCLUDE '($RABDEF)' 
  INCLUDE '($SYSSRVNAM)' 
 
!       Declare the RAB 
 
  RECORD /RABDEF/ RAB 
 
! Declare the Array to output 
 
  REAL(KIND=8) A(6400) 
 
!       Declare the status variable 
 
  INTEGER(KIND=4) STATUS 
 
!       Initialize the array 
 
  DO I=6400,1,-1 
    A(I) = I 
  ENDDO 
 
! Now, output the array, two 512-byte (64 elements) blocks at a time 
 
  OUTPUT = .FALSE. 
  RAB.RAB$W_RSZ = 1024 
  DO I=0,99,2 
 
! For each block, set the buffer address to the proper array element 
 
    RAB.RAB$L_RBF = %LOC(A(I*64+1)) 
    STATUS = SYS$WRITE(RAB) 
    IF (.NOT. STATUS) RETURN 
  ENDDO 
 
!       Successful output completion 
 
  OUTPUT = .TRUE. 
  RETURN 
  END FUNCTION OUTPUT 

11.4.2.2 INPUT Routine

The following routine reads the array A from the file and verifies its values. The USZ and UBF fields of the RAB are the only fields that need to be initialized. The I/O transfer size is twice as large as the OUTPUT routine. This can be done because the OUTPUT routine writes an integral number of 512-byte blocks to a disk device. This method cannot be used if the writing routine either specifies an RSZ that is not a multiple of 512 or attempts to write to a magnetic tape device.


! Procedure name: INPUT 
! 
! Function to input records in block I/O mode 
 
  LOGICAL FUNCTION INPUT(RAB) 
 
! Declare RMS names 
 
  INCLUDE '($RABDEF)' 
  INCLUDE '($SYSSRVNAM)' 
 
! Declare the RAB 
 
  RECORD /RABDEF/ RAB 
  
! Declare the Array to output 
 
  REAL(KIND=8) A(6400) 
  
!       Declare the status variable 
 
  INTEGER(KIND=4) STATUS 
 
! Now, read the array, four 512-byte (64 elements) blocks at a time 
 
  INPUT = .FALSE. 
  RAB.RAB$W_USZ = 2048 
  DO I=0,99,4 
 
! For each block, set the buffer address to the proper array element 
 
    RAB.RAB$L_UBF = %LOC(A(I*64+1)) 
    STATUS = SYS$READ(RAB) 
    IF (.NOT. STATUS) RETURN 
  ENDDO 
 
!       Successful input completion if data is correct 
 
  DO I=6400,1,-1 
     IF (A(I) .NE. I) RETURN 
  ENDDO 
 
  INPUT = .TRUE. 
  RETURN 
  END FUNCTION INPUT 


Chapter 12
Using Indexed Files

Sequential and direct access have traditionally been the only file access modes available to Fortran programs. To overcome some of the limitations of these access modes, Compaq Fortran supports a third access mode, called keyed access, which allows you to retrieve records, at random or in sequence, based on key fields that are established when you create a file with indexed organization. (See Section 6.8.2 for details about keyed access mode.)

You can access files with indexed organization using sequential access or keyed access, or a combination of both.

Once you have read a record by means of an indexed read request, you can then use a sequential read request to retrieve records with ascending key field values, beginning with the key field value in the record retrieved by the initial read request.

Indexed organization is especially suitable for maintaining complex files in which you want to select records based on one of several criteria. For example, a mail-order firm could use an indexed organization file to store its customer list. Key fields could be a unique customer order number, the customer's zip code, and the item ordered. Reading sequentially based on the zip-code key field would enable you to produce a mailing list sorted by zip code. A similar operation based on customer-order-number key field or item-number key field would enable you to list the records in sequences of customer order numbers or item numbers.

This chapter provides information of the following topics:

Information is provided about the effects of read and write operations on positioning your program to records within an indexed file ( Section 12.6) and about how to build logic into your programs to handle exception conditions that commonly occur ( Section 12.7).

12.1 Creating an Indexed File

You can create a file with an indexed organization by using either the Fortran OPEN statement or the RMS EDIT/FDL Utility.

Any indexed file created with EDIT/FDL can be accessed by Compaq Fortran I/O statements.

When you create an indexed file, you define certain fields within each record as key fields. The primary key, identified as key number zero, must be present as a field in every record. Alternate keys are numbered from 1 through 254. An indexed file can have as many as 255 key fields (1 primary key and up to 254 alternate keys) defined. In practice, however, few applications require more than 3 or 4 key fields.

The data types used for key fields must be INTEGER (KIND=1), INTEGER (KIND=2), INTEGER (KIND=4), INTEGER (KIND=8), or CHARACTER.

In designing an indexed file, you must decide the byte positions of the key fields. For example, in creating an indexed file for use by a mail-order firm, you might define a file record to consist of the following fields:


  STRUCTURE /FILE_REC_STRUCT/ 
    INTEGER(KIND=4) ORDER_NUMBER      ! Positions 1:4, key 0 
    CHARACTER(LEN=20)  NAME           ! Positions 5:24 
    CHARACTER(LEN=20)  ADDRESS        ! Positions 25:44 
    CHARACTER(LEN=19)  CITY           ! Positions 45:63 
    CHARACTER(LEN=2)   STATE          ! Positions 64:65 
    CHARACTER(LEN=9)   ZIP_CODE       ! Positions 66:74, key 1 
    INTEGER(KIND=2)    ITEM_NUMBER    ! Positions 75:76, key 2 
  END STRUCTURE 
     . 
     . 
     . 
  RECORD /FILE_REC_STRUCT/ FILE_REC 

Instead of using a record structure, you can define a the fields of a record using a derived-type definition with the SEQUENCE statement:


  TYPE FILE_REC 
    SEQUENCE 
    INTEGER(KIND=4) ORDER_NUMBER      ! Positions 1:4, key 0 
    CHARACTER(LEN=20)  NAME           ! Positions 5:24 
    CHARACTER(LEN=20)  ADDRESS        ! Positions 25:44 
    CHARACTER(LEN=19)  CITY           ! Positions 45:63 
    CHARACTER(LEN=2)   STATE          ! Positions 64:65 
    CHARACTER(LEN=9)   ZIP_CODE       ! Positions 66:74, key 1 
    INTEGER(KIND=2)    ITEM_NUMBER    ! Positions 75:76, key 2 
  END TYPE FILE_REC 
     . 
     . 
     . 

Given this record definition, you can use the following OPEN statement to create an indexed file:


  OPEN (UNIT=10, FILE='CUSTOMERS.DAT', STATUS='NEW', & 
    ORGANIZATION='INDEXED', ACCESS='KEYED', RECORDTYPE='VARIABLE', & 
    FORM='UNFORMATTED', RECL=19, & 
    KEY=(1:4:INTEGER, 66:74:CHARACTER, 75:76:INTEGER), & 
    IOSTAT=IOS, ERR=9999) 

This OPEN statement establishes the attributes of the file, including the definition of a primary key and two alternate keys. The definitions of the integer keys do not explicitly state INTEGER (KIND=4) and INTEGER (KIND=2). The data type sizes are determined by the number of character positions allotted to the key fields (4- and 2-digit positions in this case respectively).

If you specify the KEY keyword when opening an existing file, the key specification that you give must match that of the file.

Compaq Fortran uses RMS default key attributes when creating an indexed file. These defaults are as follows:

You can use the EDIT/FDL Utility or a USEROPEN routine to override these defaults and to specify other values not supported by Compaq Fortran, such as null key field values, null key names, and key data types other than integer and character.

For More Information:

12.2 Writing Indexed Files

You can write records to an indexed file with either formatted or unformatted indexed WRITE statements. Each write operation inserts a new record into the file and updates the key indexes so that the new record can be retrieved in a sequential order based on the values in the respective key fields.

For example, you could add a new record to the file for the mail-order firm (see Section 12.1) with the following statement:


  WRITE (UNIT=10,IOSTAT=IOS,ERR=9999) FILE_REC 

12.2.1 Duplicate Values in Key Fields

It is possible to write two or more records with the same value in a single key field. The attributes specified for the file when it was created determine whether this duplication is allowed. By default, Compaq Fortran creates files that allow duplicate alternate key field values and prohibit duplicate primary key field values. If duplicate key field values are present in a file, the records with equal values are retrieved on a first-in/first-out basis.

For example, assume that five records are written to an indexed file in this order (for clarity, only key fields are shown):
ORDER_NUMBER ZIP_CODE ITEM_NUMBER
1023 70856 375
942 02163 2736
903 14853 375
1348 44901 1047
1263 33032 690

If the file is later opened and read sequentially by primary key (ORDER_NUMBER), the order in which the records are retrieved is not affected by the duplicated value (375) in the ITEM_NUMBER key field. In this case, the records would be retrieved in the following order:
ORDER_NUMBER ZIP_CODE ITEM_NUMBER
903 14853 375
942 02163 2736
1023 70856 375
1263 33032 690
1348 44901 1047

However, if the read operation is based on the second alternate key (ITEM_NUMBER), the order in which the records are retrieved is affected by the duplicate key field value. In this case, the records would be retrieved in the following order:
ORDER_NUMBER ZIP_CODE ITEM_NUMBER
1023 70856 375
903 14853 375
1263 33032 690
1348 44901 1047
942 02163 2736

The records containing the same key field value (375) are retrieved in the order in which they were written to the file.

12.2.2 Preventing the Indexing of Alternate Key Fields

When writing to an indexed file that contains variable-length records, you can prevent entries from being added to the key indexes for any alternate key fields. This is done by omitting the names of the alternate key fields from the WRITE statement. The omitted alternate key fields must be at the end of the record; another key field cannot be specified after the omitted key field.

For example, the last record (ORDER_NUMBER 1263) in the mail-order example could be written with the following statement:


  WRITE (UNIT=10,IOSTAT=IOS,ERR=9999) FILE_REC.ORDER_NUMBER, FILE_REC.NAME, & 
     FILE_REC.ADDRESS, FILE_REC.CITY, FILE_REC.STATE, FILE_REC.ZIP_CODE 

Because the field name FILE_REC.ITEM_NUMBER is omitted from the WRITE statement, an entry for that key field is not created in the index. As a result, an attempt to read the file using the alternate key ITEM_NUMBER would not retrieve the last record and would produce the following listing:
ORDER_NUMBER ZIP_CODE ITEM_NUMBER
1023 70856 375
903 14853 375
1348 44901 1047
942 02163 2736

You can omit only trailing alternate keys from a record; the primary key must always be present.

12.3 Reading Indexed Files

You can read records in an indexed file with either sequential or indexed READ statements (formatted or unformatted) under the keyed mode of access. By specifying ACCESS='KEYED' in the OPEN statement, you enable both sequential and keyed access to the indexed file.

Indexed READ statements position the file pointers (see Section 12.6) at a particular record, determined by the key field value, the key-of-reference, and the match criterion. Once you retrieve a particular record by an indexed READ statement, you can then use sequential access READ statements to retrieve records with increasing key field values.

The form of the external record's key field must match the form of the value you specify in the KEY keyword. If the key field contains character data, you should specify the KEY keyword value as a CHARACTER data type. If the key field contains binary data, then the KEY keyword value should be of INTEGER data type.

If you write a record to an indexed file with formatted I/O, the data type is converted from its internal representation to an external representation. As a result, the key value must be specified in the external form when you read the data back with an indexed read. Otherwise, a match will occur when you do not expect it.

The following Compaq Fortran program segment prints the order number and zip code of each record where the first five characters of the zip code are greater than or equal to '10000' but less than '50000':


! Read first record with ZIP_CODE key greater than or equal to '10000'. 
 
   READ (UNIT=10,KEYGE='10000',KEYID=1,IOSTAT=IOS,ERR=9999) FILE_REC 
 
!  While the zip code previously read is within range, print the 
!  order number and zip code, then read the next record. 
 
   DO WHILE (FILE_REC.ZIP_CODE .LT. '50000') 
     PRINT *, 'Order number', FILE_REC.ORDER_NUMBER, 'has zip code', & 
           FILE_REC.ZIP_CODE 
    READ (UNIT=10,IOSTAT=IOS,END=200,ERR=9999) FILE_REC 
 
! END= branch will be taken if there are no more records in the file. 
 
   END DO 
200  CONTINUE 

The error branch on the keyed READ in this example is taken if no record is found with a zip code greater than or equal to '10000'; an attempt to access a nonexistent record is an error. If the sequential READ has accessed all records in the file, an end-of-file status occurs, as with other file organizations.

If you want to detect a failure of the keyed READ, you can examine the I/O status variable, IOS, for the appropriate error number (see Table 7-1 for a list of the returned error codes).

12.4 Updating Records

The REWRITE statement updates existing records in an indexed file. You cannot replace an existing record simply by writing it again; a WRITE statement would attempt to add a new record.

An update operation is accomplished in two steps:

  1. You must read the record in order to make it the current record.
  2. You execute the REWRITE statement.

For example, to update the record containing ORDER_NUMBER 903 (see prior examples) so that the NAME field becomes 'Theodore Zinck', you might use the following Fortran code segment:


  READ (UNIT=10,KEY=903,KEYID=0,IOSTAT=IOS,ERR=9999) FILE_REC 
  FILE_REC.NAME = 'Theodore Zinck' 
  REWRITE (UNIT=10,IOSTAT=IOS,ERR=9999) FILE_REC 

When you rewrite a record, key fields may change. The attributes specified for the file when it was created determine whether this type of change is permitted. The primary key value can never change on a REWRITE operation. If necessary, delete the old record and write a new record.

12.5 Deleting Records

The DELETE statement allows you to delete records from an indexed file. The DELETE and REWRITE statements are similar; a record must first be locked by a READ statement before it can be operated on.

The following Fortran code segment deletes the second record in the file with ITEM_NUMBER 375 (refer to previous examples):


  READ (UNIT=10,KEY=375,KEYID=2,IOSTAT=IOS,ERR=9999) 
  READ (UNIT=10,IOSTAT=IOS,ERR=9999) FILE_REC 
  IF (FILE_REC.ITEM_NUMBER .EQ. 375) THEN 
      DELETE (UNIT=10, IOSTAT=IOS, ERR=9999) 
  ELSE 
      PRINT *, 'There is no second record.' 
  END IF 

Deletion removes a record from all defined indexes in the file.

12.6 Current Record and Next Record Pointers

The RMS file system maintains two pointers into an open indexed file:

12.7 Exception Conditions

You can expect to encounter certain exception conditions when using indexed files. The two most common of these conditions involve valid attempts to read locked records and invalid attempts to create duplicate keys. Provisions for handling both of these situations should be included in a well-written program.

When an indexed file is shared by several users, any read operation may result in a "specified record locked" error. One way to recover from this error condition is to ask if the user would like to reattempt the read. If the user's response is positive, then the program can go back to the READ statement. For example:


    INCLUDE '($FORIOSDEF)' 
 . 
 . 
 . 
 
100  READ (UNIT=10,IOSTAT=IOS) DATA 
 
   IF (IOS .EQ. FOR$IOS_SPERECLOC) THEN 
     TYPE *, 'That record is locked. Press RETURN' 
     TYPE *, 'to try again, or Ctrl/Z to discontinue' 
     READ (UNIT=*,FMT=*,END=900) 
     GO TO 100 
   ELSE IF (IOS .NE. 0) THEN 
     CALL ERROR (IOS) 
   END IF 

You should avoid looping back to the READ statement without first providing some type of delay (caused by a request to try again, or to discontinue, as in this example). If your program reads a record but does not intend to modify the record, you should place an UNLOCK statement immediately after the READ statement. This technique reduces the time that a record is locked and permits other programs to access the record.

The second exception condition, creation of duplicate keys, occurs when your program tries to create a record with a key field value that is already in use. When duplicate key field values are not desirable, you might have your program prompt for a new key field value whenever an attempt is made to create a duplicate. For example:


   INCLUDE '($FORIOSDEF)' 
 
200  WRITE (UNIT=10,IOSTAT=IOS) KEY_VAL, DATA 
  
   IF (IOS .EQ. FOR$IOS_INCKEYCHG) THEN 
      TYPE *, 'This key field value already exists. Please' 
      TYPE *, 'enter a different key field value, or press' 
      TYPE *, 'Ctrl/Z to discontinue this operation.' 
      READ (UNIT=*,FMT=300,END=999) KEY_VAL 
      GO TO 200 
   ELSE IF (IOS .NE. 0) THEN 
      CALL ERROR (IOS) 
   END IF 


Previous Next Contents Index