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!

A "better" COBOL. 7

Status
Not open for further replies.

tgreer

Programmer
Oct 4, 2002
1,781
US
I've been asked to research finding a "better COBOL" for my company. I know that's subjective, so bear with me. We currently use CA-Realia Workbench 3.1.

We're in a Windows NT/2000/XP PC environment.

A short list of what "better" might mean:

- faster

- better file i/o (more on this later)

- COM/Automation/ActiveX

- .NET integration (maybe... we don't particularly care for .NET's huge installation footprint, nor Microsoft's tendency to change everything once other players get involved. And that's from a C#/ASP.NET developer, folks.)

Which Windows/PC COBOL vendor did YOU choose? Why? What were YOUR criteria?

One of the problems, I'm told, is file i/o. We work with huge customer-provided text and binary files. We have to "do stuff" to them. These may be PostScript files, PCL files, or data files. Many times the developers must code multiple passes through the file. Once to find specific records or strings, a second time to insert code, a third to move chunks of data around. I'm told this is because COBOL doesn't support random file i/o.

Is this true? Is it true under certain conditions, but not in others? Is it true of certain compilers? I ask because I see references to "RANDOM" and "DYNAMIC" access modes. (I'm not, yet, a COBOL programmer, so forgive the ignorance.)

Would another language entirely be a "better COBOL"? Perl? I used to program in PL/B, which is an ANSI standard language, with excellent file i/o, string manipulation, character- based AND GUI/event-driven programming, plus COM/ActiveX. Perhaps switching from COBOL to PL/B would be the right choice:
I'm looking for a good discussion / debate / education on the pros and cons of the various COBOL vendors, plus thoughts on migrating to other languages.

Thanks in advance for your thoughtful responses.



Thomas D. Greer

Providing PostScript & PDF
Training, Development & Consulting
 
I thank everyone for their replies and the lively discussion. I have to admit I'm still unclear on the file i/o issue. So here's a specific, scaled-down example. Consider a PostScript file with the following structure:

Code:
%!PS
[prolog section]
%%Page: 1 1
[code=for page 1]
(%%[Page: 1]%%) = 
%%Page: 2 2
[code=for page 2]
(%%[Page: 2]%%) = 
%%Page: 3 3
[code=for page 3]
(%%[Page: 3]%%) = 
[many pages omitted ]
%%Page: 50 50
[code=for page 50]
(%%[Page: 50]%%) =
(%%[LastPage]%%) = 
%%EOF

This is a single, 50-page document. Imagine that there are thousands of such documents, with a VARIABLE number of pages. Some documents might be 20 pages, some 63 pages. They are all then concatenated together into a single file and set to us for printing. However, we have to "fix" some issues.

Imagine the task is to 1) identify the last page of each document. One can do that by finding the "LastPage" comment. Then, move the last page of each document to page 1 of that document, thusly:

Code:
%!PS
[prolog section]
%%Page: 50 50
[code=for page 50]
(%%[Page: 50]%%) =
%%Page: 1 1
[code=for page 1]
(%%[Page: 2]%%) = 
%%Page: 2 2
[code=for page 2]
(%%[Page: 2]%%) = 
%%Page: 3 3
[code=for page 3]
(%%[Page: 3]%%) = 
[many pages omitted ]
(%%[LastPage]%%) = 
%%EOF

That's just ONE of the tasks we'll need to perform, but illustrates the need for random file i/o. How would you approach this? And assume, also, that the file is too big to read into memory.

Thomas D. Greer

Providing PostScript & PDF
Training, Development & Consulting
 
Clarification on earlier comment:

XML is part of the 2002 standard so that's not really an issue.

XML is *not* part of the 2002 ISO COBOL Standard. There is a "TR" (Technical Report" currently out for international review.

It may OR MAY NOT end up in the 2008 Standard (currently under revision).

As far as I khown, there is NO "fully conforming" ISO 2002 COBOL compiler (for any operating system).

Bill Klein
 
This should help a little at least on the COBOL side of the issue if you're wanting to see how it is done. There is really nothing similar to your example in terms of paging rules, but it shows how to do what you are wanting to do.

This sets up a file which can have multiple prints in it keyed by page. You can either read to a specific point or read sequentially depending on what you want to do.

Hope this helps you in the right direction.

Code:
 IDENTIFICATION DIVISION.
  PROGRAM-ID. FILENDX.
* Build a mainframe print spooler.  Places files into INPUT.DAT by
* 55 line pages which then can be accessed either sequentially (3000)
* or dynamically (2000).  
* copyright by Glenn9999@tektips.com.  Can be used freely but any use of this code must have this statement in it.

 ENVIRONMENT DIVISION.
 INPUT-OUTPUT SECTION.
 FILE-CONTROL.
     SELECT DATA-FILE
        ASSIGN TO  "INPUT.TXT"
        ORGANIZATION IS LINE SEQUENTIAL.
     SELECT MASTER-FILE
        ASSIGN TO "INPUT.DAT"
        ORGANIZATION IS INDEXED
        ACCESS IS DYNAMIC
        RECORD KEY IS MASTER-FILE-KEY
        FILE STATUS IS FILE-STAT.

 DATA DIVISION.
 FILE SECTION.
 FD  DATA-FILE.
 01  DATA-RECORD        PIC X(50).

 FD  MASTER-FILE.
 01  MASTER-FILE-RECORD.
     04  MASTER-FILE-KEY.
         08  MASTER-FILE-ID      PIC S9(4) COMP-5.
         08  MASTER-PAGE         PIC S9(4) COMP-5.
     04  MASTER-BLOCK            PIC S9(4) COMP-5.
     04  MASTER-CNT              PIC S9(4) COMP-5.
     04  MASTER-LINE OCCURS 1 TO 55 TIMES
                     DEPENDING ON MASTER-CNT
                     INDEXED BY MASTER-NDX PIC X(50).

  WORKING-STORAGE SECTION.
 01  FILE-KEY-DATA.
    04  FILE-KEY-FILE-ID     PIC S9(4) COMP-5.
    04  FILE-KEY-PAGE        PIC S9(4) COMP-5.
 01  FILE-VARS.
    04  FILE-STAT            PIC XX.
    04  EOF-FLAG             PIC S9(4) COMP-5.
 01  INFILE-RECORD           PIC X(100).
*
 PROCEDURE DIVISION.
 0000-START SECTION.
     PERFORM 1000-INITIAL-WRITE.
     DISPLAY "FILE GENERATED.".
     PERFORM 2000-SEEK-FILE.
*     PERFORM 3000-READ-ALL.
     GOBACK.

 1000-INITIAL-WRITE SECTION.
* demonstrates how to handle writing the file initially.
     OPEN INPUT DATA-FILE.
     OPEN OUTPUT MASTER-FILE.
     MOVE 0 TO EOF-FLAG.
     MOVE 1 TO MASTER-FILE-ID.
     MOVE 1 TO MASTER-PAGE.
     MOVE 1 TO MASTER-BLOCK.
     READ DATA-FILE INTO INFILE-RECORD
       AT END MOVE 1 TO EOF-FLAG.
     PERFORM 1100-WRITE-FILE UNTIL EOF-FLAG = 1.
     CLOSE DATA-FILE MASTER-FILE.

 1100-WRITE-FILE SECTION.
     MOVE 0 TO MASTER-CNT.
     PERFORM UNTIL (MASTER-CNT = 55) OR (EOF-FLAG = 1)
        ADD 1 TO MASTER-CNT
        MOVE INFILE-RECORD TO MASTER-LINE (MASTER-CNT)
        READ DATA-FILE INTO INFILE-RECORD
          AT END MOVE 1 TO EOF-FLAG
        END-READ
     END-PERFORM.
     DISPLAY "WRITING PAGE " MASTER-PAGE.
     WRITE MASTER-FILE-RECORD.
     ADD 1 TO MASTER-PAGE.

 2000-SEEK-FILE SECTION.
* demonstrates how to seek to a particular record block.
     OPEN I-O MASTER-FILE.
     MOVE 1 TO FILE-KEY-FILE-ID.
     MOVE 5 TO FILE-KEY-PAGE.
     MOVE FILE-KEY-DATA TO MASTER-FILE-KEY.
     READ MASTER-FILE.
     EVALUATE FILE-STAT
        WHEN '00' PERFORM 2100-WRITE-REC
        WHEN '23' DISPLAY "ITEM NOT FOUND"
        WHEN OTHER PERFORM 4000-ERROR
     END-EVALUATE.
     CLOSE MASTER-FILE.

 2100-WRITE-REC SECTION.
     PERFORM VARYING MASTER-NDX FROM 1 BY 1 UNTIL
                     MASTER-NDX > MASTER-CNT
        DISPLAY ": " MASTER-LINE (MASTER-NDX)
     END-PERFORM.

 3000-READ-ALL SECTION.
* demonstrates how to read from the entire file sequentially.
     MOVE 1 TO MASTER-FILE-ID.
     MOVE 1 TO MASTER-PAGE.

     OPEN I-O MASTER-FILE.
     READ MASTER-FILE NEXT RECORD.
     PERFORM UNTIL FILE-STAT NOT = '00'
        PERFORM VARYING MASTER-NDX FROM 1 BY 1
          UNTIL MASTER-NDX > MASTER-CNT
           DISPLAY MASTER-LINE (MASTER-NDX)
        END-PERFORM
        READ MASTER-FILE NEXT RECORD
     END-PERFORM.

 4000-ERROR SECTION.
     DISPLAY "BIG ERROR: " FILE-STAT.
     GOBACK.
 
Thanks, glenn. What is your "key" in the ISAM file? The entire record? I understand ISAM, but I'm not seeing how you could index a PostScript file.

Could you provide a bit more explanation? I think the concept is to turn a sequential file into an indexed file, so that you could then do random i/o by specifying a key value. If each line of the PostScript code had a unique key value, I could see this approach working. That isn't the case.

A single "page" might have thousands of lines of code. So what do you use as a "key" to a record that spans a variable number of lines?



Thomas D. Greer

Providing PostScript & PDF
Training, Development & Consulting
 
Thanks, glenn. What is your "key" in the ISAM file? The entire record? I understand ISAM, but I'm not seeing how you could index a PostScript file."

I'm making up an index to give a meaningful representation for what I'm doing with the prints. MASTER-FILE-ID is a file number and MASTER-PAGE is the page number. So in the 2000-paragraph I'm having it get File 1 Page 5.

As for your processing, each set of meaningful representations can be placed into a record. That would be how the MASTER-BLOCK field can be of use. In my example, a set of meaningful representations is 55 lines of text (per page), so each record represents one page of data and there's only one record per page. Of course if it was a necessity there could be multiple records per page without an issue (file1, page1, block1; file1, page1, block2; etc).

Of course if you find something more meaningful for the keys in your PostScript processing, go for it.
 
Another example: I could index COBOL source files the same way. File by name, then one record for each line or group of lines that represents a statement. I could index by line number of the source, but I could also possibly index by paragraphs and then place the file into multiple blocks.

Say for my code above, I could make the identification division one block, the environment division one block, the data division one block, 0000-START a block, 1000-INITIAL-WRITE, and so forth.

It is the responsibility of the programmer to make the data so it can be meaningfully processed in the manner he needs it processed. If that includes making up keys to describe his data, then more power to him.
 
What defines a "block"? Sorry if I'm being dense, but in PostScript, usually there's a comment record that indicates the start of a page. Another to indicate the end of a page. But in between, there could be any number of "records".

So how would you index a file so that an ISAM read could jump to the start of any page, and then read in a "record" consisting of a variable number of [bytes | lines | records]?

Thomas D. Greer

Providing PostScript & PDF
Training, Development & Consulting
 
Some changes to Glenn's code to make it more portable and add a capability to store multiple 'things' per 'line' per 'page' per 'file':
Code:
 FD  MASTER-FILE.
 01  MASTER-FILE-RECORD.
     04  MASTER-FILE-KEY.
         08  MASTER-FILE-ID      PIC 9(8).
         08  MASTER-PAGE         PIC 9(8).
         08  MASTER-LINE         PIC 9(8).
         08  MASTER-THING        PIC 9(8).
     04  MASTER-SIZE             PIC 9(4) BINARY.
     04  THE-THING
         05          PIC X OCCURS 1 TO 9999 TIMES
                     DEPENDING ON MASTER-SIZE.

So, first I removed COMP-5 (a nonstandard USAGE) to enhance portability.1 I removed the "S" from the picture because having binary (i.e. COMP-5) values with negative values will really do some nonintuitive things to the order of your records. The fact that some implementations store the least significant byte of COMP-5 at the lowest address will also cause some bizarre behavior.

I added two levels of heirarchy into the key of the file and placed one, and only one, item per record. This will allow you to traverse the file more easily. The master key is a set of 32 digits, which represent, from highest to lowest order, the file, page, line and 'thing'. (Since I know so little about PS and PCL, it may be true that you do not need four levels in your heirarchy.)

So, on your first, input parsing, pass, you parse the input file into 'things' and place them into the indexed file, numbering each line within each page, and numbering new 'things' from zero (or one) within each line. Probably not real easy to understand without a bit of COBOL training, but it will work and it will be sensible to your COBOL programmers that look at it later.

Now.... nothing in the above talks about reassembling the 'things' into a valid PS or PCL file. That, too, will be a bit tricky.


1 Efficiency flamers will weigh in about how COMP-5 is more efficient. At 3 GHz -- we have better things to occupy our time.

Tom Morrison
 
tgreer said:
So how would you index a file so that an ISAM read could jump to the start of any page, and then read in a "record" consisting of a variable number of [bytes | lines | records]?

Using my recent code example:
Code:
MOVE ZEROS to MASTER-FILE-KEY.
MOVE desired-file TO MASTER-FILE-ID.
MOVE desired-page TO MASTER-PAGE.
START MASTER-FILE KEY NOT LESS THAN MASTER-FILE-KEY.
READ MASTER-FILE NEXT 
    AT END MOVE HIGH-VALUES TO MASTER-FILE-KEY.
PERFORM UNTIL MASTER-PAGE NOT = desired-page
           OR MASTER-FILE-ID NOT = desired-file
    [i]process a thing[/i]
    READ MASTER-FILE NEXT 
        AT END MOVE HIGH-VALUES TO MASTER-FILE-KEY
END-PERFORM.

Tom Morrison
 
I need to be able to jump to specific spots in an open file. Forward or Backward
The MicroFocus CBL_READ_FILE and CBL_WRITE_FILE byte-stream routines both admit a file-offset and byte-count parameters.

Hope This Helps, PH.
Want to get great answers to your Tek-Tips questions? Have a look at FAQ219-2884 or FAQ181-2886
 
Oops.

make that
Code:
    AT END MOVE ALL "9" to MASTER-FILE-KEY
 
What defines a "block"?"

Whatever you want to make it. If it is necessary to break up the page data to delineate PostScript commands or for simple numbers of lines, you can do it. I think most of us (myself included) have no clue about how to process PostScript files so all that can be done is guess what you need.

"So how would you index a file so that an ISAM read could jump to the start of any page, and then read in a "record" consisting of a variable number of [bytes | lines | records]?"

That's part of my purpose in adding the MASTER-BLOCK field. The data itself is defined as an ODO table or Occurs Depending On. As you can see, it's defined to hold a minimum of one line and a maximum of 55 lines, but the real number of lines is in MASTER-CNT. That means I can have three "blocks" for a page, have 30 lines in one, 20 in the second, and 5 in the third and all will be well as long as I set MASTER-CNT properly and get the data into the record.

If you simply need to store a variable number of bytes, you can change the definition from 55 character lines to single bytes:

Code:
04  MASTER-CNT    PIC S9(5) COMP.
04  MASTER-DATA PIC X OCCURS 1 to 9999 TIMES DEPENDING ON MASTER-CNT

This def just has a block of binary data from 1 byte to 9999 bytes and the real amount is in MASTER-CNT.

You will have to mold it to your needs, but if you can isolate what will work for each record then you should be fine.


* And yes the S9(5) COMP is implementation specific and not portable - it usually means "use whatever native binary format is on the system". Much more efficient with my compiler than using big endian binaries.
 
OK didn't quite understand you...k5tm covered it...in fact I did too in the 2000 paragraph in picking up the 5th page of the 1st document. Once that read gets called successfully, the data fitting the key are in the file buffer for processing.

If I need to go on and read Page 6 and so on, I would use the READ NEXT RECORD option demonstrated in the 3000 paragraph.
 
I wince! [blush]
Code:
MOVE ZEROS to MASTER-FILE-KEY.
MOVE desired-file TO MASTER-FILE-ID.
MOVE desired-page TO MASTER-PAGE.
START MASTER-FILE KEY NOT LESS THAN MASTER-FILE-KEY.
READ MASTER-FILE NEXT
    AT END MOVE ALL "9" TO MASTER-FILE-KEY.
PERFORM UNTIL MASTER-PAGE NOT = desired-page
           OR MASTER-FILE-ID NOT = desired-file
    [i]process a thing[/i]
    READ MASTER-FILE NEXT
        AT END MOVE ALL "9" TO MASTER-FILE-KEY
    END-READ
END-PERFORM.
 
Thomas sent me a sample file, and I sent code very similar to this. I am sure Thomas will have other issues, but this did give him an idea about the way to use COBOL to achieve his requirement.
Code:
       identification division.
       program-id.  move-ps-pages.

       environment division.
       input-output section.
       file-control.
           select input-ps  assign random "omr.ps"
               organization line sequential
               file status is ps-status.

           select output-ps assign random "omrout.ps"
               organization line sequential
               file status is ps-status.

           select temp-ps   assign random "temp-ps"
               organization indexed
               access dynamic
               record key is ps-key
               file status is ps-status.

       data division.
       file section.
       fd  input-ps 
           record varying from 0 to 300 characters
                          depending on input-record-size.
       01  input-ps-record             pic x(300).   
           
       fd  output-ps 
           record varying from 0 to 300 characters
                          depending on output-record-size.
       01  output-ps-record            pic x(300).  

       fd  temp-ps
           block contains 100 records.
       01  temp-ps-record.
           02  ps-key.
               03  ps-file             pic 9(8).
               03  ps-page             pic 9(8).
               03  ps-line             pic 9(8).
           02  ps-content-size         pic 9(4).
           02  ps-content.
               03  pic x   occurs 1 to 300 
                           depending on ps-content-size. 
           

       working-storage section.

       01  ps-status                   pic xx.
           88  ps-ok                   value "00".
           88  ps-eof                  value "10".

       01  input-record-size           pic 999.
       01  output-record-size          pic 999.

       01  pic x.  88  is-in-page value "Y" false "N".

       01  current-file-number         pic 9(8).
       01  current-page-number         pic 9(8).
       01  current-line-number         pic 9(8).
       01  maximum-file-number         pic 9(8).
       01  maximum-page-number         pic 9(8).


       procedure division.
       a.
           set is-in-page to false.
           move 0 to current-file-number.
           open input input-ps.
           if not ps-ok then
               display "open input failed: ", ps-status
               stop run
           end-if.

           open output temp-ps.
           if not ps-ok then
               display "open output failed: ", ps-status
               stop run
           end-if.

           move 0 to current-page-number, current-line-number.           
           move spaces to input-ps-record.
           read input-ps
               at end continue 
           end-read.

           perform until not ps-ok

             if is-in-page
               perform capture-input
               add 1 to current-line-number
               if input-ps-record (1:10) = "(%%[Page: "
                 set is-in-page to false
               end-if
             else
               if input-ps-record (1:8) = "%%Page: "
                 set is-in-page to true
                 add 1 to current-page-number
                 move 0 to current-line-number
                 perform capture-input
                 add 1 to current-line-number
               end-if
               if input-ps-record (1:5) = "%%EOF"
                 display "file: ", current-file-number
                         " contained ", current-line-number
                         " records."
                 add 1 to current-file-number
                 move 0 to current-page-number, current-line-number
               end-if
             end-if

             move spaces to input-ps-record
             read input-ps
               at end continue
             end-read

           end-perform.

           close input-ps, temp-ps.
           open input temp-ps.
           open output output-ps.

           move current-file-number to maximum-file-number.

           perform varying current-file-number from 0 by 1
                     until current-file-number not < maximum-file-number
               move all "9" to ps-key
               move current-file-number to ps-file
               start temp-ps key < ps-key
               read temp-ps previous
                 at end
                   move 0 to maximum-page-number
                 not at end
                   move ps-page to maximum-page-number
               end-read
               move all "0" to ps-key
               move current-file-number to ps-file
               move maximum-page-number to ps-page
               start temp-ps key not < ps-key
               read temp-ps next
                 at end
                   move all "9" to ps-key
               end-read
               perform until ps-file > current-file-number
                 move ps-content-size to output-record-size
                 move ps-content      to output-ps-record
                 write output-ps-record
                 read temp-ps next
                   at end
                     move all "9" to ps-key
                 end-read
               end-perform
               move all "0" to ps-key
               move current-file-number to ps-file
               start temp-ps key not < ps-key
               read temp-ps next
                 at end
                   move all "9" to ps-key
               end-read
               perform until ps-file > current-file-number
                          or ps-page >= maximum-page-number
                 move ps-content-size to output-record-size
                 move ps-content      to output-ps-record
                 write output-ps-record
                 read temp-ps next
                   at end
                     move all "9" to ps-key
                 end-read
               end-perform

               move 5               to output-record-size
               move "%%EOF"         to output-ps-record
               write output-ps-record

           end-perform.

           close temp-ps.
           close output-ps.
           delete file temp-ps.

           stop run.

       capture-input.
           move current-file-number    to ps-file.
           move current-page-number    to ps-page.
           move current-line-number    to ps-line.
           move input-record-size to ps-content-size.
           move input-ps-record   to ps-content.
           write temp-ps-record.

Tom Morrison
 
Thanks, that program plus your coaching clarified matters greatly. I am an experienced programmer, just not in COBOL.

I would like to continue the discussion, however.

Some observations:

1) this technique requires an "indexing" pass through the file, writing out all the isam data to an indexed file. This can be time consuming.

If a language supported random access files, such an "index" could be built in memory, and so wouldn't have to write out the actual index file.

2) I'm told that IO itself isn't the biggest bottleneck. What really bogs the process down is the string manipulation needed to determine if the record we've just read is of interest. In other words, is this record the start of a page? The end of a Page? The "INPSECT" or the reference modification to parse the string will slow a typical program down a lot. What is "a lot"? I'm told that indexing a 2GB file, 20 minutes. Add in the INPSECT statements, 2-4 hours.

Why is string manipulation so slow? Is that an aspect of COBOL in general, or the version of Relia we're using?

3) all of this assumes ASCII data. We still have the issue of binary file processing, for example, with PCL files. How would you handle random i/o on a binary file?



Thomas D. Greer

Providing PostScript & PDF
Training, Development & Consulting
 
I'm told that IO itself isn't the biggest bottleneck.

IO consumes very much time!

What really bogs the process down is the string manipulation needed to determine if the record we've just read is of interest. In other words, is this record the start of a page?

String manipulation is always slow. If you read a file with some information in it, it has a structure. When you make a program, it should be designed to recognize this structure. If you are busy to inspect a huge amount of data, you should study algorithms to inspect strings in a fast way. There are books about this subject, for example from Sedgewick or Knuth. You should avoid inspecting the same data more than one time.
 
1) With any version of COBOL that has byte-stream processing, storing the pointers in memory on in an indexed file will work. You can then go back and read the relevent data from the input file.

LINE SEQUENTIAL I/O itself involves string searching, looking for the record termination codes. With byte-string access, you need not look for the record termination code, just the strings you are interested in.

2) The type of reference modification used in the sample code Tom Morrison sent should not take up any time at all. With constant values, the offsets sould be resolved at compile time.

3) Again, with byte-stream I/O, there is no difference in processing text data or binary data, as long as you know the tokens you are looking for.
 
Just a personal comment on the underlying issue (I think),

Although I "tend" to be a "COBOL bigot", I would guess that in almost all cases where such languages are available, languages "targetted" at "srring manipulation" (e.g. PERL, PYTHON, SPITBOL - even possibly REXX) will "out-perform" COBOL (even well optimized COBOL) for a program that basically is JUST "string seraches and manipulation" on LARGE quantities of data.

Having the goal (stated much earlier in this thread) of a "single" language for a single application may be a good thing, but it often (not always0 DOES lead to "less well performing" applications.

Bill Klein
 
I don't think that a good programmed and tuned string-handling programming in COBOL will be less fast than any other language except assembler. But assembler is very much more work.

The experience is completely the other way around. Good programming techniques and tuning will give excellent results. COBOL programs made by good programmers (using a good compiler!!!) are never outperformed by other languages. I never needed to use an other language for that. On the contrary. I even was once in competition with an assembler programmer on the mainframe. In the end, the assembler program was only about 10% faster. The COBOL program was chosen because it was very much more maintainable.
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top