 |
» |
|
|
|
The following programs, in COBOL and Pascal, illustrate single
and multiple file transfers via the DSCOPY
intrinsic. They also call the DSCOPYMSG
intrinsic to print an error message if necessary. The multiple-file-transfer examples use transfer specifications
that are read from a file with the formal designator DSCOPYI. In the COBOL version of the multiple-file transfer, we assume
that this file is the default $STDIN,
namely the user's terminal. A second and alternative way
of doing the COBOL multiple-file transfer would be to create an
actual unnumbered file ("copyfile") that contains
DSCOPY commands (for instance, SFILEA TO TFILEA).
You would then have to create a file equation that equates DSCOPYI
with the copyfile you have created. COBOL: Single Transfer |  |
In this application, the opt parameter
is set to zero (0). All transfers
will be attempted. Primary output is disabled. The command file
spec for multiple transfers cannot be used. The spec
parameter contains the full text of the transfer specification,
including all parameters and options, and is terminated by an ASCII
null character. 001000$CONTROL USLINIT001100 IDENTIFICATION DIVISION.001200 PROGRAM-ID. SINGLETRANSFER.001300 REMARKS. THIS PROGRAM TRANSFERS A FILE TO A REMOTE NODE;001400 IT CALLS THE DSCOPY AND DSCOPYMSG INTRINSICS.001500 ENVIRONMENT DIVISION.001600 CONFIGURATION SECTION.001700 SOURCE-COMPUTER. HP3000001800 OBJECT-COMPUTER. HP3000001900 DATA DIVISION.002000 WORKING-STORAGE SECTION.002100 01 OPT PIC S9(4) COMP VALUE 0.002200 01 SPEC.002300 02 ASCIIPART PIC X(40) VALUE002400 "NFTTEST TO NFTTARG:SOMENODE[NSUSER.NSACCT]".002500 02 TERMINATOR PIC S9(4) COMP VALUE 0.002600 01 RESULT.002700 02 RESULTS PIC S9(4) COMP OCCURS 2 TIMES.002800 01 FNUM PIC S9(4) COMP VALUE 0.002900 01 R PIC S9(4) COMP VALUE 0.003000 PROCEDURE DIVISION.003100 BEGIN.003200 CALL "DSCOPY" USING OPT, SPEC, RESULT.003300 IF RESULTS(1) > 0 CALL "DSCOPYMSG" USING RESULT, FNUM, R.}003400 STOP RUN. |
COBOL: Multiple Transfer |  |
In this application, the opt parameter
is set to one (1). DSCOPY terminates
after first failure. Primary output is disabled. The command file
spec for multiple transfers cannot be used. The spec
parameter contains a null character (numeric zero) indicating that
transfer requests are to be read from the DSCOPYI
file. The "COPYFILE"
must already exist. You must issue the file equation "FILE DSCOPYI=COPYFILE"
prior to execution of the program. 001000$CONTROL USLINIT001100 IDENTIFICATION DIVISION.001200 PROGRAM-ID. MULTTRANSFER.001300 REMARKS. THIS PROGRAM ACCEPTS INTERACTIVE TRANSFER REQUESTS;001400 IT CALLS THE DSCOPY AND DSCOPYMSG INTRINSICS.001500 ENVIRONMENT DIVISION.001600 CONFIGURATION SECTION.001700 SOURCE-COMPUTER. HP3000001800 OBJECT-COMPUTER. HP3000001900 DATA DIVISION.002000 WORKING-STORAGE SECTION.002100 01 OPT PIC S9(4) COMP VALUE 1.002200 01 SPEC.002300 02 TERMINATOR PIC S9(4) COMP VALUE 0.002400 01 RESULT.002500 02 RESULTS PIC S9(4) COMP OCCURS 2 TIMES.002600 01 FNUM PIC S9(4) COMP VALUE 0.002700 01 R PIC S9(4) COMP VALUE 0.002800 PROCEDURE DIVISION.002900 BEGIN.003000 CALL "DSCOPY" USING OPT, SPEC, RESULT.003100 IF RESULTS(1) > 0 CALL "DSCOPYMSG" USING RESULT, FNUM, R.003200 STOP RUN. |
Pascal: Single Transfer |  |
In this application, the opt parameter
is set to four (4). All transfers will be attempted. Primary output
is enabled. The command file spec for multiple transfers cannot
be used. The spec parameter contains
the full text of the transfer specification, including all parameters
and options, and is terminated by an ASCII null character. $standard_level 'hp3000', uslinit$program pcopy (input,output);type small_int = -32768..32767;const null = chr(0); {ASCII null char}@COMPUTERTXT = var opt : small_int; fnum : small_int; r : small_int; spec : string [80]; result : array [1..2] of small_int;procedure DSCOPY; intrinsic;procedure DSCOPYMSG; intrinsic;begin {program pcopy}opt := 4; All transfers attempted, output enabled, command file disabled}fnum := 0;{copy local file NFTTEST to file NFTTARG on node SOMENODE}spec := 'NFTTEST TO NFTTARG:SOMENODE[NSUSER.NSACCT]' + null; {string terminated by ASCII null char}DSCOPY (opt, spec, result);if result[1] > 0 then DSCOPYMSG (result, fnum, r)end. |
Pascal: Multiple Transfer |  |
In this application, the opt parameter
is set to two (2). All transfers will be attempted. Primary output
is disabled. The command file spec for multiple transfers is enabled.
The spec parameter contains the "COPYFILE"
name terminated by an ASCII null character. The "COPYFILE"
must exist prior to execution of the program. $standard_level 'hp3000', uslinit$program pcopy2 (copyfile);type small_int = -32768..32767;const null = chr(0); {ASCII null char}var copyfile : text; opt : small_int; fnum : small_int; r : small_int; spec : string [11]; result : array [1..2] of small_int;procedure DSCOPY; intrinsic;@COMPUTERTXT = procedure DSCOPYMSG; intrinsic;begin {program pcopy2}opt := 2; {output disabled; attempt all transfers; command file enabled}fnum := 0;spec := '(copyfile)' + null; rewrite (copyfile);writeln (copyfile, '+ ; :SOMENODE [NSUSER.NSACCT]'); {global spec}writeln (copyfile, 'SOURCE1 TO TARGET1');writeln (copyfile, 'SOURCE2 TO TARGET2');writeln (copyfile, 'SOURCE3 TO TARGET3');close (copyfile);DSCOPY (opt, spec, result);if result[1] >> 0 then DSCOPYMSG (result, fnum, r)end. |
|