Walter, many thanks.  We will certainly give this a try.

Jim McAlpine

On Thu, May 21, 2009 at 6:47 PM, Bass, Walter W <bill_b...@uhc.com> wrote:

> Jim McAlpine wrote:
> <snip>
> >
> > Thanks for all the replies and suggestions.  Having spoken again to
> > the developer who originally asked the question,  it seems it is a tad
>
> > more complicated in that he actually wants to do i/o against the file
> > from the REXX program.  The question now becomes, can we call TSO from
>
> > a COBOL program without being authorised.  And to answer Walts
> > suggestion, no we can't have the COBOL program invoked from IKJEFT01
> > as that part of the architecture is carved in stone.
> >
>
> You can call TSO from COBOL without being authorized, you just can't use
> any authorized services.  I do it in a program on the CBT called
> SYMBSUB (file 779).  Basically you just call IKJTSOEV to create the
> TSO environment, then call IKJEFTSR to issue TSO commands.
>
> Here is a code snippet to give you a head start if you wish to pursue
> this further.  This should not necessarily be considered an endorsement
> of using this approach.  It's a pretty big gun to use if your target
> happens to be small.
>
>
>  01 WS-IKJEFT-PARMS.
>      05 WS-IKJEFT-DUMMY          PIC S9(8) COMP-5.
>      05 WS-IKJEFT-RC             PIC S9(8) COMP-5.
>      05 WS-IKJEFT-REASON-CD      PIC S9(8) COMP-5.
>      05 WS-IKJEFT-INFO-CD        PIC S9(8) COMP-5.
>      05 WS-IKJEFT-CPPL-ADDR      PIC S9(8) COMP-5.
>      05 WS-IKJEFT-FLAGS          PIC X(4) VALUE X'00010001'.
>      05 WS-IKJEFT-BUFFER         PIC X(256).
>      05 WS-IKJEFT-LENGTH         PIC S9(8) COMP-5 VALUE ZERO.
> ***************************************************************
> * CREATE TSO ENVIRONMENT
>     CALL 'IKJTSOEV' USING WS-IKJEFT-DUMMY
>                           WS-IKJEFT-RC
>                           WS-IKJEFT-REASON-CD
>                           WS-IKJEFT-INFO-CD
>                           WS-IKJEFT-CPPL-ADDR
>     END-CALL
>
>     IF WS-IKJEFT-RC NOT = ZERO
>        MOVE WS-IKJEFT-RC            TO WS-DISPLAY-RC
>        DISPLAY 'IKJTSOEV FAILED - RC=' WS-DISPLAY-RC
>     END-IF
>
> * ISSUE TSO COMMAND (E.G. ALLOCATE TEMP DATASET)
>     MOVE SPACES                     TO WS-IKJEFT-BUFFER
>     STRING 'ALLOC DD(TEMPDD) '               DELIMITED BY SIZE
>            'DSORG(PS) LRECL(80) BLKSIZE(0) RECFM(F B) '
>                                              DELIMITED BY SIZE
>            'UNIT(SYSDA) SPACE(1,1) TRACKS '  DELIMITED BY SIZE
>            'NEW DELETE'                      DELIMITED BY SIZE
>         INTO WS-IKJEFT-BUFFER
>     END-STRING
>     PERFORM 8000-CALL-TSO                   THRU 8000-EXIT
>
> ***************************************************************
> * IF YOU CODED A SELECT ... ASSIGN TO TEMPDD, THEN YOU COULD
> * CODE COBOL OPEN/WRITE/CLOSE, OPEN/READ/CLOSE, ETC. HERE.
> ***************************************************************
>
> * ISSUE TSO COMMAND (E.G. FREE TEMP DATASET)
>     MOVE 'FREE DD(TEMPDD)'          TO WS-IKJEFT-BUFFER
>     PERFORM 8000-CALL-TSO                   THRU 8000-EXIT
>
> ***************************************************************
>  8000-CALL-TSO.
> ***************************************************************
>     PERFORM VARYING WS-IKJEFT-LENGTH
>       FROM LENGTH OF WS-IKJEFT-BUFFER BY -1
>       UNTIL WS-IKJEFT-LENGTH = 1
>          OR WS-IKJEFT-BUFFER(WS-IKJEFT-LENGTH:1) > SPACES
>     END-PERFORM
>
>     CALL 'IKJEFTSR' USING WS-IKJEFT-FLAGS
>                           WS-IKJEFT-BUFFER
>                           WS-IKJEFT-LENGTH
>                           WS-IKJEFT-RC
>                           WS-IKJEFT-REASON-CD
>                           WS-IKJEFT-DUMMY
>     END-CALL
>
>     IF WS-IKJEFT-RC NOT = ZERO
>        MOVE WS-IKJEFT-RC            TO WS-DISPLAY-RC
>        DISPLAY 'IKJEFTSR FAILED - RC=' WS-DISPLAY-RC
>        MOVE WS-IKJEFT-REASON-CD     TO WS-DISPLAY-RC
>        DISPLAY '         REASON CODE=' WS-DISPLAY-RC
>        DISPLAY 'CMD=<' WS-IKJEFT-BUFFER(1:WS-IKJEFT-LENGTH) '>'
>     END-IF
>     .
>  8000-EXIT. EXIT.
>
> This e-mail, including attachments, may include confidential and/or
> proprietary information, and may be used only by the person or entity
> to which it is addressed. If the reader of this e-mail is not the intended
> recipient or his or her authorized agent, the reader is hereby notified
> that any dissemination, distribution or copying of this e-mail is
> prohibited. If you have received this e-mail in error, please notify the
> sender by replying to this message and delete this e-mail immediately.
>
> ----------------------------------------------------------------------
> For IBM-MAIN subscribe / signoff / archive access instructions,
> send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
> Search the archives at http://bama.ua.edu/archives/ibm-main.html
>

----------------------------------------------------------------------
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html

Reply via email to