Why does COBOL have both `SECTION` and `PARAGRAPH`?

后端 未结 9 1219
一向
一向 2021-02-18 16:23

Why does COBOL have both SECTION and PARAGRAPH?

Can anybody explain why the designers of COBOL created both SECTIONs and PAR

相关标签:
9条回答
  • 2021-02-18 16:24

    I will do the best I can to answer this. If your only coding exposure is x86 or ARM then you will have significant difficulty. Yes those chips sell a lot but that doesn't mean they are good, just cheap enough people don't mind throwing them away.

    Much of this information can be found in "The Minimum You Need to Know to Be an OpenVMS Application Developer." You will find it is one of the scant few titles on Dr. Dobb's recommended reading list for all developers. Yes, I wrote it. It is also the book recommended by HP OpenVMS Engineering group for developers looking to learn the platform.

    My COBOL on that platform mostly happened during the 1980s when it was VAX/VMS. Then it became OpenVMS; Alpha/OpenVMS; Itanium/OpenVMS; and soon to be x86/OpenVMS. On a real computer with a real operating system, sections have meaning. Every section created a PSECT. In linker terms that was short for Program SECtion. Based on what the section was, various load attributes were set. Each PSECT would be loaded into one or more 512 Byte memory pages. Memory pages were designed to be the exact same size as a disk block. VMS stood for Virtual Memory System. IBM had several of their own operating systems which, under the hood were different, but they too were true virtual memory systems. This wasn't "overlay linking." That's an x86 term and came about due to severe architectural flaws.Read up on Compact, Small, Medium, and Large "memory models" from the 286 days on forward. Also read up on EMS and XMS memory paging. Oiy was THAT fun!

    Here is one of the numerous programs found in that book.

    IDENTIFICATION DIVISION.
    

    PROGRAM-ID. COB_ZILL_DUE_REPORT_SUB. AUTHOR. Roland Hughes. DATE-WRITTEN. 2005-02-08. DATE-COMPILED. TODAY.

    ENVIRONMENT DIVISION.

    INPUT-OUTPUT SECTION.

    FILE-CONTROL.

    SELECT DRAW-STATS
        ASSIGN TO 'DRAWING_STATS'
        ORGANIZATION IS INDEXED
        ACCESS MODE IS SEQUENTIAL
        RECORD KEY IS ELM_NO IN DSTATS-REC
        LOCK MODE IS AUTOMATIC
        FILE STATUS IS D-STAT.
    
    SELECT MEGA-STATS
        ASSIGN TO 'MEGA_STATS'
        ORGANIZATION IS INDEXED
        ACCESS MODE IS SEQUENTIAL
        RECORD KEY IS ELM_NO IN MSTATS-REC
        LOCK MODE IS AUTOMATIC
        FILE STATUS IS M-STAT.
    
    SELECT SORT-FILE ASSIGN TO 'TMP.SRT'.
    
    SELECT SORTED-FILE ASSIGN TO DISK.
    
    SELECT RPT-FILE ASSIGN TO 'ZILL_DUE.RPT'.
    

    DATA DIVISION.

    FILE SECTION.

    FD DRAW-STATS IS GLOBAL LABEL RECORDS ARE STANDARD.

    COPY 'CDD_RECORDS.ZILLIONARE_STATS_RECORD' FROM DICTIONARY
        REPLACING ZILLIONARE_STATS_RECORD BY DSTATS-REC.
    

    FD MEGA-STATS IS GLOBAL LABEL RECORDS ARE STANDARD.

    COPY 'CDD_RECORDS.ZILLIONARE_STATS_RECORD' FROM DICTIONARY
        REPLACING ZILLIONARE_STATS_RECORD BY MSTATS-REC.
    

    FD RPT-FILE LABEL RECORDS ARE OMITTED.

    01 RPT-DTL                         PIC X(80).
    

    SD SORT-FILE.

    COPY 'CDD_RECORDS.ZILLIONARE_STATS_RECORD' FROM DICTIONARY
        REPLACING ZILLIONARE_STATS_RECORD BY SORT-REC.
    

    FD SORTED-FILE VALUE OF ID IS SORTED-FILE-NAME.

    COPY 'CDD_RECORDS.ZILLIONARE_STATS_RECORD' FROM DICTIONARY
        REPLACING ZILLIONARE_STATS_RECORD BY SORTED-REC.
    

    • Data declarations

    WORKING-STORAGE SECTION. 01 CONSTANTS. 05 SORT-FILE-NAME PIC X(7) VALUE 'TMP.SRT'. 05 SORTED-FILE-NAME PIC X(8) VALUE 'STAT.SRT'.

    01 STATUS-VARIABLES.
       05 M-STAT                PIC X(2).
       05 D-STAT                PIC X(2).
       05 EOF-FLAG              PIC X.
          88 IT-IS-END-OF-FILE VALUE 'Y'.
    
    01 STUFF.
       05 TODAYS-DATE.
          10 TODAY_YYYY         PIC X(4).
          10 TODAY_MM           PIC X(2).
          10 TODAY_DD           PIC X(2).
    
       05 TODAYS-DATE-FORMATTED.
          10 FMT_MM             PIC Z9.
          10 FILLER             PIC X VALUE '/'.
          10 FMT_DD             PIC 99.
          10 FILLER             PIC X VALUE '/'.
          10 FMT_YYYY           PIC 9(4).
    
       05 FLT-1                 COMP-2.
       05 WORK-STR              PIC X(65).
    
    01 REPORT-DETAIL.
       05 ELM-NO-DTL            PIC Z9.
       05 FILLER                PIC X(3).
       05 HIT-COUNT-DTL         PIC ZZZ9.
       05 FILLER                PIC X(3).
       05 SINCE-LAST-DTL        PIC ZZZ9.
       05 FILLER                PIC X(5).
       05 PCT-HITS-DTL          PIC Z9.999.
       05 FILLER                PIC X(4).
       05 AVE-BTWN-DTL          PIC ZZ9.999.
    
    01 REPORT-HDR1.
       05 THE-DATE              PIC X(12).
       05 FILLER                PIC X(20).
       05 PAGE-TITLE            PIC X(17).
    
    01 REPORT-HDR2.
       05 FILLER                PIC X(33).
       05 GROUP-TITLE           PIC X(20).
    
    01 REPORT-HDR3.
       05 HDR3-TXT              PIC X(40) VALUE
            'No   Hits   Since   Pct_hits   Ave_btwn'.
    
    01 REPORT-HDR4.
       05 HDR4-TXT              PIC X(40) VALUE
            '--   ----   -----   --------   --------'.
    

    PROCEDURE DIVISION.

    A000-MAIN.

    PERFORM B000-HSK.
    
    SORT SORT-FILE
        ON DESCENDING KEY SINCE_LAST IN SORT-REC
        INPUT PROCEDURE IS S000-DSTAT-INPUT
        GIVING SORTED-FILE.
    
    PERFORM B010-REPORT-DRAWING-NUMBERS.
    
    
    STRING SORT-FILE-NAME, ';*' DELIMITED BY SIZE INTO WORK-STR.
    CALL 'LIB$DELETE_FILE' USING BY DESCRIPTOR WORK-STR.
    
    STRING SORTED-FILE-NAME, ';*' DELIMITED BY SIZE INTO WORK-STR.
    CALL 'LIB$DELETE_FILE' USING BY DESCRIPTOR WORK-STR.
    

    * * Set up for second part of report * MOVE SPACES TO RPT-DTL. WRITE RPT-DTL BEFORE ADVANCING PAGE.

    MOVE SPACES TO EOF-FLAG.
    MOVE ' Mega Drawing Numbers' TO GROUP-TITLE.
    
    SORT SORT-FILE
        ON DESCENDING KEY SINCE_LAST IN SORT-REC
        INPUT PROCEDURE IS S001-MSTAT-INPUT
        GIVING SORTED-FILE.
    
    
    PERFORM B010-REPORT-DRAWING-NUMBERS.
    
    
    STRING SORT-FILE-NAME, ';*' DELIMITED BY SIZE INTO WORK-STR.
    CALL 'LIB$DELETE_FILE' USING BY DESCRIPTOR WORK-STR.
    
    STRING SORTED-FILE-NAME, ';*' DELIMITED BY SIZE INTO WORK-STR.
    CALL 'LIB$DELETE_FILE' USING BY DESCRIPTOR WORK-STR.
    
    
    CLOSE RPT-FILE.
    
    CALL 'LIB$SPAWN' USING BY DESCRIPTOR 'EDIT/READ ZILL_DUE.RPT'.
    
    EXIT PROGRAM.
    

    • Paragraph to initialize our data and files.

    B000-HSK. CALL 'COB_FILL_IN_LOGICALS'.

    MOVE SPACES TO STATUS-VARIABLES.
    
    ACCEPT TODAYS-DATE FROM DATE YYYYMMDD.
    
    MOVE TODAY_YYYY TO FMT_YYYY.
    MOVE TODAY_DD   TO FMT_DD.
    MOVE TODAY_MM   TO FMT_MM.
    
    
    OPEN OUTPUT RPT-FILE.
    
    
    MOVE SPACES TO REPORT-HDR1.
    MOVE TODAYS-DATE-FORMATTED TO THE-DATE.
    MOVE 'Due Number Report' to PAGE-TITLE.
    
    MOVE SPACES TO REPORT-HDR2.
    MOVE 'Drawing Numbers' TO GROUP-TITLE.
    

    • Paragraph to process the sorted selection file and
    • create the portion of the report relating to drawing
    • numbers.

    B010-REPORT-DRAWING-NUMBERS.

    MOVE SPACES TO EOF-FLAG.
    
    OPEN INPUT SORTED-FILE.
    
    READ SORTED-FILE
        AT END SET IT-IS-END-OF-FILE TO TRUE.
    
    PERFORM C010-DRAWING-HEADINGS.
    
    PERFORM UNTIL IT-IS-END-OF-FILE
        MOVE SPACES TO REPORT-DETAIL
        MOVE ELM_NO IN SORTED-REC TO ELM-NO-DTL
        MOVE HIT_COUNT IN SORTED-REC TO HIT-COUNT-DTL
        MOVE SINCE_LAST IN SORTED-REC TO SINCE-LAST-DTL
        MOVE PCT_HITS IN SORTED-REC TO PCT-HITS-DTL
        MOVE AVE_BTWN IN SORTED-REC TO AVE-BTWN-DTL
        MOVE REPORT-DETAIL TO RPT-DTL
        WRITE RPT-DTL BEFORE ADVANCING 1 LINE
        READ SORTED-FILE
            AT END SET IT-IS-END-OF-FILE TO TRUE
        END-READ
    END-PERFORM.
    
    CLOSE SORTED-FILE.
    

    • Paragraph to print headings for the main drawing numbers
    • Which are due.

    C010-DRAWING-HEADINGS.

    MOVE SPACES TO RPT-DTL.
    
    
    MOVE REPORT-HDR1 TO RPT-DTL.
    
    WRITE RPT-DTL BEFORE ADVANCING 2 LINES.
    
    MOVE SPACES TO RPT-DTL.
    
    MOVE REPORT-HDR2 TO RPT-DTL.
    
    WRITE RPT-DTL BEFORE ADVANCING 1 LINE.
    
    MOVE SPACES TO RPT-DTL.
    MOVE REPORT-HDR3 TO RPT-DTL.
    WRITE RPT-DTL BEFORE ADVANCING 1 LINE.
    
    MOVE SPACES TO RPT-DTL.
    MOVE REPORT-HDR4 TO RPT-DTL.
    WRITE RPT-DTL BEFORE ADVANCING 1 LINE.
    

    • Paragraph to filter due numbers into sort file.
    • Creates a floating point temporary to compare against
    • floating point value from input file. When greater
    • record is released to the sort file.

    S000-DSTAT-INPUT.

    OPEN INPUT DRAW-STATS.
    
    READ DRAW-STATS NEXT
        AT END SET IT-IS-END-OF-FILE TO TRUE.
    
    PERFORM UNTIL IT-IS-END-OF-FILE
    
        MOVE SINCE_LAST IN DSTATS-REC TO FLT-1
    
        IF FLT-1 >= AVE_BTWN IN DSTATS-REC
            MOVE DSTATS-REC TO SORT-REC
            RELEASE SORT-REC
        END-IF
        READ DRAW-STATS
            AT END SET IT-IS-END-OF-FILE TO TRUE
        END-READ
    END-PERFORM.
    
    CLOSE DRAW-STATS.
    

    • Paragraph to filter due numbers into sort file.
    • Creates a floating point temporary to compare against
    • floating point value from input file. When greater
    • record is released to the sort file.

    S001-MSTAT-INPUT.

    OPEN INPUT MEGA-STATS.
    
    READ MEGA-STATS NEXT
        AT END SET IT-IS-END-OF-FILE TO TRUE.
    
    PERFORM UNTIL IT-IS-END-OF-FILE
    
        MOVE SINCE_LAST IN MSTATS-REC TO FLT-1
    
        IF FLT-1 >= AVE_BTWN IN MSTATS-REC
            MOVE MSTATS-REC TO SORT-REC
            RELEASE SORT-REC
        END-IF
        READ MEGA-STATS
            AT END SET IT-IS-END-OF-FILE TO TRUE
        END-READ
    END-PERFORM.
    
    CLOSE MEGA-STATS.
    

    END PROGRAM COB_ZILL_DUE_REPORT_SUB.

    Sorry for the way the "code" feature works in this editor.

    Certain sections have to exist. Your program cannot do I-O without an INPUT-OUTPUT SECTION. This is where you map names to physical storage.

    If you have an INPUT-OUTPUT SECTION then you have to have a FILE SECTION. This is where you define the record layout(s) of each named file. LABEL RECORDS are always STANDARD when dealing with disk data files and OMITTED when writing report text files. There are a few other clauses I don't remember. Please note the SD included in all of those FD statements. FD is File Definition and SD is Sort Definition.

    If you are going to have any local variables you have to have a WORKING-STORAGE SECTION. You cannot declare variables on the fly, they all have to be declared here. This PSECT gets a DATA segment attribute among other things. If you call some service or something and it has a bad address, attempting to execute code within this PSECT the operating system will shoot your application out of the saddle.

    All PSECTs created after PROCEDURE DIVISION are flagged EXEC, write protected. If you try to overwrite anything in here during execution the operating system will shoot your program out of the saddle. Any other program attempting to write here will also be shot out of the saddle.

    Scan down to the SORT SORT-FILE in A000-MAIN. The COBOL sort routine is amazing. Notice that I provided an INPUT PROCEDURE and it is a paragraph. On IBM mainframes running ROSCOE back in the day this had to be an INPUT SECTION. They needed different attributes on the PSECT so the system sort routine could read/write.

    Here is a snippet from another program in that book.

    *
    

    * FMS definitions * COPY 'COBFDVDEF' OF 'MEGA_TEXT_LIB'.

    LINKAGE SECTION.

    01 FMS-STUFF.
       05 FMSSTATUS                 PIC S9(9) COMP.
       05 RMSSTATUS                 PIC S9(9) COMP.
       05 TCA                       PIC X(12).
       05 WORKSPACE                 PIC X(12).
    

    PROCEDURE DIVISION USING FMS-STUFF.

    The linkage section creates a PSECT of sharable memory. When you call external routines which return values, they need to be here.You must also grant your PROCEDURE DIVISION access to various things it needs in the linkage section.

    As you can see from this snippet later in the code

    B010-USER-INPUT.
    
    PERFORM C000-FORWARD-LOAD
    
    CALL 'FDV$PUTAL' USING BY DESCRIPTOR SCREEN-REC.
    
    MOVE SPACES TO WORK-STR.
    
    CALL 'FDV$GETAL' USING BY DESCRIPTOR WORK-STR
                           BY REFERENCE TERMINATOR.
    
    
    EVALUATE TERMINATOR
        WHEN FDV$K_FK_E6    SET LOAD-FORWARD TO TRUE
        WHEN FDV$K_FK_E5    SET LOAD-REVERSE TO TRUE
        WHEN FDV$K_FK_F10   SET WE-ARE-DONE TO TRUE
    END-EVALUATE.
    

    you can pass any local variable you wish as long as you pass it correctly. It's the writing which needs special PSECT attributes.

    It's late and I'm tired but I seem to remember you could could have USING clauses on SECTION declarations in the PROCEDURE DIVISION. The on-line documentation available for COBOL, at least that indexed by GOOGLE really is quite worthless. If you want more detailed information search for a circa 1980s COBOL textbook. It won't have any of the new stuff but it will answer many questions.

    Here's a kind of bad tutorial on COBOL structure.

    0 讨论(0)
  • 2021-02-18 16:31

    We use COBOL SECTION coding in all of our 37K MVS batch COBOL programs. We use this technique to get much faster run times and significantly reduced CPU overhead. This COBOL coding technique is very similar to high performance batch assembler.

    Call it High Performance Functionally Structured COBOL programming

    Once a SECTION is defined all PERFORM xxxxx will return at the next coded SECTION not the next paragraph in the SECTION. If paragraphs are coded ahead of the first SECTION then they can be executed normally. (But we don't allow this)

    Using a SECTION has higher overhead than when using and PERFORM ing only paragraphs - U N L E S S - you use GOTO logic to bypass code that should be conditionally executed. Our rule is that a GOTO can only point to a Tag-Line in the same SECTION. (a paragraph) All paragraphs in a SECTION must be a sub function of the SECTION s function. The EXIT instruction is an assembler NOP instruction. It allow for a Tag-Line to be placed before the next SECTION - a fast exit/return.

    Executing a PERFORM xxxx THRU yyyy has more CPU overhead than execution a SECTION without the GOTO s.

    WARNING: Executing a PERFORM xxxx Tag-Line in a SECTION will fall thru all the code in the SECTION until the next SECTION is encountered. A GOTO Tag-Line outside of the current SECTION will fall thru all the code in the new landing SECTION until the next SECTION is encountered. (But we don't allow this)

    0 讨论(0)
  • 2021-02-18 16:37

    I learned COBOL around 1978, on an ICL 2903. I have a vague memory that the SECTION headers could be assigned a number range, which meant that those SECTION headers could be swapped in and out of memory, when the program was too large for memory.

    0 讨论(0)
  • 2021-02-18 16:43

    Cobol was developed in the mid-50's. As the full name alludes, it was developed for business programming, as being a language more relevant for business purposes than the existing "scientific" or "technical" languages (there were very few "languages" anyway, and "machine code" (specific, of course, to a particular architechture (I nearly said "specific chip", before thinking of vacuum tubes)) which may have to be set through physical switches/dials on some machines) and if lucky with an "Assembler". Cobol was very advanced for its day, for its purpose.

    The intention was for programs written in Cobol to be much more like English-language than just a set of "codes" which mean something to the initiated.

    If you look at some of the nomenclature relating to the language - paragraph, sentence, verb, clause - it is deliberately following the patterns ascribed to the English language.

    SECTION doesn't quite fit into this, until you relate things to a formal business document.

    Both SECTIONs and paragraphs also appear outside the PROCEDURE DIVISION. As in written English, paragraphs can exist on their own, or can be a part of a SECTION.

    SECTIONs may have a priority-number which relates to the "segmentation feature". This used to include "overlaying" of SECTIONs to afford a primitive level of memory management. This is a "computing featuer" rather than an English-language one :-) The "segmentation feature" does have something of a remaining affect, but I've never seen it actually used.

    Without DECLARATIVES (which I don't use, and have just noticed the manual to be unclear upon) then it is "choice" as to whether SECTIONs or paragraphs are used for PERFORM.

    If GO TO is used, rationally, "equivalence" can be achieved with PERFORM ... TRHU .... If not, and there is not gratuitous use of PERFORM ... THRU ..., then there is equivalence already.

    Comparisons to "structured" code and modern languages are "reading history backwards" or just outlining a particular "practice". From the reputation attained by "spaghetti code" and ALTER ... TO PROCEED TO ... it may well be that for 20 years it was "common" to not do much with PERFORM unless you needed the "memory management", but I have no references or knowledge to back this up.

    SECTIONs allow duplicate paragraph-names, otherwise paragraph-names must be unique.

    I can't put a specific finger on one over the other all the time.

    If using GO TO, I'd use SECTIONs. If not, paragraphs. With DECLARATIVES I'd use SECTIONs. If using SECTIONs I'd start PROCEDURE DIVISION with a SECTION to avoid a diagnostic message.

    Local standards may dictate, but not necessarily on a "modern" (or even "rational") basis. Much is "known" but actually misunderstood about SECTIONs and paragraphs, in my experience.

    For performance (where masses of data is being processed, and I mean masses) then a PERFORM of one SECTION rather than multiple individual paragraphs would see improvements. The effect would be the same with PERFORM ... THRU ..., but I prefer not to recommend it. GO TO outside the range of a PERFORM is 1) bad 2) can lose out on "optimization". Shouldn't be a problem *except" when GO TO abend/exception and not expecting any logical return. If the use of this is felt to be necessarily "immediately", then it is better done with a PERFORM despite the "counter-intuitive" aspect (so document it).

    0 讨论(0)
  • 2021-02-18 16:43

    For one thing, paragraph names must be unique unless they are in separate sections, so sections allow for "namespacing" of paragraphs.

    If I recall correctly, the only reason you must use a SECTION is for DECLARATIVES. Aside from that they are optional and primarily useful for grouping paragraphs. I think it's common (relatively speaking, anyway) to require that PERFORM be used on paragraphs only when they are in the same section.

    0 讨论(0)
  • 2021-02-18 16:45

    No references on this, since I heard it passed on to me from one of the old timers in my shop but...

    In the old COBOL compilers, at least for IBM and Unisys, sections were able to be loaded into memory one at a time. Back in the good old days when memory was scarce, a program that was too large to be loaded into memory all at once was able to be modularized for memory usage using sections. Having both sections and paragraphs allowed the programmer to decide which code parts were loaded into memory together if they couldn't all be loaded at once - you'd want two parts of the same perform loop loaded together for efficiency's sake. Nowadays it's more or less moot.

    My shop uses paragraphs only, prohibits GOTO and requires exit paragraphs, so all our PERFORMS are PERFORM 100-PARAGRAPH THRU 100-EXIT or something similar - which seems to make the paragraphs more like sections to me. But I don't think that there's really much of a difference now.

    0 讨论(0)
提交回复
热议问题