Trailing-Edge
-
PDP-10 Archives
-
BB-AE97A-BM
-
sources/cd32t1.vax-cob
There are 2 other files named cd32t1.vax-cob in the archive. Click here to see a list.
IDENTIFICATION DIVISION.
PROGRAM-ID.
CD32T1.
AUTHOR.
DIGITAL EQUIPMENT CORPORATION.
This program opens a remote file named DAP.TST and writes an
ASCII record into it, closes the file, reopens the file and
reads the record back and then closes the file again. This
program writes and reads the file DAP.TST using the connected
directory.
COPYRIGHT (C) DIGITAL EQUIPMENT CORPORATION 1982, 1983.
This software is furnished under a license and may be used and
copied only in accordance with the terms of such license and
with the inclusion of the above copyright notice. This
software or any other copies thereof may not be provided or
otherwise made available to any other person. No title to and
ownership of the software is hereby transferred.
The information in this software is subject to change without
notice and should not be construed as a commitment by Digital
Equipment Corporation.
Digital assumes no responsibility for the use or reliability
of its software on equipment which is not supplied by Digital.
*
* Facility: DIT-TEST
*
* Edit History:
*
* new_version (1, 0)
*
* Edit (%O'1', '15-Dec-82', 'Sandy Clemens')
* %( Add the DIT (Dap and Task-to-task) Installation Verification tests
* for the VAX and DECSYSTEM-20 to the library.
* Files: DITTHST.TXT (NEW), CD32T1.VAX-COB (NEW),
* CT32T1.VAX-COB (NEW), FD32T1.VAX-FOR (NEW),
* FT32T1.VAX-FOR (NEW), CD36T1.CBL (NEW), CT36T1.CBL (NEW),
* FD6T1.FOR (NEW), FD7T1.FOR (NEW), FT6T1.FOR (NEW),
* FT7T1.FOR (NEW) )%
*
*
* Edit (%O'2', '14-Jan-83', 'Sandy Clemens')
* %( Many edits to the Installation Verification system (ICS) files.
* Add SYS: to all the 10/20 programs in the COPY or INCLUDE
* statement for the interface files. Add SYS$LIBRARY to the VAX
* programs in the COPY or INCLUDE statement for the interface
* files. Add check for INFO or SUCCESS status return in all ICS
* programs. Remove node names from all DIT programs so that local
* node is used. Change directory used by 20 DAP programs to be
* PS:<DIL-TEST> with password DIL-TEST. Remove all directory
* specifications from VMS programs so they use the default
* connected directory. Add Lib$Match_Cond to VMS programs for
* status checking. Change some of the symbolic variable names for
* clarification. Change use of numeric parameter values to
* symbolic variable names. Get rid of use of "IMPLICIT INTEGER"
* in FORTRAN test programs. Add copyright notice to everything.
* Files: CD32T1.VAX-COB, CD36T1.CBL, CT32T1.VAX-COB, CT36T1.CBL,
* FD32T1.VAX-FOR, FD6T1.FOR, FD7T1.FOR, FT32T1.VAX-FOR, FT6T1.FOR,
* FT7T1.FOR, DITTHST.TXT )%
*
* Edit (%O'6', '25-Jan-83', 'Sandy Clemens')
* %( Add copyright and liability waiver to whatever needs it.
* FILES: CD32T1.VAX-COB, CD36T1.CBL, CT32T1.VAX-COB, CT36T1.CBL,
* FD32T1.VAX-FOR, FD6T1.FOR, FD7T1.FOR, FT32T1.VAX-FOR, FT6T1.FOR,
* FT7T1.FOR, SUB6D1.FOR, SUB6T1.FOR, SUB7D1.FOR, SUB7T1.FOR )%
*
* Edit (%O'7', '25-Jan-83', 'Sandy Clemens')
* %( Standardize "Author" entry in ICS Cobol programs.
* FILES: CD32T1.VAX-COB, CD36T1.CBL, CT32T1.VAX-COB, CT36T1.CBL )%
INSTALLATION.
DEC-MARLBOROUGH.
DATE-WRITTEN.
NOVEMBER 5, 1982.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SOURCE-COMPUTER.
VAX-11.
OBJECT-COMPUTER.
VAX-11.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 INTERFACE-FILES.
COPY DIT$COBOL OF "SYS$LIBRARY:DIL.TLB".
COPY DIL$COBOL OF "SYS$LIBRARY:DIL.TLB".
* Dil status return
01 DIL-STATUS PIC S9(9) COMP.
* File and directory description fields
01 FILE-NAME PIC X(39) VALUE "DAP.TST".
01 USERID PIC X(39) VALUE SPACES.
01 PASSWD PIC X(39) VALUE SPACES.
01 ACCT PIC X(39) VALUE SPACES.
* Record description fields
01 FILE-NUMBER USAGE COMP PIC S9(9).
01 REC-FORMAT PIC S9(9) COMP.
01 REC-ATTRIBUTES PIC S9(9) COMP.
01 REC-UNIT-SIZE PIC S9(9) COMP VALUE 0.
01 REC-SIZE PIC S9(9) COMP VALUE 100.
01 DATA-RECORD PIC X(100).
01 DIL-ACCEPT PIC X.
01 DIL-DISPLAY PIC X(12).
PROCEDURE DIVISION.
BEGIN-CD32T1.
* Get record format
DISPLAY " Enter the value for the record format (RFM):".
DISPLAY " 0 = undefined,".
DISPLAY " 1 = fixed,".
DISPLAY " 2 = variable, ".
DISPLAY " 3 = VFC, ".
DISPLAY " 4 = stream".
ACCEPT DIL-ACCEPT.
MOVE DIL-ACCEPT TO REC-FORMAT.
* Get record attributes
DISPLAY " Enter a value for the record attributes (RAT):".
DISPLAY " 0 = unspecified,".
DISPLAY " 1 = implied <LF><CR> envelope,".
DISPLAY " 2 = print file format,".
DISPLAY " 3 = Fortran carriage control,".
DISPLAY " 4 = MACY11 format".
ACCEPT DIL-ACCEPT.
MOVE DIL-ACCEPT TO REC-ATTRIBUTES.
* Open file DAP.TST for output
CALL "DIT$ROPEN" USING FILE-NUMBER, FILE-NAME, USERID, PASSWD, ACCT,
DIT$K_MODE_WRITE, DIT$K_TYPE_ASCII, REC-FORMAT,
REC-ATTRIBUTES, REC-SIZE, REC-UNIT-SIZE
GIVING DIL-STATUS.
MOVE DIL-STATUS TO DIL-DISPLAY.
DISPLAY " ROPEN Status return: " DIL-DISPLAY.
IF DIL-STATUS IS NOT SUCCESS
DISPLAY "? ROPEN: unsuccessful status return "
STOP RUN.
* Accept a record and write it to the file
DISPLAY " Enter data for the record for the remote file: ".
ACCEPT DATA-RECORD.
CALL "DIT$RWRITE" USING FILE-NUMBER, REC-UNIT-SIZE,
REC-SIZE, DATA-RECORD
GIVING DIL-STATUS.
MOVE DIL-STATUS TO DIL-DISPLAY.
DISPLAY " RWRITE Status return: " DIL-DISPLAY.
IF DIL-STATUS IS NOT SUCCESS
DISPLAY "? RWRITE: unsuccessful status return. "
STOP RUN.
* Close the file
CALL "DIT$RCLOSE" USING FILE-NUMBER, DIT$K_OPT_NOTHING
GIVING DIL-STATUS.
MOVE DIL-STATUS TO DIL-DISPLAY.
DISPLAY " RCLOSE Status return: ", DIL-DISPLAY.
IF DIL-STATUS IS NOT SUCCESS
DISPLAY "? RCLOSE: unsuccessful status return."
STOP RUN.
* Open the file to read the record
CALL "DIT$ROPEN" USING FILE-NUMBER, FILE-NAME, USERID, PASSWD, ACCT,
DIT$K_MODE_READ, DIT$K_TYPE_ASCII, REC-FORMAT,
REC-ATTRIBUTES, REC-SIZE, REC-UNIT-SIZE
GIVING DIL-STATUS.
MOVE DIL-STATUS TO DIL-DISPLAY.
DISPLAY " ROPEN Status return: ", DIL-DISPLAY.
IF DIL-STATUS IS NOT SUCCESS
DISPLAY "? ROPEN: unsuccessful status return."
STOP RUN.
* Read the record
MOVE SPACES TO DATA-RECORD.
CALL "DIT$RREAD" USING FILE-NUMBER, REC-UNIT-SIZE,
REC-SIZE, DATA-RECORD
GIVING DIL-STATUS.
MOVE DIL-STATUS TO DIL-DISPLAY.
DISPLAY " RREAD returned ", DIL-DISPLAY.
IF DIL-STATUS IS NOT SUCCESS
DISPLAY "? RREAD: unsuccesful status return."
STOP RUN.
DISPLAY " The record was: ".
DISPLAY DATA-RECORD.
* Close the file
CALL "DIT$RCLOSE" USING FILE-NUMBER, DIT$K_OPT_NOTHING
GIVING DIL-STATUS.
MOVE DIL-STATUS TO DIL-DISPLAY.
DISPLAY " RCLOSE Status return: ", DIL-DISPLAY.
IF DIL-STATUS IS NOT SUCCESS
DISPLAY "? RCLOSE: unsuccessful status return."
STOP RUN.
DISPLAY " ".
DISPLAY " CD32T1 test successful. ".
DISPLAY " ".
STOP RUN.