Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations gkittelson on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

COBOL - Output Tab Delimited Files

Status
Not open for further replies.

taoyr2000

Programmer
Oct 15, 2003
2
US
I'm looking for help in creating a COBOL program that will produce "TAB" delimited output files for eventual use in various PC programs.

Thanks in advance

Tim

 
What platform are you intending to run the Cobol program on, and what version of Cobol are you intending to use?

Marc
 
We're using MicroFocus COBOL 4.1 on a Unix platform.
 
Tim,

Try this: get hold of an ascii table ( and retrieve the ascii code for (vertical) TAB (11).
Code:
MOVE 11 TO ws-tab-num.

where:
01 ws-tab-group.
   05 ws-ascii-num   PIC 9(4) COMP.
   05 ws-ascii-red REDEFINES ws-ascii-num.
   05 ws-ascii-left  PIC X.
   05 ws-ascii-right PIC X.

Now, 
MOVE ws-ascii-right TO <where you want to insert a TAB>
That's it.

Dimandja
 
Actually, tab is ascii 9, not 11. Here is a portion of one program I wrote to produce tab-delimited output (I am unable to post the whole program).
[tt]
Identification Division.
Program-ID. R065.
Author. James C. Fairfield
Date-Written. 11/13/99
*>
*> Tab delimited output.
*>
Environment Division.
Input-Output Section.
File-Control.

Copy SORTSEL.CPY.

Data Division.
File Section.

SD SORT-FILE.
01 SORT-RECORD.
05 SORT-KEY.
10 SORT-PARM Pic X(02).
10 SORT-SKU Pic 9(05).
10 SORT-STORE Pic 9(02).
05 SORT-STYLE Pic X(10).
05 SORT-DESCRIPTION Pic X(20).
05 SORT-BRAND Pic X(14).
05 SORT-COLOR Pic X(02).
05 SORT-COST Pic S9(5)v99 Comp-5.
05 SORT-RETAIL Pic S9(7)v99 Comp-5.
05 SORT-UNITS Pic S9(5) Comp-5.
05 SORT-UNITS-2 Pic S9(5) Comp-5.
05 SORT-YTD Pic S9(9) Comp-5.
05 SORT-MODEL Pic S9(9) Comp-5.
05 SORT-STOCK-ON-HAND Pic S9(9) Comp-5.

Working-Storage Section.
01 CR1999 Pic X(36) Value 'Copyright 1999 James C. Fairfield '.
01 CR2002 Pic X(36) Value 'Copyright 2002 James C. Fairfield '.

Copy SORTSTAT.CPY.
Copy IO-BLOCK.CPY.

78 PROGRAM-NAME Value 'R065v1'.
78 MSG01 Value &quot;First Store required.&quot;.
78 MSG03 Value &quot;Last Store must be >= First Store.&quot;.
78 MSG04 Value &quot;Last Store required.&quot;.
78 TAB-DELIM Value X'09'.
78 SMALL-DOT Value X'FA'.
78 TWENTY-FIVE-OH-ONE Value X'1800'.

01 PRINT-LINE Pic X(1000).
01 redefines PRINT-LINE.
05 DE-SKU Pic Z9(4).
05 DELIM-1 Pic X(01).
05 DE-BRAND Pic X(14).
05 DELIM-2 Pic X(01).
05 DE-STYLE Pic X(10).
05 DELIM-3 Pic X(01).
05 DE-DESCRIPTION Pic X(20).
05 DELIM-4 Pic X(01).
05 DE-COLOR Pic X(02).
05 DELIM-5 Pic X(01).
05 DE-COST Pic Z(03).99.
05 DELIM-6 Pic X(01).
05 DE-RETAIL Pic Z(04).99.
05 DELIM-7 Pic X(01).
05 DE-TOTAL Pic -(6)9.
05 occurs 99 times.
10 DE-DELIM Pic X(01).
10 DE-UNITS Pic -(6)9.

01 DATE-AREA.
05 DATE-1 Pic 9(06).
05 YEAR-2 Pic 9(02).
01 redefines DATE-AREA.
05 YEAR-1 Pic 9(02).
05 DATE-2 Pic 9(06).

01.
05 PROGRESS-TITLE Pic X(05).
05 ERR-MSG Pic X(38) Value Space.
05 MASTER-COUNT Pic 9(06) Value Zero.
05 SORT-COUNT Pic 9(06) Value Zero.
05 X1 Pic 9(04) Value Zero Comp-5.
05 X2 Pic 9(04) Value Zero Comp-5.
05 X2-MAX Pic 9(04) Value Zero Comp-5.
05 X3 Pic 9(04) Value Zero Comp-5.
05 X4 Pic 9(04) Value Zero Comp-5.
05 P1X Pic 9(04) Value Zero Comp-5.
05 P2X Pic 9(04) Value Zero Comp-5.
05 P3X Pic 9(04) Value Zero Comp-5.
05 P4X Pic 9(04) Value Zero Comp-5.
05 PRM-X Pic 9(04) Value Zero Comp-5.
05 PER-X Pic 9(04) Value Zero Comp-5.
05 SRT-X Pic 9(04) Value Zero Comp-5.
05 STR-X Pic 9(04) Value Zero Comp-5.
05 STORE-CNT Pic 9(04) Value Zero Comp-5.
05 H2-SIZE Pic 9(04) Value Zero Comp-5.
05 FIRST-STORE Pic 9(02).
05 LAST-STORE Pic 9(02).
05 STORE-1 Pic 9(02) Comp-5.
05 STORE-2 Pic 9(02) Comp-5.
05 EOF-FLAG Pic X(01) Value 'N'.
05 PARM-DATA Pic X(15).

01 STORE-TABLE.
05 STORE-FLAG-0 Pic X(01).
05 STORE-FLAG Pic X(01) occurs 99 times.
01 redefines STORE-TABLE.
05 Pic X(01).
05 ST-FLAGS-0 Pic X(09).
05 ST-FLAGS-1 Pic X(10).
05 ST-FLAGS-2 Pic X(10).
05 ST-FLAGS-3 Pic X(10).
05 ST-FLAGS-4 Pic X(10).
05 ST-FLAGS-5 Pic X(10).
05 ST-FLAGS-6 Pic X(10).
05 ST-FLAGS-7 Pic X(10).
05 ST-FLAGS-8 Pic X(10).
05 ST-FLAGS-9 Pic X(10).

01 STORE-TRANSLATE-TABLE.
05 STT Pic 9(02) Comp-5 occurs 99 times.

01 OLD-RECORD.
05 OLD-RECORD-KEY.
10 OLD-PARM Pic X(02).
10 OLD-SKU Pic 9(05).
10 OLD-STORE Pic 9(02).
05 OLD-STYLE Pic X(10).
05 OLD-DESCRIPTION Pic X(20).
05 OLD-BRAND Pic X(14).
05 OLD-COLOR Pic X(02).
05 OLD-COST Pic S9(5)V99 Comp-5.
05 OLD-RETAIL Pic S9(7)V99 Comp-5.

01 WS-PARMS.
05 PERIOD-SELECTION Pic X(01).
88 STOCK-ON-HAND Value &quot;1&quot;.
88 SALES-FOR-WEEK Value &quot;2&quot;.
88 SALES-FOR-MONTH Value &quot;3&quot;.
88 SALES-FOR-YEAR Value &quot;4&quot;.
88 SALES-FOR-WEEK-MONTH Value &quot;5&quot; &quot;6&quot;.
88 SALES-FOR-WEEK-MONTH-SOH Value &quot;6&quot;.
88 ANY-SALES Value &quot;2&quot; Thru &quot;6&quot;.
88 VALID-PERIOD-SELECTION Value &quot;1&quot; Thru &quot;6&quot;.
05 SORT-SELECTION Pic X(01).
88 NO-SUB-TOTALS Value &quot;1&quot;.
88 SORT-BY-BRAND Value &quot;2&quot;.
88 SORT-BY-COLOR Value &quot;3&quot;.
88 VALID-SORT-SELECTION Value &quot;1&quot; &quot;2&quot; &quot;3&quot;.
05 TOTAL-SELECTION Pic X(01).
88 PRINT-ALL-DETAIL Value &quot;1&quot;.
88 PRINT-NON-ZERO-DETAIL Value &quot;2&quot;.
88 VALID-TOTAL-SELECTION Value &quot;1&quot; &quot;2&quot;.

01 PRINT-FLAGS.
05 PRINT-FLAG Pic X(01) occurs 99 times.

01 WS-BUCKETS Comp.
05 WS-UNITS Pic S9(4) occurs 20 times.

01 WS-BUCKETS-2 Comp.
05 WS-UNITS-2 Pic S9(4) occurs 20 times.

01 HEADER-1.
05 Pic X(07) Value PROGRAM-NAME & 'r'.
05 HD-PARMS Pic X(03).
05 HD-DATE Pic X(11).
05 HD-TIME Pic X(06).
05 Pic X(36) Value ' JackRabbit Inventory Control System'.

01 HEADER-2 Pic X(80).

01 H2-SELECTION Pic X(47).

01 HEADER-3.
05 Pic X(03) Value 'SKU'.
05 Pic X(06) Value TAB-DELIM & 'Brand'.
05 Pic X(06) Value TAB-DELIM & 'Style'.
05 Pic X(12) Value TAB-DELIM & 'Description'.
05 Pic X(06) Value TAB-DELIM & 'Color'.
05 Pic X(05) Value TAB-DELIM & 'Cost'.
05 Pic X(07) Value TAB-DELIM & 'Retail'.
05 Pic X(06) Value TAB-DELIM & 'Total'.
05 H3-COL occurs 99 times.
10 H3-DELIM Pic X(01).
10 H3-STORE Pic 9(02).

01 EOR.
05 Pic X(33) Value 'End of Report Master in Count: '.
05 EOR-MC Pic ZZZZ9.

01 PERIOD-TEXT-TABLE.
05 Pic X(30) Value &quot;15Stock on Hand &quot;.
05 Pic X(30) Value &quot;16Sales for Week &quot;.
05 Pic X(30) Value &quot;17Sales for Month &quot;.
05 Pic X(30) Value &quot;16Sales for Year &quot;.
05 Pic X(30) Value &quot;26Sales for Week and Month &quot;.
05 Pic X(30) Value &quot;30Sales for Week & Month & SOH&quot;.
01 redefines PERIOD-TEXT-TABLE.
05 PERIOD-TEXT Pic X(30) occurs 6 times.

01 SORT-TEXT-TABLE.
05 Pic X(07) Value &quot;00 &quot;.
05 Pic X(07) Value &quot;05Brand&quot;.
05 Pic X(07) Value &quot;05Color&quot;.
01 redefines SORT-TEXT-TABLE.
05 SORT-TEXT Pic X(07) occurs 3 times.

01 TEXT-DECODE.
05 TEXT-SIZE Pic 9(02).
05 TEXT-DATA Pic X(28).

01 TOTAL-TITLE-TABLE.
05 Pic X(15) Value 'Stock on Hand '.
05 Pic X(15) Value 'Sales for Week '.
05 Pic X(15) Value 'Sales for Month'.
05 Pic X(15) Value 'Sales for Year '.
05 Pic X(15) Value 'Sales for Week '.
05 Pic X(15) Value 'Sales for Week '.
01 redefines TOTAL-TITLE-TABLE.
05 TOTAL-TITLE Pic X(15) occurs 6 times.

01 Value ' BrandColor'.
05 occurs 3 times.
10 GROUP-TITLE-TEXT Pic X(05).

01 SUM-TABLES.
05 SUM-TABLE occurs 3 times.
10 SUM-UNITS Pic S9(9) Comp-5.
10 STR-UNITS Pic S9(6) Comp-5 occurs 99 times.

01 DESCRIPTION-TABLE.
05 Pic X(20) Value 'Sales for Week'.
05 Pic X(20) Value 'Sales for Month'.
05 Pic X(20) Value 'Stock on Hand'.
01 redefines DESCRIPTION-TABLE.
05 DT-TEXT Pic X(20) occurs 3 times.

Procedure Division.
000-BEGIN.
Accept WS-PARMS from Command-Line
If VALID-PERIOD-SELECTION
and VALID-SORT-SELECTION
and VALID-TOTAL-SELECTION
Perform 100-GET-STORES
Sort SORT-FILE on Ascending Key SORT-KEY
Input Procedure 200-SORT-INPUT
Output Procedure 300-SORT-OUTPUT
End-If
Go to STOP-RUN
.

100-GET-STORES.
. . .

200-SORT-INPUT.
. . .

300-SORT-OUTPUT.
Perform 310-INITIALIZE
Perform 380-RETURN
If EOF-FLAG = 'Y'
Exit Paragraph
End-If
Move 'R065.TXT' to PRINT-LINE
Set X-OPEN-OUTPUT to True
Perform CALL-S190
Perform 320-HEADINGS
Perform Until EOF-FLAG = 'Y'
Move Low-Value to SUM-TABLES
Move SORT-RECORD to OLD-RECORD
Perform Until EOF-FLAG = 'Y' or SORT-SKU not = OLD-SKU
Move SORT-STORE to X3
Move STT(X3) to X3
Add SORT-UNITS to SUM-UNITS(1)
Add SORT-UNITS-2 to SUM-UNITS(2)
Add SORT-STOCK-ON-HAND to SUM-UNITS(3)
If X3 >= 1 and <= 99
Add SORT-UNITS to STR-UNITS(1,X3)
Add SORT-UNITS-2 to STR-UNITS(2,X3)
Add SORT-STOCK-ON-HAND to STR-UNITS(3,X3)
End-If
Perform 380-RETURN
End-Perform
Perform 340-END-STOCK
End-Perform
Move MASTER-COUNT to EOR-MC
Move EOR to PRINT-LINE
Perform CALL-S190
Set X-CLOSE to True
Perform CALL-S190
Display COMPLETION-MSG
Move 15 to WS-TIMER
Call MOVE-CURSOR using HIDE-CURSOR
Perform WAIT-ROUTINE-3
.

310-INITIALIZE.
Move 'N' to EOF-FLAG
Move Zero to SORT-COUNT
Move 1 to X2-MAX
If SALES-FOR-WEEK-MONTH
Move 2 to X2-MAX
End-If
If SALES-FOR-WEEK-MONTH-SOH
Move 3 to X2-MAX
End-If
Move WS-PARMS to HD-PARMS
Perform GET-DATE-AND-TIME
Move WS-SCREEN-DATE to HD-DATE
Move WS-DISPLAY-TIME to HD-TIME
If STORE-CNT = 1
Move PERIOD-TEXT(PER-X) to TEXT-DECODE
Move TEXT-DATA to HEADER-2
Move TEXT-SIZE to H2-SIZE
Move SORT-TEXT (SRT-X) to TEXT-DECODE
If TEXT-SIZE > Zero
Move 'by' to HEADER-2(H2-SIZE:2)
Add 3 to H2-SIZE
Move TEXT-DATA to HEADER-2(H2-SIZE:5)
Add TEXT-SIZE to H2-SIZE
Add 1 to H2-SIZE
End-If
Move 'for Store' to HEADER-2(H2-SIZE:9)
Add 10 to H2-SIZE
Move FIRST-STORE to HEADER-2(H2-SIZE:2)
Add 1 to H2-SIZE
End-If
Move GROUP-TITLE-TEXT(SRT-X) to PROGRESS-TITLE
Move Zero to X2
Move Low-Value to STORE-TRANSLATE-TABLE
Perform Varying X1 from 1 by 1 Until X1 > 99
Move Space to H3-COL (X1)
If STORE-FLAG(X1) = '*'
Add 1 to X2
Move X2 to STT (X1)
Move TAB-DELIM to H3-DELIM(X2)
Move X1 to H3-STORE(X2)
End-If
End-Perform
Move X2 to STORE-CNT
Move 1 to X1
.

320-HEADINGS.
Set X-WRITE to True
Move HEADER-1 to PRINT-LINE
Perform CALL-S190
Move HEADER-2 to PRINT-LINE
Perform CALL-S190
Move TAB-DELIM to PRINT-LINE
Perform CALL-S190
Move HEADER-3 to PRINT-LINE
Perform CALL-S190
Move TAB-DELIM to PRINT-LINE
Perform CALL-S190
.

340-END-STOCK.
If PRINT-NON-ZERO-DETAIL and SUM-UNITS(1) Zero and (X2-MAX < 2 or SUM-UNITS(2) Zero and (X2-MAX < 3 or SUM-UNITS(3) Zero))
Exit Paragraph
End-If
Move Space to PRINT-LINE
Move OLD-SKU to DE-SKU
Move OLD-STYLER to DE-STYLE
Move OLD-DESCRIPTION to DE-DESCRIPTION
Move OLD-COST to DE-COST
Move OLD-RETAIL to DE-RETAIL
Move OLD-BRAND to DE-BRAND
Move OLD-COLOR to DE-COLOR
Perform Varying X2 from 1 by 1 Until X2 > X2-MAX
Move TAB-DELIM to DELIM-1
Move TAB-DELIM to DELIM-2
Move TAB-DELIM to DELIM-3
Move TAB-DELIM to DELIM-4
Move TAB-DELIM to DELIM-5
Move TAB-DELIM to DELIM-6
Move TAB-DELIM to DELIM-7
If X2-MAX > 1 and DE-DESCRIPTION = Space
Move DT-TEXT(X2) to DE-DESCRIPTION
End-If
Move SUM-UNITS(X2) to DE-TOTAL
If STORE-CNT > 1
Perform Varying X1 from 1 by 1
Until X1 > STORE-CNT
Move TAB-DELIM to DE-DELIM(X1)
Move STR-UNITS(X2,X1) to DE-UNITS(X1)
End-Perform
End-If
Set X-WRITE to True
Perform CALL-S190
Move Space to PRINT-LINE
End-Perform
.

380-RETURN.
Perform TEST-FOR-ESCAPE
Return SORT-FILE
If SORT-AT-END
Move 'Y' to EOF-FLAG
Exit Paragraph
End-If
Perform CHECK-SORT
Add 1 to SORT-COUNT
.

CHECK-SORT.
If not SORT-OK
Call 'J900' using SORT-STATUS-AREA
Go to STOP-RUN
End-If
.

TEST-FOR-ESCAPE.
Perform GET-CHAR-IF-ANY
If KEY-ESC
Go to STOP-RUN
End-If
.
CALL-S190.
Move Length of PRINT-LINE to XIO-RECORD-SIZE
Call 'S190' using EXTERNAL-IO-REQUEST-BLOCK PRINT-LINE
If not XIO-OK and not X-CLOSE
Go to STOP-RUN
End-If
.

STOP-RUN.
Call MOVE-CURSOR using TWENTY-FIVE-OH-ONE
Stop Run
.

Copy SCR-IO-P.CPY.
[/tt]
 
Actually, tab is ascii 9, not 11. Here is a portion of one program I wrote to produce tab-delimited output (I am unable to post the whole program).
[tt]
Identification Division.
Program-ID. R065.
Author. James C. Fairfield
Date-Written. 11/13/99
*>
*> Tab delimited output.
*>
Environment Division.
Input-Output Section.
File-Control.

Copy SORTSEL.CPY.

Data Division.
File Section.

SD SORT-FILE.
01 SORT-RECORD.
05 SORT-KEY.
10 SORT-PARM Pic X(02).
10 SORT-SKU Pic 9(05).
10 SORT-STORE Pic 9(02).
05 SORT-STYLE Pic X(10).
05 SORT-DESCRIPTION Pic X(20).
05 SORT-BRAND Pic X(14).
05 SORT-COLOR Pic X(02).
05 SORT-COST Pic S9(5)v99 Comp-5.
05 SORT-RETAIL Pic S9(7)v99 Comp-5.
05 SORT-UNITS Pic S9(5) Comp-5.
05 SORT-UNITS-2 Pic S9(5) Comp-5.
05 SORT-YTD Pic S9(9) Comp-5.
05 SORT-MODEL Pic S9(9) Comp-5.
05 SORT-STOCK-ON-HAND Pic S9(9) Comp-5.

Working-Storage Section.
01 CR1999 Pic X(36) Value 'Copyright 1999 James C. Fairfield '.
01 CR2002 Pic X(36) Value 'Copyright 2002 James C. Fairfield '.

78 PROGRAM-NAME Value 'R065v1'.
78 TAB-DELIM Value X'09'.

01 PRINT-LINE Pic X(1000).
01 redefines PRINT-LINE.
05 DE-SKU Pic Z9(4).
05 DELIM-1 Pic X(01).
05 DE-BRAND Pic X(14).
05 DELIM-2 Pic X(01).
05 DE-STYLE Pic X(10).
05 DELIM-3 Pic X(01).
05 DE-DESCRIPTION Pic X(20).
05 DELIM-4 Pic X(01).
05 DE-COLOR Pic X(02).
05 DELIM-5 Pic X(01).
05 DE-COST Pic Z(03).99.
05 DELIM-6 Pic X(01).
05 DE-RETAIL Pic Z(04).99.
05 DELIM-7 Pic X(01).
05 DE-TOTAL Pic -(6)9.
05 occurs 99 times.
10 DE-DELIM Pic X(01).
10 DE-UNITS Pic -(6)9.

01 OLD-RECORD.
05 OLD-RECORD-KEY.
10 OLD-PARM Pic X(02).
10 OLD-SKU Pic 9(05).
10 OLD-STORE Pic 9(02).
05 OLD-STYLE Pic X(10).
05 OLD-DESCRIPTION Pic X(20).
05 OLD-BRAND Pic X(14).
05 OLD-COLOR Pic X(02).
05 OLD-COST Pic S9(5)V99 Comp-5.
05 OLD-RETAIL Pic S9(7)V99 Comp-5.

Procedure Division.
000-BEGIN.
Perform 100-GET-STORES
Sort SORT-FILE on Ascending Key SORT-KEY
Input Procedure 200-SORT-INPUT
Output Procedure 300-SORT-OUTPUT
Go to STOP-RUN
.

100-GET-STORES.
. . .

200-SORT-INPUT.
. . .

300-SORT-OUTPUT.
Perform 310-INITIALIZE
Perform 380-RETURN
If EOF-FLAG = 'Y'
Exit Paragraph
End-If
Move 'R065.TXT' to PRINT-LINE
Set X-OPEN-OUTPUT to True
Perform CALL-S190
Perform 320-HEADINGS
Perform Until EOF-FLAG = 'Y'
Move Low-Value to SUM-TABLES
Move SORT-RECORD to OLD-RECORD
Perform Until EOF-FLAG = 'Y' or SORT-SKU not = OLD-SKU
Move SORT-STORE to X3
Move STT(X3) to X3
Add SORT-UNITS to SUM-UNITS(1)
Add SORT-UNITS-2 to SUM-UNITS(2)
Add SORT-STOCK-ON-HAND to SUM-UNITS(3)
If X3 >= 1 and <= 99
Add SORT-UNITS to STR-UNITS(1,X3)
Add SORT-UNITS-2 to STR-UNITS(2,X3)
Add SORT-STOCK-ON-HAND to STR-UNITS(3,X3)
End-If
Perform 380-RETURN
End-Perform
Perform 340-END-STOCK
End-Perform
Move MASTER-COUNT to EOR-MC
Move EOR to PRINT-LINE
Perform CALL-S190
Set X-CLOSE to True
Perform CALL-S190
Display COMPLETION-MSG
Move 15 to WS-TIMER
Call MOVE-CURSOR using HIDE-CURSOR
Perform WAIT-ROUTINE-3
.

310-INITIALIZE.
Move 'N' to EOF-FLAG
Move Zero to SORT-COUNT
Move 1 to X2-MAX
If SALES-FOR-WEEK-MONTH
Move 2 to X2-MAX
End-If
If SALES-FOR-WEEK-MONTH-SOH
Move 3 to X2-MAX
End-If
Move WS-PARMS to HD-PARMS
Perform GET-DATE-AND-TIME
Move WS-SCREEN-DATE to HD-DATE
Move WS-DISPLAY-TIME to HD-TIME
If STORE-CNT = 1
Move PERIOD-TEXT(PER-X) to TEXT-DECODE
Move TEXT-DATA to HEADER-2
Move TEXT-SIZE to H2-SIZE
Move SORT-TEXT (SRT-X) to TEXT-DECODE
If TEXT-SIZE > Zero
Move 'by' to HEADER-2(H2-SIZE:2)
Add 3 to H2-SIZE
Move TEXT-DATA to HEADER-2(H2-SIZE:5)
Add TEXT-SIZE to H2-SIZE
Add 1 to H2-SIZE
End-If
Move 'for Store' to HEADER-2(H2-SIZE:9)
Add 10 to H2-SIZE
Move FIRST-STORE to HEADER-2(H2-SIZE:2)
Add 1 to H2-SIZE
End-If
Move GROUP-TITLE-TEXT(SRT-X) to PROGRESS-TITLE
Move Zero to X2
Move Low-Value to STORE-TRANSLATE-TABLE
Perform Varying X1 from 1 by 1 Until X1 > 99
Move Space to H3-COL (X1)
If STORE-FLAG(X1) = '*'
Add 1 to X2
Move X2 to STT (X1)
Move TAB-DELIM to H3-DELIM(X2)
Move X1 to H3-STORE(X2)
End-If
End-Perform
Move X2 to STORE-CNT
Move 1 to X1
.

320-HEADINGS.
Set X-WRITE to True
Move HEADER-1 to PRINT-LINE
Perform CALL-S190
Move HEADER-2 to PRINT-LINE
Perform CALL-S190
Move TAB-DELIM to PRINT-LINE
Perform CALL-S190
Move HEADER-3 to PRINT-LINE
Perform CALL-S190
Move TAB-DELIM to PRINT-LINE
Perform CALL-S190
.

340-END-STOCK.
If PRINT-NON-ZERO-DETAIL and SUM-UNITS(1) Zero and (X2-MAX < 2 or SUM-UNITS(2) Zero and (X2-MAX < 3 or SUM-UNITS(3) Zero))
Exit Paragraph
End-If
Move Space to PRINT-LINE
Move OLD-SKU to DE-SKU
Move OLD-STYLER to DE-STYLE
Move OLD-DESCRIPTION to DE-DESCRIPTION
Move OLD-COST to DE-COST
Move OLD-RETAIL to DE-RETAIL
Move OLD-BRAND to DE-BRAND
Move OLD-COLOR to DE-COLOR
Perform Varying X2 from 1 by 1 Until X2 > X2-MAX
Move TAB-DELIM to DELIM-1
Move TAB-DELIM to DELIM-2
Move TAB-DELIM to DELIM-3
Move TAB-DELIM to DELIM-4
Move TAB-DELIM to DELIM-5
Move TAB-DELIM to DELIM-6
Move TAB-DELIM to DELIM-7
If X2-MAX > 1 and DE-DESCRIPTION = Space
Move DT-TEXT(X2) to DE-DESCRIPTION
End-If
Move SUM-UNITS(X2) to DE-TOTAL
If STORE-CNT > 1
Perform Varying X1 from 1 by 1
Until X1 > STORE-CNT
Move TAB-DELIM to DE-DELIM(X1)
Move STR-UNITS(X2,X1) to DE-UNITS(X1)
End-Perform
End-If
Set X-WRITE to True
Perform CALL-S190
Move Space to PRINT-LINE
End-Perform
.

380-RETURN.
Return SORT-FILE
If SORT-AT-END
Move 'Y' to EOF-FLAG
Exit Paragraph
End-If
.

CALL-S190.
Move Length of PRINT-LINE to XIO-RECORD-SIZE
Call 'S190' using EXTERNAL-IO-REQUEST-BLOCK PRINT-LINE
If not XIO-OK and not X-CLOSE
Go to STOP-RUN
End-If
.

STOP-RUN.
Call MOVE-CURSOR using TWENTY-FIVE-OH-ONE
Stop Run
.
[/tt]
 
Actually, tab is ascii 9, not 11. I usually code it as follows:

78 TAB-DELIM VALUE X'09'.

I have written many programs to produce tab-delimited as well as comma separated values output. I have been unable to post the code here, but if you send a request to jamescfairfield@yahoo.com, I can send it to to .
 
I see that it got posted even though I got a message saying it wasn't.
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top