View previous topic :: View next topic |
Author |
Message |
Garpz Beginner
Joined: 10 Jul 2003 Posts: 7 Topics: 1
|
Posted: Thu Jul 10, 2003 10:19 am Post subject: Using variables with the COBOL WRITE statement |
|
|
This may not be the best solution to my problem, but this is the early stages of the design...
I'm writing a COBOL program to create VSAM DELETE/DEFINE control cards (the output files of the program) for several indexed files, all of which will contain a date stamp (fed from the JCL) in the dsn.
I plan to code a generic papragraph to create each card based on working storage variables (which represent parameters of the IDCAMS DEL/DEF statement) set in a calling paragraph.
The problem is that to increase modularity, I want to create the entire card in the "generic" paragraph. Therefore, I need to be able to tell the paragraph which file I want to WRITE to during each distinct call (And I don't want a great big EVALUATE statement in the paragraph).
I tried something like the following, but as expected ended up with compile errors. Any suggestions?
DATA DIVISION
FD CNTLCD1
RECORDING MODE IS F
DATA RECORD IS CNTLCD1-REC.
10 CNTLCD1-REC PIC X(80).
WORKING-STORAGE SECTION.
01 WS-CARD-LINE PIC X(80) VALUE SPACES.
01 WS-REC-NAME PIC X(11) VALUE SPACES.
PROCEDURE DIVISION.
:
:
MOVE 'CNTLCD1-REC' TO WS-REC-NAME
:
WRITE WS-REC-NAME FROM WS-CARD-LINE |
|
Back to top |
|
|
Kathi Beginner
Joined: 14 May 2003 Posts: 25 Topics: 0 Location: Mission Viejo, California
|
Posted: Thu Jul 10, 2003 10:23 am Post subject: |
|
|
Well, first of all is the data record CNTLCD1-REC really defined as a 10 and not 01?
Secondly, you are attempting to write a data item which is not a record. You cannot do that. You will have to make WS-REC-NAME a record in an FD then the write will work.
If this does not work, please post the compile error messages. |
|
Back to top |
|
|
vp Beginner
Joined: 30 Jun 2003 Posts: 9 Topics: 0
|
Posted: Thu Jul 10, 2003 10:41 am Post subject: |
|
|
What I've done in the past is to create a parmlib member for a generic delete/define card, then read it into my program line by line modified (inserted) dsn name in the appropriate spot and wrote it out to an output dsn, to be used in the idcams step. |
|
Back to top |
|
|
Garpz Beginner
Joined: 10 Jul 2003 Posts: 7 Topics: 1
|
Posted: Thu Jul 10, 2003 11:08 am Post subject: |
|
|
Kathi,
Yes, the CNTLCD1-REC was a typo in the post, but not the program.
VP,
I also thought of a similar solution (except i was going to create a production table), but implementing that way will contradict the specs we provided.
Thanks to both of you for the responses. |
|
Back to top |
|
|
vp Beginner
Joined: 30 Jun 2003 Posts: 9 Topics: 0
|
Posted: Thu Jul 10, 2003 11:22 am Post subject: |
|
|
Here is another approach.
You could populate a variable with the file name you want to write to.
Then use dynamic allocation to create the output file.
Here is the link to dynamically allocate files in Cobol
http://www.naspa.com/PDF/2001/1201%20PDF/T0112005.pdf |
|
Back to top |
|
|
Garpz Beginner
Joined: 10 Jul 2003 Posts: 7 Topics: 1
|
Posted: Thu Jul 10, 2003 12:49 pm Post subject: |
|
|
I got the same article off this site earlier this morning, but I got stumped. Maybe I'm missing something obvious...
I could dynamically allocate each new file but how would I output a line to the files? The WRITE statement uses record names. I'd need still need unique FD statements and record names for each output file wouldn't I?. I couldn't have the same 01 level record name for each file allocated could I? |
|
Back to top |
|
|
vp Beginner
Joined: 30 Jun 2003 Posts: 9 Topics: 0
|
Posted: Thu Jul 10, 2003 1:23 pm Post subject: |
|
|
You still need to define the file in the environment and data divisions, as in:
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT DYNAMIC-OUTPUT-FILE ASSIGN TO UT-S-DYNALLOC
FILE STATUS IS WS-DYNAMIC-OUTPUT-FILE-STATUS.
DATA DIVISION.
FILE SECTION.
FD DYNAMIC-OUTPUT-FILE.
01 DYNAMIC-OUTPUT-RECORD PIC X(80).
You would then have to build the FILE-ENVIRONMENT-VARIABLE dynamically, using the passed Output file name, let's call it YOURID.IDCAMS.DELDEF.OUT.
MOVE SPACES TO FILE-ENVIRONMENT-VARIABLE
STRING
"DYNALLOC=DSN(" DELIMITED BY SIZE
YOURID.IDCAMS.DELDEF.OUT DELIMITED BY SIZE
") SHR"
INTO FILE-ENVIRONMENT-VARIABLE
END-STRING
or you can use a different construct to build it
Once you allocate the file to the dd, you would be able to WRITE DYNAMIC-OUTPUT-RECORD,
after you OPEN OUTPUT DYNAMIC-OUTPUT-FILE.
Please note,
in statement CALL "putenv" USING BY VALUE ADDRESS-POINTER
putenv - MUST BE LOWER CASE. |
|
Back to top |
|
|
Garpz Beginner
Joined: 10 Jul 2003 Posts: 7 Topics: 1
|
Posted: Wed Jul 16, 2003 4:37 pm Post subject: |
|
|
VP,
Thanks again for the assistance.
How can I check the LE version on my machine? Does it correspond to the version of the COBOL compiler?
My code looks OK, but I'm getting a CEEDUMP because my program can't find the "putenv" executable at run-time. Is that b/c I haven't linked the programs correctly, maybe missed a link-edit option? |
|
Back to top |
|
|
Garpz Beginner
Joined: 10 Jul 2003 Posts: 7 Topics: 1
|
Posted: Wed Jul 16, 2003 5:16 pm Post subject: |
|
|
Here's the message @ the top of the dump. OS/390 version is 2R10, so I should be able to call "putenv", right?
CEE3DMP V2 R10.0: CONDITION PROCESSING RESULTED IN THE UNHANDLED CONDITION. |
|
Back to top |
|
|
vp Beginner
Joined: 30 Jun 2003 Posts: 9 Topics: 0
|
Posted: Thu Jul 17, 2003 9:08 am Post subject: |
|
|
This is a little beyond my expertise. I will have to research and today I will be pretty swamped. I will try to find an answer tomorrow.
Anyone, please fill free to jump in. |
|
Back to top |
|
|
Garpz Beginner
Joined: 10 Jul 2003 Posts: 7 Topics: 1
|
Posted: Thu Jul 17, 2003 11:27 am Post subject: |
|
|
VP,
Thank you. Most of us understand busy
I made a little progress. Someone passed me a TSO command that will search all the system link list libraries for a module and if its found it'll return the library where it resides. No luck though. The module wasn't found. |
|
Back to top |
|
|
RonB Beginner
Joined: 02 Dec 2002 Posts: 93 Topics: 0 Location: Orlando, FL
|
Posted: Thu Jul 17, 2003 3:58 pm Post subject: |
|
|
May I offer the following alternative to using the "putenv" method? This method uses TSO services ( specifically the IKJTSOEV and IKJEFTSR services ). Of course that does mean that TSO services must be available on the LPAR where the code executes.
Code: | IDENTIFICATION DIVISION.
PROGRAM-ID. DYNAMTST.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT DYNAM-FILE ASSIGN TO DYNAFILE.
DATA DIVISION.
FILE SECTION.
FD DYNAM-FILE
RECORDING MODE IS F
LABEL RECORDS ARE STANDARD
BLOCK CONTAINS 0 RECORDS.
01 DYNAMIC-RECORD PIC X(80).
WORKING-STORAGE SECTION.
01 WS-TSO-SERVICES-LINKAGE.
05 WS-TSO-DUMMY PIC S9(09) COMP.
05 WS-TSO-RETURN-CODE PIC S9(09) COMP.
05 WS-TSO-REASON-CODE PIC S9(09) COMP.
05 WS-TSO-INFO-CODE PIC S9(09) COMP.
05 WS-TSO-CPPL-ADDRESS PIC S9(09) COMP.
05 WS-TSO-FLAGS PIC X(04) VALUE X'00010001'.
05 WS-TSO-LENGTH PIC S9(08) COMP VALUE 256.
05 WS-TSO-BUFFER PIC X(256).
PROCEDURE DIVISION.
*The following is a one-time call to establish a TSO environment
CALL 'IKJTSOEV' USING WS-TSO-DUMMY
WS-TSO-RETURN-CODE
WS-TSO-REASON-CODE
WS-TSO-INFO-CODE
WS-TSO-CPPL-ADDRESS.
IF WS-TSO-RETURN-CODE > ZERO
THEN
DISPLAY 'THE TSO INTERFACE COULD NOT BE ESTABLISHED.'
DISPLAY ' RETURN = ' WS-TSO-RETURN-CODE
DISPLAY ' REASON = ' WS-TSO-REASON-CODE
CALL 'ABEND'.
*The following string statement builds the tso alloc statement
MOVE SPACES TO WS-TSO-BUFFER.
STRING 'ALLOC F(DYNAFILE) DA(' DELIMITED BY SIZE
'''YOUR.DYNALLOC.FILE.NAME''' DELIMITED BY SIZE
') NEW SPACE(1,1) TRACKS' DELIMITED BY SIZE
' DSORG(PS) RECFM(F B)' DELIMITED BY SIZE
' LRECL(80) BLKSIZE(6320)' DELIMITED BY SIZE
INTO WS-TSO-BUFFER.
DISPLAY WS-TSO-BUFFER.
*The following call does the dynamic allocation.
CALL 'IKJEFTSR' USING WS-TSO-FLAGS
WS-TSO-BUFFER
WS-TSO-LENGTH
WS-TSO-RETURN-CODE
WS-TSO-REASON-CODE
WS-TSO-DUMMY.
IF WS-TSO-RETURN-CODE > ZERO
THEN
DISPLAY 'THE TSO ALLOCATION FAILED.'
DISPLAY ' RETURN = ' WS-TSO-RETURN-CODE
DISPLAY ' REASON = ' WS-TSO-REASON-CODE
CALL 'ABEND'.
OPEN OUTPUT DYNAM-FILE.
*
*Program logic goes here
*
CLOSE DYNAM-FILE.
GOBACK. |
HTH. . .
Ron |
|
Back to top |
|
|
Garpz Beginner
Joined: 10 Jul 2003 Posts: 7 Topics: 1
|
Posted: Thu Jul 17, 2003 4:51 pm Post subject: |
|
|
Thanks to everyone who's replied to my post. Its is greatly appeciated!
Unfortunately, I didn't end up using any of the solutions posted. I actually found an executable (assembler pgm) in a system link library that can do what I want.
All I need to do is call the module and pass first the variable name from the SELECT and FD statements and second, the DDNAME I want assigned.
- OPEN
- WRITE
- CLOSE
- Repeat as necessary.
That's it. Works like a charm.
Again my thanks go out to all. I hope I can be of some help in the future.
-Garpz |
|
Back to top |
|
|
|
|