Chapter 3. Fortran I/O Extensions

This chapter describes additional I/O routines and statements available with the CF90 compiler and the MIPSpro 7 Fortran 90 compiler. These additional routines, known as Fortran extensions, perform unformatted I/O.

For details about the routines discussed in this chapter, see the individual man pages for each routine. In addition, see the reference manuals for your compiler system.

BUFFER IN/BUFFER OUT Routines

BUFFERIN and BUFFER OUT statements initiate a data transfer between the specified file or unit at the current record and the specified area of program memory. To allow maximum asynchronous performance, all BUFFER IN and BUFFER OUT operations should begin and end on a sector boundary. See Chapter 9, “Devices”, for more information about sector sizes.

The BUFFER IN and BUFFER OUT statements can perform sequential asynchronous unformatted I/O if the files are assigned as unbuffered files. You must declare the BUFFER IN and BUFFER OUT files as unbuffered by using one of the following assign(1) commands.

assign -s u ...
assign -F system ...

If the files are not declared as unbuffered, the BUFFER IN and BUFFER OUT statements may execute synchronously.

For tapes, BUFFER IN and BUFFER OUT operate synchronously; when you execute a BUFFER statement, the data is placed in the buffer before you execute the next statement in the program. Therefore, for tapes, BUFFER IN has no advantage over a read statement or a CALL READ statement; however, the library code is doing asynchronous read-aheads to fill its own buffer.

The COS blocked format is the default file structure on UNICOS and UNICOS/mk systems for files (not tapes) that are opened explicitly as unformatted sequential or implicitly by a BUFFER IN or BUFFER OUT statement. The F77 format is the default file structure on IRIX systems.

The BUFFER IN and BUFFER OUT statements decrease the overhead associated with transferring data through library and system buffers. These statements also offer the advantages of asynchronous I/O. I/O operations for several files can execute concurrently and can also execute concurrently with CPU instructions. This can decrease overall wall-clock time.

In order for this to occur, the program must ensure that the requested asynchronous data movement was completed before accessing the data. The program must also be able to do a significant amount of CPU-intensive work or other I/O during asynchronous I/O to increase the program speed.

Buffer I/O processing waits until any previous buffer I/O operation on the file completes before beginning another buffer I/O operation.

Use the UNIT(3f) and LENGTH(3f) functions with BUFFER IN and BUFFER OUT statements to delay further program execution until the buffer I/O statement completes.

For details about the routines discussed in this section, see the individual man pages for each routine.

The UNIT Intrinsic

The UNIT(blank) intrinsic routine waits for the completion of the BUFFER IN or BUFFER OUT statement. A program that uses asynchronous BUFFER IN and BUFFER OUT must ensure that the data movement completes before trying to access the data. The UNIT(blank) routine can be called when the program wants to delay further program execution until the data transfer is complete. When the buffer I/O operation is complete, UNIT returns a status indicating the outcome of the buffer I/O operation.

The following is an example of the UNIT routine:

STATUS=UNIT(90)

The LENGTH Intrinsic

The LENGTH(blank) intrinsic routine returns the length of transfer for a BUFFER IN or a BUFFER OUT statement. If the LENGTH routine is called during a BUFFER IN or BUFFER OUT operation, the execution sequence is delayed until the transfer is complete. LENGTH then returns the number of words successfully transferred. A 0 is returned for an end-of-file (EOF).

The following is an example of the LENGTH routine:

LENG=LENGTH(90)

Positioning (Deferred Implementation on IRIX systems)

The GETPOS(3f) and SETPOS(3f) file positioning routines change or indicate the position of the current file. The GETPOS routine returns the current position of a file being read. The SETPOS routine positions a tape or mass storage file to a previous position obtained through a call to GETPOS.

You can use the GETPOS and SETPOS positioning statements on buffer I/O files. These routines can be called for random positioning for BUFFER IN and BUFFER OUT processing. These routines can be used with COS blocked files on disk, but not with COS blocked files on tape.

You can also use these routines with the standard Fortran READ and WRITE statements. The direct-access mode of standard Fortran is an alternative to the GETPOS and SETPOS functionality.

Random Access I/O Routines (Not Available on IRIX systems)

The record-addressable random-access file I/O routines let you generate variable length, individually addressable records. The I/O library updates indexes and pointers.

Each record in a random-access file has a 1-word (64-bit) key or number indicating its position in an index table of records for the file. This index table contains a pointer to the location of the record on the device and can also contain a name of each record within the file.

Alphanumeric record keys increase CPU time compared to sequential integer record keys because the I/O routines must perform a sequential lookup in the index array for each alphanumeric key. Each record should be named a numeric value n; n is the integer that corresponds to the n th record created on the file.

The following two sets of record-addressable random-access file I/O routines are available:

  • The Mass Storage (MS) package provides routines that perform buffered, record-addressable file I/O with variable-length records. It contains the OPENMS, READMS, WRITMS, CLOSMS, WAITMS, FINDMS, SYNCMS, ASYNCMS, CHECKMS, and STINDX routines.

  • The Direct Random (DR) package provides routines that perform unbuffered, record-addressable file I/O. It contains the OPENDR, READDR, WRITDR, CLOSDR, WAITDR, SYNCDR, ASYNCDR, CHECKDR, and STINDR routines. The amount of data transferred for a record is rounded up to a multiple of 512 words, because I/O performance is improved for many disk devices.

Both synchronous and asynchronous MS and DR I/O can be performed on a random-access file. You can use these routines in the same program, but they must not be used on the same file simultaneously. The MS and DR packages cannot be used for tape files.

If a program uses asynchronous I/O, it must ensure that the data movement is completed before trying to access the data. Because asynchronous I/O has a larger overhead in CPU time than synchronous I/O, only very large data transfers should be done with asynchronous I/O. To increase program speed, the program must be able to do a significant amount of CPU-intensive work or other I/O while the asynchronous I/O is executing.

The MS library routines are used to perform buffered record-addressable random-access I/O. The DR library routines are used to perform unbuffered record-addressable random-access I/O.

These library routines are not internally locked to ensure single-threading; a program must lock each call to the routine if the routine is called from more than one task.

The following list describes these two packages in more detail. For details about the routines discussed in this section, see the individual man pages for each routine.

  • OPENMS(3f) and OPENDR(3f) open a file and specify the file as a random-access file that can be accessed by record-addressable random-access I/O routines.

    These routines must be used to open a file before the file can be accessed by other MS or DR package routines. OPENMS sets up an I/O buffer for the random-access file. These routines read the index array for the file into the array provided as an argument to the routine. CLOSMS or CLOSDR must close any files opened by the OPENMS or OPENDR routine. The following are examples of these two routines:

    CALL OPENMS(80,intarr,len,it,ierr)
    CALL OPENDR(20,inderr,len,itflg,ierr)

  • READMS(3f) performs a read of a record into memory from a random-access file. READDR reads a record from a random-access file into memory.

    If READDR is used in asynchronous mode and the record size is not a multiple of 512 words, user data can be overwritten and not restored. You can use SYNCDR to switch to a synchronous read; the data is copied and restored after the read has completed. The following are examples of these routines:

    CALL READMS(80,ibuf,nwrd,irec,ierr)
    CALL READDR(20,iloc,nwrd,irec,ierr)

  • WRITMS(3f) writes to a random-access file on disk from memory. WRITDR writes data from user memory to a record in a random-access file on disk. Both routines update the current index. The following are examples of these routines:

    CALL WRITMS(20,ibuf,nwrd,irec,irflg,isflag,ierr)
    CALL WRITDR(20,ibuf,nwrd,irec,irflag,isflg,ierr)

  • The CLOSMS(3f) and CLOSDR routines write the master index specified in the call to OPENMS or OPENDR from the array provided in the user program to the random-access file and then close the file. These routines also write statistics about the file to the stderr file. The following are examples of these routines:

    CALL CLOSMS(20,ierr)
    CALL CLOSDR(20,ierr)

  • ASYNCMS(3f) and ASYNCDR set the I/O mode for the random-access routines to asynchronous. I/O operations can be initiated and subsequently proceed simultaneously with the actual data transfer. If the program uses READMS, precede asynchronous reads with calls to FINDMS. The following are examples of these routines:

    CALL ASYNCMS(20,ierr)
    CALL ASYNCDR(20,ierr)

  • CHECKMS(3f) and CHECKDR check the status of the asynchronous random-access I/O operation. The following are examples of these routines:

    CALL CHECKMS(20,istat,ierr)
    CALL CHECKDR(20,istat,ierr)

  • WAITMS(3f) and WAITDR wait for the completion of an asynchronous I/O operation. They return a status flag indicating if the I/O on the specified file completed without error. The following are examples of these routines:

    CALL WAITMS(20,istat,ierr)
    CALL WAITDR(20,istat,ierr)

  • SYNCMS(3f) and SYNCDR set the I/O mode for the random-access routines to synchronous. All future I/O operations wait for completion. The following are examples of these routines:

    CALL SYNCMS(20,ierr)
    CALL SYNCDR(20,ierr)

  • STINDX(3f) and STINDR allow an index to be used as the current index by creating a subindex. These routines reduce the amount of memory needed by a file that contains a large number of records. They also maintain a file containing records logically related to each other. Records in the file, rather than records in the master index area, hold secondary pointers to records in the file.

    These routines allow more than one index to manipulate the file. Generally, STINDX or STINDR toggle the index between the master index maintained by OPENMS/OPENDR and CLOSMS/CLOSDR and the subindex supplied by the Fortran program. The following are examples of these routines:

    CALL STINDX(20,inderr,len,itflg,ierr)
    CALL STINDR(20,inderr,len,itflg,ierr)

  • FINDMS(3f) asynchronously reads the desired record into the data buffers for the specified file. The next READMS or WRITMS call waits for the read to complete and transfers data appropriately. An example of a call to FINDMS follows:

    CALL FINDMS(20,inwrd,irec,ierr)

The following program example uses the MS package:

Example 3-1. MS package use

       program msio
       dimension r(512)
       dimension idx(512)
       data r/512*2.0/
       irflag=0

       call openms(1,idx,100,0,ier)

       do 100 i=1,100
         call writms(1,r,512,i,irflag,0,ier)
         if(ier.ne.0)then
           print *,"error on writms=",ier
           goto 300
         end if
100    continue

       do 200 i=1,100
         call readms(1,r,512,i,irflag,0,ier)
         if(ier.ne.0)then
           print *,"error on readms=",ier
           goto 300
         end if

200    continue
300    continue
       call closms(1,ier)
       end


The following program uses the DR package:

Example 3-2. DR package use

       program daio
       dimension r(512)
       dimension idx(512)
       data r/512*2.0/
       irflag=0
       ierrs=0

       call assign('assign -R',ier1)
       call asnunit(1,'-F mr.save.ovf1:10:200:20',ier2)
       if(ier1.ne.0.or.ier2.ne.0)then
          print *,"assign error=",ier1,ier2
          ierrs=ierrs+1
       end if

       call opendr(1,idx,100,0,ier)
       if(ier.ne.0)then
         print *,"error on opendr=",ier
         ierrs=ierrs+1
       end if

       do 100 i=1,100
         call writdr(1,r,512,i,irflag,0,ier)
         if(ier.ne.0)then
           print *,"error on writdr=",ier
           ierrs=ierrs+1
         end if
100    continue
       do 200 i=1,100
         call readdr(1,r,512,i,irflag,0,ier)
         if(ier.ne.0)then
            print *,"error on readdr=",ier
            ierrs=ierrs+1
         end if
200    continue
300    call closdr(1,ier)
       if(ier.ne.0)then
         print *,"error on readdr=",ier
         ierrs=ierrs+1
       end if
400    continue
       if(ierrs.eq.0)then
         print *,"daio passed"
       else
         print *,"daio failed"
       end if
       end


Word-addressable I/O Routines (Not Available on IRIX systems)

A word-addressable (WA) random-access file consists of an adjustable number of contiguous words. The WA package performs unformatted buffered I/O; the WA routines perform efficiently when the I/O buffers are set to a size large enough to hold several records that are frequently read and/or written. When a WA read operation is executed, the I/O buffers are searched to see if the data that will be read is already in the buffers. If the data is found in the I/O buffers, I/O speedup is achieved because a system call is not needed to retrieve the data.

A program using the package may access a word or a contiguous sequence of words from a WA random-access file. The WA package cannot be used for tape files.

Although the WA I/O routines provide greater control over I/O operations than the record-addressable routines, they require that the user track information that the system would usually maintain when other forms of I/O are used. The program must keep track of the word position of each record in a file that it will read or write with WA I/O. This is easiest to do with fixed-length records; with variable-length records, the program must store record lengths for the file where they can be retrieved when the file is accessed. When variable-length records are used, the program should use record-addressable I/O.

The WA package allows both synchronous and asynchronous I/O. To speed up the program, the program must be able to do a significant amount of CPU-intensive work or other I/O while the asynchronous I/O is executing.

These library routines are not internally locked to ensure single-threading; a program must lock each call to the routine if the routine is called from more than one task.

The following list briefly describes the routines in this package; for details about the routines discussed in this section, see the individual man pages for each routine.

  • WOPEN(3f) opens a file and specifies it as a word-addressable random-access file. WOPEN must be called before any other WA routines are called because it creates the I/O buffer for the specified file by using blocks. By using WOPEN, you can combine synchronous and asynchronous I/O to a given file while the file is opened. The following is an example of a call to WOPEN:

    CALL WOPEN(30,iblks,istat,err)

  • GETWA(3f) synchronously reads data from a buffered word-addressable random-access file. SEEK(3f) is used with GETWA to provide more efficient I/O; the SEEK routine performs an asynchronous pre-fetch of data into a buffer. The following is an example of a call to GETWA:

    CALL GETWA(30,iloc,iadr,icnt,ierr)

  • SEEK(3f) asynchronously reads data from the word-addressable file into a buffer. A subsequent GETWA call will deliver the data from the buffer to the user data area. This provides a way for the user to do asynchronous read-ahead. The following is an example of a call to SEEK:

    CALL SEEK(30,iloc,iadr,icnt,ierr)

  • PUTWA(3f) synchronously writes from memory to a word-addressable random-access file. The following is an example of a call to PUTWA:

    CALL PUTWA(30,iloc,iadr,icnt,ierr)

    APUTWA(3f) asynchronously writes from memory to a word-addressable random-access file. The following is an example of a call to APUTWA:

    CALL APUTWA(30,iloc,iadr,icnt,ierr)

  • WCLOSE(3f) finalizes changes and additions to a WA file and closes it. The following is an example of a call to WCLOSE:

    CALL WCLOSE(30,ierr)

The following is an example of a program which uses the WA I/O routines:

Example 3-3. WA package use

        program waio
        dimension r(512), r1(512)
        iblks=10             !use a 10 block buffer
        istats=1             !print out I/O Stats

        call wopen(1,iblks,0,ier)
        if(ier.ne.0)then
          print *,"error on wopen=",ier
          goto 300
        end if

        iaddr=1
        do 100 k=1,100

          do 10 j=1,512
10        r(j)=j+k
          call putwa(1,r,iaddr,512,ier)
          if(ier.ne.0)then
             print *,"error on putwa=",ier," rec=",k
             goto 300
          end if
          iaddr=iaddr+512
100     continue

        iaddr=1
        do 200 k=1,100
          call getwa(1,r1,iaddr,512,ier)
          if(ier.ne.0)then
             print *, "error on getwa=",ier," rec=",k
             goto 300
          end if
          iaddr=iaddr+512
200     continue
300     continue
        call wclose(1)
        end


Asynchronous Queued I/O (AQIO) Routines (Not Available on IRIX systems)

The asynchronous queued I/O (AQIO) routines perform asynchronous, queued I/O operations. Asynchronous I/O allows your program to continue executing while an I/O operation is in progress, and it allows several I/O requests to be active concurrently. AQIO further refines asynchronous I/O by allowing a program to queue several I/O requests and to issue one request to the operating system to perform all I/O operations. When queuing I/O requests, the overhead that is associated with calling the operating system is incurred only once per group of I/O requests rather than once per request as with other forms of I/O.

AQIO also offers options for streamlining I/O operations that involve fixed-length records with a fixed-skip increment through the user file and a fixed-skip increment through program memory. A form of this is a read or write that involves contiguous fixed-length records. Such an operation is called a compound AQIO request or a compound AQIO operation. AQIO provides separate calls for compound operations so that a program can specify multiple I/O operations in one call, thus saving I/O time.

Asynchronous I/O has a larger overhead in system CPU time than synchronous I/O; therefore, only large data transfers should be done using asynchronous I/O. To speed up the program, the program must be able to do a significant amount of CPU-intensive work or other I/O while the asynchronous I/O is executing.

The value of the queue argument on the AQWRITE/AQWRITEC(3f) or AQREAD/AQREADC(3f) call controls when the operating system is called to process the request. If queue is nonzero, packets are queued in the AQIO buffer and the operating system is not called to start packet processing until the buffer is full (for example, to queue 20 packets, the program would issue 19 AQWRITE calls with queue set to a nonzero value and then set it to 0 on the twentieth call).

On CRAY T3E systems, when a program opens a file with AQOPEN, a file handle is returned. The library associates this handle with information in the processing element's (PE) local memory; therefore, the file handle should not be used by other PEs. More than one PE can open a file with AQOPEN; if coordination between the different PEs is required, the user must do the coordination using synchronization routines.

The following list briefly describes the AQIO routines; for details about the routines discussed in this section, see the individual man pages for each routine.

  • AQOPEN(3f) opens a file for AQIO. The AQOPEN call must precede all other AQIO requests in a Fortran program.

  • AQCLOSE(3f) closes an AQIO file.

  • The AQREAD function queues a simple asynchronous I/O read request.

  • AQREADC(3f) lets you use a compound AQIO request call to transfer fixed-length records repeatedly. You must provide the values for a repeat count, memory skip increment, and disk increment arguments. AQREADC transfers the first record from disk and increments the starting disk block and the starting user memory by the amounts you specify.

    To transfer data to a continuous array in memory, set the memory skip increment value to the record length in words. To transfer data sequentially from disk, set the disk increment value to the record length in blocks. See Example 3-4, for an example of a program using AQIO read routines.

  • AQWRITE queues a simple asynchronous write request.

  • AQWRITEC provides a compound AQIO request call when repeatedly transferring fixed-length records. The program supplies the repetition count, the disk skip increment, and the memory skip increment on these compound AQIO calls.

    AQIO then transfers the first record to or from disk and increments the starting disk block and the starting user memory address. To transfer data from a contiguous array in memory, set the memory skip increment value to the record length in words. To transfer data sequentially to disk, set the disk increment value to the record length in blocks.

  • AQSTAT checks the status of AQIO requests. AQWAIT forces the program to wait until all queued entries are completed.

    After queuing a AQWRITE or AQREAD request and calling the operating system, you may need to monitor their completion status to know when it is safe to use the data or to reuse the buffer area. AQSTAT returns information about an individual AQIO request.

    The reqid argument of AQREAD/AQREADC and AQWRITE/AQWRITEC is stored in the packet buffer and can be used in an AQSTAT call to monitor the completion status of a particular transfer. The aqpsize argument to AQOPEN is important because of the ability to monitor the status.

    A requested ID can be deleted after the request completes but before its status is checked because each request buffer is reused. This can happen, for example, if you set the aqpsize argument in AQOPEN to be 20, and issued 30 requests. If you then request the status of the first request, AQSTAT returns 0, indicating that the requested ID was not found.

Error Detection by Using AQIO

Because of the asynchronous nature of AQIO, error detection and reporting with AQIO may not occur immediately on return from a call to an asynchronous queued I/O subroutine. If one of the queued I/O requests causes an error when the operating system tries to do the I/O, the error is returned in a subsequent AQIO request.

For example, if a program issues an AQWRITE with queue set to 0, I/O is initiated. If no previous errors occurred, a 0 status is returned from this statement even though this request may ultimately fail. If the request fails, for example, because it tried to exceed the maximum allowed file size, the error is returned to the user in the subsequent AQIO statement that coincides with its detection. If the next AQIO statement is AQWAIT, the error is detected and returned to the user. If the next AQIO statement is AQSTAT, the error is detected and reported only if the requested ID failed. When an error is reported to the user, it is not reported again. Checking the status after each AQIO statement ensures that the user program detects all errors.

Example 3-4. AQIO routines: compound read operations

      PROGRAM AQIO1
      IMPLICIT INTEGER(A-Z)
      PARAMETER (TOTREQ=20)
      PARAMETER (AQPSIZE=20)
      INTEGER AQP
      INTEGER BUFFER (TOTREQ*512)
      INTEGER EVNBUF (TOTREQ/2*512)
      INTEGER ODDBUF (TOTREQ/2*512)

      CALL AQOPEN (AQP,AQPSIZE,'FILE4'H,STAT)
      IF (STAT.NE.0) THEN
         PRINT *,'AQOPEN FAILED, STATUS= ',STAT
         CALL ABORT()
      ENDIF

C     INITIALIZE DATA
      DO 10 I=1,TOTREQ*512
         BUFFER(i) = I
10    CONTINUE

      DO 50 RNUM=1,TOTREQ
C       QUEUE THE REQUESTS
C       INITIATE I/O ON THE LAST REQUEST

C       THE DATA FROM BUFFER IS WRITTEN IN A SEQUENTIAL
C       FASHION TO DISK
        QUEUE=1
        IF (RNUM.EQ.TOTREQ) QUEUE=0
           OFFSET= (RNUM-1)*512+1
          CALL AQWRITE(
         '    AQP,
         '    BUFFER(OFFSET),   !start address
         '    RNUM-1,           !block address
         '    1,                !number of blocks
         '    RNUM,             !request id
         '    QUEUE,            !queue request or start I/O
         '    STAT)             !return status
        IF (STAT.NE.0)THEN
           PRINT*,'AQWRITE FAILED, STATUS= ',STAT
           CALL ABORT()
        ENDIF
50    CONTINUE

C     WAIT FOR I/O TO COMPLETE
      CALL AQWAIT (AQP,STAT)
      IF (STAT.LT.0) THEN
         PRINT*,'AQWAIT AFTER AQWRITE FAILED, STATUS=',STAT
         CALL ABORT()
      ENDIF

C     NOW ISSUE TWO COMPOUND READS.  THE FIRST READ
C     GETS THE ODD SECTORS AND THE SECOND GETS THE
C     EVEN SECTORS.
C
      INCS=TOTREQ/2-1
      CALL AQREADC(
      '    AQP,
      '    ODDBUF(1),         ! start address
      '    512,               ! mem stride
      '    1,                 ! block number
      '    1,                 ! number of blocks
      '    2,                 ! disk stride
      '    INCS,              ! incs
      '    1,                 ! request id
      '    1,                 ! queue request
      '    STAT1)             ! return status
      CALL AQREADC(
      '    AQP,
      '    EVNBUF(1),         ! start address
      '    512,               ! mem stride
      '    0,                 ! block number
      '    1,                 ! number of blocks
      '    2,                 ! disk stride
      '    INCS,              ! incs
      '    2,                 ! request id
      '    0,                 ! start request
      '    STAT2)             ! return status
      IF ((STAT1.NE.0). OR. (STAT2.NE.0)) THEN
         PRINT *,'AQREADC FAILED, STATUS= ',STAT1,STAT2
         CALL ABORT()
      ENDIF

      CALL AQWAIT (AQP,STAT)
      IF (STAT.LT.0) THEN
         PRINT *,'AQWAIT FAILED, STATUS= ',STAT
         CALL ABORT()
      ENDIF

C     VERIFY THAT THE DATA READ WAS CORRECT
      K = 1
      DO 90 I = 1,TOTREQ,2
          DO 80 J = 1,512
            IF (EVNBUF (J+(K-1)*512).NE.J+(I-1)*512)THEN
               PRINT *,'BAD DATA EVN',EVNBUF(J+(K-1)*512),J,I,K
               CALL ABORT()
            ENDIF
80        CONTINUE
          K=K+1
90    CONTINUE
      K = 1
      DO 99 I = 2,TOTREQ,2
          DO 95 J = 1,512
             IF (ODDBUF(J+(K-1)*512).NE.J+(I-1)*512)
                PRINT *,'BAD DATA ODD',ODDBUF(J+(K-1)*512),J,I,K
                CALL ABORT()
             ENDIF
95        CONTINUE
          K=K+1
99    CONTINUE
      CALL AQCLOSE(AQP,STAT)
      IF(STAT.NE.0) THEN
              PRINT *,'AQCLOSE FAILED, STATUS= ',STAT
              CALL ABORT()
            ENDIF
       END                                                                   


Example 3-5. AQIO routines: error detection

   PROGRAM AQIO2
   IMPLICIT INTEGER(A-Z)
   PARAMETER (TOTREQ=20)
   PARAMETER (AQPSIZE=20)
   INTEGER AQP
   INTEGER BUFFER (TOTREQ*512)
   INTEGER INBUF (512)

   CALL AQOPEN (AQP,AQPSIZE,'FILE4'H,STAT)
   IF (STAT.NE.0) THEN
      PRINT *,'AQOPEN FAILED, STATUS=',STAT
      CALL ABORT()
   ENDIF

   DO 50 RNUM=1,TOTREQ

C    QUEUE THE REQUESTS
C    INITIATE I/O ON THE LAST REQUEST
C    THE DATA FROM BUFFER WILL BE WRITTEN IN A
C    SEQUENTIAL FASHION TO DISK
     QUEUE=1
     IF (RNUM.EQ.TOTREQ) QUEUE=0
          OFFSET= (RNUM-1)*512+1
          CALL AQWRITE (
          '    AQP,
          '    BUFFER (OFFSET),   ! start address
          '    RNUM-1,            ! block number
          '    1,                 ! number of blocks
          '    RNUM,              ! request id
          '    QUEUE,             ! queue request or start I/O
          '    STAT)              ! return status
      IF (STAT.NE.0) THEN
          PRINT *,'AQWRITE FAILED, STATUS=',STAT
          CALL ABORT ()
      ENDIF
50 CONTINUE

C WAIT FOR I/O TO COMPLETE
   CALL AQWAIT (AQP,STAT)
   IF (STAT.LT.0) THEN
     PRINT *,'AQWAIT AFTER AQWRITE FAILED, STATUS= ',STAT
     CALL ABORT ()
   ENDIF
C  NOW ISSUE A READ. TO ILLUSTRATE ERROR DETECTION
C  ATTEMPT TO READ BEYOND THE END OF THE FILE
   CALL AQREAD (
    '    AQP,
    '    INBUF(1),     ! start address
    '    TOTREQ+1,     ! block number
    '    1,            ! number of blocks
    '    TOTREQ+1,     ! request id
    '    0,            ! start I/O
    '    STAT)         ! return status

   IF (STAT.NE.0)THEN
     PRINT *,'AQREAD FAILED, STATUS=',STAT
     CALL ABORT()
   ENDIF

   CALL AQWAIT (AQP,STAT)
C  BECAUSE WE ATTEMPTED TO READ BEYOND THE END
C  OF THE FILE, AQWAIT WILL RETURN A NEGATIVE
C  VALUE IN "STAT", AND THE PROGRAM WILL ABORT IN
C  THE FOLLOWING STATEMENT

   IF (STAT.LT.0) THEN
     PRINT *,'AQWAIT AFTER AQREAD FAILED, STATUS= ',STAT
     CALL ABORT()
   ENDIF

   CALL AQCLOSE (AQP,STAT)
   IF (STAT.NE.0) THEN
     PRINT *,'AQCLOSE, STATUS= ',STAT
     CALL ABORT()
   ENDIF
   END

The following is the output from running this program:

AQWAIT AFTER AQREAD FAILED, STATUS= -1202


Logical Record I/O Routines (Not Available on IRIX systems)

The logical record I/O routines provide word or character granularity during read and write operations on full or partial records. The read routines move data from an external device to a user buffer. The write routines move data from a user buffer to an external device.

The following list briefly describes these routines; for details about the routines discussed in this section, see the individual man pages for each routine.

  • READ and READP move words of data from disk or tape to a user data area. READ(3f) reads words in full-record mode. READP reads words in partial-record mode.

    READ positions the file at the beginning of the next record after a READ. READP positions the file at the beginning of the next word in the current record after a READP. If foreign record translation is enabled for the specified unit, the bits from the foreign logical records are moved without conversion. Therefore, if the file contained IBM data, that data is not converted before it is stored. The following are examples of calls to READ and READP:

    CALL READ (7,ibuf,icnt,istat,iubc)
    CALL READP(8,ibuf,icnt,istat,iubc)

  • READC(3f) reads characters in full-record mode. READCP reads characters in partial-record mode. Characters are moved to the user area with only one character per word and are right-justified in the word. The bits from foreign logical records are moved after conversion when foreign record translation is enabled for the specified unit. The following are examples of calls to READC and READCP:

    CALL READC (9,ibuf,icnt,istat)
    CALL READCP (10,ibuf,icnt,istat)

  • READIBM(3f) reads IBM 32-bit floating-point words that are converted to Cray 64-bit words. The IBM 32-bit format is converted to the equivalent Cray 64-bit value and the result is stored. A conversion routine, IBM2CRAY(3f), converts IBM data to Cray format. A preferred method to obtain the same result is to read the file with an unformatted READ statement and then convert the data through a call to IBM2CRAY.(blank) The following is an example of a call to READIBM:

    CALL READIBM (7,ibuf,ileng,incr)

  • WRITE(3f) writes words in full-record mode. WRITEP writes words in partial-record mode. WRITE and WRITEP move words of data from the user data area to an I/O buffer area. If foreign record translation is enabled, no data conversion occurs before the words are stored in the I/O buffer area. The following are examples of calls to WRITE and WRITEP:

    CALL WRITE (8,ibuf,icnt,iubc,istat)
    CALL WRITEP (9,ibuf,icnt,iubc,istat)

  • WRITEC(3f) writes characters in full-record mode. WRITECP writes characters in partial-record mode. Characters are packed into the buffer for the file. If foreign record translation is enabled, the characters are converted and then packed into the buffer. The following are examples of calls to WRITEC and WRITECP:

    CALL WRITEC (10,icbuf,iclen,istat)
    CALL WRITECP (11,icbuf,iclen,istat)

  • WRITIBM(3f) writes Cray 64-bit values as IBM 32-bit floating-point words. The Cray 64-bit values are converted to IBM 32-bit format, using a conversion routine, CRAY2IBM(3f). After this conversion, you can use an unformatted WRITE statement to write the file. The following is an example of the call to WRITIBM:

    CALL WRITIBM (12,ibuf,ilen,incr)