Joined: 07 Jan 2003 Posts: 1056 Topics: 91 Location: The Blue Planet
Posted: Sat Oct 16, 2004 9:05 am Post subject: Accessing Job File Control Block (JFCB)
Hi,
I was going thro' the Data Area manuals and I came across the following information regarding JFCB Data Area.
Code:
It is brought into virtual storage when the data set is opened. Information in a JFCB may be modified during OPEN processing.
It says that the JFCB is brought into Virtual storage only when the file allocated to a given DD is opened. Now here is my problem....
I have a COBOL program which tries to fetch the TCB, JCB and JFCB information when the job executes. My code (shown below) works absolutely fine for FB files, but I would like to make my code generic to take in any type of files (FB/VB....).
Code:
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
*
FILE-CONTROL.
SELECT TEST-FILE ASSIGN TO DD1.
*
DATA DIVISION.
FILE SECTION.
*
FD TEST-FILE
LABEL RECORDS OMITTED
BLOCK CONTAINS 0 RECORDS
RECORD CONTAINS 0 CHARACTERS.
01 TEST-REC1 PIC X(20000).
......
PROCEDURE DIVISION.
MAIN-ROUTINE.
OPEN INPUT TEST-FILE.
CLOSE TEST-FILE.
*---------------------------------------------------------------
* FIND DDNAMES AND ASSOCIATED DSNAMES
* PSA + X'21C' -> TCB -> TIOT -> TIOT SEG -> SWAREQ(SVA) -> JFCB
*---------------------------------------------------------------
..........
Since I gave 'RECORD CONTAINS 0 Characters' in my code, the program can accept FB files of any LRECL b/w 1 to 20,000. Note: I'm not doing any operations on the file thro' my COBOL program. I just retreive the DCB parameters of the file (LRECL, BLKSIZE,......).
The problem is that the program will not work for files that are of VB type, since during compilation, the recording mode is assumed as F by the compiler. Is there any way to overcome this ? If I code RECORD CONTAINS 0 Characters, the LRECL is obtained from the JCL during runtime. Is there something similar to detect the type of the file during RUNTIME ?
All I need to do is to issue a OPEN & CLOSE on the file to load its JFCB information into virtual storage. Is there any TSO command or any dummy utilities like IEFBR14 which could issue a OPEN & CLOSE on the input file without doing any operations on the records ? And this should be callable from my COBOL program.
Any help in this regard will be highly appreciated.
Joined: 07 Jan 2003 Posts: 1056 Topics: 91 Location: The Blue Planet
Posted: Sat Oct 16, 2004 9:33 am Post subject:
I can do the entire operation using REXX and call the rexx using my cobol. Actually thatz how my code was running till this time. But If I have to pass & get some data to & from a REXX routine I need to perform lot of Dynamic DD allocations like SYSEXEC, SYSTSPRT etc... Also I need to declare lot of pointers in my cobol to pass & get return values from the rexx routine and finally I need to call a intermediatory module IRXEXEC to invoke my REXX routine. I want to cut down the time taken to perform all these operations.
The EXECIO statements in REXX can open any type of file but COBOL as fas as I know does not have this capability. Is there any other command similar to EXECIO of REXX to open/close a dataset which could be called thro' my COBOL program (without allocating any DD's dynamically - like SYSPRINT, SYSTSPRT, .....)
Joined: 03 Jan 2003 Posts: 1014 Topics: 13 Location: Atlantis
Posted: Sat Oct 16, 2004 3:29 pm Post subject:
The JFCB is available when the ds is allocated. Some info is added by open, but you don't need to open the dataset to get at the JFCB. It depends on what you are looking for in the JFCB. DCB info is what is filled in and if you are looking for that, you might want to just use the catalog's info. It is rarely different than the VTOC. Be aware that opens are still pretty expensive and will mess up archiving strategies because it will update the last referenced date. Have a look at the OBTAIN macro too (SVC 27). It may give you what you need without opening the files. ISRDDN and similar programs usually use OBTAIN.
Joined: 07 Jan 2003 Posts: 1056 Topics: 91 Location: The Blue Planet
Posted: Mon Oct 18, 2004 1:38 am Post subject:
Wow, Thanks a lot semigeezer.
I am new to the Supervisory Calls. For the past two days I tried to find some COBOL examples (calling OBTAIN MACRO) in various sites but of no use. Could you please show me a small COBOL example which calls the OBTAIN macro ?
Try taking a look in the manual DFSMSdfp Advanced Services it has a section entitled Coding CVAF Macro Instructions theCVAFDIR macro should give you what you are looking for
Joined: 07 Jan 2003 Posts: 1056 Topics: 91 Location: The Blue Planet
Posted: Tue Oct 19, 2004 6:49 am Post subject:
Thanks a lot nevilh,
I am very new to Assemblers. I'm trying to invoke OBTAIN/CAMLST or CVAFDIR thro' COBOL. Could you please help me code a COBOL program which inturn invokes either of the above mentioned routines. All I want to know is the LRECL of a dataset given the dataset name / DDName.
Also, could some one tell me what is the difference b/w OBTAIN/CAMLST & CVAFDIR. From the manual I understood that CVAFDIR issues a OPEN on the dataset to load the DCB information into virtual storage and points to the address of DEB which inturn provides the requested DCB information.
Sorry I can't be of much help I haven't used COBOL in more years than I care to remember.
CVAFDIR will not issue an open for the dataset it goes straight to the vtoc to obtain the information .
Do you know any assemble?
If so the easiest would be to write a small assembler subroutine and pass the info back to the cobol pgm. There is a very good example in the
DFSMSdfp Advanced Services maual
Sorry, but I really haven't got the time to right a complete Assembler program to do everything you would like, but the last thing you said was, "All I want to know is the LRECL of a dataset given the dataset name / DDName."
As I mentioned on some other post on this BB, you could either use the DCBD from SYS1.MACLIB (more fiddly), or "probably the RDJFCB". I have just run a quick test of RDJFCB, and it will give you the results you want (ie: LRECL for either FB or VB). It's documented in the DFSMS Advanced Services.
And to the best of my knowledge, you cannot call ANY Macro from COBOL. They are for Assembler programs only, hence the aforementioned manual only mentions one language; ie: ASM.
Test it out by assigning different files to a DDNAME called "FILIN".
Code:
RDJ CSECT
BAKR R14,0 SAVE CALLER DATA ON STACK
LR R12,R15 GET ENTRY POINT
USING RDJ,R12 ADDRESSABILITY TO MODULE
RDJFCB FILIN GET JFCB FOR 'INFIL' DD
OPEN (FILIN,(INPUT)) OPEN FILE
XR R1,R1 CLEAR WORK REG
LH R1,FILIN+X'3E' GET BLKSIZE...
CVD R1,DWORD ...CONVERT TO DECIMAL
MVC WTOLIST2+27(6),EDPATRN2 MOVE EDIT PATTERN TO WTO
ED WTOLIST2+27(6),DWORD+5 EDIT IN BLKSIZE
WTO MF=(E,WTOLIST2) DISPLAY MSG
XR R1,R1 CLEAR WORK REG
LH R1,FILIN+X'52' GET LRECL...
CVD R1,DWORD ...CONVERT TO DECIMAL
MVC WTOLIST3+27(6),EDPATRN2 MOVE EDIT PATTERN TO WTO
ED WTOLIST3+27(6),DWORD+5 EDIT IN LRECL
WTO MF=(E,WTOLIST3) DISPLAY MSG
MVC WTOLIST4+27(6),JFCB+118 MOVE VOLSER FROM JFCB
WTO MF=(E,WTOLIST4) DISPLAY MSG
CLOSE FILIN CLOSE IT
*
RETURN DS 0H
XR R15,R15 SET RC=0
PR , RETURN
*
EOVEXIT DS 0H
BR R14 RETURN FROM EXIT
*
YREGS
DWORD DS D
EDPATRN1 DC XL8'4020202020202120'
EDPATRN2 DC XL6'402020202120'
FILIN DCB DDNAME=FILIN, X
DSORG=PS, X
MACRF=GM, X
EXLST=EXLST EXIT LIST ADDRESS
EXLST DS 0F
DC X'07' SHOWS READ JFCB
DC AL3(JFCB) ADDRESS OF AREA FOR JFCB
DC X'86' SHOWS E-O-V EXIT & END OF LIST
DC AL3(EOVEXIT) ADDRESS OF E-O-V EXIT
JFCB DS CL176' '
WTOLIST2 WTO '* BLKSIZE: 00000 *'X
,ROUTCDE=11,MF=L
WTOLIST3 WTO '* LRECL: 00000 *'X
,ROUTCDE=11,MF=L
WTOLIST4 WTO '* VOLSER: XXXXXX *'X
,ROUTCDE=11,MF=L
END
Correction:- for the above code, the RDJFCB is only used in order to get the Volser. So effectively, you can comment that out, delete the EXLST, other WTOS, etc, and make it quite small. What the "FILIN+ hex displacement" statements actually do is to go inside the DCB Macro and pick out the information from there. It is a bit crude, but at least it gives you the desired results (LRECL for FB/VB).
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