IBM Mainframe Forum Index
 
Log In
 
IBM Mainframe Forum Index Mainframe: Search IBM Mainframe Forum: FAQ Register
 

Forcing a step to run (even if abended)


IBM Mainframe Forums -> JCL & VSAM
Post new topic   Reply to topic
View previous topic :: View next topic  
Author Message
JPVRoff

New User


Joined: 06 Oct 2009
Posts: 41
Location: Melbourne, Australia

PostPosted: Fri Dec 23, 2022 7:43 am
Reply with quote

Hi,

I'm sure it's because I'm about to take a week off, but I've got a problem I don't seem to be able to work out. Essentially, I want to run a step at the end of a job, whether or not the rest of the job has an abend or high return code(s).
Normally, I've been able to do this using COND=ONLY, but for this particular job (failing with a wrong length record in a COBOL program), that doesn't seem to work. The info on the IEF450I message is ABEND=S000 U4038 REASON=00000001. Nor does an IF/THEN/ELSE/ENDIF construct using the same step included twice:
Code:
//CHKIF    IF (ABEND | RC > 0) THEN   
//CHKSTEPA EXEC PGM=IKJEFT01,DYNAMNBR=1635   
...
// ELSE
//CHKSTEPB EXEC PGM=IKJEFT01,DYNAMNBR=1635   
...
//CHKIF ENDIF

Both steps (in the above case) come up as "SMFSI2I CHKSTEP? STEP BYPASSED" without saying exactly why. I'm a bit at a loss, as I cannot see why it wouldn't work. I know I'm missing something, I just don't know what. And to make matters worse, there's a couple of steps in the original JCL that use the "IF (ABEND | RC > 0) THEN" to run a step to write to the console - and they execute successfully!?!

Oh, the reason for this is that I'm looking to allow our testers to run their inputs files in, using the scheduler authority, but without them having access to either the region files or the scheduler (OPC/Tivoli). So the step that I want to run, at the end of every job, will check the job condition codes and submit the next job in the list, A sort of a poor man's scheduler. It works for just about every execution type except this one job and its particular failure type.

I must need a couple of days off - maybe the rest of the year! I'll see if I can solve it by not thinking about ot for a while
Back to top
View user's profile Send private message
Rohit Umarjikar

Global Moderator


Joined: 21 Sep 2010
Posts: 3048
Location: NYC,USA

PostPosted: Fri Dec 23, 2022 10:04 am
Reply with quote

System abends can’t be handled as per me in subsequent steps. However, you can try to change the cobol program to set specific RC when dataset attributes mismatch occurs and this way it will not have system abend and you can continue to run all steps including last one without IFTHEN.
Back to top
View user's profile Send private message
Willy Jensen

Active Member


Joined: 01 Sep 2015
Posts: 712
Location: Denmark

PostPosted: Fri Dec 23, 2022 2:04 pm
Reply with quote

Try COND=EVEN, i.e.
Code:
//G4      EXEC PGM=IEFBR14,COND=EVEN
Back to top
View user's profile Send private message
JPVRoff

New User


Joined: 06 Oct 2009
Posts: 41
Location: Melbourne, Australia

PostPosted: Tue Jan 03, 2023 4:38 am
Reply with quote

Rohit Umarjikar wrote:
System abends can’t be handled as per me in subsequent steps. However, you can try to change the cobol program to set specific RC when dataset attributes mismatch occurs and this way it will not have system abend and you can continue to run all steps including last one without IFTHEN.

Unfortunately it's a production program and a generic IO routine at that. So changing it would be too much trouble.
But I had a thought this morning on a different approach (just in case there are abends of this type) and I might try working on that instead.

FYI, anyone interested in the Rexx used to grab the return codes from the job (in the last step), it's here:
Code:
/* */                                                                   
GetHighStep:procedure expose x.;trace "O";cvt=storage(10,4)             
ascb=storage(224,4);ascb_jbni=c2x(storage(d2x(c2d(ascb)+172),4))       
ascb_jbns=c2x(storage(d2x(c2d(ascb)+176),4))                           
assb=storage(d2x(c2d(ascb)+336),4);asxb=Storage(D2x(c2d(ascb)+108),4)   
acee=Storage(D2x(c2d(asxb)+200),4);jsab=storage(d2x(c2d(assb)+168),4)   
asid=storage(d2x(c2d(ascb)+36),2);psatold=storage(21C,4)               
jscb=storage(d2x(c2d(psatold)+180),4);jct=storage(d2x(c2d(jscb)+260),4)
sct=storage(d2x(c2d(jct)+48),3);pnt=0;sctd=c2d(sct)                     
do forever while sctd<>0;pnt=pnt+1                                     
 sctansct=storage(d2x(c2d(sct)+36),3)                                   
 sctsname.pnt=storage(d2x(c2d(sct)+68),8)                               
 sctpgmnm.pnt=storage(d2x(c2d(sct)+124),8)                             
 sctabcnd.pnt=x2b(c2x(storage(d2x(c2d(sct)+176),1)))                   
 sctstend.pnt=x2b(c2x(storage(d2x(c2d(sct)+188),1)))                   
 if \substr(sctstend.pnt,1,1)then sctsexec.pnt=0                       
 else sctsexec.pnt=c2d(storage(d2x(c2d(sct)+24),2))                     
 sct=sctansct;sctd=c2d(sct)                                             
 if substr(sctstend.pnt,1,1)&\substr(sctstend.pnt,2,1) then leave;end   
if sct<>0 then do;OKRC=-1;x.0RC=0;abend=0;step=;message.=;message=0     
 do while pnt>1;pnt=pnt-1;if substr(sctabcnd.pnt,6,1) then do           
   abend=1;step=strip(sctsname.pnt);message=message+1                   
   message.message="Step "step" abended.";end                           
  else if sctsexec.pnt>OKRC then do;message=message+1                   
   message.message="Step "strip(sctsname.pnt)" ended with RC="||,       
    sctsexec.pnt".";end                                                 
  if sctsexec.pnt>x.0RC&\abend then do;x.0RC=sctsexec.pnt               
   step=strip(sctsname.pnt);end;end;message.0=message                   
 if abend then return="ABEND";else return=x.0RC                         
 sysid=storage(d2x(c2d(cvt)+340),4);x.0id=storage(d2x(c2d(jsab)+20),8) 
 x.0us=Storage(d2x(c2d(acee)+21),7)                                     
 if ascb_jbns=0 then x.0jb=storage(ascb_jbni,8)                         
 else x.0jb=storage(ascb_jbns,8)                                       
 if x.0jb='INIT' then x.0jb=storage(d2x(c2d(jsab)+28),8)               
 if message>0 then do i0=1 to message;say message.i0;end;end;return sctd
/* */                                                                   
Back to top
View user's profile Send private message
Joerg.Findeisen

Senior Member


Joined: 15 Aug 2015
Posts: 1231
Location: Bamberg, Germany

PostPosted: Tue Jan 03, 2023 11:51 am
Reply with quote

JPVRoff wrote:
FYI, anyone interested in the Rexx used to grab the return codes from the job (in the last step), it's here:

Looks like you had fun with it. icon_smile.gif
Back to top
View user's profile Send private message
Willy Jensen

Active Member


Joined: 01 Sep 2015
Posts: 712
Location: Denmark

PostPosted: Tue Jan 03, 2023 3:27 pm
Reply with quote

I like the REXX solution for locating latest rc. You can also get it using the REXX/SDSF API, like so:
Code:
 /* REXX */                                                   
 n=isfcalls('ON')                                             
 isfprefix=mvsvar('symdef','jobname')                         
 isfowner ='*'                                               
 Call XWait 2 /* (sometimes) required for synch */                       
 Address SDSF "ISFEXEC ST"                                   
 do n=1 to jname.0 until queue.n='EXECUTION'                 
 end                                                         
 if queue.n<>'EXECUTION' then exit xmsg('Job not found')     
                                                             
 /* show return codes for job till now */                     
 Address SDSF "ISFACT ST TOKEN('"token.n"') PARM(NP SA)"     
 "execio * diskr" isfddname.3 "(stem msgs. finis)"           
 do n=1 to msgs.0                                             
   if word(msgs.n,1)='IEF142I' then say msgs.n           
 end                                                         
 exit 0                                                       
                                                             
XMsg: if arg(1)<>'' then say arg(1);return word(arg(2) 0,1)   
XWait:                                                       
 call syscalls 'ON'                                           
 address syscall 'sleep' arg(1)                               
 call syscalls 'OFF'                                         
 return 0                                                     
Back to top
View user's profile Send private message
prino

Senior Member


Joined: 07 Feb 2009
Posts: 1306
Location: Vilnius, Lithuania

PostPosted: Tue Jan 03, 2023 3:46 pm
Reply with quote

JPVRoff wrote:
FYI, anyone interested in the Rexx used to grab the return codes from the job (in the last step), it's here:

Got something similar in PL/I, but we had to change something in our system to get them run differently, as some control blocks were above the line or something like that, if I remember correctly, and that would have required the use of SWAREQ to convert pointers, or pseudo-pointers. Your code might suffer from the same problem.

Anyway, here's the PL/I code:
Code:
*process macro test(all,sym);
*process rules(laxif);
 steps: proc(param) options(main) reorder;
 dcl param char(*) var;

 /**********************************************************************
 * STEPS - Entry's, builtins & files                                   *
 **********************************************************************/
 dcl (addr,
      heximage,
      index,
      length,
      plidump,
      ptradd,
      ptrvalue,
      stg,
      substr,
      unspec,
      verify) builtin;

 dcl sysprint file;

 %include plitabs;

 dcl p1               ptr init (ptrvalue(16)) static;

 dcl 1 s1 based(p1),
       2 p2           ptr;

 dcl 1 s2 based(p2),
       2 p3           ptr;

 dcl 1 s3 based(p3),
       2 *            ptr,
       2 tcb_ptr      ptr;

 dcl 1 tcb based(tcb_ptr),
       2 *(3)         ptr,
       2 tiot_ptr     ptr,
       2 *(41)        ptr,
       2 jscb_ptr     ptr;

 dcl 1 tiot based(tiot_ptr),
       2 jobname      char (8),
       2 stepname     char (8);

 dcl 1 jscb based(jscb_ptr),
       2 *(65)        ptr,
       2 jscbjct      ptr,
       2 *(13)        ptr,
       2 jscbssib     ptr;

 dcl 1 jct based(jscbjct),
       2 *(5)         ptr,
       2 *            char,
       2 jctjstat     bit  (8),
       2 *            char (2),
       2 jctjname     char (8),            /* job name                */
       2 *(4)         ptr,
       2 jctsdkad     char (3),            /* sva of first sct        */
       2 *            char,
       2 jctjctx      char (3),            /* sva of jctx             */
       2 *            char,
       2 jctactad     char (3),            /* sva of first act        */
       2 *            char,
       2 *(26)        ptr,
       2 *            char,
       2 jmrjmrjd     fixed dec(5,3),      /* job start date (julian) */
       2 *(2)         ptr,
       2 jctuser      char (7),            /* job user id             */
       2 *            char,
       2 jctacode     char (4);            /* job abend code          */

 dcl 1 ssib based(jscbssib),
       2 *(3)         ptr,
       2 ssibjbid     char (8);            /* subsystem job id        */

 dcl act_ptr ptr;
 dcl 1 act based(act_ptr),
       2 *            char  (24),
       2 actprgnm     char  (20),
       2 *            char   (3),
       2 actjnfld     char,
       2 actaccnt     char (144);

 dcl sct_ptr ptr;
 dcl 1 sct based(sct_ptr),
       2 *(6)         ptr,
       2 sctsexec     fixed bin (15),
       2 *(2)         char,
       2 *(2)         ptr,
       2 sctansct     char (3), /* sva of next sct                    */
       2 *            char,
       2 *(5)         ptr,
       2 sctsclpc     char (8), /* name of step that called procedure */
       2 sctsname     char (8), /* step name                          */
       2 *(2)         ptr,
       2 sctx_pch     char (3),
       2 *            char,
       2 *(9)         ptr,
       2 sctpgmnm     char (8), /* program name                       */
       2 *            char (2),
       2 sctcdent(8)  char (6),
       2 *            char (6),
       2 sctstend     bit  (8);  /* bits and pieces                   */

 dcl sctx_ptr ptr;
 dcl 1 sctx based(sctx_ptr),
       2 *(5)         ptr,
       2 sctxparm     char     (100);

 dcl jctx_ptr         ptr;
 dcl sctxparm_v       char     (100) var;
 dcl have_had_current bit        (1) init ('0'b);
 dcl have_had_title   bit        (1) init ('0'b);
 dcl max_cc           fixed bin (15) init (0);
 dcl flag_after       bit        (1) init ('0'b);     /* A */
 dcl flag_before      bit        (1) init ('0'b);     /* B */
 dcl flag_current     bit        (1) init ('0'b);     /* C */
 dcl flag_desc        bit        (1) init ('0'b);     /* D */
 dcl flag_flush       bit        (1) init ('0'b);     /* F */
 dcl flag_nonzero     bit        (1) init ('0'b);     /* N */
 dcl flag_parm        bit        (1) init ('0'b);     /* P */
 dcl flag_zero        bit        (1) init ('0'b);     /* Z */

 dcl desc_max         fixed bin (31) static init (255);
 dcl desc_used        fixed bin (31) init (0);
 dcl 1 desc_array(desc_max) ctl,
       2 stepname     char       (8),
       2 text         char      (64) var;

 flag_after   = (index(param, 'A') ^= 0);
 flag_before  = (index(param, 'B') ^= 0);
 flag_current = (index(param, 'C') ^= 0);
 flag_desc    = (index(param, 'D') ^= 0);
 flag_flush   = (index(param, 'F') ^= 0);
 flag_nonzero = (index(param, 'N') ^= 0);
 flag_parm    = (index(param, 'P') ^= 0);
 flag_zero    = (index(param, 'Z') ^= 0);

 if ^flag_after  &
    ^flag_before &
    ^flag_current then
   flag_before = '1'b;

 if flag_desc then
   call load_desc_array();

 jctx_ptr = char3_to_ptr(jct.jctjctx);
 act_ptr  = char3_to_ptr(jct.jctactad);

 put skip edit(ssib.ssibjbid,
               jct.jctjname, 'run on',
               jct.jmrjmrjd, 'by',
               jct.jctuser)
              (a, x(1),
               a, x(1), a, x(1),
               p'99v.999', x(1), a, x(1),
               a);

 call print_accounting();

 sct_ptr = char3_to_ptr(jct.jctsdkad);

 do while(sct_ptr ^= ptrvalue(0));
   sctx_ptr = char3_to_ptr(sct.sctx_pch);
   if unspec(substr(sctcdent(8), 1, 1)) & '04'bx then
     do;
       if ^have_had_title then
         call print_title();

       put skip edit(sctsclpc,
                     sctsname,
                     sctpgmnm)
                    (a, x(1),
                     a, x(1),
                     a, x(1));
       put edit('ABENDed')
               (a, x(1));

       if flag_desc then
         call print_desc();

       if flag_parm then
         call print_parm();
     end;
   else
     if sctstend & '80'bx then      /* started */
       if sctstend & '40'bx then    /* ended   */
         do;
           if flag_before then
             if (flag_zero    & sctsexec  = 0) |
                (flag_nonzero & sctsexec ^= 0) then
               do;
                 if ^have_had_title then
                    call print_title();

                 put skip edit(sctsclpc, sctsname, sctpgmnm)
                              (a, x(1), a, x(1), a, x(3));
                 put edit(sctsexec)
                         (p'zzzz9');

                 if flag_desc then
                    call print_desc();

                 if flag_parm then
                    call print_parm();
               end;

           if sctsexec > max_cc then
             max_cc = sctsexec;
         end;
       else
         do;
           if flag_current then
             do;
               if ^have_had_title then
                 call print_title();

               put skip edit(sctsclpc, sctsname, sctpgmnm)
                            (a, x(1), a, x(1), a, x(9));

               if flag_desc then
                 call print_desc();

               if flag_parm then
                 call print_parm();
             end;

           have_had_current = '1'b;
         end;
     else      /* not started */
       if have_had_current then
         if flag_after then
           do;
             if ^have_had_title then
               call print_title();

             put skip edit(sctsclpc, sctsname, sctpgmnm)
                          (a, x(1), a, x(1), a, x(9));
             if flag_desc then
               call print_desc();

             if flag_parm then
               call print_parm();
           end;
         else
           do;
           end;
       else
         if flag_flush then
           do;
             if ^have_had_title then
               call print_title();

             put skip edit(sctsclpc, sctsname, sctpgmnm)
                          (a, x(1), a, x(1), a, x(1));
             put edit('Flushed') (a, x(1));

             if flag_desc then
               call print_desc();

             if flag_parm then
               call print_parm();
           end;

   sct_ptr = char3_to_ptr(sct.sctansct);
 end;

 if have_had_title then
   put skip edit((69)'-')(a);

 put skip edit('Maximum completion code was', max_cc)
              (a, x(2), p'zzzz9');

 if jctjstat & '08'bx then
   do;
     put skip edit('The job ABENDed', abend_code(jctacode))
                  (a, x(1), a);
   end;

 print_parm: proc;
 dcl ix fixed bin (31);

 ix = index(sctxparm, '00'x);
 if ix = 0 then
   sctxparm_v = sctxparm;
 else
   sctxparm_v = substr(sctxparm, 1, ix);

 put skip list('PARM=' || sctxparm_v);
 end print_parm;

 print_desc: proc;
 dcl ix fixed bin (31);

 do ix = 1 to desc_used while(sct.sctsname ^= desc_array(ix).stepname);
 end;

 if ix <= desc_used then
   put edit(desc_array(ix).text) (x(1), a);
 end print_desc;

 char3_to_ptr: proc(ch3) returns(ptr);
 dcl ch3            char (3);

 dcl 1 * union,
       2 wp  ptr,
       2 *,
         3 * char (1) init ('00'x),
         3 * char (3) init (ch3);

 return(wp);
 end char3_to_ptr;

 load_desc_array: proc;
 dcl sysin file input record sequential;
 dcl (undf,eof) bit (1) init('0'b);

 on undefinedfile(sysin) undf = '1'b;
 on endfile(sysin)       eof  = '1'b;

 dcl sysin_rec char      (80);
 dcl ix        fixed bin (31);

 open file(sysin);

 if undf then
   do;
     put skip list('Unable to open SYSIN');
     stop;
   end;

 read file(sysin) into(sysin_rec);
 if eof then
   do;
     put skip list('No records in SYSIN');
     stop;
   end;

 alloc desc_array;

 do while(^eof);
   ix = index(sysin_rec, ',');

   if ix > 1 & ix <= 9 then
     do;
       desc_used                      = desc_used + 1;
       desc_array(desc_used).stepname = substr(sysin_rec, 1, ix - 1);
       desc_array(desc_used).text     = substr(sysin_rec, ix + 1, 64);
     end;
   else
     do;
       put skip list('Invalid record in SYSIN');
       stop;
     end;

   read file(sysin) into(sysin_rec);
 end;

 close file(sysin);
 end load_desc_array;

 abend_code: proc(ch4) returns(char(5));
 dcl ch4 char       (4);
 dcl w4b fixed bin (31);
 dcl w4  char       (4) based(addr(w4b));
 dcl p4  pic     '9999';

 unspec(w4) = unspec(ch4) & '00fff000'bx;
 if unspec(w4) then
   do;
     return('S' || substr(hex(w4), 3, 3));
   end;
 else
   do;
     unspec(w4) = unspec(ch4) & '00000fff'bx;
     p4         = w4b;
     return('U' || p4);
   end;
 end abend_code;

 hex: proc(ch_string) returns(char(100) var);
 dcl ch_string  char       (*);
 dcl hex_string char     (100) var init ('');

 hex_string = heximage(addr(ch_string), stg(ch_string));
 return(hex_string);
 end hex;

 ch1_to_fb31: proc(ch1) returns(fixed bin(31));
 dcl ch1      char       (1);
 dcl 1 * union,
       2 fb31 fixed bin (31),
       2 *,
         3 *  char       (3) init ('000000'x),
         3 *  char       (1) init (ch1);

 return(fb31);
 end ch1_to_fb31;

 print_accounting: proc;
 dcl (nf, nc)  fixed bin (31);
 dcl p         ptr;
 dcl 1 actfield based(p),
       2 len   char       (1),
       2 rest  char     (144);
 dcl w_account char     (100) var init ('');
 dcl ix        fixed bin (31);

 nf = ch1_to_fb31(act.actjnfld);
 p  = addr(actaccnt);

 do ix = 1 to nf;
   nc = ch1_to_fb31(actfield.len);
   w_account = w_account || substr(actfield.rest, 1, nc);

   if ix < nf then
     w_account = w_account || ',';

   p = ptradd(p, nc + 1);
 end;

 w_account = '(' || w_account || ')';

 put edit(w_account, '''' || actprgnm || '''')
     (x(1), a, x(1), a);
 end print_accounting;

 print_title: proc;
   put skip edit((69)'-')(a);
   put skip edit('Step', 'Program', 'Code')
                (x(9), a(8), x(1), a(8), x(4), a(4));
   have_had_title = '1'b;
 end print_title;
 end steps;
 /*********************************************************************
 //.*******************************************************************
 //. Create .STEPS dataset containing summary of job steps
 //.*******************************************************************
 //#440   EXEC PGM=STEPS,COND=EVEN,
 //            PARM='/B D N'    Before Desc Nonzero
 //SYSPRINT DD DSN=&ZPREFIX..&MEM..STEPS,
 //            DISP=(,CATLG),
 //            UNIT=SYSDA
 //            SPACE=(TRK,(2,1),RLSE),
 //            DCB=(RECFM=VBA,LRECL=125,BLKSIZE=0)
 //SYSIN    DD *
 A&MEM7,Find PLI program (&MEM)
 B&MEM7,PLI Compiler (Macro/Include) (&MEM)
 V&MEM7,IDMS Special Versions (&MEM)
 C&MEM7,IDMS Preprocessor (&MEM)
 D&MEM7,DB2 Precompiler (&MEM)
 Z&MEM7,CICS Preprocessor (&MEM)
 E&MEM7,PLI Compiler (Compile) (&MEM)
 F&MEM7,InterTest Postprocess listing (&MEM)
 G&MEM7,Find LEL (&MEM)
 H&MEM7,Link Edit Load module (&MEM)
 K&MEM7,InterTest Postprocess linkedit (&MEM)
 **********************************************************************/
Back to top
View user's profile Send private message
Willy Jensen

Active Member


Joined: 01 Sep 2015
Posts: 712
Location: Denmark

PostPosted: Tue Jan 03, 2023 9:16 pm
Reply with quote

Tuens out that the REXX/SDSF API solution can be improved by using DA instead of ST:
Code:
 /* REXX */                                               
 n=isfcalls('ON')                                         
 isfprefix=mvsvar('symdef','jobname')                     
 isfowner ='*'                                             
 Call XWait 2 /* required for synch */                     
 Address SDSF "ISFEXEC DA"                                 
 Address SDSF "ISFACT DA TOKEN('"token.1"') PARM(NP SA)"   
 "execio * diskr" isfddname.3 "(stem msgs. finis)"         
 do n=1 to msgs.0  /* show return codes for job till now */                                           
   if word(msgs.n,1)='IEF142I' then say msgs.n             
 end                                                       
 exit 0                                                   
                                                           
XMsg: if arg(1)<>'' then say arg(1);return word(arg(2) 0,1)
XWait:                                                     
 call syscalls 'ON'                                       
 address syscall 'sleep' arg(1)                           
 call syscalls 'OFF'                                       
 return 0     
Back to top
View user's profile Send private message
JPVRoff

New User


Joined: 06 Oct 2009
Posts: 41
Location: Melbourne, Australia

PostPosted: Fri Feb 03, 2023 7:38 am
Reply with quote

Willy Jensen wrote:
Tuens out that the REXX/SDSF API solution can be improved by using DA instead of ST


prino wrote:
Got something similar in PL/I, but we had to change something in our system to get them run differently, as some control blocks were above the line or something like that, if I remember correctly, and that would have required the use of SWAREQ to convert pointers, or pseudo-pointers. Your code might suffer from the same problem.


Thanks for both the ideas! I'm actually using SDSF in the last step to read in all the outputs to search for "run information" created during all of the job processes. But for the initial checking in the jobs, I've found that the Rexx is a fair bit quicker.
And it's also pretty robust, as I don't think we've had to change it for more than a decade (other than how it returns results to the calling Rexx).

P.S. I'm now using COND=EVEN and that's been working fine, plus I have a catch-all process in case the job fails with a JCL or system issue.
Back to top
View user's profile Send private message
View previous topic :: :: View next topic  
Post new topic   Reply to topic View Bookmarks
All times are GMT + 6 Hours
Forum Index -> JCL & VSAM

 


Similar Topics
Topic Forum Replies
No new posts Reorg abended with REASON=X'00E40347' DB2 2
No new posts Return codes-Normal & Abnormal te... JCL & VSAM 7
No new posts How to append a PS file into multiple... JCL & VSAM 3
No new posts convert file from VB to FB and use tr... DFSORT/ICETOOL 8
No new posts step by step trace 4 ISPF dialog call... TSO/ISPF 17
Search our Forums:

Back to Top