Here is how you can do it in COBOL directly:

Define a structure like this (for setenv; you only need the ENV-VALUE part for 
putenv):
01 ENV-VARS.                           
   05 ENV-NAME       PIC X(8).         
   05 ENV-VALUE      PIC X(100).       
   05 ENV-OVERWRITE  PIC S9(8) COMP.   

Then set the environment variable (the name is the DDNAME) using one of the 
following:

MOVE z"INFILE" TO ENV-NAME.                             (INFILE is the input 
DDNAME)
MOVE z"DSN(HLQ.INPUT(MEM1)),SHR"            
     TO ENV-VALUE.                                      
MOVE 1 TO ENV-OVERWRITE.                                
CALL "setenv" USING ENV-NAME, ENV-VALUE, ENV-OVERWRITE. 

MOVE z"OUTFILE" TO ENV-NAME.                            (OUTFILE is the output 
DDNAME)
MOVE z"DSN(HLQ.OUTPUT),NEW,UNIT(SYSDA),DELETE,SPACE(4,4)" 
     TO ENV-VALUE.                                       
MOVE 1 TO ENV-OVERWRITE.                                 
CALL "setenv" USING ENV-NAME, ENV-VALUE, ENV-OVERWRITE.  

MOVE z"CARDIN=DSN(HLQ.CARDIN),SHR" TO ENV-VALUE.    (CARDIN is another input 
DDNAME)
CALL "putenv" USING ENV-VALUE.                      

You can also set an LE environment variable using PARM.GO like this:

PARM.GO=('/ENVAR("CARDIN=DSN(HLQ.CARDIN),SHR")')

Then OPEN the file. Our run-time logic checks to see if a DD for the DDNAME is 
already allocated and if not, it will use the environment variable name that 
matches the DDNAME to allocate it. The DDNAME stays allocated after CLOSE. 
However, when you OPEN the file again, the run-time logic checks to see if the 
environment variable has changed. If so, it will deallocate the DDNAME and 
reallocate it using the new parms.

For more info on the parms that you can use for the dynamic allocation support, 
see:

QSAM:
http://publibfp.boulder.ibm.com/cgi-bin/bookmgr/BOOKS/igy3pg50/1.9.4.1

VSAM:
http://publibfp.boulder.ibm.com/cgi-bin/bookmgr/BOOKS/igy3pg50/1.10.6.3

LINE SEQUENTIAL:
http://publibfp.boulder.ibm.com/cgi-bin/bookmgr/BOOKS/igy3pg50/1.11.3

Rick Arellanes (IBM COBOL Development and Service)


On Fri, 6 Sep 2013 09:06:25 -0500, John McKown <john.archie.mck...@gmail.com> 
wrote:

>setenv does not _directly_ do a dynamic allocation. It sets up an LE
>environment variable, which has the same name as what is normally
>considered the DD name. If the DD name in the SELECT in COBOL is not
>already allocated, _and_ an LE environment variable is properly set up,
>_then_ the COBOL run time will do a dynamic allocation.
>
>BPXWDYN can be used as already mention.
>
>Before either of the above was available, I had code which use IKJTSOEV to
>set up a TSO environment and then did a TSO ALLOCATE command. I got this
>from Gilbert Saint-Flour.
>
>WORKING-STORAGE SECTION.
>01  FILLER.
>    05 WS-DUMMY        PIC S9(8) COMP.
>    05 WS-RETURN-CODE  PIC S9(8) COMP.
>    05 WS-REASON-CODE  PIC S9(8) COMP.
>    05 WS-INFO-CODE    PIC S9(8) COMP.
>    05 WS-CPPL-ADDRESS PIC S9(8) COMP.
>    05 WS-FLAGS        PIC X(4) VALUE X'00010001'.
>    05 WS-BUFFER       PIC X(256).
>    05 WS-LENGTH       PIC S9(8) COMP VALUE 256.
>PROCEDURE DIVISION.
>    CALL 'IKJTSOEV' USING WS-DUMMY
>                          WS-RETURN-CODE
>                          WS-REASON-CODE
>                          WS-INFO-CODE
>                          WS-CPPL-ADDRESS.
>    IF WS-RETURN-CODE > ZERO
>       DISPLAY 'IKJTSOEV FAILED, RETURN-CODE=' WS-RETURN-CODE
>               ' REASON-CODE=' WS-REASON-CODE
>               'INFO-CODE='    WS-INFO-CODE
>       MOVE WS-RETURN-CODE TO RETURN-CODE
>       GOBACK
>    END-IF.
>    MOVE 'ALLOCATE DD(SYSPUNCH) SYSOUT HOLD' TO WS-BUFFER.
>    CALL 'IKJEFTSR' USING WS-FLAGS
>                          WS-BUFFER
>                          WS-LENGTH
>                          WS-RETURN-CODE
>                          WS-REASON-CODE
>                          WS-DUMMY.
>    IF WS-RETURN-CODE > ZERO
>       DISPLAY 'IKJEFTSR FAILED, RETURN-CODE=' WS-RETURN-CODE
>               ' REASON-CODE=' WS-REASON-CODE
>       MOVE WS-RETURN-CODE TO RETURN-CODE
>       GOBACK
>    END-IF.
>    DISPLAY 'ALLOCATE WORKED ! ' UPON SYSPUNCH.
>
>I like BPXWDYN best in today's environment. It seems the easiest to
>understand and code.
>
>
>On Fri, Sep 6, 2013 at 8:45 AM, Mark Jacobs <mark.jac...@custserv.com>wrote:
>
>> Looking at this IBM Technote, it implies they will.
>>
>> http://www-01.ibm.com/support/**docview.wss?uid=swg21046577<http://www-01.ibm.com/support/docview.wss?uid=swg21046577>
>>
>> Mark Jacobs
>>
>>
>> On 09/06/13 09:43, Charles Mills wrote:
>>
>>> I don't *think* CEEENV or setenv will do dynamic allocation.
>>>
>>> That might be a good reason to pick BPXWDYN.
>>>
>>> Charles
>>>
>>> -----Original Message-----
>>> From: IBM Mainframe Discussion List 
>>> [mailto:ibm-m...@listserv.ua.**EDU<IBM-MAIN@LISTSERV.UA.EDU>]
>>> On
>>> Behalf Of Mark Jacobs
>>> Sent: Friday, September 06, 2013 4:21 AM
>>> To: IBM-MAIN@LISTSERV.UA.EDU
>>> Subject: Dynamic Allocation in COBOL
>>>
>>> This might not be the right forum for this question, but...
>>>
>>> Doing some very limited in initial research I've found three documented
>>> methods of performing Dynamic Allocation in COBOL ( Enterprise COBOL 4.2),
>>> BPXWDYN, CEEENV or setenv.
>>>
>>> Q1) Are there any others?We already use a home grown assembler program for
>>> dynamic allocation, but our direction is to move as much to the OS as
>>> possible.
>>> Q2) Is there any reason to pick one over the others?
>>>
>>> ------------------------------**------------------------------**
>>> ----------
>>> For IBM-MAIN subscribe / signoff / archive access instructions,
>>> send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN
>>>
>>>
>>>
>>
>> --
>> Mark Jacobs
>> Time Customer Service
>> Tampa, FL
>> ----
>>
>> The quiet ones are the ones that change the universe...
>> The loud ones only take the credit.
>>
>> Londo Mollari - Babylon 5
>>
>>
>> ------------------------------**------------------------------**----------
>> For IBM-MAIN subscribe / signoff / archive access instructions,
>> send email to lists...@listserv.ua.edu with the message: INFO IBM-MAIN
>>
>
>
>
>--
>As of next week, passwords will be entered in Morse code.
>
>Maranatha! <><
>John McKown
>
>----------------------------------------------------------------------
>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

Reply via email to