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

Dyamic allocation of files using PUTENV


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

EXPERT


Joined: 15 Jun 2003
Posts: 10
Location: North Carolina

PostPosted: Fri Oct 17, 2003 5:23 am
Reply with quote

If it is possible, it is only under the Unix portion of the system, not the OS/390 part. If you check the programmers guide, it will tell you what you can do.
Back to top
View user's profile Send private message
RobertL

New User


Joined: 02 Jan 2004
Posts: 2
Location: Portugal

PostPosted: Fri Jan 02, 2004 8:13 pm
Reply with quote

Hi Shaheem,

Yes, this is possible under OS/390. I recently ran across an old article by Ed Watson on the Technical Support magazine website (Dec 2001) on how to do this. You can find the article at http://www.naspa.com/01articlesbymonth.htm#december_2001
Hope this helps.

Regards,
Robert
Back to top
View user's profile Send private message
dmmadsen

New User


Joined: 07 Dec 2005
Posts: 1
Location: Minneapolis, Minnesota

PostPosted: Wed Dec 07, 2005 10:10 pm
Reply with quote

You need to use PUTENV instead of GETENV to change the DSN name in the FCB area.

Because PUTENV is written in C++ it uses pointers intead of addresses to reference your working storage areas. That is the reason for the File-Pointer in the code below.

I just wrote a program to do this and it works great. The following code should be self explanitory. The only other thing is that in your JCL you DO NOT put a DD card in for the file you are dynamically allocating.

01 WS-WORK-DSN PIC X(55) VALUE 'XXX.XXX.XXX'.

01 WS-DYNAMIC-OPEN-AREA.

05 FILE-NAME.
10 FILLER PIC X(13) VALUE 'SRDIN001=DSN('.
10 DSNAME PIC X(55) VALUE SPACE.
10 FILLER PIC X(06) VALUE ' SHR '.
10 FILLER PIC X(01) VALUE X'00'.

05 FILE-PTR POINTER.

05 RC PIC S9(9) BINARY VALUE ZERO.


------ Sample Code --------


MOVE SPACE TO DSNAME

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 = ZERO
THEN
OPEN INPUT DYNAMIC-OPEN-FILE
IF STATUS-SUCCESS
THEN
READ DYNAMIC-OPEN-FILE

IF STATUS-SUCCESS
THEN
PERFORM PROCESS-DYNAMIC-OPEN-FILE
ELSE
DISPLAY '***** READ ERROR, DSN=' FILE-NAME
END-IF

CLOSE DYNAMIC-OPEN-FILE
ELSE
DISPLAY '***** OPEN ERROR, DSN=' FILE-NAME
END-IF
ELSE
DISPLAY '***** ERROR IN PUTENV, RETURN CODE = ' RC
DISPLAY '***** ' FILE-NAME
END-IF.
Back to top
View user's profile Send private message
ramankapoor

New User


Joined: 27 Feb 2006
Posts: 23
Location: delhi

PostPosted: Thu Mar 09, 2006 9:34 am
Reply with quote

I AM NOT GETTING THE MEANING OF DYNAMIC ALLOCATION OF FILE .
WHAT IS THE USE OF THIS AND WHY WE NEED IT.

PLS ASSIST..
Back to top
View user's profile Send private message
michaelraj

New User


Joined: 01 Sep 2005
Posts: 43
Location: Bangalore

PostPosted: Tue Mar 14, 2006 2:17 pm
Reply with quote

Hi dmmadsen,

I want to add something to your program,you have hardcoded the file name "TTT.TTT.TTT" in the program itself, to make it as general you can pass the DSN from the Job to the program. But from your program I have learned about Dynamic Allocation of the files.

Thanks & Regards,
-Mike.
Back to top
View user's profile Send private message
new2cobol

New User


Joined: 04 Jan 2006
Posts: 77
Location: Bangalore

PostPosted: Mon Apr 03, 2006 6:52 pm
Reply with quote

Now I have a doubt about this PUTENV thingy...

Is this a utility which can be found by default in our system libraries?

Or is this to be purchases and installed seperately?
Back to top
View user's profile Send private message
adiovanni

New User


Joined: 22 Nov 2006
Posts: 40
Location: USA

PostPosted: Thu Nov 23, 2006 3:13 am
Reply with quote

Fellow COBOL Appl Developers: Here's the full WORKING solution; works under COBOL3.

Al Diovanni
W#: <<removed>>
Home EMAIL: <<removed. See Forum Rules>>
---------------------------------------------------

Copybook DYNALLLS:
Code:

 01  DYNALLOC-PGM-PARMS.                     
     03  DYNALLOC-PGM-DDNAME PIC X(08).       
     03  DYNALLOC-PGM-DSN    PIC X(55).       
     03  DYNALLOC-PGM-RC     PIC S9(9) BINARY.


Copybook DYNALLOC:

Code:

 ID DIVISION.                                                 
 PROGRAM-ID.   DYNALLOC.                                     
 AUTHOR.       AL DIOVANNI.                                   
 DATE-WRITTEN. NOVEMBER 2006.                                 
 DATE-COMPILED.                                               
* NARRATIVE:                                                 
*    CHANGES DDNAME'S ENVIRONMENT VARIABLE'S                 
*    DSN ASSIGNMENT.                                         
*    DDNAME AND DSN ARE PASSED; A RC IS RETURNED.             
*    CALLED PGM MUST HAVE THIS DDNAME IN THE SELECT/ASSIGN AND
*    IN THE FD AND NOT IN THE JCL; AND CALLED PGM             
*    MUST HAVE A WORKAREA SETUP FOR THIS DDNAME.             
 ENVIRONMENT DIVISION.                                       
 DATA DIVISION.                                               
 WORKING-STORAGE SECTION.                                     
 01  WS-DYNAMIC-ALLOC-STORAGE.                               
     05 ENV-VAR-PARM-PASSED.                                 
        10  DDNAME   PIC X(08) VALUE SPACES.                 
        10           PIC X(06) VALUE '=DSN('''.           
        10  DSNAME   PIC X(55) VALUE SPACE.               
        10           PIC X(06) VALUE ' SHR '.             
        10           PIC X(01) VALUE X'00'.               
     05 PUTVAR-PARM-PTR POINTER.                           
     05 RC           PIC S9(9) BINARY VALUE +0.           
 LINKAGE         SECTION.                                 
 COPY DYNALLLS.                                           
 PROCEDURE DIVISION USING DYNALLOC-PGM-PARMS.             
     MOVE SPACES TO DDNAME                                 
     MOVE SPACES TO DSNAME                                 
     MOVE DYNALLOC-PGM-DDNAME                             
      TO  DDNAME                                           
     STRING DYNALLOC-PGM-DSN DELIMITED BY SPACE           
            ''')'            DELIMITED BY SIZE             
     INTO DSNAME                                           
     END-STRING                                           
     DISPLAY 'FILE-NAME = ' DSNAME                         
     DISPLAY 'ENV-VAR PASSED STRING = ' ENV-VAR-PARM-PASSED
     SET PUTVAR-PARM-PTR TO ADDRESS OF ENV-VAR-PARM-PASSED   
     CALL 'PUTENV' USING BY VALUE PUTVAR-PARM-PTR RETURNING RC
     END-CALL                                                 
     MOVE RC TO DYNALLOC-PGM-RC                               
     EXIT PROGRAM                                             
     .                                                       
 END PROGRAM   DYNALLOC.                                     


Sample Program DYNALLTS:
Code:

 ID DIVISION.                                                         
 PROGRAM-ID.   DYNALLTS.                                             
 AUTHOR.       AL DIOVANNI.                                           
 DATE-WRITTEN. NOVEMBER 2006.                                         
 DATE-COMPILED.                                                       
 *****************************************************************   
 *                                                               *   
 * NARRATIVE: DYNAMIC-ALLOCATION IN COBOL EXAMPLE.               *   
 * YOU WILL DYN-CALL DYNALLOC PGM 1ST TIME BEFORE ANY I/O        *   
 * TO THE FILE IS DONE PASSING THE DSN AND THEN IF THE RC IS 0,  *   
 * YOU WILL CONTINUE AS NORMAL.                                  *   
 * REPEAT THIS PROCEDURE FOR EACH FILE THAT NEEDS TO BE DYN-ALLOCATED.
 *                                                               *   
 * IMPORTANT: DO NOT PUT THIS FILE INTO THE JCL !!!              *   
 *                                                               *   
 *****************************************************************   
 ENVIRONMENT DIVISION.                                               
 INPUT-OUTPUT SECTION.                                               
 FILE-CONTROL.                                                 
***  THIS SELECT IS A WORKAREA FOR THIS UTILITY AND           
***  DOES NOT GO INTO THE JCL; HOWEVER YOU'LL STILL           
***  HAVE A SELECT/ASSIGN AND "FD" FOR IT                     
     SELECT  DYNAMIC-OPEN-FILE  ASSIGN TO  UT-S-DALDUMMY       
                                FILE STATUS  IS DALDUMMY-STATUS
     .                                                         
 DATA DIVISION.                                               
*** RECORDING-MODE AND LRECL AND WORKAREA MUST BE EQUAL TO     
*** DYNAM-ALLOCATED FILE'S PROPERTIES.                         
 FILE SECTION.                                                 
 FD  DYNAMIC-OPEN-FILE                                         
     RECORDING MODE IS F                                       
     BLOCK CONTAINS 0                                         
     LABEL RECORDS ARE STANDARD.                               
 01  DYNAMIC-OPEN-RECORD             PIC X(???).               
/                                                             
 WORKING-STORAGE SECTION.                                     
*** END TO YOUR WORKING-STORAGE - S -                         
 77  DYNALLOC-PGM    PIC X(08) VALUE 'DYNALLOC'.           
     COPY DYNALLLS.                                       
*** END TO YOUR WORKING-STORAGE - E -                     
 77  DALDUMMY-STATUS PIC X(02) VALUE SPACES.               
     88  DALDUMMY-STATUS-OK    VALUE '00'.                 
 01  WS-DDNAME       PIC X(08) VALUE 'DALDUMMY'.           
 01  WS-WORK-DSN1    PIC X(55) VALUE                       
     'FIRST.HARDCODED.DSN'.             
 01  WS-WORK-DSN2    PIC X(55) VALUE                       
     'SECOND.HARDCODED.DSN'.             
/                                                         
*** RECORDING-MODE AND LRECL AND WORKAREA MUST BE EQUAL TO
*** DYNAM-ALLOCATED FILE'S PROPERTIES.                     
 01  YOUR-READ-INTO-BUFFER.
       03  WS-INPUT-BUFFER-HEADER-REC.
                  ...
       03 WS-INPUT-BUFFER-DETAIL-REC   REDEFINES
           WS-INPUT-BUFFER-HEADER-REC.
                  ...     
/                                                         
 LINKAGE         SECTION.                                 
/                                                         
 PROCEDURE DIVISION.                                       
***                                                       
***  BEFORE YOUR OPEN(S):                                       
***  MOVE YOUR DSN THAT EXISTS IN THE FILE                     
***  (IN THIS EXAMPLE IT'S IN WORKING-STORAGE;                 
***  FOR REAL, YOU'LL READ A FILE THAT CONTAINS THE DSN)       
***  TO DYNALLOC'S PARM AND DYN-CALL IT ONCE FOR EACH FILE.     
***                                                             
     MOVE WS-DDNAME                                             
      TO  DYNALLOC-PGM-DDNAME                                   
     MOVE WS-WORK-DSN1                                         
      TO  DYNALLOC-PGM-DSN                                     
     CALL DYNALLOC-PGM USING DYNALLOC-PGM-DDNAME               
                             DYNALLOC-PGM-DSN                   
                   RETURNING DYNALLOC-PGM-RC                   
     END-CALL                                                   
     IF DYNALLOC-PGM-RC = +0                                   
***     AT THIS POINT, DO WHATEVER I/O YOU WANT TO ON FILE # 1 !
        OPEN INPUT DYNAMIC-OPEN-FILE                           
        IF DALDUMMY-STATUS-OK                                   
           READ DYNAMIC-OPEN-FILE                               
           INTO WS-INPUT-BUFFER-HEADER-REC                         
           END-READ                                       
           IF DALDUMMY-STATUS-OK                         
              DISPLAY 'HDR: ' WS-INPUT-BUFFER-HEADER-REC
              READ DYNAMIC-OPEN-FILE                     
              INTO WS-INPUT-BUFFER-DETAIL-REC                 
              END-READ                                   
              IF DALDUMMY-STATUS-OK                       
                 DISPLAY 'DTL: ' WS-INPUT-BUFFER-DETAIL-REC                 
              ELSE                                       
                 DISPLAY '***** 2ND-REC READ ERROR, DSN= '
                          DYNALLOC-PGM-DSN               
                          '; STATUS = ' DALDUMMY-STATUS   
              END-IF                                     
           ELSE                                           
              DISPLAY '***** 1ST-REC READ ERROR, DSN= '   
                       DYNALLOC-PGM-DSN                   
                      '; STATUS = ' DALDUMMY-STATUS       
           END-IF                                         
           CLOSE DYNAMIC-OPEN-FILE                           
        ELSE                                                 
           DISPLAY '***** OPEN ERROR, DSN= '                 
                    DYNALLOC-PGM-DSN                         
                   '; STATUS = ' DALDUMMY-STATUS             
        END-IF                                               
     ELSE                                                     
        DISPLAY '***** ERROR IN DYNALLOC PGM, RETURN CODE = '
                DYNALLOC-PGM-RC                               
        DISPLAY '***** DSN= ' DYNALLOC-PGM-DSN               
     END-IF                                                   
                                                             
     MOVE WS-DDNAME                                           
      TO  DYNALLOC-PGM-DDNAME                                 
     MOVE WS-WORK-DSN2                                       
      TO  DYNALLOC-PGM-DSN                                   
     CALL DYNALLOC-PGM USING DYNALLOC-PGM-DDNAME             
                             DYNALLOC-PGM-DSN                 
                   RETURNING DYNALLOC-PGM-RC                 
     END-CALL                                                   
     IF DYNALLOC-PGM-RC = +0                                     
***     AT THIS POINT, DO WHATEVER I/O YOU WANT TO ON FILE # 2 !
        OPEN INPUT DYNAMIC-OPEN-FILE                             
        IF DALDUMMY-STATUS-OK                                   
           READ DYNAMIC-OPEN-FILE                               
           INTO WS-INPUT-BUFFER-HEADER-REC
           END-READ                                             
           IF DALDUMMY-STATUS-OK                                 
              DISPLAY 'HDR: ' WS-INPUT-BUFFER-HEADER-REC
              READ DYNAMIC-OPEN-FILE                             
              INTO WS-INPUT-BUFFER-DETAIL-REC                 
              END-READ                                           
              IF DALDUMMY-STATUS-OK                             
                 DISPLAY 'DTL: ' WS-INPUT-BUFFER-DETAIL-REC                 
              ELSE                                               
                 DISPLAY '***** 2ND-REC READ ERROR, DSN= '       
                          DYNALLOC-PGM-DSN                       
                          '; STATUS = ' DALDUMMY-STATUS         
              END-IF                                         
           ELSE                                               
              DISPLAY '***** 1ST-REC READ ERROR, DSN= '       
                       DYNALLOC-PGM-DSN                       
                      '; STATUS = ' DALDUMMY-STATUS           
           END-IF                                             
           CLOSE DYNAMIC-OPEN-FILE                           
        ELSE                                                 
           DISPLAY '***** OPEN ERROR, DSN= '                 
                    DYNALLOC-PGM-DSN                         
                   '; STATUS = ' DALDUMMY-STATUS             
        END-IF                                               
     ELSE                                                     
        DISPLAY '***** ERROR IN DYNALLOC PGM, RETURN CODE = '
                DYNALLOC-PGM-RC                               
        DISPLAY '***** DSN= ' DYNALLOC-PGM-DSN               
     END-IF                                                   
                                                             
     STOP RUN                                                 
     .                 
                       
 COPY DYNALLOC.         
                       
 END PROGRAM   DYNALLTS.


Execution JCL:

Code:

//DYNALLOC EXEC PGM=DYNALLTS                                   
//STEPLIB   DD DISP=SHR,DSN=YOUR.LOAD.LIBRARY
//SYSOUT    DD SYSOUT=*                                       
//SYSPRINT  DD SYSOUT=*                                       
//SYSUDUMP  DD SYSOUT=*
Back to top
View user's profile Send private message
vijay_bn79

New User


Joined: 20 Nov 2006
Posts: 48
Location: Hyderabad

PostPosted: Fri Nov 24, 2006 5:14 pm
Reply with quote

Dynamically allocation of file means
Back to top
View user's profile Send private message
adiovanni

New User


Joined: 22 Nov 2006
Posts: 40
Location: USA

PostPosted: Mon Nov 27, 2006 10:20 pm
Reply with quote

A Real-World Example that explains what Dynamic Allocation means:
Assume you have a random unpredicable number of GDG goovels (herein termed dsns) coming into a program step each time the program is run; and all of the dsns are very large (hence you don't want to read all of them due to wasted cycles). Also assume that the number of permutations of dsns to be put into the JCL is too large and too impractical.
Also assume that you have a control file coming in that contains all of the dsns to read during this run.
Hence you have a dynamic allocation requirement.
Hence you can use dynamic allocation to change the ddname-dsn assignment to the dsn from the control file prior to doing I/O on the file; and you'd do this once per dsn in the control file.
The working coding that I wrote/tested tells you how to do this; and this CALL-to-PUTENV is contained within copybooks so as to not get in the way of your mainstream logic and so as to make this subroutine modularized.
You would replace my DYNALLTS example program with your program. You'd insert this utility and the appropriate coding snippets/copybooks into your program; and don't forget the "END PROGRAM <<your-program-name>> " at the end of your program.
Back to top
View user's profile Send private message
galecra

New User


Joined: 11 Sep 2006
Posts: 33

PostPosted: Tue Dec 05, 2006 2:11 am
Reply with quote

Hi,
I'm getting a S806 error because module PUTENV is not found ..
How should I compile the COBOL program?
How should I write the JCL in order to reference the system libraries where the PUTENV module is...
As PUTENV is a C-module, it seems it's not being searched by default in system C-libraries but only in COBOL-libraries ...
Back to top
View user's profile Send private message
adiovanni

New User


Joined: 22 Nov 2006
Posts: 40
Location: USA

PostPosted: Tue Dec 05, 2006 2:18 am
Reply with quote

1. I only tested this on COBOL/3 and I'm not sure if this works with older COBOL versions.

2. Let me see the S806 JESLOG/JESMESSAGES in your output job, please.
Back to top
View user's profile Send private message
DavidatK

Active Member


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

PostPosted: Tue Dec 05, 2006 7:17 am
Reply with quote

To all that are recently posting here.

Why are you replying to a post started "Posted: Wed Oct 08, 2003 8:06 am"?

Please start a new discussion, It keeps things so much more neat.

Thanks

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

New User


Joined: 11 Sep 2006
Posts: 33

PostPosted: Tue Dec 05, 2006 6:30 pm
Reply with quote

13.38.00 JOB04296 - --TIMINGS (MINS.)-- ----PAGING COUNTS---
13.38.00 JOB04296 -JOBNAME STEPNAME PROCSTEP RC EXCP TCB SRB CLOCK SERV PG PAGE SWAP VIO SWAPS
13.38.00 JOB04296 -AVE0288A JS010 *S806 754 .00 .00 .0 56481 0 0 0 0 0
13.38.00 JOB04296 IEF404I AVE0288A - ENDED - TIME=13.38.00

IEF236I ALLOC. FOR AVE0288A JS010
IGD103I SMS ALLOCATED TO DDNAME STEPLIB
IEF237I JES2 ALLOCATED TO SYSOUT
IEF237I JES2 ALLOCATED TO CEEDUMP
IEF237I JES2 ALLOCATED TO ABENDAID
IGD103I SMS ALLOCATED TO DDNAME ABNLTERM
IGD103I SMS ALLOCATED TO DDNAME SYS00001
GVB105I SYS00001 BUFSP=368640
IGD104I SYSPB.ABENDAID.XLS.RPT RETAINED, DDNAME=SYS00001
GVB105I ABNLTERM BUFSP=368640
AB400A ===== ABEND-AID =====
REPORT WRITTEN TO: SYSPB.ABENDAID.XLS.RPT
REPORT NUMBER: 151929
JOB-AVE0288A STEP-JS010
LE COND CODE=CEE3501S / EXPECTED COMP CODE=S806
IGD103I SMS ALLOCATED TO DDNAME ABNLDFIL
IGD103I SMS ALLOCATED TO DDNAME SLSF001
IEF237I JES2 ALLOCATED TO ABNLREPT
IGD101I SMS ALLOCATED TO DDNAME (ABNLPARM)
DSN (SYS06338.T133759.RA000.AVE0288A.R0355434 )
STORCLAS (BASE) MGMTCLAS ( ) DATACLAS (DSORG)
VOL SER NOS= VIO
GVB105I ABNLDFIL BUFSP=368640
GVB105I SLSF001 BUFSP=368640
IGD104I SYSPB.ABENDAID.XLS.RPT RETAINED, DDNAME=ABNLDFIL
IGD104I SYSPB.ABENDAID.XLS.SRC RETAINED, DDNAME=SLSF001
IEF285I AVE0288.AVE0288A.JOB04296.D0000104.? SYSOUT
IGD105I SYS06338.T133759.RA000.AVE0288A.R0355434 DELETED, DDNAME=ABNLPARM
IGD104I SYSPB.ABENDAID.XLS.RPT RETAINED, DDNAME=ABNLTERM
IEF285I AVE0288.AVE0288A.JOB04296.D0000102.? SYSOUT
IEF285I AVE0288.AVE0288A.JOB04296.D0000101.? SYSOUT
IEF472I AVE0288A JS010 - COMPLETION CODE - SYSTEM=806 USER=0000 REASON=00000004
IGD104I AVE0288.LOADLIB RETAINED, DDNAME=STEPLIB
IEF285I AVE0288.AVE0288A.JOB04296.D0000103.? SYSOUT
IEF373I STEP/JS010 /START 2006338.1337
IEF374I STEP/JS010 /STOP 2006338.1338 CPU 0MIN 00.47SEC SRB 0MIN 00.01SEC VIRT 900K SYS 384K EXT 4640K SYS 10328K
IEF375I JOB/AVE0288A/START 2006338.1337
IEF376I JOB/AVE0288A/STOP 2006338.1338 CPU 0MIN 00.47SEC SRB 0MIN 00.01SEC
** PROGRAM STARTS **
FILE-NAME:DD1=DSN('AVE0288.DYNALLOC.TEST.FILE') SHR
CEE3501S The module PUTENV was not found.
From compile unit DYNALLOC at entry point DYNALLOC at compile unit offset +000004C4 at entry offset +000004C4
at address 26000EBC.
<> LEAID ENTERED (LEVEL 11/10/2005 AT 17.17)
<> LEAID PROCESSING COMPLETE. RC=0
1CEE3DMP V1 R7.0: Condition processing resulted in the unhandled condition. 12/04/06 1:37:58 PM Page: 1

Information for enclave DYNALLOC

Information for thread 8000000000000000

Traceback:
DSA Addr Program Unit PU Addr PU Offset Entry E Addr E Offset Statement Load Mod Service Status
0002B660 CEEHDSP 05CBDFA8 +000048A0 CEEHDSP 05CBDFA8 +000048A0 CEEPLPKA UK10750 Call
0002B4C8 CEEHSGLT 05CCFEA8 +0000005C CEEHSGLT 05CCFEA8 +0000005C CEEPLPKA HLE7720 Exception
0002B320 IGZCLDL 26064FF8 +0000012A IGZCLDL 26064FF8 +0000012A IGZCPAC Call
0002B140 IGZCFCC 2601CC80 +000003EE IGZCFCC 2601CC80 +000003EE IGZCPAC Call
0002B018 DYNALLOC 260009F8 +000004C4 DYNALLOC 260009F8 +000004C4 DYNALLOC Call

Condition Information for Active Routines
Condition Information for CEEHSGLT (DSA address 0002B4C8)
CIB Address: 0002BF98
Current Condition:
CEE3501S The module PUTENV was not found.
Location:
Program Unit: CEEHSGLT Entry: CEEHSGLT Statement: Offset: +0000005C
Storage dump near condition, beginning at location: 05CCFEF4
+000000 05CCFEF4 F010D20B D0801000 58A0C2B8 58F0A01C 05EFD20B D098B108 41A0D098 50A0D08C |0.K.......B..0....K..q.....q&...|
Back to top
View user's profile Send private message
galecra

New User


Joined: 11 Sep 2006
Posts: 33

PostPosted: Tue Dec 05, 2006 6:32 pm
Reply with quote

I posted in above message the sysout for the S806 abend...
Back to top
View user's profile Send private message
adiovanni

New User


Joined: 22 Nov 2006
Posts: 40
Location: USA

PostPosted: Tue Dec 05, 2006 9:33 pm
Reply with quote

PUTENV (which is really IBMPENV or @@PUTENV),
is probably not in your shop's LINKLIST and/or LPA or ELPA.

Hence, add following library to your STEPLIB or JOBLIB:

SYS1.CEE.SCEELKED

Note: If this library is not found (unlikely), check with your MVS guy to find out the correct name for the SYS1 COBOL runtime library that ends with SCEELKED.

The member that your runtime environment needs in this library is member @@PUTENV !!!

Try again and let me know.

Good Luck !!!
Back to top
View user's profile Send private message
galecra

New User


Joined: 11 Sep 2006
Posts: 33

PostPosted: Tue Dec 05, 2006 11:07 pm
Reply with quote

Yes... it is SYS1.SCEELKED ..
But now I'm getting a S0C1
Follow is the program code and sysout:

WORKING-STORAGE SECTION.
01 WS-SWITCHES.
10 WS-DYNA-FILE-EOF PIC X VALUE 'N'.
88 WS-DYNA-FILE-EOF-Y VALUE 'Y'.
88 WS-DYNA-FILE-EOF-N VALUE 'N'.


01 WS-DYNA-FILE.
10 WS-DYNA-FILE-DSN.
15 DDNAME PIC X(08) VALUE 'DINAMIC1'.
15 FILLER PIC X(06) VALUE '=DSN('''.
15 DSNAME PIC X(55) VALUE SPACE.
15 FILLER PIC X(05) VALUE ' SHR '.
NULL TERMINATED STRING NEEDED BY C ROUTINE
15 FILLER PIC X(01) VALUE X'00'.

10 WS-DYNA-FILE-PTR POINTER.
10 WS-RC PIC S9(9) BINARY VALUE +0.

DISPLAY '** PROGRAM STARTS **'

CALL PUTENV TO ALLOCATE DYNA-FILE

MOVE 'AVE0288.DYNALLOC.TEST.FILE'')' TO DSNAME.

DISPLAY 'FILE-NAME:' WS-DYNA-FILE-DSN.

SET WS-DYNA-FILE-PTR TO ADDRESS OF WS-DYNA-FILE-DSN.

CALL 'PUTENV'
USING BY VALUE WS-DYNA-FILE-PTR RETURNING WS-RC.
IF NOT WS-RC = 0 THEN
DISPLAY 'ERROR ON CALL PUTENV:' WS-RC
ELSE

DISPLAY 'CALL PUTENV SUCCESFULL'
END-IF.


-JOBNAME STEPNAME PROCSTEP RC EXCP TCB SRB CLO
-AVE0288A JS010 *S0C1 565 .00 .00
IEF404I AVE0288A - ENDED - TIME=11.15.49
-AVE0288A ENDED. NAME-GCRAVCHI TOTAL TCB CPU TI


IEF236I ALLOC. FOR AVE0288A JS010
IGD103I SMS ALLOCATED TO DDNAME STEPLIB
IEF237I 923C ALLOCATED TO
IEF237I JES2 ALLOCATED TO SYSOUT
IEF237I JES2 ALLOCATED TO CEEDUMP
IEF237I JES2 ALLOCATED TO ABENDAID
IGD103I SMS ALLOCATED TO DDNAME ABNLTERM
IGD103I SMS ALLOCATED TO DDNAME SYS00001
GVB105I SYS00001 BUFSP=368640
IGD104I SYSPB.ABENDAID.XLS.RPT RETAINED, DDNAME=SYS00001
GVB105I ABNLTERM BUFSP=368640
AB400A ===== ABEND-AID =====
REPORT WRITTEN TO: SYSPB.ABENDAID.XLS.RPT
REPORT NUMBER: 151964
JOB-AVE0288A STEP-JS010
LE COND CODE=CEE3201S / EXPECTED COMP CODE=S0C1
IGD103I SMS ALLOCATED TO DDNAME ABNLDFIL
IGD103I SMS ALLOCATED TO DDNAME SLSF001
IEF237I JES2 ALLOCATED TO ABNLREPT
IGD101I SMS ALLOCATED TO DDNAME (ABNLPARM)
DSN (SYS06339.T111548.RA000.AVE0288A.R0319331 )
STORCLAS (BASE) MGMTCLAS ( ) DATACLAS (DSORG)
VOL SER NOS= VIO
GVB105I ABNLDFIL BUFSP=368640
GVB105I SLSF001 BUFSP=368640
IGD104I SYSPB.ABENDAID.XLS.RPT RETAINED, DDNAME=ABNLDFIL
IGD104I SYSPB.ABENDAID.XLS.SRC RETAINED, DDNAME=SLSF001
IEF285I AVE0288.AVE0288A.JOB02463.D0000104.? SYSOUT
IGD105I SYS06339.T111548.RA000.AVE0288A.R0319331 DELETED, DDNAME=ABNLPARM
IGD104I SYSPB.ABENDAID.XLS.RPT RETAINED, DDNAME=ABNLTERM
IEF285I AVE0288.AVE0288A.JOB02463.D0000102.? SYSOUT
IEF285I AVE0288.AVE0288A.JOB02463.D0000101.? SYSOUT
IEF472I AVE0288A JS010 - COMPLETION CODE - SYSTEM=0C1 USER=0000 REASON=00000001
IGD104I AVE0288.LOADLIB RETAINED, DDNAME=STEPLIB
IEF285I SYS1.SCEELKED KEPT
IEF285I VOL SER NOS= SIP5A2.
IEF285I AVE0288.AVE0288A.JOB02463.D0000103.? SYSOUT
IEF373I STEP/JS010 /START 2006339.1115
IEF374I STEP/JS010 /STOP 2006339.1115 CPU 0MIN 00.39SEC SRB 0MIN 00.01S
IEF375I JOB/AVE0288A/START 2006339.1115
IEF376I JOB/AVE0288A/STOP 2006339.1115 CPU 0MIN 00.39SEC SRB 0MIN 00.01S
** PROGRAM STARTS **
FILE-NAME:DINAMIC1=DSN('AVE0288.DYNALLOC.TEST.FILE')
CEE3201S The system detected an operation exception (System Completion Code=0C1)
From compile unit DYNALLOC at entry point DYNALLOC at compile unit offs
at address 26000EBC.
<> LEAID ENTERED (LEVEL 11/10/2005 AT 17.17)
<> LEAID PROCESSING COMPLETE. RC=0
CEE3DMP V1 R7.0: Condition processing resulted in the unhandled condition.


I think we are pretty close to get it done!... Thanks!!
Back to top
View user's profile Send private message
adiovanni

New User


Joined: 22 Nov 2006
Posts: 40
Location: USA

PostPosted: Wed Dec 06, 2006 5:11 am
Reply with quote

Let me see your SELECT, "FD" and "01" for your "DINAMIC1" DD in your program.

Also you must NOT supply the "DINAMIC1" DD in your JCL--you're not supplying it, right ? Let me know.

Thanks.
Back to top
View user's profile Send private message
galecra

New User


Joined: 11 Sep 2006
Posts: 33

PostPosted: Wed Dec 06, 2006 6:52 pm
Reply with quote

I'm not suppling DINAMIC1 in JCL ...


INPUT-OUTPUT SECTION.
FILE-CONTROL.

SELECT DYNA-FILE ASSIGN TO DINAMIC1.


****************************************************************
** DATA DIVISION
****************************************************************

DATA DIVISION.

FILE SECTION.

FD DYNA-FILE
RECORDING MODE IS F
LABEL RECORD STANDARD.
01 DYNA-FILE-REC PIC X(80).
Back to top
View user's profile Send private message
adiovanni

New User


Joined: 22 Nov 2006
Posts: 40
Location: USA

PostPosted: Wed Dec 06, 2006 8:32 pm
Reply with quote

All looks OK.

Try going FROM...

SELECT DYNA-FILE ASSIGN TO DINAMIC1.

TO...

SELECT DYNA-FILE ASSIGN TO UT-S-DINAMIC1.

Also, your dsn called 'AVE0288.DYNALLOC.TEST.FILE' must exist and must be cataloged...is that true ?
Back to top
View user's profile Send private message
galecra

New User


Joined: 11 Sep 2006
Posts: 33

PostPosted: Wed Dec 06, 2006 10:10 pm
Reply with quote

bummer bummer bummer...
it's still not working...

Could be a compilation problem?... maybe it should depend on how is compiled... (I'm compiling with Xpediter Compilation Facility with Language option ===> E-COBOL and I get a RC=0) ...

Let's see what IBMLink has to say about this error:
ERROR DESCRIPTION:
COBOL/390 program1 amode(31) rmode(24) calls COBOL program2,
amode(any), rmode(24). On OS/390 it runs fine. On z/OS 1.2.0
abend 0C1.
After re-linking program2 amode(24) rmode(24) abend 0C1 under
z/OS has gone.
Need an explanation why re-linking is required ! All migration
documents told nothing about actions on COBOL applications that
successfull with OS/390 2.10.0. The LE run time parameters were
taken unchanged from LE 2.10.0. As documented in the LE runtime


LOCAL FIX:


PROBLEM SUMMARY:
****************************************************************
* USERS AFFECTED: Users having applications where a COBOL *
* program dynamically calls an Assembler *
* program and the Assembler program changes *
* the AMODE and does not restore the *
* original AMODE before returning to COBOL. *
* *
****************************************************************
* PROBLEM DESCRIPTION: An ABEND0C1 may be received when a *
* COBOL program dynamically calls an *
* Assembler program that is AMODE(31) or *
* AMODE(ANY) and the Assembler program *
* switches to AMODE 24 and then attempts *
* to return to COBOL without switching *
* back to AMODE 31. The high order byte *
* of the return address may be truncated *
* if a load and branch are done by the *
* Assembler program while in AMODE 24 *
* because the COBOL dynamic call routine, *
* IGZCFCC, is now loaded above the line. *
* *
* The COBOL Migration Guide does not *
* contain any warning about this *
* potential change in behavior. The *
* error may not be detected until *
* migrating to LE for z/OS V1R2 or *
* later. *
* *
****************************************************************
* RECOMMENDATION: *
****************************************************************
The COBOL for z/OS and 390 Migration Guide does not have
information on a potential problem when calling an Assembler
program from COBOL under z/OS V1R2 and later. A change in the
RMODE of the COBOL dynamic call routine IGZCFCC may result in
an abend, if an assembler program called in AMODE 31 changes
to AMODE 24 and attempts to return to COBOL without restoring
the AMODE to 31.

This problem will only occur when there is an assembler
program in the application, it will not occur on a dynamic
call from a COBOL program to a COBOL program or with dynamic
calls from programs compiled with the VS COBOL II or OS/VS
COBOL compilers.



PROBLEM CONCLUSION:
Update the Enterprise COBOL for z/OS and OS/390 Compiler
and Runtime Migration Guide GC27-1409 to describe the changes
made to the dynamic call routine and the potential error when
moving to z/OS V1R2 or later.
Pubs closing code: PRELERR

DOCUMENTATION CHANGE SECTION

Add the following text to the Enterprise COBOL for z/OS and
OS/390 Compiler and Runtime Migration Guide GC27-1409

Chapter 9. Upgrading Language Environment release levels.

| Dynamic calls to Assembler programs under Language
| Environment for z/OS V1R2 and later.
|
| When you migrate from earlier Language Environment releases
| to Language Environment for z/OS V1R2 or later you need to be
| aware of a change to the RMODE of the dynamic call routine
| IGZCFCC. The change to the RMODE for IGZCFCC may cause
| problems if a dynamically called Assembler program returns in
| a different AMODE from that in which it was entered. IGZCFCC
| is used only by COBOL programs compiled with COBOL for MVS &
| VM R2 or later, it is not used by programs compiled with the
| VS COBOL II or OS/VS COBOL compilers.
|
| Beginning in z/OS V1R2 the COBOL dynamic call routine IGZCFCC
| was changed from RMODE 24 to RMODE 31 and incorporated into
| the IGZCPAC load module, which resides above the line. When
| a dynamic call is made to an AMODE 31 program the return
| address is to IGZCFCC.
|
| In Language Environment releases prior to z/OS V1R2, an
| Assembler program entered in AMODE 31 could change the
| AMODE to 24 and still return successfully to the dynamic
| call routine IGZCFCC because it was loaded below the line.
| With IGZCFCC residing above the line in Language Environment
| for z/OS V1R2 and later, this no longer works. If an
| Assembler program is entered in AMODE 31, switches to AMODE
| 24 and then does a load and branch to return to its caller,
| the high order byte of the 31 bit return address can be
| truncated, resulting in a bad branch, ABEND0C4, ABEND0C1,
| etc.
|
| Resolve the problem in either of the following ways:
| 1. Compile and link the Assembler program as
| AMODE 24. COBOL will handle the mode switching.
| 2. Modify the Assembler program to restore the
| AMODE that was in use when it was entered, when
| returning to COBOL.
|
The following is not in the reference manual, but may be
adequate for you. How to preserve the AMODE in assembler:
LA 8,RRR Query Amode


BSM 8,0 Preserve the current Amode
BASSM 14,15 Go to COBOL subroutine in Amode 24 or 31.
BSM 0,8 Restore Amode
RRR DS 0H
Back to top
View user's profile Send private message
adiovanni

New User


Joined: 22 Nov 2006
Posts: 40
Location: USA

PostPosted: Thu Dec 07, 2006 12:01 am
Reply with quote

CALL the PUTENV program DYNAMICALLY (without quotes and supply 77 PUTENV PIC X(8) value 'PUTENV ' in your working-storage) and try it again and let me know.

That usually fixes this type of problem.

Note if you're going to call DYNALLOC more that once in the run unit, then you'll obviously have to CANCEL before you CALL again (unless you make the DYNALLOC program an INITIAL program).
Back to top
View user's profile Send private message
galecra

New User


Joined: 11 Sep 2006
Posts: 33

PostPosted: Thu Dec 07, 2006 2:30 am
Reply with quote

Didn't work ... :-(
S0C1 again

77 PUTENV PIC X(8) VALUE 'PUTENV '.


CALL PUTENV
USING BY VALUE WS-DYNA-FILE-PTR RETURNING WS-RC.

I don't want to bother you so much... if you want to continue helping me, I'll be really grateful ,... because I would like this to work!!!
Back to top
View user's profile Send private message
adiovanni

New User


Joined: 22 Nov 2006
Posts: 40
Location: USA

PostPosted: Thu Dec 07, 2006 2:58 am
Reply with quote

I mentioned this earlier--did you check this:

Your dsn called 'AVE0288.DYNALLOC.TEST.FILE' must exist and must be cataloged...is that true ?
Back to top
View user's profile Send private message
adiovanni

New User


Joined: 22 Nov 2006
Posts: 40
Location: USA

PostPosted: Thu Dec 07, 2006 2:59 am
Reply with quote

Also:

You added the UT-S- before the DD is the SELECT/ASSIGN, right ?
Back to top
View user's profile Send private message
galecra

New User


Joined: 11 Sep 2006
Posts: 33

PostPosted: Thu Dec 07, 2006 6:27 am
Reply with quote

I have to say Yes to both questions...
the file is allocated, not migrated, and in direct access storage...
but maybe the file attributes are not the correct ones, how should I allocate the file (lrecl, recfm, dsorg, etc) ?

Could be something wrong dealing with the installation where I'm running the program? what should be the preconditions for this to run ok?

And, besides, this could be a topic for another discussion, but is there any other way in COBOL to process files dynamically?... For example with REXX I can use ALLOC command...
But well, let's keep trying the PUTENV way! , maybe we found the problem..

Thanks!!
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 Goto page 1, 2, 3, 4  Next

 


Similar Topics
Topic Forum Replies
No new posts Write line by line from two files DFSORT/ICETOOL 7
No new posts Compare only first records of the fil... SYNCSORT 7
No new posts CLIST - Virtual storage allocation error CLIST & REXX 5
No new posts Merge two VSAM KSDS files into third ... JCL & VSAM 6
No new posts Joinkeys - 5 output files DFSORT/ICETOOL 7
Search our Forums:

Back to Top