Re: MicroFocus Cobol - Oracle

From: Pete Hawdon <peter.hawdon_at_ppa.nhs.uk>
Date: 5 Oct 2001 01:55:37 -0700
Message-ID: <1554f8b1.0110050055.2c8b2114_at_posting.google.com>


"nv" <niko.vervenne_at_pi.be> wrote in message news:<3bb2d526$0$21070$ba620e4c_at_news.skynet.be>...
> Now i'm running Informix standard engine, and i use the informix c-isam
> files with micro focus cobol, on a Alphaserver running Unix 4.0D.
> I'm thinking of migrating to oracle.
> Can i access the tables with standard micro focus cobol? How can i do it ?

OK,

to connect you need to do something like the following: (ARGUMENT-VALUE in this case is the command line argument when running the code and is a username/password string)

01  W50-USER-PASS-INPUT                   PIC X(20).
.

.
.
           ACCEPT W50-USER-PASS-INPUT  FROM ARGUMENT-VALUE.
      
           MOVE   W50-USER-PASS-INPUT TO   W50-USER-PASS-ARR
           
           IF W50-USER-PASS-INPUT(1:1) = "/"
              MOVE 1  TO W50-USER-PASS-LEN
           ELSE
              MOVE 20 TO W50-USER-PASS-LEN
           END-IF.           
          
           EXEC SQL CONNECT :W50-USER-PASS END-EXEC.
    
           EVALUATE SQLCODE
               WHEN 0
                   CONTINUE
               WHEN OTHER
                   GOBACK GIVING 254
           END-EVALUATE.


to do a select on a table then do something like this:

       GET-DETAIL SECTION.
      *---------------------------

           EXEC SQL
             declare my_curs cursor for
              select t1.x, t2.y
                from s_tab1 t1,
                     s_tab2 t2
               where t1.col1 = RTRIM(:W50-MY-ID)
                 and t1.col2 = 'a string'
                 and t1.col3 = t2.col3END-EXEC.
           EXEC SQL
             open my_curs 
           END-EXEC.

           EXEC SQL
             fetch my_curs 
              into :W50-ID1,
                   :W50-ID2
           END-EXEC.

           IF SQLCODE <> 0
              IF SQLCODE = 1403
                 MOVE 136 TO W99-ERROR-TYPE
              END-IF
              EXEC SQL
                 close my_curs 
              END-EXEC

              PERFORM ZA-ABORT
           ELSE
              EXEC SQL
                 close my_curs 
              END-EXEC
           END-IF.
Received on Fri Oct 05 2001 - 10:55:37 CEST

Original text of this message