View previous topic :: View next topic
|
Author |
Message |
kudamala
New User
Joined: 12 Sep 2008 Posts: 51 Location: Bangalore
|
|
|
|
Hello
I have the following code to read a file dynamically.
Code: |
IDENTIFICATION DIVISION.
PROGRAM-ID. DYN
DATE-COMPILED.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT IN-FILE
ASSIGN TO INFILE
ORGANIZATION IS SEQUENTIAL.
DATA DIVISION.
FILE SECTION.
FD IN-FILE
RECORDING MODE IS F
LABEL RECORDS ARE STANDARD
BLOCK CONTAINS 0 RECORDS
DATA RECORD IS IN-REC.
01 IN-REC PIC X(80).
WORKING-STORAGE SECTION.
01 BPXWDYN PIC X(08) VALUE 'BPXWDYN'.
01 S-EOF-FILE PIC X(01) VALUE 'N'.
01 PDS-STRING.
05 PDS-LENGTH PIC S9(4) COMP VALUE 100.
05 PDS-TEXT PIC X(100) VALUE
'ALLOC DD(INFILE) DSN(''DEV.PDS.FILE.DATA)'') SHR'.
PROCEDURE DIVISION.
CALL BPXWDYN USING PDS-STRING
IF RETURN-CODE = ZERO
DISPLAY 'ALLOCATION OK'
ELSE
DISPLAY 'ALLOC FAILED, RETURN-CODE WAS ' RETURN-CODE
PERFORM INHOUSE-ABEND-ROUTINE
END-IF
OPEN INPUT IN-FILE
PERFORM 1000-READ-INFILE UNTIL S-EOF-FILE = 'Y'
CLOSE IN-FILE
GOBACK.
1000-READ-INFILE.
READ IN-FILE
AT END
MOVE 'Y' TO S-EOF-FILE
NOT AT END
DISPLAY IN-REC
END-READ |
.
The above code displays the records of the file ''DEV.PDS.FILE.DATA.
DEV.PDS.FILE.DATA contains the file names to be processed.
Can anybody help how to read the files inside the DEV.PDS.FILE.DATA? |
|
Back to top |
|
|
Robert Sample
Global Moderator
Joined: 06 Jun 2008 Posts: 8700 Location: Dubuque, Iowa, USA
|
|
|
|
Add another SELECT statement. Create a variable using STRING to build the dynamic allocation text including the file name from DEV.PDS.FILE.DATA and call BPXWDYN to allocate it. Open the second file, read, close and then repeat. |
|
Back to top |
|
|
William Thompson
Global Moderator
Joined: 18 Nov 2006 Posts: 3156 Location: Tucson AZ
|
|
|
|
A simple search of "dynamic file allocation" in the COBOL forum would have shown you the thread Dynamic allocataion of file in COBOL which would give you even a better search key of "BPXWDYN". Give it a try, the subject pops up quite often around here..... |
|
Back to top |
|
|
Marso
REXX Moderator
Joined: 13 Mar 2006 Posts: 1353 Location: Israel
|
|
|
|
You need dynamic allocation for files listed in the INFILE, but maybe you don't need for DEV.PDS.FILE.DATA ? |
|
Back to top |
|
|
Kjeld
Active User
Joined: 15 Dec 2009 Posts: 365 Location: Denmark
|
|
|
|
kudamala wrote: |
DEV.PDS.FILE.DATA contains the file names to be processed.
Can anybody help how to read the files inside the DEV.PDS.FILE.DATA? |
The dataset name suggests that the input file is allocated as PDS file. You should not read a complete PDS file sequentially with an application program, you can only allocate individual members to read them sequentially. If you are to read the directory contents and member lists you have to use a PDS utility. |
|
Back to top |
|
|
kudamala
New User
Joined: 12 Sep 2008 Posts: 51 Location: Bangalore
|
|
|
|
Hello Friends
I am reading input file and moving the record (each record in file is name of another file) to a string and concatenated string for file allocation. But I have a problem while reading the data from allocated files. It is always reading First allocated file:
Code: |
MOVE WK-STRING(1:30) TO FILE-STRING
STRING 'ALLOC DD(INFILE) DSN(' FILE-STRING ') SHR'
DELIMITED BY SIZE
INTO PDS-STRING
DISPLAY PDS-STRING
PERFORM F65-BPXWDYN-FILE
IF WK-OK
MOVE '0' TO IN-FL
MOVE ZERO TO WK-ERR-COUNT
OPEN INPUT IN-FILE
READ IN-FILE AT END MOVE '1' TO IN-FL
DISPLAY DATA...
END-READ
END-IF
CLOSE IN-FILE ----(IN-FILE is the assigned file name for INFILE) |
"Code'd"
But when I see the output, I see list of all allocated files, but data is only form first read file
Do I need to deallocate after reading each file? Is there anyway to deallocate previous file before allocating another file? or anything else I missed out?
Thanks in advance |
|
Back to top |
|
|
Robert Sample
Global Moderator
Joined: 06 Jun 2008 Posts: 8700 Location: Dubuque, Iowa, USA
|
|
|
|
Are you checking the BPXWDYN return code after each command? If not, I recommend you add that code since the return code is important. If you are using the same DD name for each file, you must close it and then call BPXWDYN to FREE the allocation before allocating the next file to the DD name -- or the same file will get used over and over. |
|
Back to top |
|
|
kudamala
New User
Joined: 12 Sep 2008 Posts: 51 Location: Bangalore
|
|
|
|
Hello Freinds
thanks for you inputs
I tried to call BPXWDYN using FREE, but encountering SOC4 error and Free failed with return code 04
MOVE SPACES TO PDS-STRING
STRING 'FREE DD(INFILE) DSN(' FILE-STRING ') SHR'
DELIMITED BY SIZE
INTO PDS-STRING
PERFORM F65-BPXWDYN-FILE-FREE
-----------------------------------------
F65-BPXWDYN-FILE-FREE.
CALL BPXWDYN USING PDS-STRING
IF RETURN-CODE = ZERO
DISPLAY 'DEALLOCATION OK'
SET WK-OK-FREE TO TRUE
ELSE
DISPLAY 'FREE FAILED, RETURN-CODE WAS ' RETURN-CODE
SET NOT-OK-FREE TO TRUE
GO TO F90-ERROR-VSAM
END-IF
.
Could you please help, if I am doing something wrong here?
Thanks in advance |
|
Back to top |
|
|
Robert Sample
Global Moderator
Joined: 06 Jun 2008 Posts: 8700 Location: Dubuque, Iowa, USA
|
|
|
|
All you need is FREE FI(INFILE) -- why have anything more? |
|
Back to top |
|
|
kudamala
New User
Joined: 12 Sep 2008 Posts: 51 Location: Bangalore
|
|
|
|
Hello
in FREE FI(INFILE) syntax
what is the FI?
Sorry for this question. I am usinng BPXWDYN first time
Thanks |
|
Back to top |
|
|
kudamala
New User
Joined: 12 Sep 2008 Posts: 51 Location: Bangalore
|
|
|
|
I tried with
FREE FI(INFILE)
FREE (INFILE)
FREE (ALL)
But I have encountered compilation error:
IGYPS2072-S "FREE" was invalid. Skipped to the next verb, period or procedure
Thanks |
|
Back to top |
|
|
dbzTHEdinosauer
Global Moderator
Joined: 20 Oct 2006 Posts: 6966 Location: porcelain throne
|
|
|
|
you could
INITIALIZE PDS-STRING
STRING 'FREE FI(INFILE)'
INTO PDS-STRING
END-STRING
PERFORM F65-BPXWDYN-FILE |
|
Back to top |
|
|
Robert Sample
Global Moderator
Joined: 06 Jun 2008 Posts: 8700 Location: Dubuque, Iowa, USA
|
|
|
|
The FREE must be done through BPXWDYN, not COBOL. And the FI means FILE (also known as DD name). |
|
Back to top |
|
|
kudamala
New User
Joined: 12 Sep 2008 Posts: 51 Location: Bangalore
|
|
|
|
Hello
I am really thankful to the Forum. I have done as specified above
MOVE SPACE TO PDS-STRING
STRING 'FREE DD(INFILE) DSN(' FILE-STRING ') SHR'
DELIMITED BY SIZE
INTO PDS-STRING
DISPLAY 'FREE FILE:' PDS-STRING
CALL BPXWDYN USING PDS-STRING
Compilation is ok. But job failed with FREE. I am furnishing the output alongwith my display statements:
FILE NAME:DEV.EUM.MKT.SELL.AABB.FTP.DATA
ALLOC DD(INFILE) DSN(DEV.EUM.MKT.SELL.AABB.FTP.DATA) SHR
ALLOCATION OK
FA-VENDOR:AABB
CUR VEND:AABB
FILE AFTER:DEV.EUM.MKT.SELL.AABB.FTP.DATA
FREE FILE:FREE DD(INFILE) DSN(DEV.EUM.MKT.SELL.AABB.FTP.DATA) SHR
FREE FAILED, RETURN-CODE WAS 0004
PROGRAM ABENDED : EUM703P1
Still I am confused, why FREE is failing
Thanks |
|
Back to top |
|
|
Ronald Burr
Active User
Joined: 22 Oct 2009 Posts: 293 Location: U.S.A.
|
|
|
|
Why do you insist in changing the code you were provided? Dick did NOT say FREE DD(INFILE), he said FREE FI(INFILE) and he did NOT add either the DSN specification nor the SHR option. |
|
Back to top |
|
|
daveporcelan
Active Member
Joined: 01 Dec 2006 Posts: 792 Location: Pennsylvania
|
|
|
|
Look at the string statement that dbzTHEdinosauer (and Robert Sample)
suggested.
Look at yours.
Are they the same?
Try what they suggested and report back. |
|
Back to top |
|
|
kudamala
New User
Joined: 12 Sep 2008 Posts: 51 Location: Bangalore
|
|
|
|
Ggreat.......
It is successful now....sorry for bothering you by changing the syntax.
Once again thankful to each and everybody who helped and thanks to Forum |
|
Back to top |
|
|
|