View previous topic :: View next topic
|
Author |
Message |
kbmkris
Active User
Joined: 24 Jun 2006 Posts: 101
|
|
|
|
hi,
I want to allocate a dataset say 'xxx.yyy.zzz' to ISPPLIB using LIBDEF in COBOL. I know how to call it in rexx.
Code: |
ADDRESS ISPEXEC "LIBDEF ISPPLIB DATASET ID('XXX.YYY.ZZZ') UNCOND" |
The purpose of this program is i have to call the panels in my program. The panels are residing in a dataset and i want to allocate that to ISPPLIB.
Can anyone please tell me how to do that using ISPLINK with an example?
Thanks,
Bala |
|
Back to top |
|
|
ofer71
Global Moderator
Joined: 27 Dec 2005 Posts: 2358 Location: Israel
|
|
|
|
It's all in the fine manual, including examples.
By the way, why not using CALL ISPEXEC?
O. |
|
Back to top |
|
|
kbmkris
Active User
Joined: 24 Jun 2006 Posts: 101
|
|
|
|
First of all thanks. I don't know than we can use ISPEXEC for the same purpose:-( I saw some existing programs where ISPLINK is used to display the panels. but there is no program that uses LIBDEF
Thanks,
Bala |
|
Back to top |
|
|
kbmkris
Active User
Joined: 24 Jun 2006 Posts: 101
|
|
|
|
hi,
I tried this piece of code and got a return code of 20. Please find the code below and correct if i did anything wrong.
Code: |
IDENTIFICATION DIVISION.
PROGRAM-ID. PANELTST.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 ISP-VAR.
05 ISP-OPTION PIC X(8) VALUE 'LIBDEF '.
05 ISP-PANEL PIC X(8) VALUE 'ISPPLIB '.
05 ISP-DSN PIC X(8) VALUE 'DATASET '.
05 ISP-DNAME PIC X(40) VALUE
"FIRST.ALL.PANELLIB".
05 ISP-COND PIC X(8) VALUE 'UNCOND '.
PROCEDURE DIVISION.
CALL 'ISPLINK' USING ISP-VAR.
DISPLAY 'RETURN CODE ' RETURN-CODE.
IF RETURN-CODE = 0 THEN
DISPLAY 'CALL SUCCESS'
ELSE
DISPLAY 'CALL FAILED'
END-IF.
STOP RUN.
EXIT. |
Thanks,
Bala |
|
Back to top |
|
|
ofer71
Global Moderator
Joined: 27 Dec 2005 Posts: 2358 Location: Israel
|
|
|
|
Display ZERRSM & ZERRLM after the command, or use Dialog Trace (option 7 in my main menu). Another option is to use ISPVCALL to see the exact message.
CALL ISPEXEC is described in the link I provided above.
O. |
|
Back to top |
|
|
kbmkris
Active User
Joined: 24 Jun 2006 Posts: 101
|
|
|
|
Hi,
I don't how to use the ZERRSM & ZERRLM. I went through the document and tried. But i am not able to get that. Also, I have never used the dialog Trace. Please help me in doing this.
Code: |
IDENTIFICATION DIVISION.
PROGRAM-ID. PANELTST.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 ISP-VAR.
05 ISP-OPTION PIC X(8) VALUE 'LIBDEF '.
05 ISP-PANEL PIC X(8) VALUE 'ISPPLIB '.
05 ISP-DSN PIC X(8) VALUE 'DATASET '.
05 ISP-DNAME PIC X(40) VALUE
"('K4CCBK1.IIRS.CAF.PARMLIB')".
05 ISP-COND PIC X(8) VALUE 'UNCOND '.
PROCEDURE DIVISION.
DISPLAY ISP-DNAME.
CALL 'ISPLINK' USING ISP-VAR.
DISPLAY 'RETURN CODE ' RETURN-CODE.
MOVE 'VGET ' TO ISP-OPTION.
MOVE 'ZERRLM' TO ISP-PANEL.
MOVE 'SHARED ' TO ISP-DSN.
CALL 'ISPLINK' USING ISP-OPTION ISP-PANEL ISP-DSN.
DISPLAY 'RETURN CODE ' RETURN-CODE.
IF RETURN-CODE = 0 THEN
DISPLAY 'CALL SUCCESS'
ELSE
DISPLAY 'CALL FAILED'
END-IF.
STOP RUN. |
Thanks,
Bala |
|
Back to top |
|
|
ofer71
Global Moderator
Joined: 27 Dec 2005 Posts: 2358 Location: Israel
|
|
|
|
Dialog Test options are fully explained in the fine manual.
ZERRSM & ZERRLM are ISPF Dialog Variables that contain a value when your dialog service ends with an RC of 8 or higher.
O. |
|
Back to top |
|
|
kbmkris
Active User
Joined: 24 Jun 2006 Posts: 101
|
|
|
|
Hi,
Do we have to use any library in the JCL to run the program that using ISPLINK?
Below is my JCL
Code: |
//RUNJCL1# JOB 00000,'PTST',MSGCLASS=6,CLASS=6
//*
//JOBLIB DD DSN=TST.MYCOBOL.LOADLIB,DISP=SHR
//*
//S05A EXEC PGM=PANELTST
//SYSOUT DD SYSOUT=*
//* |
Below is the contents of the program PANELTST
Code: |
IDENTIFICATION DIVISION.
PROGRAM-ID PANELTST
DATA DIVISION.
WORKING-STORAGE SECTION.
01 ISPLINK-FIELDS.
05 ISP-OPTION PIC X(8) VALUE 'VDEFINE'.
05 ISP-NAME PIC X(10) VALUE '(DIST)'.
05 ISP-FORMAT PIC X(6) VALUE 'CHAR'.
05 ISP-LENGTH PIC S9(9) COMP VALUE +10.
01 WS-ZERRLM PIC X(512).
PROCEDURE DIVISION.
DISPLAY PANAUDIT.
A00-MAIN.
MOVE SPACES TO WS-ZERRLM.
MOVE '(ZERRLM)' TO ISP-NAME.
MOVE +512 TO ISP-LENGTH.
CALL 'ISPLINK' USING ISP-OPTION ISP-NAME
WS-ZERRLM
ISP-FORMAT ISP-LENGTH.
DISPLAY 'RETURN-CODE : ' RETURN-CODE. |
Whatever I tried with ISPLINK, the Return-code I am getting is 20. Please help me.
Thanks,
Bala |
|
Back to top |
|
|
ofer71
Global Moderator
Joined: 27 Dec 2005 Posts: 2358 Location: Israel
|
|
|
|
If you have LIBDEF in your code, and if the compile was clean, you don't need additional libraries in your job.
O. |
|
Back to top |
|
|
kbmkris
Active User
Joined: 24 Jun 2006 Posts: 101
|
|
|
|
Hi,
My actual requirement is below.
There is an existing COBOL program which uses panel. Now a small change is being implemented in the code. I actually don't know how this program is being executed. I heard that there will be no JCL for this. I want to simulate this program and run and verify the changes I made. I copied the panels to my dataset. Now the problem is I want to concatenated the ISPPLIB to my dataset (I dont want to fuss with production panel). But I am not able to do that. I'm getting severe error (RC=20). In the above code I'm just mapping a variable to a dialog variable.
Could you provide me some piece of code with LIBDEF? How to use the ZERRLM in our COBOL? Whether we have to vdefine it or anything?
Thanks,
Bala |
|
Back to top |
|
|
ofer71
Global Moderator
Joined: 27 Dec 2005 Posts: 2358 Location: Israel
|
|
|
|
If the program contains panel display, then it probably going to be executed in foreground (although panels can be displayed in background, too).
Simply enter the TSO command CALL with your program name, or use the Dialog TEST screen (7.1 in my main menu).
O. |
|
Back to top |
|
|
kbmkris
Active User
Joined: 24 Jun 2006 Posts: 101
|
|
|
|
Hi,
Very thanks. Using TSO CALL I am able to run that program:-)
Thanks,
Bala. |
|
Back to top |
|
|
kbmkris
Active User
Joined: 24 Jun 2006 Posts: 101
|
|
|
|
Hi,
One more doubt. If I am running my COBOL program using TSO CALL statement, then where i can see my job logs. I normally check the job logs in SDSF while running in batch.
Thanks,
Bala |
|
Back to top |
|
|
ofer71
Global Moderator
Joined: 27 Dec 2005 Posts: 2358 Location: Israel
|
|
|
|
Why do you expect to see a job output when you run a foreground program???
O. |
|
Back to top |
|
|
kbmkris
Active User
Joined: 24 Jun 2006 Posts: 101
|
|
|
|
hi,
Sorry. I was confused. We can see the display message then and there right. Thanks for your timely help.
Thanks,
Bala |
|
Back to top |
|
|
|