000100 ID DIVISION. 00010000 000200 PROGRAM-ID. TRPGM85. 00020000 000300*AUTHOR. Kenneth W. Caldwell. 00030000 000400*INSTALLATION. Train-Right. 00040000 000500*DATE-WRITTEN. January 29, 2011. 00050000 000600*DATE-COMPILED. 00060000 000700* 00070000 000800*SECURITY. This program is for students of Train-Right 00080000 000900* courses ONLY!. 00090000 001000* 00100000 001100*REMARKS. This is a TCP/IP Web based program. 00110000 001200* It displays the contents of the TRTABLE data program. 00120000 001300* It receives the http request via the commarea. 00130000 001400* It sends an http response via the commarea 00140000 001500* (An http response header is required). 00150000 001600* CICS will convert the EBCDIC to ASCII. 00160000 001700* The client is a Web Browser. 00170000 001800* 00180000 001900 DATA DIVISION. 00190000 002000 WORKING-STORAGE SECTION. 00200000 002100 77 crlfcrlf PIC X(4) VALUE X'0D250D25'. 00210000 002200 77 crlf REDEFINES crlfcrlf PIC X(2). 00220000 002300 00230000 002400 77 ws-length PIC S9(8) BINARY. 00240000 002500 00250000 002600 01 html-out. 00260000 002700 05 html-length PIC S9(8) BINARY. 00270000 002800 05 html-text PIC X(2000). 00280000 002900 00290000 003000 LINKAGE SECTION. 00300000 003100 01 dfhcommarea. 00310000 003200 05 http-request PIC X OCCURS 0 TO 32767 TIMES 00320000 003300 DEPENDING ON eibcalen. 00330000 003400 00340000 003500 COPY TBLREC. 00350000 003600 00360000 003700 PROCEDURE DIVISION. 00370000 003800 Main. 00380000 003900* No http request means not a Web client. 00390000 004000 IF eibcalen = ZERO 00400000 004100 THEN MOVE 'Client is not an HTTP Web Browser.' TO html-text 00410000 004200 EXEC CICS SEND FROM(html-text) LENGTH(34) ERASE END-EXEC00420000 004300 EXEC CICS RETURN END-EXEC 00430000 004400 END-IF. 00440000 004500 00450000 004600 Receive-Trans-Input. 00460000 004700 EXEC CICS LOAD PROGRAM('TRTABLE') 00470000 004800 SET(ADDRESS OF tr-table) 00480000 004900 FLENGTH(ws-length) 00490000 005000 END-EXEC. 00500000 005100 00510000 005200 DIVIDE ws-length BY LENGTH OF tr-table-entries 00520000 005300 GIVING ws-length 00530000 005400 END-DIVIDE. 00540000 005500 00550000 005600 Process-Data. 00560000 005700* Build http response and html output. 00570000 005800 MOVE +1 TO html-length. 00580000 005900 STRING 'HTTP/1.0 200 OK' crlf 00590000 006000 'Content-Type: text/html' crlfcrlf 00600000 006100 '' 00610000 006200 'Train-Right Advanced CICS Programming Concepts' 00620000 006300 '' 00630000 006400 '' 00640000 006500 '' 00650000 006600 '

Train-Right CICS WEB COBOL - TRPGM85

' 00660000 006700 '

The contents of program TRTABLE is:

' 00670000 006800 '' crlf 00680000 006900 DELIMITED BY SIZE 00690000 007000 INTO html-text 00700000 007100 WITH POINTER html-length 00710000 007200 END-STRING. 00720000 007300 00730000 007400 PERFORM VARYING tr-index FROM +1 BY +1 00740000 007500 UNTIL tr-index > ws-length 00750000 007600 STRING '' crlf 00800000 008100 DELIMITED BY SIZE 00810000 008200 INTO html-text 00820000 008300 WITH POINTER html-length 00830000 008400 END-STRING 00840000 008500 END-PERFORM. 00850000 008600 00860000 008700 STRING '
' 00760000 007700 tr-table-num(tr-index) 00770000 007800 '' 00780000 007900 tr-table-data(tr-index) 00790000 008000 '
' crlf 00870000 008800 ' ' 00880000 008900 DELIMITED BY SIZE 00890000 009000 INTO html-text 00900000 009100 WITH POINTER html-length 00910000 009200 END-STRING. 00920000 009300 00930000 009400* String statement points to next byte. 00940000 009500 SUBTRACT +1 FROM html-length. 00950000 009600* Html output length includes the length field. 00960000 009700 ADD +4 TO html-length. 00970000 009800 00980000 009900 Send-Result. 00990000 010000* CICS converts EBCDIC to ASCII. 01000000 010100 MOVE html-out(1:html-length) TO dfhcommarea. 01010000 010200 01020000 010300 Process-Exit. 01030000 010400 EXEC CICS RETURN END-EXEC. 01040000 010500* Dummy GOBACK. 01050000 010600 GOBACK. 01060000