Top
NetCOBOL V11.0 Syntax Samples
FUJITSU Software

1.1 Concatenation

The concatenation expression is used for nonnumeric literals.

The concatenation expression is useful for adding control characters because it allows nonnumeric literals, symbolic constants and hexadecimal literals to be connected.

Use caution as Windows functions are invoked in this sample and USER32.LIB stored in the COBOL installation folder (directory) must be included at linkage.

This sample applies to Win32. However, similar processing will be required for linking to C with an operating system other than Win32.

000010 @OPTIONS MAIN,ALPHAL(WORD)
000020*----------------------------------------------------------------------
000030* The concatenation expression can be used to connect nonnumeric
000035* literals.
000040*----------------------------------------------------------------------
000050 IDENTIFICATION   DIVISION.
000060 PROGRAM-ID.      SAMPLE.
000070 DATA             DIVISION.
000080 WORKING-STORAGE  SECTION.
000090 01 TITLE-TXT     PIC X(20).
000100 01 MSG-TXT       PIC X(20).
000110 01 RET           PIC S9(9) COMP-5 VALUE 0.
000120 PROCEDURE        DIVISION.
000130*----------------------------------------------------------------------
000140* Nonnumeric literals can be connected using &.
000150* As shown in the following example, this expression is useful for 
000155* setting null terminating characters when linking to C.
000160*  -> When passing character string data to C, a null character is 
000170*     required at the end of the character string.
000180*     While reference modification could be used to accomplish the same 
000185*     result, the concatenation expression makes for easy and elegant 
000187*     coding.
000190*----------------------------------------------------------------------
000200     MOVE "SAMPLE"        & X"00" TO TITLE-TXT.
000210     MOVE "Hello COBOL!!" & X"00" TO MSG-TXT.
000220*----------------------------------------------------------------------
000230     CALL "MessageBoxA" WITH STDCALL USING BY VALUE     0
000240                                           BY REFERENCE MSG-TXT
000250                                           BY REFERENCE TITLE-TXT
000260                                           BY VALUE     1
000270                                     RETURNING RET.
000280     EXIT PROGRAM.
000290 END PROGRAM SAMPLE.