IBM Mainframe Forum Index
 
Log In
 
IBM Mainframe Forum Index Mainframe: Search IBM Mainframe Forum: FAQ Register
 

LRECL Mismatch in the Compile & run JCL and Cobol progra


IBM Mainframe Forums -> COBOL Programming
Post new topic   Reply to topic
View previous topic :: View next topic  
Author Message
usharaniA

New User


Joined: 22 Jan 2008
Posts: 85
Location: India

PostPosted: Tue Jun 02, 2009 4:46 pm
Reply with quote

Hi,
I could not able to run my compile jcl for the cobol program , the JCL is not showing any error so i could not able to trace out what the actual error is.
The JCL which compiles and run the Cobol program is
Code:
//VALIDTR# JOB A(123),'COMPILE',MSGCLASS=X,                           
//       MSGLEVEL=(1,1),CLASS=B,REGION=5M,                             
//         NOTIFY=U162936                                             
//STEP1    EXEC IGYWCL,LNGPRFX='IGY',PARM=LIB                         
//SYSLIB DD DSN=USERID.MAP.COPYLIB(USHA),DISP=SHR                     
//SYSPRINT DD SYSOUT=*                                                 
//COBOL.SYSIN DD DSN=USERID.TOOLS.VALIDTR.TABLE(COBPGM),DISP=SHR       
//LKED.SYSLMOD DD DSN=USERID.LOADLIBS.VALIDTR(COBPGM),DISP=SHR   
//*run the cobol program     
//STEP2 EXEC PGM=COBPGM                                               
//STEPLIB DD DISP=SHR,DSN=USERID.LOADLIBS.VALIDTR                     
//DD1 DD DISP=SHR,DSN=USERID.A1.PS                                     
//DD2 DD DISP=SHR,DSN=USERID.TOOLS.VALIDTR.TEMP                       
//SYSPRINT DD SYSOUT=*                                                 
//SYSOUT DD SYSOUT=*                                                   
//SYSIN DD *                                                           


and my cobol program is
Code:
IDENTIFICATION DIVISION.                               
PROGRAM-ID. COBPGM.                                   
ENVIRONMENT DIVISION.                                 
INPUT-OUTPUT SECTION.                                 
FILE-CONTROL.                                         
     SELECT INFILE ASSIGN TO DD1.                     
     SELECT OUTFILE ASSIGN TO DD2.                     
DATA DIVISION.                                         
FILE SECTION.                                         
FD INFILE.                                             
01 IN-RECORDS                 PIC X(140).               
FD OUTFILE.                                           
01 OUT-RECORDS                 PIC X(140).             
WORKING-STORAGE SECTION.                               
 COPY   USHA.                                         
 77  EOF                       PIC 9 VALUE IS 0.       
PROCEDURE DIVISION.                                   
0000-MAIN-PARA.                                       
     OPEN INPUT INFILE                                 
          OUTPUT OUTFILE.                             
     DISPLAY 'FILES ARE OPENED SUCCESSFULLY'.         
     DISPLAY OUT-RECORDS                               
     PERFORM READ-PARA THRU READ-EXIT UNTIL EOF = 1.   
     PERFORM CLOSE-PARA THRU CLOSE-EXIT.               



The lrecl of the loadlib i used in the JCL is 140 and record format is U.
The lrecl of the DD1 and DD2 statement is also 140 and record format is FB.

if i use the lrecl of 80 for the DD1 , DD2,loadlib and if the FD section is as follows i'm getting maxcc 0.
FD INFILE.
01 IN-RECORDS PIC X(80).
FD OUTFILE.
01 OUT-RECORDS PIC X(80).


1.Is there any mismatch in the lrecl of the JCL and cobol program or is there any standard attributes should be given while allocating the loadlib.

2.Can we give maximum lrecl for the loadlib and varying lrecl in the DD1 and DD2 statement.

3.As i'm using the copybook in the working storage section i could not use
record contains..........depending on......in the FD section, if i should change the FD section what the changes i should make.
Back to top
View user's profile Send private message
Robert Sample

Global Moderator


Joined: 06 Jun 2008
Posts: 8697
Location: Dubuque, Iowa, USA

PostPosted: Tue Jun 02, 2009 5:03 pm
Reply with quote

A load library works best when defined as RECFM=U,BLKSIZE=????? and no LRECL. The load library characteristics have absolutely nothing to do with the characteristics of the files your application is reading and writing. Set the block size of the load library fairly big -- 27998 or 32760 and stop thinking about it since that has very little, if anything, to do with your problems. You should never redefine a load library just because an application is doing something different.

Add file status clauses to your COBOL ASSIGN statements and check the file status after each OPEN, READ, WRITE, REWRITE, and CLOSE to prevent future problems. This is good programming practice.

If the DCB of the defined files for DD01 and DD02 do not match the file definitions as specified in your COBOL program, your program will not run, as you have found.

Your point #3 is absolute rubbish. There is nothing, I repeat NOTHING, keeping you from using a RECORD CONTAINS clause just because you have a copy book in WORKING-STORAGE. Add a 77 level definition for the variable and away you go. Furthermore, since the files are both fixed length you have absolutely no reason to even use the RECORD CONTAINS clause in your code.

Post the DD01 and DD02 characteristics (ISPF option 3.4 and put an I beside the file. And use BBcode for this and JCL and code; it simplifies looking at the data.

Oh, and your JCL is a compile and execute -- not a compile. There should be something displayed if you have an error anywhere.
Back to top
View user's profile Send private message
usharaniA

New User


Joined: 22 Jan 2008
Posts: 85
Location: India

PostPosted: Tue Jun 02, 2009 5:27 pm
Reply with quote

DD1:Information
Code:
Data class . . . . . : **None** 
 Organization  . . . : PS       
 Record format . . . : FB       
 Record length . . . : 140       
 Block size  . . . . : 1400     
 1st extent tracks . : 1         
 Secondary tracks  . : 50             


DD2:
Code:
  Data class . . . . . : **None**   
  Organization  . . . : PS         
  Record format . . . : FB         
  Record length . . . : 140         
  Block size  . . . . : 1400       
  1st extent blocks . : 27         
  Secondary blocks  . : 50


FD Section in Cobol Program:
Code:
FILE SECTION.                                         
FD INFILE.                                             
01 IN-RECORDS                 PIC X(140).               
FD OUTFILE.                                           
01 OUT-RECORDS                 PIC X(140). 



Im not getting any error when i club the compile and the run JCL and run the DD statement which contains files of LRECL=80.
Back to top
View user's profile Send private message
Robert Sample

Global Moderator


Joined: 06 Jun 2008
Posts: 8697
Location: Dubuque, Iowa, USA

PostPosted: Tue Jun 02, 2009 5:49 pm
Reply with quote

With the files defined as in your last post, the program should do whatever it is supposed to do. Look at the SYSOUT for output. If nothing is there, add the file status clauses, add DISPLAY statements for the file status after OPEN and READ, recompile, and run again. Post the output you get.
Back to top
View user's profile Send private message
View previous topic :: :: View next topic  
Post new topic   Reply to topic View Bookmarks
All times are GMT + 6 Hours
Forum Index -> COBOL Programming

 


Similar Topics
Topic Forum Replies
No new posts WER247A SORTOUT HAS INCOMPATIBLE LRECL SYNCSORT 7
No new posts Compile Several JCL JOB Through one r... CLIST & REXX 4
No new posts Replace each space in cobol string wi... COBOL Programming 3
No new posts COBOL -Linkage Section-Case Sensitive COBOL Programming 1
No new posts COBOL ZOS Web Enablement Toolkit HTTP... COBOL Programming 0
Search our Forums:

Back to Top