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

Regarding 'PUTENV' utility...


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

New User


Joined: 04 Jan 2006
Posts: 77
Location: Bangalore

PostPosted: Tue May 02, 2006 1:41 am
Reply with quote

Hi,
Continuing to add to the stack of problems I already have...

I have a requirement to dynamically create files for reports. I could do this with an inhouse assembler utility. This utility takes in the dd name and dsn together with other parameters and creates a new file.

I hvw only one SELECT statement, which points to one Env variable FILEIO01. I have not coded any DD statement in the JCL.

So the Code is like this


Code:

SELECT DYNA-FILE ASSIGN TO FILEIO01.
.
.
.
.
01 WS-DYN-OPEN-AREA.
   05 WS-DYN-FILE-NAME.
      10 FILLER                       PIC X(14)
                            VALUE "FILEIO01=DSN(".
      10 WS-DYN-DSN                 PIC X(55) VALUE SPACES.
      10 FILLER                       PIC X(06) VALUE "OLD".
      10 FILLER                       PIC X(01) VALUE X'00'.
   05 WS-FILE-POINTER               POINTER.
   05 WS-RC                         PIC S9(09) COMP VALUE ZERO.
.
.
.
             CALL ALLOC-PGM USING WS-FILE-NAME, WS-DDNAME
             MOVE SPACES TO WS-DYN-DSN
             STRING WS-FILE-NAME DELIMITED BY SPACE
                ")" DELIMITED BY SIZE INTO WS-DYN-DSN
             SET WS60-FILE-POINTER TO ADDRESS OF WS-DYN-FILE-NAME
             CALL 'PUTENV' USING BY VALUE WS-FILE-POINTER
                                    RETURNING WS-RC
               IF WS-RC = ZERO THEN
                 OPEN OUTPUT DYNA-FILE



It works cool in the first round, where WS-DDNAME

In the second round the value of the DDname changes into FILEIO02, and the WS60-FILE-NAME is also created dynamically, ie a new file name is created using ALLOC-PGM.

But the DD in PUTENV does not change as it is hard coded, but file name changes. But now PUTENV opens the same file, not the new one created!!!

So finally, it over-writes the old file giving me one useless file and several blank files....

Am I doing anything wrong here?
Back to top
View user's profile Send private message
DavidatK

Active Member


Joined: 22 Nov 2005
Posts: 700
Location: Troy, Michigan USA

PostPosted: Wed May 03, 2006 1:16 am
Reply with quote

New2cobol,

If I remember correctly, you want to output X number of records to a file, close assign a new file open and output x records, again, and again until all records have been written. Right?

This is a small program (complete) using PUTENV to four output files using only one SELECT/FD. Results are below.

I don?t know if there is some environmental condition between your allocate program and PUTENV? Or what. But this seems to work for me.

Code:

 ID DIVISION.                               
 PROGRAM-ID.   GETENVX.                     
 AUTHOR.       DAVIDATK.                   
 DATE-WRITTEN.                             
 DATE-COMPILED.                             
 ENVIRONMENT DIVISION.                     
 INPUT-OUTPUT SECTION.                     
 FILE-CONTROL.                             
     SELECT TEST-FILE ASSIGN TO DD1.       
 DATA DIVISION.                             
 FILE SECTION.                             
 FD  TEST-FILE                             
     LABEL RECORDS ARE STANDARD             
     BLOCK CONTAINS 0 RECORDS.             
 01  TEST-REC           PIC X(80).         
     EJECT                                 
 WORKING-STORAGE SECTION.                   
                                           
 01  OUTPUT-REC.                           
     05  REC-NUM         PIC 9(10).                             
     05  FILLER          PIC X(70)        VALUE SPACES.         
                                                               
 01 WS-WORK-DSN PIC X(55) VALUE 'TTT.TTT.TTT'.                 
 01 WS-DYNAMIC-OPEN-AREA.                                       
     05 FILE-NAME.                                             
         10 FILLER PIC X(8)  VALUE 'DD1=DSN('.                 
         10 DSNAME PIC X(55) VALUE SPACE.                       
         10 FILLER PIC X(50) VALUE                             
            ' NEW TRACKS SPACE(100,100) UNIT(SYSDA) CATALOG '. 
         10 FILLER PIC X(01) VALUE X'00'.                       
     05 FILE-PTR POINTER.                                       
     05 RC PIC S9(9) BINARY VALUE ZERO.                         
 01  FNAMES.                                                   
     05  FNAME-01             PIC X(55)    VALUE               
         'XXXXX.PS.TESTFILE.OUT01'.                             
     05  FNAME-02             PIC X(55)    VALUE               
         'XXXXX.PS.TESTFILE.OUT02'.                             
     05  FNAME-03             PIC X(55)    VALUE               
         'XXXXX.PS.TESTFILE.OUT03'.                         
     05  FNAME-04             PIC X(55)    VALUE             
         'XXXXX.PS.TESTFILE.OUT04'.                         
 01  FNAME-TABLE REDEFINES FNAMES.                           
     05  FNAME                PIC X(55)    OCCURS 4 TIMES.   
 01  SUB                      PIC S9(9)    COMP-3.           
 LINKAGE SECTION.                                           
     EJECT                                                   
 PROCEDURE DIVISION.                                         
                                                             
     PERFORM                                                 
       VARYING SUB FROM 1 BY 1 UNTIL SUB > 4                 
         MOVE SPACE TO DSNAME                               
         MOVE FNAME(SUB)              TO WS-WORK-DSN         
         STRING WS-WORK-DSN DELIMITED BY SPACE               
             ')' DELIMITED BY SIZE                           
             INTO DSNAME                                     
         DISPLAY 'FILE-NAME = ' FILE-NAME                   
         SET FILE-PTR TO ADDRESS OF FILE-NAME               
         CALL 'PUTENV' USING BY VALUE FILE-PTR RETURNING RC 
         IF RC NOT = 0                                       
         THEN                                               
             MOVE RC     TO RETURN-CODE                     
             GOBACK                                         
         END-IF                                             
         OPEN OUTPUT TEST-FILE                               
         PERFORM                                             
           10 TIMES                                         
             ADD 1 TO REC-NUM                               
             WRITE TEST-REC FROM OUTPUT-REC                 
         END-PERFORM                                         
         CLOSE TEST-FILE                                     
     END-PERFORM.                                           
                                                             
     MOVE 0           TO RETURN-CODE.                       
                                                             
     GOBACK.   


results of test

Code:


BROWSE    XXXXX.PS.TESTFILE.OUT01                 
 Command ===>                                     
********************************* Top of Data *****
0000000001                                         
0000000002                                         
0000000003                                         
0000000004                                         
0000000005                                         
0000000006                                         
0000000007                                         
0000000008                                         
0000000009                                         
0000000010                                         
******************************** Bottom of Data ***
                                                   
BROWSE    XXXXX.PS.TESTFILE.OUT02               
 Command ===>                                     
********************************* Top of Data *****
0000000011                                       
0000000012                                       
0000000013                                       
0000000014                                       
0000000015                                       
0000000016                                       
0000000017                                       
0000000018                                       
0000000019                                       
0000000020                                       
******************************** Bottom of Data ***

BROWSE    XXXXX.PS.TESTFILE.OUT03                 
 Command ===>                                     
********************************* Top of Data *****
0000000021                                         
0000000022                                         
0000000023                                         
0000000024                                         
0000000025                                         
0000000026                                         
0000000027                                         
0000000028                                         
0000000029                                         
0000000030                                         
******************************** Bottom of Data ***

BROWSE    XXXXX.PS.TESTFILE.OUT04                 
 Command ===>                                     
********************************* Top of Data *****
0000000031                                         
0000000032                                         
0000000033                                         
0000000034                                         
0000000035                                         
0000000036                                         
0000000037                                         
0000000038                                         
0000000039                                         
0000000040                                         
******************************** Bottom of Data ***



Please keep me up to date, Thanks

Dave
Back to top
View user's profile Send private message
new2cobol

New User


Joined: 04 Jan 2006
Posts: 77
Location: Bangalore

PostPosted: Wed May 03, 2006 2:55 am
Reply with quote

How do I declare a 133 record length FBA file using PUTENV ?? Or do you have some link explaining the options of putenv,setenv etc?
Back to top
View user's profile Send private message
new2cobol

New User


Joined: 04 Jan 2006
Posts: 77
Location: Bangalore

PostPosted: Wed May 03, 2006 10:46 pm
Reply with quote

This is the code I am trying... I don't get output here!!! even though I get an RC of 0
Code:

       IDENTIFICATION DIVISION.                                                 
      *                                                                         
       PROGRAM-ID. TESTPUT.                                                     
      *                                                                         
       AUTHOR. NEW2COBOL.                                           
      *                                                                         
       DATE-WRITTEN.  02/14/06.                                                 
       DATE-COMPILED.                                                           
      *                                                                         
       ENVIRONMENT DIVISION.                                                   
       CONFIGURATION SECTION.                                                   
      *                                                                         
       SOURCE-COMPUTER.  IBM-3090.                                             
       OBJECT-COMPUTER.  IBM-3090.                                             
      *                                                                         
       INPUT-OUTPUT SECTION.                                                   
       FILE-CONTROL.                                                           
             SELECT DYN-FILE ASSIGN TO FILE01.                                 
      *                                                                         
       DATA DIVISION.                                                           
       FILE SECTION.                                                           
       FD DYN-FILE                                                             
            RECORDING MODE IS F.                                               
       01 DYN-REC                  PIC X(132).                                 
      *                                                                         
       WORKING-STORAGE SECTION.                                                 
      * INPUT RECORD                                                           
       01  TOP-OF-PAGE             PIC X(132) VALUE SPACES.                     
       01  OUTPUT-RECORD           PIC X(132)                                   
                                    VALUE "WRITING IN DYNALLOC FILE".           
      *                                                                         
       01 FILENAM1                PIC X(44)                                     
                             VALUE "TSA.TEST.D.DYN01".                         
       01 DD-NAM1                 PIC X(08)                                     
                             VALUE "FILE01".                                   
       01 FILENAM2                PIC X(44)                                     
                             VALUE "TSA.TEST.D.DYN02".                         
       01 DD-NAM2                 PIC X(08)                                     
                             VALUE "FILE02".                                   
       01 FILENAM3                PIC X(44)                                     
                             VALUE "TSA.TEST.D.DYN03".                         
       01 DD-NAM3                 PIC X(08)                                     
                             VALUE "FILE03".                                   
       01 DYN-DSN.                                                             
          05 FILLER               PIC X(11)                                     
                             VALUE "FILE01=DSN(".                               
          05 DYN-NAME             PIC X(44).                                   
          05 FILLER               PIC X(01) VALUE SPACES.                       
          05 FILLER               PIC X(03) VALUE "NEW".                       
          05 FILLER               PIC X(01) VALUE SPACES.                       
          05 FILLER               PIC X(03)                                     
                             VALUE "CYL".                                       
          05 FILLER               PIC X(01) VALUE SPACES.                       
          05 FILLER               PIC X(17)                                     
                             VALUE "SPACE(10,10,RLSE)".                         
          05 FILLER               PIC X(01) VALUE SPACES.                       
          05 FILLER               PIC X(11) VALUE "UNIT(SYSDA)".               
          05 FILLER               PIC X(01) VALUE SPACES.                       
          05 FILLER               PIC X(07) VALUE "CATALOG".
          05 FILLER               PIC X(01) VALUE SPACES.                       
          05 FILLER               PIC X(10)                                     
                             VALUE "LRECL(133)".                               
          05 FILLER               PIC X(01) VALUE SPACES.                       
          05 FILLER               PIC X(12)                                     
                             VALUE "BLOCK(13300)".                             
          05 FILLER               PIC X(01) VALUE SPACES.                       
          05 FILLER               PIC X(12)                                     
                             VALUE "RECFM(F,B,A)".                             
          05 FILLER               PIC X(01) VALUE SPACES.                       
          05 FILLER               PIC X(09)                                     
                             VALUE "DSORG(PS)".                                 
          05 FILLER               PIC X(01) VALUE X'00'.                       
       01 FILE-PTR                POINTER.                                     
       01 RC                      PIC S9(9) BINARY VALUE ZERO.                 
       01 RC-PRT                  PIC Z(8)9.                                   
       PROCEDURE DIVISION.                                                     
      *                                                                         
       1000-MAIN-PARA.                                                         
             STRING FILENAM1 DELIMITED BY SPACE                                 
               ')' DELIMITED BY SIZE INTO DYN-NAME
             END-STRING
             SET FILE-PTR TO ADDRESS OF DYN-DSN
             CALL 'PUTENV' USING BY VALUE FILE-PTR
                  RETURNING RC
             END-CALL
             MOVE RC TO RC-PRT
             DISPLAY RC-PRT
             DISPLAY DYN-DSN
             OPEN OUTPUT DYN-FILE
             MOVE TOP-OF-PAGE  TO DYN-REC       
             WRITE DYN-REC AFTER ADVANCING PAGE
             MOVE OUTPUT-RECORD TO DYN-REC     
             WRITE DYN-REC                     
             MOVE OUTPUT-RECORD TO DYN-REC     
             WRITE DYN-REC
             CLOSE DYN-FILE
             STRING FILENAM2 DELIMITED BY SPACE                                 
               ')' DELIMITED BY SIZE INTO DYN-NAME
             END-STRING
             SET FILE-PTR TO ADDRESS OF DYN-DSN
             CALL 'PUTENV' USING BY VALUE FILE-PTR
                  RETURNING RC
             END-CALL
             DISPLAY DYN-DSN
             MOVE RC TO RC-PRT
             DISPLAY RC-PRT
             OPEN OUTPUT DYN-FILE
             MOVE TOP-OF-PAGE  TO DYN-REC       
             WRITE DYN-REC AFTER ADVANCING PAGE
             MOVE OUTPUT-RECORD TO DYN-REC     
             WRITE DYN-REC                     
             MOVE OUTPUT-RECORD TO DYN-REC     
             WRITE DYN-REC
             CLOSE DYN-FILE
             STRING FILENAM3 DELIMITED BY SPACE                                 
               ')' DELIMITED BY SIZE INTO DYN-NAME
             END-STRING
             SET FILE-PTR TO ADDRESS OF DYN-DSN
             CALL 'PUTENV' USING BY VALUE FILE-PTR
                  RETURNING RC
             END-CALL
             DISPLAY DYN-DSN
             MOVE RC TO RC-PRT
             DISPLAY RC-PRT
             OPEN OUTPUT DYN-FILE
             MOVE TOP-OF-PAGE  TO DYN-REC       
             WRITE DYN-REC AFTER ADVANCING PAGE
             MOVE OUTPUT-RECORD TO DYN-REC     
             WRITE DYN-REC                     
             MOVE OUTPUT-RECORD TO DYN-REC     
             WRITE DYN-REC
             CLOSE DYN-FILE
             STOP RUN
             .

Back to top
View user's profile Send private message
new2cobol

New User


Joined: 04 Jan 2006
Posts: 77
Location: Bangalore

PostPosted: Thu May 04, 2006 1:24 am
Reply with quote

Ok, the file name sizes should be X(55) and we can't add DD statement key words to the arguments... My mistake... Now it is running fine...

Sorry!!!
Back to top
View user's profile Send private message
DavidatK

Active Member


Joined: 22 Nov 2005
Posts: 700
Location: Troy, Michigan USA

PostPosted: Thu May 04, 2006 1:31 am
Reply with quote

new2cobol,

Here is the document that I am working off of for the PUTENV variables.

4.2.3.1 Assignment name for environment variable

I tried the RECFM you have in you code and got an error when I tried it. The only options you can specify are the ones in the document above. I almost never us the ?after advancing?, but when I tried it the file was allocated as ?FBA?. Remove all that is not in the doc above, and you know that you cannot have the DDNAME specified in the JCL you are running.

I got a return code of zero even though PUTENV didn?t work. Don?t know why. It did put out some messages in SYSOUT though.

If you still have problems I will post the entire program again that is producing LRECL=133,RECFM=FBA. This works good for me.

Please let me know your progress,

Sometimes the road is long and we seem to only be making small steps, but will never arrive if we quit.

Dave
Back to top
View user's profile Send private message
DavidatK

Active Member


Joined: 22 Nov 2005
Posts: 700
Location: Troy, Michigan USA

PostPosted: Thu May 04, 2006 1:35 am
Reply with quote

Hey, glad to hear, I didn't see your post until after I sent my last post.

Congratulations and good luck,

Dave
Back to top
View user's profile Send private message
View previous topic :: :: View next topic  
Post new topic   Reply to topic View Bookmarks
All times are GMT + 6 Hours
Forum Index -> COBOL Programming

 


Similar Topics
Topic Forum Replies
No new posts REASON 00D70014 in load utility DB2 6
No new posts ISRSUPC search utility - using high l... TSO/ISPF 2
No new posts Any JCL or VSAM Utility to get number... JCL & VSAM 1
No new posts DATA SET LIST UTILITY screen TSO/ISPF 6
No new posts Which SORT utility can improve the Pe... DFSORT/ICETOOL 16
Search our Forums:

Back to Top