2010年8月29日 星期日

Using TSO Allocate and Free commands from inside the program

The Program needs to Allocate, then OPEN, Read or Write, then Close,
then Free the file. This can be repeated in a single run of the program
as many times as needed.
01  WS-DYNAMIC-ALLOCATIONS.                         
05 WS-ALLOCATE.
10 FILLER PIC X(28)
VALUE 'ALLOCATE F(JOBPROC) DSNAME('''.
10 FILLER PIC X(20)
VALUE 'SDEV.PROD.P.PROCLIB('.
10 MEMBER-NAME PIC X(8) .
10 FILLER PIC X(7)
VALUE ')'') SHR'.
05 WS-DEALLOCATE PIC X(15)
VALUE 'FREE F(JOBPROC)'.

* WORK AREA'S FOR TSO INTERFACING
01 TSO-LINK PIC X(8) VALUE 'TSOLNK'.
01 TSO-FLAGS PIC S9(9) COMP VALUE 257.
01 TSO-LENGTH PIC S9(9) COMP VALUE 0.
01 TSO-RC PIC S9(9) COMP VALUE 0.
01 TSO-REASON PIC S9(9) COMP VALUE 0.
01 TSO-ABEND PIC S9(9) COMP VALUE 0.

/****************************************************************
* DYNAMICALY ALLOCATE FILE THROUGH TSO SERVICES
*****************************************************************
8000-TSO-ALLOCATE.

MOVE LENGTH OF WS-ALLOCATE TO TSO-LENGTH.
CALL TSO-LINK USING TSO-FLAGS WS-ALLOCATE TSO-LENGTH
TSO-RC TSO-REASON TSO-ABEND.

8000-EXIT. EXIT.

/****************************************************************
* DYNAMICALY DEALLOCATE FILE THROUGH TSO SERVICES
*****************************************************************
8100-TSO-DEALLOCATE.

MOVE LENGTH OF WS-DEALLOCATE TO TSO-LENGTH.
CALL TSO-LINK USING TSO-FLAGS WS-DEALLOCATE TSO-LENGTH
TSO-RC TSO-REASON TSO-ABEND.

8100-EXIT. EXIT.

The Program needs to run under batch TSO services similar to a DB2
program

//STEP010 EXEC PGM=IKJEFT01
//SYSTSPRT DD SYSOUT=*
//SYSOUT DD SYSOUT=*
//SYSTSIN DD *
CALL *(MYPROG)

Retrieve the TIME data for each JOBCLASS

I am looking for a way to retrieve the TIME data for each JOBCLASS entry.

$D JOBCLASS,TIME
$HASP837 JOBCLASS(A) TIME=(001440,00)
$HASP837 JOBCLASS(B) TIME=(001440,00)
$HASP837 JOBCLASS(C) TIME=(001440,00)
$HASP837 JOBCLASS(D) TIME=(001440,00)
$HASP837 JOBCLASS(E) TIME=(001440,00)
$HASP837 JOBCLASS(F) TIME=(001440,00)
$HASP837 JOBCLASS(G) TIME=(001440,00)
$HASP837 JOBCLASS(H) TIME=(001440,00)
$HASP837 JOBCLASS(I) TIME=(001440,00)
$HASP837 JOBCLASS(J) TIME=(001440,00)
$HASP837 JOBCLASS(K) TIME=(001440,00)
$HASP837 JOBCLASS(L) TIME=(001440,00)
$HASP837 JOBCLASS(M) TIME=(001440,00)
$HASP837 JOBCLASS(N) TIME=(001440,00)
$HASP837 JOBCLASS(O) TIME=(001440,00)
$HASP837 JOBCLASS(P) TIME=(001440,00)
$HASP837 JOBCLASS(Q) TIME=(001440,00)
$HASP837 JOBCLASS(R) TIME=(001440,00)
$HASP837 JOBCLASS(S) TIME=(001440,00)
$HASP837 JOBCLASS(STC) TIME=(001440,00)
$HASP837 JOBCLASS(T) TIME=(001440,00)
$HASP837 JOBCLASS(TSU) TIME=(001440,00)
$HASP837 JOBCLASS(U) TIME=(001440,00)
$HASP837 JOBCLASS(V) TIME=(001440,00)
$HASP837 JOBCLASS(W) TIME=(001440,00)
$HASP837 JOBCLASS(X) TIME=(001440,00)
$HASP837 JOBCLASS(Y) TIME=(001440,00)
$HASP837 JOBCLASS(Z) TIME=(001440,00)
$HASP837 JOBCLASS(0) TIME=(001440,00)
$HASP837 JOBCLASS(1) TIME=(001440,00)
$HASP837 JOBCLASS(2) TIME=(001440,00)
$HASP837 JOBCLASS(3) TIME=(001440,00)
$HASP837 JOBCLASS(4) TIME=(001440,00)
$HASP837 JOBCLASS(5) TIME=(001440,00)
$HASP837 JOBCLASS(6) TIME=(001440,00)
$HASP837 JOBCLASS(7) TIME=(001440,00)
$HASP837 JOBCLASS(8) TIME=(001440,00)
$HASP837 JOBCLASS(9) TIME=(001440,00)

Re-catalog the tape

you can easily re-catalog the tape as follow:

Use IDCAMS DEFINE NONVSAM -

DEF NVSAM(NAME(SYS1.JES2.OFFLOAD.TAPE) -
DEVT(3590) -
FSEQN(1) -
VOL(123456))