Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations strongm on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

Opening files in append mode

Status
Not open for further replies.

adityai

Programmer
Aug 8, 2004
10
US
How can I open a file in append mode? I use Fujitsu Cobol v 3.0. I know how to open indexed sequential files and regular files. Please suggest a solution.
 
I was able to input more records to the file in append mode. I was not able to read from the file at the same time. The error message that I see is: JMP0330I-U STATEMENT SEQUENCE ERROR. STM=READ.FILE=(DATAFILE).'OPEN-MODE'.PGM=SAMPLE1 ADR=0040155E. Can you help me fix this bug? Also, can you suggest a way to move to the top of the file or to seek a particular record from the file?

The following is the full source code:

IDENTIFICATION DIVISION.
PROGRAM-ID. SAMPLE1.
AUTHOR. ADITYA.
*
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT DATAFILE
ASSIGN TO DISK
ORGANIZATION IS LINE SEQUENTIAL.

DATA DIVISION.
FILE SECTION.
FD DATAFILE.
01 INPUT-RECORD.
05 PERSON-RECORD.
10 FIRSTNAME PIC X(6).
10 PIC X.
10 LASTNAME PIC X(9).
10 PIC X.
10 PHONE PIC X(10).
10 PIC X.
10 FAX PIC X(10).
10 PIC X.
10 EMAIL PIC X(30).
10 PIC X.

WORKING-STORAGE SECTION.
01 WORD-INDEX PIC 9(3).
01 INPUT-PERSON.
05 INPUT-FIRST-NAME PIC X(6).
05 PIC X VALUE SPACES.
05 INPUT-LAST-NAME PIC X(9).
05 PIC X VALUE SPACES.
05 INPUT-PHONE PIC X(10).
05 PIC X VALUE SPACES.
05 INPUT-FAX PIC X(10).
05 PIC X VALUE SPACES.
05 INPUT-EMAIL PIC X(30).
05 PIC X VALUE SPACES.


01 REQUEST-MESSAGE PIC X(42)
VALUE "DIGITAL ORGANIZER".

01 OPTION PIC 9.
01 LASTNAME-SEARCH PIC X(9).

*
PROCEDURE DIVISION.
DATA-INPUT SECTION.

OPEN EXTEND DATAFILE WITH LOCK.
PERFORM MENU-OPTIONS.
DISPLAY REQUEST-MESSAGE.

MENU-OPTIONS.
DISPLAY "SELECT AN OPTION".
DISPLAY "1 - NEW ENTRY".
DISPLAY "2 - VIEW BY LAST-NAME".
DISPLAY "3 - EXIT".
ACCEPT OPTION.

IF OPTION = 1 THEN
PERFORM LOOP-INPUT.
IF OPTION = 2 THEN
PERFORM SEARCH-LASTNAME.
IF OPTION = 3 THEN
PERFORM TERMINATE-FILE-WRITE.

SEARCH-LASTNAME.
* DISPLAY "ENTER THE LAST-NAME".
* ACCEPT LASTNAME-SEARCH.
READ DATAFILE AT END PERFORM MENU-OPTIONS.
MOVE INPUT-RECORD TO INPUT-PERSON.
DISPLAY "FIRST NAME: " INPUT-FIRST-NAME.
DISPLAY "LAST NAME: " INPUT-LAST-NAME.
DISPLAY "EMAIL: " INPUT-EMAIL.
DISPLAY "PHONE: " INPUT-PHONE.
GO TO SEARCH-LASTNAME.
* PERFORM MENU-OPTIONS.

TERMINATE-FILE-WRITE.
DISPLAY "CLOSING DATAFILE".
CLOSE DATAFILE.
EXIT PROGRAM.

LOOP-INPUT.
DISPLAY "Enter your information:".
DISPLAY "LAST-NAME: " UPON CONSOLE NO ADVANCING.
ACCEPT INPUT-LAST-NAME FROM CONSOLE.

DISPLAY "FIRST-NAME: " UPON CONSOLE NO ADVANCING.
ACCEPT INPUT-FIRST-NAME FROM CONSOLE.

DISPLAY "PHONE: " UPON CONSOLE NO ADVANCING.
ACCEPT INPUT-PHONE FROM CONSOLE.

DISPLAY "FAX: " UPON CONSOLE NO ADVANCING.
ACCEPT INPUT-FAX FROM CONSOLE.

DISPLAY "EMAIL: " UPON CONSOLE NO ADVANCING.
ACCEPT INPUT-EMAIL FROM CONSOLE.

MOVE INPUT-PERSON TO INPUT-RECORD.
WRITE INPUT-RECORD.
PERFORM MENU-OPTIONS.

EXIT PROGRAM.
END PROGRAM SAMPLE1.
 
1. INPUT and EXTEND are mutually exclusive. Your cannot READ a file and WRITE to end of it without an intervening CLOSE and OPEN. You can, however, open a RELATIVE or INDEXED file I-O and both read existing records and write new ones.

2. LINE SEQUENTIAL records are variable in length. There is no way to "find" a particular record without reading the file from the beginning.

3. Looking at your code, I think your application would be best served by an INDEXED file.
 
Just some info...

A sequential file in COBOL can only be processed forwards.
A sequential file can only be processed in one of the following ways:
(based on COBOL-85)

OPEN OUTPUT /* creates new file
OPEN INPUT /* positions at the beginning of an existing file
OPEN EXTEND /* opens at the end of an existing file (to add new records)
OPEN I-O with REWRITE /* modifies the record just read and positions to the next record

For a clear explanation and more detailed information see:


Regards, Wim.
 
Webrabbit,
LOL; been there, done that, that's why no peroids

Steve
 
A sequential file in COBOL can only be processed forwards."


In the IBM world you could put it on a tape and read it backwards. OPEN REVERSED
 
Even in the IBM world, you cannot read a varable length sequential file backwards. The length field is at the beginning of the record. How do you find it if you don't know the length? It is true that if you use BSAM, you can read the blocks backward, then scan the records forward. Of course, with VSAM you can read the records backwards, as VSAM has all its magic pointers.

In the PC world, LINE SEQUENTIAL records are intrinsically variable length. Variable length BINARY (or RECORD) SEQUENTIAL records have the length field at the beginning, just like on IBM mainframes. Again, INDEXED files can be read backwards by key, even if the data records are variable length, because the indices have all their magic pointers.
 
RM/COBOL supports READ PREVIOUS on BINARY SEQUENTIAL files. We place the record length field at both ends of the record. Don't know how many folks actually use this feature though.

Tom Morrison
 
Ignore previous post. xyzzy has informed me via the back channel that I was wrong. I hate to admit but he ... is ...... ....... right. That hurt.[blush]

Tom Morrison
 
Hi Adityai,

I know in Mainframe COBOL you could possibly read existing recs in the file and append new recs to the end of the file. You could also update those recs you read.

Someone here should be able to tell you if it's possible w/Fujitsu. I suspect that it is.


But first you have to tell us what ALL your true requirements are.

Regards, Jack.

"A problem well stated is a problem half solved" -- Charles F. Kettering
 
Try this version. I changed the file Organization to INDEXED and added a little error checking.
Code:
 Identification Division.
 Program-ID. SAMPLE1.
 Author.     ADITYA -- Changes by WebRabbit.

 Environment Division.
 Input-Output Section.
 File-Control.
     Select DATAFILE
          Assign       to Disk
          File Status  is FILE-STATUS
          Organization is Indexed
          Access       is Dynamic
          Record Key   is PERSON-KEY
          .

 Data Division.
 File Section.
 FD  DATAFILE.
 01  PERSON-RECORD.
     05  PERSON-KEY              Pic X(50).
     05  PERSON-NAME.
         10  PERSON-LAST-NAME    Pic X(30).
         10  PERSON-FIRST-NAME   Pic X(20).
     05  PERSON-PHONE            Pic X(10).
     05  PERSON-FAX              Pic X(10).
     05  PERSON-EMAIL            Pic X(30).

 Working-Storage Section.
 01  FILE-STATUS.
     88  ENTRY-NOT-FOUND                   Value "23".
     88  DUPLICATE-ENTRY                   Value "22".
     05  FILE-STATUS-1           Pic X(01).
         88  FILE-OK                       Value "0".
         88  FILE-AT-END                   Value "1".
     05  FILE-STATUS-2           Pic X(01) Comp-X.

 01  WORK-RECORD.
     05  WORK-KEY                Pic X(50).
     05  WORK-NAME.
         10  WORK-LAST-NAME      Pic X(30).
         10  WORK-FIRST-NAME     Pic X(20).
     05  WORK-PHONE              Pic X(10).
     05  WORK-FAX                Pic X(10).
     05  WORK-EMAIL              Pic X(30).

 01  OPTION                      Pic 9(01).

 Procedure Division.
 MAIN-ROUTINE.
     Open I-O DATAFILE
     If FILE-OK
         Move Zero to OPTION
         Display "Digital Organizer"
         Perform Until OPTION = 3
             Display "Select an Option"
             Display "1 - New Entry"
             Display "2 - View by Last Name"
             Display "3 - Exit"
             Accept OPTION
             Evaluate OPTION
                 When 1
                     Perform ADD-A-NAME
                 When 2
                     Perform SEARCH-BY-LAST-NAME
                 When 3
                     Continue
                 When Other
                     Display "Invalid Option"
             End-Evaluate
         End-Perform
         Close DATAFILE
     End-If
     Perform DISPLAY-ERROR
     Stop Run
     .

 SEARCH-BY-LAST-NAME.
     Move Space                                   to WORK-LAST-NAME
     Display "Enter Last Name - " with no Advancing
     Accept WORK-LAST-NAME
     If WORK-LAST-NAME not = Space
         Move Function UPPER-CASE(WORK-LAST-NAME) to WORK-KEY
         Move WORK-KEY                            to PERSON-KEY
         Start DATAFILE Key = PERSON-KEY Size 30
         If FILE-OK
             Read DATAFILE Next Record
             If FILE-OK
                 Move PERSON-RECORD               to WORK-RECORD
                 Read DATAFILE Next Record
                 If FILE-AT-END
                     Move '00'                    to FILE-STATUS
                     Move Space                   to PERSON-KEY
                 End-If
                 If FILE-OK
                     If PERSON-KEY(1:30) = WORK-KEY(1:30)
                         Perform SEARCH-BY-FIRST-NAME
                     Else
                         Perform DISPLAY-ENTRY
                     End-If
                 End-If
             End-If
         End-If
         Perform DISPLAY-ERROR
     End-If
     .

 SEARCH-BY-FIRST-NAME.
     Display "Multiple entries for " WORK-LAST-NAME
     Move Space to WORK-FIRST-NAME
     Display "Enter First Name - " with no Advancing
     Accept WORK-FIRST-NAME
     If WORK-FIRST-NAME not = Space
         Move Function UPPER-CASE(WORK-NAME) to WORK-KEY
         Move WORK-KEY to PERSON-KEY
         Start DATAFILE Key = PERSON-KEY
         If FILE-OK
             Read DATAFILE Next Record
             If FILE-OK
                 Move PERSON-RECORD to WORK-RECORD
                 Perform DISPLAY-ENTRY
             End-If
         End-If
     End-If
     .

 DISPLAY-ERROR.
     If FILE-STATUS-1 > "1"
         Display " "
         Evaluate True
             When ENTRY-NOT-FOUND
                 Display "Not found."
             When DUPLICATE-ENTRY
                 Display "Duplicate entry."
             When Other
                 Display "File error - " with no advancing
                 If FILE-STATUS-1 = "9" or FILE-STATUS-2 < 48 or > 57
                     Display FILE-STATUS-2
                 Else
                     Display FILE-STATUS
                 End-If
         End-Evaluate
         Display " "
     End-If
     .

 DISPLAY-ENTRY.
     Display " "
     Move Space to WORK-KEY
     String WORK-FIRST-NAME Delimited by "  " " " Delimited by Size WORK-LAST-NAME Delimited by "  " into WORK-KEY
     Display WORK-KEY
     If WORK-PHONE not = Space
         Display "Phone: " WORK-PHONE
     End-If
     If WORK-FAX not = Space
         Display "Fax:   " WORK-FAX
     End-If
     If WORK-EMAIL not = Space
         Display "email: " WORK-EMAIL
     End-If
     Display " "
     .

 ADD-A-NAME.
     Move Space to WORK-RECORD
     Display "Enter First Name - " with no Advancing
     Accept WORK-FIRST-NAME
     If WORK-FIRST-NAME not = Space
         Display "Enter Last Name  - " with no Advancing
         Accept WORK-LAST-NAME
         If WORK-LAST-NAME not = Space
             Move Function UPPER-CASE(WORK-NAME) to WORK-KEY
             Move WORK-KEY to PERSON-KEY
             Start DATAFILE Key = PERSON-KEY
             If FILE-OK
                 Set DUPLICATE-ENTRY to True
             Else
                 If ENTRY-NOT-FOUND
                     Display "Enter Phone - " with no Advancing
                     Accept WORK-PHONE
                     Display "Enter Fax   - " with no Advancing
                     Accept WORK-FAX
                     Display "Enter email - " with no Advancing
                     Accept WORK-EMAIL
                     Write PERSON-RECORD from WORK-RECORD
                 End-If
             End-If
             Perform DISPLAY-ERROR
         End-If
     End-If
     .
This works a lot better with a formatted screen, but that is somewhat beyond the request. I built a separate key in upper case only to eliminate case significance in the search.
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top