Top
NetCOBOL V11.0 CGI Subroutines User's Guide
FUJITSU Software

2.2.1 COBOL Programs Using CGI Subroutines

Create one or more COBOL programs that comprise the Web application.

These COBOL programs can use all of the standard COBOL functions other than the screen input-output functions.

For conditions regarding COBOL program creation, see "Conditions for CGI application creation using COBOL" in Chapter 2.

Sample Program

The sample program shown below comes with NetCOBOL and is contained in the CGISMP01 subdirectory under the SAMPLES folder. It is a program that contains a simple Web application. NetCOBOL CGI application programs can call other COBOL programs as well, although this simple sample does not require such. The following figure shows the source code for the sample program named SAMPLE01, which is part of the CGISMP01 project:

Example

*-----------------------------------------------------------------------*
*  All Rights Reserved, Copyright(C) FUJITSU LIMITED 1997-2002          *
*                                                                       *
* - Module Name    SAMPLE01                                             *
* - Outline        CGI Sample Program showing data input and output     *
*-----------------------------------------------------------------------*
 IDENTIFICATION   DIVISION.
 PROGRAM-ID       SAMPLE01.
 ENVIRONMENT      DIVISION.
 CONFIGURATION    SECTION.
 INPUT-OUTPUT     SECTION.
 DATA             DIVISION.
 WORKING-STORAGE  SECTION.
   COPY  COBW3.
*
 01  WORK-CHARA-LENGTH              PIC S9(4) COMP-5 .
 01  WORK-CHARA                     PIC X(50) VALUE SPACE .
 01  WORK-COMMA                     PIC X(2)  VALUE ", " .
*
 PROCEDURE        DIVISION.
*
 SAMPLE01-START.
*
*  Initialize CGI work environment
     CALL  "COBW3_INIT"      USING  COBW3 .
*
*  Obtain the text entered by the user 
     MOVE  "ENTRY1"            TO  COBW3-SEARCH-DATA .
     CALL  "COBW3_GET_VALUE"      USING  COBW3 .

*  Set the GET-TEXT variable in the prototype HTML to the data entered
     MOVE  "GET-TEXT"          TO     COBW3-CNV-NAME .
     MOVE  COBW3-GET-DATA      TO     COBW3-CNV-VALUE .
     CALL  "COBW3_SET_CNV"   USING  COBW3 .

*  Obtain the setting of the radio button
     MOVE  "RADIO1"            TO     COBW3-SEARCH-DATA .
     CALL  "COBW3_GET_VALUE"      USING  COBW3 .

*  Set the GET-RADIO variable to the value of the selected button
     MOVE  "GET-RADIO"         TO     COBW3-CNV-NAME .
     MOVE  COBW3-GET-DATA      TO     COBW3-CNV-VALUE .
     CALL  "COBW3_SET_CNV"   USING  COBW3 .

*  Obtain the setting of the check boxes
     MOVE  "CHECK1"            TO     COBW3-SEARCH-DATA .
     MOVE  1                   TO     WORK-CHARA-LENGTH .

     PERFORM WITH TEST AFTER
             VARYING COBW3-NUMBER FROM 1 BY 1
               UNTIL COBW3-NUMBER > 4

         CALL "COBW3_GET_VALUE" USING COBW3
         IF  COBW3-SEARCH-FLAG-EXIST   THEN
             IF  COBW3-NUMBER  >  1    THEN
                 MOVE  WORK-COMMA    TO  WORK-CHARA(WORK-CHARA-LENGTH:2)
                 ADD   2             TO  WORK-CHARA-LENGTH
             END-IF
             MOVE  COBW3-GET-DATA(1:COBW3-GET-LENGTH)
                    TO  WORK-CHARA(WORK-CHARA-LENGTH:COBW3-GET-LENGTH)
             ADD   COBW3-GET-LENGTH  TO  WORK-CHARA-LENGTH
         END-IF

     END-PERFORM .

*  Output "?" if nothing selected
     IF  WORK-CHARA-LENGTH  =  1  THEN
       MOVE   "?"                 TO     WORK-CHARA
     END-IF .

*  Set the GET-CHECK variable to the list of check box values
     MOVE  "GET-CHECK"         TO     COBW3-CNV-NAME .
     MOVE  WORK-CHARA          TO     COBW3-CNV-VALUE .
     CALL  "COBW3_SET_CNV"   USING  COBW3 .

*  Setup the prototype HTML file name
     MOVE  "sample01_1.htm"     TO  COBW3-HTML-FILENAME .



*  Send the completed HTML to the user
     CALL  "COBW3_PUT_HTML"   USING  COBW3 .

*  Send a final message to the user
     MOVE  "<CENTER>Thank you for cooperation. </CENTER></BODY></HTML>"
                       TO     COBW3-PUT-STRING.
     MOVE  58          TO     COBW3-PUT-STRING-LENGTH.
     CALL  "COBW3_PUT_TEXT"   USING  COBW3 .

*  Release the resources obtained by NetCOBOL CGI 
     CALL  "COBW3_FREE"       USING  COBW3 .
*
 SAMPLE01-END.
*
     EXIT PROGRAM.

For the flow of the processing of the sample program, see "Appendix C. Conceptual Diagram of Web Application Creation".

The following explains the CGI specific program code added to the SAMPLE01 COBOL:

IDENTIFICATION DIVISION

None

ENVIRONMENT DIVISION

None

DATA DIVISION

Using a standard COPY statement, the copy library that is to be used as the interface to the CGI subroutines must be added into the WORKING-STORAGE SECTION.

     WORKING-STORAGE SECTION.
             COPY COBW3.

This copy library (COBW3.cbl) is already installed in the folder in which NetCOBOL was installed.

PROCEDURE DIVISION

To initialize the environment for the CGI subroutines and to acquire Web parameters, COBW3_INIT must be called first. To terminate the processing of the CGI subroutines and release acquired resources, the last step of the CGI COBOL application should always be to call COBW3_FREE. Other CGI subroutines may be executed using the standard CALL statement when necessary. The Specific CGI subroutines used in the sample application (in the order in which they appear) include:

COBW3_INIT

initializes the CGI subroutines environment

COBW3_GET_VALUE

returns the value entered/selected by the user in the input HTML form for the input item (control) whose name has been placed in COBW3-SEARCH-DATA (a field contained in the COBW3.cbl copy library file)

COBW3_SET_CNV

sets the value of an HTML variable in the prototype HTML to be output as a result

COBW3_PUT_HTML

sends the response HTML Web page back to the client

COBW3_PUT_TEXT

sends additional HTML back to the client

COBW3_FREE

Releasing of resources that were acquired by CGI subroutines

See Chapter 3, "Use of CGI Subroutines," for additional details of Web parameter reception and referencing, and processing result output.