Re: COBOL to dynamic DD name

2023-05-05 Thread rpinion865
The date on the COBOL program is 2005.

Sent from Proton Mail mobile

 Original Message 
On May 5, 2023, 7:06 PM, Farley, Peter wrote:

> Took me a while to find it, but I *think* this is my re-implementation for 
> TIOT access in Rexx when SWA=ABOVE (I know I copied this technique from 
> another author whose name I did not save, so my apologies to that author - if 
> you are still reading this list, please take credit where it is due). Notes 
> about errors or omissions in the below logic are welcomed. The date on the 
> source member where I found these routines was 2006, so things may be 
> different now. I haven't had a need to use this code since 2006, and I can't 
> test it again right at this moment. If I can find any round tuits I can try 
> to convert the logic to valid Enterprise COBOL and test it. If someone else 
> has the time now, please be my guest and let us know your results. Peter 
> --- alldsn: procedure parse upper arg ddname nextdsn 
> = getdsn(ddname) dsnlist = '' do xi = 1 by 1 while nextdsn /= (ddname 'NOT 
> FOUND') dsnlist = dsnlist nextdsn nextdsn = getdsn(ddname'+'xi) end if xi = 1 
> then , dsnlist = nextdsn return dsnlist getdsn: procedure parse upper arg 
> ddname parse var ddname ddname '+' concat if concat = '' then concat = 0 
> tcb_address = storage(21C,4) tiot_address = 
> storage(d2x(c2d(tcb_address)+12),4) dd_address = d2x(c2d(tiot_address)+28) 
> dd_length = storage(d2x(c2d(tiot_address)+24),1) tiot_address = 
> d2x(c2d(tiot_address)+24) jfcb_address = storage(d2x(x2d(tiot_address)+12),3) 
> do while dd_length /= '00'x if storage(dd_address,8) = ddname then leave 
> tiot_address = d2x(x2d(tiot_address)+c2d(dd_length)) dd_length = 
> storage(tiot_address,1) dd_address = d2x(x2d(tiot_address)+4) jfcb_address = 
> storage(d2x(x2d(tiot_address)+12),3) end if dd_length = '00'x then return 
> ddname 'NOT FOUND' do concat tiot_address = 
> d2x(x2d(tiot_address)+c2d(dd_length)) dd_length = storage(tiot_address,1) 
> dd_address = d2x(x2d(tiot_address)+4) jfcb_address = 
> storage(d2x(x2d(tiot_address)+12),3) if dd_length = '00'x then return ddname 
> 'NOT FOUND' if storage(dd_address,8) /== ' ' then , return ddname 'NOT FOUND' 
> end return strip(storage(d2x(c2d(jfcb_address)+16),44),'T') 
> - -Original Message- From: IBM Mainframe 
> Discussion List  On Behalf Of Farley, Peter Sent: Friday, May 5, 2023 5:58 PM 
> To: IBM-MAIN@LISTSERV.UA.EDU Subject: Re: COBOL to dynamic DD name EXTERNAL 
> EMAIL That logic is fine for SWA below the line, but I don't think many shops 
> still run that way, at least not the larger ones. ISTR there was at one time 
> a published Rexx implementation of the SWA-above logic, but I can't put my 
> finger on it just yet. That logic (if found) should be transferable to 
> Enterprise COBOL. Peter -Original Message- From: IBM Mainframe 
> Discussion List  On Behalf Of rpinion865 Sent: Friday, May 5, 2023 2:00 PM 
> To: IBM-MAIN@LISTSERV.UA.EDU Subject: COBOL to dynamic DD name I don't know 
> if this program is of any use to the original poster. But, I came across the 
> source this afternoon. It would seem if you can read the JFCB, maybe you 
> could update it? IDENTIFICATION DIVISION. PROGRAM-ID. COBJFCB. INSTALLATION. 
> AUTHOR. KEVIN. DATE-WRITTEN. 11/07/2005. ENVIRONMENT DIVISION. INPUT-OUTPUT 
> SECTION. DATA DIVISION. FILE SECTION. WORKING-STORAGE SECTION. 01 
> TCB-ADDRESS-POINTER. 05 TCB-ADDR-POINTER USAGE IS POINTER. 01 TIOT-SEG-POINT. 
> 05 TIOT-SEG-POINTER USAGE IS POINTER. 05 TIOT-SEG-PNT REDEFINES 
> TIOT-SEG-POINTER PIC S9(9) COMP. 01 JFCB-POINT. 05 JFCB-POINTER USAGE IS 
> POINTER. 05 JFCB-POINT-RED REDEFINES JFCB-POINTER. 10 FILLER PIC X. 10 
> JFCB-LOW-3 PIC X(3). LINKAGE SECTION. 01 DDNAME-DSN-ARRAY. 05 DDNAME-DSN 
> OCCURS 100 TIMES INDEXED BY NDX1. 10 DDA-DDNAME PIC X(8). 10 DDA-DSN PIC 
> X(44). 01 TCB-POINTER USAGE IS POINTER. 01 TCB. 05 FILLER PIC X(12). 05 
> TIOT-POINTER USAGE IS POINTER. 01 TIOT-START PIC X(24). 01 TIOT-SEG. 05 
> TIO-LEN PIC X. 05 FILLER PIC X(3). 05 DD-NAME PIC X(8). 05 JFCB-ADDR PIC 
> X(3). 01 JFCB. 05 FILLER PIC X(16). 05 DS-NAME PIC X(44). PROCEDURE DIVISION 
> USING DDNAME-DSN-ARRAY. MOVE LOW-VALUES TO JFCB-POINT. MOVE X'021C' TO 
> TCB-ADDRESS-POINTER. SET ADDRESS OF TCB-POINTER TO TCB-ADDR-POINTER. SET 
> ADDRESS OF TCB TO TCB-POINTER. SET ADDRESS OF TIOT-START TO TIOT-POINTER. SET 
> TIOT-SEG-POINTER TO TIOT-POINTER. ADD 24 TO TIOT-SEG-PNT. SET ADDRESS OF 
> TIOT-SEG TO TIOT-SEG-POINTER. SET NDX1 TO 1. PERFORM UNTIL TIO-LEN = 
> LOW-VALUES OR NDX1 > 100 MOVE DD-NAME TO DDA-DDNAME(NDX1) MOVE JFCB-ADDR TO 
> JFCB-LOW-3 SET ADDRESS OF JFCB TO JFCB-POINTER MOVE DS-NAME TO DDA-DSN(NDX1) 
> DISPLAY DDA-DDNAME(NDX1) DDA-DSN(NDX1) ADD 

Re: COBOL to dynamic DD name

2023-05-05 Thread Farley, Peter
Took me a while to find it, but I *think* this is my re-implementation for TIOT 
access in Rexx when SWA=ABOVE (I know I copied this technique from another 
author whose name I did not save, so my apologies to that author - if you are 
still reading this list, please take credit where it is due).

Notes about errors or omissions in the below logic are welcomed.  The date on 
the source member where I found these routines was 2006, so things may be 
different now.  I haven't had a need to use this code since 2006, and I can't 
test it again right at this moment.

If I can find any round tuits I can try to convert the logic to valid 
Enterprise COBOL and test it.  If someone else has the time now, please be my 
guest and let us know your results.

Peter

---
alldsn: procedure 
parse upper arg ddname
nextdsn = getdsn(ddname)  
dsnlist = ''  
do xi = 1 by 1 while nextdsn /= (ddname 'NOT FOUND')  
   dsnlist = dsnlist nextdsn  
   nextdsn = getdsn(ddname'+'xi)  
end   
if xi = 1 then ,  
   dsnlist = nextdsn  
return dsnlist
  
getdsn: procedure 
parse upper arg ddname
parse var ddname ddname '+' concat
if concat = '' then concat = 0
tcb_address = storage(21C,4)  
tiot_address = storage(d2x(c2d(tcb_address)+12),4)
dd_address = d2x(c2d(tiot_address)+28)
dd_length = storage(d2x(c2d(tiot_address)+24),1)  
tiot_address = d2x(c2d(tiot_address)+24)  
jfcb_address = storage(d2x(x2d(tiot_address)+12),3)   
do while dd_length /= '00'x   
 if storage(dd_address,8) = ddname then leave 
 tiot_address = d2x(x2d(tiot_address)+c2d(dd_length)) 
 dd_length = storage(tiot_address,1)  
 dd_address = d2x(x2d(tiot_address)+4)
 jfcb_address = storage(d2x(x2d(tiot_address)+12),3)  
end   
if dd_length = '00'x then return ddname 'NOT FOUND'   
do concat 
 tiot_address = d2x(x2d(tiot_address)+c2d(dd_length)) 
 dd_length = storage(tiot_address,1)  
 dd_address = d2x(x2d(tiot_address)+4)
 jfcb_address = storage(d2x(x2d(tiot_address)+12),3)  
 if dd_length = '00'x then return ddname 'NOT FOUND'  
 if storage(dd_address,8) /== '' then ,   
return ddname 'NOT FOUND' 
end   
return strip(storage(d2x(c2d(jfcb_address)+16),44),'T')   
-

-Original Message-
From: IBM Mainframe Discussion List  On Behalf Of 
Farley, Peter
Sent: Friday, May 5, 2023 5:58 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: Re: COBOL to dynamic DD name

EXTERNAL EMAIL

That logic is fine for SWA below the line, but I don't think many shops still 
run that way, at least not the larger ones.

ISTR there was at one time a published Rexx implementation of the SWA-above 
logic, but I can't put my finger on it just yet.  That logic (if found) should 
be transferable to Enterprise COBOL.

Peter

-Original Message-
From: IBM Mainframe Discussion List  On Behalf Of 
rpinion865
Sent: Friday, May 5, 2023 2:00 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: COBOL to dynamic DD name

I don't know if this program is of any use to the original poster. But, I came 
across the source this afternoon. It would seem if you can read the JFCB, maybe 
you could update it?

IDENTIFICATION DIVISION.
PROGRAM-ID. COBJFCB.
INSTALLATION.
AUTHOR. KEVIN.
DATE-WRITTEN. 11/07/2005.

ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.

DATA DIVISION.
FILE SECTION.

WORKING-STORAGE SECTION.
01 TCB-ADDRESS-POINTER.
05 TCB-ADDR-POINTER USAGE IS POINTER.
01 TIOT-SEG-POINT.
05 TIOT-SEG-POINTER USAGE IS POINTER.
05 TIOT-SEG-PNT REDEFINES TIOT-SEG-POINTER
PIC S9(9) COMP.
01 JFCB-POINT.
05 JFCB-POINTER USAGE IS POINTER.
05 JFCB-POINT-RED REDEFINES JFCB-POINTER.
10 FILLER PIC X.
10 JFCB-LOW-3 PIC X(3).

LINKAGE SECTION.
01 DDNAME-DSN-ARRAY.
05 DDNAME-DSN OCCURS 100 TIMES INDEXED BY NDX1.
10 DDA-DDNAME PIC X(8).
10 DDA-DSN PIC X(44).

01 TCB-POINTER USAGE IS POINTER.
01 TCB.
05 FILLER PIC X(12).
05 TIOT-POINTER USAGE IS POINTER.
01 TIOT-START PIC X(24).
01 TIOT-SEG.
05 TIO-LEN PIC X.
05 FILLER PIC X(3).
05 DD-NAME PIC X(8).
05 JFCB-ADDR PIC X(3).
01 JFCB.
05 FILLER PIC X(16).
05 DS-NAME PIC X(44

Re: COBOL to dynamic DD name

2023-05-05 Thread Farley, Peter
That logic is fine for SWA below the line, but I don't think many shops still 
run that way, at least not the larger ones.

ISTR there was at one time a published Rexx implementation of the SWA-above 
logic, but I can't put my finger on it just yet.  That logic (if found) should 
be transferable to Enterprise COBOL.

Peter

-Original Message-
From: IBM Mainframe Discussion List  On Behalf Of 
rpinion865
Sent: Friday, May 5, 2023 2:00 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: COBOL to dynamic DD name

I don't know if this program is of any use to the original poster. But, I came 
across the source this afternoon. It would seem if you can read the JFCB, maybe 
you could update it?

IDENTIFICATION DIVISION.
PROGRAM-ID. COBJFCB.
INSTALLATION.
AUTHOR. KEVIN.
DATE-WRITTEN. 11/07/2005.

ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.

DATA DIVISION.
FILE SECTION.

WORKING-STORAGE SECTION.
01 TCB-ADDRESS-POINTER.
05 TCB-ADDR-POINTER USAGE IS POINTER.
01 TIOT-SEG-POINT.
05 TIOT-SEG-POINTER USAGE IS POINTER.
05 TIOT-SEG-PNT REDEFINES TIOT-SEG-POINTER
PIC S9(9) COMP.
01 JFCB-POINT.
05 JFCB-POINTER USAGE IS POINTER.
05 JFCB-POINT-RED REDEFINES JFCB-POINTER.
10 FILLER PIC X.
10 JFCB-LOW-3 PIC X(3).

LINKAGE SECTION.
01 DDNAME-DSN-ARRAY.
05 DDNAME-DSN OCCURS 100 TIMES INDEXED BY NDX1.
10 DDA-DDNAME PIC X(8).
10 DDA-DSN PIC X(44).

01 TCB-POINTER USAGE IS POINTER.
01 TCB.
05 FILLER PIC X(12).
05 TIOT-POINTER USAGE IS POINTER.
01 TIOT-START PIC X(24).
01 TIOT-SEG.
05 TIO-LEN PIC X.
05 FILLER PIC X(3).
05 DD-NAME PIC X(8).
05 JFCB-ADDR PIC X(3).
01 JFCB.
05 FILLER PIC X(16).
05 DS-NAME PIC X(44).

PROCEDURE DIVISION USING DDNAME-DSN-ARRAY.

MOVE LOW-VALUES TO JFCB-POINT.
MOVE X'021C' TO TCB-ADDRESS-POINTER.
SET ADDRESS OF TCB-POINTER TO TCB-ADDR-POINTER.
SET ADDRESS OF TCB TO TCB-POINTER.
SET ADDRESS OF TIOT-START TO TIOT-POINTER.
SET TIOT-SEG-POINTER TO TIOT-POINTER.
ADD 24 TO TIOT-SEG-PNT.
SET ADDRESS OF TIOT-SEG TO TIOT-SEG-POINTER.
SET NDX1 TO 1.
PERFORM UNTIL TIO-LEN = LOW-VALUES OR NDX1 > 100
MOVE DD-NAME TO DDA-DDNAME(NDX1)
MOVE JFCB-ADDR TO JFCB-LOW-3
SET ADDRESS OF JFCB TO JFCB-POINTER
MOVE DS-NAME TO DDA-DSN(NDX1)
DISPLAY DDA-DDNAME(NDX1) DDA-DSN(NDX1)
ADD 20 TO TIOT-SEG-PNT
SET ADDRESS OF TIOT-SEG TO TIOT-SEG-POINTER
SET NDX1 UP BY 1
END-PERFORM.
GOBACK.
--


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...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-05-05 Thread Seymour J Metz
How old is it?  Does anybody still run with SWA below the line?


From: IBM Mainframe Discussion List  on behalf of 
rpinion865 <042a019916dd-dmarc-requ...@listserv.ua.edu>
Sent: Friday, May 5, 2023 2:00 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: COBOL to dynamic DD name

I don't know if this program is of any use to the original poster. But, I came 
across the source this afternoon. It would seem if you can read the JFCB, maybe 
you could update it?

IDENTIFICATION DIVISION.
PROGRAM-ID. COBJFCB.
INSTALLATION.
AUTHOR. KEVIN.
DATE-WRITTEN. 11/07/2005.

ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.

DATA DIVISION.
FILE SECTION.

WORKING-STORAGE SECTION.
01 TCB-ADDRESS-POINTER.
05 TCB-ADDR-POINTER USAGE IS POINTER.
01 TIOT-SEG-POINT.
05 TIOT-SEG-POINTER USAGE IS POINTER.
05 TIOT-SEG-PNT REDEFINES TIOT-SEG-POINTER
PIC S9(9) COMP.
01 JFCB-POINT.
05 JFCB-POINTER USAGE IS POINTER.
05 JFCB-POINT-RED REDEFINES JFCB-POINTER.
10 FILLER PIC X.
10 JFCB-LOW-3 PIC X(3).

LINKAGE SECTION.
01 DDNAME-DSN-ARRAY.
05 DDNAME-DSN OCCURS 100 TIMES INDEXED BY NDX1.
10 DDA-DDNAME PIC X(8).
10 DDA-DSN PIC X(44).

01 TCB-POINTER USAGE IS POINTER.
01 TCB.
05 FILLER PIC X(12).
05 TIOT-POINTER USAGE IS POINTER.
01 TIOT-START PIC X(24).
01 TIOT-SEG.
05 TIO-LEN PIC X.
05 FILLER PIC X(3).
05 DD-NAME PIC X(8).
05 JFCB-ADDR PIC X(3).
01 JFCB.
05 FILLER PIC X(16).
05 DS-NAME PIC X(44).

PROCEDURE DIVISION USING DDNAME-DSN-ARRAY.

MOVE LOW-VALUES TO JFCB-POINT.
MOVE X'021C' TO TCB-ADDRESS-POINTER.
SET ADDRESS OF TCB-POINTER TO TCB-ADDR-POINTER.
SET ADDRESS OF TCB TO TCB-POINTER.
SET ADDRESS OF TIOT-START TO TIOT-POINTER.
SET TIOT-SEG-POINTER TO TIOT-POINTER.
ADD 24 TO TIOT-SEG-PNT.
SET ADDRESS OF TIOT-SEG TO TIOT-SEG-POINTER.
SET NDX1 TO 1.
PERFORM UNTIL TIO-LEN = LOW-VALUES OR NDX1 > 100
MOVE DD-NAME TO DDA-DDNAME(NDX1)
MOVE JFCB-ADDR TO JFCB-LOW-3
SET ADDRESS OF JFCB TO JFCB-POINTER
MOVE DS-NAME TO DDA-DSN(NDX1)
DISPLAY DDA-DDNAME(NDX1) DDA-DSN(NDX1)
ADD 20 TO TIOT-SEG-PNT
SET ADDRESS OF TIOT-SEG TO TIOT-SEG-POINTER
SET NDX1 UP BY 1
END-PERFORM.
GOBACK.

Sent with [Proton Mail](https://proton.me/) secure email.

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


COBOL to dynamic DD name

2023-05-05 Thread rpinion865
I don't know if this program is of any use to the original poster. But, I came 
across the source this afternoon. It would seem if you can read the JFCB, maybe 
you could update it?

IDENTIFICATION DIVISION.
PROGRAM-ID. COBJFCB.
INSTALLATION.
AUTHOR. KEVIN.
DATE-WRITTEN. 11/07/2005.

ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.

DATA DIVISION.
FILE SECTION.

WORKING-STORAGE SECTION.
01 TCB-ADDRESS-POINTER.
05 TCB-ADDR-POINTER USAGE IS POINTER.
01 TIOT-SEG-POINT.
05 TIOT-SEG-POINTER USAGE IS POINTER.
05 TIOT-SEG-PNT REDEFINES TIOT-SEG-POINTER
PIC S9(9) COMP.
01 JFCB-POINT.
05 JFCB-POINTER USAGE IS POINTER.
05 JFCB-POINT-RED REDEFINES JFCB-POINTER.
10 FILLER PIC X.
10 JFCB-LOW-3 PIC X(3).

LINKAGE SECTION.
01 DDNAME-DSN-ARRAY.
05 DDNAME-DSN OCCURS 100 TIMES INDEXED BY NDX1.
10 DDA-DDNAME PIC X(8).
10 DDA-DSN PIC X(44).

01 TCB-POINTER USAGE IS POINTER.
01 TCB.
05 FILLER PIC X(12).
05 TIOT-POINTER USAGE IS POINTER.
01 TIOT-START PIC X(24).
01 TIOT-SEG.
05 TIO-LEN PIC X.
05 FILLER PIC X(3).
05 DD-NAME PIC X(8).
05 JFCB-ADDR PIC X(3).
01 JFCB.
05 FILLER PIC X(16).
05 DS-NAME PIC X(44).

PROCEDURE DIVISION USING DDNAME-DSN-ARRAY.

MOVE LOW-VALUES TO JFCB-POINT.
MOVE X'021C' TO TCB-ADDRESS-POINTER.
SET ADDRESS OF TCB-POINTER TO TCB-ADDR-POINTER.
SET ADDRESS OF TCB TO TCB-POINTER.
SET ADDRESS OF TIOT-START TO TIOT-POINTER.
SET TIOT-SEG-POINTER TO TIOT-POINTER.
ADD 24 TO TIOT-SEG-PNT.
SET ADDRESS OF TIOT-SEG TO TIOT-SEG-POINTER.
SET NDX1 TO 1.
PERFORM UNTIL TIO-LEN = LOW-VALUES OR NDX1 > 100
MOVE DD-NAME TO DDA-DDNAME(NDX1)
MOVE JFCB-ADDR TO JFCB-LOW-3
SET ADDRESS OF JFCB TO JFCB-POINTER
MOVE DS-NAME TO DDA-DSN(NDX1)
DISPLAY DDA-DDNAME(NDX1) DDA-DSN(NDX1)
ADD 20 TO TIOT-SEG-PNT
SET ADDRESS OF TIOT-SEG TO TIOT-SEG-POINTER
SET NDX1 UP BY 1
END-PERFORM.
GOBACK.

Sent with [Proton Mail](https://proton.me/) secure email.

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-05-01 Thread Schmitt, Michael
Micro Focus.

But it appears I misread the Micro Focus COBOL documentation.

I already had a program that set the data set name dynamically. I thought there 
was syntax that would allow the "external" identifier (dd name) to be a data 
name, but that's not true.

So ironically, now I have an easy way to do what I want in z/OS COBOL but not 
in Micro Focus COBOL!


-Original Message-
From: IBM Mainframe Discussion List  On Behalf Of 
Steve Thompson
Sent: Monday, May 1, 2023 12:24 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: Re: COBOL to dynamic DD name

Whose COBOL are you using on the PC side? If it is Fujitsu's, I
think SORT is built in. I'm not sure about the MicroFocus COBOL.
I don't have one of their systems.

Steve Thompson

On 5/1/2023 10:33 AM, Schmitt, Michael wrote:
> The data I'm trying to write is mixed up in an input file, so I don't know 
> which DDs I need to write to until I get there.
>
> I know that I could change the program to do an internal sort, but what I'm 
> trying to do is an *interim* solution for testing using the *PC* version of 
> the program, which *can* write to dynamic DD names.
>
> -Original Message-
> From: IBM Mainframe Discussion List  On Behalf Of 
> Farley, Peter
> Sent: Friday, April 28, 2023 3:33 PM
> To: IBM-MAIN@LISTSERV.UA.EDU
> Subject: Re: COBOL to dynamic DD name
>
> I don't think you can do that.  Unfortunately COBOL does not yet support 
> actual FILE-type variables.  COBOL files are essentially CONSTANTS in the 
> language definition.  I wish that we had PL/I's FILE variable capability, but 
> we don't.
>
> IMHO your best bet is to avoid multiple DD allocations entirely. Instead 
> start with a list of DSN's to be input (can be another separate input file) 
> and dynamically assign each DSN you wish to process to the "constant" COBOL 
> DD name in the ASSIGN clause, then FREE it (also using BPXWDYN) when you 
> finish processing each file and then start with the next DSN (if any left).
>
> You could also leave the DD names allocated as they already are and use an 
> assembler function to retrieve the JFCB (or BXWDYN) to get the DSN of each 
> assigned DD name and then use those to do a dynamic assign of each DSN to the 
> COBOL file DD name from the ASSIGN clause, but the you will have two DD names 
> assigned to the same file in the same step, which won't work unless DISP=SHR 
> for all of them.  And if any of them is a GDG (+1) from a prior step, you 
> have to mess around with getting the GDG suffix right in the dynamic allocate.
>
> I once tried to mess around with dynamically changing the DCB DD name field 
> of the closed COBOL file, but finding the DCB for a COBOL file is very 
> compiler-release dependent and is a reverse-engineering effort that can be 
> upset by IBM any time they decide to update COBOL implementation structures.  
> Messy and a maintenance nightmare, so I dropped that effort.
>
> HTH
>
> Peter
>
> -Original Message-
> From: IBM Mainframe Discussion List  On Behalf Of 
> Schmitt, Michael
> Sent: Friday, April 28, 2023 3:38 PM
> To: IBM-MAIN@LISTSERV.UA.EDU
> Subject: COBOL to dynamic DD name
>
> I know how to have a COBOL program on z/OS use a data set name that isn't 
> determined until runtime, via an environment variable. My question is can you 
> use one file (i.e. one select/assign and one FD) to write to different DD 
> names, that were already allocated in the JCL?
>
> I can't find a way, and in the manual the syntax for the environment variable 
> method requires a DSN or PATH, no option for a DD name.
> --
>
> 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...@listserv.ua.edu with the message: INFO IBM-MAIN
>
> --
> For IBM-MAIN subscribe / signoff / archive access instructions,
> send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN

--
Regards,
Steve Thompson
VS Strategies LLC
Westfield IN
972-983-9430 cell

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send e

Re: COBOL to dynamic DD name

2023-05-01 Thread Steve Thompson
Whose COBOL are you using on the PC side? If it is Fujitsu's, I 
think SORT is built in. I'm not sure about the MicroFocus COBOL. 
I don't have one of their systems.


Steve Thompson

On 5/1/2023 10:33 AM, Schmitt, Michael wrote:

The data I'm trying to write is mixed up in an input file, so I don't know 
which DDs I need to write to until I get there.

I know that I could change the program to do an internal sort, but what I'm 
trying to do is an *interim* solution for testing using the *PC* version of the 
program, which *can* write to dynamic DD names.

-Original Message-
From: IBM Mainframe Discussion List  On Behalf Of 
Farley, Peter
Sent: Friday, April 28, 2023 3:33 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: Re: COBOL to dynamic DD name

I don't think you can do that.  Unfortunately COBOL does not yet support actual 
FILE-type variables.  COBOL files are essentially CONSTANTS in the language 
definition.  I wish that we had PL/I's FILE variable capability, but we don't.

IMHO your best bet is to avoid multiple DD allocations entirely. Instead start with a 
list of DSN's to be input (can be another separate input file) and dynamically assign 
each DSN you wish to process to the "constant" COBOL DD name in the ASSIGN 
clause, then FREE it (also using BPXWDYN) when you finish processing each file and then 
start with the next DSN (if any left).

You could also leave the DD names allocated as they already are and use an 
assembler function to retrieve the JFCB (or BXWDYN) to get the DSN of each 
assigned DD name and then use those to do a dynamic assign of each DSN to the 
COBOL file DD name from the ASSIGN clause, but the you will have two DD names 
assigned to the same file in the same step, which won't work unless DISP=SHR 
for all of them.  And if any of them is a GDG (+1) from a prior step, you have 
to mess around with getting the GDG suffix right in the dynamic allocate.

I once tried to mess around with dynamically changing the DCB DD name field of 
the closed COBOL file, but finding the DCB for a COBOL file is very 
compiler-release dependent and is a reverse-engineering effort that can be 
upset by IBM any time they decide to update COBOL implementation structures.  
Messy and a maintenance nightmare, so I dropped that effort.

HTH

Peter

-Original Message-
From: IBM Mainframe Discussion List  On Behalf Of 
Schmitt, Michael
Sent: Friday, April 28, 2023 3:38 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: COBOL to dynamic DD name

I know how to have a COBOL program on z/OS use a data set name that isn't 
determined until runtime, via an environment variable. My question is can you 
use one file (i.e. one select/assign and one FD) to write to different DD 
names, that were already allocated in the JCL?

I can't find a way, and in the manual the syntax for the environment variable 
method requires a DSN or PATH, no option for a DD name.
--

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...@listserv.ua.edu with the message: INFO IBM-MAIN

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


--
Regards,
Steve Thompson
VS Strategies LLC
Westfield IN
972-983-9430 cell

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-05-01 Thread Schmitt, Michael
This works, and is the winning solution!


All that is needed is to add a nested program:

identification division.
program-id. set_dd_name.

data division.
linkage section.
01  dcb-i.
05  fillerpic x(40).
05  dd-name-dcb-i pic x(8).

01  dd-name-i pic x(8).

procedure division using dcb-i
 dd-name-i.

move dd-name-i   to dd-name-dcb-i.
goback.

end program set_dd_name.


In the parent program the select/assign is to a dummy dd name:

select output-file assign to DUMMYDD

To use, while the file is closed, call set_dd_name with the file name (e.g. 
output-file) and the desired dd name.





-Original Message-
From: IBM Mainframe Discussion List  On Behalf Of 
Schmitt, Michael
Sent: Monday, May 1, 2023 9:39 AM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: Re: COBOL to dynamic DD name

That's an interesting idea: add a nested program, call it passing the file-name 
(so it passes the FD), and then within the nested program find the offset of 
the ddname in the passed data and change it.

But it assumes that when you then open the file, COBOL doesn't move the 
select/assign dd name to the DCB again.

-Original Message-
From: IBM Mainframe Discussion List  On Behalf Of 
Charles Hardee
Sent: Friday, April 28, 2023 3:50 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: Re: COBOL to dynamic DD name

*I have not tried this*, but could you use SET FILE-VAR TO ADDRESS OF
FILE-NAME?
Does that make FILE-VAR point to the DCB?
If so, then, with the file closed, move in your DD name, open, write, close.
Rinse and repeat.

Like I said, I don't know if this will work, but it's worth a try.

Chuck


On Fri, Apr 28, 2023 at 2:38 PM Schmitt, Michael 
wrote:

> I know how to have a COBOL program on z/OS use a data set name that isn't
> determined until runtime, via an environment variable. My question is can
> you use one file (i.e. one select/assign and one FD) to write to different
> DD names, that were already allocated in the JCL?
>
> I can't find a way, and in the manual the syntax for the environment
> variable method requires a DSN or PATH, no option for a DD name.
>
> --
> For IBM-MAIN subscribe / signoff / archive access instructions,
> send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN
>

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN




--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN




--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-05-01 Thread Schmitt, Michael
To all the repliers, thanks for your ideas.

I think the answer is that there's no *simple* way to do what I asked in COBOL. 
Most replies were to suggest other ways to do it, but they were not what I 
wanted.*

I've run a test of reading a file where the DD name is determined at runtime. 
This works:

1. The select/assign is to a dummy DD name.

2. The program does a DYNALLOC call to determine the DSN for the actual target 
DD name, i.e. it is finding how it was allocated in the JCL.

   I'm using a different DYNALLOC interface than BPXWDYN but the concept is the 
same.

3. The program uses the environment variable trick to assign the DSN determined 
in step #2 to the dummy DD name.

4. Open and read.

I think this will work for writing with a disp of MOD.


* the key here is I'm trying to do in z/OS what I can easily do in not-ZOS. So 
I don't want a different language, or 100 files in the program, or assembler 
assists, etc.


-Original Message-
From: IBM Mainframe Discussion List  On Behalf Of 
Schmitt, Michael
Sent: Friday, April 28, 2023 2:38 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: COBOL to dynamic DD name

I know how to have a COBOL program on z/OS use a data set name that isn't 
determined until runtime, via an environment variable. My question is can you 
use one file (i.e. one select/assign and one FD) to write to different DD 
names, that were already allocated in the JCL?

I can't find a way, and in the manual the syntax for the environment variable 
method requires a DSN or PATH, no option for a DD name.

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-05-01 Thread Sri h Kolusu
>> SORT would be tricky to only write the header record once per file, and to 
>> resequence the records.

Michael,

Not really. There are ways to get around it.  Here is a sample job of writing 
to 2 files. You can expand that to “n” number of files.

//STEP0100 EXEC PGM=SORT
//SYSOUT   DD SYSOUT=*
//SORTIN   DD *
FILE-HEADER-01
  DATA REC01
  DATA REC02
  DATA REC04
  DATA REC05
  DATA REC06
FILE-HEADER-02
  DATA REC01
  DATA REC02
  DATA REC03
FILE-HEADER-01
  DATA REC07
  DATA REC08
  DATA REC09
//OUT01DD SYSOUT=*
//OUT02DD SYSOUT=*
//SYSINDD *
  OPTION COPY
  INREC IFTHEN=(WHEN=GROUP,
   BEGIN=(01,11,CH,EQ,C'FILE-HEADER'),
PUSH=(81:13,02,01,80)),
IFTHEN=(WHEN=(01,11,CH,EQ,C'FILE-HEADER'),
 OVERLAY=(81:82X))

  OUTFIL FNAMES=OUT01,REMOVECC,
  INCLUDE=(81,02,CH,EQ,C'01'),
  BUILD=(01,80),
  HEADER1=(83,80)

  OUTFIL FNAMES=OUT02,REMOVECC,
  INCLUDE=(81,02,CH,EQ,C'02'),
  BUILD=(01,80),
  HEADER1=(83,80)
/*


OUT01 file will have the following data.

FILE-HEADER-01
  DATA REC01
  DATA REC02
  DATA REC04
  DATA REC05
  DATA REC06
  DATA REC07
  DATA REC08
  DATA REC09

OUT02 file will have the following data.

FILE-HEADER-02
  DATA REC01
  DATA REC02
  DATA REC03


Thanks,
Kolusu
DFSORT Development
IBM Corporation



--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-05-01 Thread Sri h Kolusu
>> The data I'm trying to write is mixed up in an input file, so I don't know 
>> which DDs I need to write to until I get there.

You Code for ALL the ddnames possible and open them and write to them based on 
the file indicator.

>> I know that I could change the program to do an internal sort, but what I'm 
>> trying to do is an *interim* solution for testing using the *PC* version of 
>> the program, which *can* write to dynamic DD names.

Not sure as to why you need to sort, but you don't have to.

Assuming  the data looks like this

file-header-01
  data rec-01
  data rec02
  data rec03
...
file-header-02
  data rec-01
  data rec02
  data rec03
...

again file-header-01
file-header-01
  data rec-01
  data rec02
  data rec03
...


If that is the case, you just read the header and write it that file if it is a 
data record and as soon as you hit the next header record you switch to writing 
to the new file.  If the header record is not needed you turn on a switch to 
say s-hdr-record-written = 'y' and you check to write the next time you 
encounter the header that you have already written to

Thanks,
Kolusu


--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-05-01 Thread Jon Butler
SELECT specifies the COBOL FILE name to be ASSIGNED to a DDNAME.  The FILE name 
is then used in an FD to nominate the I/O area(s).  

There is no dynamic SELECT that I am aware of.  You have to use some form of 
SVC99.  BPXWDYN can be used for this purpose.

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-05-01 Thread Schmitt, Michael
SORT would be tricky to only write the header record once per file, and to 
resequence the records.

-Original Message-
From: IBM Mainframe Discussion List  On Behalf Of 
Mike Schwab
Sent: Friday, April 28, 2023 10:42 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: Re: COBOL to dynamic DD name

I've  seen several uses of sort to split a file into multiple output files.

On Fri, Apr 28, 2023 at 2:38 PM Schmitt, Michael
 wrote:
>
> I know how to have a COBOL program on z/OS use a data set name that isn't 
> determined until runtime, via an environment variable. My question is can you 
> use one file (i.e. one select/assign and one FD) to write to different DD 
> names, that were already allocated in the JCL?
>
> I can't find a way, and in the manual the syntax for the environment variable 
> method requires a DSN or PATH, no option for a DD name.
>
> --
> For IBM-MAIN subscribe / signoff / archive access instructions,
> send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN



--
Mike A Schwab, Springfield IL USA
Where do Forest Rangers go to get away from it all?

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN




--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-05-01 Thread Schmitt, Michael
Requirement is for COBOL; that's what the end-state program will be.

-Original Message-
From: IBM Mainframe Discussion List  On Behalf Of 
Andrew Rowley
Sent: Friday, April 28, 2023 8:18 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: Re: COBOL to dynamic DD name

On 29/04/2023 6:29 am, Schmitt, Michael wrote:
> I have an input file that contains thousands of records. They are in groups: 
> header record, then a bunch of segments all for one database name, then 
> another header, records for another database. But the same database can 
> appear more than once in the input.

Have you considered Java?

This is untested, and I don't know File Manager so I'm not 100% sure of
the logic or even the field definitions, but it should give you the
idea. Run under JZOS Batch Launcher so JCL DDs are available.

A complete Java program:

import java.io.*;
import java.util.*;
import com.ibm.jzos.*;
import com.ibm.jzos.fields.*;
import com.ibm.jzos.fields.daa.*;

public class App
{
 public static void main(String[] args) throws IOException
 {
 BinaryUnsignedIntField keyField = new BinaryUnsignedIntField(0, 2);
 BinaryUnsignedIntField countField = new
BinaryUnsignedIntField(4, 4);
 StringField ddField = new StringField(8, 8);

 byte[] nextHeader = null;

 Map outEntries = new HashMap<>();
 RecordReader in = null;
 try
 {
 in = RecordReader.newReaderForDD("INPUT");
 int bytesRead = 0;
 byte[] record = new byte[in.getLrecl()];
 while ((bytesRead = in.read(record)) >= 0)
 {
 if (keyField.getInt(record) == 0)
 {
 nextHeader = Arrays.copyOfRange(record, 0, bytesRead);
 }
 else
 {
 String ddname = ddField.getString(record);
 OutEntry out = outEntries.get(ddname);
 if (out == null)
 {
 out = new OutEntry(ddname);
 outEntries.put(ddname, out);
 out.writer.write(nextHeader);
 }
 out.count++;
 countField.putInt(out.count, record);
 out.writer.write(record, 0, bytesRead);
 }
 }
 }
 finally
 {
 if (in != null)
 in.close();
 for (OutEntry entry : outEntries.values())
 {
 entry.writer.close();
 }
 }
 }

 private static class OutEntry
 {
 OutEntry(String ddname) throws IOException
 {
 writer = RecordWriter.newWriterForDD(ddname);
 }
 int count = 0;
 RecordWriter writer;
 }
}

--
Andrew Rowley
Black Hill Software

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN




--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-05-01 Thread Schmitt, Michael
Requirement is for COBOL.

-Original Message-
From: IBM Mainframe Discussion List  On Behalf Of 
Seymour J Metz
Sent: Friday, April 28, 2023 5:49 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: Re: COBOL to dynamic DD name

How many different files does he have? An equivalent to the PL/I FILE keyword 
would be more flexible than hard-wiring the ddnames at compile time.


From: IBM Mainframe Discussion List  on behalf of Sri 
h Kolusu 
Sent: Friday, April 28, 2023 4:59 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: Re: COBOL to dynamic DD name

>> The OP isn't trying to retrieve the information; he's trying to open a file 
>> using a dynamic ddname. Put another way, he wants to open the same DCB 
>> multiple times, with a different DCBDDNAM each time.

SeyMour

>From the limited information that OP provided, IMHO he was planning on having 
>multiple open and close of files.  However, he doesn't really need to do that. 
>He can open all the files and then have the logic to write to specific file

Sample pseudo code

OPEN INPUT   file-input
 OUTPUT  fileout1
 fileout2
 fileout3
 fileout4
 ..
 fileoutn

MAIN-LOGIC


EVALUATE TRUE
WHEN WS-FILE-IND = 'f01'
 PERFORM WRITE-TO-FILE01
 PERFORM READ-INPUT-FILE
WHEN WS-FILE-IND = 'f02'
 PERFORM WRITE-TO-FILE02
 PERFORM READ-INPUT-FILE
WHEN WS-FILE-IND = 'f03'
 PERFORM WRITE-TO-FILE03
 PERFORM READ-INPUT-FILE
n... files
END-EVALUATE


CLOSE  file-input
   fileout1
   ..


Thanks,
Kolusu
DFSORT Development
IBM Corporation


--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-05-01 Thread Schmitt, Michael
I'm trying to avoid that because the end-state program won't be doing that, if 
I'm not in z/OS COBOL I can just have one file and dynamically switch the DD 
name.

At least I think I can; I haven't tested that exact syntax yet.

-Original Message-
From: IBM Mainframe Discussion List  On Behalf Of Sri 
h Kolusu
Sent: Friday, April 28, 2023 4:00 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: Re: COBOL to dynamic DD name

>> The OP isn't trying to retrieve the information; he's trying to open a file 
>> using a dynamic ddname. Put another way, he wants to open the same DCB 
>> multiple times, with a different DCBDDNAM each time.

SeyMour

>From the limited information that OP provided, IMHO he was planning on having 
>multiple open and close of files.  However, he doesn't really need to do that. 
>He can open all the files and then have the logic to write to specific file

Sample pseudo code

OPEN INPUT   file-input
 OUTPUT  fileout1
 fileout2
 fileout3
 fileout4
 ..
 fileoutn

MAIN-LOGIC


EVALUATE TRUE
WHEN WS-FILE-IND = 'f01'
 PERFORM WRITE-TO-FILE01
 PERFORM READ-INPUT-FILE
WHEN WS-FILE-IND = 'f02'
 PERFORM WRITE-TO-FILE02
 PERFORM READ-INPUT-FILE
WHEN WS-FILE-IND = 'f03'
 PERFORM WRITE-TO-FILE03
 PERFORM READ-INPUT-FILE
n... files
END-EVALUATE


CLOSE  file-input
   fileout1
   ..


Thanks,
Kolusu
DFSORT Development
IBM Corporation


--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-05-01 Thread Schmitt, Michael
That's an interesting idea: add a nested program, call it passing the file-name 
(so it passes the FD), and then within the nested program find the offset of 
the ddname in the passed data and change it.

But it assumes that when you then open the file, COBOL doesn't move the 
select/assign dd name to the DCB again.

-Original Message-
From: IBM Mainframe Discussion List  On Behalf Of 
Charles Hardee
Sent: Friday, April 28, 2023 3:50 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: Re: COBOL to dynamic DD name

*I have not tried this*, but could you use SET FILE-VAR TO ADDRESS OF
FILE-NAME?
Does that make FILE-VAR point to the DCB?
If so, then, with the file closed, move in your DD name, open, write, close.
Rinse and repeat.

Like I said, I don't know if this will work, but it's worth a try.

Chuck


On Fri, Apr 28, 2023 at 2:38 PM Schmitt, Michael 
wrote:

> I know how to have a COBOL program on z/OS use a data set name that isn't
> determined until runtime, via an environment variable. My question is can
> you use one file (i.e. one select/assign and one FD) to write to different
> DD names, that were already allocated in the JCL?
>
> I can't find a way, and in the manual the syntax for the environment
> variable method requires a DSN or PATH, no option for a DD name.
>
> --
> For IBM-MAIN subscribe / signoff / archive access instructions,
> send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN
>

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN




--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-05-01 Thread Schmitt, Michael
Yeah, the File Manager solution is slick, but the end state won't be running on 
z/OS.

-Original Message-
From: IBM Mainframe Discussion List  On Behalf Of Sri 
h Kolusu
Sent: Friday, April 28, 2023 3:35 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: Re: COBOL to dynamic DD name

>> Now we're trying to replace the File Manager step. If it was possible to do 
>> this in z/OS COBOL we could use it, but it isn't worth a large effort 
>> because it would be an interim solution anyway.

Michael,

Not sure as to why you want to replace file manager step with a COBOL program, 
but DFSORT can easily be used to fulfil the requirement. Let me know the DCB 
properties(LRECL, RECFM) of the input file and I can show you way to split the 
records into multiple files.

Thanks,
Kolusu
DFSORT Development
IBM Corporation


--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN




--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-05-01 Thread Schmitt, Michael
I don't have a license for the PL/I compiler, and...

The ends state will be a program that runs on my PC, where it doesn't have the 
same limitation as z/OS COBOL. What I'm trying to do now is test that program 
logic in z/OS. So, I need it to be COBOL.

-Original Message-
From: IBM Mainframe Discussion List  On Behalf Of 
Seymour J Metz
Sent: Friday, April 28, 2023 3:33 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: Re: COBOL to dynamic DD name

Is PL/I an option at your shop?


From: IBM Mainframe Discussion List  on behalf of 
Schmitt, Michael 
Sent: Friday, April 28, 2023 4:29 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: Re: COBOL to dynamic DD name

I have an input file that contains thousands of records. They are in groups: 
header record, then a bunch of segments all for one database name, then another 
header, records for another database. But the same database can appear more 
than once in the input.

The step takes this input and creates one output file per database, with one 
header. And resequences the records so they go 1,2,3,4, for each output DD.

On z/OS this step is done using File Manager, with this code:

if fld(1,2,B) = 0 then do   /* if sort key is 0 then  */
   header_rec = inrec   /*save the header record  */
   return 'drop'/*get next record */
   end

dd_name = overlay('N', fld(9,8), 4) /* get DD name from DBD name  */

if recsout(dd_name) = 0 then do /* if 1st record for database */
   outrec.dd_name = header_rec
   write(dd_name)   /*write the header*/
   drop outrec.dd_name
   end

ovly_out(recsout(dd_name), 5,4,B)   /* resequence the records */
write(dd_name)  /* write the segment record   */
return 'drop'


That's the ENTIRE program!


On my PC I have a COBOL program, with a lot more logic, that does essentially 
the same thing. As it is reading the input, each time it gets to a different 
database name, it closes the file it has been writing to and opens the file for 
the appropriate DD name, extending it. So the program only needs to have one 
output file defined, even though it is writing to different DDs as it goes.


Now we're trying to replace the File Manager step. If it was possible to do 
this in z/OS COBOL we could use it, but it isn't worth a large effort because 
it would be an interim solution anyway.


-Original Message-
From: IBM Mainframe Discussion List  On Behalf Of Tom 
Marchant
Sent: Friday, April 28, 2023 3:18 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: Re: COBOL to dynamic DD name

I don't know any Cobol syntax that would change the DDNAME in a DCB, but you 
could call an assembler routine to change the DDNAME before OPEN. Why would you 
want to do that?

I'm a bit baffled. In z/OS and its ancestors, the data set name isn't 
determined until runtime, via JCL.

Perhaps if you describe the problem you are trying to solve.

--
Tom Marchant

On Fri, 28 Apr 2023 19:37:39 +, Schmitt, Michael  
wrote:

>I know how to have a COBOL program on z/OS use a data set name that isn't 
>determined until runtime, via an environment variable. My question is can you 
>use one file (i.e. one select/assign and one FD) to write to different DD 
>names, that were already allocated in the JCL?
>
>I can't find a way, and in the manual the syntax for the environment variable 
>method requires a DSN or PATH, no option for a DD name.

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN




--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-05-01 Thread Schmitt, Michael
All are VB

-Original Message-
From: IBM Mainframe Discussion List  On Behalf Of Sri 
h Kolusu
Sent: Friday, April 28, 2023 3:38 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: Re: COBOL to dynamic DD name

>> So use it to retrieve the data set name that is allocated in the JCL to the 
>> DD, then use the environment variable method to write to that same data set 
>> name? Hmmm.

Michael,

Not really,  once you get the Dataset name, you can open it in EXTENDED mode 
and write the output.  However, you are still limited by the LRECL and RECFM of 
the ddname.   Since you are splitting the records, I guess all of them have the 
same length

Thanks,
Kolusu
DFSORT Development
IBM Corporation

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-05-01 Thread Schmitt, Michael
The data I'm trying to write is mixed up in an input file, so I don't know 
which DDs I need to write to until I get there.

I know that I could change the program to do an internal sort, but what I'm 
trying to do is an *interim* solution for testing using the *PC* version of the 
program, which *can* write to dynamic DD names.

-Original Message-
From: IBM Mainframe Discussion List  On Behalf Of 
Farley, Peter
Sent: Friday, April 28, 2023 3:33 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: Re: COBOL to dynamic DD name

I don't think you can do that.  Unfortunately COBOL does not yet support actual 
FILE-type variables.  COBOL files are essentially CONSTANTS in the language 
definition.  I wish that we had PL/I's FILE variable capability, but we don't.

IMHO your best bet is to avoid multiple DD allocations entirely. Instead start 
with a list of DSN's to be input (can be another separate input file) and 
dynamically assign each DSN you wish to process to the "constant" COBOL DD name 
in the ASSIGN clause, then FREE it (also using BPXWDYN) when you finish 
processing each file and then start with the next DSN (if any left).

You could also leave the DD names allocated as they already are and use an 
assembler function to retrieve the JFCB (or BXWDYN) to get the DSN of each 
assigned DD name and then use those to do a dynamic assign of each DSN to the 
COBOL file DD name from the ASSIGN clause, but the you will have two DD names 
assigned to the same file in the same step, which won't work unless DISP=SHR 
for all of them.  And if any of them is a GDG (+1) from a prior step, you have 
to mess around with getting the GDG suffix right in the dynamic allocate.

I once tried to mess around with dynamically changing the DCB DD name field of 
the closed COBOL file, but finding the DCB for a COBOL file is very 
compiler-release dependent and is a reverse-engineering effort that can be 
upset by IBM any time they decide to update COBOL implementation structures.  
Messy and a maintenance nightmare, so I dropped that effort.

HTH

Peter

-Original Message-
From: IBM Mainframe Discussion List  On Behalf Of 
Schmitt, Michael
Sent: Friday, April 28, 2023 3:38 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: COBOL to dynamic DD name

I know how to have a COBOL program on z/OS use a data set name that isn't 
determined until runtime, via an environment variable. My question is can you 
use one file (i.e. one select/assign and one FD) to write to different DD 
names, that were already allocated in the JCL?

I can't find a way, and in the manual the syntax for the environment variable 
method requires a DSN or PATH, no option for a DD name.
--

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...@listserv.ua.edu with the message: INFO IBM-MAIN

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-05-01 Thread Schmitt, Michael
The goal is to OPEN the DD name that is already allocated in the JCL, but with 
one select/assign and FD, in COBOL.

-Original Message-
From: IBM Mainframe Discussion List  On Behalf Of 
Paul Gilmartin
Sent: Friday, April 28, 2023 2:53 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: Re: COBOL to dynamic DD name

On Fri, 28 Apr 2023 19:37:39 +, Schmitt, Michael wrote:

>I know how to have a COBOL program on z/OS use a data set name that isn't 
>determined until runtime, via an environment variable. My question is can you 
>use one file (i.e. one select/assign and one FD) to write to different DD 
>names, that were already allocated in the JCL?
>
>I can't find a way, and in the manual the syntax for the environment variable 
>method requires a DSN or PATH, no option for a DD name.
>
Do you know the DSN or PATH?

Do you want to specify the DD name or let Dynalloc choose one?

Do BPXWDYN keys RTDDN and INFO help you?  BPXWDYN can be called with OS 
standard linkage.
<https://www.ibm.com/docs/en/zos/2.5.0?topic=services-bpxwdyn-text-interface-dynamic-allocation-dynamic-output>

--
gil

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-05-01 Thread Jon Butler
As suggested, simply define four output files, open them, and then write to 
them based on the data in the input file record, perhaps using an EVALUATE 
statement.  Opening them all at the start of your program has another 
advantage: if you open only one output at a time and loop between them, it's 
possible that another job could open your target file when you have it closed 
and you will not be able to get ahold to write to it.

If you really must have only one output file open at a time, you can 
dynamically allocate and deallocate the DDNAME amongst multiple DSNs with 
BPXWDYN; ostensibly an OMVS routine designed for use with REXX, but I have used 
it with COBOL as well.  

call BPXWDYN using "alloc fi(ddanme) da(my.dataset.name) old" *> change the 
DISP as required

call BPXWDYN using "free fi(ddanme)"

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-05-01 Thread Allan Staller
Classification: Confidential

Same answer as my previous post. Open/close/read/write as needed.
Nothing here need to be dynamic.

Am I missing something?

-Original Message-
From: IBM Mainframe Discussion List  On Behalf Of 
Schmitt, Michael
Sent: Friday, April 28, 2023 3:30 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: Re: COBOL to dynamic DD name

[CAUTION: This Email is from outside the Organization. Unless you trust the 
sender, Don’t click links or open attachments as it may be a Phishing email, 
which can steal your Information and compromise your Computer.]

I have an input file that contains thousands of records. They are in groups: 
header record, then a bunch of segments all for one database name, then another 
header, records for another database. But the same database can appear more 
than once in the input.

The step takes this input and creates one output file per database, with one 
header. And resequences the records so they go 1,2,3,4, for each output DD.

On z/OS this step is done using File Manager, with this code:

if fld(1,2,B) = 0 then do   /* if sort key is 0 then  */
   header_rec = inrec   /*save the header record  */
   return 'drop'/*get next record */
   end

dd_name = overlay('N', fld(9,8), 4) /* get DD name from DBD name  */

if recsout(dd_name) = 0 then do /* if 1st record for database */
   outrec.dd_name = header_rec
   write(dd_name)   /*write the header*/
   drop outrec.dd_name
   end

ovly_out(recsout(dd_name), 5,4,B)   /* resequence the records */
write(dd_name)  /* write the segment record   */
return 'drop'


That's the ENTIRE program!


On my PC I have a COBOL program, with a lot more logic, that does essentially 
the same thing. As it is reading the input, each time it gets to a different 
database name, it closes the file it has been writing to and opens the file for 
the appropriate DD name, extending it. So the program only needs to have one 
output file defined, even though it is writing to different DDs as it goes.


Now we're trying to replace the File Manager step. If it was possible to do 
this in z/OS COBOL we could use it, but it isn't worth a large effort because 
it would be an interim solution anyway.


-Original Message-
From: IBM Mainframe Discussion List  On Behalf Of Tom 
Marchant
Sent: Friday, April 28, 2023 3:18 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: Re: COBOL to dynamic DD name

I don't know any Cobol syntax that would change the DDNAME in a DCB, but you 
could call an assembler routine to change the DDNAME before OPEN. Why would you 
want to do that?

I'm a bit baffled. In z/OS and its ancestors, the data set name isn't 
determined until runtime, via JCL.

Perhaps if you describe the problem you are trying to solve.

--
Tom Marchant

On Fri, 28 Apr 2023 19:37:39 +, Schmitt, Michael  
wrote:

>I know how to have a COBOL program on z/OS use a data set name that isn't 
>determined until runtime, via an environment variable. My question is can you 
>use one file (i.e. one select/assign and one FD) to write to different DD 
>names, that were already allocated in the JCL?
>
>I can't find a way, and in the manual the syntax for the environment variable 
>method requires a DSN or PATH, no option for a DD name.

--
For IBM-MAIN subscribe / signoff / archive access instructions, send email to 
lists...@listserv.ua.edu with the message: INFO IBM-MAIN




--
For IBM-MAIN subscribe / signoff / archive access instructions, send email to 
lists...@listserv.ua.edu with the message: INFO IBM-MAIN
::DISCLAIMER::

The contents of this e-mail and any attachment(s) are confidential and intended 
for the named recipient(s) only. E-mail transmission is not guaranteed to be 
secure or error-free as information could be intercepted, corrupted, lost, 
destroyed, arrive late or incomplete, or may contain viruses in transmission. 
The e mail and its contents (with or without referred errors) shall therefore 
not attach any liability on the originator or HCL or its affiliates. Views or 
opinions, if any, presented in this email are solely those of the author and 
may not necessarily reflect the views or opinions of HCL or its affiliates. Any 
form of reproduction, dissemination, copying, disclosure, modification, 
distribution and / or publication of this message without the prior written 
consent of authorized representative of HCL is strictly prohibited. If you have 
received this email in error please delete it and notify the sender 
immediately. Before opening any email and/or attachments, please check them for 
viruses and other defects.


--
For IBM-MAI

Re: COBOL to dynamic DD name

2023-05-01 Thread Allan Staller
Classification: Confidential

If the JCL has all of the DD's defined. Just open/close the requested file(s) 
as needed. No need for dynamic ddname.

>> I'm not trying to allocate the files. The JCL for the step has all the DDs. 
>> I just need to be able open, extend, and close the select/assign to 
>> different DDs where which ones I use and which order is not known until I'm 
>> working through an input file.

::DISCLAIMER::

The contents of this e-mail and any attachment(s) are confidential and intended 
for the named recipient(s) only. E-mail transmission is not guaranteed to be 
secure or error-free as information could be intercepted, corrupted, lost, 
destroyed, arrive late or incomplete, or may contain viruses in transmission. 
The e mail and its contents (with or without referred errors) shall therefore 
not attach any liability on the originator or HCL or its affiliates. Views or 
opinions, if any, presented in this email are solely those of the author and 
may not necessarily reflect the views or opinions of HCL or its affiliates. Any 
form of reproduction, dissemination, copying, disclosure, modification, 
distribution and / or publication of this message without the prior written 
consent of authorized representative of HCL is strictly prohibited. If you have 
received this email in error please delete it and notify the sender 
immediately. Before opening any email and/or attachments, please check them for 
viruses and other defects.


--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: File Handles (was: COBOL to dynamic DD name)

2023-04-30 Thread Binyamin Dissen
COBOL does NOT demand a DSNAME. It is perfectly happy with DDNAMEs.

There were extensions to COBOL to allow a DSNAME via a system variable by
playing with the SELECT statement.

Of course, one could ask if the dsname is already in a system variable, why
not supply it in the JCL. But I digress.


On Sat, 29 Apr 2023 08:58:36 -0500 Paul Gilmartin
<042bfe9c879d-dmarc-requ...@listserv.ua.edu> wrote:

:>On Fri, 28 Apr 2023 19:37:39 +, Schmitt, Michael wrote:
:>
:>>I know how to have a COBOL program on z/OS use a data set name that isn't 
determined until runtime, via an environment variable. My question is can you 
use one file (i.e. one select/assign and one FD) to write to different DD 
names, that were already allocated in the JCL?
:>>
:>When I wear my ill-fitting MVS hat, I find it bizarre that any HLL is
:>DDNAME-ignorant.  It's what most of them require.  Think EXECIO.
:>But COBOL ...
:>
:>A DDNAME is a component of I/O abstraction, a handle for a data set,
:>analogous to the way in UNIX that a descriptor is a handle for a
:>pathname.  And some UNIX utilities accept only pathnames, not
:>descriptors.  But UNIX-like systems that I nave used, Solaris, Linux,
:>MacOS, OMVS, provide a pseudo-mountpoint, "/dev/fd/" to treat a
:>descriptor as a pathname.  This is not required by POSIX.
:>For example:
:>exec 42wc /dev/fd/42
:>... just works.
:>
:>A modest proposal: Wouldn't it be nice if z/OS provided a pseudo-HLQ 
:>such as "DDHLQ." to meet the requirements of languages
:>such as COBOL which demand a DSN, not a DDNAME, so given
:>SYSUT42 a program could form "DSN=DDHLQ.SYSUT42", look it up
:>in the catalog, OPEN, and read it.
:>
:>RFE, anyone?

--
Binyamin Dissen 
http://www.dissensoftware.com

Director, Dissen Software, Bar & Grill - Israel

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-04-29 Thread Farley, Peter
From the COBOL Language Reference:

The ADDRESS OF special register references the address of a data item in the 
LINKAGE SECTION, the LOCAL-STORAGE SECTION, or the WORKING-STORAGE SECTION.

Note the exclusion of the FILE SECTION from that list.  We had to set up an 
assembler "get address of" subroutine and pass a file name to get a FILE 
address when we had a particular need.

As I remember it, the address you get even using a subroutine may be the COBOL 
FCB rather than the actual DCB, but it's been too long and I don't remember 
accurately if that is true or not, and it may be compiler-release dependent.  
Plus no one can promise you that future generated COBOL code or updated 
compiler subroutines won't overlay your dynamic DCB changes with values 
declared in the program (e.g., record length and format from the COBOL FCB 
area), thus undoing the change you wanted to make.  Caveat emptor.

Even if you can get the DCB address that way and COBOL lets you change it as 
you please, mucking about with the DCB may work but it is likely to be less 
maintainable as time passes and those of us who intimately understand OS 
control blocks leave the field and those left are less knowledgeable about the 
uses (and abuses) that can trip you up.

IMHO, BPXWDY2 or a full-on assembler dynamic I/O subroutine (i.e., no COBOL 
FILE usage at all) are both better solutions.  I believe CBT has at least one 
version of the assembler solution out there somewhere.

Peter

-Original Message-
From: IBM Mainframe Discussion List  On Behalf Of 
Charles Hardee
Sent: Friday, April 28, 2023 4:50 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: Re: COBOL to dynamic DD name

*I have not tried this*, but could you use SET FILE-VAR TO ADDRESS OF FILE-NAME?
Does that make FILE-VAR point to the DCB?
If so, then, with the file closed, move in your DD name, open, write, close.
Rinse and repeat.

Like I said, I don't know if this will work, but it's worth a try.

Chuck


On Fri, Apr 28, 2023 at 2:38 PM Schmitt, Michael 
wrote:

> I know how to have a COBOL program on z/OS use a data set name that 
> isn't determined until runtime, via an environment variable. My 
> question is can you use one file (i.e. one select/assign and one FD) 
> to write to different DD names, that were already allocated in the JCL?
>
> I can't find a way, and in the manual the syntax for the environment 
> variable method requires a DSN or PATH, no option for a DD name.
--

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...@listserv.ua.edu with the message: INFO IBM-MAIN


File Handles (was: COBOL to dynamic DD name)

2023-04-29 Thread Paul Gilmartin
On Fri, 28 Apr 2023 19:37:39 +, Schmitt, Michael wrote:

>I know how to have a COBOL program on z/OS use a data set name that isn't 
>determined until runtime, via an environment variable. My question is can you 
>use one file (i.e. one select/assign and one FD) to write to different DD 
>names, that were already allocated in the JCL?
>
When I wear my ill-fitting MVS hat, I find it bizarre that any HLL is
DDNAME-ignorant.  It's what most of them require.  Think EXECIO.
But COBOL ...

A DDNAME is a component of I/O abstraction, a handle for a data set,
analogous to the way in UNIX that a descriptor is a handle for a
pathname.  And some UNIX utilities accept only pathnames, not
descriptors.  But UNIX-like systems that I nave used, Solaris, Linux,
MacOS, OMVS, provide a pseudo-mountpoint, "/dev/fd/" to treat a
descriptor as a pathname.  This is not required by POSIX.
For example:
exec 42" to meet the requirements of languages
such as COBOL which demand a DSN, not a DDNAME, so given
SYSUT42 a program could form "DSN=DDHLQ.SYSUT42", look it up
in the catalog, OPEN, and read it.

RFE, anyone?

-- 
gil

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-04-28 Thread Paul Gilmartin
On Sat, 29 Apr 2023 13:51:00 +1000, Andrew Rowley wrote:
>
>Fair point... although I would contend that a Java program without
>comments is easier to understand than DFSORT control statements!
>
Yes.  It appears as if the specifier of DFSORT control statement syntax
was traumatized in utero by CMS or POSIX test(1).

There's too much key,value,key,value,key,value,...
where either ...,key(value),key(value),key(value),...
or ...,key=value,key=value,key=value,...
would be preferable.

-- 
gil

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-04-28 Thread Andrew Rowley

On 29/04/2023 11:48 am, Paul Gilmartin wrote:

Obviously a complete Java program needs very few comments.


Fair point... although I would contend that a Java program without 
comments is easier to understand than DFSORT control statements! Here is 
a version with comments (again, untested):


import java.io.*;
import java.util.*;
import com.ibm.jzos.*;
import com.ibm.jzos.fields.*;
import com.ibm.jzos.fields.daa.*;

public class App
{
    public static void main(String[] args) throws IOException
    {
    // define JZOS fields for the key, count and ddname
    BinaryUnsignedIntField keyField = new BinaryUnsignedIntField(0, 2);
    BinaryUnsignedIntField countField = new 
BinaryUnsignedIntField(4, 4);

    StringField ddField = new StringField(8, 8);

    // variable to save the current header record
    // I'm not sure I understand the input data i.e. why this is
    // necessary but I think this matches the logic from the File 
Manager

    // sample
    byte[] nextHeader = null;

    // map of ddname -> OutEntry containing RecordWriter and count
    Map outEntries = new HashMap<>();

    RecordReader input = null;
    try
    {
        // open the input dataset
        input = RecordReader.newReaderForDD("INPUT");
        int bytesRead = 0;

        // create a buffer for the input record
        byte[] record = new byte[input.getLrecl()];
        // read records
        while ((bytesRead = input.read(record)) >= 0)
        {
            if (keyField.getInt(record) == 0) // if key is zero
            {
                // copy and save the header record to a new byte array
                nextHeader = Arrays.copyOfRange(record, 0, bytesRead);
            }
            else
            {
                // get the ddname from the record
                // (this probably doesn't match the File Manager 
sample -

                // might need to concatenate/substring etc)
                String ddname = ddField.getString(record);

                // find the output entry for this ddname
                OutEntry out = outEntries.get(ddname);

                if (out == null) // doesn't exist: this is the 
first record for database

                {
                    out = new OutEntry(ddname);   // create/open a 
new entry

                    outEntries.put(ddname, out);  // save it in the map
                    out.writer.write(nextHeader, 0, 
nextHeader.length); // write the saved header entry

                }
                out.count++; // increment record count for this entry
                countField.putInt(out.count, record);   // update 
sequence in the record
                out.writer.write(record, 0, bytesRead); // write 
the record

            }
        }
    }
    finally // close all files
    {
        if (input != null)
            input.close();
        for (OutEntry entry : outEntries.values()) // each output 
writer

        {
            entry.writer.close();
        }
    }
    }

    /**
     * A class to keep a RecordWriter and count for each ddname
     * best practice would be to encapsulate with getters/setters
     * but we're trying to keep things simple for the sample
     */
    private static class OutEntry
    {
    OutEntry(String ddname) throws IOException
    {
        // open a RecordWriter for the supplied ddname
        writer = RecordWriter.newWriterForDD(ddname);
    }
    int count = 0;
    RecordWriter writer;
    }
}




--
Andrew Rowley
Black Hill Software

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-04-28 Thread Mike Schwab
I've  seen several uses of sort to split a file into multiple output files.

On Fri, Apr 28, 2023 at 2:38 PM Schmitt, Michael
 wrote:
>
> I know how to have a COBOL program on z/OS use a data set name that isn't 
> determined until runtime, via an environment variable. My question is can you 
> use one file (i.e. one select/assign and one FD) to write to different DD 
> names, that were already allocated in the JCL?
>
> I can't find a way, and in the manual the syntax for the environment variable 
> method requires a DSN or PATH, no option for a DD name.
>
> --
> For IBM-MAIN subscribe / signoff / archive access instructions,
> send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN



-- 
Mike A Schwab, Springfield IL USA
Where do Forest Rangers go to get away from it all?

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-04-28 Thread Paul Gilmartin
On Fri, 28 Apr 2023 20:40:37 +, Seymour J Metz wrote:

>The OP isn't trying to retrieve the information; ...
>
>
>From:  Sri h Kolusu 
>Sent: Friday, April 28, 2023 4:26 PM
>
>As steve mentioned in earlier post , you can BPXWDYN2 to retrieve the info a 
>dataset/ddname.
>
ITYM BPXWDY2.

>Here is an example
>https://www.mvsforums.com/helpboards/viewtopic.php?p=62866#62866

-- 
gil

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-04-28 Thread Paul Gilmartin
On Sat, 29 Apr 2023 11:17:39 +1000, Andrew Rowley  wrote:
>...
>A complete Java program:
>

Obviously a complete Java program needs very few comments.

-- 
gil

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-04-28 Thread Andrew Rowley

On 29/04/2023 6:29 am, Schmitt, Michael wrote:

I have an input file that contains thousands of records. They are in groups: 
header record, then a bunch of segments all for one database name, then another 
header, records for another database. But the same database can appear more 
than once in the input.


Have you considered Java?

This is untested, and I don't know File Manager so I'm not 100% sure of 
the logic or even the field definitions, but it should give you the 
idea. Run under JZOS Batch Launcher so JCL DDs are available.


A complete Java program:

import java.io.*;
import java.util.*;
import com.ibm.jzos.*;
import com.ibm.jzos.fields.*;
import com.ibm.jzos.fields.daa.*;

public class App
{
    public static void main(String[] args) throws IOException
    {
    BinaryUnsignedIntField keyField = new BinaryUnsignedIntField(0, 2);
    BinaryUnsignedIntField countField = new 
BinaryUnsignedIntField(4, 4);

    StringField ddField = new StringField(8, 8);

    byte[] nextHeader = null;

    Map outEntries = new HashMap<>();
    RecordReader in = null;
    try
    {
        in = RecordReader.newReaderForDD("INPUT");
        int bytesRead = 0;
        byte[] record = new byte[in.getLrecl()];
        while ((bytesRead = in.read(record)) >= 0)
        {
            if (keyField.getInt(record) == 0)
            {
                nextHeader = Arrays.copyOfRange(record, 0, bytesRead);
            }
            else
            {
                String ddname = ddField.getString(record);
                OutEntry out = outEntries.get(ddname);
                if (out == null)
                {
                    out = new OutEntry(ddname);
                    outEntries.put(ddname, out);
                    out.writer.write(nextHeader);
                }
                out.count++;
                countField.putInt(out.count, record);
                out.writer.write(record, 0, bytesRead);
            }
        }
    }
    finally
    {
        if (in != null)
            in.close();
        for (OutEntry entry : outEntries.values())
        {
            entry.writer.close();
        }
    }
    }

    private static class OutEntry
    {
    OutEntry(String ddname) throws IOException
    {
        writer = RecordWriter.newWriterForDD(ddname);
    }
    int count = 0;
    RecordWriter writer;
    }
}

--
Andrew Rowley
Black Hill Software

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-04-28 Thread Seymour J Metz
How many different files does he have? An equivalent to the PL/I FILE keyword 
would be more flexible than hard-wiring the ddnames at compile time.


From: IBM Mainframe Discussion List  on behalf of Sri 
h Kolusu 
Sent: Friday, April 28, 2023 4:59 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: Re: COBOL to dynamic DD name

>> The OP isn't trying to retrieve the information; he's trying to open a file 
>> using a dynamic ddname. Put another way, he wants to open the same DCB 
>> multiple times, with a different DCBDDNAM each time.

SeyMour

>From the limited information that OP provided, IMHO he was planning on having 
>multiple open and close of files.  However, he doesn't really need to do that. 
>He can open all the files and then have the logic to write to specific file

Sample pseudo code

OPEN INPUT   file-input
 OUTPUT  fileout1
 fileout2
 fileout3
 fileout4
 ..
 fileoutn

MAIN-LOGIC


EVALUATE TRUE
WHEN WS-FILE-IND = 'f01'
 PERFORM WRITE-TO-FILE01
 PERFORM READ-INPUT-FILE
WHEN WS-FILE-IND = 'f02'
 PERFORM WRITE-TO-FILE02
 PERFORM READ-INPUT-FILE
WHEN WS-FILE-IND = 'f03'
 PERFORM WRITE-TO-FILE03
 PERFORM READ-INPUT-FILE
n... files
END-EVALUATE


CLOSE  file-input
   fileout1
   ..


Thanks,
Kolusu
DFSORT Development
IBM Corporation


--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-04-28 Thread Paul Gilmartin
On Fri, 28 Apr 2023 20:26:38 +, Sri h Kolusu wrote:
>...
>Here is an example
>
>https://www.mvsforums.com/helpboards/viewtopic.php?p=62866#62866
>
Thanks.  I think I see how that works.  Trying to understand it, I found a
contradiction in the REXX UNIX  Ref.  I submitted an RCF.

-- 
gil

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-04-28 Thread Sri h Kolusu
>> The OP isn't trying to retrieve the information; he's trying to open a file 
>> using a dynamic ddname. Put another way, he wants to open the same DCB 
>> multiple times, with a different DCBDDNAM each time.

SeyMour

>From the limited information that OP provided, IMHO he was planning on having 
>multiple open and close of files.  However, he doesn't really need to do that. 
>He can open all the files and then have the logic to write to specific file

Sample pseudo code

OPEN INPUT   file-input
 OUTPUT  fileout1
 fileout2
 fileout3
 fileout4
 ..
 fileoutn

MAIN-LOGIC


EVALUATE TRUE
WHEN WS-FILE-IND = 'f01'
 PERFORM WRITE-TO-FILE01
 PERFORM READ-INPUT-FILE
WHEN WS-FILE-IND = 'f02'
 PERFORM WRITE-TO-FILE02
 PERFORM READ-INPUT-FILE
WHEN WS-FILE-IND = 'f03'
 PERFORM WRITE-TO-FILE03
 PERFORM READ-INPUT-FILE
n... files
END-EVALUATE


CLOSE  file-input
   fileout1
   ..


Thanks,
Kolusu
DFSORT Development
IBM Corporation


--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-04-28 Thread Charles Hardee
*I have not tried this*, but could you use SET FILE-VAR TO ADDRESS OF
FILE-NAME?
Does that make FILE-VAR point to the DCB?
If so, then, with the file closed, move in your DD name, open, write, close.
Rinse and repeat.

Like I said, I don't know if this will work, but it's worth a try.

Chuck


On Fri, Apr 28, 2023 at 2:38 PM Schmitt, Michael 
wrote:

> I know how to have a COBOL program on z/OS use a data set name that isn't
> determined until runtime, via an environment variable. My question is can
> you use one file (i.e. one select/assign and one FD) to write to different
> DD names, that were already allocated in the JCL?
>
> I can't find a way, and in the manual the syntax for the environment
> variable method requires a DSN or PATH, no option for a DD name.
>
> --
> For IBM-MAIN subscribe / signoff / archive access instructions,
> send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN
>

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-04-28 Thread Seymour J Metz
The OP isn't trying to retrieve the information; he's trying to open a file 
using a dynamic ddname. Put another way, he wants to open the same DCB multiple 
times, with a different DCBDDNAM each time.


From: IBM Mainframe Discussion List  on behalf of Sri 
h Kolusu 
Sent: Friday, April 28, 2023 4:26 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: Re: COBOL to dynamic DD name

>> I'm not trying to allocate the files. The JCL for the step has all the DDs. 
>> I just need to be able open, extend, and close the select/assign to 
>> different DDs where which ones I use and which order is not known until I'm 
>> working through an input file.

Michael,

As steve mentioned in earlier post , you can BPXWDYN2 to retrieve the info a 
dataset/ddname.

Here is an example

https://www.mvsforums.com/helpboards/viewtopic.php?p=62866#62866

Thanks,
Kolusu

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-04-28 Thread Sri h Kolusu
>> Now we're trying to replace the File Manager step. If it was possible to do 
>> this in z/OS COBOL we could use it, but it isn't worth a large effort 
>> because it would be an interim solution anyway.

Michael,

Not sure as to why you want to replace file manager step with a COBOL program, 
but DFSORT can easily be used to fulfil the requirement. Let me know the DCB 
properties(LRECL, RECFM) of the input file and I can show you way to split the 
records into multiple files.

Thanks,
Kolusu
DFSORT Development
IBM Corporation


--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-04-28 Thread Sri h Kolusu
>> So use it to retrieve the data set name that is allocated in the JCL to the 
>> DD, then use the environment variable method to write to that same data set 
>> name? Hmmm.

Michael,

Not really,  once you get the Dataset name, you can open it in EXTENDED mode 
and write the output.  However, you are still limited by the LRECL and RECFM of 
the ddname.   Since you are splitting the records, I guess all of them have the 
same length

Thanks,
Kolusu
DFSORT Development
IBM Corporation

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-04-28 Thread Seymour J Metz
Is PL/I an option at your shop?


From: IBM Mainframe Discussion List  on behalf of 
Schmitt, Michael 
Sent: Friday, April 28, 2023 4:29 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: Re: COBOL to dynamic DD name

I have an input file that contains thousands of records. They are in groups: 
header record, then a bunch of segments all for one database name, then another 
header, records for another database. But the same database can appear more 
than once in the input.

The step takes this input and creates one output file per database, with one 
header. And resequences the records so they go 1,2,3,4, for each output DD.

On z/OS this step is done using File Manager, with this code:

if fld(1,2,B) = 0 then do   /* if sort key is 0 then  */
   header_rec = inrec   /*save the header record  */
   return 'drop'/*get next record */
   end

dd_name = overlay('N', fld(9,8), 4) /* get DD name from DBD name  */

if recsout(dd_name) = 0 then do /* if 1st record for database */
   outrec.dd_name = header_rec
   write(dd_name)   /*write the header*/
   drop outrec.dd_name
   end

ovly_out(recsout(dd_name), 5,4,B)   /* resequence the records */
write(dd_name)  /* write the segment record   */
return 'drop'


That's the ENTIRE program!


On my PC I have a COBOL program, with a lot more logic, that does essentially 
the same thing. As it is reading the input, each time it gets to a different 
database name, it closes the file it has been writing to and opens the file for 
the appropriate DD name, extending it. So the program only needs to have one 
output file defined, even though it is writing to different DDs as it goes.


Now we're trying to replace the File Manager step. If it was possible to do 
this in z/OS COBOL we could use it, but it isn't worth a large effort because 
it would be an interim solution anyway.


-Original Message-
From: IBM Mainframe Discussion List  On Behalf Of Tom 
Marchant
Sent: Friday, April 28, 2023 3:18 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: Re: COBOL to dynamic DD name

I don't know any Cobol syntax that would change the DDNAME in a DCB, but you 
could call an assembler routine to change the DDNAME before OPEN. Why would you 
want to do that?

I'm a bit baffled. In z/OS and its ancestors, the data set name isn't 
determined until runtime, via JCL.

Perhaps if you describe the problem you are trying to solve.

--
Tom Marchant

On Fri, 28 Apr 2023 19:37:39 +, Schmitt, Michael  
wrote:

>I know how to have a COBOL program on z/OS use a data set name that isn't 
>determined until runtime, via an environment variable. My question is can you 
>use one file (i.e. one select/assign and one FD) to write to different DD 
>names, that were already allocated in the JCL?
>
>I can't find a way, and in the manual the syntax for the environment variable 
>method requires a DSN or PATH, no option for a DD name.

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN




--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-04-28 Thread Farley, Peter
I don't think you can do that.  Unfortunately COBOL does not yet support actual 
FILE-type variables.  COBOL files are essentially CONSTANTS in the language 
definition.  I wish that we had PL/I's FILE variable capability, but we don't.

IMHO your best bet is to avoid multiple DD allocations entirely. Instead start 
with a list of DSN's to be input (can be another separate input file) and 
dynamically assign each DSN you wish to process to the "constant" COBOL DD name 
in the ASSIGN clause, then FREE it (also using BPXWDYN) when you finish 
processing each file and then start with the next DSN (if any left).

You could also leave the DD names allocated as they already are and use an 
assembler function to retrieve the JFCB (or BXWDYN) to get the DSN of each 
assigned DD name and then use those to do a dynamic assign of each DSN to the 
COBOL file DD name from the ASSIGN clause, but the you will have two DD names 
assigned to the same file in the same step, which won't work unless DISP=SHR 
for all of them.  And if any of them is a GDG (+1) from a prior step, you have 
to mess around with getting the GDG suffix right in the dynamic allocate.

I once tried to mess around with dynamically changing the DCB DD name field of 
the closed COBOL file, but finding the DCB for a COBOL file is very 
compiler-release dependent and is a reverse-engineering effort that can be 
upset by IBM any time they decide to update COBOL implementation structures.  
Messy and a maintenance nightmare, so I dropped that effort.

HTH

Peter

-Original Message-
From: IBM Mainframe Discussion List  On Behalf Of 
Schmitt, Michael
Sent: Friday, April 28, 2023 3:38 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: COBOL to dynamic DD name

I know how to have a COBOL program on z/OS use a data set name that isn't 
determined until runtime, via an environment variable. My question is can you 
use one file (i.e. one select/assign and one FD) to write to different DD 
names, that were already allocated in the JCL?

I can't find a way, and in the manual the syntax for the environment variable 
method requires a DSN or PATH, no option for a DD name.
--

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...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-04-28 Thread Schmitt, Michael
So use it to retrieve the data set name that is allocated in the JCL to the DD, 
then use the environment variable method to write to that same data set name? 
Hmmm.

-Original Message-
From: IBM Mainframe Discussion List  On Behalf Of Sri 
h Kolusu
Sent: Friday, April 28, 2023 3:27 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: Re: COBOL to dynamic DD name

>> I'm not trying to allocate the files. The JCL for the step has all the DDs. 
>> I just need to be able open, extend, and close the select/assign to 
>> different DDs where which ones I use and which order is not known until I'm 
>> working through an input file.

Michael,

As steve mentioned in earlier post , you can BPXWDYN2 to retrieve the info a 
dataset/ddname.

Here is an example

https://www.mvsforums.com/helpboards/viewtopic.php?p=62866#62866

Thanks,
Kolusu

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-04-28 Thread Schmitt, Michael
I have an input file that contains thousands of records. They are in groups: 
header record, then a bunch of segments all for one database name, then another 
header, records for another database. But the same database can appear more 
than once in the input.

The step takes this input and creates one output file per database, with one 
header. And resequences the records so they go 1,2,3,4, for each output DD.

On z/OS this step is done using File Manager, with this code:

if fld(1,2,B) = 0 then do   /* if sort key is 0 then  */
   header_rec = inrec   /*save the header record  */
   return 'drop'/*get next record */
   end

dd_name = overlay('N', fld(9,8), 4) /* get DD name from DBD name  */

if recsout(dd_name) = 0 then do /* if 1st record for database */
   outrec.dd_name = header_rec
   write(dd_name)   /*write the header*/
   drop outrec.dd_name
   end

ovly_out(recsout(dd_name), 5,4,B)   /* resequence the records */
write(dd_name)  /* write the segment record   */
return 'drop'


That's the ENTIRE program!


On my PC I have a COBOL program, with a lot more logic, that does essentially 
the same thing. As it is reading the input, each time it gets to a different 
database name, it closes the file it has been writing to and opens the file for 
the appropriate DD name, extending it. So the program only needs to have one 
output file defined, even though it is writing to different DDs as it goes.


Now we're trying to replace the File Manager step. If it was possible to do 
this in z/OS COBOL we could use it, but it isn't worth a large effort because 
it would be an interim solution anyway.


-Original Message-
From: IBM Mainframe Discussion List  On Behalf Of Tom 
Marchant
Sent: Friday, April 28, 2023 3:18 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: Re: COBOL to dynamic DD name

I don't know any Cobol syntax that would change the DDNAME in a DCB, but you 
could call an assembler routine to change the DDNAME before OPEN. Why would you 
want to do that?

I'm a bit baffled. In z/OS and its ancestors, the data set name isn't 
determined until runtime, via JCL.

Perhaps if you describe the problem you are trying to solve.

--
Tom Marchant

On Fri, 28 Apr 2023 19:37:39 +, Schmitt, Michael  
wrote:

>I know how to have a COBOL program on z/OS use a data set name that isn't 
>determined until runtime, via an environment variable. My question is can you 
>use one file (i.e. one select/assign and one FD) to write to different DD 
>names, that were already allocated in the JCL?
>
>I can't find a way, and in the manual the syntax for the environment variable 
>method requires a DSN or PATH, no option for a DD name.

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN




--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-04-28 Thread Sri h Kolusu
>> I'm not trying to allocate the files. The JCL for the step has all the DDs. 
>> I just need to be able open, extend, and close the select/assign to 
>> different DDs where which ones I use and which order is not known until I'm 
>> working through an input file.

Michael,

As steve mentioned in earlier post , you can BPXWDYN2 to retrieve the info a 
dataset/ddname. 

Here is an example

https://www.mvsforums.com/helpboards/viewtopic.php?p=62866#62866

Thanks,
Kolusu

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-04-28 Thread Tom Marchant
I don't know any Cobol syntax that would change the DDNAME in a DCB, but you 
could call an assembler routine to change the DDNAME before OPEN. Why would you 
want to do that?

I'm a bit baffled. In z/OS and its ancestors, the data set name isn't 
determined until runtime, via JCL.

Perhaps if you describe the problem you are trying to solve.

-- 
Tom Marchant

On Fri, 28 Apr 2023 19:37:39 +, Schmitt, Michael  
wrote:

>I know how to have a COBOL program on z/OS use a data set name that isn't 
>determined until runtime, via an environment variable. My question is can you 
>use one file (i.e. one select/assign and one FD) to write to different DD 
>names, that were already allocated in the JCL?
>
>I can't find a way, and in the manual the syntax for the environment variable 
>method requires a DSN or PATH, no option for a DD name.

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-04-28 Thread Schmitt, Michael
I'm not trying to allocate the files. The JCL for the step has all the DDs. I 
just need to be able open, extend, and close the select/assign to different DDs 
where which ones I use and which order is not known until I'm working through 
an input file.

I can do it on other platforms, and obviously in assembler, just not in IBM 
COBOL for z/OS. The problem is the assignment name is compiled in to the 
program, not a variable, and using an environment variable doesn't allow for 
DD(ddname).

-Original Message-
From: IBM Mainframe Discussion List  On Behalf Of 
Steve Thompson
Sent: Friday, April 28, 2023 3:08 PM
To: IBM-MAIN@LISTSERV.UA.EDU
Subject: Re: COBOL to dynamic DD name

You may want to use BPXWDY2. It dow not require the setting of
R0. And it does almost everything that BPXWDYN does.

Steve Thompson.

PS. Speaking of RCFS, this is one I did an RCF about and I
understand there are some updates being done to/with the DOC for
examples.



On 4/28/2023 3:52 PM, Paul Gilmartin wrote:
> On Fri, 28 Apr 2023 19:37:39 +, Schmitt, Michael wrote:
>
>> I know how to have a COBOL program on z/OS use a data set name that isn't 
>> determined until runtime, via an environment variable. My question is can 
>> you use one file (i.e. one select/assign and one FD) to write to different 
>> DD names, that were already allocated in the JCL?
>>
>> I can't find a way, and in the manual the syntax for the environment 
>> variable method requires a DSN or PATH, no option for a DD name.
>>
> Do you know the DSN or PATH?
>
> Do you want to specify the DD name or let Dynalloc choose one?
>
> Do BPXWDYN keys RTDDN and INFO help you?  BPXWDYN can be called with OS 
> standard linkage.
> <https://www.ibm.com/docs/en/zos/2.5.0?topic=services-bpxwdyn-text-interface-dynamic-allocation-dynamic-output>
>

--
Regards,
Steve Thompson
VS Strategies LLC
Westfield IN
972-983-9430 cell

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-04-28 Thread Steve Thompson
You may want to use BPXWDY2. It dow not require the setting of 
R0. And it does almost everything that BPXWDYN does.


Steve Thompson.

PS. Speaking of RCFS, this is one I did an RCF about and I 
understand there are some updates being done to/with the DOC for 
examples.




On 4/28/2023 3:52 PM, Paul Gilmartin wrote:

On Fri, 28 Apr 2023 19:37:39 +, Schmitt, Michael wrote:


I know how to have a COBOL program on z/OS use a data set name that isn't 
determined until runtime, via an environment variable. My question is can you 
use one file (i.e. one select/assign and one FD) to write to different DD 
names, that were already allocated in the JCL?

I can't find a way, and in the manual the syntax for the environment variable 
method requires a DSN or PATH, no option for a DD name.


Do you know the DSN or PATH?

Do you want to specify the DD name or let Dynalloc choose one?

Do BPXWDYN keys RTDDN and INFO help you?  BPXWDYN can be called with OS 
standard linkage.




--
Regards,
Steve Thompson
VS Strategies LLC
Westfield IN
972-983-9430 cell

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


Re: COBOL to dynamic DD name

2023-04-28 Thread Paul Gilmartin
On Fri, 28 Apr 2023 19:37:39 +, Schmitt, Michael wrote:

>I know how to have a COBOL program on z/OS use a data set name that isn't 
>determined until runtime, via an environment variable. My question is can you 
>use one file (i.e. one select/assign and one FD) to write to different DD 
>names, that were already allocated in the JCL?
>
>I can't find a way, and in the manual the syntax for the environment variable 
>method requires a DSN or PATH, no option for a DD name.
> 
Do you know the DSN or PATH?

Do you want to specify the DD name or let Dynalloc choose one?

Do BPXWDYN keys RTDDN and INFO help you?  BPXWDYN can be called with OS 
standard linkage.


-- 
gil

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN


COBOL to dynamic DD name

2023-04-28 Thread Schmitt, Michael
I know how to have a COBOL program on z/OS use a data set name that isn't 
determined until runtime, via an environment variable. My question is can you 
use one file (i.e. one select/assign and one FD) to write to different DD 
names, that were already allocated in the JCL?

I can't find a way, and in the manual the syntax for the environment variable 
method requires a DSN or PATH, no option for a DD name.

--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN