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

CA-Relia Sequential file with CR/LF and LF

Status
Not open for further replies.

tgreer

Programmer
Oct 4, 2002
1,781
US
I'm trying to do sequential file i/o on a PostScript file (yes, the same old project).

I don't create the PostScript file, a Windows driver does. A note to the curious: Microsoft's PostScript driver is terrible.

The PostScript file is ASCII. However, while most lines are CR/LF terminated, certain code blocks (in particular, those that deal with TrueType font setup statements) are output with a solitary LF (0x0A) character as the line terminator.

Some compilers (Fujitsu, for example) apparently have no difficulty seeing any combination of CR/LF as valid line terminators.

CA-Realia does NOT, and so my program "fails" when it reaches these regions in the file.

So, two questions:

1) Are there any compiler directives or other means of forcing CA-Realia to recognize CRLF, CR, or LF as valid line teriminators, rather than only CRLF?

2) What would be a good work-around? I've thought of UNSTRING using LF as a delimiter. However, another complication is that I want to INDEX each "line". I'm using a buffer length of 300, and some of these "sections" of PostScript code exceed 300 bytes.

Thanks in advance.

Thomas D. Greer

Providing PostScript & PDF
Training, Development & Consulting
 
I realize that this is not quite what you are asking for but it could be modified to pre-process the file.

Code:
      ******************************************************************

       IDENTIFICATION DIVISION.

      ******************************************************************

       PROGRAM-ID.    UTWRAP.
       AUTHOR.        CLIVE CUMMINS.
       INSTALLATION.  TUBULARITY.
       DATE-WRITTEN.  JAN 21,1995.

      ******************************************************************

       ENVIRONMENT DIVISION.

      ******************************************************************

      ******************************************************************

       DATA DIVISION.

      ******************************************************************

      ******************************************************************
       WORKING-STORAGE SECTION.
      ******************************************************************

       01  PROGRAM-DETAILS.
           05  PROGRAM-RELEASE.
               10  PROGRAM-NAME PIC X(08) VALUE 'UTWRAP'.
               10  PROGRAM-REL  PIC X(08) VALUE '  1.0.00'.
           05  PROGRAM-COPYRIGHT.
               10  PROGRAM-COPY PIC X(16) VALUE 'COPYRIGHT: 1995'.
               10  PROGRAM-AUTH PIC X(16) VALUE ' Clive Cummins.'.

      ******************************************************************
       01  WORK-AREAS.
      ******************************************************************

           05  HEX-0A                    PIC X(1) VALUE X'0A'.
           05  SPACE-FOUND-SW            PIC X(1) VALUE LOW-VALUES.
               88  SPACE-FOUND                    VALUE HIGH-VALUES.

      ******************************************************************
       LINKAGE SECTION.
      ******************************************************************

      ******************************************************************
       01  UTWRAP-PARAMETERS.
      ******************************************************************

           05  UTWRAP-TEXT               PIC X(3600).
           05  UTWRAP-TEXT-R REDEFINES UTWRAP-TEXT.
               10  UTWRAP-LETTER OCCURS 3600 TIMES
                   INDEXED BY UTWRAP-IDX PIC X(1).

      ******************************************************************

       PROCEDURE DIVISION USING UTWRAP-PARAMETERS.

      ******************************************************************

           SET UTWRAP-IDX TO 64.
           SET UTWRAP-IDX UP BY 1.

           PERFORM UNTIL UTWRAP-IDX GREATER THAN 3600
               MOVE LOW-VALUES TO SPACE-FOUND-SW
               PERFORM UNTIL SPACE-FOUND
                   IF UTWRAP-LETTER (UTWRAP-IDX) EQUAL SPACE
                       MOVE HEX-0A TO UTWRAP-LETTER (UTWRAP-IDX)
                       MOVE HIGH-VALUES TO SPACE-FOUND-SW
                   ELSE
                       SET UTWRAP-IDX DOWN BY 1
                   END-IF
               END-PERFORM
               SET UTWRAP-IDX UP BY 64
           END-PERFORM.

           GOBACK.

Clive
 
Here is a very old REALIA program that changes LF into CRLF.

have fun!

Regards,

Crox

Code:
000100  IDENTIFICATION DIVISION.
000200  PROGRAM-ID. CRLF.
000300  ENVIRONMENT DIVISION.
000400  CONFIGURATION SECTION.
000500  SOURCE-COMPUTER. IBM-PC.
000600  OBJECT-COMPUTER. IBM-PC.
000700  INPUT-OUTPUT SECTION.
000800  FILE-CONTROL.
000900      SELECT FILE01 ASSIGN TO VARYING A FILE STATUS FILE-STATUS1.
001000      SELECT FILE02 ASSIGN TO VARYING B FILE STATUS FILE-STATUS2.
001100  DATA DIVISION.
001200  FILE SECTION.
001300  FD FILE01
001400      LABEL RECORD STANDARD.
001500  01  EERSTE                        PIC X.
001600  FD FILE02
001700      LABEL RECORD STANDARD.
001800  01  TWEEDE                        PIC X.
001900  WORKING-STORAGE SECTION.
002000  01  HULPVELDEN.
002100      03  A                         PIC X(30) VALUE SPACE.
002200      03  B                         PIC X(30) VALUE SPACE.
002300      03  FILE-STATUS1              PIC XX.
002400      03  FILE-STATUS2              PIC XX.
002500      03  TEMP.
002600          05  FILLER                PIC X VALUE LOW-VALUE.
002700          05  TESTWAARDE            PIC X.
002800      03  TESTVELD REDEFINES TEMP   PIC S9(4) COMP.
002900      03  CRLF.
003000          05  DECIMAAL-13               PIC X.
003100          05  DECIMAAL-10               PIC X.
003200 PROCEDURE DIVISION.
003300 0001.
003400      DISPLAY 'INPUT FILE MET LF ?'.
003500      ACCEPT A FROM CONSOLE.
003600      STRING A DELIMITED BY SPACE
003700          '[B:63]' DELIMITED BY SIZE INTO A.
003800      OPEN INPUT FILE01.
003900      IF FILE-STATUS1 NOT = ZERO THEN
004000          DISPLAY '*  FOUTIEF OPGEGEVEN, DOE ''T NOG EENS  *'
004100          GO TO 0001.
004200 0002.
004300      DISPLAY 'OUTPUT MET CRLF ?    '.
004400      ACCEPT B FROM CONSOLE.
004500      STRING B DELIMITED BY SPACE
004600          '[B:63]' DELIMITED BY SIZE INTO B.
004700      OPEN OUTPUT FILE02.
004800      IF FILE-STATUS2 NOT = ZERO THEN
004900          DISPLAY '*  FOUTIEF OPGEGEVEN, DOE ''T NOG EENS  *'
005000          GO TO 0002.
005100      DISPLAY 'VAN ' A 'NAAR ' B.
005200      MOVE 13 TO TESTVELD.
005300      MOVE TESTWAARDE TO DECIMAAL-13.
005400      MOVE 10 TO TESTVELD.
005500      MOVE TESTWAARDE TO DECIMAAL-10.
005600      READ FILE01.
005700 0003.
005800      PERFORM UNTIL FILE-STATUS1 NOT = ZERO
005900          IF EERSTE = DECIMAAL-10
006000             WRITE TWEEDE FROM DECIMAAL-13
006100          END-IF
006200          WRITE TWEEDE FROM EERSTE
006210          READ FILE01
006300      END-PERFORM.
006400 9999.
006500      CLOSE FILE01 FILE02.
006600      DISPLAY ' '.
006700      DISPLAY '*** EINDE CRLF ***'.
006800      STOP RUN.
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top