Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations TouchToneTommy on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

How can I use my browser as a COBOL front-end

COBOL Weblers

How can I use my browser as a COBOL front-end

by  CliveC  Posted    (Edited  )
This FAQ explains how you may use your IE6 browser on the client-side to provide a GUI front-end interface to a COBOL PC program. To bypass browser security without updating your browser settings, an HTA extension instead of an HTM extension is used.

This example uses a simple application which prints a certificate to an HTM file.
1 - An entry field is presented in the browser.
2 - Enter a name
3 - The name will be written to a file named CERTIFY.TXT
4 - The COBOL program CERTIFY.EXE is called
5 - The program opens CERTIFY.TXT and reads the name and outputs OUTPUT.HTM

When the COBOL program has executed the browser will close and another browser window will open to display the certificate.

Using the browsers print facility the certificate can be printed.

Here is the COBOL code for CERTIFY.CBL
Code:
      ******************************************************************
       IDENTIFICATION DIVISION.
      ******************************************************************

       PROGRAM-ID.    CERTIFY.
       AUTHOR.        CLIVE CUMMINS.
       INSTALLATION.  http://tubularity.com
       DATE-WRITTEN.  DEC  7,2003.

      ******************************************************************
       ENVIRONMENT DIVISION.
      ******************************************************************

       INPUT-OUTPUT SECTION.

       SELECT INPUT-FILE ASSIGN TO INPUT-FILE-ID
              FILE STATUS  IS INPUT-RETURN-CODE
              ACCESS MODE  IS SEQUENTIAL
              ORGANIZATION IS LINE SEQUENTIAL.

       SELECT OUTPUT-FILE ASSIGN TO OUTPUT-FILE-ID
              FILE STATUS  IS OUTPUT-RETURN-CODE
              ACCESS MODE  IS SEQUENTIAL
              ORGANIZATION IS LINE SEQUENTIAL.

      ******************************************************************
       DATA DIVISION.
      ******************************************************************

       FILE SECTION.

       FD  INPUT-FILE.
       01  INPUT-RECORD      PIC X(72).

       FD  OUTPUT-FILE.
       01  OUTPUT-RECORD     PIC X(72).

       WORKING-STORAGE SECTION.

       01 FILE-DETAILS.
           02 INPUT-RETURN-CODE  PIC X(02).
           02 INPUT-FILE-ID      PIC X(12) VALUE "CERTIFY.TXT".
           02 OUTPUT-RETURN-CODE PIC X(02).
           02 OUTPUT-FILE-ID     PIC X(12) VALUE "OUTPUT.HTM".

       01 CERT-TBL.
       02 FILLER PIC X(36) VALUE "<html><head><title>COBOL Webler Cert".
       02 FILLER PIC X(36) VALUE "ification</title>                   ".
       02 FILLER PIC X(36) VALUE "<style type='text/css'>             ".
       02 FILLER PIC X(36) VALUE "                                    ".
       02 FILLER PIC X(36) VALUE "h2 {font-family: 'Lucida Calligraphy".
       02 FILLER PIC X(36) VALUE "','Viner Hand ITC','Comic Sans MS', ".
       02 FILLER PIC X(36) VALUE "'Cursive'}                          ".
       02 FILLER PIC X(36) VALUE "                                    ".
       02 FILLER PIC X(36) VALUE "</style></head><body><div align='cen".
       02 FILLER PIC X(36) VALUE "ter'><br /><br />                   ".
       02 FILLER PIC X(36) VALUE "<h1>This is to Certify that</h1><u><".
       02 FILLER PIC X(36) VALUE "h2>                                 ".
       02 C-NAME PIC X(72) VALUE "Your Name                           ".
       02 FILLER PIC X(36) VALUE "</h2></u><h3>has acheived the status".
       02 FILLER PIC X(36) VALUE " of Master COBOL Webler</h3>        ".
       02 FILLER PIC X(36) VALUE "</div></body></html>                ".
       02 FILLER PIC X(36) VALUE "                                    ".
       01 FILLER REDEFINES CERT-TBL.
       02 CERT-TBL-ENTRY PIC X(72) OCCURS 009 INDEXED BY CERT-TBL-IDX.

      ******************************************************************
       01  SYSTEM-COMMAND-LINE.
      ******************************************************************

           05  MY-BROWSER              PIC X(49)  VALUE
           '"C:\Program Files\Internet Explorer\iexplore.exe"'.
           05  FILLER                  PIC X(01)  VALUE SPACE.
           05  MY-HTML-FILE            PIC X(80)  VALUE
           "C:\CERTIFY\OUTPUT.HTM".
           05  FILLER                  PIC X(01)  VALUE LOW-VALUE.

      ******************************************************************
       PROCEDURE DIVISION.
      ******************************************************************

           OPEN INPUT INPUT-FILE.
           READ INPUT-FILE INTO C-NAME.
           CLOSE INPUT-FILE.

           OPEN OUTPUT OUTPUT-FILE.
           PERFORM
             VARYING CERT-TBL-IDX FROM 1 BY 1
               UNTIL CERT-TBL-IDX GREATER THAN 9
             MOVE CERT-TBL-ENTRY (CERT-TBL-IDX) TO OUTPUT-RECORD
             WRITE OUTPUT-RECORD
           END-PERFORM.
           CLOSE OUTPUT-FILE.

           CALL "SYSTEM" USING SYSTEM-COMMAND-LINE.
           GOBACK.

Here is the code for CERTIFY.HTA
Code:
<html><head>
<title>Master COBOL Webler Certification</title>

<!--
***************************************************
**** This javascript subroutine is called when   
**** the form's "Certify" button is clicked. It
**** calls two subroutines, writeToFile & Launch.
**** Launch is delayed 1 second to make sure that
**** the file has had time to be written and closed.
**** Finally the window is closed
***************************************************      
-->
<script type="text/javascript">
function process(data) {
  writeToFile(data);
  timer=setTimeout('launch()',1000)
  timer=setTimeout('self.close()',1000)  
}
</script>

<!--
***************************************************
**** writeToFile
**** This VBscript subroutine is called to write 
**** the contents of the input text to a file.     
**** In this case the file is name CERTIFY.TXT 
***************************************************   
-->
<script type="text/vbscript">
sub writeToFile(data) 
set oFS = createobject("scripting.filesystemobject")
set oFile = oFS.opentextfile("CERTIFY.TXT", 2, true)
oFile.writeline(data)
oFile.close()
set oFile = nothing
set oFS = nothing
end sub
</script>

<!--
***************************************************
**** launch  
**** This VBscript subroutine will call the COBOL    
**** program CERTIFY.EXE. 
***************************************************   
-->
<script type="text/vbscript">
sub launch()
Dim MyObj
Set MyObj=CreateObject("WScript.Shell")
MyObj.Run "CERTIFY.EXE"
end sub
</script>

</head>
<!--
***************************************************
***** This is the HTML for the Cerification form 
***************************************************
-->
<body style="background:yellow">
<h2>Master COBOL Webler Certification</h2>
ENTER Candidate's Name:<br />
<form name="formC">
<input name="candidate" type="text" size="40" maxsize="72" />
<br /><br />
<input type="button" value="Certify" 
 onclick="process(document.formC.candidate.value)" />
</form>
<script type="text/javascript">
document.formC.candidate.focus()
</script>
</body></html>
Register to rate this FAQ  : BAD 1 2 3 4 5 6 7 8 9 10 GOOD
Please Note: 1 is Bad, 10 is Good :-)

Part and Inventory Search

Back
Top