Concatenate string by its length COBOL

眉间皱痕 提交于 2020-01-23 06:58:41

问题


Need to concatenate 4 strings to a destination variable in cobol.

Like,

01 WS-S1 X(10) VALUE "HI ".
01 WS-S2 X(10) VALUE "HOW ".
01 WS-S3 X(10) VALUE "ARE ".
01 WS-S4 X(10) VALUE "YOU?".

to a resultant string

"HI HOW ARE YOU?"

Can anyone please help me out?


回答1:


Here is a working example of the STRING verb that does what you are looking for:

   IDENTIFICATION DIVISION.
   PROGRAM-ID. EXAMPLE.
   DATA DIVISION.
   WORKING-STORAGE SECTION.
   01    WS-S1 PIC X(10) VALUE 'HI '.
   01    WS-S2 PIC X(10) VALUE 'HOW '.
   01    WS-S3 PIC X(10) VALUE 'ARE '.
   01    WS-S4 PIC X(10) VALUE 'YOU?'.
   01    WS-CONCAT PIC X(43) VALUE SPACES.
   PROCEDURE DIVISION.
   MAIN-PARAGRAPH.
        STRING WS-S1 DELIMITED BY SPACE
               ' '   DELIMITED BY SIZE
               WS-S2 DELIMITED BY SPACE
               ' '   DELIMITED BY SIZE
               WS-S3 DELIMITED BY SPACE
               ' '   DELIMITED BY SIZE
               WS-S4 DELIMITED BY SPACE
          INTO WS-CONCAT
        END-STRING
        DISPLAY '>' WS-CONCAT '<'
        GOBACK
        .

Output is:

>HI HOW ARE YOU?                            <



回答2:


OpenCOBOL has an intrinsic FUNCTION extension, CONCATENATE.

DISPLAY FUNCTION CONCATENATE(
    FUNCTION TRIM(WS-S1); SPACE;
    FUNCTION TRIM(WS-S2); SPACE;
    FUNCTION TRIM(WS-S3); SPACE;
    FUNCTION TRIM(WS-S4))
END-DISPLAY

but I like the STRING verb DELIMITED BY answer, as it'll work with most, if not all, compilers.

As to the reason for semi-colon delimiters inside FUNCTION parameter lists, it isn't strictly necessary, personal preference, as it sometimes avoids potential problems with

SPECIAL-NAMES.
DECIMAL POINT IS COMMA.

and COBOL, being the robust lexical animal that it is

DISPLAY FUNCTION CONCATENATE(WS-S1 WS-S2 WS-S3 WS-S4)
DISPLAY FUNCTION CONCATENATE(WS-S1, WS-S2, WS-S3, WS-S4)

syntax works as well.




回答3:


There is a problem with 'delimited by space'. If ws-s1 = 'how are' - delimited by space will put only 'how'. Here are some examples:

01  ws-string-test.
03 y1                pic x(10) value 'y1 a'.
03 y2                pic x(10) value 'y2 b'.
03 y3                pic x(10) value 'y3 c'.

01 ws-work pic x(200).

       move spaces   to ws-work 
       string y1 delimited by size
              y2 delimited by space
              y3 delimited by size
              into ws-work.
       ws-work = "y1 a      y2y3 c                "

       move spaces   to ws-work 
       string y1  
              y2  
              y3
              delimited by size into ws-work
        ws-work = "y1 a      y2 b           y3 c          "


       string y1  
              y2  
              y3
              delimited by spaces into ws-work. 
        ws-work = "y1y2y3   

       string  y1 y2 y3 into ws-work by csv-format. 
       ws-work = "y1 a,y2 b,y3 c      "

Hope it will help.

zalek




回答4:


Give this a whirl. Should be platform independent.

   DATA DIVISION.

   WORKING-STORAGE SECTION.

   01  result-string-text           X(100).
   01  result-string-length         9(03).
   01  result-string-datalength     9(03).

   01  new-string-text              X(20).
   01  new-string-length            9(03).
   01  new-string-datalength        9(03).

   01  hold-string-text             X(100).

   01  trailing-space-count         9(03).

   PROCEDURE DIVISION.

       MOVE SPACES TO result-string-text.
       MOVE FUNCTION LENGTH(result-string-text) TO result-string-length.
       MOVE FUNCTION LENGTH(new-string-text) TO new-string-length.

       MOVE ws-s1 TO new-string-text.
       PERFORM 5500-concatenate.

       MOVE ws-s2 TO new-string-text.
       PERFORM 5500-concatenate.

       MOVE ws-s3 TO new-string-text.
       PERFORM 5500-concatenate.

       MOVE ws-s4 TO new-string-text.
       PERFORM 5500-concatenate.

   5500-concatenate.
       MOVE ZERO TO trailing-space-count
       INSPECT FUNCTION REVERSE(result-string-text) TALLYING trailing-space-count FOR LEADING ' '
       COMPUTE result-string-datalength = result-string-length - trailing-space-count

       IF (result-string-datalength > ZERO)
           MOVE ZERO TO trailing-space-count
           INSPECT FUNCTION REVERSE(new-string-text) TALLYING trailing-space-count FOR LEADING ' '
           COMPUTE new-string-datalength = new-string-length - trailing-space-count

           MOVE SPACES TO hold-string-text
           STRING
               result-string-text(1:result-string-datalength)
               ' '
               new-string-text(1:new-string-datalength)
                   DELIMITED BY SIZE
           INTO
               hold-string-text
           END-STRING

           MOVE hold-string-text to result-string-text
       ELSE
           MOVE new-string-text TO result-string-text
       END-IF.


来源:https://stackoverflow.com/questions/13966716/concatenate-string-by-its-length-cobol

标签
易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!