Skip to main content

I am trying to create a function that uses a variable parameter list. 

So i can invoke the function like;

function cat(var1, var2) or function cat(var1, var2, var3) or function cat(var1, var2, var3, var4) etc

Everything I try causes a crash or fails to work.

My latest attempt is trying to implement the "REPEATED" option of the USING clause which doesn't crash but it also doesn't work;

Function;

      $set preservecase case repository(update ON)
       ID DIVISION.      
       FUNCTION-ID. CAT.
       WORKING-STORAGE SECTION.
       01 WS-BUFFER    PIC X(1024) VALUE SPACES.
       01 WS-FUNC      PIC 9(2) COMP VALUE 16.
       01 WS-RESULT    PIC 9(2) COMP.
       01 WS-PARMS     PIC 99 COMP.
       01 WS-SIZE      PIC 9(5).  
       01 P            PIC 9(3).
       01 R            PIC XXX COMP-X.
       LINKAGE SECTION.
       01 STR         PIC X(1024) OCCURS 10.
       
       01 RESULT       PIC X(1024).
       
       PROCEDURE DIVISION USING STR REPEATED  
                          RETURNING RESULT.

           CALL X"91" USING WS-RESULT WS-FUNC WS-PARMS.
           display "parameters=" ws-parms

           SET R TO 1
           PERFORM VARYING P FROM 1 BY 1 UNTIL P > WS-PARMS
               CALL "C$PARAMSIZE" USING P GIVING WS-SIZE
               display "size=" ws-size
               MOVE STR(P)(1:WS-SIZE) TO RESULT(R:WS-SIZE)
               ADD WS-SIZE TO R
           END-PERFORM

           GOBACK.

       END FUNCTION CAT.

Calling program;

       identification division.
       program-id. Program1.
       environment division.
       repository.
           function CAT.
       data division.
       working-storage section.
       01 parm1 pic x(8) value "tony".
       01 parm2 pic x(8) value "blink".
       
       procedure division.
       
           display function CAT(parm1, parm2)
           accept parm1.
           goback.
           
       end program Program1.

I am working with Visual COBOL and a INT/GNT output project

Any help at all is very much appreciated


#VisualCOBOL
#Windows
#error

I am trying to create a function that uses a variable parameter list. 

So i can invoke the function like;

function cat(var1, var2) or function cat(var1, var2, var3) or function cat(var1, var2, var3, var4) etc

Everything I try causes a crash or fails to work.

My latest attempt is trying to implement the "REPEATED" option of the USING clause which doesn't crash but it also doesn't work;

Function;

      $set preservecase case repository(update ON)
       ID DIVISION.      
       FUNCTION-ID. CAT.
       WORKING-STORAGE SECTION.
       01 WS-BUFFER    PIC X(1024) VALUE SPACES.
       01 WS-FUNC      PIC 9(2) COMP VALUE 16.
       01 WS-RESULT    PIC 9(2) COMP.
       01 WS-PARMS     PIC 99 COMP.
       01 WS-SIZE      PIC 9(5).  
       01 P            PIC 9(3).
       01 R            PIC XXX COMP-X.
       LINKAGE SECTION.
       01 STR         PIC X(1024) OCCURS 10.
       
       01 RESULT       PIC X(1024).
       
       PROCEDURE DIVISION USING STR REPEATED  
                          RETURNING RESULT.

           CALL X"91" USING WS-RESULT WS-FUNC WS-PARMS.
           display "parameters=" ws-parms

           SET R TO 1
           PERFORM VARYING P FROM 1 BY 1 UNTIL P > WS-PARMS
               CALL "C$PARAMSIZE" USING P GIVING WS-SIZE
               display "size=" ws-size
               MOVE STR(P)(1:WS-SIZE) TO RESULT(R:WS-SIZE)
               ADD WS-SIZE TO R
           END-PERFORM

           GOBACK.

       END FUNCTION CAT.

Calling program;

       identification division.
       program-id. Program1.
       environment division.
       repository.
           function CAT.
       data division.
       working-storage section.
       01 parm1 pic x(8) value "tony".
       01 parm2 pic x(8) value "blink".
       
       procedure division.
       
           display function CAT(parm1, parm2)
           accept parm1.
           goback.
           
       end program Program1.

I am working with Visual COBOL and a INT/GNT output project

Any help at all is very much appreciated


#VisualCOBOL
#Windows
#error

Your first post where you were receiving a 114 error appeared to be caused by the name of the function having the same name as a C function STRCAT. When I changed the name to STRCAT2 then the 114 error went away.

You can use the REPEATED phrase to pass variable parameters to a function but the parameters being passed must be defined as the same length as used in the table with the REPEATED phrase on it. For example if you made parm1 and parm2 pic x(1024) then it would work. This means that all of your parameters have to be defined the same. The number of parameters returned by the X"91" function will always be the same because the table counts as 1 parameter regardless of how many occurences are in it. Any table items that weren't being used would be empty.

Alternatively, you could specify the parameters in the function as optional and then they can be omitted but the OMITTED phrase would have to be used in the calling program for any parameters that were missing., Example: display function cat(param1, omitted). 

This is very easy to do in managed code as you can create a method with an overloaded constructer for each possibility but it is not so easy in native code which I assume you are using.


Your first post where you were receiving a 114 error appeared to be caused by the name of the function having the same name as a C function STRCAT. When I changed the name to STRCAT2 then the 114 error went away.

You can use the REPEATED phrase to pass variable parameters to a function but the parameters being passed must be defined as the same length as used in the table with the REPEATED phrase on it. For example if you made parm1 and parm2 pic x(1024) then it would work. This means that all of your parameters have to be defined the same. The number of parameters returned by the X"91" function will always be the same because the table counts as 1 parameter regardless of how many occurences are in it. Any table items that weren't being used would be empty.

Alternatively, you could specify the parameters in the function as optional and then they can be omitted but the OMITTED phrase would have to be used in the calling program for any parameters that were missing., Example: display function cat(param1, omitted). 

This is very easy to do in managed code as you can create a method with an overloaded constructer for each possibility but it is not so easy in native code which I assume you are using.

When i match the parameter sizes using REPEATED they have blank values and C$PARMS returns the wrong value (2 instead of 3)

Is that the way you use REPEATED, The parameter being an array?

Unfortunately managed code is not an option.

Thank you very much for your help. I appreciate it

      $set preservecase case repository(update ON)
       ID DIVISION.      
       FUNCTION-ID. CAT.
       WORKING-STORAGE SECTION.
       01 WS-BUFFER    PIC X(1024) VALUE SPACES.
       01 WS-FUNC      PIC 9(2) COMP VALUE 16.
       01 WS-RESULT    PIC 9(2) COMP.
       01 WS-PARMS     PIC 99 COMP.
       01 WS-SIZE      PIC 9(5).  
       01 P            PIC 9(3).
       01 R            PIC XXX COMP-X.

       LINKAGE SECTION.
       01 STR        PIC X(1024) OCCURS 10.
       01 RESULT      PIC X(1024).
       
       PROCEDURE DIVISION USING STR repeated  
                          RETURNING RESULT.

           CALL X"91" USING WS-RESULT WS-FUNC WS-PARMS.
           display "parameters=" ws-parms

           SET R TO 1
           PERFORM VARYING P FROM 1 BY 1 UNTIL P = WS-PARMS
               CALL "C$PARAMSIZE" USING P GIVING WS-SIZE
               display "size=" ws-size
               MOVE STR(p)(1:WS-SIZE) TO RESULT(R:WS-SIZE)
               ADD WS-SIZE TO R
           END-PERFORM
           GOBACK.

       END FUNCTION CAT.

Calling program

      
       identification division.
       program-id. Program1.
       environment division.
       repository.
           function CAT.
       data division.
       working-storage section.
       01 parm1 pic x(1024) value "tony".
       01 parm2 pic x(1024) value "blink".
       01 parm3 pic x(1024) value "another".
       01 result pic x(1024) value spaces.
       procedure division.
       
           move function CAT(parm1, parm2, parm3) to result
           display result
           accept result
           goback.
           
       end program Program1.

My output looks like

parameters=02 
size=01024    


When i match the parameter sizes using REPEATED they have blank values and C$PARMS returns the wrong value (2 instead of 3)

Is that the way you use REPEATED, The parameter being an array?

Unfortunately managed code is not an option.

Thank you very much for your help. I appreciate it

      $set preservecase case repository(update ON)
       ID DIVISION.      
       FUNCTION-ID. CAT.
       WORKING-STORAGE SECTION.
       01 WS-BUFFER    PIC X(1024) VALUE SPACES.
       01 WS-FUNC      PIC 9(2) COMP VALUE 16.
       01 WS-RESULT    PIC 9(2) COMP.
       01 WS-PARMS     PIC 99 COMP.
       01 WS-SIZE      PIC 9(5).  
       01 P            PIC 9(3).
       01 R            PIC XXX COMP-X.

       LINKAGE SECTION.
       01 STR        PIC X(1024) OCCURS 10.
       01 RESULT      PIC X(1024).
       
       PROCEDURE DIVISION USING STR repeated  
                          RETURNING RESULT.

           CALL X"91" USING WS-RESULT WS-FUNC WS-PARMS.
           display "parameters=" ws-parms

           SET R TO 1
           PERFORM VARYING P FROM 1 BY 1 UNTIL P = WS-PARMS
               CALL "C$PARAMSIZE" USING P GIVING WS-SIZE
               display "size=" ws-size
               MOVE STR(p)(1:WS-SIZE) TO RESULT(R:WS-SIZE)
               ADD WS-SIZE TO R
           END-PERFORM
           GOBACK.

       END FUNCTION CAT.

Calling program

      
       identification division.
       program-id. Program1.
       environment division.
       repository.
           function CAT.
       data division.
       working-storage section.
       01 parm1 pic x(1024) value "tony".
       01 parm2 pic x(1024) value "blink".
       01 parm3 pic x(1024) value "another".
       01 result pic x(1024) value spaces.
       procedure division.
       
           move function CAT(parm1, parm2, parm3) to result
           display result
           accept result
           goback.
           
       end program Program1.

My output looks like

parameters=02 
size=01024    

You are stringing the result in incorrectly as the parm-size will always be 1024.

Others may have a better suggestion on how to do this but what about just packing your parameters into an array and passing the number of elements as part of the parameter also. The following example does that and then does the CAT of the 3 strings while removing trailing spaces from each. It isn't exactly what you are looking for but it works.

      $set preservecase case repository(update ON)
       ID DIVISION.      
       FUNCTION-ID. CAT.
       WORKING-STORAGE SECTION.
       01 WS-SIZE      PIC 9(5) value zeroes.  
       01 ws-size-hold pic 9(5) value zeroes.
       01 string-point pic 9(3).
       01 P            PIC 9(3).
       LINKAGE SECTION.
       01 parm-array.
          05 num-parms pic 9(2).
          05 parms     pic x(1024) occurs 10 times.
       01 RESULT       PIC X(1024).
       
       PROCEDURE DIVISION USING parm-array
                          RETURNING RESULT.


           display "parameters=" num-parms
           move spaces to RESULT
           move zeroes to ws-size 
           move 1 to string-point ws-size-hold
           
           PERFORM VARYING P FROM 1 BY 1 UNTIL P > num-parms
              string function trim(parms(p)) into result
                   with pointer string-point
              end-string
              compute WS-SIZE = string-point - WS-SIZE-HOLD
              display "size=" ws-size
              move string-point to ws-size-hold
           end-perform
           GOBACK.

       END FUNCTION CAT.

       identification division.
       program-id. Program1.
       environment division.
       repository.
           function CAT.
       data division.
       working-storage section.
       01 parm1     pic x(1024) value "tony".
       01 parm2     pic x(1024) value "blink".
       01 parm3     pic x(1024) value "another".
       01 parm-array.
          05 num-parms pic 9(2) value zeroes.
          05 parms     pic x(1024) occurs 10 times.
       
       01 result    pic x(1024) value spaces.
       procedure division.
       
           move parm1 to parms(1)
           move parm2 to parms(2)
           move parm3 to parms(3)
           move 3 to num-parms
           move function CAT(parm-array) to result
           display result
           accept result
           goback.
           


You are stringing the result in incorrectly as the parm-size will always be 1024.

Others may have a better suggestion on how to do this but what about just packing your parameters into an array and passing the number of elements as part of the parameter also. The following example does that and then does the CAT of the 3 strings while removing trailing spaces from each. It isn't exactly what you are looking for but it works.

      $set preservecase case repository(update ON)
       ID DIVISION.      
       FUNCTION-ID. CAT.
       WORKING-STORAGE SECTION.
       01 WS-SIZE      PIC 9(5) value zeroes.  
       01 ws-size-hold pic 9(5) value zeroes.
       01 string-point pic 9(3).
       01 P            PIC 9(3).
       LINKAGE SECTION.
       01 parm-array.
          05 num-parms pic 9(2).
          05 parms     pic x(1024) occurs 10 times.
       01 RESULT       PIC X(1024).
       
       PROCEDURE DIVISION USING parm-array
                          RETURNING RESULT.


           display "parameters=" num-parms
           move spaces to RESULT
           move zeroes to ws-size 
           move 1 to string-point ws-size-hold
           
           PERFORM VARYING P FROM 1 BY 1 UNTIL P > num-parms
              string function trim(parms(p)) into result
                   with pointer string-point
              end-string
              compute WS-SIZE = string-point - WS-SIZE-HOLD
              display "size=" ws-size
              move string-point to ws-size-hold
           end-perform
           GOBACK.

       END FUNCTION CAT.

       identification division.
       program-id. Program1.
       environment division.
       repository.
           function CAT.
       data division.
       working-storage section.
       01 parm1     pic x(1024) value "tony".
       01 parm2     pic x(1024) value "blink".
       01 parm3     pic x(1024) value "another".
       01 parm-array.
          05 num-parms pic 9(2) value zeroes.
          05 parms     pic x(1024) occurs 10 times.
       
       01 result    pic x(1024) value spaces.
       procedure division.
       
           move parm1 to parms(1)
           move parm2 to parms(2)
           move parm3 to parms(3)
           move 3 to num-parms
           move function CAT(parm-array) to result
           display result
           accept result
           goback.
           

Thank you very much for your time and effort. I do appreciate it.

Unfortunately I do not have the luxury of using work fields. The whole idea here is to minimize the code in the calling program as sometimes this may have to accomodate 40 or more parameters.

If possible, could you show me how to implement a variable using parameter list?

I am sure as long as i can reference a variable parameter list then i can solve the problem.

Thanks again


Thank you very much for your time and effort. I do appreciate it.

Unfortunately I do not have the luxury of using work fields. The whole idea here is to minimize the code in the calling program as sometimes this may have to accomodate 40 or more parameters.

If possible, could you show me how to implement a variable using parameter list?

I am sure as long as i can reference a variable parameter list then i can solve the problem.

Thanks again

The only way I can find to code this as a function is to use the OMITTED keyword for parameters that are missing. This is because the returning parameter is also passed as a parameter and unless the other parameters are present or OMITTED you can not reference the RETURNING parameter.

I can get this to work when it instead calls a subprogram and the result field is passed directly as a parameter.

Here are the examples of each. These examples assume a maximum of 5 parameters being passed.

The function:

      $set preservecase case repository(update ON)
       id division.      
       function-id. CAT.
       working-storage section.
       01 ws-size      pic 9(5) value zeroes.  
       01 ws-size-hold pic 9(5) value zeroes.
       01 string-point pic 9(3).
       01 sub-1        pic 9(3).
       01 num-params   pic 9(3) value zeroes.
       01 ws-param-table.
          05 ws-param  pic x(10) occurs 10 times.
       linkage section.
       01 param1        pic x(10).
       01 param2        pic x(10).
       01 param3        pic x(10).
       01 param4        pic x(10).
       01 param5        pic x(10).
       01 result        pic x(1024).
       
       procedure division using optional param1
                                optional param2
                                optional param3
                                optional param4 
                                optional param5 
                          returning result.

           
           perform 100-find-param-num
           display num-params
           move spaces to result
           if num-params = 0
              goback
           end-if

           move zeroes to ws-size 
           move 1 to string-point ws-size-hold
          
           perform varying sub-1 from 1 by 1 until sub-1 > num-params
              string function trim(ws-param(sub-1)) into result
                  with pointer string-point
              end-string
              compute ws-size = string-point - ws-size-hold
              display "size=" ws-size
              move string-point to ws-size-hold
           end-perform
           goback.
       100-find-param-num.

           move zeroes to num-params
           if address of param1 not = null
               move param1 to ws-param(1)
               add 1 to num-params
           end-if
           if address of param2 not = null
               move param2 to ws-param(2)
               add 1 to num-params
           end-if
           if address of param3 not = null
               move param3 to ws-param(3)
               add 1 to num-params
           end-if
           if address of param4 not = null
               move param4 to ws-param(4)
               add 1 to num-params
           end-if
           if address of param5 not = null
               move param5 to ws-param(5)
               add 1 to num-params
           end-if.
           
       end function CAT.

The subprogram:

       id division.      
       program-id. CATPROG.
       working-storage section.
       01 ws-size      pic 9(5) value zeroes.  
       01 ws-size-hold pic 9(5) value zeroes.
       01 string-point pic 9(3).
       01 sub-1        pic 9(3).
       01 num-params   pic 9(3) value zeroes.
       01 ws-param-table.
          05 ws-param  pic x(10) occurs 10 times.
       linkage section.
       01 result        pic x(1024).
       01 param1        pic x(10).
       01 param2        pic x(10).
       01 param3        pic x(10).
       01 param4        pic x(10).
       01 param5        pic x(10).
       procedure division using result
                                param1
                                param2
                                param3
                                param4 
                                param5 .

           
           perform 100-find-param-num
           display num-params
           move spaces to result
           if num-params = 0
              goback
           end-if

           move zeroes to ws-size 
           move 1 to string-point ws-size-hold
          
           perform varying sub-1 from 1 by 1 until sub-1 > num-params
              string function trim(ws-param(sub-1)) into result
                  with pointer string-point
              end-string
              compute ws-size = string-point - ws-size-hold
              display "size=" ws-size
              move string-point to ws-size-hold
           end-perform
           goback.
       100-find-param-num.

           move zeroes to num-params
           if address of param1 not = null
               move param1 to ws-param(1)
               add 1 to num-params
           end-if
           if address of param2 not = null
               move param2 to ws-param(2)
               add 1 to num-params
           end-if
           if address of param3 not = null
               move param3 to ws-param(3)
               add 1 to num-params
           end-if
           if address of param4 not = null
               move param4 to ws-param(4)
               add 1 to num-params
           end-if
           if address of param5 not = null
               move param5 to ws-param(5)
               add 1 to num-params
           end-if.

       end program CATPROG.

The calling program:

       id division.      
       program-id. CATPROG is external.
       working-storage section.
       linkage section.
       01 result        pic x(1024).
       01 param1        pic x(10).
       procedure division using result
                                param1 repeated 1 to 5.
       end program CATPROG.
       identification division.
       program-id. Program1.
       environment division.
       repository.
           function CAT.
       data division.
       working-storage section.
       01 param1     pic x(10) value "tony".
       01 param2     pic x(10) value "blink".
       01 param3     pic x(10) value "another".
       
       01 result    pic x(1024) value spaces.
       procedure division.
       
           call "CATPROG" using result param1 param2 param3
           display result

           move function CAT(param1 param2 param3 omitted omitted)
              to result
           display result
           accept result
           goback.
           
       end program Program1.


The only way I can find to code this as a function is to use the OMITTED keyword for parameters that are missing. This is because the returning parameter is also passed as a parameter and unless the other parameters are present or OMITTED you can not reference the RETURNING parameter.

I can get this to work when it instead calls a subprogram and the result field is passed directly as a parameter.

Here are the examples of each. These examples assume a maximum of 5 parameters being passed.

The function:

      $set preservecase case repository(update ON)
       id division.      
       function-id. CAT.
       working-storage section.
       01 ws-size      pic 9(5) value zeroes.  
       01 ws-size-hold pic 9(5) value zeroes.
       01 string-point pic 9(3).
       01 sub-1        pic 9(3).
       01 num-params   pic 9(3) value zeroes.
       01 ws-param-table.
          05 ws-param  pic x(10) occurs 10 times.
       linkage section.
       01 param1        pic x(10).
       01 param2        pic x(10).
       01 param3        pic x(10).
       01 param4        pic x(10).
       01 param5        pic x(10).
       01 result        pic x(1024).
       
       procedure division using optional param1
                                optional param2
                                optional param3
                                optional param4 
                                optional param5 
                          returning result.

           
           perform 100-find-param-num
           display num-params
           move spaces to result
           if num-params = 0
              goback
           end-if

           move zeroes to ws-size 
           move 1 to string-point ws-size-hold
          
           perform varying sub-1 from 1 by 1 until sub-1 > num-params
              string function trim(ws-param(sub-1)) into result
                  with pointer string-point
              end-string
              compute ws-size = string-point - ws-size-hold
              display "size=" ws-size
              move string-point to ws-size-hold
           end-perform
           goback.
       100-find-param-num.

           move zeroes to num-params
           if address of param1 not = null
               move param1 to ws-param(1)
               add 1 to num-params
           end-if
           if address of param2 not = null
               move param2 to ws-param(2)
               add 1 to num-params
           end-if
           if address of param3 not = null
               move param3 to ws-param(3)
               add 1 to num-params
           end-if
           if address of param4 not = null
               move param4 to ws-param(4)
               add 1 to num-params
           end-if
           if address of param5 not = null
               move param5 to ws-param(5)
               add 1 to num-params
           end-if.
           
       end function CAT.

The subprogram:

       id division.      
       program-id. CATPROG.
       working-storage section.
       01 ws-size      pic 9(5) value zeroes.  
       01 ws-size-hold pic 9(5) value zeroes.
       01 string-point pic 9(3).
       01 sub-1        pic 9(3).
       01 num-params   pic 9(3) value zeroes.
       01 ws-param-table.
          05 ws-param  pic x(10) occurs 10 times.
       linkage section.
       01 result        pic x(1024).
       01 param1        pic x(10).
       01 param2        pic x(10).
       01 param3        pic x(10).
       01 param4        pic x(10).
       01 param5        pic x(10).
       procedure division using result
                                param1
                                param2
                                param3
                                param4 
                                param5 .

           
           perform 100-find-param-num
           display num-params
           move spaces to result
           if num-params = 0
              goback
           end-if

           move zeroes to ws-size 
           move 1 to string-point ws-size-hold
          
           perform varying sub-1 from 1 by 1 until sub-1 > num-params
              string function trim(ws-param(sub-1)) into result
                  with pointer string-point
              end-string
              compute ws-size = string-point - ws-size-hold
              display "size=" ws-size
              move string-point to ws-size-hold
           end-perform
           goback.
       100-find-param-num.

           move zeroes to num-params
           if address of param1 not = null
               move param1 to ws-param(1)
               add 1 to num-params
           end-if
           if address of param2 not = null
               move param2 to ws-param(2)
               add 1 to num-params
           end-if
           if address of param3 not = null
               move param3 to ws-param(3)
               add 1 to num-params
           end-if
           if address of param4 not = null
               move param4 to ws-param(4)
               add 1 to num-params
           end-if
           if address of param5 not = null
               move param5 to ws-param(5)
               add 1 to num-params
           end-if.

       end program CATPROG.

The calling program:

       id division.      
       program-id. CATPROG is external.
       working-storage section.
       linkage section.
       01 result        pic x(1024).
       01 param1        pic x(10).
       procedure division using result
                                param1 repeated 1 to 5.
       end program CATPROG.
       identification division.
       program-id. Program1.
       environment division.
       repository.
           function CAT.
       data division.
       working-storage section.
       01 param1     pic x(10) value "tony".
       01 param2     pic x(10) value "blink".
       01 param3     pic x(10) value "another".
       
       01 result    pic x(1024) value spaces.
       procedure division.
       
           call "CATPROG" using result param1 param2 param3
           display result

           move function CAT(param1 param2 param3 omitted omitted)
              to result
           display result
           accept result
           goback.
           
       end program Program1.

Thank you very much for your time chris. I really appreciate it.

I'm thinking that 30 or 40 omitted phrases might be a little too verbose for the client.

Do you think there is a compiler switch that would stop it from throwing an error when the number of parameters didn't match?

Similar functionality to the CALL statement.


Thank you very much for your time chris. I really appreciate it.

I'm thinking that 30 or 40 omitted phrases might be a little too verbose for the client.

Do you think there is a compiler switch that would stop it from throwing an error when the number of parameters didn't match?

Similar functionality to the CALL statement.

There is no compiler directive that will allow this to work successfully. It is not supported, unfortunately, in native code as long as there is a returning phrase being used. 


There is no compiler directive that will allow this to work successfully. It is not supported, unfortunately, in native code as long as there is a returning phrase being used. 

Thank you very much for your time and patience chris. I do appreciate it