HP3000-L Archives

September 1999, Week 4

HP3000-L@RAVEN.UTC.EDU

Options: Use Monospaced Font
Show Text Part by Default
Show All Mail Headers

Message: [<< First] [< Prev] [Next >] [Last >>]
Topic: [<< First] [< Prev] [Next >] [Last >>]
Author: [<< First] [< Prev] [Next >] [Last >>]

Print Reply
Subject:
From:
"Eric H. Sand" <[log in to unmask]>
Reply To:
Eric H. Sand
Date:
Mon, 27 Sep 1999 17:21:14 -0500
Content-Type:
text/plain
Parts/Attachments:
text/plain (122 lines)
<In reply to Bruce after Arthur>

I have found that using the following CoBOL structure I am able to write
records to an fixed length(determined at execution time) file. I haven't
tried it yet, but I'm sure the same structure would apply to input files. I
use a driver file to build my concatenated fields, count the number of
characters I've strung together, and issue a file equate that includes the
length of my to be created file. Various techniques could be used to
determine the length of a file(input or output) prior to issuing a file
equate and then opening that file. Works like a charm...

                        Thank You.....Eric Sand
                                            [log in to unmask]

----------------------------------------------------------------------------
-----------------------------------------

        $CONTROL USLINIT,POST85
                          .
         FILE-CONTROL.
             SELECT PATRON-DATA ASSIGN TO "PATOUT".
             .
         DATA                  DIVISION.
         FILE SECTION.
             .
         FD  PATRON-DATA
             RECORD IS VARYING IN SIZE FROM 2 TO 4096 CHARACTERS
                 DEPENDING ON OUTPUT-LENGTH
             RECORDING MODE IS U
             DATA RECORD IS PATRON-DATA-RECORD.
         01  PATRON-DATA-RECORD                 PIC X(4096).
             .
         WORKING-STORAGE        SECTION.
             .
             .
         01  OUTPUT-LENGTH                      PIC S9(4) COMP VALUE +0.
             .
         01  OUTPUT-DATA                        PIC X(4096) VALUE SPACES.
             .
         01  PATRON-OUT-FILE-EQUATE.
             02  FILLER                         PIC X(37) VALUE
                 "FILE PATOUT=PATOUT.PUB;DEV=DISC;REC=-".
             02  PATRON-OUT-REC-SIZE            PIC 9(4)   VALUE ZEROES.
             02  FILLER                         PIC X(10)  VALUE
                 ",1,F,ASCII".
             02  FILLER                         PIC X(6)   VALUE
                 ";DISC=".
             02  PATRON-OUT-FILE-SIZE           PIC 9(6)   VALUE ZEROES.
             02  FILLER                         PIC X(10)  VALUE
                 ",32,1;SAVE".
             02 FILLER                          PIC X      VALUE %15.
             .
         PROCEDURE DIVISION.
             .
             ADD IMAGE-FIELD-LGTH(FIELD-CNT) TO OUTPUT-LENGTH.
             .
             COMPUTE ODD-OR-EVEN = FUNCTION MOD (OUTPUT-LENGTH 2).
             .
             COMPUTE OUTPUT-LENGTH = OUTPUT-LENGTH + ODD-OR-EVEN.
             .
             MOVE OUTPUT-LENGTH TO PATRON-OUT-REC-SIZE.
             .
             CALL INTRINSIC "COMMAND" USING PATRON-OUT-FILE-EQUATE
                                            CMD-ERROR
                                            PARM-NUM.
             .
             OPEN OUTPUT PATDATA.
             .
             WRITE PATRON-DATA-RECORD FROM OUTPUT-DATA.
             .
             CLOSE PATDATA.



> -----Original Message-----
> From: Bruce Hobbs [SMTP:[log in to unmask]]
> Sent: Saturday, September 25, 1999 10:38 PM
> To:   [log in to unmask]
> Subject:      Re: Simple COBOL question
>
> At 12:01 AM -0400 09/25/1999, Arthur Frank <[log in to unmask]> wrote:
>
> > FD  INPUT-FILE
> >     LABEL RECORDS ARE STANDARD.
> > 01  INPUT-RECORD.
> >     05  KEY-VALUE-IN     PIC X(10).
> >     05  INPUT-DATA       PIC X(128).          <-----
> >
> > FD  OUTPUT-FILE
> >     LABEL RECORDS ARE STANDARD.
> > 01  OUTPUT-RECORD.
> >     05  KEY-VALUE-OUT    PIC X(10).
> >     05  KEY-COUNT        PIC 9(4).
> >     05  OUTPUT-DATA      PIC X(128).          <-----
> >
> >I would like the INPUT-DATA and OUTPUT-DATA to be variable size,
> depending =
> >on the size of the input file.  I'm sure that this is possible, but I'm =
> >pretty new to the language...
> >
> I don't think there's really any way you can accomplish what you want
> using the current version of the COBOL standard unless you're willing to
> utilize an HP extension (the compiler directive $DEFINE):
>
> $DEFINE %DATALENGTH=128#
> ...
>      05  INPUT-DATA       PIC X(%DATALENGTH).
> ...
>      05  OUTPUT-DATA      PIC X(%DATALENGTH).
>
> Not that it'll do you any good now, but the next standard includes a data
> division construct, SAME AS, that should be just the ticket:
>
> ...
>      05  INPUT-DATA       PIC X(128).
> ...
>      05  OUTPUT-DATA SAME AS INPUT-DATA.
> =======================================================================
> Bruce Hobbs, CCP, CDP   856 N Monterey St         Phone: (626) 570-8028
> Partner                 Alhambra, CA 91801-1574   FAX:   (626) 570-9850
> Engineered Software     E-mail: [log in to unmask]

ATOM RSS1 RSS2