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 

Current GDG version thru PLI.
Goto page 1, 2  Next
 
Post new topic   Reply to topic   printer-friendly view    MVSFORUMS.com Forum Index -> Application Programming
View previous topic :: View next topic  
Author Message
bauer
Intermediate


Joined: 10 Oct 2003
Posts: 315
Topics: 49
Location: Germany

PostPosted: Fri Jan 14, 2005 7:36 am    Post subject: Reply with quote

Hi Ravi,

difficult question.

Have you checked then content of the JFCB Data Area? I'm not sure, but any of this data areas may contain the version number.

regards,
bauer
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12372
Topics: 75
Location: San Jose

PostPosted: Fri Jan 14, 2005 10:10 am    Post subject: Reply with quote

Ravi,

I am not sure as to what your requirement is but, here check the last post in this topic to get the last GDG generation using REXX and may be you can use the same logic in your program also.

http://www.mvsforums.com/helpboards/viewtopic.php?t=3082&highlight=gdg

Hope this helps...

Cheers

kolusu
_________________
Kolusu
www.linkedin.com/in/kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12372
Topics: 75
Location: San Jose

PostPosted: Fri Jan 14, 2005 11:20 am    Post subject: Reply with quote

Ravi,

Here is a cobol example(written 4 years back) which I beleive still works. so try to simulate this code to PLI. Right now I don't have time to convert to PLI .
Code:

 CBL DATA(24)                                               
 IDENTIFICATION DIVISION.                                   
 PROGRAM-ID.    CALLDCAM                                   
 AUTHOR. KOLUSU
 DATE-COMPILED.                                             
 ENVIRONMENT DIVISION.                                     
 CONFIGURATION SECTION.                                     
 INPUT-OUTPUT SECTION.                                     
 FILE-CONTROL.                                             
                                                           
       SELECT IDCAMS-FILE                                   
       ASSIGN TO IDCOMND                                   
       ORGANIZATION IS SEQUENTIAL.                         
                                                           
 DATA DIVISION.                                             
 FILE SECTION.                                             
                                                           
 FD IDCAMS-FILE                                             
     RECORDING MODE IS F                                   
     LABEL RECORDS ARE STANDARD                             
     BLOCK CONTAINS 0 RECORDS                               
     DATA RECORD IS IDCAMS-REC.                             
                                                           
 01 IDCAMS-REC                  PIC X(80).                 
                                                           
 WORKING-STORAGE SECTION.                                   
 01 WS-FILE-NAME                PIC X(44).                 
 01 WS-DYN-MODULE               PIC X(08) VALUE 'IDCAMS'.   
                                                           
 01 WS-COMMAND-REC              PIC X(80) VALUE SPACES.     
                                                           
 01 PARM-OPTIONS.                                           
    05 PARM-LENGTH              PIC S9(04) COMP VALUE 0.   
                                                           
 01 DD-OPTIONS.                                             
    05 DD-LENGTH                PIC S9(04) COMP VALUE +48. 
    05 FILLER                   PIC X(32) VALUE LOW-VALUES.
    05 SYSIN-DD                 PIC X(08) VALUE 'IDCOMND'. 
    05 SYSPRINT-DD              PIC X(08) VALUE 'SYSOUT'.   
                                                           

 PROCEDURE DIVISION.                                 
                                                     
       OPEN OUTPUT  IDCAMS-FILE                     
                                                     
       MOVE 'your gdg base name' TO WS-FILE-NAME

       STRING                                         
            ' LISTC ENT('          DELIMITED BY SIZE   
            QUOTE                  DELIMITED BY SIZE   
            WS-FILE-NAME           DELIMITED BY SPACE 
            QUOTE                  DELIMITED BY SIZE   
            ') ALL'                DELIMITED BY SIZE   
            INTO WS-COMMAND-REC                       
       END-STRING.                                         
   
       WRITE IDCAMS-REC FROM WS-COMMAND-REC               
       CLOSE IDCAMS-FILE                                   
       CALL WS-DYN-MODULE USING PARM-OPTIONS, DD-OPTIONS   

       EVALUATE RETURN-CODE                                 
           WHEN 0                                           
                DISPLAY ' IDCAMS CALL SUCCESSFULL'     
           WHEN OTHER                                       
                DISPLAY ' ERROR CALLING IDCAMS'
                PERFORM INHOUSE-ABEND-ROUTINE               
       END-EVALUATE                         
               
       GOBACK                                               
       . 


The JCL used to run this pgm is

Code:

//STEP0100 EXEC PGM=CALLDCAM                                         
//STEPLIB  DD DSN=your pgm LOADLIB,                           
//            DISP=SHR                                               
//         DD DSN=SYS1.LINKLIB,    <=== Idcams Loadlib   
//            DISP=SHR 
//SYSUDUMP DD SYSOUT=*                                               
//SYSPRINT DD SYSOUT=*                                               
//SYSOUT   DD SYSOUT=*                                               
//IDCOMND  DD DSN=a 80 byte seq file for idcam command,
//            DISP=(NEW,CATLG,DELETE),
//            UNIT=SYSDA,
//            SPACE=(TRK,(1,1),RLSE)
/*   



The listcat listing can be seen in the SYSOUT.

Hope this helps...

Cheers

kolusu
_________________
Kolusu
www.linkedin.com/in/kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
Mervyn
Moderator


Joined: 02 Dec 2002
Posts: 415
Topics: 6
Location: Hove, England

PostPosted: Fri Jan 14, 2005 3:27 pm    Post subject: Reply with quote

Looks like you left out the "FETCH" bit.
_________________
The day you stop learning the dinosaur becomes extinct
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12372
Topics: 75
Location: San Jose

PostPosted: Fri Jan 14, 2005 4:07 pm    Post subject: Reply with quote

Ravi,

I would really appreciate if you can post the updated code , so that it can be useful for other users here.

Kolusu
_________________
Kolusu
www.linkedin.com/in/kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
Mervyn
Moderator


Joined: 02 Dec 2002
Posts: 415
Topics: 6
Location: Hove, England

PostPosted: Sat Jan 15, 2005 6:39 pm    Post subject: Reply with quote

Quote:

The access method services processor is loaded by issuing a FETCH IDCAMS statement, is branched to via a CALL statement, and deleted via a RELEASE IDCAMS statement.


I don't understand how this has worked without the FETCH. Can anyone enlighten me?
_________________
The day you stop learning the dinosaur becomes extinct
Back to top
View user's profile Send private message
Mervyn
Moderator


Joined: 02 Dec 2002
Posts: 415
Topics: 6
Location: Hove, England

PostPosted: Tue Jan 18, 2005 9:55 am    Post subject: Reply with quote

Thanks, Ravi. It still looks wrong, but it obviously works.
_________________
The day you stop learning the dinosaur becomes extinct
Back to top
View user's profile Send private message
DaveyC
Moderator


Joined: 02 Dec 2002
Posts: 151
Topics: 3
Location: Perth, Western Australia

PostPosted: Wed Mar 02, 2005 7:07 am    Post subject: Reply with quote

Wow, you gotta love the high level in PL/1. The only problem is you have to open the data set to be able to RDJFCB. If you don't mind using assembler here's a nice little routine that does the trick.

Code:

LOCATE   TITLE 'DSN Catalog Look Up'                                    00010000
LOCATE   CSECT ,                                                        00020000
LOCATE   AMODE 31                                                       00310000
LOCATE   RMODE ANY                                                      00320000
         SAVE  (14,12)          .Save caller's registers                00330000
         LR    R12,R15          .R12=base                               00360000
         USING LOCATE,R12       .Module addressability                  00370000
         ICM   R11,15,0(R1)     .-> Parameter List Structure            00380000
         USING LOCPLIST,R11     .Parameter List Structure addressing    00390000
*---------------------------------------------------------------------* 00400000
* Locate the DSN                                                      * 00410000
*---------------------------------------------------------------------* 00420000
         MVC   LOCCAML(CAMLSTL),CAMLST .Init CAMLST                     00430000
         LA    R1,LOCDSN               .DSN                             00440000
         ST    R1,LOCCAML+4            .Put into CAMLST                 00450000
         LA    R1,LOCAREA              .Work Area                       00460000
         ST    R1,LOCCAML+12           .Put into CAMLST                 00470000
         LOCATE LOCCAML                .Look in Catalog for DSN         00480000
         LTR   R15,R15                  .Cataloged?                     00490001
         BNZ   EXIT                     .N:                             00500001
         MVC   LOCWAREA(6),LOCAREA+6    .Set VOLSER from catalog        00510001
         MVI   LOCWAREA+6,C' '          .7 byte VOLSER for MIGRAT       00520001
         CLC   LOCWAREA(6),=CL8'MIGRAT' .Dataset is HSM migrated?       00530001
         BNE   EXIT                     .N: Finished                    00540001
         TM    LOCAREA+4,X'20'          .DASD?                          00550001
         BO    HSMMIGL1                 .Y:                             00560001
         TM    LOCAREA+4,X'80'          .Tape?                          00570001
         BO    HSMMIGL2                 .Y:                             00580001
         B     EXIT                     .Return to caller               00590001
HSMMIGL1 MVI   LOCWAREA+6,C'1'          .Migration Level 1 - DASD       00600001
         B     EXIT                     .Return to caller               00610001
HSMMIGL2 MVI   LOCWAREA+6,C'2'          .Migration Level 2 - Tape       00620001
         B     EXIT                     .Pass back return code          00630001
*---------------------------------------------------------------------* 00640000
* Exit                                                                * 00650000
*---------------------------------------------------------------------* 00660000
EXITNEG  L     R15,=F'-1'          .RC=Negative, PLIST is in error      00670000
         B     EXIT                                                     00680000
EXITPOS  LA    R15,8               .RC=8, LOCATE request failed         00690000
         B     EXIT                                                     00700000
EXIT0    SR    R15,R15             .RC=0, LOCATE request successful     00710000
EXIT     RETURN (14,12),RC=(15)    .Return to caller                    00720000
         EJECT ,                                                        00730000
*---------------------------------------------------------------------* 00740000
* Constants                                                           * 00750000
*---------------------------------------------------------------------* 00760000
CAMLST   CAMLST NAME,0,,0          .LOCATE SVC Parameter List           00770000
CAMLSTL  EQU   *-CAMLST                                                 00780000
         LTORG ,                   .Literal Pool Origin                 00790000
         EJECT ,                                                        00800000
*---------------------------------------------------------------------* 00810000
* Locate DSN Parameter List                                           * 00820000
*---------------------------------------------------------------------* 00830000
LOCPLIST DSECT ,                   .Locate Parameter List               00840000
LOCDSN   DS    CL44                .Data Set Name                       00850000
LOCWAREA DS    0D,CL300            .Work area                           00860000
         ORG   LOCWAREA            .Map our work area                   00870000
LOCCAML  CAMLST NAME,0,,0          .LOCATE SVC Parameter List           00880000
LOCAREA  DS    268C                .LOCATE SVC Work Area                00890000
         ORG   ,                                                        00900000
LOC1LEN  EQU   *-LOCPLIST          .Version 1 Plist length              00910000
         EJECT ,                                                        00920000
*---------------------------------------------------------------------* 00930000
* System macros                                                       * 00940000
*---------------------------------------------------------------------* 00950000
         YREGS ,                   .Register equates                    00960000
         END                                                            00970000


Exercise for the user, you have to convert the parmater list from a DSECT to a PL/1 structure, or COBOL record or whatever.
_________________
Dave Crayford
Back to top
View user's profile Send private message Send e-mail
Mervyn
Moderator


Joined: 02 Dec 2002
Posts: 415
Topics: 6
Location: Hove, England

PostPosted: Wed Mar 02, 2005 5:43 pm    Post subject: Reply with quote

Welcome back, Dave. I thought you'd retired!!! Mr. Green
_________________
The day you stop learning the dinosaur becomes extinct
Back to top
View user's profile Send private message
Cogito-Ergo-Sum
Advanced


Joined: 15 Dec 2002
Posts: 637
Topics: 43
Location: Bengaluru, INDIA

PostPosted: Thu Mar 03, 2005 7:23 am    Post subject: Reply with quote

Ravi,
I think, you have got the explantion of the FETCH vis-a-vis a simple CALL the other way round. If you simply use a CALL, then the main program expects the called program to be avaliable in that load module itself. Thus, for a simple CALL, the called program object code must be LINK edited.

In case of FETCH, the called program can be in a physically different PDS member. You do not have to LINK edit the object code of the called program.

In other words, a simple CALL is like a static call of COBOL. Whereas, the FETCH/CALL/RELEASE is like dynamic call in COBOL.

One last thing. If you are at PLI for MVS and VM, then you cannot call a program which resides in a CHAR(8 ) variable (just as the way, you implement the dynamic call in COBOL). A called program name must be declared with the data type as ENTRY. I believe, such declaration ensures the varaible (with the datatype as ENTRY) will hold the address of first executable code in the called program.
_________________
ALL opinions are welcome.

Debugging tip:
When you have eliminated all which is impossible, then whatever remains, however improbable, must be the truth.
-- Sherlock Holmes.
Back to top
View user's profile Send private message
DaveyC
Moderator


Joined: 02 Dec 2002
Posts: 151
Topics: 3
Location: Perth, Western Australia

PostPosted: Fri Mar 04, 2005 1:41 am    Post subject: Reply with quote

Thanks Merv,

Retired! If only mate, enjoy a game of golf and a cold beer...
_________________
Dave Crayford
Back to top
View user's profile Send private message Send e-mail
Mervyn
Moderator


Joined: 02 Dec 2002
Posts: 415
Topics: 6
Location: Hove, England

PostPosted: Mon Mar 07, 2005 7:09 am    Post subject: Reply with quote

Dave,

I was on a C++ course last week. I'm really, really looking forward to retirement after that!

Confused
_________________
The day you stop learning the dinosaur becomes extinct
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 -> Application Programming All times are GMT - 5 Hours
Goto page 1, 2  Next
Page 1 of 2

 
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