Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

Dynamic file allocation on IBM mainframe

68 views
Skip to first unread message

Howard Brazee

unread,
Jul 22, 2002, 12:53:06 PM7/22/02
to
Someone had some code for dynamic file allocation from within IBM Cobol, but
I have had some trouble getting it to work.

Here's some code:
FD TEST-FILE
LABEL RECORDS ARE STANDARD
RECORDING MODE IS F
BLOCK CONTAINS 0 RECORDS.
01 TEST-RECORD PIC X(80).
WORKING-STORAGE SECTION.
01 TEST-STATUS PIC XX.
01 RC PIC 9(9) COMP.
01 RC-DISPLAY PIC 9(9).
01 ADDR-POINTER USAGE IS POINTER.
01 DYNALLOC.
05 FILLER PIC X(12) VALUE
'DYNAMDD=DSN('.
05 DYN-DSN PIC X(17).
05 FILLER PIC X(90) VALUE
'NEW TRACKS SPACE(1,1) CATALOG STORCLAS(STANDARD) MGMTCLAS(WO
'RK)'.
- - - - - - - - - - - - - - - 6 Line(s) not Displayed
MOVE 'D5.P.NOR.GDGTEST(+1))' TO DYN-DSN.
- - - - - - - - - - - - - - - 3 Line(s) not Displayed
CALL 'PUTENV'
USING BY VALUE ADDR-POINTER
RETURNING RC.
IF RC NOT = ZERO
MOVE RC TO RC-DISPLAY
DISPLAY 'PUTENV FAILED, RC = ' RC-DISPLAY
GOBACK.
OPEN OUTPUT TEST-FILE.


One thing, we don't have GDGs available here which may be part of my problem
- but I changed the file name. I would like to dynamically send the output
to either a file or a printer with forms and destination. I got a file
status of 98 and "IGZ0252W An invalid delimiter was found at position 22 in
environment variable DYNAMDD while processing file TEST-FILE".

What should I play with to get this working?

William M. Klein

unread,
Jul 22, 2002, 1:46:08 PM7/22/02
to
Howard,
A couple of things:

1) To use "putenv" and be supported you *must* use NODYNAM and
PGMNAME(LONGMIXED). See:
http://publib.boulder.ibm.com/cgi-bin/bookmgr/BOOKS/igy3pg00/3.4.3


2) The correct name of the program to call is "putenv" *not* "PUTENV". See:
http://publib.boulder.ibm.com/cgi-bin/bookmgr/BOOKS/igy3pg00/3.4.2.4


Finally, I am NOT positive that GDG's are supported. Have you tried the
same program with a "simple" DSName? I am going to check further on this.

--
Bill Klein
wmklein <at> ix.netcom.com
"Howard Brazee" <howard...@cusys.edu> wrote in message
news:ahhd8i$kl$1...@peabody.colorado.edu...

Howard Brazee

unread,
Jul 22, 2002, 2:59:01 PM7/22/02
to

On 22-Jul-2002, "William M. Klein" <wmk...@nospam.ix.netcom.com> wrote:

> 1) To use "putenv" and be supported you *must* use NODYNAM and
> PGMNAME(LONGMIXED). See:
> http://publib.boulder.ibm.com/cgi-bin/bookmgr/BOOKS/igy3pg00/3.4.3

I compiled with PGM NODYNAM, but didn't try PGMNAME(LONGMIXED) (unless
that's the default). Changing compile parms is a pain when I have to use
Endevor to move to production.


> 2) The correct name of the program to call is "putenv" *not* "PUTENV".
> See:
> http://publib.boulder.ibm.com/cgi-bin/bookmgr/BOOKS/igy3pg00/3.4.2.4

I am so used to having caps on with TSO. Will change and leave a note.


> Finally, I am NOT positive that GDG's are supported. Have you tried the
> same program with a "simple" DSName? I am going to check further on this.

The sample code I cribbed from is a GDG. I don't want GDGs - I want a
simple dataset and would also like the ability to switch to a SYSOUT such as
'R,FCB=941S'


Thanks, I'll check into these.

Howard Brazee

unread,
Jul 22, 2002, 3:24:51 PM7/22/02
to

On 22-Jul-2002, "William M. Klein" <wmk...@nospam.ix.netcom.com> wrote:

> 1) To use "putenv" and be supported you *must* use NODYNAM and
> PGMNAME(LONGMIXED). See:
> http://publib.boulder.ibm.com/cgi-bin/bookmgr/BOOKS/igy3pg00/3.4.3
>
>
> 2) The correct name of the program to call is "putenv" *not* "PUTENV".
> See:
> http://publib.boulder.ibm.com/cgi-bin/bookmgr/BOOKS/igy3pg00/3.4.2.4

I added PGM(LONGMIXED) and changed to a lower case call, but it didn't
compile cleanly:
A user-defined word was found as a "PROGRAM-ID" name under the
"PGMNAME(LONGMIXED)" compiler option. When
"PGMNAME(LONGMIXED)" is in effect, a literal is expected for the
"PROGRAM-ID" name. The name was accepted in
its uppercased format.

I changed my PROGRAM-ID to lower case and put quotes around it as per the
example and it compiled OK, but didn't link:
IEW2606S 4B39 MODULE INCORPORATES PROGRAM MANAGEMENT 3 FEATURES AND CANNOT
BE SAVED IN LOAD MODULE FORMAT.

What does it mean having a PROGRAM-ID lower case in quotes? Is that field
used? Is it's name meaningful? Why won't it compile?

Thanks for your help.

William M. Klein

unread,
Jul 22, 2002, 6:20:28 PM7/22/02
to
The world of LONGMIXED and/or POSIX is "confusing".

If you compile with LONGMIXED, you want your PROGRAM-ID to be in quotes -
but it may (probably SHOULD BE) all CAPS. HOWEVER, you want your CALL
"literal" (putenv) to be lower-case.

Hope this helps.

P.S. You can put PGMNAME(LONGMIXED) in a CBL card *in* your source code and
not require Endevor to process it for you.

--
Bill Klein
wmklein <at> ix.netcom.com
"Howard Brazee" <howard...@cusys.edu> wrote in message

news:ahhm52$49r$1...@peabody.colorado.edu...

Ron

unread,
Jul 22, 2002, 7:08:30 PM7/22/02
to
I am the originator of this program. When I tested this it DID
work.

1) NODYNAM *WAS* required. Despite what the manual says, PGMNAME(LONGMIXED)
*WAS NOT* required. PGMNAME(COMPAT) worked just fine. To use LONGMIXED
you MUST use the pre-linker before the link, with COMPAT you do not need
the pre-link.

2) Despite what the manual says both 'PUTENV' and 'putenv' worked the same.

3) GDG's *ARE* supported and worked fine.

I suspect the posters problem is PIC X(17) for DYN-DSN. Either he
has truncated the closing ')' for his dataset name or has not included
the required SPACE after it.


----------------------------------------------------------------------------


"William M. Klein" <wmk...@nospam.ix.netcom.com> wrote in message news:ahhge3$e1i$1...@slb6.atl.mindspring.net...

Ron

unread,
Jul 22, 2002, 7:10:24 PM7/22/02
to
The dataset name must have a closing ')' and a SPACE afterward.
Are you truncating the SPACE with pic x(17)?


"Howard Brazee" <howard...@cusys.edu> wrote in message news:ahhd8i$kl$1...@peabody.colorado.edu...

William M. Klein

unread,
Jul 22, 2002, 8:09:20 PM7/22/02
to
Ron,
Sorry - I thought that I posted this already - but may not have. The
following is what IBM says about NOT using LONGMIXED and/or using PUTENV,

"Bill,

PUTENV and GETENV might work, but it is not documented in any C or LE books.

C function names are mangled to get them down to 8 characters, but in the
case of short names the name is sometimes just folded to uppercase in
SCEELKED.

This cannot be counted on, in general, and other C functions may not behave
this way.
Using LONGMIXED, BINDER, and SCEELKEX will work for ALL C functions, while
trying to call lowercase function names with uppercase is guaranteed to fail
in most cases. For example, how would you call _getenv (different from
getenv)?"

As far as LONGMIXED and the pre-linker, can you say WHY you think this is
required? According to:
http://publib.boulder.ibm.com/cgi-bin/bookmgr/BOOKS/igy3pg00/2.4.39.3

"When using the extended character set supported by PGMNAME(LONGMIXED), be
sure to use names that conform to the linkage-editor, binder, prelinker, or
system conventions that apply, depending on the mechanism used to resolve
the names. "

but I haven't tried it without this - so you MIGHT be correct.

--
Bill Klein
wmklein <at> ix.netcom.com

"Ron" <No...@swbell.net> wrote in message
news:ahi39f$dpe$1...@nntp-m01.news.aol.com...

Harry Carter

unread,
Jul 22, 2002, 8:36:12 PM7/22/02
to
On Mon, 22 Jul 2002 17:20:28 -0500, "William M. Klein"
<wmk...@nospam.ix.netcom.com> wrote:

>The world of LONGMIXED and/or POSIX is "confusing".
>
>If you compile with LONGMIXED, you want your PROGRAM-ID to be in quotes -
>but it may (probably SHOULD BE) all CAPS. HOWEVER, you want your CALL
>"literal" (putenv) to be lower-case.

??I compiled a program successfully using good old fashioned full caps
using Cobol for OS/390.including my call to putenv.

Harry Carter

unread,
Jul 22, 2002, 8:41:31 PM7/22/02
to

When I played around with getting this to work at my shop, I
discovered that contrary to the manuals, I needed commas between the
various parms (space, disp, etc). I got nasty soc4's without it
whining about invalid delimiters. The manual claims spaces work. For
me they didn't. I needed commas.

Charles Hottel

unread,
Jul 22, 2002, 8:46:42 PM7/22/02
to
Here is another way:

IDENTIFICATION DIVISION.
PROGRAM-ID. COBDYNAL.
*===============================================================*
* This program dynamically allocates and deallocates a file
* using the BPXWDYN IBM subroutine. No DD statements for the
* file sould appear in the JCL:
*===============================================================*
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT FILEIN ASSIGN TO FILEIN.
/
DATA DIVISION.
FILE SECTION.
FD FILEIN
RECORD CONTAINS 80 CHARACTERS
RECORDING MODE IS F
LABEL RECORDS ARE STANDARD
BLOCK CONTAINS 0 CHARACTERS
DATA RECORD IS FILEIN-REC.
01 FILEIN-REC.
05 FILLER PIC X(80).

WORKING-STORAGE SECTION.
01 INPUT-REC PIC X(80).
01 IN-COUNT PIC 9(9) BINARY VALUE 0.
01 SUB-PGM PIC X(8) VALUE 'BPXWDYN '.
01 ALLOC-CMD.
05 FILLER PIC X(50) VALUE
' ALLOC DD(FILEIN) DSN(EGHF3PY.TEMP80 MSG(WTP) OLD '.
05 FILLER PIC X(50) VALUE
' '.

01 COMMAND-STRING.
05 C-S-LEN PIC S9(4) BINARY VALUE +100.
05 C-S-DATA.
07 FILLER PIC X(100).
/
PROCEDURE DIVISION.
INITIAL-STUFF.

MOVE ALLOC-CMD TO C-S-DATA.
CALL SUB-PGM USING COMMAND-STRING.

OPEN INPUT FILEIN.

READER.
READ FILEIN INTO INPUT-REC,
AT END GO TO E-O-J.
ADD +1 TO IN-COUNT.
DISPLAY FILEIN-REC.
GO TO READER.

E-O-J.
CLOSE FILEIN.
MOVE 'FREE DD(FILEIN)' TO C-S-DATA.
CALL SUB-PGM USING COMMAND-STRING.
GOBACK.

Howard Brazee <howard...@cusys.edu> wrote in article
<ahhd8i$kl$1...@peabody.colorado.edu>...

Charles Hottel

unread,
Jul 22, 2002, 9:27:43 PM7/22/02
to
Or if you prefer using the TSo ALLOC command:

IDENTIFICATION DIVISION.
PROGRAM-ID. CB2TSOEV.
******************************************************************
* *
* MODULE NAME = COB2TSO *
* *
* DESCRIPTIVE NAME = ISSUE TSO COMMANDS FROM A COBOL PROGRAM. *
* *
* FUNCTION = THIS SAMPLE PROGRAM DEMONSTRATES HOW TO INVOKE *
* TSO COMMANDS FROM A COBOL PROGRAM USING *
* STANDARD TSO SERVICES AS DOCUMENTED IN THE *
* TSO/E PROGRAMMING SERVICES MANUAL. *
* *
* MOST TSO COMMANDS, INCLUDING CLISTS AND REXX *
* EXECS CAN BE EXECUTED USING THIS TECHNIQUE. *
* TSO COMMANDS WHICH REQUIRE AUTHORIZATION *
* (SUCH AS OUTPUT, SEND, TRANSMIT AND RECEIVE) *
* WILL NOT WORK. *
* *
* AUTHOR = GILBERT SAINT-FLOUR <G...@POBOX.COM> *
* *
******************************************************************
/
DATA DIVISION.
WORKING-STORAGE SECTION.
01 FILLER.
05 WS-DUMMY PIC S9(8) COMP.
05 WS-RETURN-CODE PIC S9(8) COMP.
05 WS-REASON-CODE PIC S9(8) COMP.
05 WS-INFO-CODE PIC S9(8) COMP.
05 WS-CPPL-ADDRESS PIC S9(8) COMP.
05 WS-FLAGS PIC X(4) VALUE X'00010001'.
05 WS-BUFFER PIC X(256).
05 WS-LENGTH PIC S9(8) COMP VALUE 256.
/
PROCEDURE DIVISION.
*----------------------------------------------------------------*
* CALL IKJTSOEV TO CREATE THE TSO/E ENVIRONMENT *
*----------------------------------------------------------------*
CALL 'IKJTSOEV' USING WS-DUMMY
WS-RETURN-CODE
WS-REASON-CODE
WS-INFO-CODE
WS-CPPL-ADDRESS.
IF WS-RETURN-CODE > ZERO
DISPLAY 'IKJTSOEV FAILED, RETURN-CODE=' WS-RETURN-CODE
' REASON-CODE=' WS-REASON-CODE
'INFO-CODE=' WS-INFO-CODE
MOVE WS-RETURN-CODE TO RETURN-CODE
STOP RUN.
*----------------------------------------------------------------*
* BUILD THE TSO/E COMMAND IN WS-BUFFER *
*----------------------------------------------------------------*

MOVE 'ALLOCATE DD(SYSPUNCH) SYSOUT HOLD' TO WS-BUFFER.

*----------------------------------------------------------------*
* CALL THE TSO/E SERVICE ROUTINE TO EXECUTE THE TSO/E COMMAND *
*----------------------------------------------------------------*
CALL 'IKJEFTSR' USING WS-FLAGS
WS-BUFFER
WS-LENGTH
WS-RETURN-CODE
WS-REASON-CODE
WS-DUMMY.
IF WS-RETURN-CODE > ZERO
DISPLAY 'IKJEFTSR FAILED, RETURN-CODE=' WS-RETURN-CODE
' REASON-CODE=' WS-REASON-CODE
MOVE WS-RETURN-CODE TO RETURN-CODE
STOP RUN.

*----------------------------------------------------------------*
* CHECK THAT THE ALLOCATE COMMAND WORKED *
*----------------------------------------------------------------*
DISPLAY 'ALLOCATE WORKED ! ' UPON SYSPUNCH.

STOP RUN.

Howard Brazee <howard...@cusys.edu> wrote in article
<ahhd8i$kl$1...@peabody.colorado.edu>...

Howard Brazee

unread,
Jul 23, 2002, 9:37:03 AM7/23/02
to
I'll try that. At first glance, it appears that there's an unbalanced
parenthesis in:

Howard Brazee

unread,
Jul 23, 2002, 9:53:48 AM7/23/02
to
With or without a closing parenthesis I am getting a file status 35 with my
open

My last test was changed to:

01 ALLOC-CMD.
05 FILLER PIC X(50) VALUE

' ALLOC DD(FILEIN) DSN(UMS.D44201.DYN) '.


05 FILLER PIC X(50) VALUE

' MSG(WTP) OLD '.

Does this allocate catalog the dataset?

What happens if the dataset already exists?

Howard Brazee

unread,
Jul 23, 2002, 10:13:31 AM7/23/02
to
My mistake - looking at it, it's obviously an input file - and the program
works fine.

How do I change it to allocate and catalog an output file? (which may or
may not exist)?

Can I dynamically pick a SDSF form for output?

Ron

unread,
Jul 23, 2002, 12:41:01 PM7/23/02
to
> As far as LONGMIXED and the pre-linker, can you say WHY you think this is
> required? According to:
> http://publib.boulder.ibm.com/cgi-bin/bookmgr/BOOKS/igy3pg00/2.4.39.3
>
> "When using the extended character set supported by PGMNAME(LONGMIXED), be
> sure to use names that conform to the linkage-editor, binder, prelinker, or
> system conventions that apply, depending on the mechanism used to resolve
> the names. "
>
> but I haven't tried it without this - so you MIGHT be correct.

When using LONGMIXED I believe certain LE elements are included in the
load module that otherwise are not included. The pre-link resolves these
LE modules in preparation for the final link. Anyway, if you do not
pre-link when using LONGMIXED you get this error from the link-edit.

IEW2606S 4B39 MODULE INCORPORATES PROGRAM MANAGEMENT 3 FEATURES AND CANNOT
BE SAVED IN LOAD MODULE FORMAT.

When you do pre-link, the final link works successfully.


john gilmore

unread,
Jul 23, 2002, 1:39:38 PM7/23/02
to
What the binder message IEW2606S 4B39 . . .

is telling you is that (not LE features but) features usable only when a PDSE-resident program object (not a load module) is to be produced have been found in its input.
'Program management' is IBM jargon for the DFSMS Binder and PMLoader.

John Gilmore

The opinions expressed above are mine alone. In particular, they are not necessarily shared by my company or its clients.

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

William M. Klein

unread,
Jul 23, 2002, 4:29:03 PM7/23/02
to
Ron,
What was your setting for the DLL compiler option? As indicated in
IBM-MAIN, the messages that you are getting have to do with PDSE vs PDS -
not PGMNAME (or at least not that I know of).

If you look at:
http://publib.boulder.ibm.com/cgi-bin/bookmgr/BOOKS/igy3pg00/4.3.4

It does say that *IF* you are creating a DLL *and* you do not use PDSE, THEN
you must use the pre-linker. However, I don't see anything (but could be
missing it) that says that you must use DLL's if you are using
PGMNAME(LONGMIXED).

--
Bill Klein
wmklein <at> ix.netcom.com
"Ron" <No...@swbell.net> wrote in message

news:ahk0ut$1vs$1...@nntp-m01.news.aol.com...

Ron

unread,
Jul 23, 2002, 6:16:31 PM7/23/02
to
I cannot check the setting for the compiler option because I no longer work
at the company where I was doing this testing. :(
But what you say does make sense to me. Pgmname(longmixed) in all probability
forces the DLL option and I was linking to a PDS not a PDSE thus requiring
the prelink.

"William M. Klein" <wmk...@nospam.ix.netcom.com> wrote in message news:ahkear$d4s$1...@slb6.atl.mindspring.net...

Charles Hottel

unread,
Jul 23, 2002, 9:34:26 PM7/23/02
to
I got this code from an earlier posting and am no expert. I will
investigate the unbalanced parenthesis. You can find documentation for
BPXWDYN at:

ftp://ftp.software.ibm.com/s390/zos/tools/bpxwdyn/bpxwdyn.html

I believe what you coded below is equivalent to:

//FILEIN DD DSN=UMS.D44201.DYN,DISP=OLD

MSG(WTP) causes messages to be written to the job log.

Since the dataset already exists (OLD) the DCB in your program is filled in
so that it points to the DSN=
just as if you coded the JCL above. You can open it and process it and
close it. Then if you FREE it you can the do another ALLOC and make the
DCB point to another file that you want to process.

Howard Brazee <howard...@cusys.edu> wrote in article

<ahjn4b$6in$1...@peabody.colorado.edu>...

Charles Hottel

unread,
Jul 23, 2002, 9:34:27 PM7/23/02
to
See: ftp://ftp.software.ibm.com/s390/zos/tools/bpxwdyn/bpxwdyn.html

The above explains all the various parameters accepted by BPXWDYN better
than I can.

I am not sure what an "SDSF form" is. I believe SDSF is a TSO option for
looking at job output? If it is a dataset you should be able to allocate
it. Depending upon the parameters you use, the most common problem you
might experience is contention for a dataset. If you specify OLD and some
other job is already using the dataset, your job may have to wait to get
exculsive control of the dataset.

Howard Brazee <howard...@cusys.edu> wrote in article

<ahjo9a$72i$1...@peabody.colorado.edu>...

Howard Brazee

unread,
Jul 24, 2002, 11:14:04 AM7/24/02
to
I have the code working - my CoBOL can read a file, and it can write a file
- but I haven't yet found the CLIST commands to catalog it. It writes the
output file and then deletes it - which has limited utility.

So I am going through CLIST manuals on-line trying to figure out the
following commands:

DISP=(NEW,CATLG,DELETE)
DISP=(MOD,DELETE)

I figure I should do a MOD,DELETE in case it exists, then a FREE then open
it again for output with NEW,CATLG,DELETE.

However there may be a better solution for this need. I want to create a
file (which may or may not exist), that is named within the CoBOL program,
write to it, and have it available cataloged when I am done.

Howard Brazee

unread,
Jul 24, 2002, 11:38:13 AM7/24/02
to
I try code such as:
MOVE 'DELETE ''UMS.D44201.TEST'' '
TO C-S-DATA
CALL SUB-PGM USING COMMAND-STRING.
DISPLAY 'DELETE RETURN-CODE="' RETURN-CODE '"'.

MOVE 'FREE ''UMS.D44201.TEST'' '
TO C-S-DATA
CALL SUB-PGM USING COMMAND-STRING.
DISPLAY ' FREE RETURN-CODE="' RETURN-CODE '"'.

But the return-code is 002K both cases if the file does exist and is
cataloged (I cataloged it with
STRING 'ALLOC DD(FILEOUT) DSN(''UMS.D44201.TEST'') NEW '
' UNIT(DEVEDISK) CYL SPACE(05,05) CATALOG '
DELIMITED BY SIZE
)

Actually, it may be better to check to see if the file exists. If it does,
I increment part of the file name and try again. But it has to be done from
within the CoBOL program. Both commands - to verify its existence, and to
delete it (whether or not it exists) would be useful.

Jim Harrison

unread,
Jul 24, 2002, 12:54:39 PM7/24/02
to
I haven't been following this thread closely and I'm not up on COBOL's
dynamic allocation capabilities, but if you are interested, I have some
assembler dynamic allocation modules you might want to look at.

http://jim_harrison2.tripod.com/files/dynallo2.zip

At 03:38 PM 7/24/2002 +0000 Howard Brazee said:
>Actually, it may be better to check to see if the file exists. If it does,
>I increment part of the file name and try again. But it has to be done from
>within the CoBOL program. Both commands - to verify its existence, and to
>delete it (whether or not it exists) would be useful.

----------------------------------------------------------------------

Charles Hottel

unread,
Jul 24, 2002, 9:31:20 PM7/24/02
to
This reply is based solely upon reading the documentation from the URL that
I posted.
For ALLOC the following specifiy dataset status: MOD, NEW, OLD, SHR and the
following specify data set disposition: CATALOG, DELETE, KEEP, UNCATALOG.

The equivalent to DISP=(NEW,CATLG,DELETE) would be:
ALLOC NEW CATALOG DD(----) DSN(----) followed later by:
ALLOC OLD DELETE DD(----) DSN(----)

The equivalent to DISP=(MOD,DELETE) would be :
ALLOC MOD DELETE DD(-----) DSN(----)

The documentation advices that it is easier to understand messages via
MSG(WTP) than trying to deal with the return codes.

For FREE the following dispositions are available: CATALOG, DELETE, KEEP,
UNCATALOG
If you don't specify one of these with your FREE it probably does not know
what to do with your request.

I re-tested my original posting with and without the missing parenthesis
and it worked fine on my system both ways. I am pretty busy right now or I
would experiment and get back to you with my results. Again I have NOT yet
tested my recommendation from above. Please let us know the solution that
you finally arrive at. Thanks.

Howard Brazee <howard...@cusys.edu> wrote in article

<ahmg6q$gel$1...@peabody.colorado.edu>...

Liam Devlin

unread,
Jul 30, 2002, 11:13:04 AM7/30/02
to
Howard Brazee wrote:
> On 22-Jul-2002, "William M. Klein" <wmk...@nospam.ix.netcom.com> wrote:
>
>
>>1) To use "putenv" and be supported you *must* use NODYNAM and
>>PGMNAME(LONGMIXED). See:
>> http://publib.boulder.ibm.com/cgi-bin/bookmgr/BOOKS/igy3pg00/3.4.3
>
>
> I compiled with PGM NODYNAM, but didn't try PGMNAME(LONGMIXED) (unless
> that's the default). Changing compile parms is a pain when I have to use
> Endevor to move to production.
>
>
>
>>2) The correct name of the program to call is "putenv" *not* "PUTENV".
>>See:
>> http://publib.boulder.ibm.com/cgi-bin/bookmgr/BOOKS/igy3pg00/3.4.2.4
>
>
> I am so used to having caps on with TSO.

ACK! That is so 60's.

Liam Devlin

unread,
Jul 30, 2002, 9:55:54 PM7/30/02
to
Howard Brazee wrote:
> I have the code working - my CoBOL can read a file, and it can write a file
> - but I haven't yet found the CLIST commands to catalog it. It writes the
> output file and then deletes it - which has limited utility.

CLIST? Ick! IMHO you'be much better off looking into REXX for this
(CLIST is a dead product).

I wrote a REXX program to do this for our ISPF environment. What you can
do is to try first to ALLOC the file as OLD. If that works, you're done,
else ALLOC it NEW, which would look something like (this is just off the
top):

Alloc_Routine:
/**********************************************************/
/* DSN is passed as a parm when Alloc_Routine is called */
/**********************************************************/
ARG dsn_name .

DSN_status = SYSDSN(dsn_name)

If DSN_status = "OK"
Then Do
"ALLOC DSN('"dsn_name"') OLD REUSE"
AllocRC = RC
Else Do
"ALLOC DSN('"dsn_name"') NEW CATLG SPACE(CYL,1,1) UNIT(SYSDA)" ,
"LRECL(80) BLKSIZE(0)..."
AllocRC = RC
End

If AllocRC = 0
Then Nop
Else Say "Unable to Allocate DSN("dsn_name"), RC="AllocRC

Return AllocRC


If it's writing it & deleting it in the same step, sounds as though it's
a temporary dataset, otherwise you'd be able to find it on the volume
shown when it's allocated.

Edward E. Jaffe

unread,
Jul 30, 2002, 10:13:20 PM7/30/02
to
Liam Devlin wrote:
> Howard Brazee wrote:
>
>> I have the code working - my CoBOL can read a file, and it can write a
>> file
>> - but I haven't yet found the CLIST commands to catalog it. It writes
>> the
>> output file and then deletes it - which has limited utility.
>
> CLIST? Ick! IMHO you'be much better off looking into REXX for this
> (CLIST is a dead product).

Huh??? I like REXX too. But there are still powerful things CLIST can do
that REXX cannot. I don't consider it a dead language at all. We deliver
some fairly sophisticated CLISTs with our products. These CLISTs take
advantage of intrinsic CLIST capabilities that do *NOT* exist in REXX!

--
-----------------------------------------------------------------
| Edward E. Jaffe | |
| Mgr, Research & Development | edj...@phoenixsoftware.com |
| Phoenix Software International | Tel: (310) 338-0400 x318 |
| 5200 W Century Blvd, Suite 800 | Fax: (310) 338-0801 |
| Los Angeles, CA 90045 | http://www.phoenixsoftware.com |
-----------------------------------------------------------------

Thomas Conley

unread,
Jul 30, 2002, 10:31:46 PM7/30/02
to
----- Original Message -----
From: "Liam Devlin" <Li...@optonline.NOSPAM.net>
Newsgroups: bit.listserv.ibm-main,comp.lang.cobol
Sent: Tuesday, July 30, 2002 9:55 PM
Subject: Re: Dynamic file allocation on IBM mainframe


> Howard Brazee wrote:
> > I have the code working - my CoBOL can read a file, and it can write a
file
> > - but I haven't yet found the CLIST commands to catalog it. It writes
the
> > output file and then deletes it - which has limited utility.
>
> CLIST? Ick! IMHO you'be much better off looking into REXX for this
> (CLIST is a dead product).
>

REXX under TSO is also a dead product.

Regards,
Tom Conley

ted.macneil

unread,
Jul 30, 2002, 10:36:10 PM7/30/02
to
Name 5!

-----Original Message-----
From: "Edward E. Jaffe" <edj...@PHOENIXSOFTWARE.COM>
Date: Tue, 30 Jul 2002 19:12:33
To: IBM-...@BAMA.UA.EDU
Subject: Re: Dynamic file allocation on IBM mainframe

Liam Devlin wrote:
> Howard Brazee wrote:
>
>> I have the code working - my CoBOL can read a file, and it can write a
>> file
>> - but I haven't yet found the CLIST commands to catalog it. It writes
>> the
>> output file and then deletes it - which has limited utility.
>
> CLIST? Ick! IMHO you'be much better off looking into REXX for this
> (CLIST is a dead product).

Huh??? I like REXX too. But there are still powerful things CLIST can do


that REXX cannot. I don't consider it a dead language at all. We deliver
some fairly sophisticated CLISTs with our products. These CLISTs take
advantage of intrinsic CLIST capabilities that do *NOT* exist in REXX!

--
-----------------------------------------------------------------
| Edward E. Jaffe | |
| Mgr, Research & Development | edj...@phoenixsoftware.com |
| Phoenix Software International | Tel: (310) 338-0400 x318 |
| 5200 W Century Blvd, Suite 800 | Fax: (310) 338-0801 |
| Los Angeles, CA 90045 | http://www.phoenixsoftware.com |
-----------------------------------------------------------------

----------------------------------------------------------------------


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


Ted.M...@mobile.rogers.com

Card-carrying member of "Dino's R Us" since 1981.

When the going gets stupid, the stupid get annoying!

Kumar

unread,
Jul 31, 2002, 1:32:25 AM7/31/02
to
Hello everybody,

So much been talked about PUTENV and dynamic file allocation in cobol.
I need some help here...I replicated the program from naspa document
and it will not work for. Got a compiler error which is:

IGYPS2160-S The "ADDRESS OF" operand "FILE-VARIABLE" was found as the
sending operand of a "SET" statement, but was not a
"LINKAGE SECTION" item, or was a level-66 or level-88 item. The
statement was discarded.

From the compiler listing, I get this message, which I hope is the
cobol version:
PP 5688-197 IBM COBOL for MVS and VM 1.2.0 . Hope this version is okay
for this module.

If this is wrong version of cobol, what more needs to be done to
achieve the same thing in this cobol ?

Any advises?

Thanks
Kamur

Edward E. Jaffe

unread,
Jul 31, 2002, 2:54:19 AM7/31/02
to
ted.macneil wrote:
> Name 5!

The unique capability of a CLIST to programmatically interact with a
command processor provides 5, 10, 15, or as many functions as you can
dream up! REXX is limited to placing expected input onto the stack and
then invoking the command processor, which runs to completion before
returning control to the REXX exec. With a CLIST, you can invoke the
command processor and, while in subcommand mode, send commands, inspect
the responses, issue additional commands based on the contents of
previous responses, perform any CLIST functions (including file I/O)
with the command processor still active, and terminate the command
processor when finished. We leverage this capability heavily.

Thomas Conley

unread,
Jul 31, 2002, 8:28:03 AM7/31/02
to
----- Original Message -----
From: "Edward E. Jaffe" <edj...@PHOENIXSOFTWARE.COM>
Newsgroups: bit.listserv.ibm-main
Sent: Tuesday, July 30, 2002 10:13 PM
Subject: Re: Dynamic file allocation on IBM mainframe

> Huh??? I like REXX too. But there are still powerful things CLIST can do
> that REXX cannot. I don't consider it a dead language at all. We deliver
> some fairly sophisticated CLISTs with our products. These CLISTs take
> advantage of intrinsic CLIST capabilities that do *NOT* exist in REXX!
>

Ed,

There's nothing CLIST can do that REXX can't (please don't give the parsing
parms argument). Let's argue at SCIDS.

Tom

Howard Brazee

unread,
Jul 31, 2002, 9:42:20 AM7/31/02
to

On 30-Jul-2002, Liam Devlin <Li...@optonline.NOSPAM.net> wrote:

> I wrote a REXX program to do this for our ISPF environment. What you can
> do is to try first to ALLOC the file as OLD. If that works, you're done,
> else ALLOC it NEW, which would look something like (this is just off the
> top):
>
> Alloc_Routine:
> /**********************************************************/
> /* DSN is passed as a parm when Alloc_Routine is called */
> /**********************************************************/
> ARG dsn_name .
>
> DSN_status = SYSDSN(dsn_name)
>
> If DSN_status = "OK"
> Then Do
> "ALLOC DSN('"dsn_name"') OLD REUSE"
> AllocRC = RC
> Else Do
> "ALLOC DSN('"dsn_name"') NEW CATLG SPACE(CYL,1,1) UNIT(SYSDA)" ,
> "LRECL(80) BLKSIZE(0)..."
> AllocRC = RC
> End
>
> If AllocRC = 0
> Then Nop
> Else Say "Unable to Allocate DSN("dsn_name"), RC="AllocRC
>
> Return AllocRC

I have used Rexx more than CLISTs. But my question is - how do you do that
from within a CoBOL program?

Howard Brazee

unread,
Jul 31, 2002, 9:47:56 AM7/31/02
to
This program worked fine for me:
000100 IDENTIFICATION DIVISION.
000200 PROGRAM-ID. COBDYNAL.
000300*===============================================================*
000400* THIS PROGRAM DYNAMICALLY ALLOCATES AND DEALLOCATES A FILE
000500* USING THE BPXWDYN IBM SUBROUTINE. NO DD STATEMENTS FOR THE
000600* FILE SOULD APPEAR IN THE JCL:
000700*===============================================================*
000800 ENVIRONMENT DIVISION.
000900 CONFIGURATION SECTION.
001000 SOURCE-COMPUTER.
001100**** IBM-390 WITH DEBUGGING MODE.
001200 IBM-390.
001300
001400 INPUT-OUTPUT SECTION.
001500 FILE-CONTROL.
001600 SELECT FILEIN ASSIGN TO FILEIN
001700 FILE STATUS IS FILEIN-STATUS.
001800 SELECT FILEOUT ASSIGN TO FILEOUT
001900 FILE STATUS IS FILEOUT-STATUS.
002000 SELECT PARMIN ASSIGN TO PARMIN.
002100/
002200 DATA DIVISION.
002300 FILE SECTION.
002400 FD FILEIN
002500 RECORD CONTAINS 80 CHARACTERS
002600 RECORDING MODE IS F
002700 LABEL RECORDS ARE STANDARD
002800 BLOCK CONTAINS 0 CHARACTERS
002900 DATA RECORD IS FILEIN-REC.
003000 01 FILEIN-REC.
003100 05 FILLER PIC X(80).
003200
003300 FD FILEOUT
003400 RECORD CONTAINS 80 CHARACTERS
003500 RECORDING MODE IS F
003600 LABEL RECORDS ARE STANDARD
003700 BLOCK CONTAINS 0 CHARACTERS
003800 DATA RECORD IS FILEOUT-REC.
003900 01 FILEOUT-REC.
004000 05 FILLER PIC X(80).
004100
004200 FD PARMIN
004300 RECORD CONTAINS 80 CHARACTERS
004400 RECORDING MODE IS F
004500 LABEL RECORDS ARE STANDARD
004600 BLOCK CONTAINS 0 CHARACTERS
004700 DATA RECORD IS FILEIN-REC.
004800 01 PARM-REC.
004900 05 FILLER PIC X(80).
005000
005100 WORKING-STORAGE SECTION.
005200 01 FILEIN-STATUS PIC X(02) VALUE '00'.
005300 88 FILEIN-STATUS-OK VALUE '00' '10' '97'.
005400 88 FILEIN-AT-END VALUE '10'.
005500
005600 01 FILEOUT-STATUS PIC X(02) VALUE '00'.
005700 88 FILEOUT-STATUS-OK VALUE '00' '97'.
005800
005900 01 INPUT-REC PIC X(80).
006000 01 IN-COUNT PIC 9(9) BINARY VALUE 0.
006100 01 SUB-PGM PIC X(8) VALUE 'BPXWDYN '.
006200
006300 01 COMMAND-STRING.
006400**** THIS FOLLOWING APPEARS TO BE OPTIONAL
006500**** COMMENT IT OUT, KEEP IT AT 100, OR PUT IN THE LENGTH!!
006600 05 C-S-LEN PIC S9(4) BINARY VALUE +100.
006700 05 C-S-DATA.
006800 07 FILLER PIC X(100).
006900
007000 01 WS-INPUT-REC PIC X(80).
007100 01 MYINFILE PIC X(73)
007200 VALUE 'UMS.D44201.COBOL(COBDYN)'.
007300 01 MYINFILE-LENGTH PIC S9(2) VALUE 24.
007400 01 MYOUTFILE PIC X(72)
007500 VALUE 'UMS.D44201.TEST'.
007600 01 MYOUTFILE-LENGTH PIC S9(2) VALUE 16.
007700 01 SWITCHES.
007800 05 SW-PARM-EOF-SWITCH PIC X(01) VALUE 'N'.
007900 88 SW-PARM-EOF VALUE 'Y'.
008000 05 SW-FILE-EOF-SWITCH PIC X(01) VALUE 'N'.
008100 88 SW-FILE-EOF VALUE 'Y'.
008200
008300 01 PARM-RECORD.
008400 05 INFILE-PARM.
008500 10 INFILE-PARM-NAME PIC X(06).
008600 88 INFILE-PARM-FOUND VALUE 'INFILE'.
008700 10 FILLER PIC X(01).
008800 10 INFILE-NAME PIC X(73).
008900 05 OUTFILE-PARM REDEFINES INFILE-PARM.
009000 10 OUTFILE-PARM-NAME PIC X(07).
009100 88 OUTFILE-PARM-FOUND VALUE 'OUTFILE'.
009200 10 FILLER PIC X(01).
009300 10 OUTFILE-NAME PIC X(72).
009400/
009500 PROCEDURE DIVISION.
009600 0000-MAIN.
009700 PERFORM 0100-INIT.
009800 READ FILEIN INTO WS-INPUT-REC,
009900 AT END SET SW-FILE-EOF TO TRUE.
010000 PERFORM 1000-READ-LOOP UNTIL SW-FILE-EOF.
010100 PERFORM 9000-CLEANUP.
010200 GOBACK.
010300
010400 0100-INIT.
010500 PERFORM 0200-READ-PARMS.
010600 PERFORM 0300-OPEN-INPUT.
010700 PERFORM 0400-OPEN-OUTPUT.
010800
010900 0200-READ-PARMS.
011000 OPEN INPUT PARMIN.
011100 READ PARMIN INTO PARM-RECORD
011200 AT END SET SW-PARM-EOF TO TRUE.
011300 PERFORM 0210-READ-PARM
011400 UNTIL SW-PARM-EOF.
011500 CLOSE PARMIN.
011600 PERFORM VARYING MYINFILE-LENGTH FROM 73 BY -1
011700 UNTIL MYINFILE-LENGTH < 3
011800 OR MYINFILE(MYINFILE-LENGTH:1) > SPACE
011900 END-PERFORM.
012000
012100 PERFORM VARYING MYOUTFILE-LENGTH FROM 72 BY -1
012200 UNTIL MYOUTFILE-LENGTH < 3
012300 OR MYOUTFILE(MYOUTFILE-LENGTH:1) > SPACE
012400 END-PERFORM.
012500
012600 0210-READ-PARM.
012700 IF INFILE-PARM-FOUND
012800 MOVE INFILE-NAME TO MYINFILE
012900 END-IF.
013000
013100 IF OUTFILE-PARM-FOUND
013200 MOVE OUTFILE-NAME TO MYOUTFILE
013300 END-IF.
013400
013500 READ PARMIN INTO PARM-RECORD
013600 AT END SET SW-PARM-EOF TO TRUE.
013700
013800 0300-OPEN-INPUT.
013900 MOVE SPACE TO C-S-DATA.
014000 STRING ' ALLOC DD(FILEIN) '
014100 'DSN(' MYINFILE (1:MYINFILE-LENGTH) ')'
014200 ' SHR '
014300 DELIMITED BY SIZE
014400 INTO C-S-DATA
014500 END-STRING
014600 PERFORM 9000-CLIST.
014700 OPEN INPUT FILEIN.
014800 IF FILEIN-STATUS-OK
014900 CONTINUE
015000 DISPLAY 'OPENED "' MYINFILE (1:MYINFILE-LENGTH) '"'
015100 ELSE
015200 DISPLAY 'VSAM STATUS "' FILEIN-STATUS '" OPENING "'
015300 MYINFILE (1:MYINFILE-LENGTH) '"'
015400 MOVE FILEIN-STATUS TO RETURN-CODE
015500 GOBACK
015600 END-IF.
015700
015800 0400-OPEN-OUTPUT.
015900
016000 PERFORM 0410-IEFBR14-DELETE.
016100
016200 MOVE SPACE TO C-S-DATA.
016300 STRING ' ALLOC DD(FILEOUT) '
016400 'DSN(' MYOUTFILE (1:MYOUTFILE-LENGTH) ')'
016500 ' NEW UNIT(DEVEDISK) CYL SPACE(05,05) CATALOG '
016600 DELIMITED BY SIZE
016700 INTO C-S-DATA
016800 END-STRING
016900 PERFORM 9000-CLIST.
017000
017100 OPEN OUTPUT FILEOUT.
017200 IF FILEOUT-STATUS-OK
017300 CONTINUE
017400 DISPLAY 'OPENED "' MYOUTFILE (1:MYOUTFILE-LENGTH) '"'
017500 ELSE
017600 DISPLAY 'VSAM STATUS "' FILEOUT-STATUS '" OPENING "'
017700 MYOUTFILE (1:MYOUTFILE-LENGTH) '"'
017800 MOVE FILEOUT-STATUS TO RETURN-CODE
017900 GOBACK
018000 END-IF.
018100
018200 0410-IEFBR14-DELETE.
018300**** DELETE IF IT EXISTS.
018400 MOVE SPACE TO C-S-DATA.
018500 STRING ' ALLOC DD(FILEOUT) '
018600 'DSN(' MYOUTFILE (1:MYOUTFILE-LENGTH) ')'
018700 ' MOD UNIT(DEVEDISK) CYL SPACE(05,05) DELETE '
018800 DELIMITED BY SIZE
018900 INTO C-S-DATA
019000 PERFORM 9000-CLIST.
019100
019200 MOVE 'FREE DD(FILEOUT)' TO C-S-DATA.
019300 PERFORM 9000-CLIST.
019400**** THE ABOVE ALLOWS THAT FILE TO BE OPENED AGAIN.
019500
019600 1000-READ-LOOP.
019700 ADD +1 TO IN-COUNT.
019800D DISPLAY FILEIN-REC.
019900
020000 WRITE FILEOUT-REC FROM WS-INPUT-REC.
020100
020200 READ FILEIN INTO WS-INPUT-REC,
020300 AT END SET SW-FILE-EOF TO TRUE.
020400
020500 9000-CLEANUP.
020600 CLOSE FILEIN.
020700 IF FILEIN-STATUS-OK
020800 CONTINUE
020900 ELSE
021000 DISPLAY 'VSAM STATUS "' FILEIN-STATUS '" CLOSING "'
021100 MYINFILE (1:MYINFILE-LENGTH) '"'
021200 MOVE FILEIN-STATUS TO RETURN-CODE
021300 GOBACK
021400 END-IF.
021500
021600 MOVE 'FREE DD(FILEIN)' TO C-S-DATA.
021700 PERFORM 9000-CLIST.
021800**** THE ABOVE ALLOWS THAT FILE TO BE OPENED AGAIN.
021900 CLOSE FILEOUT.
022000 IF FILEOUT-STATUS-OK
022100 CONTINUE
022200 ELSE
022300 DISPLAY 'VSAM STATUS "' FILEOUT-STATUS '" CLOSING "'
022400 MYINFILE (1:MYINFILE-LENGTH) '"'
022500 MOVE FILEOUT-STATUS TO RETURN-CODE
022600 GOBACK
022700 END-IF.
022800
022900 MOVE 'FREE DD(FILEOUT)' TO C-S-DATA.
023000 PERFORM 9000-CLIST.
023100**** THE ABOVE ALLOWS THAT FILE TO BE OPENED AGAIN.
023200 GOBACK.
023300
023400 9000-CLIST.
023500***** I DON'T THINK C-S-LEN IS NEEDED
023600 PERFORM VARYING C-S-LEN FROM 100 BY -1
023700 UNTIL C-S-LEN < 2
023800 OR C-S-DATA (C-S-LEN:1) > SPACE
023900 END-PERFORM.
024000D DISPLAY 'C-S-DATA="' C-S-DATA (1:C-S-LEN) '"'.
024100 CALL SUB-PGM USING COMMAND-STRING.
024200 IF RETURN-CODE = 0
024300 CONTINUE
024400D DISPLAY 'RETURN-CODE ="' RETURN-CODE '"'
024500 ELSE
024600 DISPLAY 'RETURN-CODE ="' RETURN-CODE '" FOR "'
024700 C-S-DATA(1:C-S-LEN) '"'
024800 DISPLAY '**** ERROR ABORTING ****'
024900 MOVE '35' TO RETURN-CODE
025000 GOBACK
025100 END-IF.
025200****** COBDYNN ENDS HERE.

The JCL had:
//PARMIN DD *
INFILE=UMS.D44201.COBOL(SIPR702)
OUTFILE=UMS.D44201.TEST1
//*

Bruce Black

unread,
Jul 31, 2002, 9:38:00 AM7/31/02
to
>
>
>(CLIST is a dead product).
>>
>
>
>REXX under TSO is also a dead product.
>

Lets define "dead", guys.

To me, dead means "no longer maintained" and either
1) no longer working on current op sys, or
2) working only by the grace of God and likely to fail on future
releases with no possibility of fixes.

I don't think that CLIST or REXX is in either category. It may be true
that they are no longer being enhanced, which I would call "elderly",
but AFAIK IBM still supports and maintains them.

--
Bruce A. Black
Senior Software Developer for FDR
Innovation Data Processing 973-890-7300
personal: bbl...@fdrinnovation.com
sales info: sa...@fdrinnovation.com
tech support: sup...@fdrinnovation.com
web: www.innovationdp.fdr.com

ted.macneil

unread,
Jul 31, 2002, 9:36:28 AM7/31/02
to
Okay, but I have never had that need.
But, you win.

-teD


Ted.M...@mobile.rogers.com

Card-carrying member of "Dino's R Us" since 1981.

When the going gets stupid, the stupid get annoying!

----------------------------------------------------------------------

Binyamin Dissen

unread,
Jul 31, 2002, 10:46:53 AM7/31/02
to
On Wed, 31 Jul 2002 08:28:05 -0400 Thomas Conley <pinn...@FRONTIERNET.NET>
wrote:

:>----- Original Message -----


:>From: "Edward E. Jaffe" <edj...@PHOENIXSOFTWARE.COM>
:>Newsgroups: bit.listserv.ibm-main
:>Sent: Tuesday, July 30, 2002 10:13 PM
:>Subject: Re: Dynamic file allocation on IBM mainframe
:>> Huh??? I like REXX too. But there are still powerful things CLIST can do
:>> that REXX cannot. I don't consider it a dead language at all. We deliver
:>> some fairly sophisticated CLISTs with our products. These CLISTs take
:>> advantage of intrinsic CLIST capabilities that do *NOT* exist in REXX!

:>There's nothing CLIST can do that REXX can't (please don't give the parsing


:>parms argument). Let's argue at SCIDS.

Will not be there, so will give my $.02

CLIST allows logic within a command processor, i.e., conditional give
subcommands based on return codes from previous subcommands. REXX requires a
complete pre-built list of subcommands to be queued.

--
Binyamin Dissen <bdi...@dissensoftware.com>
http://www.dissensoftware.com

Director, Dissen Software, Bar & Grill - Israel

Marchant, Tom , T.C.

unread,
Jul 31, 2002, 2:14:21 PM7/31/02
to
Except over who's buying the beer. See you there.

Tom Marchant

Edward E. Jaffe wrote:
>
<snip!>
>
>Anyway, I never argue at SCIDS.

Shmuel Metz , Seymour J.

unread,
Jul 31, 2002, 3:34:51 PM7/31/02
to
Sure there is. But I still prefer REXX for normal use.

Alas, I won't be at Share.

--
Shmuel (Seymour J.) Metz
The opinions expressed are not necessarily those of USCS, DSI,
my wife, my children or my cat.


Thomas Conley <pinn...@FRONTIERNET.NET>
Sent by: IBM Mainframe Discussion List <IBM-...@BAMA.UA.EDU>
07/31/02 08:28 AM
Please respond to IBM Mainframe Discussion List


To: IBM-...@BAMA.UA.EDU
cc:


Subject: Re: Dynamic file allocation on IBM mainframe

There's nothing CLIST can do that REXX can't (please don't give the
parsing

parms argument). Let's argue at SCIDS.

Charles Hottel

unread,
Jul 31, 2002, 8:54:17 PM7/31/02
to
Try this program which uses subroutine SETPTO from the cbttape:
(You might want to use lowercase for "putenv" )

IDENTIFICATION DIVISION.
PROGRAM-ID. DYNALLC.
*===============================================================*
* This program dynamically allocates and deallocates a file
* using environment variables. No DD statements for the
* file sould appear in the JCL:
*
* Needs COBOL 2.2.0
* Compile with NODYNAM. CALL must be static.
*
* PUTENV is a C function that creates an environment variable.
* See C/C++ Run-Time Library Reference (SC28-1663)
*
* Language Environment Programming Reference (SC26-3312)
*
* COBOL Language Reference (SC26-9046-04)
*
*===============================================================*
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT FILEIN ASSIGN UT-S-DYNFILE
FILE STATUS IS FILEIN-STATUS.
/
DATA DIVISION.
FILE SECTION.
FD FILEIN
RECORD CONTAINS 80 CHARACTERS
RECORDING MODE IS F
LABEL RECORDS ARE STANDARD
BLOCK CONTAINS 0 CHARACTERS
DATA RECORD IS FILEIN-REC.
01 FILEIN-REC.
05 FILLER PIC X(80).

WORKING-STORAGE SECTION.
01 FILEIN-STATUS PIC 9(02).
01 RC PIC 9(9) BINARY.
01 ADDRESS-POINTER POINTER.
01 FILE-ENVIRONMENT-VARIABLE PIC X(31)
VALUE 'DYNFILE=DSN(EGHF3PY.TEMP80) SHR'.
*
01 INPUT-REC PIC X(80).


01 IN-COUNT PIC 9(9) BINARY VALUE 0.

/
PROCEDURE DIVISION.
INITIAL-STUFF.

***********SET ADDRESS-POINTER TO ADDRESS OF
************** FILE-ENVIRONMENT-VARIABLE.
CALL "SETPTO" USING ADDRESS-POINTER
FILE-ENVIRONMENT-VARIABLE.

CALL "PUTENV" USING BY VALUE ADDRESS-POINTER
RETURNING RC.
IF RC NOT = ZERO
DISPLAY 'PUTENV FAILED'
GOBACK
END-IF.

OPEN INPUT FILEIN.

READER.
READ FILEIN INTO INPUT-REC,
AT END GO TO E-O-J.
ADD +1 TO IN-COUNT.
DISPLAY FILEIN-REC.
GO TO READER.

E-O-J.
CLOSE FILEIN.
GOBACK.

Here is the subroutine:


*****************************************************************
* Documentation: *
* SETPTRTO - SET pointer-name TO ADDRESS OF working-storage-name*
* --------------------------------------------------------------*
* The purpose of this general routine is to set the pointer *
* POINTER-TO to the address of the object POINTED-OBJECT. Since *
* we do not touch the latter, its type is insignificant, and is *
* reduced here to the minimum, PIC X. *
* This subroutine forces the address of the WORKING-STORAGE *
* data item to the pointer. This subroutine should be used in *
* cojunction with a regular SET command in order to establish *
* the right addressing. *
* Usage of the routine is like that: *
* ... *
* CALL 'SETPTRTO' USING WS-PTR WS-AREA. *
* SET ADDRESS OF LS-AREA TO WS-PTR. *
* ... *
* and from than on, any reference to LS-AREA-A1 etc., will *
* actually refer to some part of WS-AREA. *
* The "Application programming Guide" (*) brings in part 4 - *
* "Compiling Your Program", an example similar to my SETPTRTO, *
* under the name GETADDRESS. This subroutine does *
* "SET pointer TO ADDRESS OF data-item", *
* while both are in the LINKAGE SECTION. Note that calling such*
* a subroutine (IBM's or mine), must be BY REFERENCE (which is *
* the default). *
******************************************************************
IDENTIFICATION DIVISION.
PROGRAM-ID. SETPTO.
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
-INC LCS001C
LINKAGE SECTION.
01 POINTER-TO POINTER.
01 POINTED-OBJECT PIC X.
PROCEDURE DIVISION USING POINTER-TO POINTED-OBJECT.
SET POINTER-TO TO ADDRESS OF POINTED-OBJECT
GOBACK.

Kumar <ka...@lycos.com> wrote in article
<7517e3e1.02073...@posting.google.com>...

Charles Hottel

unread,
Jul 31, 2002, 9:01:53 PM7/31/02
to
I hope to solve this problem as soon as I have time. If/when I do I will
post my code.

<snip>

Joe Zitzelberger

unread,
Aug 1, 2002, 12:18:53 AM8/1/02
to

You write a small assembler subprogram that accepts text units and 99's
them...

psychede...@mindless.com

Web Servers Do It With Cookies

Stephen E. Bacher

unread,
Aug 1, 2002, 10:42:27 AM8/1/02
to
Liam Devlin <Li...@optonline.nospam.net> wrote:

>I wrote a REXX program to do this for our ISPF environment. What you can
>do is to try first to ALLOC the file as OLD. If that works, you're done,
>else ALLOC it NEW, which would look something like (this is just off the
>top):
>
>Alloc_Routine:
>/**********************************************************/
>/* DSN is passed as a parm when Alloc_Routine is called */
>/**********************************************************/
>ARG dsn_name .
>
>DSN_status = SYSDSN(dsn_name)
>
>If DSN_status = "OK"
> Then Do
> "ALLOC DSN('"dsn_name"') OLD REUSE"
> AllocRC = RC

(You left out an "End" here.)

> Else Do
> "ALLOC DSN('"dsn_name"') NEW CATLG SPACE(CYL,1,1) UNIT(SYSDA)" ,
> "LRECL(80) BLKSIZE(0)..."
> AllocRC = RC
> End

I prefer the following code:

If DSN_status = "DATASET NOT FOUND"
Then Do


"ALLOC DSN('"dsn_name"') NEW CATLG SPACE(CYL,1,1) UNIT(SYSDA)" ,
"LRECL(80) BLKSIZE(0)..."

End
Else Do
"ALLOC DSN('"dsn_name"') OLD REUSE"
End
AllocRC = RC

That way, if DSN_status is neither "OK" nor "DATASET NOT FOUND", the
error you will get is one you encounter while trying to allocate the
existing data set, which is unavailable for some other reason (e.g.
dataset in use, or access not authorized). With your code, the error
you get in such a situation would be "duplicate data set", which would
be confusing as to why the program was trying to allocate the obviously
existing data set as a new one.

Even better would be:

If DSN_status = "OK"
Then Do
"ALLOC DSN('"dsn_name"') OLD REUSE"
AllocRC = RC

End
Else
If DSN_status = "DATASET NOT FOUND"
Then Do


"ALLOC DSN('"dsn_name"') NEW CATLG SPACE(CYL,1,1) UNIT(SYSDA)" ,
"LRECL(80) BLKSIZE(0)..."
AllocRC = RC
End

Else Do
Say "Cannot access '"dsn_name"', error:" DSN_status
AllocRC = 9999
End
End

- seb

Stephen E. Bacher

unread,
Aug 1, 2002, 10:44:28 AM8/1/02
to
Bruce Black <bbl...@fdrinnovation.com> wrote:

>To me, dead means "no longer maintained" and either
>1) no longer working on current op sys, or
>2) working only by the grace of God and likely to fail on future
>releases with no possibility of fixes.
>
>I don't think that CLIST or REXX is in either category. It may be true
>that they are no longer being enhanced, which I would call "elderly",
>but AFAIK IBM still supports and maintains them.

Does that mean you don't expect REXX on MVS^WOS/390^Wz/OS to be
enhanced to conform to the X3J18 standard, or to contain the
standard line I/O functions available on all other implementations?

Tom Ross

unread,
Aug 1, 2002, 11:51:07 AM8/1/02
to
>I have used Rexx more than CLISTs. But my question is - how do you dothat
>from within a COBOL program?

You can now do permanent dynamic allocation in COBOL programs: Use 5648-A25
COBOL for OS/390 & VM V2R2 or later, SELECT filename ASSIGN to environment-variable,
and set the environment variable to your dataset attributes with either
the LE ENVAR run-time option or the 'putenv' C function that comes with LE.
See examples in the COBOL Programming Guide:
http://www-3.ibm.com/software/ad/cobol/zos/library/

Cheers,
TomR >> COBOL is the Language of the Future! <<

David Alcock

unread,
Aug 1, 2002, 11:57:19 AM8/1/02
to
> (CLIST is a dead product).

> REXX under TSO is also a dead product

> Lets define "dead", guys.

Okay, maybe dead is the wrong term, how about "functionally stabilized" ;-)

Howard Brazee

unread,
Aug 1, 2002, 1:51:42 PM8/1/02
to

On 1-Aug-2002, dal...@CSW.COM (David Alcock) wrote:

> > REXX under TSO is also a dead product
>
> > Lets define "dead", guys.
>
> Okay, maybe dead is the wrong term, how about "functionally stabilized"
> ;-)

Now that's a line worth remembering!

Anonymous

unread,
Aug 2, 2002, 10:21:44 AM8/2/02
to
Seems to me like you would catalog it the same way you do in JCL -- by
specifying the catalog option on your COBOL "DD" parameters.

"Charles Hottel" <cho...@cpcug.org> wrote in message
news:01c238f6$e683c1e0$e1c2f943@chottel...


-----------== Posted via Newsfeed.Com - Uncensored Usenet News ==----------
http://www.newsfeed.com The #1 Newsgroup Service in the World!
-----= Over 100,000 Newsgroups - Unlimited Fast Downloads - 19 Servers =-----

Charles Hottel

unread,
Aug 2, 2002, 7:10:51 PM8/2/02
to
He wants to process datasets that already exist and are cataloged, and new
datasets.

I have experimented a little with bpxwdyn and on a previously catalogued
dataset first using:

alloc dd(sysut1) dsn(file.name1) old msg(wtp)

and then the same command except with shr, mod, and new. To my suprise
they all worked. I was expecting 'new' to fail and set the return code to
a non zero value. Then I would do a ' free delete' to get rid of it and
then create a new dataset with the same name and whatever characteristics I
want.

If you don't want to change any dataset characteristics then just alloc and
'open output' is enough.

In my test I then 'free catalog' the file and try to create a brand new
dataset using the same ddname and dcb. I am getting messages about not
being able to access the catalog and then an abend. The messages say that
the refcm is F even though I told it FB. The lrecl is 80 and the blksize
is greater than 80. It says make the lrecl equal the blksize because
recfm is F. The open gives file status of 90. Despite all of this at the
end of the job the new file is created with the one record that I write to
it and the file has been catalogued.

I have not had much time to experiment so not too much progress has been
made.

<rant/opinion>

The bpxwdyn documentation is pretty bad in places. First it says that the
low order two digits of the return code is the number of key that failed
the parse, offset by 20. Later it says there is no indication of the key
that is in error. I could not figure out from the return code which caused
the error.

Dynamic allocation in assembler is much better documented and seems more
straightforward to me. "Advanced Assembler" by Carmine Cannatello has good
examples and they are available from the cbttape. "MVS Power Programming"
also has a dynamic allocation example program.

<end rant/opinion>

Anonymous <Nobody> wrote in article <3d49e97d_1@anonymous>...

Liam Devlin

unread,
Aug 10, 2002, 2:31:08 AM8/10/02
to
Charles Hottel wrote:
> Using BPXWDYN I tried mod, old, shr and new on an existing catalogued
> dataset. I expected new to fail, but I received a zero return code from
> all of them! Have not had any more time to experiment.

This doesn't sound like something I'd want to use in production. I'm
guesing there's more to it.

Charles Hottel

unread,
Aug 10, 2002, 5:58:58 PM8/10/02
to
That is what I am thinking also.

Liam Devlin <Li...@optonline.NOSPAM.net> wrote in article
<3D54B32C...@optonline.NOSPAM.net>...

p...@sweng.stortek.com

unread,
Aug 11, 2002, 1:08:10 AM8/11/02
to
In a recent note, Charles Hottel said:

> Date: Sat, 10 Aug 2002 21:58:58 GMT

Allocation WAD. The same thing would happen with TSO ALLOCATE or with
JCL DD: the "new" data set is allocated on any available storage volume
which does not already have the DSN in its VTOC, and deleted when freed.
You should be able to confirm this from allocation messages in the job
log.

-- gil
--
StorageTek
INFORMATION made POWERFUL

Hugh Candlin

unread,
Aug 12, 2002, 6:07:03 PM8/12/02
to

Liam Devlin <Li...@optonline.NOSPAM.net> wrote in message
news:3D46AD00...@optonline.NOSPAM.net...
>
> ACK! That is so 60's.

Ack. That response is so trendy.


Simon Smith

unread,
Aug 13, 2002, 10:14:21 PM8/13/02
to
Throughout this thread there are references to return-code. I'm never
getting a non-zero rc from BPXWDYN even when I know the alloc failed.
I'm using:

01 WS-BPXWDYN-PARMS.
03 WS-BPXWDYN-LEN PIC S9(4) COMP VALUE +150.
03 WS-BPXWDYN-DATA PIC X(150).
.
CALL WS-BPXWDYN USING WS-BPXWDYN-PARMS.
IF RETURN-CODE NOT = ZERO
DISPLAY 'DAD RETURN FROM BPXWDYN'
END-IF

I know it failed because I specified MSG(WTP) and got a message on the
job log saying
IKJ56893I DATA SET RFS.TEST.RFADRVR.TR.DD1 NOT ALLOCATED+
IGD17101I DATA SET RFS.TEST.RFADRVR.TR.DD1 NOT DEFINED BECAUSE
DUPLICAT
RETURN CODE IS 8 REASON CODE IS 38 IGG0CLEH

Any thoughts?

Simon

Charles Hottel

unread,
Aug 14, 2002, 8:44:19 PM8/14/02
to
I can confirm that I have had the exact same thing happen. I have not yet
found a solution due to lack of time.

Simon Smith <ssm...@adelaidebank.com.au> wrote in article
<64826f50.0208...@posting.google.com>...

CAMERONP

unread,
Dec 11, 2002, 4:48:24 PM12/11/02
to
I have managed to get the dynamic file allocation to work on z/os and I
have a few questions since I could not find sufficient documentation out
there on the web.
1) How do I specify abend processing in the dynalloc parms eg. uncatalog
files in an abend situation?
2) How do I get a list of usable environment variables for DDs in the
program? eg.filename, etc?
3) Where is all this officially documented other than the very sparse
examples in the IBM manuals?

Please help.

--
posted via MFF : http://www.mainframeforum.com/f1363/s

registration is required to reply to posts

Edward E. Jaffe

unread,
Dec 11, 2002, 6:00:04 PM12/11/02
to
CAMERONP wrote:
> I have managed to get the dynamic file allocation to work on z/os and I
> have a few questions since I could not find sufficient documentation out
> there on the web.
> 1) How do I specify abend processing in the dynalloc parms eg. uncatalog
> files in an abend situation?
> 2) How do I get a list of usable environment variables for DDs in the
> program? eg.filename, etc?
> 3) Where is all this officially documented other than the very sparse
> examples in the IBM manuals?

Dynamic allocation is exhaustively documented in z/OS MVS Programming:
Authorized Assembler Services Guide (SA22-7608). The URL for the latest
one on the web is:
http://publibz.boulder.ibm.com/cgi-bin/bookmgr_OS390/BOOKS/IEA2A830/CCONTENTS.
I also suggest you read z/OS MVS JCL User's Guide (SA22-7598) and z/OS
MVS JCL Reference (SA22-7597).

--
-----------------------------------------------------------------
| Edward E. Jaffe | |
| Mgr, Research & Development | edj...@phoenixsoftware.com |
| Phoenix Software International | Tel: (310) 338-0400 x318 |
| 5200 W Century Blvd, Suite 800 | Fax: (310) 338-0801 |
| Los Angeles, CA 90045 | http://www.phoenixsoftware.com |
-----------------------------------------------------------------

CAMERONP

unread,
Dec 11, 2002, 7:48:20 PM12/11/02
to
Thanks for the reply. I did take a look at this website and found the
information. What confuses me is that I am using the 'putenv' variant of
dynamic allocation and it works real good. I just cannot find how to use
it do deallocate files or provide abnormal termination DISP parameters.

Is there any place this version has been documented?

Thanks again.

CAMERONP

unread,
Dec 11, 2002, 8:03:23 PM12/11/02
to
I also forgot to mention that I am doing this in good ol' COBO, not
Assembler.

Edward E. Jaffe

unread,
Dec 12, 2002, 2:59:46 AM12/12/02
to
CAMERONP wrote:

>Thanks for the reply. I did take a look at this website and found the
>information. What confuses me is that I am using the 'putenv' variant of
>dynamic allocation and it works real good. I just cannot find how to use
>it do deallocate files or provide abnormal termination DISP parameters.
>

Normal disposition = DALNDISP
Conditional disposition = DALCDISP

Table 26-10. "JCL DD Statement Parameters and Equivalent Text Units" is
quite handy to understand the uses of the keys with direct JCL equivalents.

BTW, override disposition during deallocation = DUNOVDSP can come in
handy as well.

I'm sorry, I can't help you with COBOL interfaces. The only thing I know
about COBOL is how to spell it. Never learned the language.

0 new messages