HP 3000 Manuals

Supported Data File Types [ COBOL/HP-UX Compatibility Guide for the Series 700 and 800 ] MPE/iX 5.0 Documentation


COBOL/HP-UX Compatibility Guide for the Series 700 and 800

Supported Data File Types 

convert5 can convert sequential, relative and indexed files from DG
Interactive COBOL format to Micro Focus COBOL format.  You do not need to
convert line sequential files as these are already in a format which is
compatible with this COBOL system's requirements.

Sequential Files 

convert5 supports sequential files with either fixed or variable length
records.  The default record type has fixed length records.  However, it
will handle a sequential file with variable length records if the
RECORDING MODE IS VARIABLE clause is included within the FD entry.

Relative Files 

Before transferring relative files to this COBOL environment, you must
reformat them.  To do this, you must add a four-byte field containing
each record's relative key, to the start of every record contained within
the original data file.  Figure 15-1 is an example of a program which
performs this reformatting for a specified relative file which must be
run on your DG machine.

      IDENTIFICATION DIVISION.
      PROGRAM-ID. REL2SEQ.
      DATE-WRITTEN. 10/22/85.
     *
     * THIS PROGRAM CONVERTS A DG RELATIVE FILE TO A
     * FORMAT SUITABLE FOR SUBSEQUENT CONVERSION
     * FOR USE WITH THIS SYSTEM
     *
      ENVIRONMENT DIVISION.
      CONFIGURATION SECTION.
      SOURCE-COMPUTER. DG-10.
      OBJECT-COMPUTER. DG-10.
     *
      INPUT-OUTPUT SECTION.
      FILE-CONTROL.

         SELECT RELATIVE-FILE
         ASSIGN TO DISK "DGRELATIVE"
            ORGANIZATION IS RELATIVE
            ACCESS IS SEQUENTIAL
            RELATIVE KEY IS RELATIVE-KEY
            FILE STATUS IS FILE-STAT.

         SELECT MF-FILE ASSIGN TO DISK "MFRELATIVE"
            ORGANIZATION IS SEQUENTIAL
            ACCESS IS SEQUENTIAL
            FILE STATUS IS FILE-STAT.

       DATA DIVISION.
       FILE SECTION
     .
       FD RELATIVE-FILE
          LABEL RECORDS ARE OMITTED.
       01 RELATIVE-REC                  PIC X(20).

       FD MF-FILE
          LABEL RECORDS ARE OMITTED.
       01 MF-REC.
          03 MF-KEY                PIC 9(9) COMP.
          03 MF-DATA               PIC X(20).

       WORKING-STORAGE SECTION.
       01 RELATIVE-KEY             PIC 9(4) COMP VALUE 0.<%-4>
       01 FILE-STAT                PIC XX VALUE "00".
       01 RELATIVE-FLAG            PIC 9 VALUE 0.
       01 RELATIVE-CNT             PIC 9(9) VALUE 0.
       01 MF-CNT                   PIC 9(9) VALUE 0.

       PROCEDURE DIVISION.
       MAIN-PROCEDURE SECTION.
       MAIN-PROC1.
           OPEN INPUT RELATIVE-FILE
               OUTPUT MF-FILE.
           PERFORM READ-WRITE UNTIL RELATIVE-FLAG = 1.
           DISPLAY "RELATIVE RECORDS READ = " RELATIVE-CNT.
           DISPLAY "MF RECORDS WRITTEN = " MF-CNT.
           CLOSE MF-FILE RELATIVE-FILE.
           STOP RUN.

       READ-WRITE SECTION.
       READ-WRITE1.
           READ RELATIVE-FILE AT END
               MOVE 1 TO RELATIVE-FLAG
               GO TO READ-WRITE-EXIT.
           IF FILE-STAT NOT = "00"
               DISPLAY "INPUT FILE STATUS = " FILE-STAT
               STOP RUN.
           ADD 1 TO RELATIVE-CNT.
           ADD 1 TO MF-CNT.
           MOVE RELATIVE-KEY TO MF-KEY.
           MOVE RELATIVE-REC TO MF-DATA.
           WRITE MF-REC.
           IF FILE-STAT NOT = "00"
              DISPLAY "OUTPUT FILE STATUS = " FILE-STAT
               STOP RUN.

       READ-WRITE-EXIT.
           EXIT.

Once you have reformatted your data file, following the guidelines given
in Figure 15-1, reform5 can read it sequentially and convert it to the
relative format used by this system.

Indexed Files 

You must pass any indexed data files which you wish to convert to Micro
Focus COBOL format, through the DG Interactive COBOL utility REORG. This
enables convert5 to read the data portion of the files sequentially.  It
can then convert them to the indexed format used by this system.



MPE/iX 5.0 Documentation