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 SkipVought on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

After Advancing Constant

Status
Not open for further replies.

SMAlvarez

Programmer
Dec 4, 2005
27
0
0
US
Ok I'm trying to add the after advancing constant in the write command to double space my output. Here are all the write commands in the code:

Code:
WRITE PRINT-LINE FROM OUT-REC AFTER 2

WRITE PRINT-LINE FROM HEADING1 AFTER TOP-PAGE.
WRITE PRINT-LINE FROM HEADING2 AFTER 2.

how do I add double spacing to my output?

I tried the following:

Code:
WRITE PRINT-LINE FROM OUT-REC AFTER ADVANCING 2.

WRITE PRINT-LINE FROM HEADING1 AFTER ADVANCING TOP-PAGE.
WRITE PRINT-LINE FROM HEADING2 AFTER ADCANCING 2.

Didn't doublespace anything? Why?

My full source is:

Code:
IDENTIFICATION DIVISION.
PROGRAM-ID.   PROJECT1.
AUTHOR. STEVEN.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SOURCE-COMPUTER.    IBM-370.
OBJECT-COMPUTER.    IBM-370.
SPECIAL-NAMES. C01 IS TOP-PAGE.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
    SELECT SONG-FILE ASSIGN TO UT-S-SYSIN.
    SELECT PRINT-FILE ASSIGN TO UT-S-SYSOUT.
DATA DIVISION.
FILE SECTION.
FD  SONG-FILE
    LABEL RECORDS ARE OMITTED
    RECORD CONTAINS 80 CHARACTERS
    DATA RECORD IS SONG-IN.
01  SONG-IN.
    05 SONG-TITLE      PIC X(35).
    05 SONG-ARTIST     PIC X(30).
    05 SONG-LABEL      PIC X(11).
    05 SONG-YEAR       PIC X(4).
FD  PRINT-FILE
     LABEL RECORDS ARE OMITTED
     RECORD CONTAINS 133 CHARACTERS
     DATA RECORD IS PRINT-LINE.
 01  PRINT-LINE PIC X(133).
 WORKING-STORAGE SECTION.
 01  EOF        PIC 9     VALUE ZERO.
 01  LINE-COUNT PIC 9(2)  VALUE ZERO.
 01  PAGE-NUM   PIC 9(2)  VALUE 1.
*
01  HEADING1.
    02 FILLER      PIC X(8)  VALUE SPACES.
    02 FILLER      PIC X(35) VALUE 'TITLE'.
    02 FILLER      PIC X(5)  VALUE SPACES.
    02 FILLER      PIC X(36) VALUE 'ARTIST'.
    02 FILLER      PIC X(5)  VALUE SPACES.
    02 FILLER      PIC X(8)  VALUE 'LABEL'.
    02 FILLER      PIC X(11) VALUE SPACES.
    02 FILLER      PIC X(4)  VALUE 'YEAR'.
    02 FILLER      PIC X(2)  VALUE  SPACES.
    02 FILLER      PIC X(4)  VALUE 'PAGE'.
    02 PG-NUM      PIC 99    VALUE ZEROS.
    02 FILLER      PIC X(16) VALUE SPACES.
*
 01  HEADING2.
      02 FILLER   PIC X(1)   VALUE SPACES.
      02 FILLER   PIC X(133) VALUE ALL '-'.
*
 01  OUT-REC.
      02 FILLER        PIC X(8)    VALUE SPACES.
      02 PRINT-TITLE   PIC X(35)   VALUE SPACES.
      02 FILLER        PIC X(4)    VALUE SPACES.
      02 PRINT-ARTIST  PIC X(36)   VALUE SPACES.
      02 FILLER        PIC X(6)    VALUE SPACES.
      02 PRINT-LABEL   PIC X(15)   VALUE SPACES.
      02 FILLER        PIC X(4)    VALUE SPACES.
      02 PRINT-YEAR    PIC X(4)    VALUE SPACES.
*
 PROCEDURE DIVISION.
 MAINLINE.
     OPEN INPUT SONG-FILE
      OUTPUT PRINT-FILE.
     PERFORM HEADING-RTN.
     READ SONG-FILE
      AT END MOVE 1 TO EOF.
     PERFORM PROCESS-RECORDS
      UNTIL EOF = 1.
*    PERFORM CLOSING-RTM.
     CLOSE SONG-FILE
          PRINT-FILE.
     STOP RUN.
*
 PROCESS-RECORDS.
        MOVE SONG-TITLE TO PRINT-TITLE
        MOVE SONG-ARTIST TO PRINT-ARTIST
        MOVE SONG-LABEL TO PRINT-LABEL
        MOVE SONG-YEAR TO PRINT-YEAR
        MOVE SPACES TO PRINT-LINE
        WRITE PRINT-LINE FROM OUT-REC AFTER 2
        ADD 1 TO LINE-COUNT.
*
*
     READ SONG-FILE
        AT END MOVE 1 TO EOF.
*
 HEADING-RTN.
     MOVE PAGE-NUM TO PG-NUM.
     WRITE PRINT-LINE FROM HEADING1 AFTER TOP-PAGE.
     WRITE PRINT-LINE FROM HEADING2 AFTER 2.
     ADD 1 TO PAGE-NUM.
     MOVE ZERO TO LINE-COUNT.
*CLOSING-RTM. WRITE PRINT-LINE FROM HEADING2.
 
your AFTER 2 on the heading is printing the record with a line spaced between the first heading and the second, which is what the AFTER 2 means. If you need more lines interval just increase the after 2 to be after 3 or after 4.


Now if you are looking at the output file on a SPOOLER instead of a printed copy, then it MAY seem to you that there is no line interval. That is common with many SPOOLER managers like the AS400 or even some Mainframe ones.



Regards

Frederico Fonseca
SysSoft Integrated Ltd
 
I believe we telnet into a IBM-370 or 360.

Ok so how would I double space all my output?
 
If I type:

Code:
WRITE PRINT-LINE FROM OUT-REC AFTER ADVANCING.

It still doesnt give me the space that I needed. Why?
 
you DONT HAVE TO FIX IT.

Have you printed it in plain paper?

If not, and if you just want to see it on SCREEN with double spacing, THEN you need to create a different type of file, NOT A PRINT FILE, but a normal sequential file, and instead of doing a write AFTER, you do a WRITE of a record with SPACES.

Regards

Frederico Fonseca
SysSoft Integrated Ltd
 
SMAlvarez,
Is the file on the IBM370 defined as 133 FBA?

Also, in your program it is best to define the first character as a filler or CARRIAGE-CONTROL and move your data to the remaining 132 characters.

Marc
 
Just put a field in working storage and use that field for the number of lines to advance.

01 WS-LINES PIC 9(01) VALUE 2.

However this job runs allow the user to change the value of ws-lines depending on how they want to run it, or leave it set at 2 if that is what you will always want. Nothing always stays the same.

WRITE PRINT-LINE FROM OUT-REC AFTER WS-LINES.
ADD WS-LINES TO LINE-COUNT.

Whatever you have WS-LINES set to, it will work.


If you do not like my post feel free to point out your opinion or my errors.
 
BTW, the C01 special name is not syntactically compatible with AFTER (or BEFORE) ASVANCING. It is use only for AFTER POSITIIONING. AFTER ADVAINCING and AFTER POSITIONING, if ther is no BEFORE syntax for the same file, generate ASA control characters. On the IBM 360, 370, etc, BEFORE [ADVANCING] generates machinge control characters. which are very different.
 
ceh4702,

If the file is not defined to the operating system as FBA, it will not know that the first byte contains a print control character, so your fix will produce the same result as the original problem.

Marc
 
Unless you override it in the JCL, COBOL will assign the "A" to the RECFMT, as long as you use the AFTER syntax.
 
This is how I assign my files:

SELECT PRINT-FILE ASSIGN SYS007-UR-1403-S.
SELECT PRINT-FILE2 ASSIGN SYS008-UR-1403-S.

I never pay much attention to it.

I think the printfiles are already set up in our system because we use the same printfiles in all the programs.

Then we use a list statement in the JCL

* $$ LST FNO=2PTN,DISP=L,PRI=3

Every program I have ever seen uses after advancing or after.

However, you have to print this out to actually see it. In the List Que you may not be able to see all the blank lines.

If you do not like my post feel free to point out your opinion or my errors.
 
We use CO1 all the time also. It is hardware specific for the printer.

If you do not like my post feel free to point out your opinion or my errors.
 
ROFL!!! All I had to do was change AFTER ADVANCING 2 to AFTER ADVANCING 4. heh.
 
You got the results that way becouse there is no ASA code for "AFTER 4", so the compiler had to generate a blank line with "AFTER 1" then the requested line with "AFTER 3".

BTW, the C01 is an IBM extension to explicitly code an ASA character that means "AFTER (skipping to) C(hannel) 01" It is not hardware specific at all.

I used to have all the ASA characters memorized. but it has been too many years sice I used them. There are 16 of them, representing AFTER 0 thru AFTER 3, and Channel 01 thru Channel 12. It is only tradition that Channel 01 represents Top of Page.
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top