MVSFORUMS.com Forum Index MVSFORUMS.com
A Community of and for MVS Professionals
 
 FAQFAQ   SearchSearch   Quick Manuals   RegisterRegister 
 ProfileProfile   Log in to check your private messagesLog in to check your private messages   Log inLog in 

Invoking a REXX program from JCL
Goto page Previous  1, 2, 3
 
Post new topic   Reply to topic   printer-friendly view    MVSFORUMS.com Forum Index -> TSO and ISPF
View previous topic :: View next topic  
Author Message
Phantom
Data Mgmt Moderator
Data Mgmt Moderator


Joined: 07 Jan 2003
Posts: 1056
Topics: 91
Location: The Blue Planet

PostPosted: Thu May 15, 2003 10:49 pm    Post subject: Reply with quote

Well, is there any way to get around this problem ?

Thanks,
Back to top
View user's profile Send private message
semigeezer
Supermod


Joined: 03 Jan 2003
Posts: 1014
Topics: 13
Location: Atlantis

PostPosted: Fri May 16, 2003 12:38 am    Post subject: Reply with quote

OK. I'm confused... that is to say, I can't reproduce this with a simple testcase.
If my TSO session has PROF INT WTP and I submit

       //USERIDA JOB ...
       //BATCH    EXEC PGM=IKJEFT01,DYNAMNBR=128
       //SYSTSPRT DD SYSOUT=*
       //SYSTSIN  DD *
       SUB 'HLQ.CNTL(IEBGENER)'
       /*

I don't get a message at my terminal that the 2nd job was submitted. I just get the Notify message when the second job ends. What am I missing?

Assuming I am missing something major, which would be no big surprise, you could just avoid the SUBMIT command altogether and just write the JCL directly to the 'internal reader'. Basic JCL for that is:

       //* SEND AN INLINE JOB TO THE INTERNAL READER
       //GENER1   EXEC PGM=IEBGENER
       //SYSPRINT DD  SYSOUT=*
       //SYSUT1   DD  DATA,DLM=99
       //USERIDB JOB ...
       //IEFBR14  EXEC PGM=IEFBR14
       99
       //SYSUT2   DD  SYSOUT=(A,INTRDR)
       //SYSIN    DD  DUMMY

but you can do it from a program by allocating the internal reader to a ddname and writing to that.


Last edited by semigeezer on Sun Oct 09, 2005 9:48 pm; edited 1 time in total
Back to top
View user's profile Send private message Visit poster's website
Phantom
Data Mgmt Moderator
Data Mgmt Moderator


Joined: 07 Jan 2003
Posts: 1056
Topics: 91
Location: The Blue Planet

PostPosted: Fri May 16, 2003 1:17 am    Post subject: Reply with quote

Semigeezer,

I feel very sorry to say this, but really speaking I don't understand what you have suggested. Let me try to explain my situation.

I already have a big JCL which requires a file which is available only in PRODPLEX. One way is to manually NDM the file from PRODPLEX and run the JCL (JCL should run only in TESTPLEX). But, I wanted to automate this stuff.

I had another JCL which NDMs the file from PROD to TEST but that JCL can run only in PRODPLEX. Instead I used JOBPARM SYSAFF=333C and tried to submit the JCL from test. It works fine.

Now, I need to put everything together. As far as I know, JOBPARM SYSAFF cannot be specified for a particular step alone. So I wrote a REXX program which inturn submits the NDM Jcl and also wait untils the file gets copied to testplex. Then this file is used in the subsequent steps of the first JCL as input.
This is the scenario. I wanted to the whole process without any user interaction until the job completes. But Once the NDM jcl is submitted I receive a submitted message and also another message saying that the JCL is transferred to PRODPLEX. I want to stop this messages from being displayed.

I haven't yet tried ur suggestion. Still, If you submit a JCL from another JCL, will the first jcl wait until the submitted (second) JCL completes ??? This is my question. Because the next step in JCL1 requires the input file, But it takes some finite time for the file to be transferred from PROD to TEST even if it is a small one.

Please correct me if I'm wrong at any point. If you have a better solution for my problem, please advice me. It would be of real help.
Back to top
View user's profile Send private message
Mike
Beginner


Joined: 03 Dec 2002
Posts: 114
Topics: 0
Location: Sydney, Australia

PostPosted: Sun May 18, 2003 7:13 pm    Post subject: Reply with quote

Phantom,
no the first job will not wait for the second to complete unless you code this within a program. If the submit message is a problem as well then I'd go for some code along the lines of :-

Code:

"ALLOC F(JOBSUB) SYSOUT(A) WRITER(INTRDR) RECFM(F) LRECL(80)"
"EXECIO * DISKW JOBSUB (STEM myjob. FINIS"
Do Forever
  If SYSDSN(xfrdsn) = "OK" Then leave
   x = REXXWAIT("F00:01:00.00")
End
Say "Dataset has been transferred"


Where the JCL has been built into the variables myjob.1, myjob.2 ........
xfrdsn is the variable that contains the dataset name of the dataset to be received.
REXXWAIT is a program that will wait for a specified amount of time without wasting CPU (I can provide this program or there are alternative programs).
Using the Internal reader gets around the notifcation problem.

Actually I wouldn't do it this way, if the transfer failed, you'd wait forever. I'd actually have the NDM process submit a job upon the completion of the process (this should occur even if the transfer failed) which creates a dataset used to indicate the completion of the NDM process. You'd then possibly want to determine whether or not the transfer worked. You could then check for the existence of the transferred dataset to do this.

You get NDM to submit a job by using a second step in the NDM process e.g. :-

Code:

S2 RUN JOB(DSN=YOUR.JCL(NDMDONE))


One other point, is that you appear to be submitting a job from the TESTPLEX, to the PRODPLEX to invoke an NDM send of a dataset from PRODPLEX to TESTPLEX. I think that you could simplify the process if you used the NDM on TESTPLEX to receive the dataset (it may be that the NDM subsystem on TESTPLEX will not allow this but that's how I do things here).
_________________
Regards,
Mike.
Back to top
View user's profile Send private message
Phantom
Data Mgmt Moderator
Data Mgmt Moderator


Joined: 07 Jan 2003
Posts: 1056
Topics: 91
Location: The Blue Planet

PostPosted: Sun May 18, 2003 11:26 pm    Post subject: Reply with quote

Mike,

Thanks for your suggestions. I see that, semigeezer had given me a similiar or infact same solution but through JCL. I would try your suggestions and let you know. I need to get more details regarding Internal readers. I would appreciate any help from you all regarding this.


I also would like to know more about REXXWAIT. Can you please post the code. As you can find in my earlier posts, I had used
Code:

ADDRESS SYSCALL 'SLEEP 2'                                       


Frankly speaking, I don't know anything about SYSCALL command. I found it some posts in mvsforums and tried it and it worked fine. Do you have any idea about this and I would be interested in knowing which command is better or best as far as the usage of CPU is concerned. You have also said about some alternative programs. Can you please list them too.

Last one. As you have said, I had already tried to submit a NDM to receive the dataset from TESTPLEX. Unfortunately, I didn't work for me. Also, I'm not sure whether this is because of some errors in my code. I would appreciate if you could post the NDM PROCESS you used to receive a file from testplex.

Thanks all,
Back to top
View user's profile Send private message
Mike
Beginner


Joined: 03 Dec 2002
Posts: 114
Topics: 0
Location: Sydney, Australia

PostPosted: Mon May 19, 2003 9:09 pm    Post subject: Reply with quote

Phantom,

regarding internal readers there's nothing that special about them, they are, as far as I'm aware, just a special writer (printer) that instead of printing the ouput passes the output to JES. Basically when you use the SUBMIT command it wil be passing the data to the internal reader. What you might have to check is whether your site standards allow their use (probably not for production jobs).

Regarding the SYSCALL command if it works then it's probably no worse or better then the REXXWAIT routine, however you've got it installed. Basically things like this simply call the STIMER MACRO with the appropriate parameter. The one I've written just has a Rexx interface, which isn't necessary. The main thing iin using such a utility is that it avoids using a loop that will clock an impressive (or not depending upon your viewpint Smile) amount of CPU. I'll include the code for REXXWAIT at the end as it's quite long.

Regarding the NDM PROC here it is :-
Code:

MJTNDMD PROCESS SNODE=PPRD HOLD=YES                                     
S1 COPY FROM (SNODE DSN=&DSN1) TO (PNODE DSN=&DSN2 DISP=(,CATLG))       
S2 RUN JOB (DSN=&JCLLIB) PNODE                                         


PPRD is the equivalent of your PRDPLEX as the transfer is being initiated from PDEV (equivalent to TESTPLEX) there is no need for this to be encoded. Using PNODE (I thinks it stands for processing NODE, if not then I'm sure that someone will enlighten us) does this.

Obviously you need to pass three parameters when invoking the PROC e.g. :-
SUB PROC=MJTNDMD &&DSN1=MY.PROD.DSET &&DSN2=MY.TEST.DSET &JCLLIB=MY.JCLLIB(NDMDONE)

You may not want the second step, and therefore the line starting with S2 and the JCLLIB parameter, would not be required, although, as I said previously, this is probably a better method (not 100% though, only this morning I had to intervene because a process did not complete SVTM104I [The session with the adjacent mode has been lost]).

Well here's the code for REXXWAIT (actually there's code for two programs REXXWAIT and WAITCON, the latter is attached as a subtask, to get around S522's).

REXXWAIT
Code:

         TITLE 'REXXWAIT - REXX CALLABLE WAIT ROUTINE'                 
*=====================================================================*
*                                                                     *
*  OPERATIONS MANAGEMENT REXX WAIT ROUTINE                            *
*  =======================================                            *
*                                                                     *
*  FUNCTION : WAIT FOR A SEPECIFIED AMOUNT OF TIME OR WAIT UNTIL A    *
*             SPECIFIED TIME. THE TYPE OF WAIT IS DETERMINED BY THE   *
*             PARAMETER.                                              *
*             THE FIRST CHARACTER OF THE PARAMETER IS THE TYPE OF     *
*             WAIT. IF IT IS F THEN THE WAIT IS FOR A TIME. IF IT IS  *
*             U THEN THE WAIT IS UNTIL THE SPECIFIED TIME.            *
*             THE NEXT 11 CHARACTERS SPECIFY THE TIME TO WAIT IN THE  *
*             FORMAT HH:MM:SS.TH (HH=HOURS MM=MINUTES SS=SECONDS      *
*             T=TENTHS OF A SECOND H=HUNDREDTHS OF A SECOND)          *
*             E.G. TO WAIT FOR TEN SECONDS THEN THE PARAMETER SHOULD  *
*             BE F00:00:10.00                                         *
*             E.G. TO WAIT UNTIL 10 O'CLOCK THEN THE PARAMETER SHOULD *
*             BE U10:00:00.00                                         *
*                                                                     *
* EXAMPLE :   X = REXXWAIT('F00:10:00.00')                            *
*                                                                     *
*             THE ABOVE EXAMPLE WILL WAIT FOR A PERIOD OF 10 MINUTES  *
*                                                                     *
*                                                                     *
*             -***- NOTE THIS IS WRITTEN AS A REXX FUNCTION AND MUST  *
*                   ONLY BE INVOKED FROM REXX.                        *
*                                                                     *
*  AUTHOR   : M.TYALOR                                                *
*  DATE     : 11/14/96                                                *
*                                                                     *
*=====================================================================*
         PRINT NOGEN                                                   
         EJECT                                                         
ALOFFSET EQU   16                                                       
EBOFFSET EQU   20                                                       
REXXWAIT INIT  REGNUM=5                                                 
         ST    0,ENVBLK00              SAVE THE ENVIRONMENT BLOCK ADDR 
         ST    1,EFPL00                SAVE THE EFPL ADDRESS           
         L     2,ALOFFSET(1)           ADDRESS OF ARGUMENT LIST         
         ST    2,ARGLST00              SAVE IT                         
         L     3,EBOFFSET(1)           ADDRESS OF THE EVALUATION BLOCK 
         ST    3,EVLBLK00              SAVE IT                         
*---------------------------------------------------------------------*
* CALCULATE THE NUMBER OF ARGUMENTS PASSED TO ROUTINE                 *
*---------------------------------------------------------------------*
CALCARGN L     2,ARGLST00              GET THE ARG LIST ADDRESS         
         SR    3,3                     0 ARGUMENTS                     
CA_001   CLC   ARGEND(8),0(2)          END OF ARG LIST ?               
         BE    CA_999                  YES THEN FINISH                 
         LA    2,8(2)                  NEXT ENTRY                       
         LA    3,1(3)                  INCREMENT COUNT                 
         B     CA_001                                                   
CA_999   ST    3,ARGNUM00              STORE ARGUMNET COUNT             
         C     3,ARGNUM                ONLY 1 WANTED                   
         BE    PCNTOK                  OK                               
ERRRET   L     13,4(13)                INVALID LENGTH                 
         RETURN (14,12),RC=8                                           
ERRRET_2 L     13,4(13)                INVALID SEPRATOR               
         RETURN (14,12),RC=9                                           
ERRRET_3 L     13,4(13)                INVALID TYPE                   
         RETURN (14,12),RC=10                                         
ERRRET_4 L     13,4(13)                NON NUMERIC FIELD               
         RETURN (14,12),RC=11                                         
*---------------------------------------------------------------------*
* MAKE SURE THE LENGTH OF THE PARAMETER IS OK                         *
*---------------------------------------------------------------------*
PCNTOK   L     2,ARGLST00              GET ARGUMENT LIST ADDRESS       
         L     3,0(2)                  GET THE ADDRESS OF THE PARAMETER
         L     4,4(2)                  GET THE LENGTH OF THE PARAMETER
         C     4,MINLEN                MUST BE 2 OR GREATER           
         BL    ERRRET                  WHOOPS                         
         C     4,MAXLEN                MUST BE 16 OR LESS             
         BH    ERRRET                  WHOOPS                         
*---------------------------------------------------------------------*
* CHECK THE PARAMETER FOR VALIDITY                                    *
*---------------------------------------------------------------------*
CHK_2_00 CLC   3(1,3),TSEP             CHECK 4TH CHARACTER IS :       
         BNE   ERRRET_2                                               
         CLC   6(1,3),TSEP             CHECK 7TH CHARACTER IS :       
         BNE   ERRRET_2                                               
         CLC   9(1,3),SSEP             CHECK 10TH CHARACTER IS .       
         BNE   ERRRET_2                                               
         CLC   0(1,3),TYPFOR           IS TYPE F ?                     
         BE    CHK_3_00                YES THEN SKIP TO NUMERIC CHECK 
         CLC   0(1,3),TYPUNTIL         IS TYPE U ?                     
         BNE   ERRRET_3                NO THEN TYPE IS INVALID         
*---------------------------------------------------------------------*
* CHECK THAT THE NUMERIC FIELDS ARE NUMERIC                           *
*---------------------------------------------------------------------*
CHK_3_00 CLC   1(2,3),CHAR00           CHECK THE HOUR                 
         BL    ERRRET_4                                               
         CLC   1(2,3),CHAR23                                           
         BH    ERRRET_4                                               
         CLC   4(2,3),CHAR00           CHECK THE MINUTES               
         BL    ERRRET_4                                               
         CLC   4(2,3),CHAR59                                           
         BH    ERRRET_4                                               
         CLC   7(2,3),CHAR00           CHECK THE SECONDS               
         BL    ERRRET_4                                               
         CLC   7(2,3),CHAR59                                           
         BH    ERRRET_4                                               
         CLC   10(2,3),CHAR00          CHECK THE TENTHS & HUNDREDTHS   
         BL    ERRRET_4                                               
         CLC   10(2,3),CHAR99                                         
         BH    ERRRET_4                                               
*---------------------------------------------------------------------*
* READY THE VALUES FOR THE STIMER INVOCATION                          *
*---------------------------------------------------------------------*
MVE_TIME MVC   HOURS(2),1(3)           STORE THE HOURS                 
         MVC   MINUTES(2),4(3)         STORE THE MINUTES               
         MVC   SECONDS(2),7(3)         STORE THE SECONDS               
         MVC   TENTHS(1),10(3)         STORE THE TENTHS               
         MVC   HUNDREDS(1),11(3)       STORE THE HUNDREDTHS           
         ST    3,REG3STR               STORE REGISTER 3               
*---------------------------------------------------------------------*
* ATTACH THE SUBTASK WAITCON SO THAT THE PROCESS DOES NOT TIMEOUT     *
*---------------------------------------------------------------------*
ATTACH   ATTACH EP=WAITCON             HAVE SUBTASK SO THAT NO TIMEOUT
         ST    1,TASKCB                                               
*---------------------------------------------------------------------*
* CALL THE RESPECTIVE STIMER                                          *
*---------------------------------------------------------------------*
         L     3,REG3STR               RESTORE REGISTER 3             
         CLC   0(1,3),TYPUNTIL                                         
         BE    W_UNTIL                                                 
W_FOR    STIMER WAIT,DINTVL=ALARMT,ERRET=STOP_TSK                     
         B     STOP_TSK                                               
W_UNTIL  STIMER WAIT,TOD=ALARMT,ERRET=STOP_TSK                         
*---------------------------------------------------------------------*
* RETURN                                                              *
*---------------------------------------------------------------------*
STOP_TSK L     1,TASKCB                                               
         DETACH TASKCB                                                 
RET_PRM  LA    1,RETPLIST              ADDRESS OF PARAMETER LIST       
         LINK  EP=IRXRLT               CALL GET RESULT ROUTINE         
         L     2,RPARM2                GET EVAL BLOCK ADDRESS         
         MVC   16(1,2),RETPARM                                         
         LA    3,1                                                     
         ST    3,8(2)                                                 
PGM_END  FINISH                                                       
         EJECT                                                         
TASKCB   DS    1F                                                     
REG3STR  DS    1F                                                     
*---------------------------------------------------------------------*
* REXX ENVIRONMENT STORAGE AREAS                                      *
*---------------------------------------------------------------------*
ENVBLK00 DS    1F                      REXX ENVIRONMENT BLOCK ADDRESS 
EFPL00   DS    1F                      REXX EXTERNAL FUNCTION PARAMETER
*                                      LIST ADDRESS                   
ARGLST00 DS    1F                                                     
ARGNUM00 DS    1F                      NUMBER OF ARGUMENTS             
EVLBLK00 DS    1F                      EVALUTION BLOCK                 
ARGEND   DC    X'FFFFFFFFFFFFFFFF'     END OF ARGUMENT ADDRESS         
ARGNUM   DC    1F'1'                                                   
MINLEN   DC    1F'12'                                                   
MAXLEN   DC    1F'12'                                                   
CHAR00   DC    CL2'00'                                                 
CHAR23   DC    CL2'23'                                                 
CHAR59   DC    CL2'59'                                                 
CHAR99   DC    CL2'99'                                                 
TYPUNTIL DC    CL1'U'                                                   
TYPFOR   DC    CL1'F'                                                   
SSEP     DC    CL1'.'                                                   
TSEP     DC    CL1':'                                                   
ALARMT   DS    0CL8                                                     
HOURS    DS    CL2                                                     
MINUTES  DS    CL2                                                     
SECONDS  DS    CL2                                                     
TENTHS   DS    CL1                                                     
HUNDREDS DS    CL1                                                     
RETPLIST DS    0D                      PARAMETER LIST FOR IRXRLT CALL   
         DC    A(RPARM1)               ADDRESS OF CALL TYPE (GETBLOCK) 
         DC    A(RPARM2)               ADDRESS OF EVAL BLOCK ADDRESS   
         DC    X'80'                   END OF PARAMETER LIST           
         DC    AL3(RPARM3)             ADDRESS OF PARAMETER LENGTH     
RPARM1   DC    CL8'GETBLOCK'           CALL TYPE                       
RPARM2   DS    A                       ADDRESS OF EVAL BLOCK           
RPARM3   DC    F'1'                    LENGTH OF RETURN PARAMETER       
RETPARM  DS    0D                      RETURN PARAMETER                 
APPL_ID  DC    CL1'Z'                                                   
         EJECT                                                         
         END                                                           


WAITCON (don't run this on it's own)
Code:

         TITLE 'CONTINUAL WAIT'                                         
         PRINT NOGEN                                                   
WAITCON  CSECT                                                         
*----------------------------------------------------------------------
*                                                                       
*          THIS PROGRAM SHOULD ONLY BE USED AS A SUBTASK. THE FUNCTION 
*        OF THIS PROGRAM IS TO LOOP ONCE FOR A SET PERIOD AS DETERMINED
*        BY DOUBLEWORD AT ADDRESS ALARMT. THEREFORE IT CAN BE USED TO   
*        ENSURE THAT THE OWNING TASK WILL NOT FAIL WITH A 522. THE     
*        PROGRAM WILL USE HARDLY ANY CPU AND COULD THEREFORE PROBABLY   
*        RUN FOR A SUBSTANTIAL TIME BEFORE ABENDING WITH A 322.         
*                                                                       
*----------------------------------------------------------------------
         EJECT                                                         
*----------------------------------------------------------------------
*        CREATE SAVE AREA FOR RETURN TO CONTROL PROGRAM                 
*----------------------------------------------------------------------
         SPACE 1                                                       
         SAVE  (14,12)                      SAVE REGISTERS             
         BALR  12,0                         LOAD R12 WITH CURRENT ADDR
         USING *,12                         USE R12 AS BASE REGISTER   
         ST    13,SAVEAREA+4                STORE R13 AT SAVEAREA + 4 
         LR    9,13                         R9=R13                     
         LA    13,SAVEAREA                  R13=SAVEAREA ADDR         
         ST    13,8(9)                      STORE SAVE AREA FOR COMP   
         EJECT                                                         
*----------------------------------------------------------------------
*        OPTIONS                                                       
*----------------------------------------------------------------------
         SPACE 1                                                       
DINTVL   STIMER WAIT,DINTVL=ALARMT,ERRET=TERROR                       
         B     DINTVL                                                 
         EJECT                                                         
FINOK    L     13,4(13)                                               
         RETURN (14,12),RC=0                                           
TERROR   WTO   '-*****- ERROR DETECTED IN SYSTEM CLOCK',ROUTCDE=1     
         L     13,4(13)                                               
         RETURN (14,12),RC=2001                                         
*----------------------------------------------------------------------
*        STORAGE AREA                                                   
*----------------------------------------------------------------------
         SPACE 1                                                       
SAVEAREA DS    18F                                                     
ALARMT   DS    0CL8                                                     
HOURS    DC    CL2'00'                       HOURS                     
MINUTES  DC    CL2'00'                       MINUTES                   
SECONDS  DC    CL2'10'                       SECONDS                   
TENTHS   DC    CL1'0'                        TENTHS                     
HUNDREDS DC    CL1'0'                        HUNDREDTHS                 
BUFFER1  DS    CL80                                                     
         END                                                           


I've got some non system macros in the code called INIT & FINISH, you'd have to place these into a library allocated to SYSLIB with member names the same as the macro name (or you can imbed the macros in the source, something which I don't do).

INIT
Code:

         MACRO                                                         
&CSECT   INIT  &REGNUM=1                                               
         AIF   (&REGNUM GT 5).MAXREG   MAXIMUM OF 5 BASE REGISTERS     
         LCLA  &BREG,&PREG,&CNT1,&CNT2                                 
         LCLC  &BLIST                                                   
&BLIST   SETC  '*,12'                                                   
&BREG    SETA  12                      STARTING BASE REGISTER           
&CNT1    SETA  &REGNUM                 SAVE NUMBER OF REGISTERS         
&CNT2    SETA  &REGNUM                                                 
&CSECT   CSECT                                                         
         SAVE  (14,12)                 SAVE REGISTERS                   
         BALR  12,0                                                     
.NXTLST  ANOP                                                           
&BREG    SETA  &BREG-1                                                 
&CNT2    SETA  &CNT2-1                                                 
         AIF   (&CNT2 EQ 0).LSTDONE                                     
&BLIST   SETC  '&BLIST,&BREG'                                           
         AGO   .NXTLST                                                 
.LSTDONE USING &BLIST                                                   
&BREG    SETA  12                      STARTING BASE REGISTER           
.NXTREG  ANOP                                                           
&PREG    SETA  &BREG                   PREVIOUS REGISTER               
&CNT1    SETA  &CNT1-1                 DECREMENT NUMBER OF REGISTERS   
&BREG    SETA  &BREG-1                 DECREMENT CURRENT REGISTER       
         AIF   (&CNT1 EQ 0).DOUSING    END IF NO MORE TO DO             
         LA    &BREG,4095(&PREG)                                       
         LA    &BREG,1(&BREG)                                           
         AGO   .NXTREG                 GO AND DO NEXT REGISTER         
.DOUSING ANOP                                                           
         B     SMAIN                                                   
SAVEAREA DS    18F                                                     
COMPDATE DC    C'&SYSDATE.'                                             
COMPTIME DC    C'&SYSTIME.'                                             
         DS    0F                                                       
SMAIN    ST    13,SAVEAREA+4                                           
         LR    9,13                                                     
         LA    13,SAVEAREA                                             
         ST    13,8(9)                                                 
         AGO   .ENDBASE                                                 
.MAXREG  MNOTE 8,'&REGNUM BASE REGISTERS SPECIFIED ONLY 5 ALLOWED'     
.ENDBASE MEXIT                                                         
         MEND                                                           


FINISH
Code:

         MACRO                                                         
&LABEL   FINISH &RC=0                                                   
&LABEL   L     13,4(13)                                                 
         RETURN (14,12),RC=&RC                                         
         MEND                                                           

_________________
Regards,
Mike.
Back to top
View user's profile Send private message
Phantom
Data Mgmt Moderator
Data Mgmt Moderator


Joined: 07 Jan 2003
Posts: 1056
Topics: 91
Location: The Blue Planet

PostPosted: Tue May 20, 2003 4:52 am    Post subject: Reply with quote

Thanks Mike.

I tried your suggestion of using internal readers. I have one more question in that. Now, I'm not receiving the Job Submitted message. Still, I receive 2 messages. 1. a message that says that the Job has been transferred to the PROD region. (Since I have used JOBPARM SYSAFF=333C) and another message, once the job completes in PRODPLEX. I'm not sure whether these 2 messages can be stopped by removing the NOTIFY parameter in JOB Card. Well, I haven't yet tried it. Can it be stopped by removing the NOTIFY parameter ?


My next question is regarding the NDM process. Moderators... I start to feel that this thread is breaking into a new discussion. But still for continuity I would like it this way. I hope you wont' mind this.

Mike, as far as I know, in the NDM Process, PNODE Stands for Primary node and SNODE for secondary node. Now, whenever we NDM a file using a process similar to what you have shown, the received file gets created in Scratch. I just tried to fancy my chances by writing a NDM process in my own library with DCB Paremeter overrides. But It failed just as I had expected. Have you ever created a new NDM Process? Can we ever create one ? and If yes how ? In our shop we have a process similar to what you have given us but without the S2 step. Now If I want to use your process. How do I do it ?
Back to top
View user's profile Send private message
Mike
Beginner


Joined: 03 Dec 2002
Posts: 114
Topics: 0
Location: Sydney, Australia

PostPosted: Tue May 20, 2003 8:08 pm    Post subject: Reply with quote

Phantom,
regarding the messages, I'm pretty sure that at least the second message is dependant upon the NOTIFY, no too sure about the first. But try removing the NOTIFY. You could try XEQ (e.g. /*XEQ jesnode) which is what I perefer to use.

Regarding NDM processes, yes I have created my own, in fact the one that I sent was created specifically for the work we do in our team (we create and populate testing environments for UAT testing). Basically when you invoke DMBATCH the process name being used must be a member in the dataset(s) allocated to the DDNAME DMPUBLIB.

Here's some JCL that creates a temporary PDS (CRTDS step), populates the appropriate member (MITICT) with the NDM process called MITICT (CPYPDS step) and then performs the transfer via the NDMBATCH program (STEP001 step). This example is pretty old and is run (via XEQ) on the PPRD system. from the more recent process I sent yesterday, you can see that we now use the recipient system as the PNODE. and therefore use COPY FROM(SNODE .......)

Code:

//DMI021ND JOB (U,NM),'MIT NDM JOB',CLASS=2,MSGCLASS=Q,TIME=180         
/*XEQ PPRD                                                             
//*------------------------------------------------------------------- 
//CRTPDS  EXEC PGM=IEFBR14                                             
//CRT01    DD DSN=&&PDS,DISP=(,PASS),UNIT=SYSDA,SPACE=(CYL,(1,1,1)),   
//            DCB=TS99G.TSC.NDMPROCS                                   
//*------------------------------------------------------------------- 
//CPYPDS  EXEC PGM=IEBGENER                                             
//SYSUT1   DD DATA,DLM='{{'                                             
MITICT   PROCESS  PNODE=&PNODE SNODE=&SNODE                             
 COPY FROM(PNODE DSN=DMI021.USER.JCL) -                                 
      TO (SNODE DSN=DMI021.FROMPPRD.JCL -                               
      DISP=(,CATLG))                                                   
{{                                                                     
//SYSUT2   DD DSN=&&PDS(MITICT),DISP=(SHR,PASS)                         
//SYSPRINT DD SYSOUT=*                                                 
//SYSIN    DD DUMMY                                                     
//*------------------------------------------------------------------- 
//STEP001 EXEC PGM=DMBATCH,REGION=0M                                   
//DMNETMAP DD  DSN=SYSS.NDM.NETMAP,DISP=SHR                             
//DMPUBLIB DD DSN=&&PDS,DISP=(SHR,DELETE)                               
//DMMSGFIL DD  DSN=SYSS.NDM.MSG,DISP=SHR                               
//DMPRINT  DD  SYSOUT=*                                                 
//SYSIN    DD  *                                                       
    SIGNON                                                             
    SUBMIT PROC=MITICT &PNODE=PPRD &SNODE=PDEV                         
    SIGNOFF                                                             
/*                                                                     


Note In the above example the only available process will be MITICT
_________________
Regards,
Mike.
Back to top
View user's profile Send private message
Phantom
Data Mgmt Moderator
Data Mgmt Moderator


Joined: 07 Jan 2003
Posts: 1056
Topics: 91
Location: The Blue Planet

PostPosted: Thu May 22, 2003 4:04 am    Post subject: Reply with quote

Hi Mike,

Thanks for all your help. Everything is working fine now.

Regarding the NOTIFY parameter. I tried to invoke the JCL without the NOTIFY parameter, This time I received no messages (JCL Transfer message, as well as the JCL completion notification message). I get the same response even if I manually turn off INTERCOM (ie. PROFILE NOINTERCOM) and then directly run the JCL. But I don't know why this doesnot happen when I issue the PROFILE NOINTERCOM command in the REXX routine which invokes the JCL.

Now, regarding the NDM Process. I created a new NDM process, following your suggestions with all the parameters that I wanted to have and It worked absolutely fine.

Here is the NDM process that I Created.
Code:

NDMTEST PROCESS PNODE=&PNODE  SNODE=&SNODE                       
&NAME     COPY   FROM(SNODE DSN=&DSN1 DISP=SHR) -                 
              TO(PNODE DSN=&DSN2 DISP=SHR        -               
              DCB=(DSORG=PS,RECFM=FB,LRECL=&LRECL, -             
              BLKSIZE=&BLKSIZE)                    -             
              DISP=(NEW,CATLG,DELETE)            -               
              SPACE=(&SPUNITS,(&PRIM,1),RLSE)    -               
              STORCLAS=&STORCLAS                 -               
              UNIT=SYSDA)                        -               
              CKPT=&CKPTVAL                                       
          IF (&NAME EQ 0) THEN                                   
&NAME1    RUN JOB (DSN=T.CRD.A427541.TEST.SOURCE(COMPILE)) PNODE 
          EIF                                                     


Thanks to everyone who helped me resolve my issues.

Thanks,
Back to top
View user's profile Send private message
Mike
Beginner


Joined: 03 Dec 2002
Posts: 114
Topics: 0
Location: Sydney, Australia

PostPosted: Thu May 22, 2003 4:25 pm    Post subject: Reply with quote

Glad to see that you're happy Phantom and glad to be of assistance.
_________________
Regards,
Mike.
Back to top
View user's profile Send private message
Display posts from previous:   
Post new topic   Reply to topic   printer-friendly view    MVSFORUMS.com Forum Index -> TSO and ISPF All times are GMT - 5 Hours
Goto page Previous  1, 2, 3
Page 3 of 3

 
Jump to:  
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum


MVSFORUMS
Powered by phpBB © 2001, 2005 phpBB Group