Menu

linkage section

Anonymous
2022-11-03
2022-11-08
  • Anonymous

    Anonymous - 2022-11-03

    greetings
    running linux, a cobol program with a linkage section
    question is ; how to execute the program and pass it a parameter
    ./name and what next ?
    what is the gnu cobol linux equvalent of exec pgm=myprgram,parm=(myparm)
    I already know I can call program b from program a 'using' - I do not want that
    I want to execute program b and pass it a parameter from the command line in unix
    99.99% of cobol documents are 'hello world' nonsense
    thanks

     
    • Vincent (Bryan) Coen

      On 03/11/2022 15:40, noreply@sourceforge.net wrote:

      greetings
      running linux, a cobol program with a linkage section
      question is ; how to execute the program and pass it a parameter
      ./name and what next ?
      what is the gnu cobol linux equvalent of exec pgm=myprgram,parm=(myparm)
      I already know I can call program b from program a 'using' - I do not
      want that
      I want to execute program b and pass it a parameter from the command
      line in unix
      99.99% of cobol documents are 'hello world' nonsense

      Normally,  a main program does NOT have a linkage section as that is
      used for called Cobol modules (compiled as cobc -m).

      To pass up to 3 parameters to a program you use the Environment
      parameter system such as :

      In W-S :

      01  P1                      pic x(64) value spaces.       > P for
      NONIGHT|NONITE
       01  P2                      pic x(64)     value spaces.
      > P for
      path/filename of CSV data file
       01  P3                      pic x(64)     value spaces. *> P for AFLD-DATE

      Here I test for the values given and store such for further processing .

      In Proc :

      PROCEDURE DIVISION chaining P1 P2 P3.

      ...

      if       P1 (1:2) = "HE" or "he" or "-H" or "-h"
                    display "Parameter Help for " at 0101 with erase eos
                    display Prog-Name at 0120
                    display "P1 = NONIGHT or NONITE for no night time calcs
      against table" at 0301
                    display "P2 = 'CSV=' CSV path and file name for Config
      file if not default"   at 0401
                    display "P3 = ACFT-DATE for report excludes unused
      Aircraft"           at 0501
      >             display "P4 = EBCDIC conversion of CSV data [NOT
      CURRENTLY IN USE]
      "    at 0601
                    display FL006 at 0801
                    accept ws-reply at 0831
                    goback.
      >
           if       P1 (1:8) = "CSV-TEST"
                    set SW-Testing to true
           end-if.
           if       "NONIGHT" = P1 or = P2 or = P3
                    move 1 to NO-NIGHT-Calcs.
           if       "NONITE" = P1 or = P2 or = P3
           move     spaces to P-Temp.
           if       P1 (1:4) = "CSV="  move P1 (5:60) to P-Temp.
           if       P2 (1:4) = "CSV="  move P2 (5:60) to P-Temp.
           if       P3 (1:4) = "CSV="  move P3 (5:60) to P-Temp.
           if       P-Temp (1:8) not = spaces
                    move P-Temp to CSV-Config-Name.
           if       "ACFT-DATE" = P3 or = P2 or = P1
                    move 1 to SW-ACFT-Date.

      There is also a way to test for how many params have been passed using
      Environment values but this example keeps it simple.

      For fancier ways see the Contribs, tools section and program cobxref as
      a program that can accept up to 11+ parameters on the line. I do have
      other examples of such.

      There is a version of cobxref designed for running under MVS and Ansi
      Cobol compiler that does similar but for a M/F and that is in SF as
      cobxref along with the one for GC

      Vince

       
    • Simon Sobisch

      Simon Sobisch - 2022-11-03

      what is the gnu cobol linux equvalent of exec pgm=myprgram,parm=(myparm)
      I already know I can call program b from program a 'using' - I do not want that
      I want to execute program b and pass it a parameter from the command line in unix

      If you combine what you know with what Vince said you can get what you want :-)

      • write a minimal exec.cob and compile that with cobc -x exec.cob - thos gives you a main program you can execute
      • in there do either an ACCEPT FROM COMMAND-LINE to get your argument or use a simple PROCEDURE DIVISION CHAINING EXEC-OPTIONS. (and define EXEC-OPTIONS in WORKING STORAGE)
      • then split that data there into the variable "PGM" and the variable "PARM-DATA", setup "PARM-LENGTH" via MOVE FUNCTION STORED-LENGTH(PARM-DATA) TO PARM-LENGTH
      • then do a CALL PGM USING PARM.

      When this is done you can always do a exec pgm=myprgram,parm=(myparm) and then have myprgram executed with a PARM linkage as expected.

      It would be nice if you could provide the resulting program under a free license so we may add it to GnuCOBOL "extras".

       
  • Simon Sobisch

    Simon Sobisch - 2022-11-03

    ... actually I've found that on my harddisk, in two variants - have fun with it (ideally gets integrated into "extras" before 3.2 rc-1):

     

    Last edit: Simon Sobisch 2022-11-03
    • Gregory A Failing

      Simon, While those programs are excellent examples of command line argument acquisition neither actually uses the 'CHAINING' option. I enclose a small knockoff of the code I came up with to deal with arguments in RMCobol invocations in scripts.

      As you know RMC passes command line arguments by using the -a "arg1 arg2" format. The 'CHAINING' option allowed me to find the contents of the '-a' option and then pass the contents en masse to existing code without modification when transitioning to GC.

      G

       
    • Gregory A Failing

      Simon, Ignore my previous post. I think I misunderstood what was being asked.

      Thanks,

      Gregory

       

Anonymous
Anonymous

Add attachments
Cancel