Hi Scott,

>From experience I have found that BPXWDYN is not the easiest beast to
control. Whilst I do program in Assembler, it has to be acknowledged that
not everybody does and hence more prolific languages with calls to existing
functionality should be favoured. 

I personally think that BPXWDYN is the route to take in preference to
calling TSO from within COBOL, and hopefully the code below may be of use.

I am not sure why there was an issue with FREE as one test I conducted was
creating the TEMPFLE data set as a temporary using default DISP processing,
and the FREE caused the data set to be deleted prior to the STEP WAS EXECITE
COND CODE 0000 message line.

Note that I ensured that BPXWDYN was invoked dynamically, not statically
liked via IEWL.

Good luck - 

       IDENTIFICATION DIVISION.                                         
       PROGRAM-ID.                      BPXWDYNT.                       
       AUTHOR.                          T.R.SAMBROOKS.                  
           INSTALLATION.                                                
           DATE-WRITTEN.                16TH FEB 2012.                  
       ENVIRONMENT DIVISION.                                            
       CONFIGURATION SECTION.                                           
           SKIP1                                                        
      *----------------------------------------------------------------*
      *    ROUTINE TO DEMONSTARTE THE USE OF BPXWDYN.                  *
      *----------------------------------------------------------------*
           SKIP3                                                        
       INPUT-OUTPUT SECTION.                                            
       FILE-CONTROL.                                                    
           SELECT TEST-OUT              ASSIGN TEMPFLE.                 
       DATA DIVISION.                                                   
       FILE SECTION.                                                    
       FD  TEST-OUT                     RECORDING MODE IS F             
                                        LABEL RECORDS ARE STANDARD      
                                        BLOCK CONTAINS 0 RECORDS        
                                        RECORD CONTAINS 80 CHARACTERS   
                                        DATA RECORD IS TEST-REC.        
       01  TEST-REC                     PIC X(80).                      
           EJECT                                                        
       WORKING-STORAGE SECTION.                                         
           SKIP1                                                        
       01  EXTERNAL-ROUTINES.                                           
           03  WS-BPXWDYN               PIC X(8) VALUE 'BPXWDYN '.      
       01  ALLOC-FILE.                                                  
           03                           PIC S9(4) COMP VALUE +108.      
           03                           PIC X(45) VALUE                 
             'ALLOC FI(TEMPFLE) DA(PIONEER.TEST.SYSIN) NEW '.           
           03                           PIC X(37) VALUE                 
             ' SPACE(1,1) TRACKS CATALOG LRECL(80) '.                   
           03                           PIC X(26) VALUE                 
             ' RECFM(F,B) BLKSIZE(3200) '.                              
       01  FREE-FILE.                                                   
           03                           PIC S9(4) COMP VALUE +16.       
           03                           PIC X(16) VALUE                 
             'FREE FI(TEMPFLE)'.                                        
       01  WS-TESTREC.                                                  
           03                           PIC X(80) VALUE                 
             ' PRINT INFILE(TEMPLE) CHAR COUNT(10) '.                   
           EJECT                                                        
       PROCEDURE DIVISION.                                              
           SKIP1                                                        
       AA-MAIN-LINE SECTION.                                            
           SKIP1                                                        
           CALL WS-BPXWDYN              USING ALLOC-FILE.               
           DISPLAY 'ALLOC CODE' RETURN-CODE UPON SYSOUT.                
           OPEN                         OUTPUT TEST-OUT.                
           WRITE TEST-REC               FROM WS-TESTREC.                
           CLOSE TEST-OUT.                                              
           CALL WS-BPXWDYN              USING FREE-FILE.                
           DISPLAY 'FREE  CODE' RETURN-CODE UPON SYSOUT.                
           SKIP1                                                        
       AA-MAIN-LINE-EOJ.                                                
           GOBACK.                                                      
           SKIP3                                                        
      *----------------------------------------------------------------*
      * THIS IS THE PHYSICAL END OF THE SOURCE CODE PROGRAM - BPXWDYNT *
      *----------------------------------------------------------------*


Kind Regards - Terry
 
Director
KMS-IT Limited
228 Abbeydale Road South
Dore
Sheffield
S17 3LA
UK
 
Reg : 3767263
 
Outgoing e-mails have been scanned, but it is the recipients responsibility
to ensure their anti-virus software is up to date.
 
 


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

Reply via email to