Several years ago I created a little utility to open sequential files as
needed. It's pretty robust; hasn't given me much trouble over the years.
Like Kevin, I've had problems with the full path version of openseq, so my
utility converts full path mode to VOC pointer mode and creates the VOC
pointer if it doesn't already exist.

I'll include it below and attach it in text form.

Dana Baron
System Manager
Smugglers' Notch Resort


SUBROUTINE OPEN_UNIX_FILE (UNIX.FN, MODE, UNIX.FILE, ERR.CODE)
!**************************************************************************
!       SYSTEM:         AHS
!       MODULE:         UTILITY
!       PROGRAM:        OPEN_UNIX_FILE
!
!       DESCRIPTION:    This subroutine opens a sequential file. Sequential
!                       files can be used to export Unidata data to UNIX.
!
!       Notes:  The parameters passed to this routine are:
!
!               UNIX.FN   - the full file name of the file to open.
!               MODE      - expects the following choices:
!                       C - create a new file
!                       U - update existing file (error message if not there)
!                       UC- update the file if it exists, create a new file if
!                           it doesn't exist.
!               UNIX.FILE - the file reference num returned to calling program
!               ERR.CODE - Error code to indicate results as follows:
!                       0 = No error. Everthing is OK.
!                       1 = (Fatal) Can't open the VOC item for the directory
!                       2 = (Info) VOC item for directory already defined
!                       3 = (Info) In C mode, file exists so renamed
!                       4 = (Warning) In U mode, file does not exist
!                       5 = (Fatal, calling program bug) Invalid mode parameter
!
!**************************************************************************
!                       MODIFICATION HISTORY
!
! EDIT DATE     WHO     REASON/DESCRIPTION
!
! 07/12/96      GDB     Created
!
! 11/14/97      GDB     Added "UC" mode to update file if it exists, create
!                       the file if it doesn't exist.
!
! 02/15/01      GDB     Copied OPEN_VMS_FILE to OPEN_UNIX_FILE and modified
!                       to work in Unix as part of conversion from VMS to Unix.
!**************************************************************************

        TRUE = 1
        FALSE = 0
        ERR.CODE = 0

        OPEN "","VOC" TO VOC.FILE ELSE
                PRINT "CANT OPEN VOC!!!"
                ERR.CODE = 1
                ABORT
        END
!DEBUG
        NUM.SLASH = DCOUNT(UNIX.FN, "/")
        UNIX.DIR = ""
        UNIX.ID = FIELD(UNIX.FN,"/",NUM.SLASH)
        FOR II = 2 TO NUM.SLASH - 1
                UNIX.DIR = UNIX.DIR : "/" : FIELD(UNIX.FN,"/",II)
        NEXT II

        VOC.ITEM = "DIR":@AM:UNIX.DIR
        READ TEST.ITEM FROM VOC.FILE , UNIX.DIR THEN
                IF (TEST.ITEM<2>) = UNIX.DIR THEN
                        NULL
                END ELSE
                        PRINT "VOC ITEM '":UNIX.DIR:"' DEFINED IN VOC AS " :
                        PRINT '"' : TEST.ITEM : '"'
                        ERR.CODE = 2
                END
        END ELSE
                WRITE VOC.ITEM ON VOC.FILE , UNIX.DIR
        END

        BEGIN CASE
        CASE MODE = "C"
                PASS = 1
                RENAME = FALSE
                DONE = 0
                NEW.UNIX.ID = UNIX.ID
                LOOP UNTIL DONE DO
                        OPENSEQ UNIX.DIR, NEW.UNIX.ID TO UNIX.FILE THEN
                                PRINT "FILE ALREADY EXISTS...RENAMING"
                                NEW.UNIX.ID = UNIX.ID : "_" : PASS
                                RENAME = TRUE
                                PASS = PASS + 1
                                ERR.CODE = 3
                        END ELSE
                                DONE = 1
                        END
                REPEAT
                IF RENAME = TRUE THEN
                        PRINT "FILE RENAMED TO " : NEW.UNIX.ID
                END

        CASE MODE = "U"
                DONE = 0
                OPENSEQ UNIX.DIR, UNIX.ID TO UNIX.FILE ELSE
                        PRINT "FILE DOES NOT EXIST"
                        ERR.CODE = 4
                END

        CASE MODE = "UC"
                DONE = 0
                OPENSEQ UNIX.DIR, UNIX.ID TO UNIX.FILE ELSE
                        ! File doesn't exist. A new file is created
                END

        CASE -1
                PRINT "Function called with a bad Mode parameter."
                ERR.CODE = 5
        END CASE

RETURN
SUBROUTINE OPEN_UNIX_FILE (UNIX.FN, MODE, UNIX.FILE, ERR.CODE)
!**************************************************************************
!       SYSTEM:         AHS
!       MODULE:         UTILITY
!       PROGRAM:        OPEN_UNIX_FILE
!
!       DESCRIPTION:    This subroutine opens a sequential file. Sequential
!                       files can be used to export Unidata data to UNIX.
!
!       Notes:  The parameters passed to this routine are:
!
!               UNIX.FN   - the full file name of the file to open.
!               MODE      - expects the following choices:
!                       C - create a new file
!                       U - update existing file (error message if not there)
!                       UC- update the file if it exists, create a new file if
!                           it doesn't exist.
!               UNIX.FILE - the file reference num returned to calling program
!               ERR.CODE - Error code to indicate results as follows:
!                       0 = No error. Everthing is OK.
!                       1 = (Fatal) Can't open the VOC item for the directory
!                       2 = (Info) VOC item for directory already defined
!                       3 = (Info) In C mode, file exists so renamed
!                       4 = (Warning) In U mode, file does not exist
!                       5 = (Fatal, calling program bug) Invalid mode parameter
!
!**************************************************************************
!                       MODIFICATION HISTORY
!
! EDIT DATE     WHO     REASON/DESCRIPTION
!
! 07/12/96      GDB     Created
!
! 11/14/97      GDB     Added "UC" mode to update file if it exists, create
!                       the file if it doesn't exist.
!
! 02/15/01      GDB     Copied OPEN_VMS_FILE to OPEN_UNIX_FILE and modified
!                       to work in Unix as part of conversion from VMS to Unix.
!**************************************************************************

        TRUE = 1
        FALSE = 0
        ERR.CODE = 0

        OPEN "","VOC" TO VOC.FILE ELSE
                PRINT "CANT OPEN VOC!!!"
                ERR.CODE = 1
                ABORT
        END
!DEBUG
        NUM.SLASH = DCOUNT(UNIX.FN, "/")
        UNIX.DIR = ""
        UNIX.ID = FIELD(UNIX.FN,"/",NUM.SLASH)
        FOR II = 2 TO NUM.SLASH - 1
                UNIX.DIR = UNIX.DIR : "/" : FIELD(UNIX.FN,"/",II)
        NEXT II

        VOC.ITEM = "DIR":@AM:UNIX.DIR
        READ TEST.ITEM FROM VOC.FILE , UNIX.DIR THEN
                IF (TEST.ITEM<2>) = UNIX.DIR THEN
                        NULL
                END ELSE
                        PRINT "VOC ITEM '":UNIX.DIR:"' DEFINED IN VOC AS " :
                        PRINT '"' : TEST.ITEM : '"'
                        ERR.CODE = 2
                END
        END ELSE
                WRITE VOC.ITEM ON VOC.FILE , UNIX.DIR
        END

        BEGIN CASE
        CASE MODE = "C"
                PASS = 1
                RENAME = FALSE
                DONE = 0
                NEW.UNIX.ID = UNIX.ID
                LOOP UNTIL DONE DO
                        OPENSEQ UNIX.DIR, NEW.UNIX.ID TO UNIX.FILE THEN
                                PRINT "FILE ALREADY EXISTS...RENAMING"
                                NEW.UNIX.ID = UNIX.ID : "_" : PASS
                                RENAME = TRUE
                                PASS = PASS + 1
                                ERR.CODE = 3
                        END ELSE
                                DONE = 1
                        END
                REPEAT
                IF RENAME = TRUE THEN
                        PRINT "FILE RENAMED TO " : NEW.UNIX.ID
                END

        CASE MODE = "U"
                DONE = 0
                OPENSEQ UNIX.DIR, UNIX.ID TO UNIX.FILE ELSE
                        PRINT "FILE DOES NOT EXIST"
                        ERR.CODE = 4
                END

        CASE MODE = "UC"
                DONE = 0
                OPENSEQ UNIX.DIR, UNIX.ID TO UNIX.FILE ELSE
                        ! File doesn't exist. A new file is created
                END

        CASE -1
                PRINT "Function called with a bad Mode parameter."
                ERR.CODE = 5
        END CASE

RETURN
-------
u2-users mailing list
u2-users@listserver.u2ug.org
To unsubscribe please visit http://listserver.u2ug.org/

Reply via email to