Skip to main content

I installed Micro Focus Cobol visual 2010 trial for eclipse (windows 32 bit), I added an application that I want to debug COBOL. But after my  EXEC SQL .CONNECT END EXEC and after EXEC SQL INSERT END EXEC, eclipse tells me that as an error: "SQL ERROR 19703 in Connect command and SQL error 10702 in Insert Command". I want to link to a database SQL SERVER 2012 for the application to debug COBOL. I put the directives "SQL(DBMan=ODBC). When I try to put others Directives like INIT,  DB or PASS I can´t . I need some others thing like install ODBC Drivers for SQL Server ? When I do that out the Eclipse ednvironment I connected withw SQL Server and I can see my Databases and my tables there.

Thank you for your help.

I installed Micro Focus Cobol visual 2010 trial for eclipse (windows 32 bit), I added an application that I want to debug COBOL. But after my  EXEC SQL .CONNECT END EXEC and after EXEC SQL INSERT END EXEC, eclipse tells me that as an error: "SQL ERROR 19703 in Connect command and SQL error 10702 in Insert Command". I want to link to a database SQL SERVER 2012 for the application to debug COBOL. I put the directives "SQL(DBMan=ODBC). When I try to put others Directives like INIT,  DB or PASS I can´t . I need some others thing like install ODBC Drivers for SQL Server ? When I do that out the Eclipse ednvironment I connected withw SQL Server and I can see my Databases and my tables there.

Thank you for your help.

The 19703 error on the connect simply means that the connect failed which usually indicates that the connect statement is incorrect or the ODBC driver or DSN is not set up properly. The error on the INSERT is due to the failure of the connect.

If you add the following to your program's working-storage:

01 MFSQLMESSAGETEXT    PIC X(256).

Then this variable will contain the actual error message text after the error occurs.

Have you setup the DSN using the ODBC Administrator?

You can start this by navigating to Start Menu-->All Programs-->Micro Focus Visual COBOL-->Data Tools-->Data Connections-->ODBC Data Source Administrator 32-bit.

Create a DSN and use its name in the connect statement:

EXEC SQL CONNECT TO MYDSN END-EXEC

After setting up the DSN press the Test Connect button.

If it connects successfully then it should also connect successfully within your COBOL application by using the same DSN.

I am assuming that you are creating a 32-bit DSN because you said that this was a 32-bit Windows system.

You can use the sample program below to test the various connect statements that can be used.

Provide the parameters for DSN, userid and password when prompted.

     $SET SQL(dbman=ODBC)                                            

     ****************************************************************

     *  Copyright (C) 1992-2002  Micro Focus International Ltd.      

     *  All rights reserved.                                          

     *---------------------------------------------------------------

      working-storage section.                                        

     *  Include the SQL Communications Area. This includes the        

     *  definitions of SQLCODE, etc                                  

      EXEC SQL INCLUDE SQLCA END-EXEC                                

      EXEC SQL BEGIN DECLARE SECTION END-EXEC                        

      01 svr          pic x(32).                                      

      01 usr          pic x(32).                                      

      01 pass         pic x(32).                                      

      01 usr-pass     pic x(64).                                      

      EXEC SQL END DECLARE SECTION END-EXEC.                          

      procedure division.                                            

     *    Connect to an SQL Server.                                  

          display "Connect statement tests"                          

          display " "                                                

          display "Enter data source (Eg UserSample2) "              

                  with no advancing                                  

          accept svr                                                  

          display "Enter username (Eg admin) "                        

                   with no advancing                                  

          accept usr                                                  

          display "Enter password (Eg <blank>) "                      

                   with no advancing                                  

          accept pass                                                

     *test 1 - basic SQL Server style connect                        

          display "Test 1:"                                          

          string                                                      

              usr delimited space                                    

              "." delimited size                                      

              pass delimited space                                    

          into usr-pass                                              

          EXEC SQL                                                    

              CONNECT TO :svr USER :usr-pass                          

          END-EXEC                                                    

          if sqlcode not = 0                                          

               display "Error: cannot connect "                      

               display sqlcode                                        

               display sqlerrmc                                      

               stop run                                              

          end-if                                                      

          display "Test 1: OK"                                        

          EXEC SQL                                                    

              DISCONNECT CURRENT                                      

          END-EXEC                                                    

          if sqlcode not = 0                                          

               display "Error: cannot disconnect "                    

               display sqlcode                                        

               display sqlerrmc                                      

               stop run                                              

          end-if                                                      

     *test 2 - SQL Server style connect with no prompt and slash      

          display "Test 2:"                                          

          string                                                      

              usr delimited space                                    

              "/" delimited size                                      

              pass delimited space                                    

          into usr-pass                                              

          EXEC SQL                                                    

              CONNECT TO :svr USER :usr-pass WITH NO PROMPT          

          END-EXEC                                                    

          if sqlcode not = 0                                          

               display "Error: cannot connect "                      

               display sqlcode                                        

               display sqlerrmc                                      

               stop run                                              

          end-if                                                      

          display "Test 2: OK"                                        

          EXEC SQL                                                    

              DISCONNECT DEFAULT                                      

          END-EXEC                                                    

          if sqlcode not = 0                                          

               display "Error: cannot disconnect "                    

               display sqlcode                                        

               display sqlerrmc                                      

               stop run                                              

          end-if                                                      

     *test 3 - Oracle style connect with combined user and password  

          display "Test 3:"                                          

          string                                                      

              usr delimited space                                    

              "/" delimited size                                      

              pass delimited space                                    

          into usr-pass                                              

          EXEC SQL                                                    

              CONNECT :usr-pass USING :svr                            

          END-EXEC                                                    

          if sqlcode not = 0                                          

               display "Error: cannot connect "                      

               display sqlcode                                        

               display sqlerrmc                                      

               stop run                                              

          end-if                                                      

          display "Test 3: OK"                                        

          EXEC SQL                                                    

              DISCONNECT                                              

          END-EXEC                                                    

          if sqlcode not = 0                                          

               display "Error: cannot disconnect "                    

               display sqlcode                                        

               display sqlerrmc                                      

               stop run                                              

          end-if                                                      

     *test 4 - Oracle style connect with separate user and password  

          display "Test 4:"                                          

          EXEC SQL                                                    

              CONNECT :usr IDENTIFIED BY :pass USING :svr            

          END-EXEC                                                    

          if sqlcode not = 0                                          

               display "Error: cannot connect "                      

               display sqlcode                                        

               display sqlerrmc                                      

               stop run                                              

          end-if                                                      

          display "Test 4: OK"                                        

          EXEC SQL                                                    

              DISCONNECT ALL                                          

          END-EXEC                                                    

          if sqlcode not = 0                                          

               display "Error: cannot disconnect "                    

               display sqlcode                                        

               display sqlerrmc                                      

               stop run                                              

          end-if                                                      

     *test 5 - Connect with prompt                                    

          display "Test 5:"                                          

          EXEC SQL                                                    

              CONNECT WITH PROMPT                                    

          END-EXEC                                                    

          if sqlcode not = 0                                          

               display "Error: cannot connect "                      

               display sqlcode                                        

               display sqlerrmc                                      

               stop run                                              

          end-if                                                      

          display "Test 5: OK"                                        

          EXEC SQL                                                    

              CONNECT RESET                                          

          END-EXEC                                                    

          if sqlcode not = 0                                          

               display "Error: cannot disconnect "                    

               display sqlcode                                        

               display sqlerrmc                                      

               stop run                                              

          end-if                                                      

          stop run.                                                  


I installed Micro Focus Cobol visual 2010 trial for eclipse (windows 32 bit), I added an application that I want to debug COBOL. But after my  EXEC SQL .CONNECT END EXEC and after EXEC SQL INSERT END EXEC, eclipse tells me that as an error: "SQL ERROR 19703 in Connect command and SQL error 10702 in Insert Command". I want to link to a database SQL SERVER 2012 for the application to debug COBOL. I put the directives "SQL(DBMan=ODBC). When I try to put others Directives like INIT,  DB or PASS I can´t . I need some others thing like install ODBC Drivers for SQL Server ? When I do that out the Eclipse ednvironment I connected withw SQL Server and I can see my Databases and my tables there.

Thank you for your help.

YES...Many Thanks....


The 19703 error on the connect simply means that the connect failed which usually indicates that the connect statement is incorrect or the ODBC driver or DSN is not set up properly. The error on the INSERT is due to the failure of the connect.

If you add the following to your program's working-storage:

01 MFSQLMESSAGETEXT    PIC X(256).

Then this variable will contain the actual error message text after the error occurs.

Have you setup the DSN using the ODBC Administrator?

You can start this by navigating to Start Menu-->All Programs-->Micro Focus Visual COBOL-->Data Tools-->Data Connections-->ODBC Data Source Administrator 32-bit.

Create a DSN and use its name in the connect statement:

EXEC SQL CONNECT TO MYDSN END-EXEC

After setting up the DSN press the Test Connect button.

If it connects successfully then it should also connect successfully within your COBOL application by using the same DSN.

I am assuming that you are creating a 32-bit DSN because you said that this was a 32-bit Windows system.

You can use the sample program below to test the various connect statements that can be used.

Provide the parameters for DSN, userid and password when prompted.

     $SET SQL(dbman=ODBC)                                            

     ****************************************************************

     *  Copyright (C) 1992-2002  Micro Focus International Ltd.      

     *  All rights reserved.                                          

     *---------------------------------------------------------------

      working-storage section.                                        

     *  Include the SQL Communications Area. This includes the        

     *  definitions of SQLCODE, etc                                  

      EXEC SQL INCLUDE SQLCA END-EXEC                                

      EXEC SQL BEGIN DECLARE SECTION END-EXEC                        

      01 svr          pic x(32).                                      

      01 usr          pic x(32).                                      

      01 pass         pic x(32).                                      

      01 usr-pass     pic x(64).                                      

      EXEC SQL END DECLARE SECTION END-EXEC.                          

      procedure division.                                            

     *    Connect to an SQL Server.                                  

          display "Connect statement tests"                          

          display " "                                                

          display "Enter data source (Eg UserSample2) "              

                  with no advancing                                  

          accept svr                                                  

          display "Enter username (Eg admin) "                        

                   with no advancing                                  

          accept usr                                                  

          display "Enter password (Eg <blank>) "                      

                   with no advancing                                  

          accept pass                                                

     *test 1 - basic SQL Server style connect                        

          display "Test 1:"                                          

          string                                                      

              usr delimited space                                    

              "." delimited size                                      

              pass delimited space                                    

          into usr-pass                                              

          EXEC SQL                                                    

              CONNECT TO :svr USER :usr-pass                          

          END-EXEC                                                    

          if sqlcode not = 0                                          

               display "Error: cannot connect "                      

               display sqlcode                                        

               display sqlerrmc                                      

               stop run                                              

          end-if                                                      

          display "Test 1: OK"                                        

          EXEC SQL                                                    

              DISCONNECT CURRENT                                      

          END-EXEC                                                    

          if sqlcode not = 0                                          

               display "Error: cannot disconnect "                    

               display sqlcode                                        

               display sqlerrmc                                      

               stop run                                              

          end-if                                                      

     *test 2 - SQL Server style connect with no prompt and slash      

          display "Test 2:"                                          

          string                                                      

              usr delimited space                                    

              "/" delimited size                                      

              pass delimited space                                    

          into usr-pass                                              

          EXEC SQL                                                    

              CONNECT TO :svr USER :usr-pass WITH NO PROMPT          

          END-EXEC                                                    

          if sqlcode not = 0                                          

               display "Error: cannot connect "                      

               display sqlcode                                        

               display sqlerrmc                                      

               stop run                                              

          end-if                                                      

          display "Test 2: OK"                                        

          EXEC SQL                                                    

              DISCONNECT DEFAULT                                      

          END-EXEC                                                    

          if sqlcode not = 0                                          

               display "Error: cannot disconnect "                    

               display sqlcode                                        

               display sqlerrmc                                      

               stop run                                              

          end-if                                                      

     *test 3 - Oracle style connect with combined user and password  

          display "Test 3:"                                          

          string                                                      

              usr delimited space                                    

              "/" delimited size                                      

              pass delimited space                                    

          into usr-pass                                              

          EXEC SQL                                                    

              CONNECT :usr-pass USING :svr                            

          END-EXEC                                                    

          if sqlcode not = 0                                          

               display "Error: cannot connect "                      

               display sqlcode                                        

               display sqlerrmc                                      

               stop run                                              

          end-if                                                      

          display "Test 3: OK"                                        

          EXEC SQL                                                    

              DISCONNECT                                              

          END-EXEC                                                    

          if sqlcode not = 0                                          

               display "Error: cannot disconnect "                    

               display sqlcode                                        

               display sqlerrmc                                      

               stop run                                              

          end-if                                                      

     *test 4 - Oracle style connect with separate user and password  

          display "Test 4:"                                          

          EXEC SQL                                                    

              CONNECT :usr IDENTIFIED BY :pass USING :svr            

          END-EXEC                                                    

          if sqlcode not = 0                                          

               display "Error: cannot connect "                      

               display sqlcode                                        

               display sqlerrmc                                      

               stop run                                              

          end-if                                                      

          display "Test 4: OK"                                        

          EXEC SQL                                                    

              DISCONNECT ALL                                          

          END-EXEC                                                    

          if sqlcode not = 0                                          

               display "Error: cannot disconnect "                    

               display sqlcode                                        

               display sqlerrmc                                      

               stop run                                              

          end-if                                                      

     *test 5 - Connect with prompt                                    

          display "Test 5:"                                          

          EXEC SQL                                                    

              CONNECT WITH PROMPT                                    

          END-EXEC                                                    

          if sqlcode not = 0                                          

               display "Error: cannot connect "                      

               display sqlcode                                        

               display sqlerrmc                                      

               stop run                                              

          end-if                                                      

          display "Test 5: OK"                                        

          EXEC SQL                                                    

              CONNECT RESET                                          

          END-EXEC                                                    

          if sqlcode not = 0                                          

               display "Error: cannot disconnect "                    

               display sqlcode                                        

               display sqlerrmc                                      

               stop run                                              

          end-if                                                      

          stop run.                                                  

Hi Chris,

We are facing the same issue (Database connect attempt failed. Sqlcode: -000019703) reported in this thread when using the Red Hat Enterprise Linux(RHEL) 8.3 version. On top of it, we had installed the Microfocus COBOL v6.0 and Microsoft SQL server version 2019. Could you please provide your suggestion on this issue.

Thanks,

Soundar


Hi Chris,

We are facing the same issue (Database connect attempt failed. Sqlcode: -000019703) reported in this thread when using the Red Hat Enterprise Linux(RHEL) 8.3 version. On top of it, we had installed the Microfocus COBOL v6.0 and Microsoft SQL server version 2019. Could you please provide your suggestion on this issue.

Thanks,

Soundar

My advice wiould be the same as the verified answer on this thread.

Can you connect using the same connection string outside of COBOL?


My advice wiould be the same as the verified answer on this thread.

Can you connect using the same connection string outside of COBOL?

Thanks for your response Chris.

Could you please let us know the steps to setup the DSN in Linux as the above verified answer is for Windows. Below is the current syntax of the command which we are trying to access the DB through the Cobol batch program,

EXEC SQL

CONNECT TO 'sqldbcon' AS '<<dbname>>'
      -     USER '<<username>>.<<password>>'

END-EXEC.

When we are trying to access the DB using the terminal below command and we are able to access the DB successfully

isql sqldbcon <<username>> <<password>>


Thanks for your response Chris.

Could you please let us know the steps to setup the DSN in Linux as the above verified answer is for Windows. Below is the current syntax of the command which we are trying to access the DB through the Cobol batch program,

EXEC SQL

CONNECT TO 'sqldbcon' AS '<<dbname>>'
      -     USER '<<username>>.<<password>>'

END-EXEC.

When we are trying to access the DB using the terminal below command and we are able to access the DB successfully

isql sqldbcon <<username>> <<password>>

Hi Soundrarajan Venugopal,

You've mentioned that you are able to connect to the SQL Server database on Linux from the isql prompt. That sounds like you have the DSN configured, and just need an example of how you could specify the connection in COBOL. Please see the following program for an example:

      $set sql(dbman=odbc)
       program-id. cobconnect as "cobconnect".

       environment division.
       configuration section.

       data division.
       working-storage section.

       exec sql include sqlca end-exec.
       01 mfsqlmessagetext    pic x(256).
       77 dbms-server         pic x(32).
       77 dbms-user           pic x(64) value spaces.
       77 dbms-passwd         pic x(64) value spaces.
       77 dbms-userpwd        pic x(128) value spaces.

       procedure division.

           move "username" to dbms-user
           move "password" to dbms-passwd
           move "sqldbcon" to dbms-server
           move spaces to dbms-userpwd

           string dbms-user delimited BY spaces
             "/" delimited BY spaces
             dbms-passwd delimited BY spaces
             into dbms-userpwd

           end-string
           .

           exec sql
                connect TO :dbms-server USER :dbms-userpwd
           end-exec
           .

           if sqlcode not = 0
               display "connect failed with SQLCODE:" SQLCODE
               display "       SQLERRMC:" SQLERRMC
               exhibit named mfsqlmessagetext
               display "stopping..."
               goback
           end-if
           .

      *  Change context to desired database "DBNAME" in SQL Server.

           exec sql
               use DBNAME
           end-exec

           if sqlcode NOT = 5701
               display "Cannot set database name for MSSQL "
               display "SQLCODE: SQLCODE"
               display "       SQLERRMC:" SQLERRMC
               exhibit named mfsqlmessagetext
               display "stopping..."
               goback
           end-if

           goback
           .

       end program cobconnect.

Please let me know if you have questions about the above example.


Hi Soundrarajan Venugopal,

You've mentioned that you are able to connect to the SQL Server database on Linux from the isql prompt. That sounds like you have the DSN configured, and just need an example of how you could specify the connection in COBOL. Please see the following program for an example:

      $set sql(dbman=odbc)
       program-id. cobconnect as "cobconnect".

       environment division.
       configuration section.

       data division.
       working-storage section.

       exec sql include sqlca end-exec.
       01 mfsqlmessagetext    pic x(256).
       77 dbms-server         pic x(32).
       77 dbms-user           pic x(64) value spaces.
       77 dbms-passwd         pic x(64) value spaces.
       77 dbms-userpwd        pic x(128) value spaces.

       procedure division.

           move "username" to dbms-user
           move "password" to dbms-passwd
           move "sqldbcon" to dbms-server
           move spaces to dbms-userpwd

           string dbms-user delimited BY spaces
             "/" delimited BY spaces
             dbms-passwd delimited BY spaces
             into dbms-userpwd

           end-string
           .

           exec sql
                connect TO :dbms-server USER :dbms-userpwd
           end-exec
           .

           if sqlcode not = 0
               display "connect failed with SQLCODE:" SQLCODE
               display "       SQLERRMC:" SQLERRMC
               exhibit named mfsqlmessagetext
               display "stopping..."
               goback
           end-if
           .

      *  Change context to desired database "DBNAME" in SQL Server.

           exec sql
               use DBNAME
           end-exec

           if sqlcode NOT = 5701
               display "Cannot set database name for MSSQL "
               display "SQLCODE: SQLCODE"
               display "       SQLERRMC:" SQLERRMC
               exhibit named mfsqlmessagetext
               display "stopping..."
               goback
           end-if

           goback
           .

       end program cobconnect.

Please let me know if you have questions about the above example.

Hi Blair, 

PFB the source code which we are currently using to establish the DB connection. I guess that our code is more or less similar to the source that you had shared above. Please let us know if we need to make any modifications in the source code.

      *************************
       IDENTIFICATION DIVISION.
      *************************

       PROGRAM-ID. COBCICON.


      *****************************************************************
      **  MEMBER :  COBCICON                                         **
      **  REMARKS:  SQL PROGRAM USED TO INVOKE SQL COMMANDS NOT      **
      **            RELATED TO A SPECIFIC TABLE                      **
      *****************************************************************
      /
      **********************
       ENVIRONMENT DIVISION.
      **********************

      ***************
       DATA DIVISION.
      ***************
      /
      *************************
       WORKING-STORAGE SECTION.
      *************************

      *****************
       LINKAGE SECTION.
      *****************

           EXEC SQL INCLUDE SQLCA     END-EXEC.

           EXEC SQL INCLUDE XCWLICON  END-EXEC.
      /
       PROCEDURE DIVISION USING SQLCA
                                LICON-PARM-AREA.

      ***************
       0000-MAINLINE.
      ***************

           PERFORM  1000-CONNECT
               THRU 1000-CONNECT-X.

       0000-MAINLINE-X.
           EXIT.
      /
      **************
       1000-CONNECT.
      **************

           MOVE ZERO TO SQLCODE.
TESTIN* CURRENTLY WE HAVE DIRECTLY HARDCODED THE DB CONNECTION DETAILS, 
TESTIN*DSN NAME sqldbcon
TESTIN*DB NAME SQDBI1
TESTIN*USER dbapuser
TESTIN*PWD admindb-7890
	   
           EXEC SQL
            CONNECT TO 'sqldbcon' AS 'SQDBI1' 
            - USER 'dbapuser.admindb-7890'
           END-EXEC.

           EVALUATE SQLCODE

               WHEN +1
               WHEN ZERO
                    SET  LICON-RETURN-OK     TO  TRUE

               WHEN OTHER
                    SET  LICON-RETURN-ERROR  TO  TRUE

           END-EVALUATE.

       1000-CONNECT-X.
           EXIT.
      /
      *****************************************************************
      **                 END OF PROGRAM COBCICON                     **
      *****************************************************************
 


Hi Blair, 

PFB the source code which we are currently using to establish the DB connection. I guess that our code is more or less similar to the source that you had shared above. Please let us know if we need to make any modifications in the source code.

      *************************
       IDENTIFICATION DIVISION.
      *************************

       PROGRAM-ID. COBCICON.


      *****************************************************************
      **  MEMBER :  COBCICON                                         **
      **  REMARKS:  SQL PROGRAM USED TO INVOKE SQL COMMANDS NOT      **
      **            RELATED TO A SPECIFIC TABLE                      **
      *****************************************************************
      /
      **********************
       ENVIRONMENT DIVISION.
      **********************

      ***************
       DATA DIVISION.
      ***************
      /
      *************************
       WORKING-STORAGE SECTION.
      *************************

      *****************
       LINKAGE SECTION.
      *****************

           EXEC SQL INCLUDE SQLCA     END-EXEC.

           EXEC SQL INCLUDE XCWLICON  END-EXEC.
      /
       PROCEDURE DIVISION USING SQLCA
                                LICON-PARM-AREA.

      ***************
       0000-MAINLINE.
      ***************

           PERFORM  1000-CONNECT
               THRU 1000-CONNECT-X.

       0000-MAINLINE-X.
           EXIT.
      /
      **************
       1000-CONNECT.
      **************

           MOVE ZERO TO SQLCODE.
TESTIN* CURRENTLY WE HAVE DIRECTLY HARDCODED THE DB CONNECTION DETAILS, 
TESTIN*DSN NAME sqldbcon
TESTIN*DB NAME SQDBI1
TESTIN*USER dbapuser
TESTIN*PWD admindb-7890
	   
           EXEC SQL
            CONNECT TO 'sqldbcon' AS 'SQDBI1' 
            - USER 'dbapuser.admindb-7890'
           END-EXEC.

           EVALUATE SQLCODE

               WHEN +1
               WHEN ZERO
                    SET  LICON-RETURN-OK     TO  TRUE

               WHEN OTHER
                    SET  LICON-RETURN-ERROR  TO  TRUE

           END-EVALUATE.

       1000-CONNECT-X.
           EXIT.
      /
      *****************************************************************
      **                 END OF PROGRAM COBCICON                     **
      *****************************************************************
 

Hi Soundrarajan,

I'm still checking into this. In my preliminary testing, the specification of the desired database with the AS option on the CONNECT statement is not working as you've shown it:

           MOVE ZERO TO SQLCODE.

TESTIN* CURRENTLY WE HAVE DIRECTLY HARDCODED THE DB CONNECTION DETAILS,

TESTIN*DSN NAME sqldbcon

TESTIN*DB NAME SQDBI1

TESTIN*USER dbapuser

TESTIN*PWD admindb-7890

  

           EXEC SQL

            CONNECT TO 'sqldbcon' AS 'SQDBI1'

            - USER 'dbapuser.admindb-7890'

           END-EXEC.

However, the method I showed in the program I attached earlier in this thread *is* working in my tests. In my sample, you first just connect, and then separately switch to the desired database with a separate SQL USE statement:

      *  Change context to desired database "DBNAME" in SQL Server.

 

           exec sql

               use DBNAME

           end-exec

 

           if sqlcode NOT = 5701

               display "Cannot set database name for MSSQL "

               display "SQLCODE: SQLCODE"

               display "       SQLERRMC:" SQLERRMC

               exhibit named mfsqlmessagetext

               display "stopping..."

               goback

           end-if

Would it possible for you to create a Support Case for this issue? In the case description, you can ask for the case to be assigned to Blair McDonald.

Thanks.


Hi Soundrarajan,

I'm still checking into this. In my preliminary testing, the specification of the desired database with the AS option on the CONNECT statement is not working as you've shown it:

           MOVE ZERO TO SQLCODE.

TESTIN* CURRENTLY WE HAVE DIRECTLY HARDCODED THE DB CONNECTION DETAILS,

TESTIN*DSN NAME sqldbcon

TESTIN*DB NAME SQDBI1

TESTIN*USER dbapuser

TESTIN*PWD admindb-7890

  

           EXEC SQL

            CONNECT TO 'sqldbcon' AS 'SQDBI1'

            - USER 'dbapuser.admindb-7890'

           END-EXEC.

However, the method I showed in the program I attached earlier in this thread *is* working in my tests. In my sample, you first just connect, and then separately switch to the desired database with a separate SQL USE statement:

      *  Change context to desired database "DBNAME" in SQL Server.

 

           exec sql

               use DBNAME

           end-exec

 

           if sqlcode NOT = 5701

               display "Cannot set database name for MSSQL "

               display "SQLCODE: SQLCODE"

               display "       SQLERRMC:" SQLERRMC

               exhibit named mfsqlmessagetext

               display "stopping..."

               goback

           end-if

Would it possible for you to create a Support Case for this issue? In the case description, you can ask for the case to be assigned to Blair McDonald.

Thanks.

We had changed the connection logic as below based on your above suggestion.

EXEC SQL

    CONNECT TO 'sqldbcon' USER 'dbapuser/admindb-7890'

END-EXEC.

IF SQLCODE NOT = '5701'

    DISPLAY "CANNOT SET DATABASE NAME FOR MSSQL "

    DISPLAY "SQLCODE:" SQLCODE

    DISPLAY " SQLERRMC:" SQLERRMC

    EXHIBIT NAMED WS-MFSQLMESSAGETEXT

    DISPLAY "STOPPING..."

END-IF.

EXEC SQL

    USE SQDBI1

END-EXEC.

IF SQLCODE NOT = '5701'

    DISPLAY "CANNOT SET DATABASE NAME FOR MSSQL "

    DISPLAY "SQLCODE:" SQLCODE

    DISPLAY " SQLERRMC:" SQLERRMC

    EXHIBIT NAMED WS-MFSQLMESSAGETEXT

    DISPLAY "STOPPING..."

END-IF.

 

Below messages gets displayed in batch output. Exhibit named didn’t work as we are getting spaces for this field.

CANNOT SET DATABASE NAME FOR MSSQL

SQLCODE:-0000019703

 SQLERRMC:Driver's SQLAllocHandle on SQL_HANDLE_HENV failed

WS-MFSQLMESSAGETEXT =                                                                                                                                                                                                                          

STOPPING...

CANNOT SET DATABASE NAME FOR MSSQL

SQLCODE:-0000019702

 SQLERRMC:Connection name not found.

WS-MFSQLMESSAGETEXT =                                                                                                                                                                                                                           

STOPPING...


We had changed the connection logic as below based on your above suggestion.

EXEC SQL

    CONNECT TO 'sqldbcon' USER 'dbapuser/admindb-7890'

END-EXEC.

IF SQLCODE NOT = '5701'

    DISPLAY "CANNOT SET DATABASE NAME FOR MSSQL "

    DISPLAY "SQLCODE:" SQLCODE

    DISPLAY " SQLERRMC:" SQLERRMC

    EXHIBIT NAMED WS-MFSQLMESSAGETEXT

    DISPLAY "STOPPING..."

END-IF.

EXEC SQL

    USE SQDBI1

END-EXEC.

IF SQLCODE NOT = '5701'

    DISPLAY "CANNOT SET DATABASE NAME FOR MSSQL "

    DISPLAY "SQLCODE:" SQLCODE

    DISPLAY " SQLERRMC:" SQLERRMC

    EXHIBIT NAMED WS-MFSQLMESSAGETEXT

    DISPLAY "STOPPING..."

END-IF.

 

Below messages gets displayed in batch output. Exhibit named didn’t work as we are getting spaces for this field.

CANNOT SET DATABASE NAME FOR MSSQL

SQLCODE:-0000019703

 SQLERRMC:Driver's SQLAllocHandle on SQL_HANDLE_HENV failed

WS-MFSQLMESSAGETEXT =                                                                                                                                                                                                                          

STOPPING...

CANNOT SET DATABASE NAME FOR MSSQL

SQLCODE:-0000019702

 SQLERRMC:Connection name not found.

WS-MFSQLMESSAGETEXT =                                                                                                                                                                                                                           

STOPPING...

    We have raised a support ticket 02460183 and assigned it to you