ContentsIndexPreviousNext

3.1 The ESQL Translation Process

The AcuSQL pre-compiler identifies and translates ESQL statements into COBOL statements. It begins its work in the program's DATA DIVISION. The pre-compiler identifies ESQL statements by searching for the keywords "EXEC SQL" and "END-EXEC" in the source code. When it finds these markers it encapsulates them with comments and line numbers and then parses and generates COBOL code, including CALLs to the AcuSQL library.

For example, if your code specifies an include file such as:

       EXEC SQL INCLUDE SQLCA END-EXEC.

This line is translated into:

    *(( PREPROC ACUSQL LINE BEGIN 12 ))
       01  SQLCA IS EXTERNAL.
           05  SQLCAID                PIC X(8).
           05  SQLCABC         COMP-5 PIC S9(9).
           05  SQLCODE         COMP-5 PIC S9(9).
           05  SQLERRM.
               10  SQLERRML    COMP-5 PIC S9(4).
               10  SQLERRMC           PIC X(70).
           05  SQLERRP                PIC X(8).
           05  SQLERRD OCCURS 6 TIMES COMP-5 PIC S9(9).
           05  SQLWARN.
               10  SQLWARN0           PIC X.
               10  SQLWARN1           PIC X.
               10  SQLWARN2           PIC X.
               10  SQLWARN3           PIC X.
               10  SQLWARN4           PIC X.
               10  SQLWARN5           PIC X.
               10  SQLWARN6           PIC X.
               10  SQLWARN7           PIC X.
               10  SQLWARN8           PIC X.
               10  SQLWARN9           PIC X.
               10  SQLWARNA           PIC X.
           05  SQLSTATE               PIC X(5).
           05  SQLERRM-PREFIX.
               10  SQLERRPL    COMP-5 PIC S9(4).
               10  SQLERRPC           PIC X(70)
      *EXEC SQL INCLUDE SQLCA END-EXEC.
      *(( PREPROC ACUSQL LINE END 12 ))
           .

The following ESQL statement:

      EXEC SQL
          SELECT MIN(C_NUMBER)
              INTO :MIN-C-NUMBER
              FROM CUSTOMER
      END-EXEC.

is translated into:

*(( PREPROC ACUSQL LINE BEGIN 41 ))
           PERFORM CALL "SQL$START" END-CALL CALL "SQL$PREPARE" USING 'S
      -    'QLISTM' "SELECT MIN(C_NUMBER) FROM CUSTOMER " END-CALL IF SQ
      -    LCODE OF SQLCA < 0 THEN GO TO Error-Exit END-IF CALL "SQL$BIN
      -    "DCOLUMN" USING 'SQLISTM' 1 MIN-C-NUMBER   END-CALL IF SQLCOD
      -    E OF SQLCA < 0 THEN GO TO Error-Exit END-IF CALL "SQL$CURSOR"
            USING 'SQLICUR' 'SQLISTM' IF SQLCODE OF SQLCA < 0 THEN GO TO
            Error-Exit END-IF CALL "SQL$OPEN" USING 'SQLICUR' IF SQLCODE
            OF SQLCA < 0 THEN GO TO Error-Exit END-IF CALL "SQL$FETCH" U
      -    SING 1 0 'SQLICUR' IF SQLCODE OF SQLCA < 0 THEN GO TO Error-E
      -    xit END-IF CALL "SQL$CLOSE" USING 'SQLICUR' IF SQLCODE OF SQL
      -    CA < 0 THEN GO TO Error-Exit END-IF CALL "SQL$UNPREPARE" USIN
      -    G 'SQLISTM'  END-CALL END-PERFORM
      *    EXEC SQL
      *        SELECT MIN(C_NUMBER)
      *            INTO :MIN-C-NUMBER
      *            FROM CUSTOMER
      *    END-EXEC.
      *(( PREPROC ACUSQL LINE END 45 ))
           .

The line numbers that appear in the comment lines specify the original line numbers in the input file.


Note: The pre-compiler generates a standard 72-character line without regard for the end of statements or other formatting considerations.

Also Note: The precise results of these translations may vary depending on your version of the pre-compiler.
As AcuSQL works through your ESQL source, it creates a temporary COBOL source file, also known as the "intermediate file." This file is later compiled by ACUCOBOL-GT to produce an executable object file. You can save, and subsequently view the temporary file, by specifying the "-Po" option when invoking AcuSQL (see Section 3.2.2 Invoking the Pre-compiler From the ACUCOBOL-GT Command Line).

Into the temporary file, AcuSQL inserts directives that instruct the compiler to reset certain internal state variables. These directives, which begin with the words "PREPROC ACUSQL," are listed below.

Pre-compiler Directive
Function
PREPROC ACUSQL LINE BEGIN
Inserted whenever AcuSQL finds "EXEC SQL". Informs the compiler that a pre-compiler automatically generated future lines. Important for cross-listings and debugging.
PREPROC ACUSQL LINE END
Inserted whenever AcuSQL finds "END-EXEC". Informs the compiler to start counting lines itself. Important for cross-listings and debugging.
PREPROC ACUSQL FILE
Informs the compiler which file should be considered the source file for future lines.
PREPROC ACUSQL INCLUDE BEGIN
Informs the compiler that it should detect ANSI vs. terminal format, and push the old format onto a stack.
PREPROC ACUSQL INCLUDE END
Informs the compiler that it should pop its ANSI vs. terminal format stack.