Skip to main content

Hi,

We have the exact same data.bin file including binary data on an HP-UX machine and a RedHat Linux machine.

  • HP-UX(big-endian):

smppru@bayyana:/cralm/simep/prue/Arquitectura/testreadbindata> od -x data.bin | head -1 | nl
1  0000000 0fcc 0000 00bc 0000 f1f6 f4f4 8030 0198

  • Linux RedHat(little-endian):

int-cob-d-01u:/cralm/simep/prue/apps/testreadbindata>od -x data.bin | head -1 | nl
1  0000000 cc0f 0000 bc00 0000 f6f1 f4f4 3080 9801

I have created a Cobol program that retrieves two of these binary data in COMP-5 variables and displays them on the screen, thus being able to verify that the binary data is interpreted differently on the HP-UX(big-endian) and Linux(little-endian) platforms.

The code of the executed program is exactly the same on both the HP-UX and Linux platforms:

     1         IDENTIFICATION DIVISION.
     2         PROGRAM-ID. testreadbindata.
     3
     4         ENVIRONMENT DIVISION.
     5         CONFIGURATION SECTION.
     6         SOURCE-COMPUTER. UNIX.
     7         OBJECT-COMPUTER. UNIX.
     8
     9         SPECIAL-NAMES.
    10              DECIMAL-POINT IS COMMA.
    11
    12         INPUT-OUTPUT SECTION.
    13
    14         FILE-CONTROL.
    15             SELECT EPRLVORSE  ASSIGN TO "./data.bin".
    16
    17         DATA DIVISION.
    18         FILE SECTION.
    19
    20         FD  EPRLVORSE
    21             BLOCK CONTAINS 4096 CHARACTERS.
    22
    23         01  REG-EPRLVORSE.
    24             05  W4096X-EPRLVORSE       PIC X(4096).
    25
    26         WORKING-STORAGE SECTION.
    27
    28         01  RREG-ENTRADA   PIC X(4096).
    29         01  REG-ENTRADA REDEFINES RREG-ENTRADA.
    30             05  W4P-VLIENT   PIC 9(4) COMP-5.
    31             05  W4P-FILLER1  PIC 9(4) COMP-5.
    32             05  W4P-VLISUB   PIC 9(4) COMP-5.
    33             05  W4P-FILLER2  PIC 9(4) COMP-5.
    34             05  W4088X-RESTO PIC X(4088).
    35    
    36         01  W1X-VLI-AUX      PIC X(1).
    37
    38         01  W4P-VLI-AUX      PIC 9(4) COMP-5.
    39         01  FILLER-VLI REDEFINES W4P-VLI-AUX.
    40             05 W1X-VLIA-1    PIC X(1).
    41             05 W1X-VLIA-2    PIC X(1).
    42
    43         01  W4X-VLI-ACT.
    44             05  W4P-VLI-WRK  PIC 9(4) COMP-5.
    45             05  W4P-FILLER3  PIC 9(4) COMP-5.
    46
    47         01  W1X-FIN          PIC X VALUE '0'.
    48             88  FIN-EPRLVORSE      VALUE 'F'.
    49
    50         01  K1XF             PIC X VALUE 'F'.
    51
    52         PROCEDURE DIVISION.
    53
    54             OPEN INPUT  EPRLVORSE.
    55
    56             READ EPRLVORSE INTO REG-ENTRADA
    57                AT END MOVE K1XF TO W1X-FIN
    58                NOT AT END
    59                DISPLAY 'testreadbindata::W4P-VLIENT: [' W4P-VLIENT '].'.
    60                DISPLAY 'testreadbindata::W4P-VLISUB: [' W4P-VLISUB '].'.
    61             CLOSE EPRLVORSE.
    62             STOP RUN.

The outputs of the testreadbindata program on both platforms are different::

•    HP-UX:

smppru@bayyana:/cralm/simep/prue/Arquitectura/testreadbindata> testreadbindata
testreadbindata::W4P-VLIENT: [04044] - 0000 1111 1100 1100(binary) - 0FCC(hex) -> BIG ENDIAN
testreadbindata::W4P-VLISUB: [00188] - 0000 0000 1011 1100(binary) - 00BC(hex) -> BIG ENDIAN

•    Linux:

int-cob-d-01u:/cralm/simep/prue/apps/testreadbindata>testreadbindata
testreadbindata::W4P-VLIENT: [52239] - 1100 1100 0000 1111(binary) - CC0F(hex) -> LITTLE ENDIAN
testreadbindata::W4P-VLISUB: [48128] – 1011 1100 0000 0000(binary) - BC00(hex) -> LITTLE ENDIAN

How should we proceed so that the data retrieved by the testreadbindata program on the Linux RedHat platform from the binary file in COMP-5 variables are exactly the same as those retrieved by the testreadbindata program on the HP-UX platform?

Thanks a lot.

Regards.

<------------------------------------------------------------------------------------------------------------------------------>
Platform information:

•    HP-UX:

smppru@bayyana:/opt/microfocus/cobol/etc> cat cobver
ServerExpress cobol v5.1.00
PRN=RXCAQ/AAP:9p.k5.51.07
PTI=WrapPack 6
PTI=ES

smppru@bayyana:/opt/microfocus/cobol/etc> uname -a
HP-UX bayyana B.11.31 U ia64 0804249662 unlimited-user license


•    Linux:

int-cob-d-01u:/cralm/simep/prue/uxna/bdon>cat $COBDIR/etc/cobver
Visual cobol v7.0.0
PRN=K1CRH/AAK:Ao.U4.13.04
PTI=32/64 bit
PTI=Micro Focus COBOL Server 7.0 - Patch Update 08
PTI=Patch Update 08
PTI=pkg_303630
PTI=MFInstaller


int-cob-d-01u:/cralm/simep/prue/uxna/bdon>cat /etc/os-release
NAME="Red Hat Enterprise Linux Server"
VERSION="7.9 (Maipo)"
ID="rhel"
ID_LIKE="fedora"
VARIANT="Server"
VARIANT_ID="server"
VERSION_ID="7.9"
PRETTY_NAME="Red Hat Enterprise Linux Server 7.9 (Maipo)"
ANSI_COLOR="0;31"
CPE_NAME="cpe:/o:redhat:enterprise_linux:7.9:GA:server"
HOME_URL="">https://www.redhat.com/"
BUG_REPORT_URL="
">bugzilla.redhat.com/"

REDHAT_BUGZILLA_PRODUCT="Red Hat Enterprise Linux 7"
REDHAT_BUGZILLA_PRODUCT_VERSION=7.9
REDHAT_SUPPORT_PRODUCT="Red Hat Enterprise Linux"
REDHAT_SUPPORT_PRODUCT_VERSION="7.9"

Hi,

We have the exact same data.bin file including binary data on an HP-UX machine and a RedHat Linux machine.

  • HP-UX(big-endian):

smppru@bayyana:/cralm/simep/prue/Arquitectura/testreadbindata> od -x data.bin | head -1 | nl
1  0000000 0fcc 0000 00bc 0000 f1f6 f4f4 8030 0198

  • Linux RedHat(little-endian):

int-cob-d-01u:/cralm/simep/prue/apps/testreadbindata>od -x data.bin | head -1 | nl
1  0000000 cc0f 0000 bc00 0000 f6f1 f4f4 3080 9801

I have created a Cobol program that retrieves two of these binary data in COMP-5 variables and displays them on the screen, thus being able to verify that the binary data is interpreted differently on the HP-UX(big-endian) and Linux(little-endian) platforms.

The code of the executed program is exactly the same on both the HP-UX and Linux platforms:

     1         IDENTIFICATION DIVISION.
     2         PROGRAM-ID. testreadbindata.
     3
     4         ENVIRONMENT DIVISION.
     5         CONFIGURATION SECTION.
     6         SOURCE-COMPUTER. UNIX.
     7         OBJECT-COMPUTER. UNIX.
     8
     9         SPECIAL-NAMES.
    10              DECIMAL-POINT IS COMMA.
    11
    12         INPUT-OUTPUT SECTION.
    13
    14         FILE-CONTROL.
    15             SELECT EPRLVORSE  ASSIGN TO "./data.bin".
    16
    17         DATA DIVISION.
    18         FILE SECTION.
    19
    20         FD  EPRLVORSE
    21             BLOCK CONTAINS 4096 CHARACTERS.
    22
    23         01  REG-EPRLVORSE.
    24             05  W4096X-EPRLVORSE       PIC X(4096).
    25
    26         WORKING-STORAGE SECTION.
    27
    28         01  RREG-ENTRADA   PIC X(4096).
    29         01  REG-ENTRADA REDEFINES RREG-ENTRADA.
    30             05  W4P-VLIENT   PIC 9(4) COMP-5.
    31             05  W4P-FILLER1  PIC 9(4) COMP-5.
    32             05  W4P-VLISUB   PIC 9(4) COMP-5.
    33             05  W4P-FILLER2  PIC 9(4) COMP-5.
    34             05  W4088X-RESTO PIC X(4088).
    35    
    36         01  W1X-VLI-AUX      PIC X(1).
    37
    38         01  W4P-VLI-AUX      PIC 9(4) COMP-5.
    39         01  FILLER-VLI REDEFINES W4P-VLI-AUX.
    40             05 W1X-VLIA-1    PIC X(1).
    41             05 W1X-VLIA-2    PIC X(1).
    42
    43         01  W4X-VLI-ACT.
    44             05  W4P-VLI-WRK  PIC 9(4) COMP-5.
    45             05  W4P-FILLER3  PIC 9(4) COMP-5.
    46
    47         01  W1X-FIN          PIC X VALUE '0'.
    48             88  FIN-EPRLVORSE      VALUE 'F'.
    49
    50         01  K1XF             PIC X VALUE 'F'.
    51
    52         PROCEDURE DIVISION.
    53
    54             OPEN INPUT  EPRLVORSE.
    55
    56             READ EPRLVORSE INTO REG-ENTRADA
    57                AT END MOVE K1XF TO W1X-FIN
    58                NOT AT END
    59                DISPLAY 'testreadbindata::W4P-VLIENT: [' W4P-VLIENT '].'.
    60                DISPLAY 'testreadbindata::W4P-VLISUB: [' W4P-VLISUB '].'.
    61             CLOSE EPRLVORSE.
    62             STOP RUN.

The outputs of the testreadbindata program on both platforms are different::

•    HP-UX:

smppru@bayyana:/cralm/simep/prue/Arquitectura/testreadbindata> testreadbindata
testreadbindata::W4P-VLIENT: [04044] - 0000 1111 1100 1100(binary) - 0FCC(hex) -> BIG ENDIAN
testreadbindata::W4P-VLISUB: [00188] - 0000 0000 1011 1100(binary) - 00BC(hex) -> BIG ENDIAN

•    Linux:

int-cob-d-01u:/cralm/simep/prue/apps/testreadbindata>testreadbindata
testreadbindata::W4P-VLIENT: [52239] - 1100 1100 0000 1111(binary) - CC0F(hex) -> LITTLE ENDIAN
testreadbindata::W4P-VLISUB: [48128] – 1011 1100 0000 0000(binary) - BC00(hex) -> LITTLE ENDIAN

How should we proceed so that the data retrieved by the testreadbindata program on the Linux RedHat platform from the binary file in COMP-5 variables are exactly the same as those retrieved by the testreadbindata program on the HP-UX platform?

Thanks a lot.

Regards.

<------------------------------------------------------------------------------------------------------------------------------>
Platform information:

•    HP-UX:

smppru@bayyana:/opt/microfocus/cobol/etc> cat cobver
ServerExpress cobol v5.1.00
PRN=RXCAQ/AAP:9p.k5.51.07
PTI=WrapPack 6
PTI=ES

smppru@bayyana:/opt/microfocus/cobol/etc> uname -a
HP-UX bayyana B.11.31 U ia64 0804249662 unlimited-user license


•    Linux:

int-cob-d-01u:/cralm/simep/prue/uxna/bdon>cat $COBDIR/etc/cobver
Visual cobol v7.0.0
PRN=K1CRH/AAK:Ao.U4.13.04
PTI=32/64 bit
PTI=Micro Focus COBOL Server 7.0 - Patch Update 08
PTI=Patch Update 08
PTI=pkg_303630
PTI=MFInstaller


int-cob-d-01u:/cralm/simep/prue/uxna/bdon>cat /etc/os-release
NAME="Red Hat Enterprise Linux Server"
VERSION="7.9 (Maipo)"
ID="rhel"
ID_LIKE="fedora"
VARIANT="Server"
VARIANT_ID="server"
VERSION_ID="7.9"
PRETTY_NAME="Red Hat Enterprise Linux Server 7.9 (Maipo)"
ANSI_COLOR="0;31"
CPE_NAME="cpe:/o:redhat:enterprise_linux:7.9:GA:server"
HOME_URL="
">https://www.redhat.com/"
BUG_REPORT_URL="
">bugzilla.redhat.com/"

REDHAT_BUGZILLA_PRODUCT="Red Hat Enterprise Linux 7"
REDHAT_BUGZILLA_PRODUCT_VERSION=7.9
REDHAT_SUPPORT_PRODUCT="Red Hat Enterprise Linux"
REDHAT_SUPPORT_PRODUCT_VERSION="7.9"

This is the intended behavior of COMP-5. It always stores binary data in the native byte order of the processor. On big-endian systems it will store data in big endian format and on little endian machines it will reverse the order of the bytes.

If you use USAGE BINARY, COMP, COMP-4 or COMP-X the storage will always be interpreted as big endian format.

You could change the USAGE in your program to one of the above so the data is always treated as big endian or you could use the compiler directive

makesyn "comp-x" == "comp-5"


This is the intended behavior of COMP-5. It always stores binary data in the native byte order of the processor. On big-endian systems it will store data in big endian format and on little endian machines it will reverse the order of the bytes.

If you use USAGE BINARY, COMP, COMP-4 or COMP-X the storage will always be interpreted as big endian format.

You could change the USAGE in your program to one of the above so the data is always treated as big endian or you could use the compiler directive

makesyn "comp-x" == "comp-5"

Hi Chris,

     I have tested it in the test program testreadbindata and the proposed solution works correctly:

int-cob-d-01u:/cralm/simep/prue/apps/testreadbindata>cat testreadbindata.sh
# Set COBMODE to 64 for 64bit.  Defaults to 32bit.
MODE=${COBMODE:-32}
#cob$MODE -v -x -o testreadbindata  testreadbindata.cbl
cob$MODE -v -x -C 'makesyn "comp-x" == "comp-5"' -o testreadbindata  testreadbindata.cbl

int-cob-d-01u:/cralm/simep/prue/apps/testreadbindata>testreadbindata.sh
cob32 -C use=/cralm/simep/prue/jobs/cobol.dir -v -x -C makesyn "comp-x" == "comp-5" -o testreadbindata testreadbindata.cbl
* Micro Focus COBOL                  V7.0 revision 000           Compiler
* (C) Copyright 1984-2022 Micro Focus or one of its affiliates.
* Accepted - verbose
* Accepted - use(/cralm/simep/prue/jobs/cobol.dir)
* Accepted - HOSTARITHMETIC
* Accepted - SERIAL
* Accepted - COMMAND-LINE-LINKAGE
* Accepted - makesyn "comp-x" = "comp-5"
* Compiling testreadbindata.cbl
* Total Messages:     0
* Data:        9056     Code:         441
* Micro Focus COBOL Code Generator
* (C) Copyright 1984-2022 Micro Focus or one of its affiliates.
* Accepted - verbose
* Generating testreadbindata
* Data:        9312     Code:         858     Literals:         507
cob32: Entry points defined in module: testreadbindata.o
        *testreadbindata
        TESTREADBINDATA

The values ​​retrieved and displayed now match those of the same program running on the HP-UX platform.
int-cob-d-01u:/cralm/simep/prue/apps/testreadbindata>testreadbindata
testreadbindata::W4P-VLIENT: [04044].
testreadbindata::W4P-VLISUB: [00188].

The problem now is that the development team also uses COMP-5 to exchange int/long values ​​with C functions and replacing COMP-5 with COMP-X also affects the values ​​exchanged between Visual Cobol and C in this functions. Something like that.

      1        IDENTIFICATION DIVISION.
      2        PROGRAM-ID. maincob.
      3        DATA DIVISION.
      4        WORKING-STORAGE SECTION.
      5            01  Arg1     PIC X(7).
      6            01  Arg2     PIC X(7).
      7            01  Arg3     USAGE BINARY-LONG.
      8       * ----- Arg4 definition options -----
      9       *    01  Arg4     PIC X(4) COMP-5.
     10       *    01  Arg4     PIC 9(4) COMP.
     11       *    01  Arg4     USAGE BINARY-LONG.
     12       *    01  Arg4     PIC S9(4) COMP.
     13       *    01  Arg4     USAGE BINARY-LONG.
     14       *    01  Arg4     PIC X(4) COMP-X.
     15            01  Arg4     PIC 9(4) COMP-5.
     16       * ----- Arg4 definition options -----
     17            01  K1U0     PIC 9 VALUE 0.
     18            01  K1U1     PIC 9 VALUE 1.
     19        LINKAGE SECTION.
     20            01  CMD-LINE PIC X(64).
     21        PROCEDURE DIVISION USING CMD-LINE.
     22        000-Main.
     23            DISPLAY 'Starting maincob...'
     24       *    DISPLAY 'Cadena de entrada:    [' CMD-LINE '].'.
     25            MOVE Z'Arg1'   TO Arg1.
     26            MOVE Z'Arg2'   TO Arg2.
     27            MOVE 123456789 TO Arg3.
     28            MOVE K1U1      TO Arg4.
     29            DISPLAY 'Values before call C Routine...'.
     30            DISPLAY 'Arg1 = [' Arg1 ']'.
     31            DISPLAY 'Arg2 = [' Arg2 ']'.
     32            DISPLAY 'Arg3 = [' Arg3 ']'.
     33            DISPLAY 'Arg4 = [' Arg4 ']'.
     34            DISPLAY 'Calling C Routine...'.
     35            CALL 'subc'
     36                USING BY REFERENCE Arg1,
     37                      BY REFERENCE Arg2,
     38                      BY REFERENCE Arg3,
     39                      BY REFERENCE Arg4.
     40            DISPLAY 'Back from C Routine...'.
     41            DISPLAY 'Values after call C Routine...'.
     42            DISPLAY 'Arg1 = [' Arg1 ']'.
     43            DISPLAY 'Arg2 = [' Arg2 ']'.
     44            DISPLAY 'Arg3 = [' Arg3 ']'.
     45            DISPLAY 'Arg4 = [' Arg4 ']'.
     46            DISPLAY 'Returned value = [' RETURN-CODE ']'.
     47            STOP RUN.

int-cob-d-01u:/cralm/simep/prue/apps/callcfromcob>cat subc.c

      1 #include <stdio.h>
      2
      3 int subc(char *arg1,
      4          char *arg2,
      5          unsigned long *arg3,
      6          long *arg4)
      7 {
      8
      9   printf("Starting subc...\\n");
     10   printf("Input values:\\n");
     11   printf("Arg1 = [%s].\\n", arg1);
     12   printf("Arg2 = [%s].\\n", arg2);
     13   printf("Arg3 = [%ld].\\n", *arg3);
     14   printf("Arg4 = [%ld](0x%x).\\n", *arg4, *arg4);
     15
     16   arg1[0] = 'X';
     17   arg2[0] = 'Y';
     18   *arg3 = 987654321;
     19
     20   switch(*arg4){
     21      case 0:
     22          printf("El valor del argumento 4 es 0.\\n");
     23          break;
     24      default:
     25          printf("El valor del argumento 4 no es 0.\\n");
     26          break;
     27   }
     28
     29   *arg4 = -1;
     30
     31   printf("Output values:\\n");
     32   printf("Arg1 = [%s].\\n", arg1);
     33   printf("Arg2 = [%s].\\n", arg2);
     34   printf("Arg3 = [%ld].\\n", *arg3);
     35   printf("Arg4 = [%ld](0x%x).\\n", *arg4, *arg4);
     36
     37   return 2;
     38
     39 }

int-cob-d-01u:/cralm/simep/prue/apps/callcfromcob>build_callcfromcob.sh
cob32 -C use=/cralm/simep/prue/jobs/cobol.dir -v -x -C makesyn "comp-x" == "comp-5" -o callcfromcob maincob.cbl -L . -lsubc
* Micro Focus COBOL                  V7.0 revision 000           Compiler
* (C) Copyright 1984-2022 Micro Focus or one of its affiliates.
* Accepted - verbose
* Accepted - use(/cralm/simep/prue/jobs/cobol.dir)
* Accepted - HOSTARITHMETIC
* Accepted - SERIAL
* Accepted - COMMAND-LINE-LINKAGE
* Accepted - makesyn "comp-x" = "comp-5"
* Compiling maincob.cbl
* Total Messages:     0
* Data:         368     Code:         615
* Micro Focus COBOL Code Generator
* (C) Copyright 1984-2022 Micro Focus or one of its affiliates.
* Accepted - verbose
* Generating maincob
* Data:         624     Code:        1044     Literals:         363
cob32: Entry points defined in module: maincob.o
        *maincob
        MAINCOB


int-cob-d-01u:/cralm/simep/prue/apps/callcfromcob>callcfromcob
Starting maincob...
Values before call C Routine...
Arg1 = [Arg1  ]
Arg2 = [Arg2  ]
Arg3 = [+0123456789]
Arg4 = [00001]
Calling C Routine...
Starting subc...
Input values:
Arg1 = [Arg1].
Arg2 = [Arg2].
Arg3 = [123456789].
Arg4 = [538968320](0x20200100).
El valor del argumento 4 no es 0.
Output values:
Arg1 = [Xrg1].
Arg2 = [Yrg2].
Arg3 = [987654321].
Arg4 = [-1](0xffffffff).
Back from C Routine...
Values after call C Routine...
Arg1 = [Xrg1  ]
Arg2 = [Yrg2  ]
Arg3 = [+0987654321]
Arg4 = [65535]
Returned value = [+000000002]

But this is another story :(

Thanks Chris.

Regards.


Hi Chris,

     I have tested it in the test program testreadbindata and the proposed solution works correctly:

int-cob-d-01u:/cralm/simep/prue/apps/testreadbindata>cat testreadbindata.sh
# Set COBMODE to 64 for 64bit.  Defaults to 32bit.
MODE=${COBMODE:-32}
#cob$MODE -v -x -o testreadbindata  testreadbindata.cbl
cob$MODE -v -x -C 'makesyn "comp-x" == "comp-5"' -o testreadbindata  testreadbindata.cbl

int-cob-d-01u:/cralm/simep/prue/apps/testreadbindata>testreadbindata.sh
cob32 -C use=/cralm/simep/prue/jobs/cobol.dir -v -x -C makesyn "comp-x" == "comp-5" -o testreadbindata testreadbindata.cbl
* Micro Focus COBOL                  V7.0 revision 000           Compiler
* (C) Copyright 1984-2022 Micro Focus or one of its affiliates.
* Accepted - verbose
* Accepted - use(/cralm/simep/prue/jobs/cobol.dir)
* Accepted - HOSTARITHMETIC
* Accepted - SERIAL
* Accepted - COMMAND-LINE-LINKAGE
* Accepted - makesyn "comp-x" = "comp-5"
* Compiling testreadbindata.cbl
* Total Messages:     0
* Data:        9056     Code:         441
* Micro Focus COBOL Code Generator
* (C) Copyright 1984-2022 Micro Focus or one of its affiliates.
* Accepted - verbose
* Generating testreadbindata
* Data:        9312     Code:         858     Literals:         507
cob32: Entry points defined in module: testreadbindata.o
        *testreadbindata
        TESTREADBINDATA

The values ​​retrieved and displayed now match those of the same program running on the HP-UX platform.
int-cob-d-01u:/cralm/simep/prue/apps/testreadbindata>testreadbindata
testreadbindata::W4P-VLIENT: [04044].
testreadbindata::W4P-VLISUB: [00188].

The problem now is that the development team also uses COMP-5 to exchange int/long values ​​with C functions and replacing COMP-5 with COMP-X also affects the values ​​exchanged between Visual Cobol and C in this functions. Something like that.

      1        IDENTIFICATION DIVISION.
      2        PROGRAM-ID. maincob.
      3        DATA DIVISION.
      4        WORKING-STORAGE SECTION.
      5            01  Arg1     PIC X(7).
      6            01  Arg2     PIC X(7).
      7            01  Arg3     USAGE BINARY-LONG.
      8       * ----- Arg4 definition options -----
      9       *    01  Arg4     PIC X(4) COMP-5.
     10       *    01  Arg4     PIC 9(4) COMP.
     11       *    01  Arg4     USAGE BINARY-LONG.
     12       *    01  Arg4     PIC S9(4) COMP.
     13       *    01  Arg4     USAGE BINARY-LONG.
     14       *    01  Arg4     PIC X(4) COMP-X.
     15            01  Arg4     PIC 9(4) COMP-5.
     16       * ----- Arg4 definition options -----
     17            01  K1U0     PIC 9 VALUE 0.
     18            01  K1U1     PIC 9 VALUE 1.
     19        LINKAGE SECTION.
     20            01  CMD-LINE PIC X(64).
     21        PROCEDURE DIVISION USING CMD-LINE.
     22        000-Main.
     23            DISPLAY 'Starting maincob...'
     24       *    DISPLAY 'Cadena de entrada:    [' CMD-LINE '].'.
     25            MOVE Z'Arg1'   TO Arg1.
     26            MOVE Z'Arg2'   TO Arg2.
     27            MOVE 123456789 TO Arg3.
     28            MOVE K1U1      TO Arg4.
     29            DISPLAY 'Values before call C Routine...'.
     30            DISPLAY 'Arg1 = [' Arg1 ']'.
     31            DISPLAY 'Arg2 = [' Arg2 ']'.
     32            DISPLAY 'Arg3 = [' Arg3 ']'.
     33            DISPLAY 'Arg4 = [' Arg4 ']'.
     34            DISPLAY 'Calling C Routine...'.
     35            CALL 'subc'
     36                USING BY REFERENCE Arg1,
     37                      BY REFERENCE Arg2,
     38                      BY REFERENCE Arg3,
     39                      BY REFERENCE Arg4.
     40            DISPLAY 'Back from C Routine...'.
     41            DISPLAY 'Values after call C Routine...'.
     42            DISPLAY 'Arg1 = [' Arg1 ']'.
     43            DISPLAY 'Arg2 = [' Arg2 ']'.
     44            DISPLAY 'Arg3 = [' Arg3 ']'.
     45            DISPLAY 'Arg4 = [' Arg4 ']'.
     46            DISPLAY 'Returned value = [' RETURN-CODE ']'.
     47            STOP RUN.

int-cob-d-01u:/cralm/simep/prue/apps/callcfromcob>cat subc.c

      1 #include <stdio.h>
      2
      3 int subc(char *arg1,
      4          char *arg2,
      5          unsigned long *arg3,
      6          long *arg4)
      7 {
      8
      9   printf("Starting subc...\\n");
     10   printf("Input values:\\n");
     11   printf("Arg1 = [%s].\\n", arg1);
     12   printf("Arg2 = [%s].\\n", arg2);
     13   printf("Arg3 = [%ld].\\n", *arg3);
     14   printf("Arg4 = [%ld](0x%x).\\n", *arg4, *arg4);
     15
     16   arg1[0] = 'X';
     17   arg2[0] = 'Y';
     18   *arg3 = 987654321;
     19
     20   switch(*arg4){
     21      case 0:
     22          printf("El valor del argumento 4 es 0.\\n");
     23          break;
     24      default:
     25          printf("El valor del argumento 4 no es 0.\\n");
     26          break;
     27   }
     28
     29   *arg4 = -1;
     30
     31   printf("Output values:\\n");
     32   printf("Arg1 = [%s].\\n", arg1);
     33   printf("Arg2 = [%s].\\n", arg2);
     34   printf("Arg3 = [%ld].\\n", *arg3);
     35   printf("Arg4 = [%ld](0x%x).\\n", *arg4, *arg4);
     36
     37   return 2;
     38
     39 }

int-cob-d-01u:/cralm/simep/prue/apps/callcfromcob>build_callcfromcob.sh
cob32 -C use=/cralm/simep/prue/jobs/cobol.dir -v -x -C makesyn "comp-x" == "comp-5" -o callcfromcob maincob.cbl -L . -lsubc
* Micro Focus COBOL                  V7.0 revision 000           Compiler
* (C) Copyright 1984-2022 Micro Focus or one of its affiliates.
* Accepted - verbose
* Accepted - use(/cralm/simep/prue/jobs/cobol.dir)
* Accepted - HOSTARITHMETIC
* Accepted - SERIAL
* Accepted - COMMAND-LINE-LINKAGE
* Accepted - makesyn "comp-x" = "comp-5"
* Compiling maincob.cbl
* Total Messages:     0
* Data:         368     Code:         615
* Micro Focus COBOL Code Generator
* (C) Copyright 1984-2022 Micro Focus or one of its affiliates.
* Accepted - verbose
* Generating maincob
* Data:         624     Code:        1044     Literals:         363
cob32: Entry points defined in module: maincob.o
        *maincob
        MAINCOB


int-cob-d-01u:/cralm/simep/prue/apps/callcfromcob>callcfromcob
Starting maincob...
Values before call C Routine...
Arg1 = [Arg1  ]
Arg2 = [Arg2  ]
Arg3 = [+0123456789]
Arg4 = [00001]
Calling C Routine...
Starting subc...
Input values:
Arg1 = [Arg1].
Arg2 = [Arg2].
Arg3 = [123456789].
Arg4 = [538968320](0x20200100).
El valor del argumento 4 no es 0.
Output values:
Arg1 = [Xrg1].
Arg2 = [Yrg2].
Arg3 = [987654321].
Arg4 = [-1](0xffffffff).
Back from C Routine...
Values after call C Routine...
Arg1 = [Xrg1  ]
Arg2 = [Yrg2  ]
Arg3 = [+0987654321]
Arg4 = [65535]
Returned value = [+000000002]

But this is another story :(

Thanks Chris.

Regards.

I don't think you can have it both ways, I am afraid. The directive changes all occurrences of comp-5 to comp-x. There are some conversion routines available which are defined in cobgetput.h that can be called from C that will convert COBOL data from one type to another.

Please see the docs here:

I think in your case you will be passing a PIC 9(4) COMP-X field which is actually a 16-bit (2 byte) field and not a 32-bit one so should be received as a short * instead of a long *.

The conversion routine to use would be cobget_sx2_compx which would return the field to C as a native short.

The alternative would be to not use the compiler directive and define the fields in the file as COMP-X and then move them to COMP-5 fields before using them in any CALLS, etc.