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 gkittelson on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

File Status code 47 Error

Status
Not open for further replies.

razalas

Programmer
Apr 23, 2002
237
US
Am trying to trap all I/O errors using DECLARATIVES (see code below). I have a declarative section for each of the file processing modes (INPUT, I-O, OUTPUT, EXTEND), but when I get a "47" error (attempted read on an unopened file), none of the declarative sections get invoked and instead I get the default system action. I think this happens because the I/O is for a file that has not yet been opened, and hence there is no declarative section "active" to handle the error for the file in question.

Granted a "47" error is indicative of a program logic problem and should be pretty rare in production. Still I would like to be able to trap these errors (also "42", "47" & "48") for reporting purposes. Has anyone experienced this? and does anyone have any suggestions for handling it?

Or is this just a "hole" in the current COBOL def'n? I want to say that I've heard/read something somewhere about expanded exception facilities in the next COBOL standard. Can anyone shed any light on this?

Code:
IDENTIFICATION DIVISION.
PROGRAM-ID. MY-PROGRAM.
...
ENVIRONMENT DIVISION.
...
INPUT-OUTPUT SECTION.
   SELECT CNTL-FILE
       ASSIGN TO DISK
       ORGANIZATION IS INDEXED
       ACCESS IS DYNAMIC
       RECORD KEY IS CF-RCD-KEY
       FILE STATUS IS IO-STATUS.
...
DATA DIVISION.
FILE SECTION.
FD  CNTL-FILE
    DATA RECORD IS CNTL-FILE-RCD.
01  CNTL-FILE-RCD.
    03  CF-RCD-KEY PIC X(08).
    03  CF-RCD-DATA PIC X(72).
    ...
WORKING-STORAGE SECTION.
77  IO-STATUS PIC X(02).
    88  IO-STATUS-IS-SUCCESSFUL VALUES "00" "02"
                                       "05" "07".
    COPY STD-ERR-DATA.
    ...
PROCEDURE DIVISION.
DECLARATIVES.
INPUT-ERROR SECTION.
    USE AFTER STANDARD ERROR PROCEDURE INPUT.
INPUT-ERRORS.
    PERFORM I-O-ERRORS.
OUTPUT-ERROR SECTION.
    USE AFTER STANDARD ERROR PROCEDURE OUTPUT.
OUTPUT-ERRORS.
    PERFORM I-O-ERRORS.
EXTEND-ERROR SECTION.
    USE AFTER STANDARD ERROR PROCEDURE EXTEND.
EXTEND-ERRORS.
    PERFORM I-O-ERRORS.
IO-ERROR SECTION.
    USE AFTER STANDARD ERROR PROCEDURE I-O.
I-O-ERRORS.
    ACCEPT STD-ERR-TIME-STAMP FROM DATE-AND-TIME
    MOVE SIGNON-NAME TO STD-ERR-USER
    MOVE IO-STATUS TO STD-ERR-STATUS
    ...
END DECLARATIVES.
PROCESSING SECTION.
MAIN.
    ...
    PERFORM GET-SYS-ID
    ...
GET-SYS-ID.
    MOVE "SYS-ID" TO CF-RCD-KEY
    READ CNTL-FILE
    IF  IO-STATUS-IS-SUCCESSFUL
        MOVE CF-RCD-DATA TO WS-SYS-ID
    ELSE
        MOVE "CNTL-FILE" TO STD-ERR-RESOURCE
        MOVE CF-RCD-KEY  TO STD-ERR-KEY
        CALL STD-ERROR USING STD-ERR-DATA
        STOP RUN
    END-IF.
    ...
END PROGRAM MY-PROGRAM.

I abend on the "READ CNTL-FILE" statement if GET-SYS-ID is PERFORM'ed when the CNTL-FILE has not been opened yet. I would rather that STD-ERROR were CALL'ed to log the error instead.

Environment is RM/Cobol 7.1 on Unix (SCO 5.0.6a).

"Code what you mean,
and mean what you code!
But by all means post your code!"

Razalas
 
I found this statement in my book. If a file is described with the standard LABEL RECORDS ARE OMITTED statement, the Use statement procedures do not apply, and the standard system procedures are performed.

I have never used declaratives myself.

I also noted procedures used must be in the declarative section and can not be referenced from other sections. This means do not leave the declaratives section, and if you do you can not come back. Beware of a GO TO!

It seems there are a lot of ins and outs if you use declaratives. This is a subject that an entire book could be wrtitten about.



If you do not like my post feel free to point out your opinion or my errors.
 
You might consider:
Code:
EXTEND-ERROR SECTION.
    USE AFTER ERROR PROCEDURE CNTL-FILE.
A.  PERFORM I-O-ERRORS.

While this may seem a bit more tedious it will work in the case you are concerned about, since it specifies the file and cures the ambiguity when the file is neither open nor in the process of being opened.

Tom Morrison
 
The way I do it is not to have a DECLARATIVES at all, but to define a file status and check it after every I/O. It helps to put all the I/O for each file in a separate paragraph/section. You can then do record counts, key control and such in the same paragraph as the read/write. In most cases, I put all the I/O for a given file in a separate program, then call that program with I/O requests. That way I can put robust error processing routines in the sub-program and not have to worry about putting such in the applications.
 
webrabbit,

It would seem that you would need a "do nothing" DECLARATIVES procedure for the file within the subprogram to keep errors from terminating your run unit.

This gets into an implementor defined area. The COBOL standard states that the implementor defines what action is taken when "critical" errors (any status >= 30) so if your code is working without a DECLARATIVES procedure it almost certainly not portable. [sad]

Tom Morrison
 
Have you traced extactly where your logic crashes?
Are you sure it's after the READ but before the IF?
Do you actually get into STD-ERROR before the crash?
Could is be the subprogram crashing?
I know this is no help to you, but I've never had
any problem with DOS Microfocus COBOL - it's
truely bullet-proof.
 
I know this shouldn't make any difference, and probably
doesn't, but ...

I noticed you've decided not to put a full-stop
after your MOVE statement & after your READ statement.

 
Webrabbit & Tom,

thanks for your input. Sorry I haven't responded sooner.

Webrabbit,

I totally agree with your suggestion of using separate file I/O modules[medal]. That is an architectural technique which has many benefits. At my last shop, we used them exclusively with great success. Unfortunately, in my current shop I am still working on convincing those with the clout that this is the way to go.

Tom,

changing the DECLARATIVE/USE statement from being associated with the file open mode to the specific file works and allows me to trap the error[Bigsmile]. Unfortunately, I was trying to develop some generic code that could be copied into any program to cover all the files. For now I will have to code a SECTION/USE statement for every file in each program. This is workable, but less than ideal.

Regarding Webrabbit's comments about a file I/O program without any DECLARATIVES, as you are well aware there are 3 facilities in COBOL for handling I/O errors: the FILE STATUS clause, declaratives and exception clauses (i.e. INVALID KEY, AT END). IBM's implementation of COBOL requires that only one of these be present/active in order to prevent program termination. So that the FILE STATUS clause is sufficient to trap all I/O errors. This allows for handling all I/O errors by checking the file status code instead of using the declaratives. However, as you point out, this is "implementor defined" so that this technique results in code that is not always portable (as I have found out). RM/Cobol requires either declaratives or exception clauses to prevent program termination. It would be nice if this were a configurable option. But at least for now I can do what I need.

"Code what you mean,
and mean what you code!
But by all means post your code!"

Razalas
 
Terminate,

thank you too for taking the time to look at my code!

Yes, Yes, No, No.

Regarding the lack of period's in my code, I prefer a style of coding that only uses the period to terminate paragraphs not imperative statements, especially since the inclusion of the "END-" statement terminators with the Cobol 85 standard. I believe this results in better code. A period can too easily be ambiguous whereas END-IF, END-PERFORM, etc. is much less likely to be so. This is part of what I am referring to with my by-line.

"Code what you mean,
and mean what you code!
But by all means post your code!"

Razalas
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top