forked from cicsdev/cics-java-liberty-restappext
-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathADDPART.cbl
68 lines (66 loc) · 2.17 KB
/
ADDPART.cbl
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
PROCESS NODYNAM,RENT,APOST,CICS,TRUNC(OPT)
*****************************************************************
* Licensed Materials - Property of IBM
*
* SAMPLE
*
* Copyright IBM Corp. 2017 All Rights Reserved
*
* Government Users Restricted Rights - Use, duplication or
* disclosure restricted by GSA ADP Schedule Contract with
* IBM Corp.
*
*****************************************************************
*
* Simple program used to receive a record in the commarea and
* write it out to a VSAM file. This program is the non-Java
* part of the LinkCommareaResource example.
*
* To simplify the code, this program has minimal error-handling
* logic.
*
*****************************************************************
IDENTIFICATION DIVISION.
PROGRAM-ID. ADDPART.
DATE-WRITTEN. May 2017.
*
ENVIRONMENT DIVISION.
*
DATA DIVISION.
*
WORKING-STORAGE SECTION.
*
* STOCK-PART copybook
COPY STOKPART REPLACING STOCK-PART BY WS-STOCK-PART.
*
* Name of the CICS file to use
77 FILE-NAME PIC X(8) VALUE 'SMPLXMPL'.
*
LINKAGE SECTION.
*
01 DFHCOMMAREA PIC X(80).
*
PROCEDURE DIVISION USING DFHEIBLK DFHCOMMAREA.
*
MAIN-PROCESSING SECTION.
*
* Assume the commarea is well-formed and use as our record
MOVE DFHCOMMAREA TO WS-STOCK-PART.
*
* Write to the file using CICS file control services
EXEC CICS WRITE FILE(FILE-NAME)
FROM(WS-STOCK-PART)
RIDFLD(PART-ID of WS-STOCK-PART)
END-EXEC.
*
* Update the description to prove we can pass data back in
* a commarea to Java
MOVE '<ADDED>' TO DESCRIPTION OF WS-STOCK-PART(1:7).
*
* Copy the updated record back to the commarea
MOVE WS-STOCK-PART TO DFHCOMMAREA.
*
* Back to CICS
EXEC CICS RETURN END-EXEC.
*
GOBACK.