1

I'm a COBOL developer and I need to connect to a SQLite DB. I'm using NetExpress. I've seen this guide and also this post but I need a previous step, please. I don't know how to pass those c calls to COBOL. The guide explains that:

sqlite3_open("test.db", &db)

sqlite3_exec(sqlite3*, const char *sql, sqlite_callback, void *data, char **errmsg)

I have the database 'test.db', with one table 'tabla' with 2 columns (type text). I tried with this COBOL solution for open/insert/select:

  *
  *----------------------------------------------------------------*
  *                                                                *
  *                                                                *
  *                                                                *
  * SYSTEM                                                         *
  *                                                                *
  * PROGRAM-ID    Pxxxxxx
  *                                                                *
  * AUTHOR                                                         *
  *                                                                *
  * DATE          10/2016                                          *
  *                                                                *
  *                                                                *
  *                                                                *
  *                                                                *
  *----------------------------------------------------------------*
  *                                                                *
  *                                                                *
  *                                                                *
  *----------------------------------------------------------------*
   IDENTIFICATION DIVISION.
   PROGRAM-ID.  Pxxxxxx.

   ENVIRONMENT DIVISION.
   CONFIGURATION SECTION.

  /----------------------------------------------------------------*
   INPUT-OUTPUT SECTION.
   FILE-CONTROL.

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



  /----------------------------------------------------------------*
   DATA DIVISION.
   FILE SECTION.
  *----------------------------------------------------------------*

  /----------------------------------------------------------------*
   WORKING-STORAGE SECTION.
  *----------------------------------------------------------------*



   01 proc-ptr usage procedure-pointer.


   01 sqlite3-db         pointer.

   01 err-msg            pointer.
   01 sqlite             pointer.
   01 res                pointer.



   01 rc                 pic 9 comp-5.
   01 dbName             pic x(08).






   01 sqlQuery       pic x(100).

   01 result         pic x(100).
   01 argv.
       03  firstColumn   pointer.
       03  secondColumn  pointer.

   01 azColName          pointer.
   01 argc               pic 99 comp-5.
   01 notused            pointer.

   01 Writefunction-Ptr  procedure-pointer.


   01 PERSON-POST.
       03 NAMN     PIC X(60).
       03 AGE      PIC 9(3).
       03 ADRESS   PIC X(100).
       03 TELNR    PIC X(20).
   01 Column-Id       pic X(3).
   01 Column-Name     pic X(20).



  *-----------------------------------------------------------------
   Linkage Section.





  /-----------------------------------------------------------------
   procedure division.
  *-----------------------------------------------------------------

  *
            set proc-ptr to entry "sqlite3.dll"

            display sqlQuery


            set sqlite3-db to null
            set err-msg    to null
            set res        to null

            move z"test.db" to dbName

            display "Running sqlite3_open"

            call "sqlite3_open" using
                    by reference  z"test.db"
                    by reference  sqlite3-db
                    returning     rc
            end-call


            if rc not = zero
               display "error opening database."

            else
               display "database opened."

            end-if


            move "INSERT INTO tabla VALUES ('020', '8855');"
               to sqlQuery

           initialize Column-Id
           initialize Column-Name





  *
  *
  *
            call "sqlite3_exec" using
               by value sqlite3-db
               by reference sqlQuery
               by value     0
               by value     0
               by reference err-msg
               returning rc
            end-call


          set Writefunction-Ptr to entry "sqlite-callback".

          initialize sqlQuery
          move "SELECT * FROM tabla;" to sqlQuery


          call "sqlite3_exec" using
             by value sqlite3-db
             by reference sqlQuery
             by value Writefunction-Ptr
             by value 0
             by reference err-msg
           returning rc
          end-call
  *
          entry "sqlite-callback" using
             by value notused
             by value argc
             by reference argv
             by reference azColName.

  *    how to get column1
  *    how to get column2


       display Column-Id "|" Column-Name

  *


          call "sqlite3_close" using
                  by reference sqlite3-db
          end-call

          display "sqlite3_close"

    .

  *----------------------------------------------------------------
    stop run.


   Entry-Termination.

Now, open & insert are working fine, but I need to know how to get the records from Select sentence. I need to get several rows and show them.

Community
  • 1
  • 1
  • What exactly "doesn't work"? What compiler and environment do you use? BTW: the second sample won't work as `sq3-dll` is no valid entry. – Simon Sobisch Oct 10 '16 at 13:08
  • Hi Simon, I've just change the question to show how I'm trying to insert a row. I've also changed sq3-dll. I'm using NetExpress. Thank you. – user6948899 Oct 10 '16 at 14:11
  • I see, it is much better now. The entry point is still invalid as it doesn't exist in your program. According to the linked C tutorial this entry would be called on error with a descriptive message, therefore I suggest to chippy the necessary parts from the linked post and compile and run the program and provide the output you see. – Simon Sobisch Oct 10 '16 at 17:52
  • I've also included the 'sqlite3.dll' entry point, I don't know if this the entry point you're talking about. I've also included the output. – user6948899 Oct 11 '16 at 05:44
  • For the entry look at the post you've already linked `ENTRY 'yourname' USING ...`. Please post the new output directly as text as this helps more (you can select the text in the command window and use context-menu->copy). You can use the same entry for all calls, just set a flag (or a text like `MOVE 'SELECT1' TO stuff-to-do) before the actual `CALL` giving you the option to `EVALUATE` and/or `DISPLAY` it. – Simon Sobisch Oct 11 '16 at 07:14
  • Ok, I've changed the code: now there is a entry for connect+insert and other entry for select statement. I've also included the output directly as text. – user6948899 Oct 11 '16 at 08:51
  • Please post your complete program, the current one cannot be compiled. – Simon Sobisch Oct 11 '16 at 11:22
  • In any case you may want to consider using prepared sql statements (especially as this removes the need to escape the data). For a complete COBOL example code see https://sourceforge.net/p/open-cobol/discussion/help/thread/cc255167/#6d89 – Simon Sobisch Oct 11 '16 at 11:43
  • I've included the entire program. Now open & insert are working ok, but I need how to get several records and show them (select sentence). – user6948899 Oct 11 '16 at 12:16
  • When SELECT call is executed, it gets the error message "Recursive COBOL CALL is illegal". – user6948899 Oct 11 '16 at 14:40
  • You can attempt "IS RECURSIVE" on the PROGRM-ID. However, normally a COBOL program is not re-entered without exiting, and a recursive program would be expected to eventually exit for each entry, and I have no clue if it may cause issues for your run-time. Why not ask Micro Focus how to do this? – Bill Woodger Oct 11 '16 at 14:54
  • Despite the hint from Bill: you have an unused `proc-ptr` in (just assigning a not available entry) and "normally" a callback-entry like `sqlite-callback` comes *after* the program end (you only want to execute this if an error occurs) and ends with `goback`. – Simon Sobisch Oct 11 '16 at 20:55
  • Thank you so much Simon and Bill, you were right, I did what you said: - Declare program as recursive. For this, is not possible to declare it as "Recursive" or "is Recursive" on program-id. This is made by including "local-storage section". - I declared de callback entry after the program end, and ended it with "goback". – user6948899 Oct 13 '16 at 11:01

1 Answers1

0

Finally, this is the code to open/insert/select/close in netExpress:

  *
  *----------------------------------------------------------------*
  *                                                                *
  *                                                                *
  *                                                                *
  * SYSTEM                                                         *
  *                                                                *
  * PROGRAM-ID    Pxxxxxx
  *                                                                *
  * AUTHOR                                                         *
  *                                                                *
  * DATE          10/2016                                          *
  *                                                                *
  *                                                                *
  *                                                                *
  *                                                                *
  *----------------------------------------------------------------*
  *                                                                *
  *                                                                *
  *                                                                *
  *----------------------------------------------------------------*
   IDENTIFICATION DIVISION.
   PROGRAM-ID.  Pxxxxx.

   ENVIRONMENT DIVISION.
   CONFIGURATION SECTION.

  /----------------------------------------------------------------*
   INPUT-OUTPUT SECTION.
   FILE-CONTROL.

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



  /----------------------------------------------------------------*
   DATA DIVISION.
   FILE SECTION.
  *----------------------------------------------------------------*

  /----------------------------------------------------------------*
   WORKING-STORAGE SECTION.
  *----------------------------------------------------------------*



   01 proc-ptr usage procedure-pointer.


   01 sqlite3-db         pointer.

   01 err-msg            pointer.
   01 sqlite             pointer.
   01 res                pointer.



   01 rc                 pic 9 comp-5.
   01 dbName             pic x(08).






   01 sqlQuery       pic x(100).

   01 result         pic x(100).
   01 argv.
       03  firstColumn   pointer.
       03  secondColumn  pointer.

   01 azColName          pointer.
   01 argc               pic 99 comp-5.
   01 notused            pointer.

   01 Writefunction-Ptr  procedure-pointer.







  *-----------------------------------------------------------------
   Local-storage Section.
   Linkage Section.
   01 Column-Id       pic X(3).
   01 Column-Name     pic X(20).





  /-----------------------------------------------------------------
   procedure division.
  *-----------------------------------------------------------------

  *
            set proc-ptr to entry "sqlite3.dll"

            display sqlQuery


            set sqlite3-db to null
            set err-msg    to null
            set res        to null

            move z"test.db" to dbName

            display "Running sqlite3_open"

            call "sqlite3_open" using
                    by reference  z"test.db"
                    by reference  sqlite3-db
                    returning     rc
            end-call


            if rc not = zero
               display "error opening database."

            else
               display "database opened."

            end-if


            move "INSERT INTO tabla VALUES ('002', '8855');"
               to sqlQuery
  *
  *
  *
            call "sqlite3_exec" using
               by value sqlite3-db
               by reference sqlQuery
               by value     0
               by value     0
               by reference err-msg
               returning rc
            end-call
  *
         set Writefunction-Ptr to entry "sqlite-callback".

          initialize sqlQuery
          move "SELECT * FROM tabla;" to sqlQuery


          call "sqlite3_exec" using
             by value sqlite3-db
             by reference sqlQuery
             by value Writefunction-Ptr
             by value 0
             by reference err-msg
           returning rc
          end-call

          call "sqlite3_close" using
                  by reference sqlite3-db
          end-call

          display "sqlite3_close"

            .
  * -------------------------------------------------------
   stop run.
         entry "sqlite-callback"
         using
             by value notused
             by value argc
             by reference argv
             by reference azColName.

        set address of Column-Id   to firstColumn
        set address of Column-Name to secondColumn

        display Column-id "|" Column-Name
        goback.
   Entry-Termination.