View previous topic :: View next topic |
Author |
Message |
rakshith Beginner
Joined: 26 Jul 2005 Posts: 32 Topics: 16 Location: bangalore
|
Posted: Thu Jul 28, 2005 3:28 am Post subject: BPXWDYN file allocation |
|
|
Hi all
can any one post a cobol code which will create a new file dynamically
thanks
rakshith |
|
Back to top |
|
|
kolusu Site Admin
Joined: 26 Nov 2002 Posts: 12376 Topics: 75 Location: San Jose
|
Posted: Thu Jul 28, 2005 8:05 am Post subject: |
|
|
rakshith,
Check this
Code: |
IDENTIFICATION DIVISION.
PROGRAM-ID. DYN
DATE-COMPILED.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
SELECT OUT-FILE
ASSIGN TO OUTFILE
ORGANIZATION IS SEQUENTIAL.
DATA DIVISION.
FILE SECTION.
FD OUT-FILE
RECORDING MODE IS F
LABEL RECORDS ARE STANDARD
BLOCK CONTAINS 0 RECORDS
DATA RECORD IS OUT-REC.
01 OUT-REC PIC X(80).
WORKING-STORAGE SECTION.
01 W-DYNAM-MODULE PIC X(08) VALUE 'BPXWDYN'.
01 W-DS-NAME PIC X(44) VALUE SPACES.
01 W-LEN PIC S9(4) COMP VALUE 1.
01 W-DYN-STRING.
05 W-DYN-LENGTH PIC S9(4) COMP.
05 W-DYN-TEXT PIC X(150).
PROCEDURE DIVISION.
PERFORM 1000-DYN-ALLOC
GOBACK.
1000-DYN-ALLOC.
MOVE SPACES TO W-DYN-TEXT
MOVE 'your new dynamic dsn name'
TO W-DS-NAME
STRING
'ALLOC DD(OUTFILE) DSN(' DELIMITED BY SIZE
QUOTE DELIMITED BY SIZE
W-DS-NAME DELIMITED BY SPACE
QUOTE DELIMITED BY SIZE
') NEW' DELIMITED BY SIZE
' CYL' DELIMITED BY SIZE
' SPACE(1,1)' DELIMITED BY SIZE
' UNIT(SYSDA)' DELIMITED BY SIZE
' CATALOG' DELIMITED BY SIZE
' BLKSIZE(27920)' DELIMITED BY SIZE
' LRECL(80)' DELIMITED BY SIZE
' RECFM(F,B)' DELIMITED BY SIZE
' DSORG(PS)' DELIMITED BY SIZE
INTO W-DYN-TEXT
POINTER W-LEN
END-STRING.
MOVE W-LEN TO W-DYN-LENGTH
CALL W-DYNAM-MODULE USING W-DYN-STRING
IF RETURN-CODE = ZERO
DISPLAY 'ALLOCATION OK FOR : ' W-DS-NAME
ELSE
DISPLAY 'ALLOCATION FAILED : ' RETURN-CODE
END-IF
.
|
Hope this helps....
Cheers
kolusu _________________ Kolusu
www.linkedin.com/in/kolusu |
|
Back to top |
|
|
rakshith Beginner
Joined: 26 Jul 2005 Posts: 32 Topics: 16 Location: bangalore
|
Posted: Thu Jul 28, 2005 10:38 am Post subject: |
|
|
Thanks Kolusu,
It works.....
and I want to delete this file dynamically at the end of the program!
how can I accomplish this task.
I used FREE commands, but the dataset is not physically deleted..
can you please help me in this case also....
Thaks,
rakshith |
|
Back to top |
|
|
kolusu Site Admin
Joined: 26 Nov 2002 Posts: 12376 Topics: 75 Location: San Jose
|
Posted: Thu Jul 28, 2005 10:42 am Post subject: |
|
|
rakshith,
Quote: |
STRING
'ALLOC DD(OUTFILE) DSN(' DELIMITED BY SIZE
QUOTE DELIMITED BY SIZE
W-DS-NAME DELIMITED BY SPACE
QUOTE DELIMITED BY SIZE
') NEW' DELIMITED BY SIZE
' CYL' DELIMITED BY SIZE
' SPACE(1,1)' DELIMITED BY SIZE
' UNIT(SYSDA)' DELIMITED BY SIZE
' CATALOG' DELIMITED BY SIZE
' BLKSIZE(27920)' DELIMITED BY SIZE
' LRECL(80)' DELIMITED BY SIZE
' RECFM(F,B)' DELIMITED BY SIZE
' DSORG(PS)' DELIMITED BY SIZE
INTO W-DYN-TEXT
POINTER W-LEN
END-STRING
|
Just remove the line in bold and the dataset is automatically deleted at the end of the program as the default disp parameter is (New,Delete,Delete)
Hope this helps...
Cheers
Kolusu _________________ Kolusu
www.linkedin.com/in/kolusu |
|
Back to top |
|
|
rakshith Beginner
Joined: 26 Jul 2005 Posts: 32 Topics: 16 Location: bangalore
|
Posted: Fri Jul 29, 2005 4:17 am Post subject: |
|
|
thanks Kolusu....
regds.
rakshith |
|
Back to top |
|
|
madhuroyus Beginner
Joined: 09 Jan 2006 Posts: 45 Topics: 14 Location: Bangalore
|
Posted: Wed Jan 18, 2006 9:06 am Post subject: |
|
|
Hi Kolusu,
Can you please give me the jcl to run this program.
Thanks
Madhu _________________ Self confidence is something that says U will do it, when the rest of the world has exactly opposite view. |
|
Back to top |
|
|
kolusu Site Admin
Joined: 26 Nov 2002 Posts: 12376 Topics: 75 Location: San Jose
|
Posted: Wed Jan 18, 2006 10:41 am Post subject: |
|
|
Quote: |
Can you please give me the jcl to run this program.
|
madhuroyus,
You serious about the JCL? Just compile the the pgm and just run it like any normal program.
Code: |
//STEP0100 EXEC PGM=YOUR COB PGM
//*
//STEPLIB DD DSN=YOUR LOADLIB PDS,
// DISP=SHR
//SYSPRINT DD SYSOUT=*
//SYSOUT DD SYSOUT=*
//SYSUDUMP DD SYSOUT=*
|
Hope this helps...
Cheers
Kolusu _________________ Kolusu
www.linkedin.com/in/kolusu |
|
Back to top |
|
|
stalin Beginner
Joined: 22 Aug 2005 Posts: 23 Topics: 4
|
Posted: Tue May 30, 2006 4:34 am Post subject: |
|
|
Hi ,
i have gone through the code and it worked perfectly.but this doesnt suit my requirement and i need help from all you guys.
i need to allocate many files dynamically depending upon the input value.
say if the input value is X(we pass it from JCL). this X may have any value.
we need to allocates so x number of files dynamically.
if the value of X = 5 then the file names should be like this.
a.b.c1
a.b.c2
a.b.c3
a.b.c4
a.b.c5
can you guys help me out.
Thanks
Stalin. |
|
Back to top |
|
|
kolusu Site Admin
Joined: 26 Nov 2002 Posts: 12376 Topics: 75 Location: San Jose
|
Posted: Tue May 30, 2006 5:13 am Post subject: |
|
|
stalin,
Code a PERFORM varying loop starting from 1 upto the value and allocate the files. A simple programming task.
kolusu _________________ Kolusu
www.linkedin.com/in/kolusu |
|
Back to top |
|
|
stalin Beginner
Joined: 22 Aug 2005 Posts: 23 Topics: 4
|
Posted: Tue May 30, 2006 5:44 am Post subject: |
|
|
i tried it Kolusu,
but it allocate it for the first time and for the next it says allocation failed, though the filename is different.got no clue why this happens. |
|
Back to top |
|
|
stalin Beginner
Joined: 22 Aug 2005 Posts: 23 Topics: 4
|
Posted: Tue May 30, 2006 5:48 am Post subject: |
|
|
here is the code....
Code: |
FILE-CONTROL.
SELECT OUT-FILE ASSIGN TO OUTIFLE
ORGANIZATION IS SEQUENTIAL.
DATA DIVISION.
FILE SECTION.
FD OUT-FILE
LABEL RECORDS ARE STANDARD
RECORDING MODE IS F
BLOCK CONTAINS 0 RECORDS
DATA RECORD IS OUT-REC.
01 OUT-REC PIC X(80).
WORKING-STORAGE SECTION.
01 WS-DYNAM-MODULE PIC X(80) VALUE 'BPXWDYN'.
01 WS-DS-NAME PIC X(44) VALUE SPACES.
01 WS-LEN PIC S9(4) COMP VALUE 1.
01 WS-DYN-STRING.
05 WS-DYN-LENGTH PIC S9(4) COMP.
05 WS-DYN-TEXT PIC X(150).
77 I PIC 9(2).
77 J PIC 9(2).
77 SBAL PIC A(10).
77 SBAL1 PIC A(1).
77 SBAL2 PIC X(2).
77 SBAL3 PIC X(13).
PROCEDURE DIVISION.
ACCEPT I.
ACCEPT J.
PERFORM 1000-DYN-ALLOC VARYING I FROM 1 BY 1 UNTIL I = 3
GOBACK.
1000-DYN-ALLOC.
MOVE SPACES TO WS-DYN-TEXT
MOVE '@SBAL.A.B.' TO SBAL.
MOVE 'C' TO SBAL1.
MOVE I TO SBAL2.
DISPLAY SBAL2.
DISPLAY J.
STRING
SBAL SBAL1 SBAL2 DELIMITED BY SIZE INTO SBAL3.
MOVE SBAL3 TO WS-DS-NAME
STRING
'ALLOC DD(OUTFILE) DSN(' DELIMITED BY SIZE
QUOTE DELIMITED BY SIZE
WS-DS-NAME DELIMITED BY SPACE
QUOTE DELIMITED BY SIZE
') NEW' DELIMITED BY SIZE
' CYL' DELIMITED BY SIZE
' SPACE(1,1)' DELIMITED BY SIZE
' UNIT(SYSDA)' DELIMITED BY SIZE
' CATALOG' DELIMITED BY SIZE
' BLKSIZE(600)' DELIMITED BY SIZE
' LRECL(60)' DELIMITED BY SIZE
' RECFM(F,B)' DELIMITED BY SIZE
' DSORG(PS)' DELIMITED BY SIZE
INTO WS-DYN-TEXT
POINTER WS-LEN
END-STRING.
MOVE WS-LEN TO WS-DYN-LENGTH
CALL WS-DYNAM-MODULE USING WS-DYN-STRING
IF RETURN-CODE = 0
DISPLAY 'ALLOCATION OK'
ELSE
DISPLAY 'ALLOCATION FAILED'
END-IF.
|
|
|
Back to top |
|
|
kolusu Site Admin
Joined: 26 Nov 2002 Posts: 12376 Topics: 75 Location: San Jose
|
Posted: Tue May 30, 2006 10:21 am Post subject: |
|
|
stalin,
The reason is simple. You did NOT initialize the WS-LEN after the first allocation. So the pointer stays at the length of first allocation.
Code the following statement before the STRING allocation statement.
Hope this helps...
Cheers
Kolusu _________________ Kolusu
www.linkedin.com/in/kolusu |
|
Back to top |
|
|
issac1029 Intermediate
Joined: 10 Dec 2005 Posts: 159 Topics: 75
|
Posted: Wed May 31, 2006 8:23 am Post subject: |
|
|
kolusu,
Quote: |
3.35.3 POINTER Phrase
identifier-4
Represents the pointer field, which points to a character position in
the receiving field.
It must be an elementary integer data item large enough to contain a
value equal to the length of the receiving area plus 1. The pointer
field must not contain the symbol P in its PICTURE character-string.
x When identifier-3 (the receiving field) is a DBCS data item,
x identifier-4 indicates the relative DBCS character position (not the
x relative byte position) in the receiving field.
|
POINTER can not overwrite the WS-LEN ?I can not find relative information in cobol reference,pls give me some tip.thanks! |
|
Back to top |
|
|
kolusu Site Admin
Joined: 26 Nov 2002 Posts: 12376 Topics: 75 Location: San Jose
|
Posted: Wed May 31, 2006 8:49 am Post subject: |
|
|
Quote: |
POINTER can not overwrite the WS-LEN ?I can not find relative information in cobol reference,pls give me some tip.thanks!
|
issac1029,
If you have read the complete STRING documentation you would have found this
When the POINTER phrase is specified, an explicit pointer field is available to the COBOL user to control placement of data in the receiving field. The user must set the explicit pointer's initial value, which must not be less than 1 and not more than the character position count of the receiving field.
Hope this helps...
Cheers
Kolusu _________________ Kolusu
www.linkedin.com/in/kolusu |
|
Back to top |
|
|
|
|