Member LISTCTRIFM in CGICBLDEV2 / QCBLLESRC

1.00 
 ********START OF PGM : LISTCTRIFM  ****************************************
2.00 
       *================================================================
3.00 
       *
4.00 
       *  After compiling this module, create the program as follow:
5.00 
       *
6.00 
       *  CRTPGM  PGM(CGICBLDEV2/LISTCTRIFM) MODULE(CGICBLDEV2/LISTCTRIFM)
7.00 
       *          BNDDIR(CGICBLDEV2/CGICBLDEV2)
8.00 
       *          ACTGRP(LISTCTRIFM) AUT(*USE)
9.00 
       *
10.00 
       *================================================================
11.00 
        PROCESS NOXREF APOST
12.00 
        ID    DIVISION.
13.00 
        PROGRAM-ID. LISTCTRIFM.
14.00 
        ENVIRONMENT DIVISION.
15.00 
        CONFIGURATION SECTION.
16.00 
        SPECIAL-NAMES.
17.00 
              copy CPYSPCNAME of CGICBLDEV2-QCBLLESRC.
18.00 
        INPUT-OUTPUT SECTION.
19.00 
        FILE-CONTROL.
20.00 
       *----------------------------------
21.00 
            SELECT ctrdvy
22.00 
                   ASSIGN       TO         DATABASE-ctrdvy
23.00 
                   ORGANIZATION IS         INDEXED
24.00 
                   ACCESS       IS         DYNAMIC
25.00 
                   RECORD KEY   IS         EXTERNALLY-DESCRIBED-KEY
26.00 
                   FILE STATUS  IS         STATUS-ctrdvy.
27.00 
       *----------------------------------
28.00 
        DATA DIVISION.
29.00 
        FILE SECTION.
30.00 
       *----------------------------------
31.00 
        FD  ctrdvy
32.00 
                                           LABEL RECORD IS STANDARD.
33.00 
        01  ctrdvy-RECFD.
34.00 
            COPY DDS-ALL-FORMAT   OF ctrdvy.
35.00 
       *=================================================================
36.00 
        WORKING-STORAGE SECTION.
37.00 
       *=================================================================
38.00 
       *       ----- Variables specific to this program ------
39.00 
       *
40.00 
        01         HTML-DATA.
41.00 
       * Variables to execute a command
42.00 
            05     rc                  PIC  S9(9) comp-4.
43.00 
            05     cmd                 PIC  X(2000).
44.00 
       * Variables to parse the input string
45.00 
            05     varnamein           PIC  X(50).
46.00 
            05     xyrname             PIC  X(1000).
47.00 
            05     request             PIC  X(1000).
48.00 
       * Variables to load external HTML via QgetHtmlIFSMult
49.00 
            05     IFSFiles            PIC  X(32767).
50.00 
            05     sectionDelimStr     PIC  X(20) VALUE '<as400>'.
51.00 
       * Variable for QWrtSection subprocedure
52.00 
            05     HtmlSects           PIC  X(1000).
53.00 
       * Variables for QUpdHtmlVar subprocedure
54.00 
            05     varnameout          PIC  X(30).
55.00 
            05     varvalout           PIC  X(1000).
56.00 
       * Miscellaneous variables
57.00 
        01         MISC-DATA.
58.00 
            05     LinesNbr            PIC  S9(05).
59.00 
            05     wkf                 PIC  X(01).
60.00 
            05     openSW              PIC  X(01).
61.00 
            05     edited-ctrday       PIC  ZZ9.
62.00 
       * Status field
63.00 
            05     status-ctrdvy       PIC  X(02).
64.00 
       *=================================================================
65.00 
       *                M A I N  -  L I N E
66.00 
       *=================================================================
67.00 
        PROCEDURE DIVISION.
68.00 
        A-start-pgm.
69.00 
            perform OpenFiles              thru z-OpenFiles.
70.00 
            perform GetCGIInput            thru z-GetCGIInput.
71.00 
            perform LoadHtml               thru z-LoadHtml.
72.00 
            perform SendHtml               thru z-SendHtml.
73.00 
       *----------------------------------
74.00 
        B-end-pgm.
75.00 
            exit program and continue run unit.
76.00 
       *=================================================================
77.00 
        GetCGIInput.
78.00 
       * Get input data from POST or GET
79.00 
            call 'QZHBGETINPUT'.
80.00 
       * Parse input string into program field 'xyrname':
81.00 
            move 'xyrname' to varnamein.
82.00 
            call 'QZHBGETVAR' using
83.00 
                                        by content varnamein
84.00 
                                        returning into xyrname.
85.00 
       * Parse input string into program field 'request', cvt to uppercase
86.00 
            move 'request' to varnamein.
87.00 
            call 'QZHBGETVARUPPER' using
88.00 
                              by content varnamein
89.00 
                              returning into request.
90.00 
       *----------------------------------
91.00 
        z-GetCGIInput.
92.00 
            EXIT.
93.00 
       *=================================================================
94.00 
        LoadHtml.
95.00 
       * Load html skeleton source member from IFS file
96.00 
            move '/cgicbldev2/html/part1.txt /cgicbldev2/html/part2.txt'
97.00 
                 to IFSFiles.
98.00 
            call 'QGETHTMLIFSMULT' using
99.00 
                                   IFSFiles
100.00 
                                   SectionDelimStr.
101.00 
       *----------------------------------
102.00 
        z-LoadHtml.
103.00 
            EXIT.
104.00 
       *=================================================================
105.00 
        SendHtml.
106.00 
       *Send section /$top
107.00 
            move 'top' to HtmlSects
108.00 
            call 'QWRTSECTION' using HtmlSects.
109.00 
       *Initial bootstrap
110.00 
            if request = ' '
111.00 
               perform Case1 thru z-Case1
112.00 
            else
113.00 
               perform Case2 thru z-Case2
114.00 
            end-if.
115.00 
       *Send HTML buffer
116.00 
            move '*fini' to HtmlSects
117.00 
            call 'QWRTSECTION' using HtmlSects.
118.00 
       *----------------------------------
119.00 
        z-SendHtml.
120.00 
            EXIT.
121.00 
       *=================================================================
122.00 
        Case1.
123.00 
               move 'case1' to HtmlSects
124.00 
               call 'QWRTSECTION' using HtmlSects.
125.00 
       *----------------------------------
126.00 
        z-Case1.
127.00 
            EXIT.
128.00 
       *=================================================================
129.00 
        Case2.
130.00 
       *Set output variable /%xyrname%/
131.00 
            move 'xyrname' to varnameout
132.00 
            move xyrname to varvalout
133.00 
            call 'QUPDHTMLVAR' using varnameout varvalout.
134.00 
       *Send section /$case2
135.00 
            move 'case2' to HtmlSects
136.00 
               call 'QWRTSECTION' using HtmlSects.
137.00 
       *Send countries table
138.00 
            perform WriteRows thru z-WriteRows
139.00 
       *Send section /$end
140.00 
            move 'end' to HtmlSects
141.00 
               call 'QWRTSECTION' using HtmlSects.
142.00 
       *----------------------------------
143.00 
        z-Case2.
144.00 
            EXIT.
145.00 
       *=================================================================
146.00 
        WriteRows.
147.00 
            compute LinesNbr = 0.
148.00 
            perform WriteRow thru z-WriteRow
149.00 
                    until status-ctrdvy not = '00'.                        60
150.00 
            if LinesNbr >= 1
151.00 
               move 'tabend' to HtmlSects
152.00 
            else
153.00 
               move 'none' to HtmlSects
154.00 
            end-if.
155.00 
            call 'QWRTSECTION' using HtmlSects.
156.00 
       *----------------------------------
157.00 
        z-WriteRows.
158.00 
            EXIT.
159.00 
       *=================================================================
160.00 
        WriteRow.
161.00 
            read ctrdvy next record
162.00 
            at end
163.00 
                  move wkf to wkf.
164.00 
            if status-ctrdvy = '00'
165.00 
               compute LinesNbr = LinesNbr + 1
166.00 
               if LinesNbr = 1
167.00 
                  move 'tabstr' to HtmlSects
168.00 
                  call 'QWRTSECTION' using HtmlSects
169.00 
               end-if
170.00 
               perform SetTabRow thru z-SetTabRow
171.00 
               move 'tabrow' to HtmlSects
172.00 
               call 'QWRTSECTION' using HtmlSects
173.00 
            end-if.
174.00 
       *----------------------------------
175.00 
        z-WriteRow.
176.00 
            EXIT.
177.00 
       *=================================================================
178.00 
        SetTabRow.
179.00 
       * Set HTML output variables
180.00 
       * for section "tabrow"
181.00 
       *==================================
182.00 
       * Set output variable /%country%/
183.00 
            move 'country' to varnameout
184.00 
            move ctrnam to varvalout
185.00 
            call 'QUPDHTMLVAR' using varnameout varvalout.
186.00 
       * Set variable /%delvDays%/
187.00 
       * editing numeric filed "ctrday" (Signed 3,0)
188.00 
            move 'delvdays' to varnameout
189.00 
            move ctrday to edited-ctrday
190.00 
            move edited-ctrday to varvalout
191.00 
            call 'QUPDHTMLVAR' using varnameout varvalout.
192.00 
       *----------------------------------
193.00 
        z-SetTabRow.
194.00 
            EXIT.
195.00 
       *=================================================================
196.00 
        OpenFiles.
197.00 
            if openSW = ' '
198.00 
               move 'ovrdbf ctrdvy cgicbldev2/ctrdvy secure(*yes)' to cmd
199.00 
               call 'QDOCMD' using cmd
200.00 
                             returning into rc
201.00 
               open input ctrdvy
202.00 
               move 'x' to openSW
203.00 
            else
204.00 
               move ' ' to ctrnam
205.00 
               start ctrdvy key is >= externally-described-key
206.00 
            end-if.
207.00 
       *----------------------------------
208.00 
        Z-OpenFiles.
209.00 
            EXIT.
210.00 
       *=================================================================
211.00 
        TearDown.
212.00 
            close ctrdvy
213.00 
            move 'dltovr ctrdvy' to cmd
214.00 
            call 'QDOCMD' using cmd
215.00 
                          returning into rc.
216.00 
       *----------------------------------
217.00 
        z-TearDown.
218.00 
            EXIT.
219.00 
 ********* END OF PGM : LISTCTRIFM ****************************************
0.075 sec.s