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

Supra/Total calls

Status
Not open for further replies.

beswar

Programmer
Feb 9, 2005
4
US
Hi

I need some information regarding COBOL-Supra/Total db calls. could you please provide any documenatatiion on how to code supra/Total db call in the COBOL

Thanks
Eswar
 
What are you looking to do? Do you want to call a Total db file and run it through the program? And do you have the structure of the TOTAL file you need to access?

I assume this is a mainframe you are working on.
 
Thanks for your reply. I am looking on how to access total databse using COBOL(similar to access db2 using embeded SQL queries in the cobol)
 
I do not have documentation, but I do have an example of a program reading against the TOTAL db. Here is the meat and bones of the file.

What this example does is links a TOTAL file to another TOTAL file to grab information. If you are just needing to read one TOTAL db file, then you would just use para 830000, where the 'READV' is reading the file sequentially in order. but the concept is the same.

Code:
        01  WS02-TOTAL-AREA.
           03  WS02-MY-TASK                  PIC X(08) VALUE 'TOTAL'.
           03  WS02-TOTAL2-QUAL              PIC X(40) VALUE
               'BEGNSKIPSERIAL'.
           03  WS02-TOTAL1-QUAL              PIC X(4) VALUE
               'BEGN'.
           03  WS02-ENDP                     PIC X(06) VALUE 'END.'.
           03  WS02-UPD-FILE-LIST.
             05  WS02-TOTAL1                 PIC X(04) VALUE 'TOTAL1'.
             05  FILLER                      PIC X(09) VALUE
                 'READ****,'.
             05  WS02-TOTAL2                 PIC X(04) VALUE 'TOTAL2'.
             05  FILLER                      PIC X(09) VALUE
                 'SUPD****,'.
             05  FILLER                      PIC X(04) VALUE 'END.'.
      *
       01  WS03-DB.
           03  WS03-DB-ELEM.
               05  FILLER                      PIC X(04) VALUE 'END.'.
           03  WS03-DB-WORK.
              05  WS03-DB-CTRL              PIC X(24).
      *
       01 WS04-DB.
          03 WS04-DB-ELEM.
             05 FILLER                 PIC X(08) VALUE 'TOTAL2CODE'.
             05 FILLER                 PIC X(08) VALUE 'TOTAL2NAME'.
             05 FILLER                 PIC X(04) VALUE 'END.'.
          03 WS04-DB-WORK.
             05 WS04-DB-CODE         PIC X(02).
             05 WS04-DB-NAME         PIC X(24).
             
 
      *********************************************************
      * READ NEXT TO.TOTAL1 RECORD
      *********************************************************
       800000-RDNXT-TOTAL1.

           MOVE WS02-TOTAL1-QUAL TO   TOTAL-QUAL.
           MOVE 'RDNXT'          TO   TOTAL-FUNCT.
           MOVE WS02-ENDP        TO   TOTAL-ENDP.
           MOVE WS02-TOTAL1      TO   TOTAL-DSET.
           MOVE WS03-DB-ELEM TO   TOTAL-ELEM.
           PERFORM DATBAS10 THRU DATBAS10-X.
      D    DISPLAY "AFTER DB CALL".
      D    DISPLAY "TOTAL-STAT  "  TOTAL-STAT.
           IF TOTAL-STAT EQUAL TO 'END.'
              MOVE 'YES' TO WS05-TOTAL1-EOF
           ELSE
              MOVE TOTAL-QUAL TO WS02-TOTAL1-QUAL
              MOVE TOTAL-WORK TO WS03-DB-WORK
      D       DISPLAY ' WS03-DB-CTRL ' WS03-DB-CTRL
              ADD 1 TO WS07-TOTAL1-READ.
              MOVE 'Y' TO WS05-NEW-TOTAL1-FLAG.

       800000-EXIT.
           EXIT.

      *********************************************************
      * READING NEXT RECORD FROM TO.TOTAL2 FILE
      *********************************************************
       830000-READV-TOTAL2.

           MOVE WS02-TOTAL2-QUAL TO   TOTAL-QUAL.
           MOVE 'READV'        TO   TOTAL-FUNCT.
           MOVE WS02-ENDP      TO   TOTAL-ENDP.
           MOVE WS02-TOTAL2      TO   TOTAL-DSET.
           MOVE WS04-DB-ELEM TO   TOTAL-ELEM.
           MOVE WS03-DB-CTRL TO   TOTAL-KEY.
           MOVE 'TOTAL1LKAP'     TO   TOTAL-LINK.
           PERFORM DATBAS09 THRU DATBAS09-X.
           IF TOTAL-REFER EQUAL TO 'END.'
              MOVE SPACES TO WS10-CURR-TOTAL2
              GO TO 830000-EXIT
           ELSE
              MOVE TOTAL-WORK TO WS04-DB-WORK
              ADD 1 TO WS07-TOTAL2-READ
           END-IF.



       830000-EXIT.
           EXIT.

 
Don't we need to see

DATBAS09 THRU DATBAS09-X

to understand the actual DB access?

Bill Klein
 
Kind of hard to explain without knowing exactly what is being retrieved.

Here is the rest of the code:

Code:
DATBAS09 SECTION.
      IF TOTAL-VEDS-FUNC
          PERFORM DATBAS9 THRU DATBAS9-X
      ELSE
          MOVE 'FTYP'            TO TOTAL-STAT
          PERFORM STATANAL-NOSV  THRU STATANAL-NOSV-X
          PERFORM STATANAL-ABEND THRU STATANAL-ABEND-X.
 DATBAS09-X.
     EXIT.

 DATBAS9.
    IF TOTAL-ACCESS EQUAL TO 'RDONLY'
        MOVE 'RLSE'  TO TOTAL-ENDP.
    CALL 'DATBAS' USING TOTAL-FUNCT
                        TOTAL-STAT
                        TOTAL-DSET
                        TOTAL-REFER
                        TOTAL-LINK
                        TOTAL-KEY
                        TOTAL-ELEM
                        TOTAL-WORK
                        TOTAL-ENDP.
    PERFORM STATANAL THRU STATANAL-X.
 DATBAS9-X.
    EXIT.

where the call to DATBAS is equivalant to selecting * from the TOTAL file.
 
Thanks for your information. It is very useful for me.

Thanks
Eswar
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top