Skip to main content

SQL FETCH doesn't move values into :ws-variables

  • September 21, 2022
  • 6 replies
  • 0 views

Here is a program using sql cursor against an MSSQL Server database. It runs but does not move any values into the ag-code nor ag-name WORKING STORAGE as specified in the FETCH.

$SET SQL sourceformat(variable)
$set constant driverClass "com.microsoft.sqlserver.jdbc.SQLServerDriver"
$set constant AMPDBdatabaseURL "jdbc:sqlserver://xxxxxxx.gov:1433;database=XXXXXXXX;user=XXXXxxxxXXXXX;password=xxxxxxxxxx;trustServerCertificate=true;"

program-id. Program1 as "twelve.Program1".

environment division.

data division.
working-storage section.

EXEC SQL INCLUDE SQLCA END-EXEC.
EXEC SQL BEGIN DECLARE SECTION END-EXEC

01 ag-code pic x(02).
01 ag-name pic x(60).
exec sql at ampdb
   declare foo cursor for select
      ag_code, ag_name from agency
end-exec

01 connectionstring pic x(300) value spaces.
EXEC SQL END DECLARE SECTION END-EXEC

01 MFSQLMESSAGETEXT PIC X(250).

01 IDX2 PIC 9(09).

Procedure Division.

mainline.
   move "Driver=" & driverClass & ";URL=" & ampDBdatabaseURL to connectionstring

   exec sql connect using :connectionstring AS AMPDB end-exec
   if sqlcode not = 0
      perform sql-err
   end-if.

   EXEC SQL OPEN foo END-EXEC.
   MOVE ZEROS TO IDX2
   PERFORM UNTIL SQLCODE < 0 OR SQLCODE = +100 OR IDX2 > 10
      ADD 1 TO IDX2
      EXEC FETCH foo INTO :ag-code, :ag-name END-EXEC
      IF SQLCODE = 0
         DISPLAY "AMP FOUND IDX2=" IDX2 " ag-code " ag-code " ag-name " ag-name
      END-IF
   END-PERFORM.
   exec sql disconnect ALL end-exec.
   goback.

sql-err.
   display "SQLCODE IS " sqlcode
   DISPLAY "SQLSTATE IS " SQLSTATE
   display "MFSQLMESSAGETEXT IS " MFSQLMESSAGETEXT
   stop run.

end program Program1.

Here are the results:

AMP FOUND IDX2=000000001 ag-code   ag-name
AMP FOUND IDX2=000000002 ag-code   ag-name
AMP FOUND IDX2=000000003 ag-code   ag-name
AMP FOUND IDX2=000000004 ag-code   ag-name
AMP FOUND IDX2=000000005 ag-code   ag-name
AMP FOUND IDX2=000000006 ag-code   ag-name
AMP FOUND IDX2=000000007 ag-code   ag-name
AMP FOUND IDX2=000000008 ag-code   ag-name
AMP FOUND IDX2=000000009 ag-code   ag-name
AMP FOUND IDX2=000000010 ag-code   ag-name
AMP FOUND IDX2=000000011 ag-code   ag-name

As you can see, the ag-code shows two spaces, as its definition is pic x(02). If I define it as pic 9(02), I see two zeros.

The definition of the source fields in the SQL database are nvarchar(2) and nvarchar(60).

This type of query works for other tables in a different database.

Any assistance would be grand. Thank you. James.

6 replies

Chris Glazier
Forum|alt.badge.img+2
  • Moderator
  • September 21, 2022

Here is a program using sql cursor against an MSSQL Server database. It runs but does not move any values into the ag-code nor ag-name WORKING STORAGE as specified in the FETCH.

$SET SQL sourceformat(variable)
$set constant driverClass "com.microsoft.sqlserver.jdbc.SQLServerDriver"
$set constant AMPDBdatabaseURL "jdbc:sqlserver://xxxxxxx.gov:1433;database=XXXXXXXX;user=XXXXxxxxXXXXX;password=xxxxxxxxxx;trustServerCertificate=true;"

program-id. Program1 as "twelve.Program1".

environment division.

data division.
working-storage section.

EXEC SQL INCLUDE SQLCA END-EXEC.
EXEC SQL BEGIN DECLARE SECTION END-EXEC

01 ag-code pic x(02).
01 ag-name pic x(60).
exec sql at ampdb
   declare foo cursor for select
      ag_code, ag_name from agency
end-exec

01 connectionstring pic x(300) value spaces.
EXEC SQL END DECLARE SECTION END-EXEC

01 MFSQLMESSAGETEXT PIC X(250).

01 IDX2 PIC 9(09).

Procedure Division.

mainline.
   move "Driver=" & driverClass & ";URL=" & ampDBdatabaseURL to connectionstring

   exec sql connect using :connectionstring AS AMPDB end-exec
   if sqlcode not = 0
      perform sql-err
   end-if.

   EXEC SQL OPEN foo END-EXEC.
   MOVE ZEROS TO IDX2
   PERFORM UNTIL SQLCODE < 0 OR SQLCODE = +100 OR IDX2 > 10
      ADD 1 TO IDX2
      EXEC FETCH foo INTO :ag-code, :ag-name END-EXEC
      IF SQLCODE = 0
         DISPLAY "AMP FOUND IDX2=" IDX2 " ag-code " ag-code " ag-name " ag-name
      END-IF
   END-PERFORM.
   exec sql disconnect ALL end-exec.
   goback.

sql-err.
   display "SQLCODE IS " sqlcode
   DISPLAY "SQLSTATE IS " SQLSTATE
   display "MFSQLMESSAGETEXT IS " MFSQLMESSAGETEXT
   stop run.

end program Program1.

Here are the results:

AMP FOUND IDX2=000000001 ag-code   ag-name
AMP FOUND IDX2=000000002 ag-code   ag-name
AMP FOUND IDX2=000000003 ag-code   ag-name
AMP FOUND IDX2=000000004 ag-code   ag-name
AMP FOUND IDX2=000000005 ag-code   ag-name
AMP FOUND IDX2=000000006 ag-code   ag-name
AMP FOUND IDX2=000000007 ag-code   ag-name
AMP FOUND IDX2=000000008 ag-code   ag-name
AMP FOUND IDX2=000000009 ag-code   ag-name
AMP FOUND IDX2=000000010 ag-code   ag-name
AMP FOUND IDX2=000000011 ag-code   ag-name

As you can see, the ag-code shows two spaces, as its definition is pic x(02). If I define it as pic 9(02), I see two zeros.

The definition of the source fields in the SQL database are nvarchar(2) and nvarchar(60).

This type of query works for other tables in a different database.

Any assistance would be grand. Thank you. James.

Is this a typo:

EXEC FETCH foo INTO :ag-code, :ag-name END-EXEC

It should say EXEC SQL


  • September 21, 2022

Is this a typo:

EXEC FETCH foo INTO :ag-code, :ag-name END-EXEC

It should say EXEC SQL

Indeed. Correcting that typo results in NO DISPLAYS (zero records). There are records present in that table confirmed by a different sql client.


Chris Glazier
Forum|alt.badge.img+2
  • Moderator
  • September 21, 2022

Indeed. Correcting that typo results in NO DISPLAYS (zero records). There are records present in that table confirmed by a different sql client.

What is the SQLCODE returned by the FETCH? If it is non-zero you don't display anything nor do you execute the error routine.


  • September 21, 2022

What is the SQLCODE returned by the FETCH? If it is non-zero you don't display anything nor do you execute the error routine.

(post-fetch) sqlcode +0000000001 sqlstate 01004 mfsqlmessagetext String data - right truncation. Thanks for pointing me int he right direction, @chris


Claude Greiner
  • Participating Frequently
  • September 21, 2022

Here is a program using sql cursor against an MSSQL Server database. It runs but does not move any values into the ag-code nor ag-name WORKING STORAGE as specified in the FETCH.

$SET SQL sourceformat(variable)
$set constant driverClass "com.microsoft.sqlserver.jdbc.SQLServerDriver"
$set constant AMPDBdatabaseURL "jdbc:sqlserver://xxxxxxx.gov:1433;database=XXXXXXXX;user=XXXXxxxxXXXXX;password=xxxxxxxxxx;trustServerCertificate=true;"

program-id. Program1 as "twelve.Program1".

environment division.

data division.
working-storage section.

EXEC SQL INCLUDE SQLCA END-EXEC.
EXEC SQL BEGIN DECLARE SECTION END-EXEC

01 ag-code pic x(02).
01 ag-name pic x(60).
exec sql at ampdb
   declare foo cursor for select
      ag_code, ag_name from agency
end-exec

01 connectionstring pic x(300) value spaces.
EXEC SQL END DECLARE SECTION END-EXEC

01 MFSQLMESSAGETEXT PIC X(250).

01 IDX2 PIC 9(09).

Procedure Division.

mainline.
   move "Driver=" & driverClass & ";URL=" & ampDBdatabaseURL to connectionstring

   exec sql connect using :connectionstring AS AMPDB end-exec
   if sqlcode not = 0
      perform sql-err
   end-if.

   EXEC SQL OPEN foo END-EXEC.
   MOVE ZEROS TO IDX2
   PERFORM UNTIL SQLCODE < 0 OR SQLCODE = +100 OR IDX2 > 10
      ADD 1 TO IDX2
      EXEC FETCH foo INTO :ag-code, :ag-name END-EXEC
      IF SQLCODE = 0
         DISPLAY "AMP FOUND IDX2=" IDX2 " ag-code " ag-code " ag-name " ag-name
      END-IF
   END-PERFORM.
   exec sql disconnect ALL end-exec.
   goback.

sql-err.
   display "SQLCODE IS " sqlcode
   DISPLAY "SQLSTATE IS " SQLSTATE
   display "MFSQLMESSAGETEXT IS " MFSQLMESSAGETEXT
   stop run.

end program Program1.

Here are the results:

AMP FOUND IDX2=000000001 ag-code   ag-name
AMP FOUND IDX2=000000002 ag-code   ag-name
AMP FOUND IDX2=000000003 ag-code   ag-name
AMP FOUND IDX2=000000004 ag-code   ag-name
AMP FOUND IDX2=000000005 ag-code   ag-name
AMP FOUND IDX2=000000006 ag-code   ag-name
AMP FOUND IDX2=000000007 ag-code   ag-name
AMP FOUND IDX2=000000008 ag-code   ag-name
AMP FOUND IDX2=000000009 ag-code   ag-name
AMP FOUND IDX2=000000010 ag-code   ag-name
AMP FOUND IDX2=000000011 ag-code   ag-name

As you can see, the ag-code shows two spaces, as its definition is pic x(02). If I define it as pic 9(02), I see two zeros.

The definition of the source fields in the SQL database are nvarchar(2) and nvarchar(60).

This type of query works for other tables in a different database.

Any assistance would be grand. Thank you. James.

Here any corrections:

EXEC SQL
DECLARE FOO CURSOR FOR SELECT
,A.code
,A.name
,FROM t_tabelle  A *> insert correct table 
WHERE A.code  = :ag-cod
ORDER BY A.cod, A.Name
END-EXEC

   EXEC SQL OPEN foo END-EXEC.


   MOVE ZEROS TO IDX2
   PERFORM UNTIL SQLCODE < 0 OR SQLCODE = +100 OR IDX2 > 10
      ADD 1 TO IDX2
      EXEC SQL

      FETCH foo INTO :ag-code, :ag-name

           END-EXEC
      IF SQLCODE = 0
         DISPLAY "AMP FOUND IDX2=" IDX2 " ag-code " ag-code " ag-name " ag-name
      END-IF
   END-PERFORM.

you must declare your cursor first, then as Chris remarks start with exec sql

you don't need the idx2 variable

i have only take a look on a part of your cbl, but with this code you must becomes values.

By compiling you must have no errors, also by sql commands.

Wich compiler are you using?

cg


  • September 21, 2022

Here any corrections:

EXEC SQL
DECLARE FOO CURSOR FOR SELECT
,A.code
,A.name
,FROM t_tabelle  A *> insert correct table 
WHERE A.code  = :ag-cod
ORDER BY A.cod, A.Name
END-EXEC

   EXEC SQL OPEN foo END-EXEC.


   MOVE ZEROS TO IDX2
   PERFORM UNTIL SQLCODE < 0 OR SQLCODE = +100 OR IDX2 > 10
      ADD 1 TO IDX2
      EXEC SQL

      FETCH foo INTO :ag-code, :ag-name

           END-EXEC
      IF SQLCODE = 0
         DISPLAY "AMP FOUND IDX2=" IDX2 " ag-code " ag-code " ag-name " ag-name
      END-IF
   END-PERFORM.

you must declare your cursor first, then as Chris remarks start with exec sql

you don't need the idx2 variable

i have only take a look on a part of your cbl, but with this code you must becomes values.

By compiling you must have no errors, also by sql commands.

Wich compiler are you using?

cg

I solved using Chris' guidance - I displayed the SQLCODE (and other useful sql variables SQLSTATE, and mfsqlmessagetext) AFTER the FETCH. The mfsqlmessagetext indicated a truncation error (the receiving working storage was not large enough to hold the incoming value from SQL).

Thank you for your effort today!