Re: COBOL question: Why can't we use RECORD CONTAINS 0 CHARACTERS for RECFM=V files?

2008-12-30 Thread Kirk Talman
IBM Mainframe Discussion List IBM-MAIN@bama.ua.edu wrote on 12/17/2008 
05:16:27 PM:

  Subject: Re: COBOL question: Why can't we use RECORD CONTAINS 0
  CHARACTERS for RECFM=V files?
  
  Overriding LRECL for varying-length files simply works.
  Specify LRECL=32756 (32752?) and be done with it.
 
 Do you mean just define the COBOL FD as RECORD CONTAINS 0 TO 32756
 CHARACTERS and then use LRECL=32760 as a JCL override for a file no
 matter what it's variable max length is?
 
 Have not tried that but I certainly will.  Thanks!
 
 Peter

I am very interested in this because I gave someone advice on this 
recently.

So I coded a small program to test my memory (see below).

I get this error message of the actual LRECL of input file is not the same 
as the implied LRECL from 01(s) under the FD.

So yes you need a JCL override that matches the program.  Or else some 
parameter I have been unable to define.

richard

IGZ0201W A file attribute mismatch was detected. File QSAMVARIABLE in 
program T the file specified in the ASSIGN clause had a record length of 
255.
39

IDENTIFICATION DIVISION.
PROGRAM-ID.  TSNOTIFX.
***
Environment Division.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT QsamVariableASSIGN  I
   FILE STATUS  IS InStatusWs.
***
DATA DIVISION.
File Section.
FD  QsamVariable
Record varying.
01  InRecord1.
  05 InData1 PIC X.
01  InRecord2.
  05 InData2 PIC XX.
***
Working-Storage Section.
01.
  05 PIC X VALUE SPACE.
88 InEof   VALUE 'E'.
88 InInit  VALUE SPACE.
  05 InStatusWs  PIC 99.
***
PROCEDURE DIVISION.
OPEN INPUT QsamVariable
DISPLAY '' InStatusWs ''
READ QsamVariable
  AT END
SET InEofTO TRUE
  NOT AT END
DISPLAY '' InData1 ''
DISPLAY '' InData2 ''
END-READ
Goback
.

-
The information contained in this communication (including any
attachments hereto) is confidential and is intended solely for the
personal and confidential use of the individual or entity to whom
it is addressed. If the reader of this message is not the intended
recipient or an agent responsible for delivering it to the intended
recipient, you are hereby notified that you have received this
communication in error and that any review, dissemination, copying,
or unauthorized use of this information, or the taking of any
action in reliance on the contents of this information is strictly
prohibited. If you have received this communication in error,
please notify us immediately by e-mail, and delete the original
message. Thank you 

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html


COBOL question: Why can't we use RECORD CONTAINS 0 CHARACTERS for RECFM=V files?

2008-12-17 Thread Farley, Peter x23353
I was asked this question from an internal source and I don't know the
answer myself, so I am hoping someone here does. 

The business task is to be able to handle multiple varying-length
sequentially-accessed input files, each with different LRECL values,
from a single COBOL file definition, as can be done now with
fixed-length input files.

Current Enterprise COBOL (we're at V3.4) allows you to specify RECORD
CONTAINS 0 CHARACTERS in the FD for a file, but for fixed-format files
only.  This specification allows the same FD definition to be used for
input files with different LRECL values in different jobs using the same
program.

The program, of course, must be prepared to recognize the different
input LRECL values and do something sensible with each one.  In our case
we use an assembler subroutine to issue RDJFCB to find out what the
actual DCB LRECL is after OPEN (is there a COBOL way to do this?), and
then we use READ followed by a move with a range qualifier (move
data-name (1:reclength) to ...) into the appropriate structure.

Why can't that same phrase (or an equivalent one) be used for
varying-length files?  The Enterprise COBOL compiler gives the following
error if you try:

Or is there an alternative COBOL-only solution for varying-length files
that none of us have thought of yet?  The solution of using an assembler
subroutine to do dynamic DCB control block building and I/O functions
has already been considered and rejected, even though assembler has to
be used now for the RDJFCB function.

TIA for any info you can provide.

Peter
This message and any attachments are intended only for the use of the addressee 
and
may contain information that is privileged and confidential. If the reader of 
the 
message is not the intended recipient or an authorized representative of the
intended recipient, you are hereby notified that any dissemination of this
communication is strictly prohibited. If you have received this communication in
error, please notify us immediately by e-mail and delete the message and any
attachments from your system.


--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html


Re: COBOL question: Why can't we use RECORD CONTAINS 0 CHARACTERS for RECFM=V files?

2008-12-17 Thread Paul Gilmartin
On Wed, 17 Dec 2008 16:55:55 -0500, Farley, Peter x23353 wrote:

I was asked this question from an internal source and I don't know the
answer myself, so I am hoping someone here does.

The business task is to be able to handle multiple varying-length
sequentially-accessed input files, each with different LRECL values,
from a single COBOL file definition, as can be done now with
fixed-length input files.

Overriding LRECL for varying-length files simply works.
Specify LRECL=32756 (32752?) and be done with it.

-- gil

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html


Re: COBOL question: Why can't we use RECORD CONTAINS 0 CHARACTERS for RECFM=V files?

2008-12-17 Thread John McKown
I've always used:

RECORD CONTAINS 0 TO 32767 CHARACTERS DEPENDING ON var-name

and then define var-name in WORKING-STORAGE to be a 77 level with the
PICTURE of S9(9) BINARY.

--
John

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html


Re: COBOL question: Why can't we use RECORD CONTAINS 0 CHARACTERS for RECFM=V files?

2008-12-17 Thread Farley, Peter x23353
 -Original Message-
 From: IBM Mainframe Discussion List [mailto:ibm-m...@bama.ua.edu] On
 Behalf Of Paul Gilmartin
 Sent: Wednesday, December 17, 2008 5:08 PM
 To: IBM-MAIN@bama.ua.edu
 Subject: Re: COBOL question: Why can't we use RECORD CONTAINS 0
 CHARACTERS for RECFM=V files?
 
 Overriding LRECL for varying-length files simply works.
 Specify LRECL=32756 (32752?) and be done with it.

Do you mean just define the COBOL FD as RECORD CONTAINS 0 TO 32756
CHARACTERS and then use LRECL=32760 as a JCL override for a file no
matter what it's variable max length is?

Have not tried that but I certainly will.  Thanks!

Peter
This message and any attachments are intended only for the use of the addressee 
and
may contain information that is privileged and confidential. If the reader of 
the 
message is not the intended recipient or an authorized representative of the
intended recipient, you are hereby notified that any dissemination of this
communication is strictly prohibited. If you have received this communication in
error, please notify us immediately by e-mail and delete the message and any
attachments from your system.


--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html


Re: COBOL question: Why can't we use RECORD CONTAINS 0 CHARACTERS for RECFM=V files?

2008-12-17 Thread Ted MacNEIL
Do you mean just define the COBOL FD as RECORD CONTAINS 0 TO 32756 CHARACTERS 
and then use LRECL=32760 as a JCL override for a file no matter what it's 
variable max length is?

I don't believe you need the JCL override.
-
Too busy driving to stop for gas!

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html


COBOL question: Why can't we use RECORD CONTAINS 0 CHARACTERS for RECFM=V files?

2008-12-17 Thread Bill Klein
Hopefully, you mean
  RECORD VARYING IN SIZE from 0 to 32767 depending on var-name

I do NOT think you can use RECORD CONTAINS with the DEPENDING onphrase.

John McKown joa...@swbell.net wrote in message
news:listserv%20081217160815.1...@bama.ua.edu...
 I've always used:
 
 RECORD CONTAINS 0 TO 32767 CHARACTERS DEPENDING ON var-name
 
 and then define var-name in WORKING-STORAGE to be a 77 level with the
 PICTURE of S9(9) BINARY.
 
 --
 John
 
 --
 For IBM-MAIN subscribe / signoff / archive access instructions,
 send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
 Search the archives at http://bama.ua.edu/archives/ibm-main.html

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html


COBOL question: Why can't we use RECORD CONTAINS 0 CHARACTERS for RECFM=V files?

2008-12-17 Thread Bill Klein
I am not positive of this, but I think you DO need the JCL override.  If the
hard coded maximum LRECL in the FD does NOT match the maximum for the
physical file and you don't have the JCL override, I believe you will get a
file status of 39 when you OPEN the file indicating a physical file
attribute conflict.

As indicated elsewhere in the thread, I recommend using the
  RECORD VARYING IN SIZE
rather than
  RECORD CONTAINS

form for the FD of a variable length file.  (Among other things, this allows
you to determine the actual record length after every read - without
negative subscripting to get the LLZZ information from the RDW)

FYI,
  There is an existing SHARE requirement for getting COBOL to (better)
handle SMS information without worrying about coding FD stuff. 

Ted MacNEIL eamacn...@yahoo.ca wrote in message
news:756912698-1229553371-cardhu_decombobulator_blackberry.rim.net-61158795
8...@bxe348.bisx.prod.on.blackberry...
 Do you mean just define the COBOL FD as RECORD CONTAINS 0 TO 32756
CHARACTERS and then use LRECL=32760 as a JCL override for a file no matter
what it's variable max length is?
 
 I don't believe you need the JCL override.
 -
 Too busy driving to stop for gas!

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html


Re: COBOL question: Why can't we use RECORD CONTAINS 0 CHARACTERS for RECFM=V files?

2008-12-17 Thread Ted MacNEIL
I am not positive of this, but I think you DO need the JCL override.

There is a better way than discussing it.
Test it.

Unfortunately, I can't at the moment.
(Can you say 'downsizing' boys  girls?)

-
Too busy driving to stop for gas!

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html


Re: COBOL question: Why can't we use RECORD CONTAINS 0 CHARACTERS for RECFM=V files?

2008-12-17 Thread Clark Morris
On 17 Dec 2008 14:37:47 -0800, in bit.listserv.ibm-main you wrote:

Do you mean just define the COBOL FD as RECORD CONTAINS 0 TO 32756 CHARACTERS 
and then use LRECL=32760 as a JCL override for a file no matter what it's 
variable max length is?

I don't believe you need the JCL override.

You DO because of the terminal *** of the compiler/runt-time
designers.
-
Too busy driving to stop for gas!


--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html


Re: COBOL question: Why can't we use RECORD CONTAINS 0 CHARACTERS for RECFM=V files?

2008-12-17 Thread Paul Gilmartin
On Wed, 17 Dec 2008 19:26:01 -0400, Clark Morris wrote:

On 17 Dec 2008 14:37:47 -0800, in bit.listserv.ibm-main you wrote:

Do you mean just define the COBOL FD as RECORD CONTAINS 0 TO 32756 
CHARACTERS and then use LRECL=32760 as a JCL override for a file no matter 
what it's variable max length is?

I don't believe you need the JCL override.

You DO because of the terminal *** of the compiler/runt-time
designers.
-
They probably used the same validation code for output, where
it makes sense, and for input, where an inequality would
suffice.

-- gil

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@bama.ua.edu with the message: GET IBM-MAIN INFO
Search the archives at http://bama.ua.edu/archives/ibm-main.html