HP3000-L Archives

February 2005, Week 2

HP3000-L@RAVEN.UTC.EDU

Options: Use Monospaced Font
Show Text Part by Default
Show All Mail Headers

Message: [<< First] [< Prev] [Next >] [Last >>]
Topic: [<< First] [< Prev] [Next >] [Last >>]
Author: [<< First] [< Prev] [Next >] [Last >>]

Print Reply
Subject:
From:
Brian Donaldson <[log in to unmask]>
Reply To:
Brian Donaldson <[log in to unmask]>
Date:
Sat, 12 Feb 2005 13:53:27 -0500
Content-Type:
text/plain
Parts/Attachments:
text/plain (105 lines)
Interesting little thing I just discovered -- maybe programmer brain
damage, maybe not.......   :-)

I have a Cobol program that does read/writes to multiple files.

Code examples here:


SELECT PAGE-012-FILE ASSIGN TO "PAGE012,,,DISC,500000"
                      ORGANIZATION IS INDEXED
                      RECORD KEY   IS PAGE-012-KEY
                                 WITH DUPLICATES
            ALTERNATE RECORD KEY   IS PAGE-012-LINE-SEQ-NO-X
                                 WITH DUPLICATES
                      ACCESS MODE  IS RANDOM
                      FILE STATUS  IS WS-STATUS.

FD  PAGE-012-FILE.
 01  PAGE-012-RECORD.
     05  PAGE-012-FILE-NAME               PIC  X(26).
     05  PAGE-012-DATA-RECORD.
         10  PAGE-012-KEY.
             15  PAGE-012-PAGE-NO         PIC  9(05).
             15  PAGE-012-LINE-NO-X.
                 20  PAGE-012-LINE-NO     PIC  9(02).
         10  PAGE-012-DATA-TABLE.
             15  PAGE-012-LINE-SEQ-NO-X.
                 20  PAGE-012-LINE-SEQ-NO PIC  9(04).
             15  PAGE-012-STREAM-LINE     PIC  X(256).

The "PAGE012" (temporary) file is accessed with the Cobol READ/WRITE verbs.

I use the MPEiX intrinsics FOPEN/FWRITE/FCLOSE on another temporary file
named "TEMPOUT".

"PAGE012" is already open when I try to work on the "TEMPOUT" file. (Opened
with the Cobol OPEN I-O verb.)

Before I do the "FOPEN" on the temp file "TEMPOUT" I do an "FCLOSE" on it
with a \4\ disposition (close with delete option). Just a precautionary
measure to make sure the old version of "TEMPOUT" is gone before FOPENing a
new one.

Well, guess what? The "FCLOSE" with the \4\ disposition is closing and
purging the "PAGE012" file !!

My solution to the problem was to remove the "FCLOSE" with the \4\
disposition but therein remains the mystery.

Is this a bug in the file system or an application bug in my program? (Nah,
never -- every programmer writes "perfect" code, right?)



Actually, this reminds me of another "problem" I discovered many eons ago
(pre 5.5) that it was disastrous to use "FOPEN" and "HPFOPEN" in the same
program as they both can return the SAME file number on different files!!

I don't know if HP ever fixed that probem or not....


PROCEDURE DIVISION.



…
…

*Added as precaution to ensure file is closed and non-existent before FOPEN
    CALL INTRINSIC “FCLOSE” USING WS-FILE-NUM-OUT,
                                                                     \4\ \0
\.

     MOVE "TEMPOUT" TO WS-TEMP-FILE-NAME.
     MOVE ZEROES    TO ERR-FLAG.
     MOVE SPACES    TO WS-STOP-FLAG.
     CALL INTRINSIC "FOPEN" USING WS-TEMP-FILE-NAME,
                                  \4\ \1\
                                  WS-REC-SIZE,
                                  \\ \\ \\ \\
                                  \\    WS-FLIMIT-SIZE
                                  \\ \\ WS-FILE-CODE-2
                           GIVING WS-FILE-NUM-OUT
     END-CALL.
     IF C-C NOT = ZEROES THEN
        CALL INTRINSIC "FCHECK" USING WS-FILE-NUM-OUT,
                                      WS-ERROR-CODE
                                      \\ \\ \\
        END-CALL
        MOVE 10  TO WS-MSGNUM
        MOVE 1   TO ERR-FLAG
        MOVE "Y" TO WS-STOP-FLAG
        GO TO XXXX-EXIT
     END-IF.

     CALL INTRINSIC "FCLOSE" USING WS-FILE-NUM-OUT,
                                   \%12\ \0\
     END-CALL.


Brian Donaldson.

* To join/leave the list, search archives, change list settings, *
* etc., please visit http://raven.utc.edu/archives/hp3000-l.html *

ATOM RSS1 RSS2