Looking in SYS1.MACLIB(CVT), we see that z/OS has a control block called the CVT (Communications Vector Table) that contains the sysname 340 bytes into it. In the comments at the top of that member, we learn that there is a pointer to the CVT in the PSA (Prefixed Save Area) x’10′ bytes into it. The PSA is easy to find – it is at address 0. So, armed with this info, I wrote the sample code below, which you are welcome to use or incorporate into your own project. If you use this code, just define a PPT for it (if you do not use autoinstall for programs) and point a tranid to the program.
IDENTIFICATION DIVISION.
PROGRAM-ID. CVTTEST.
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 WS-PSA-POINTER.
10 PSA-PTR-PIC9 PIC S9(8) COMP-5 VALUE 0.
10 PSA-PTR REDEFINES PSA-PTR-PIC9 POINTER.
01 SEND-AREA.
10 FILLER PIC X(1) VALUE SPACE.
10 FILLER PIC X(11) VALUE 'CVTSNAME = '.
10 SA-CVTSNAME PIC X(8) VALUE SPACES.
LINKAGE SECTION.
01 PSA.
10 FILLER PIC X(16).
10 CVT-PTR POINTER.
01 CVT.
10 FILLER PIC X(340).
10 CVTSNAME PIC X(8).
EJECT
PROCEDURE DIVISION.
100-MAINLINE.
SET ADDRESS OF PSA TO PSA-PTR.
SET ADDRESS OF CVT TO CVT-PTR.
MOVE CVTSNAME TO SA-CVTSNAME.
EXEC CICS SEND FROM(SEND-AREA)
LENGTH(LENGTH OF SEND-AREA)
END-EXEC.
999-RETURN.
EXEC CICS RETURN
END-EXEC.
GOBACK.
PROGRAM-ID. CVTTEST.
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 WS-PSA-POINTER.
10 PSA-PTR-PIC9 PIC S9(8) COMP-5 VALUE 0.
10 PSA-PTR REDEFINES PSA-PTR-PIC9 POINTER.
01 SEND-AREA.
10 FILLER PIC X(1) VALUE SPACE.
10 FILLER PIC X(11) VALUE 'CVTSNAME = '.
10 SA-CVTSNAME PIC X(8) VALUE SPACES.
LINKAGE SECTION.
01 PSA.
10 FILLER PIC X(16).
10 CVT-PTR POINTER.
01 CVT.
10 FILLER PIC X(340).
10 CVTSNAME PIC X(8).
EJECT
PROCEDURE DIVISION.
100-MAINLINE.
SET ADDRESS OF PSA TO PSA-PTR.
SET ADDRESS OF CVT TO CVT-PTR.
MOVE CVTSNAME TO SA-CVTSNAME.
EXEC CICS SEND FROM(SEND-AREA)
LENGTH(LENGTH OF SEND-AREA)
END-EXEC.
999-RETURN.
EXEC CICS RETURN
END-EXEC.
GOBACK.
沒有留言:
張貼留言