Reading record levels from a file using CFF

Post questions here relative to DataStage Enterprise/PX Edition for such areas as Parallel job design, Parallel datasets, BuildOps, Wrappers, etc.

Moderators: chulett, rschirm, roy

Post Reply
suryadev
Premium Member
Premium Member
Posts: 211
Joined: Sun Jul 11, 2010 7:39 pm

Reading record levels from a file using CFF

Post by suryadev »

Hello,

I have a file which needs to be read using CFF. The file is divided into segments and each segment has columns seperately.
A1 B1 C1 D1 E1
A1 has 4 columns, B1 has 3 columns, C1 has 5 columns, D1 has 4 columns, E1 has 5 columns

for example C1 had 5 columns but there are 5 records for 5 columns seperately and I assume they are children for the parent C1. There is no sepecific number of records for each segment. How do I read them using the CFF with out disturbing the data?

Tried to import the metadata but that looks confusing,Please suggest if there is any other option to read this kind of file
Thanks,
Surya
chulett
Charter Member
Charter Member
Posts: 43085
Joined: Tue Nov 12, 2002 4:34 pm
Location: Denver, CO

Post by chulett »

I'm assuming this is a COBOL file... if so can you post the FD or whatever you have for the metadata?
-craig

"You can never have too many knives" -- Logan Nine Fingers
suryadev
Premium Member
Premium Member
Posts: 211
Joined: Sun Jul 11, 2010 7:39 pm

Post by suryadev »

Code: Select all

01  AMCBCB02-CB-HEADER-REC.
     05  AMCBCB02-CB-REC-ID          PIC X(6)
                                              VALUE 'HEADER'.
     05  AMCBCB02-CB-CYCLE-NUM       PIC X(2).
*      INNOVIS PROGRAM IDENTIFIER
     05  AMCBCB02-RP-CB-CTL-NUM-1    PIC X(10).
*      ABC PROGRAM IDENTIFIER
     05  AMCBCB02-RP-CB-CTL-NUM-2    PIC X(10).
*      DEF PROGRAM IDENTIFIER
     05  AMCBCB02-RP-CB-CTL-NUM-3    PIC X(5).
*      GHI PROGRAM IDENTIFIER
     05  AMCBCB02-RP-CB-CTL-NUM-4    PIC X(10).
     05  AMCBCB02-CB-ACTY-DATE       PIC 9(8).
     05  AMCBCB02-CB-CREATE-DATE     PIC 9(8).
     05  AMCBCB02-CB-PROGRAM-DATE    PIC 9(8).
     05  AMCBCB02-CB-REV-DATE        PIC 9(8).
     05  AMCBCB02-CB-REPORTER-NAME   PIC X(40).
     05  AMCBCB02-CB-REPORTER-ADDR   PIC X(96).
     05  AMCBCB02-CB-REPORTER-TEL    PIC 9(10).
     05  AMCBCB02-CB-VENDOR-NAME     PIC X(40).
     05  AMCBCB02-CB-SOFTWARE-VRSN   PIC X(5).
     05  FILLER                      PIC X(96).

 01  AMCBCB02-CB-366-BASE-REC.
     05  AMCBCB02-CB-PROCESS-IND       PIC 9(1).
     05  AMCBCB02-CB-TIME-STAMP        PIC S9(15) COMP-3.
*** MONTHLY REPORTING VALUE IS 0
*** SPECIAL REPLACEMENT FILES SHOULD HAVE A 1
     05  AMCBCB02-CB-CORRECTION-IND    PIC 9(1).
     05  AMCBCB02-CB-IDENT-IND         PIC X(20).
     05  AMCBCB02-CB-CYCLE-ID          PIC X(2).
     05  AMCBCB02-RT-ACCT-NUM          PIC X(30).
     05  AMCBCB02-CB-PORTFOLIO-TYPE    PIC X.
     05  AMCBCB02-RT-CB-TYPE           PIC X(2).
     05  AMCBCB02-CB-DATE-OPEN         PIC S9(9) COMP-3.
     05  AMCBCB02-CB-CURR-CM-AMT       PIC S9(9) COMP-3.
     05  AMCBCB02-CB-ORIG-AMT          PIC S9(9) COMP-3.
     05  AMCBCB02-CB-ORIG-TERM         PIC X(3).
     05  AMCBCB02-CB-FREQ              PIC X(1).
     05  AMCBCB02-CB-MO-PMT-AMT        PIC S9(9) COMP-3.
     05  AMCBCB02-CB-AMT-PD-MTD        PIC S9(9) COMP-3.
     05  AMCBCB02-RT-CB-STAT           PIC X(2).
     05  AMCBCB02-CB-PMT-RATING        PIC X(1).
     05  AMCBCB02-CB-PMT-HIST          PIC X(24).
     05  AMCBCB02-RT-CB-COMMENT-CD     PIC XX.
     05  AMCBCB02-RT-CB-COMPL-CD       PIC XX.
     05  AMCBCB02-RT-CURR-BAL          PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-AMT-PDUE      PIC S9(9) COMP-3.
     05  AMCBCB02-CB-CURR-COFF         PIC S9(9) COMP-3.
     05  AMCBCB02-CB-ACCT-INFO-DATE    PIC S9(9) COMP-3.
     05  AMCBCB02-CB-FIRST-DQ-DATE     PIC S9(9) COMP-3.
     05  AMCBCB02-CB-CLOSE-DATE        PIC S9(9) COMP-3.
     05  AMCBCB02-CB-LST-PMT-DATE      PIC S9(9) COMP-3.
     05  FILLER                        PIC X(17).
     05  AMCBCB02-CB-TRAN-TYPE         PIC X(1).
     05  AMCBCB02-CB-SURNAME           PIC X(25).
     05  AMCBCB02-CB-FIRST-NAME        PIC X(20).
     05  AMCBCB02-CB-MID-NAME          PIC X(20).
     05  AMCBCB02-CB-GENERATION        PIC X(1).
     05  AMCBCB02-CB-SSN-CUST          PIC S9(9) COMP-3.
     05  AMCBCB02-CB-DOB               PIC S9(9) COMP-3.
     05  AMCBCB02-CB-PHONE-NUM         PIC S9(11) COMP-3.
     05  AMCBCB02-CB-ECOA-CODE         PIC X(1).
     05  AMCBCB02-CB-CII               PIC X(2).
     05  AMCBCB02-CB-COUNTRY           PIC X(2).
     05  AMCBCB02-CB-ADDRESS.
         10  AMCBCB02-CB-ADDR1         PIC X(32).
         10  AMCBCB02-CB-ADDR2         PIC X(32).
         10  AMCBCB02-CB-CITY          PIC X(20).
         10  AMCBCB02-CB-STATE         PIC X(2).
         10  AMCBCB02-CB-ZIP           PIC X(9).
     05  AMCBCB02-CB-ADDR-IND          PIC X.
     05  AMCBCB02-CB-RES-CD            PIC X.
     05  AMCBCB02-CB-SEG-AREA-BYTE OCCURS 2136.
         10  FILLER                    PIC X(1).

**** ASSOCIATED CONSUMER - SAME ADDRESS - 100 BYTES
**** MULTIPLE OCCURANCES POSSIBLE.
 01  AMCBCB02-CB-J1-SEG.
     05  AMCBCB02-J1-SEG-FIELDS OCCURS 10 TIMES.
         10  AMCBCB02-J1-ID                   PIC X(2)
                                           VALUE 'J1'.
         10  AMCBCB02-J1-TRAN-TYPE            PIC X(1).
         10  AMCBCB02-J1-SURNAME              PIC X(25).
         10  AMCBCB02-J1-FIRST-NAME           PIC X(20).
         10  AMCBCB02-J1-MID-NAME             PIC X(20).
         10  AMCBCB02-J1-GENERATION           PIC X(1).
         10  AMCBCB02-J1-SSN-CUST             PIC 9(9).
         10  AMCBCB02-J1-DOB                  PIC 9(8).
         10  AMCBCB02-J1-PHONE-NUM            PIC 9(10).
         10  AMCBCB02-J1-ECOA-CODE            PIC X(1).
         10  AMCBCB02-J1-CII                  PIC X(2).
         10  FILLER                           PIC X(1).

**** ASSOCIATED CONSUMER - DIFFERENT ADDRESS - 200 BYTES
**** MULTIPLE OCCURANCES POSSIBLE.
**** (SAME ADDRESS AS PRIMARY BASE IS OK FOR THIS SEGMENT)
 01  AMCBCB02-CB-J2-SEG.
     05  AMCBCB02-J2-SEG-FIELDS OCCURS 10 TIMES.
         10  AMCBCB02-J2-ID                   PIC X(2)
                                            VALUE 'J2'.
         10  AMCBCB02-J2-TRAN-TYPE            PIC X(1).
         10  AMCBCB02-J2-SURNAME              PIC X(25).
         10  AMCBCB02-J2-FIRST-NAME           PIC X(20).
         10  AMCBCB02-J2-MID-NAME             PIC X(20).
         10  AMCBCB02-J2-GENERATION           PIC X(1).
         10  AMCBCB02-J2-SSN-CUST             PIC 9(9).
         10  AMCBCB02-J2-DOB                  PIC 9(8).
         10  AMCBCB02-J2-PHONE-NUM            PIC 9(10).
         10  AMCBCB02-J2-ECOA-CODE            PIC X(1).
         10  AMCBCB02-J2-CII                  PIC X(2).
         10  AMCBCB02-J2-COUNTRY              PIC X(2).
         10  AMCBCB02-J2-ADDRESS.
             15  AMCBCB02-J2-ADDR1            PIC X(32).
             15  AMCBCB02-J2-ADDR2            PIC X(32).
             15  AMCBCB02-J2-CITY             PIC X(20).
             15  AMCBCB02-J2-STATE            PIC X(2).
             15  AMCBCB02-J2-ZIP              PIC X(9).
         10  AMCBCB02-J2-ADDR-IND             PIC X.
         10  AMCBCB02-J2-RES-CD               PIC X.
         10  FILLER                           PIC X(2).

**** ORIGINAL CREDITOR NAME - 34 BYTES
 01  AMCBCB02-CB-K1-SEG.
     05  AMCBCB02-K1-ID                   PIC X(2)
                                             VALUE 'K1'.
     05  AMCBCB02-K1-ORIG-CREDITOR        PIC X(30).
     05  AMCBCB02-K1-CLASSIFICATION       PIC 9(2).

**** PURCHASED PORTFOLIO/SOLD TO - 34 BYTES
 01  AMCBCB02-CB-K2-SEG.
     05  AMCBCB02-K2-ID                   PIC X(2)
                                             VALUE 'K2'.
     05  AMCBCB02-K2-PORTFOLIO-IND        PIC 9(1).
     05  AMCBCB02-K2-SOLD-TO-NAME         PIC X(30).
     05  FILLER                           PIC X(1).

**** MORTGAGE INFORMATION - 40 BYTES
 01  AMCBCB02-CB-K3-SEG.
     05  AMCBCB02-K3-ID                   PIC X(2)
                                             VALUE 'K3'.
     05  AMCBCB02-K3-AGENCY-ID            PIC 9(2).
     05  AMCBCB02-K3-ACCT-NUM             PIC X(18).
     05  AMCBCB02-K3-MORTGAGE-ID          PIC X(18).

**** SPECIALIZED PAYMENT INFORMATION - 30 BYTES
 01  AMCBCB02-CB-K4-SEG.
     05  AMCBCB02-K4-ID                   PIC X(2)
                                             VALUE 'K4'.
     05  AMCBCB02-K4-SPECIAL-PMT-IND      PIC 9(2).
     05  AMCBCB02-K4-DEFERRED-PMT-DATE    PIC 9(8).
     05  AMCBCB02-K4-PMT-DUE-DATE         PIC 9(8).
     05  AMCBCB02-K4-PMT-AMT              PIC 9(9).
     05  FILLER                           PIC X(1).

**** ACCOUNT NUMBER/IDENTIFICATION NUMBER CHANGE  - 54 BYTES
 01  AMCBCB02-CB-L1-SEG.
     05  AMCBCB02-L1-ID                   PIC X(2)
                                             VALUE 'L1'.
     05  AMCBCB02-L1-CHANGE-IND           PIC 9(1).
     05  AMCBCB02-L1-NEW-ACCT-NUM         PIC X(30).
     05  AMCBCB02-L1-NEW-ID-NUM           PIC X(20).
     05  FILLER                           PIC X(1).

**** EMPLOYMENT 146 BYTES
 01  AMCBCB02-CB-N1-SEG.
     05  AMCBCB02-N1-ID                   PIC X(2)
                                             VALUE 'N1'.
     05  AMCBCB02-N1-EMPLOYER-NAME        PIC X(30).
     05  AMCBCB02-N1-ADDR1                PIC X(32).
     05  AMCBCB02-N1-ADDR2                PIC X(32).
     05  AMCBCB02-N1-CITY                 PIC X(20).
     05  AMCBCB02-N1-STATE                PIC X(2).
     05  AMCBCB02-N1-ZIP                  PIC X(9).
     05  AMCBCB02-N1-OCCUPATION           PIC X(18).
     05  FILLER                           PIC X(1).

**** TRAILER RECORD
 01  AMCBCB02-CB-TRAILER-REC.
*    05  AMCBCB02-CB-TRLR-LNGTH        PIC 9(4).
     05  AMCBCB02-CB-TRLR-ID           PIC X(7)
                                    VALUE 'TRAILER'.
     05  AMCBCB02-CB-TOT-BASE          PIC S9(9) COMP-3.
     05  FILLER                        PIC X(5) VALUE SPACES.
     05  AMCBCB02-CB-TOT-DF            PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-J1            PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-J2            PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-BLK-CNT       PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-DA            PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-05            PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-11            PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-13            PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-61            PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-62            PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-63            PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-64            PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-65            PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-71            PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-78            PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-80            PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-82            PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-83            PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-84            PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-88            PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-89            PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-93            PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-94            PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-95            PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-96            PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-97            PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-ECOA-Z        PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-N1            PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-K1            PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-K2            PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-K3            PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-K4            PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-L1            PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-SSN-ALL       PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-SSN-BASE      PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-SSN-J1        PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-SSN-J2        PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-DOB-ALL       PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-DOB-BASE      PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-DOB-J1        PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-DOB-J2        PIC S9(9) COMP-3.
     05  AMCBCB02-CB-TOT-PHONE-NUM     PIC S9(9) COMP-3.
     05  FILLER                        PIC X(135) VALUE SPACES.
Thanks,
Surya
FranklinE
Premium Member
Premium Member
Posts: 739
Joined: Tue Nov 25, 2008 2:19 pm
Location: Malvern, PA

Post by FranklinE »

Surya,

The FD you provided defines a variable-length record format. I would hesitate to read this file as-is with any approach DataStage provides.

As a guess -- not knowing any other details about your requirements -- I would first split the different records into separate files, then import each 01-level record definition as a distinct table definition and read the file with it.

Putting all of those records into one file is bad design. Best practice is to keep every record the same length, identify record types with a consistent first column (two positions is standard), and construct the FD with each record-type layout defined under a "redefines" of the first one. CFF works best with that.
Franklin Evans
"Shared pain is lessened, shared joy increased. Thus do we refute entropy." -- Spider Robinson

Using mainframe data FAQ: viewtopic.php?t=143596 Using CFF FAQ: viewtopic.php?t=157872
suryadev
Premium Member
Premium Member
Posts: 211
Joined: Sun Jul 11, 2010 7:39 pm

Post by suryadev »

Thank you Franklin
Following the below approach
Best practice is to keep every record the same length, identify record types with a consistent first column (two positions is standard), and construct the FD with each record-type layout defined under a "redefines" of the first one.

I can see the positions for each column. Lets say there are 50 columns and these 50 columns are divided into 5 segments(A,B,C,D,E)(10 columns each segment).
The file when looked at would be easy if the data comes like ABCDE but what I see is ABBBCDE for one record and ABBCDE for other record. How can I construct the FD for this kind of layout. What I mean to say is the FD should read only ABCDE and it should read if the segments are repeated like B three times as the number is not consistent I cannot give positions for 3 B's

Please suggest how can I achieve this? thanks again!
Thanks,
Surya
FranklinE
Premium Member
Premium Member
Posts: 739
Joined: Tue Nov 25, 2008 2:19 pm
Location: Malvern, PA

Post by FranklinE »

Surya, glad to help.

Your question goes back to the initial design of the record. You have a hierarchy with variable numbers of segments, something that would have been covered if the intial design were as I described. The following is generic, so I'll leave out the PIC clauses.

Code: Select all

01 BASE-RECORD.
03 HEADER-RECORD.
05 RECORD-TYPE-IND. (01 for header, etc.)
05 HEADER-FIELD-1.
05 HEADER-FIELD-2.
...
05 FILLER (extend to consistent length).

03 DETAIL-RECORD-1 REDEFINES HEADER-RECORD.
05 RECORD-TYPE-IND. (02 etc.)
05 DETAIL-FIELD-1.
05 DETAIL-FIELD-2.
...
05 FILLER.

Each DETAIL type would have the segment coding. If there are a varying number of instances, the design would have to settle on a maximum each segment could have, and code it accordingly.

03 DETAIL-RECORD-2 REDEFINES HEADER-RECORD.
05 DTL-SEGMENT-A OCCURS 10 TIMES. (number reflects maximum)
10 DTL-SEG-A-FIELD-1.
10 DTL-SEG-A-FIELD-2.
10 DTL-SEG-A-FIELD-3.
...
10 DTL-SEG-A-FIELD-LAST.
05 FILLER.
You'd have as many REDEFINES as you have segments, each one with its unique coding but all conforming to the consistent record length using FILLER. I've left out other important details, but I hope you get the picture.

This all assumes that your mainframe developers are willing to redesign your source file. I also assume that is not likely. Your alternative is to parse the file in its current state and do a sort of pre-extract to get the segments lined up with how you need to process them. The difficult part will be identifying each record type. Your FD will make that an obstacle. Unless there is a consistent first column, always the same length, you are not going to find that easy to do in DataStage.
Franklin Evans
"Shared pain is lessened, shared joy increased. Thus do we refute entropy." -- Spider Robinson

Using mainframe data FAQ: viewtopic.php?t=143596 Using CFF FAQ: viewtopic.php?t=157872
suryadev
Premium Member
Premium Member
Posts: 211
Joined: Sun Jul 11, 2010 7:39 pm

Post by suryadev »

I could read the file properly but the segments are falling in others positions.

I took the max of occurrences for B segment as only it has the occurrences and gave occurs 2 times giving it as a group but it did not read the 2 records from B segment and I gave 1 as occurrence it worked. Below is how I gave
02 A1
02 A2
02 A3
02 A4 (for segment A there are no occurrences so no group)
02 B GROUP occurs 1
03 B1
03 B2
03 B3
02 C1
02 C2
02 C3
02 C4 ( for segment c also there are no occurrences so no group)

The data looks good when given in above format but where ever there is no B segment for some records C segment is falling on B positions
like A1A2A3A4C1C2C3C4 and other one is let say there are 2 B segments the second one comes next to first B segment which is C' segment
like A1A2A3A4B1B2B3B1B2B3. Any changes I need to do so that the occurrences read accordingly. thanks again!
Thanks,
Surya
Post Reply