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 Mike Lewis on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

"Literal" line to line continuation 3

Status
Not open for further replies.

SiouxCityElvis

Programmer
Jun 6, 2003
228
0
0
US
Hello everyone,

I am using RMCOBOL-85 on Linux.

The following I have on one line but it goes past column 72 and thus I get an error
1152 "SELECT JunkId, JunkName, JunkDate, Descripti

***** 1) 0098: E Nonnumeric literal must end with quotation mark. (scan suppr

Code:
 "SELECT JunkId, JunkName, JunkDate, Description FROM Junk".

I know that I'm going to have long SQL statements like this and longer ones so is there any way I can append two stings together or continue a string from line to line?

I tried something like:

Code:
"SELECT JunkId, JunkName, "
+ "JunkDate, Description "
+ "FROM Junk".
 
I've not used this particular version of Cobol but the usual way is to code up to column 72, then on the next line, place a hyphen '-' in column 7. You then just code on from column 11.

Hope this helps

Marc
 
I hate continuation lines.

If doing the SQL on Working Storage then just use a group of PIC X(50) for that.

If doing it on Procedure then use "string " or "&" (concatenation)

I think you have a recent versio nof RM/COBOL so you can do
move "SELECT JunkId, JunkName, "
& "JunkDate, Description "
& "FROM Junk"
to SQL-STM.


Regards

Frederico Fonseca
SysSoft Integrated Ltd
 
Like Frederico says...star for him!
 
Beware of using "concatenation" of literals - for one reason. If you ever use COPY REPLACING or the REPLACE statement

"A" & "B"

does *not* match "AB" (as the former is 3 separate text words - 2 literals and the concatenation operator).

The ISO 2002 Standard provides concatenation of literals (with the restriction described above) but there is *ALSO* a *much* (IMHO) improved way to continue quoted literals (in either fixed or free reference format).

You may now code:

"A"-
"B"

to mean "AB"

with no regard to Column 72 (R-Margin) or column 7 or counting trailing spaces.

I don't think that RM supports this yet (or Tom would have said so), but it is one of the REALLY nice enhancements from the 2002 Standard that I hope many implmementors pick up soon.

Bill Klein
 
Okay.

This will work as long as I am not using the WHERE clause.

I'm confused as to how go and populate the "?" values after my PREPARE stmt.

Example from InstantSQL...
Code:
SQL PREPARE QUERY Statement Example:

 

       01 ws-SelectQueryHandle        USAGE ISqlHandle.
       01 ws-UpdateQueryHandle        USAGE ISqlHandle.

           MOVE "select LastName from Employee where EmpID = ?"
               TO sql-QrySQL.
           PERFORM ISQL-PREPARE-QUERY.

           MOVE sql-QueryHandle TO ws-SelectQueryHandle.
           
           MOVE "update Employee set FirstName = ? where EmpId = ?"
               TO sql-QrySQL.
           PERFORM ISQL-PREPARE-QUERY.

           MOVE sql-QueryHandle TO ws-UpdateQueryHandle.

        ISQL-PREPARE-QUERY.
           IF sql-ConnectionHandle = ZERO
             PERFORM ISQL-CONNECT-DATASOURCE
           END-IF.
           SQL PREPARE QUERY
               sql-QueryHandle,
               sql-ConnectionHandle,
               sql-QrySQL.

Are the "?" marks above just something the site is saying "these are not actually put here, you should put your values here", or is it to be taken as character to character and I then go back and somehow plug in values where the "?" are?

I haven't found anywhere in the examples how to populate those ? fields with actual values I want to query with.

Thanks.
-David
 
Those are parameter markers, to which you must bind actual COBOL data items. This is the standard SQL means to do a parameterized query.

Have a look here. You must bind a data item for each parameter marker (?) in the prepared query after you have executed the PREPARE. Then, each time you use the prepared query, the current value(s) of the bound COBOL data item(s) will be substituted for the parameter marker(s). This is somewhat analogous to the way a subprogram, which describes formal parameters (in the LINKAGE SECTION) binds at runtime to the actual parameters (provided on the CALL statement). So, for your first query you would need one SQL BIND PARAMETER (to supply the EmpID value), and your second query would require two SQL BIND PARAMETER (to supply the FirstName and EmpID values). Note that parameter markers are numbered from left to right, starting with one (l).

Tom Morrison
 
With regard to your continuation line problem, consider the SQL CONSTRUCT QUERY statement to assemble your query string from piece parts. This would obviate the need for continuation and concatenation.

Tom Morrison
 
The documentation has a flow chart which might be useful in understanding how all this query stuff works. You may find it here.

Tom Morrison
 
I don't know RM/COBOL.
I am familiar with COBOL II and DB2.

COBOL II (a COBOL-85 compliant) compiler does (did?) not have a 'built-in' SQL translator.

In order to include SQL a precompiler was necessary.
This precompiler generated the necessary COBOL code.

With regard to the SQL statements being translated it had to remain within the COBOL B-region area.
However no continuation character was necessary whatsoever!
I have coded some pretty long SQL statements (close to a page length!) without any 'continuation' problems as mentioned here...again...I am not familiar with RM/COBOL at all, this is a COBOL II / DB2 desription!

Within the COBOL II environment an SQL statement looked more or less like this:
Code:
EXEC SQL.

SELECT field-A,
       field-B,
       field-C,
        ...
       field-Z,
 INTO  ...respective COBOL working-storage fields...

 FROM tablelist 

[WHERE criteria ]

[ORDER BY sortfieldlist]

[GROUP BY groupfieldlist]

[HAVING groupcriteria]

END-EXEC.
The sql statement between EXEC SQL and END EXEC are the begin and end marker for the DB2 precompiler.
The SQL statement between these begin and end marker is free format but must be, if I remember correctly, in the COBOL B-area.
No continuation character is needed or required when the long SQL statement is continued on the next line.

The DB2 precompiler did have at least one restriction!
That is; no SQL statement could be coded in a contained (=nested) program.

Note: I know that the SQL precompiler begin and end marker may have other 'names' in other environments.
E.g. 'END EXEC' may be in other languages one of the following:
'END-EXEC', 'ENDEXEC', or nothing - that is, the first non-SQL word or field marks the end of the SQL statement.

Assuming RM/COBOL works similar to COBOL II then the following remark may be true:

Your SQL statement is restricted by the rules of the SQL precompiler. In turn, your SQL precompiler is vendor dependent. Concluded, the syntax of your SQL statement (including any possible DECLARE statements) is dictated by the vendor and should be described in the corresponding vendor database manual.


Regards, Wim Ahlers.
 
Oops...

Looks that I misunderstood the problem!

After rereading it looks that you are just trying to move a constant into a variable. And the contents happens to be an SQL statement.

If this is the case then this has nothing to do with SQL whatsover but just with the normal COBOL continuation rules.
These rules are standard and should be known. For a description see:

Warning! There is a maximum to the literal you can use. Check your compiler (I forgot the limit but I believe for most compilers the maximum size is less (or equal) to 256).

When your SELECT statement is larger then 256 characters then you can split your select statement (as suggested earlier) to concatenated working-storage fields. Like:
(example)
Code:
01  mySELECTstatement.
  05  part-01  PIC  X(40).
  05  part-02  PIC  X(40).
  05  part-03  PIC  X(40).
  05    ...
  05  part-xx  PIC  X(40).
   
   
    MOVE 'SELECT blah, blah, blah' TO part-01
    MOVE 'FROM  xxxxxxxxxxxxxxxxx' TO part-02
    MOVE 'WHERE xxx and so on xxx' TO part-03
                     ....
    MOVE 'HAVING xxxxxxxxxxxxxxxx' TO part-kk
In this case you - the programmer - are responsible for the correct contents (e.g. any literal longer than 40 characters is truncated. This trunction is probably not intended and unwanted!).


Regards, Wim Ahlers.
 
Okay,

Thanks all.

Tom,
Looks like I've got it working a couple of different ways.
There is a flow chart on the site showing how SQL CONSTRUCT QUERY precedes SQL PREPARE QUERY, and examples of each, I just don't see an example of how PREPARE would follow CONSTRUCT.

CONSTRUCT code...

Code:
SQL CONSTRUCT QUERY
     sql-QrySQL,
     sql-DirSetDS  sql-ConnectionHandle,  *> set connection
     "SELECT * FROM ",
         sql-DirQtID  sql-TableName,   *> quoted table name
         " WHERE HireDate = ",
          sql-DirDate  MyDateField.     *> SQL date literal

So, I'm at a guessing game on how SQL PREPARE QUERY would follow the above example.
Code:
How does that work?
Also, I was able to execute a prepare and run a query using parameters - but I didn't use BIND, I simply put my query code into WS vars and strung them together into 1 WS var and used it in my PREPARE stmt.  This is how I accomplished this, and if for some reason anyone thinks that it is an inefficient way to do queries, please let me know.  If I don't have to use BIND stmts, then that's great.

[code]
WORKING STORAGE.
.....
01 WS-JUNK-DATA.
   05 WS-ID                 PIC 9(11).  *> JunkId
   05 WS-NAME               PIC X(100). *> JunkName
   05 WS-DATE               PIC X(8).   *> JunkDate
   05 WS-DESCR              PIC X(100). *> JunkDescription

01 WS-JUNK-TABLE  PIC X(4) VALUE "Junk".
01 WS-JUNK-FIELDS PIC X(40)
       VALUE " JunkId, JunkName, JunkDate, Description".
01 WS-JUNK-WHERE  PIC X(16)
       VALUE " WHERE JunkId = ".
01 WS-JUNKPK      PIC 9(11) VALUE 0.

01 WS-MYSQL-STATEMENT       PIC X(200) VALUE SPACES.

.....
PROCEDURE DIVISION.
......

CONNECT blah blah blah..
this is to find rec(s) with PK of value 1....

MOVE 1 TO WS-JUNKPK.
STRING "SELECT " DELIMITED BY SIZE
        WS-JUNK-FIELDS DELIMITED BY SIZE
        " FROM " DELIMITED BY SIZE
        WS-JUNK-TABLE DELIMITED BY SIZE
        WS-JUNK-WHERE DELIMITED BY SIZE
        WS-JUNKPK DELIMITED BY SIZE
       INTO WS-MYSQL-STATEMENT
END-STRING.
DISPLAY "QUERY STMT: " WS-MYSQL-STATEMENT.

SQL PREPARE QUERY sql-QueryHandle
           sql-ConnectionHandle
           WS-MYSQL-STATEMENT.

SQL START QUERY sql-QueryHandle
PERFORM WITH TEST AFTER UNTIL NOT sql-OK
         SQL FETCH ROW sql-QueryHandle
         IF sql-OK
            SQL GET DATA sql-QueryHandle
              "JunkId" WS-ID           OMITTED
              "JunkName" WS-NAME       OMITTED
              "JunkDate" WS-DATE       OMITTED
              "Description" WS-DESCR   OMITTED
            DISPLAY "JunkId: " WS-ID
            DISPLAY "JunkName: " WS-NAME
            DISPLAY "JunkDate: " WS-DATE
            DISPLAY "Description: " WS-DESCR
            DISPLAY "*************************"
         ELSE IF sql-EndOfData
            DISPLAY "<End of data.>"
         ELSE
            DISPLAY "<Error fetching row.>"
            STOP RUN
         END-IF END-IF
END-PERFORM.

Let me know if this is an insane approach. I'm new to this, so go ahead, slam my code all you want if need be.

Thanks.

-David

 
David,

The concept of PREPAREing a query is that you can 'compile' a query once and use it many, many times. The result of a PREPARE is normally referred to as a query plan and is analogous to the object file produced by a compiler. In most SQL engines, the compilation of an SQL statement can have enough overhead that it is worthwhile, if you have a situation where you can reuse a query (via parameterization) rather than recompile it, to do the PREPARE and then the BINDs. Parameter substitution is usually quite a bit faster than recompiling the SQL statement.

If you are only going to make only casual use of a statement during a COBOL run unit, then your method will be fine. Use it once and throw it away...

If you plan to execute the statement in a loop that will have, say, 10000 iterations, you would be better served using a parameterized query; the PREPARE and BINDs will fall outside the loop. Your method will also work inside a loop -- it just won't execute as quickly.

Tom Morrison
 
David,

I was rereading your post and noticed this:
AmarilloElvis said:
So, I'm at a guessing game on how SQL PREPARE QUERY would follow the above example.

The following is from the description below the flowchart previously referenced:
InstantSQL said:
The SQL CONSTRUCT QUERY statement can be used prior to the SQL PREPARE QUERY statement to construct the SQL statement text string to be prepared.

SQL CONSTRUCT QUERY is simply a tool that can help chunk together a query text string that will then be passed to SQL PREPARE QUERY. There are some special things that SQL CONSTRUCT QUERY does that make it superior in some cases to a simple COBOL STRING statement (trimming spaces, dealing with SQL literal representations, date and time format conversion, etc.).

Tom Morrison
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top