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

Initializing filler default value when redefine present


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

New User


Joined: 06 Jul 2012
Posts: 43
Location: INDIA

PostPosted: Thu Feb 13, 2014 11:17 am
Reply with quote

Hi,

I've a simple query regd Redefine and intialize verbs.

This is the working storage.
Code:

01 ws-n.
    03 ws-a pic X(10).
    03 FILLER PIC X(1) VALUE ','.
    03 WS-B PIC X(3).
01 WS-Z REDEFINES WS-N.
    03 WS-ZA PIC X(14).



In my code i gave a statement "MOVE SPACES TO WS-ZA" and wrote a blank record into the output file.
Now i've to move WS-N record to output with FILLER VALUE ',' for creating a csv file. But the filler has got overwritten with SPACES due to previous statement.
INITIALIZE WS-N also may not work as it can't initialize FILLER to its default values.

In this case, what should i write to get FILLER ',' in my output inspite of moving SPACES to redefine storage ??


ps: this is a sample working storage. my actual code has many csv columns. So i need to retain all the ',' while writing to output.
Back to top
View user's profile Send private message
Pandora-Box

Global Moderator


Joined: 07 Sep 2006
Posts: 1592
Location: Andromeda Galaxy

PostPosted: Thu Feb 13, 2014 11:29 am
Reply with quote

Why are you using REDEFINES here?
Back to top
View user's profile Send private message
dsivapradeep

New User


Joined: 06 Jul 2012
Posts: 43
Location: INDIA

PostPosted: Thu Feb 13, 2014 11:43 am
Reply with quote

Well, the redefines structure is actually trailer record layout for my file.
and the WS-N is data layout. So I'm using same copybook for creating data + trailer for my file.

Also the Redefine will have a different layout from the main data layout.

Using redefine simplifies my code alot. So it's present!!
Back to top
View user's profile Send private message
Bill Woodger

Moderator Emeritus


Joined: 09 Mar 2011
Posts: 7309
Location: Inside the Matrix

PostPosted: Thu Feb 13, 2014 12:49 pm
Reply with quote

dsivapradeep wrote:
Well, the redefines structure is actually trailer record layout for my file.
and the WS-N is data layout. So I'm using same copybook for creating data + trailer for my file.

Also the Redefine will have a different layout from the main data layout.

Using redefine simplifies my code alot. So it's present!!


No.

There is nothing about a copybook which prevents you having multiple 01s in it.

There is nothing about a copybook or an 01 that prevents you having multiple group definitions which define what will be different records on your output file.

There is nothing about a copybook or an 01 that prevents you using different definitions.

I can't imagine what code you have which allows that REDEFINES to simplify it.

Even if you have simplified it, which I doubt, your code does not work, so it can't really be counted as simplification anyway.

When you get to "I've messed it up, the way I've defined the data prevents me getting the result I want (in a simple way)" then you think again about your data-definitions, you don't just try to hack in something else to make it "work" - until someone comes to change something without the expectation of obfuscation.
Back to top
View user's profile Send private message
Rohit Umarjikar

Global Moderator


Joined: 21 Sep 2010
Posts: 3053
Location: NYC,USA

PostPosted: Thu Feb 13, 2014 2:50 pm
Reply with quote

Why do you need a redefine at first place ? Also WS-Z is already point in to WS-N address so you can simply populate all 03 level variable individually from WS-N and then write it to the file. I hope am getting you right here.
Back to top
View user's profile Send private message
dbzTHEdinosauer

Global Moderator


Joined: 20 Oct 2006
Posts: 6966
Location: porcelain throne

PostPosted: Thu Feb 13, 2014 3:46 pm
Reply with quote

the TS mentioned INITIALIZE.

When you INITIALIZE an area,
numeric values receive zeroes
x type receive spaces.

FILLER items are not modified.

if you move spaces to the area, the FILLER items are populated by spaces.

any further INITIALIZE activity, again does not include the FILLER items.
what ever is in the FILLER item, remains.

INITIALIZE on the area will not populate the ',' character in a FILLER item.
Back to top
View user's profile Send private message
Terry Heinze

JCL Moderator


Joined: 14 Jul 2008
Posts: 1249
Location: Richfield, MN, USA

PostPosted: Thu Feb 13, 2014 10:18 pm
Reply with quote

To populate your output CSV file with a delimeter, you can use something like the following:
Code:
      * | PROCESS:                                                    |
      * |          THIS PROGRAM CREATES A DELIMITED FILE SUITABLE FOR |
      * |      IMPORTING INTO A SPREADSHEET. FOR THE MOST PART, THE   |
      * |      CHANGES NEEDED FOR CUSTOMIZING ARE IDENTIFIED BY THE   |
      * |      INLINE COMMENTS (*>). FEW, IF ANY, CHANGES ARE         |
      * |      REQUIRED IN THE PROCEDURE DIVISION.                    |
.
.
.
       01  WS-FILE001I-RCD.            *> DO NOT CHANGE THIS LINE
      *    REPLACE THE FOLLOWING WITH YOUR  INPUT RECORD LAYOUT
           05 WS-PAYMENT-RECORD.
               10 WS-SSN                       PIC X(09).
               10 WS-LAST-NAME                 PIC X(15).
               10 WS-FIRST-NAME                PIC X(12).
               10 WS-ADDRESS-LINE1             PIC X(40).
               10 WS-ADDRESS-LINE2             PIC X(40).
               10 WS-ADDRESS-LINE3             PIC X(40).
               10 WS-CITY                      PIC X(25).
               10 WS-STATE-CODE                PIC XX.
               10 WS-ZIP-CODE                  PIC X(9).
               10 WS-FINANCE-NO                PIC X(6).
               10 WS-INVOICE-NO                PIC X(11).
.
.
.
       01  WS-FILE002O-RCD.            *> DO NOT CHANGE THIS LINE
      *    REPLACE THE FOLLOWING WITH YOUR OUTPUT RECORD LAYOUT
           05 WS-PAYMENT-RECORD.
               10 WS-SSN                       PIC X(09).
               10                              PIC X.
               10 WS-LAST-NAME                 PIC X(15).
               10                              PIC X.
               10 WS-FIRST-NAME                PIC X(12).
               10                              PIC X.
               10 WS-ADDRESS-LINE1             PIC X(40).
               10                              PIC X.
               10 WS-ADDRESS-LINE2             PIC X(40).
               10                              PIC X.
               10 WS-ADDRESS-LINE3             PIC X(40).
               10                              PIC X.
               10 WS-CITY                      PIC X(25).
               10                              PIC X.
               10 WS-STATE-CODE                PIC XX.
               10                              PIC X.
               10 WS-ZIP-CODE                  PIC X(9).
               10                              PIC X.
               10 WS-FINANCE-NO                PIC X(6).
               10                              PIC X.
               10 WS-INVOICE-NO                PIC X(11).
               10                              PIC X.
.
.
.
       01  LS-PARM-AREA.
      *    THE FOLLOWING LENGTH FIELD IS REQUIRED ONLY IF THIS 01 LEVEL
      *    HAS BEEN DEFINED AS A RESULT OF A PARM PARAMETER IN THE JCL.
           05  LS-PARM-LENGTH          PIC S9(4)             COMP.
           05  LS-PARM-DATA.
               10  LS-DELIMITER        PIC  X.
      /
       PROCEDURE DIVISION              USING LS-PARM-AREA.


           PERFORM A10-INITIATE        THRU A10-X


           PERFORM B10-PROCESS         THRU B10-X
             UNTIL WS-END-OF-FILE001I

           PERFORM Z10-TERMINATE       THRU Z10-X


           MOVE ZERO                   TO RETURN-CODE


           GOBACK
           .
.
.
.
           IF LS-PARM-LENGTH > ZERO
               DISPLAY 'LS-DELIMITER >' LS-DELIMITER '<'
      *  THE FOLLOWING STATEMENTS POPULATE THE OUTPUT RECORD AREA WITH
      *  THE DELIMITER
               MOVE SPACE                      TO WS-FILE002O-RCD
               INSPECT WS-FILE002O-RCD
                   REPLACING ALL SPACE         BY LS-DELIMITER
      D        DISPLAY 'WS-FILE002O-RCD >' WS-FILE002O-RCD '<'
           ELSE
               MOVE 'THIS PROGRAM REQUIRES A DELIMITER'
                                               TO WS-AIM4
               MOVE WS-ABEND-COMP-CODE         TO WS-ABEND-CODE
               PERFORM Z90-ABEND               THRU Z90-X
           END-IF
.
.
.       B10-PROCESS.
           MOVE 'B10-PROCESS'                  TO WS-PAR
           MOVE CORRESPONDING WS-FILE001I-RCD  TO WS-FILE002O-RCD
           PERFORM W10-WRITE-FILE002O          THRU W10-X
           PERFORM R10-READ-FILE001I           THRU R10-X
           .
       B10-X.
           EXIT
           .

If you want headers and/or trailers, you'd need to add code for that.
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

 


Similar Topics
Topic Forum Replies
No new posts Running a Job with the Default User ID JCL & VSAM 2
No new posts Change Default Scroll Setting TSO/ISPF 1
No new posts Need to add field to copybook, proble... COBOL Programming 14
No new posts File transfer from host with filler f... TSO/ISPF 15
No new posts Define default volume for DSN storage... JCL & VSAM 8
Search our Forums:

Back to Top