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

Parameter=Sequential File to read - getting Unix error 21 1

Status
Not open for further replies.

SiouxCityElvis

Programmer
Jun 6, 2003
228
US
Can someone explain to me why

runcobol FILLGACH.COB a=TESTACHRECS
causes this to come up?
I am running RMCOBOL-85 on Linux.

PASS-FILENAME:
TESTACHRECS
WS-FILENAME:
TESTACHRECS

COBOL I/O error 30, UNIX error 21 on FILE-ARG-INPUT file /gach/data/.
COBOL I/O error at line 260 in program FILLGACH.COB (/gach/FILLGACH.COB)

Here's my code snippet and my TESTACHRECS exists in a /gach/data/ directory.

Code:
FILE-CONTROL.

       SELECT OPTIONAL FILE-ARG-INPUT ASSIGN TO 
               WS-FILE-ARGUMENT
               ORGANIZATION IS LINE SEQUENTIAL
               ACCESS IS SEQUENTIAL.
   

WORKING-STORAGE SECTION.
     ...
     ...
     01 WS-FILE-ARGUMENT.
          02 WS-FILE-ARG-DIRECTORY PIC X(11)    
              VALUE "/gach/data/".
          02 WS-FILE-ARG-NAME      PIC X(30).


     PROCEDURE DIVISION USING LINK-ARGUMENT.
        ...
        ...
     MAIN-PROGRAM.
           PERFORM A-100-INITIALIZATION.
           MOVE 0 TO ADD-CTR.
           PERFORM TEST-INPUT-FILE.
           GO TO END-IT.

      ******************************************************************
       A-100-INITIALIZATION.

           DISPLAY "PASS-FILENAME: " PASS-FILENAME.
           MOVE PASS-FILENAME TO WS-FILE-ARG-NAME.
           DISPLAY "WS-FILENAME: " WS-FILE-ARG-NAME.
           OPEN INPUT FILE-ARG-INPUT.

           OPEN OUTPUT GACHDB-FILE.

      ******************************************************************
      *                                                                *
      *        FILE PROCRESSING CONTROL ROUTINE                        *
      *                                                                *
      ******************************************************************

      ******************************************************************
       TEST-INPUT-FILE.
           MOVE "N" TO SW-EOF-ARG-FILE.
           PERFORM UNTIL EOF-ARG-FILE
             READ FILE-ARG-INPUT NEXT RECORD
                AT END
debug             DISPLAY "AT END OF FILE"
                NOT AT END
                   PERFORM UNSTRING-REC-FIELDS
                   PERFORM WRITE-ACHDB-REC
             END-READ
           END-PERFORM.

...
...


So, my display statements show up, which tells me that there is no problem opening the file. The error says line 260(the READ statement line) is where the problem is.

Thanks.

-David
 
Check your file definition, size, "ORGANIZATION IS LINE SEQUENTIAL".

 
Okay, from what I've done in the past, you can do a READ BLAHBLAH NEXT RECORD.

My file definition is good from what I can see also.

My file size should be fine also, right?
Code:
WORKING-STORAGE SECTION.
01 WS-FILE-ARGUMENT.
          02 WS-FILE-ARG-DIRECTORY PIC X(11)    
              VALUE "/gach/data/".
          02 WS-FILE-ARG-NAME      PIC X(30).

LINKAGE SECTION .
      01  LINK-ARGUMENT.
      05  PASS-FILENAME               PIC  X(30).
...
PROCEDURE DIVISION USING LINK-ARGUMENT.
      
A-100-INITIALIZATION.

           DISPLAY "PASS-FILENAME: " PASS-FILENAME.
           MOVE PASS-FILENAME TO WS-FILE-ARG-NAME.
           DISPLAY "WS-FILENAME: " WS-FILE-ARG-NAME.
           OPEN INPUT FILE-ARG-INPUT.


...

The move PASS-FILENAME TO WS-FILE-ARG-NAME and subsequent OPEN INPUT FILE-ARG-INPUT seems to work.
As I said the error occurs at the READ line, not on the OPEN INPUT line.

So, I'm confused here....

 
Another frustrating point while trying to troubleshoot this "unix error 21". I go to Page A-13 in the RMCOBOL-85 User's Guide, and it tells me to go into my errno.h #include file. So, I go to the /usr/include/ dir and view the errno.h file and there's nothing worth a darn in there about 21 errors or any other error values with their definitions.
 
21 EISDIR
ie you are trying to read a directory as a sequential file.

Hope This Helps, PH.
Want to get great answers to your Tek-Tips questions? Have a look at FAQ219-2884 or FAQ222-2244
 
Here's what I found due to using Display statements.
For example, if I execute with

runcobol FILLGACH.COB a=TESTACHRECS.txt

the 'a=' portion is part of the PASS-FILENAME value. I have no idea why, but it is.

So, if I say I want to open only the TESTACHRECS.txt portion and not the whole parameter of a=TESTACHRECS.txt, then it works. I do this via a substring of WS-FILE-ARG-NAME(3:) and it will work.

I don't understand it through and through, but for some reason the 'a=' portion is also part of my PASS-FILENAME value. I thought whatever followed the 'a=' would be the part that would populate the variable. Actually, the value a= does not appear, but 2 leading blanks do.

?????? Baffled.

 
Those two blanks you are seeing are the length of the parameter passed in with the A= command line option. They are not blanks, they are a two-byte binary number. See Chapter 7 of the RM/COBOL User's guide.

Try something like this:

Code:
      01 WS-FILE-ARGUMENT.
          02 WS-FILE-ARG-DIRECTORY PIC X(11)
              VALUE "/gach/data/".
          02 WS-FILE-ARG-NAME      PIC X(30).

       LINKAGE SECTION .
       01  LINK-ARGUMENT.
           05  PASS-SIZE                   PIC S9(4) BINARY.
           05  PASS-FILENAME.
               10   PASS-STRING            PIC  X
                    OCCURS 0 TO 100 DEPENDING ON PASS-SIZE.

       PROCEDURE DIVISION USING LINK-ARGUMENT.
       A-100-INITIALIZATION.
           IF PASS-SIZE > 0
               DISPLAY "PASS-FILENAME: " PASS-FILENAME(1:Pass-Size)
               MOVE PASS-FILENAME(1:Pass-Size) TO WS-FILE-ARG-NAME
               DISPLAY "WS-FILENAME: " WS-FILE-ARG-NAME
               OPEN INPUT FILE-ARG-INPUT.

-Robert Heady
Liant Software Corp.
 
xyzzy,

Thanks. That was actually a much cleaner way of coding for this.

-David
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top