Menu

Procedure Division Copybooks

2014-11-24
2022-01-30
  • Robert W.Mills

    Robert W.Mills - 2014-11-24

    Does anybody have any examples of a procedure division copybook that requires text substitution (COPY...REPLACING). I've never used them and a Google search has only resulted in data division examples. I'm also after the COPY...REPLACING command required to invoke it.

     
  • Brian Tiffin

    Brian Tiffin - 2014-11-24

    There is kinda a blurb in the FAQ. Probably not very enlightening actually.

    http://opencobol.add1tocobol.com/gnucobol/#replace

    Changing up the sample, the entire prog.cob source file would be

    ::cobolfree
    COPY copybook REPLACING
        ==MARKER== BY ==DISPLAY "REPLACE EXAMPLE" END-DISPLAY==.
    

    and the copybook.cpy would be

    ::cobolfree
    identification division.
    program-id. prog.
    
    procedure division.
    MARKER
    goback.
    end program prog.
    

    Robert; having typed that, I'm thinking it may not be very helpful.

    Cheers,
    Brian

     
  • Bill Woodger

    Bill Woodger - 2014-11-24

    From the Enterprise COBOL Language Reference PDF there are some useful examples. Tried to google for the words, failed, you you get other references.

    There's no real difference between use in DATA DIVISION and PROCEDURE DIVISION so I'm guessing it is some of the things needed to get parts of words. The PDF and google "COBOL When the REPLACING phrase is specified" should get sufficient, but if not, expand on what it is that you're after but can't get.

     
  • Anonymous

    Anonymous - 2014-11-24

    You may have

    au640.cpy :

    ::cobol
           1 (tag)au640.
             2 (tag)au640-type-enreg          pic xx.
             2 (tag)au640-sep1                pic x.
             2 (tag)au640-portoir             pic 9(4).
    

    And a cobol program : myprog.cbl

    ::cobol
           data division.
           file section.
           fd file1.
           copy "au640.cpy" replacing ==(tag)== by ==fd1==.
           fd file2.
           copy "au640.cpy" replacing ==(tag)== by ==fd2==.
           ...
           working-storage section.
           copy "au640.cpy" replacing ==(tag)== by ==wss==.
           ...
           procedure division.
           ...
           move fd1au640 to wssau640
           .... some computation with wssau640
           move wssau640 to fd2au640 
    

    Hope this helps.

     

    Last edit: Simon Sobisch 2014-11-27
  • Robert W.Mills

    Robert W.Mills - 2014-11-27

    In 30+ years of writing COBOL the only use I've ever made of copybooks is for file-control selects, file section FD & record layouts, and standard (fixed) procedures which are shared by all/most programs within a system. None of which required the use of the replacing clause on the copy statement.

    What I am realy looking for are some 'real world' examples (10 would be a nice number but 25-30 would be even nicer) of copybooks used within the 'procedure division' to get an idea of what people have used them for. As I said, I'm also after the copy...replacing statment required by the copybook.

    @Brian: I had seen that one. It looked like an example you find in a students workbook (contrived). Also, your last statement was correct.

    @Bill: Found several IBM copybook examples but all for the data division.

    @Anonymous: Wrong division. Looking for procedure not data.

     

    Last edit: Robert W.Mills 2014-11-27
    • Vincent (Bryan) Coen

      Well for me and since starting with Cobol around 1961 I do not recall ever using procedure div copy books and these days there is no need as it is all copy and paste.

      I do use reusable called modules though !

      Vince

       

      Last edit: Simon Sobisch 2014-11-27
      • Simon Sobisch

        Simon Sobisch - 2014-11-27

        these days there is no need as it is all copy and paste

        You miss one important point in this: the one thing is the re-usability within different programs but the may even much more important thing is the possibility to fix / extend multiple programs by just changing one file and recompiling all sources that include the copy (will often only work if you have a counterpart copy in WORKING-STORAGE that you change together with the PROCEDURE DIVISION part).

        This is much more true if you place reusable PROCEDURE DIVISION stuff in called modules, of course and has the benefit of no need for recompiling hundreds of programs for most fixes/extensions and it possibly frees some memory (when comparing to COPY larger copybooks).

        Simon

         
  • Bill Woodger

    Bill Woodger - 2014-11-27

    The COPY/REPLACING is the same wherever it is. I have no examples, and can't remember ever having seen it used in the PROCEDURE DIVISION either (except as below).

    You can easily make some. OPENing a file and checking the FILE STATUS field (and CLOSE, READ, WRITE) would be useful examples.

    A lot of systems, and people with experience, date from before COPY got cleverer. Many people seem suspicious of (as in ready to blame) code that they can't see in the source.

    The example I only remembered seeing whilst typing, was on a Mainframe discussion group on LinkedIn. It was very interesting. It was an entire program. The idea being to use it as a contained program. It was a binary-search-plus program. A CALL to a contained program is much less code than a CALL to an external program, on IBM. At a cost of program size, better performance.

    The LinkedIn group in question is a closed group, so I probably can't give a link for it, but I'll try to produce a skeleton based on that.

     

    Last edit: Bill Woodger 2014-11-27
  • Bill Woodger

    Bill Woodger - 2014-11-27

    The program wasn't posted in the group, but was e-mailed to me. Here it is, heavily redacted, it is a replacement for SEARCH ALL with many features. I'll contact the author and see if he'd like to contribute it.

    ::cobol
           IDENTIFICATION DIVISION.
           PROGRAM-ID.   :TABLE: COMMON.
          * >>>  TO USE:
          *
          * 1) IN WORKING-STORAGE DEFINE THE DETAILED TABLE ENTRY FOR USE.
          *
          * 2) ALSO IN WS, USE THE CODE-BLOCK REPLACING :KEYL: WITH LENGTH.
          *     01  CALL-BLOCK.
          *         05  REQ-FUNC             PIC X(4).
          *         05  SEARCH-KEY           PIC X(06).   ---------------
          *                                                              |
          * 3) JUST BEFORE THE END-PROGRAM STATEMENT, INSERT THE 'COPY'  |
          *     STATEMENT FOR EACH TABLE YOU WANT TO USE.                |
          *        COPY KDYNTBL1 REPLACING ==:KEYL:==   BY ==06==   <----
          *                                ==:REST:==   BY ==07==
          *                                ==:OCCURS:== BY ==400000==
          *                                ==:NOTFND:== BY =='HIGHER'==
          *                                ==:TABLE:==  BY =='ITPMTBL1'==.
          *                                                   ========----\
          *        END PROGRAM YOURPGM1.                                  |
          *                                                               |
          * 4) IN THE PROCEDURE DIVISION, SET THE FUNCTION, SEARCH-KEY,   |
          *     AND FOR 'LOAD', 'ISRT' AND 'REPL' THE TABLE-ENTRY THEN    |
          *     CALL THE MODULE DEFINED BY THE ':TABLE: BY' STATEMENT.    |
          *                                                               |
          *       MOVE MY-SEARCH-KRY TO SEARCH-KEY.                       |
          *       MOVE 'FIND'        TO FUNCTION.                         |
          *       CALL 'ITPMTBL1'    USING CALL-BLOCK TPM-ELEMENT.        |
          *             ========------------------------------------------/
          *       IF SEARCH-KEY = TPM-KEY
          *           PERFORM 1111-MATCHING-ENTRY-FOUND
          *       ELSE
          *           PERFORM 2222-MATCHING-ENTRY-NOT-FOUND
          *       END-IF
          *
          *
          * ***************************************************************
           ENVIRONMENT DIVISION.
           INPUT-OUTPUT SECTION.
           DATA DIVISION.
          ****************************************************************
          *                                                              *
          ****************************************************************
           WORKING-STORAGE SECTION.
           77  WS-START                    PIC X(44)   VALUE
                   'PROGRAM :TABLE:  WORKING STORAGE BEGINS HERE'.
          *
           01  WORK-AREAS.
               05  MAX-ENTRIES          PIC 9(8) COMP VALUE :OCCURS:.
               05  MAX-ENTRIES-1        PIC 9(8) COMP VALUE :OCCURS:.
               05  NOT-FOUND-POS        PIC X(06)     VALUE :NOTFND:.
               05  PGM-ID               PIC X(08)     VALUE :TABLE:.
    
           01  FILLER           VALUE LOW-VALUES.
               05  FILLER               PIC X(:KEYL:).
               05  FILLER               PIC X(:REST:).
           01  KDYNTBL1-TABLE           VALUE HIGH-VALUES.
               05  KDYNTBL1-ELEMENT     OCCURS :OCCURS: TIMES.
                   10  KDYNTBL1-KEY     PIC X(:KEYL:).
                   10  FILLER           PIC X(:REST:).
           01  FILLER           VALUE HIGH-VALUES.
               05  FILLER               PIC X(:KEYL:).
               05  FILLER               PIC X(:REST:).
          *
           01  FILLER                   PIC X(12) VALUE 'HOLD-AREA'.
           01  HOLD-1.
               05  HKEY-1               PIC X(:KEYL:) VALUE SPACES.
               05  FILLER               PIC X(:REST:) VALUE SPACES.
          *
           LINKAGE SECTION.
          *                                                              *
           01  CALL-BLOCK.
               05  REQ-FUNC             PIC X(4).
               05  SEARCH-KEY           PIC X(:KEYL:).
           01  ELEMENT-DATA.
               05  LINK-KEY             PIC X(:KEYL:).
               05  FILLER               PIC X(:REST:).
          *                                                              *
           PROCEDURE DIVISION        USING CALL-BLOCK ELEMENT-DATA.
    
           0500-INITIALIZATION.
               MOVE PGM-ID            TO WS-START (9:8)
               MOVE PGM-ID            TO WS-END   (9:8)
               MOVE PGM-ID            TO DISP02   (6:8)
               MOVE :OCCURS:          TO DISP02N1
               MOVE PGM-ID            TO DISP03   (6:8)
               COMPUTE MAX-90PCT      = :OCCURS: * .90
               COMPUTE MAX-95PCT      = :OCCURS: * .95
               COMPUTE MAX-99PCT      = :OCCURS: * .99
               COMPUTE TOT-TBL-SIZE   = :OCCURS: * (:KEYL: + :REST:)
               .
    
            END PROGRAM :TABLE:.
    

    Perhaps the potential, intended, for the use of multiple table searches in the same program (so multiple COPY statements with, at minimum, a different value for :TABLE:) show a situation where COPY outdoes DEFINE?

     

    Last edit: Simon Sobisch 2014-11-27
    • Brian Tiffin

      Brian Tiffin - 2014-11-27

      Bill; if you get permission, I'd like to add this to the FAQ. Ask on my behalf if you could.

      Cheers,
      Brian

       
    • Simon Sobisch

      Simon Sobisch - 2014-11-27

      Interesting thought while it's not 100% clear why one should use a nested program instead of SEARCH ALL, leading to at least duplicate memory needed for the key part of the table. Likely not clear because of the redaction - I'd like to see the full version contributed (please ask the author for a license of the contribution, too).

      Despite that I did not get the point of

      where COPY outdoes DEFINE

      How would you do something like the COPY does with a DEFINE???

      Simon

       
  • Bill Woodger

    Bill Woodger - 2014-11-28

    Brian,

    I'll ask. Guy is another retiree, and I suspect he won't mind.

    Simon,

    Last thing first, from a previous discussion COPY/REPLACING in its usual use I thought could be replaced by use of DEFINE. With this example, where the same copy can be used more than once in the same program, I was wondering. Same copybook in one program I've also used for FD and WORKING-STORAGE definitions of same layout (without using qualification, which I avoid like the plague).

    I did have a migraine yesterday, so probably thinking even less clear than usual (since I've not used DEFINE except the ones you suggested).

    There are two reasons for using something other than SEARCH ALL: performance; flexibility. The value of the index data-name is undefined when the SEARCH ALL does not get a hit. If you want something else (like key lower than, key higher than, the table-entry not found) then you have to code it yourself.

    Putting it in a contained/nested program negates some of the overhead of having the code in a CALLed program. Overall, more storage will likely be used (multiple program copies) compared to having one dynamically-called module.

    Before I proceed with another round of e-mail discussion on contributions, is the Sudoku solver going into the repository?

     
  • László Erdős

    László Erdős - 2014-11-28

    Hi,

    I've seen "Procedure Division copybooks with replacing". All programs needed parameter from a SQL table ("PARAMETER"). The parameters were dependent on the program name. And there were optional and not optional parameter. There was a small section (in a COPYBOOK) to read the parameter value. And the program name, the parameter type and the target variable (for the parameter value) was made with substitution (COPY ... REPLACING).

    László

     
  • Klaus Schäfer

    Klaus Schäfer - 2014-11-28

    We use procedure-division copies for checking data-input. We have systems, that get input from batch and others, that get input from cics, but the data-checking is the same. So we put the checking-code in the batch- and online-version of the program and so we have the same checking-logig. external calls made sometimes problems in a cics-environment and the message-processing for erros in batch and cics is different - so we used procedure-copies insted of external calls.

     
  • Simon Sobisch

    Simon Sobisch - 2014-11-28

    One old usage case I've seen in sources for a big application was for switches that changed runtime behaviour. These switches were accessed by a COPY statement in PROCEDURE DIVISION like

    ::cobol
           COPY GETVAR REPLACING VARNAME    BY 'THIS-IS-A-SWITCH'
                                 VARCONTENT BY SWITCH-1-VALUE.
          *>
           COPY SETVAR REPLACING VARNAME    BY 'THIS-IS-A-SWITCH'
                                 VARCONTENT BY '2'.
    

    In this case the content of the copies GETVAR and SETVAR were dependent on the system used to compile the sources (most sources were identical on all systems but a bunch of copybooks not). The content of the copybooks looked like

    ::cobol
          *> Variant 1: ENVIRONMENT via ACCEPT/SET
                ACCEPT VARCONTENT FROM ENVIRONMENT VARNAME
                SET ENVIRONMENT VARNAME TO VARCONTENT
    
          *> Variant 2: program that read/write the switches via ISAM file
                CALL 'ISAMSWITCH' USING '0', VARNAME, VARCONTENT
                CALL 'ISAMSWITCH' USING '1', VARNAME, VARCONTENT
    
          *> Variant 3: C program handling the switches (sharing them over network or whatever)
                CALL 'GET_SWITCH_FROM_C_PROG' USING VARNAME, VARCONTENT
                CALL 'SET_SWITCH_BY_C_PROG' USING VARNAME, VARCONTENT
    

    Newer usage cases I've completely rewrote myself (for hire, I don't own copyrights and therefore cannot share the copybooks) and used wherever possible are for file handling in two areas:

    • selecting a record (listing parts of the records on screen and accepting one/multiple records as selection, returning the primary key value(s) to the program)
    • printing the file content (with optional positioning, possible exceptions and lots of functions), you find a very simplified sample below (I've wrote it only for this post and later reference, didn't test it at all ;-)

    program:

    ::cobol
           [...]
          *-----------------------------------------------------------------
          *-----------------------------------------------------------------
           DATA DIVISION.
          *-----------------------------------------------------------------
           FILE SECTION.
           FD  customers.
           01  cu-record.
               03  cu-customerid      PIC 9(08).
               03  cu-name            PIC x(50).
               03  cu-city            PIC x(50).
               [...]
           FD  orders.
           01  co-record.
               03  co-key.
                   05  co-cu-customerid   PIC 9(08).
                   05  co-date            PIC 9(08).
                   05  co-pos             PIC 9(04).
               03  co-p-ident         PIC 9(08).
           FD  parts.
           01  p-record.
               03  p-ident            PIC 9(08).
               03  p-name             PIC x(50).
               03  p-price            PIC s9(08)v99.
               [...]
          *-----------------------------------------------------------------
           WORKING-STORAGE SECTION.
           COPY PRINT-ROUTINES-WK.
          *
               [...]
           77  cl-city-to-print       PIC x(50).
           77  co-customerid-to-print PIC 9(08).
           77  co-date-to-print       PIC x(08).
               [...]
           77  edited-price           PIC Z(07)9.99$.
               [...]
          *-----------------------------------------------------------------
           PROCEDURE DIVISION [...]
          *
               [...]
          *
               MOVE cu-customerid   TO co-customerid-to-print
               MOVE entered-date    TO co-date-to-print
               PERFORM print-customer-order
          *
               [...]
          *
               EXIT PROGRAM.
          *-----------------------------------------------------------------
               [...]
          *-----------------------------------------------------------------
           print-customer-order SECTION.
          *
               OPEN INPUT customers, orders, parts
               READ customers KEY IS cu-customerid
          *
               MOVE SPACES TO print-data
               STRING 'Order of ' FUNCTION TRIM (cu-name) ' '
                      'placed on ' co-date-to-print (1:4) '-'
                      co-date-to-print (5:2) '-' co-date-to-print (7:2)
                      DELIMITED BY SIZE
                      INTO print-data
               END-STRING
          *
               MOVE co-customerid-to-print   TO co-cu-customerid
               MOVE co-date-to-print         TO co-date
               MOVE ZERO                     TO co-pos
               START orders KEY IS EQUAL TO co-key
                  INVALID KEY CONTINUE
               END-START
          *
            COPY PRINT-ROUTINE-TEMPLATE REPLACING
               =='FILENAME'==  BY ==orders==
               =='KEYVALUE-CHANGE'== BY 
               ==IF (co-cu-customerid > co-customerid-to-print) OR
                    (co-date          > co-date-to-print      )
                    EXIT PERFORM
                 END-IF==
               =='RECORDCHECK'== BY ==1 EQUALS 1==
               =='PROVIDE-PRINT-DATA'==  BY
               ==MOVE co-p-ident TO p-ident
                 READ parts KEY IS p-ident
                 MOVE SPACES  TO print-data
                 MOVE p-price TO edited-price
                 STRING p-ident '   ' p-name '    ' edited-price
                        DELIMITED BY SIZE
                        INTO print-data
                 END-STRING==.
          *
               CLOSE customers, orders, parts
          *
               CONTINUE.
          *-----------------------------------------------------------------
          *-----------------------------------------------------------------
           print-customers-all SECTION.
          *
               MOVE SPACES          TO cl-city-to-print
               PERFORM print-customers
          *
               CONTINUE.
          *-----------------------------------------------------------------
           print-customers-berlin SECTION.
               MOVE 'BERLIN'        TO cl-city-to-print
               PERFORM print-customers
          *
               CONTINUE.
          *-----------------------------------------------------------------
           print-customers SECTION.
          *
               OPEN INPUT customers
          *
               MOVE "Customer''s List" TO print-data
          *
            COPY PRINT-ROUTINE-TEMPLATE REPLACING
               =='FILENAME'==  BY ==customers==
               =='KEYVALUE-CHANGE'== BY ==CONTINUE==
               =='RECORDCHECK'== BY
               ==cl-city-to-print EQUALS SPACE OR cu-city==
               =='PROVIDE-PRINT-DATA'==  BY
               ==MOVE SPACES TO print-data
                 STRING cu-customerid '   ' cu-name ' ' cu-city
                        [...]
                        DELIMITED BY SIZE
                        INTO print-data
                 END-STRING==.
          *
               CLOSE customers
          *
               CONTINUE.
          *-----------------------------------------------------------------
          *-----------------------------------------------------------------
          * PRINT-ROUTINES includes the following sections that are called
          *   from outside:   print-init, print-header, print-line,
          *                   print-pagefeed, print-close
          * the main content of all these sections is
          *    SET  print-fnkt-xyz TO TRUE
          *    CALL 'PRINT1' USING print-call-block END-CALL
          *
           COPY PRINT-ROUTINES.
          *-----------------------------------------------------------------
           [...]
    

    copybook PRINT-ROUTINE-TEMPLATE:

    ::cobol
               PERFORM print-init
          *
               PERFORM print-header
          *
               READ 'FILENAME' NEXT RECORD
                  AT END CONTINUE
                  NOT AT END
                     PERFORM UNTIL EXIT
               'KEYVALUE-CHANGE'
          *
                        IF 
               'RECORDCHECK'
          *
               'PROVIDE-PRINT-DATA'
          *
                           PERFORM print-line
                        END-IF
          *
                        READ 'FILENAME' NEXT RECORD
                           AT END EXIT PERFORM
                        END-READ
                     END-PERFORM
               END-READ
          *
               PERFORM print-close
    

    This sample is quite simple, the original version of PRINT-ROUTINE-TEMPLATE had about 1000 lines of code and included options for listing to printer, listing to file [with a nice save-as + "do you want to open the file now" dialogue] or listing to screen.
    After the initial coding every program could come up with a printer/file/screen listing within 1-2 coding hours (copy and paste the REPLACING clause and change it, quick test, finished :-).

    Because of using PROCEDURE DIVISION copybooks with REPLACING instead of copy and paste of the code directly from/into the program sources and do the REPLACING-part by hand, all programs got the option for listing to file for free when it was implemented in the copy book - a simple recompiling of the programs was enough.

    Does anyone think a compilable (not runnable) stub sample of this would be useful in the contrib-repo?

    Simon

     
  • Luke Smith

    Luke Smith - 2014-11-30

    Does anybody have any examples of a procedure division copybook that requires text substitution (COPY...REPLACING). I've never used them and a Google search has only resulted in data division examples. I'm also after the COPY...REPLACING command required to invoke it.

    We use copy files for all of the I/O statements. That way the file status is checked and reported if something goes wrong, line and page numbers incremented, differences are handled between platforms, all counters reset on open and close, and all sorts of other things are done automatically.

    Then I came across a program where two reports are written at the same time. We used the copy replacing to have two sets of I/O routines for the two report files. Then performed PF-WRITE for one and PF2-WRITE for the other. The same for the opens and closes.

     
  • Larry Martin

    Larry Martin - 2022-01-08

    Brian and Simon,

    I am the author of the program from which Bill Woodger provided the excerpt. Are you still pursuing a better understanding of how and why I built this module? The biggest reasons were performance and flexibility. A plug and play answer to many of the problems facing developers when using internal tables.

     
    • Brian Tiffin

      Brian Tiffin - 2022-01-08

      I'm ok, Larry, but I'm sure the group would not mind expanding on a discussion about site specific custom copybooks, and what they can do for refactoring, code reduction and quality of life issues.

      I don't have a pile of production books, but a few oft used ones for programming in the small for examples. A lot of the Intrinsic Function entries in the FAQ are shortened by leveraging COPY, REPLACE, and >>IF

      GnuCOBOL has pretty good coverage of the current Compiler Directing Facility and Text Manipulation phase, and we should toot that horn from time to time, perhaps more frequently than every 7 years. ;-)

      Have good, make well,
      Blue

       
    • Simon Sobisch

      Simon Sobisch - 2022-01-08

      Wow, this discussion contains some code from the times where I was heavily coding (and refactoring) COBOL - nice memories :-)

      To answer the question @larrymartin: the main point back-then (as I see it when reading the old posts) was: this would be a nice code snipped to publish in COBOL documentation - to do so it is necessary to have a copyright notice which allows us to do so.

      But also as Brian said: if you can share some experience about optimization techniques (even if they may not apply to GnuCOBOL) this will be very useful, too. Optimization by copybooks is something I don't remember to see a discussion of.

       
  • Larry Martin

    Larry Martin - 2022-01-10

    I see this module being used extensively to replace SEARCH, SEARCH ALL and PERFORM VARYING….code in new and existing modules. It’s usage in large corporate and government locations can have superior benefits, saving that organization millions of dollars each year. Its reusability will dramatically reduce developer’s time and improve software reliability. It can be used to unit test changes while waiting for DBAs to complete the DB definitions and other functions. My personal experience resulted in a $3.2 million savings in one year based on charge back rates per CPU hour. Once implemented those saving continue year after year.

    Care should be exercised since additional memory will be utilized if the table is new and CPU utilization will drop which will leave the Capacity Planning organization scratching their heads since they seldom see utilization levels decrease. The greater the number of times a lookup is performed, the greater the cost reduction benefit. Review of the SYSOUT from each execution should be reviewed to monitor if table capacity needs expansion.

    This module is stored in a PDS that is accessed via the compile process as a COPYLIB. It can be a member of an existing COPYLIB or a new PDS to be concatenated into existing compile procedures with other COPYLIBs that would house only Procedure Division copybooks and Nested Programs. For the initial implementation, I chose to use an existing COPYLIB to which all known applications had access. Using this option, I chose the first letter of the copy structure name that was the least used or never used at all. For my purposes that was the letter ‘K’. I then titled this Nested Program uniquely as ‘KDYNTBL1’ for Dynamic Table version1. Installation naming standards and conventions should be taken into count.

    I then started a list of problems and limitations with the use of internal tables I had seen over my 40+ years in IT. The last 15 years focused on application performance and triage of production size testing failures at the last minute. These items to be addressed in no order;

    • Effective use of CPU resources and reduced development and execution time.
    • Module is developed using only COBOL with NO 3rd party products.
    • Remove the table definition and allocation from the calling module
    • Allows for multiple different table definitions in the same calling module.
    • Utilize newer capabilities of the COBOL language.
    • Format and populate table elements using the LOAD function.
    • Remove the requirement of pre-sorting table key data before loading for SEARCH ALL activities.
    • Help limit or avoid late night abends caused by table overflow or table over allocation.
    • Ability to establish initial position in table with a FIND and then move forward or backward from that position using the NEXT and PREV commands.
    • Ability to ADD, DELETE, and REPLACE table rows during execution using ISRT, DELT and REPL commands.
    • Allow calling module the ability to take appropriate action on a no matching key condition.
    • Allow for key ranges as a single table entry
    • Provide ability to limit table size to key and only required referenced table data required by the application.
    • Allow the calling program to request the next higher (default) or next lower table entry be returned on a key requested but not found condition.
    • Provide statistics on requested table entries, actual table entries used, percent of table utilized, and if requested, table entries bypassed due to table full condition.
    • Dataset/DB IO operations are the responsibility of the calling module for loading the table.
    • NEW key wild card lookup functions (Requires more testing).

    The limitations for utilizing this module include;
    • USE THIS ROUTINE ONLY IN 'DATA(31)' MODULES.
    • COBOL TABLE SIZE LIMITS APPLY.
    • Best used in a reentry and reusable environment.
    • CONTIGUOUS TABLE KEY must start in position 1 of table element.
    • ONLY ASCENDING KEYS ARE SUPPORTED.
    • TABLE ':KEYL:' AND ':REST:' TOGETHER DETERMINE ENTRY LENGTH
    • ':KEYL:', ':REST:', ':OCCURS:', AND MODULE NAME ARE SET BY THE 'COPY REPLACING ......' STATEMENT.

    I would like to share this module with all that need it, but would like to share in ownership and benefits derived. I am interested in your thoughts.

     
    • Brian Tiffin

      Brian Tiffin - 2022-01-11

      I am not a lawyer, and this is not legal advice, only an opinion.

      Yeah, ownership can still rest in the hands of the author, as the copyright holder. A license that allows others to use the code is the trickier, more option filled choice.

      GnuCOBOL itself is GPL/LGPL, with the code in the main source trees "owned" by the Free Software Foundation, because contributors to the main all sign legal documents to re-assign the copyright. Work on the compiler proper is FSF code.

      We request a free license choice for contributions that are not core, but the copyright remains with the individual contributors, not the GNU Project as managed by the FSF legal entity.

      GPL means people and programmers can freely use the code, but are under an obligation to provide sources when redistributing any code that might uses a GPL component, compile time or run-time.

      LGPL means people can freely use the code, but are not under any obligation to share surrounding code that uses the Lesser licensed sources. You can ship code in binary form, and keep surrounding source private, as long as the user is free to swap out any LGPL components as part of their freedom. GNU licensing has an end-user centric point
      of view. The freedom is all about user freedom, and less about developer freedom and their ability to use free software in a non-free application.

      A license like MIT allows free use, no requirement to share down the line, but it is still owned by the copyright holder, and the license is mostly about keeping the copyright notice in place. There are quite a few options when it comes to licensing free software.

      Sharing in benefits, can be a little trickier when it comes to free software. Any kind of rule in the license starts to run counter to the idea of free software if there are caveats for the user of the software. Fame, sure, fortune, not as much. Dual licensing is a thing, give the user a choice to follow a free license for derived works that are also free, or to make a deal with the copyright holder (which can include fees and royalty obligations) and be allowed to use the code in proprietary closed source systems.

      We can talk more about this Larry, but it is by necessity, only opinion. Here in Canada it is actually illegal to give legal advice if you are not licensed to practice law, hence the famous IANAL, I am not a lawyer acronym. Take a look through the Contributions tree that is here at https://sourceforge.net/p/gnucobol/contrib/HEAD/tree/trunk/ for some examples of how others have licensed their free software contributions.

      Cheers,
      Blue

       
    • Brian Tiffin

      Brian Tiffin - 2022-01-30

      By the by, Larry, do you run any Hercules, MVS? Using the COBOL circa 1972? And the Dr. JCL? ;-)

      I'm on a slow go project, Back in Time, BKNTYM, publish some documented code for COBOL that will compile 1960, and still be of relevant use in the 20s. Fragments, for file loops, utility stuff found in C libraries and other odds and sods.

      On the plate is an ACROYNM command, that has pertinent text from the copious IBM word sets. COBOL that submits to MVS, from the 3270 emulator, or scripted from bash, and runs with GnuCOBOL. The tricky bit is working out the COPY phase powers of 1972 with conditional compilation for deltas between big iron and small tin.

      Then go imaginary, and say yeah, this code is effectively 60 years old, still compiles, still runs, still comes in handy when trying to remember what DASD or KSDS stands for, and why the COBOL compiler source assembly was called IJKFC01 (or somethin' somethin').

      I'd be curious, and interested, but will admit that GnuCOBOL and Hercules time is slow go from here for the now, and days may pass... ;-)

      Have good, make well,
      Blue

       
  • Vincent (Bryan) Coen

    You need the following two manuals :

    GC28-6396-6_IBM_OS_Full_American_National_Standard_COBOL_Apr76.pdf
    GC28-6399-2_COBOL_Compiler_and_Library_Version_2_Programmers_Guide_Jul72.pdf

    You can find them via :

    http://www.applewood.linkpc.net/files/MVS3.8J/PDFs/Cobol/

    Help yourself.

     
    👍
    1

Anonymous
Anonymous

Add attachments
Cancel