Skip to main content

We're trying to call the following C function from COBOL:

unsigned int MagickSetResolution( MagickWand *wand, const double x_resolution,
                                  const double y_resolution );

This function is part of the GraphicsMagick Wand API. The problem is in the 'double' parameters. It's not possible to CALL using a variable declared as USAGE IS DOUBLE, this gives the following compiler error:

BY VALUE parameter WWK-RES-X illegal type

We tried a variety of different options, including PIC X(8) COMP-N, but nothing seems to work. Is calling this function even possible?

N.B. we're using the 32 bit runtime.

We're trying to call the following C function from COBOL:

unsigned int MagickSetResolution( MagickWand *wand, const double x_resolution,
                                  const double y_resolution );

This function is part of the GraphicsMagick Wand API. The problem is in the 'double' parameters. It's not possible to CALL using a variable declared as USAGE IS DOUBLE, this gives the following compiler error:

BY VALUE parameter WWK-RES-X illegal type

We tried a variety of different options, including PIC X(8) COMP-N, but nothing seems to work. Is calling this function even possible?

N.B. we're using the 32 bit runtime.

Try using either USAGE SIGNED-LONG  or PIC S9(18) COMP-5.


We're trying to call the following C function from COBOL:

unsigned int MagickSetResolution( MagickWand *wand, const double x_resolution,
                                  const double y_resolution );

This function is part of the GraphicsMagick Wand API. The problem is in the 'double' parameters. It's not possible to CALL using a variable declared as USAGE IS DOUBLE, this gives the following compiler error:

BY VALUE parameter WWK-RES-X illegal type

We tried a variety of different options, including PIC X(8) COMP-N, but nothing seems to work. Is calling this function even possible?

N.B. we're using the 32 bit runtime.

Thanks for your reply. Unfortunately both options don't work for us.

It seems like only the first 4 bytes of the parameter are sent to the C function, even when explicitly using PIC X(8) COMP-N (which is 8 bytes, and shows up correctly in the debugger's 'Display in hex' function).

Can you confirm whether it's actually possible to call C-functions with 64-bit parameters when using the 32 bit runtime? Thanks.


We're trying to call the following C function from COBOL:

unsigned int MagickSetResolution( MagickWand *wand, const double x_resolution,
                                  const double y_resolution );

This function is part of the GraphicsMagick Wand API. The problem is in the 'double' parameters. It's not possible to CALL using a variable declared as USAGE IS DOUBLE, this gives the following compiler error:

BY VALUE parameter WWK-RES-X illegal type

We tried a variety of different options, including PIC X(8) COMP-N, but nothing seems to work. Is calling this function even possible?

N.B. we're using the 32 bit runtime.

Thanks for your reply. Unfortunately both options don't work for us.

It seems like only the first 4 bytes of the parameter are sent to the C function, even when explicitly using PIC X(8) COMP-N (which is 8 bytes, and shows up correctly in the debugger's 'Display in hex' function).

Can you confirm whether it's actually possible to call C-functions with 64-bit parameters when using the 32 bit runtime? Thanks.


We're trying to call the following C function from COBOL:

unsigned int MagickSetResolution( MagickWand *wand, const double x_resolution,
                                  const double y_resolution );

This function is part of the GraphicsMagick Wand API. The problem is in the 'double' parameters. It's not possible to CALL using a variable declared as USAGE IS DOUBLE, this gives the following compiler error:

BY VALUE parameter WWK-RES-X illegal type

We tried a variety of different options, including PIC X(8) COMP-N, but nothing seems to work. Is calling this function even possible?

N.B. we're using the 32 bit runtime.

Thanks for your reply. Unfortunately both options don't work for us.

It seems like only the first 4 bytes of the parameter are sent to the C function, even when explicitly using PIC X(8) COMP-N (which is 8 bytes, and shows up correctly in the debugger's 'Display in hex' function).

Can you confirm whether it's actually possible to call C-functions with 64-bit parameters when using the 32 bit runtime? Thanks.


We're trying to call the following C function from COBOL:

unsigned int MagickSetResolution( MagickWand *wand, const double x_resolution,
                                  const double y_resolution );

This function is part of the GraphicsMagick Wand API. The problem is in the 'double' parameters. It's not possible to CALL using a variable declared as USAGE IS DOUBLE, this gives the following compiler error:

BY VALUE parameter WWK-RES-X illegal type

We tried a variety of different options, including PIC X(8) COMP-N, but nothing seems to work. Is calling this function even possible?

N.B. we're using the 32 bit runtime.

That can't be right. C's double is a floating-point type - usually a 64-bit floating-point value, though C99 only requires that double be a real floating-point type, and that the range of float be a subset of the range of double, and that of double be a subset of the range of long double. (N.B. Not necessarily a proper subset.

In any case, though, while some integer type such as S9(18) COMP-5 might have the correct size, it won't have the correct representation to match C's double.

In MF COBOL, you'd use COMP-2 or (equivalently) FLOAT-LONG. I don't know about ACU.


We're trying to call the following C function from COBOL:

unsigned int MagickSetResolution( MagickWand *wand, const double x_resolution,
                                  const double y_resolution );

This function is part of the GraphicsMagick Wand API. The problem is in the 'double' parameters. It's not possible to CALL using a variable declared as USAGE IS DOUBLE, this gives the following compiler error:

BY VALUE parameter WWK-RES-X illegal type

We tried a variety of different options, including PIC X(8) COMP-N, but nothing seems to work. Is calling this function even possible?

N.B. we're using the 32 bit runtime.

We're on a regular Windows system, so I assume the double type is 64 bit double precision like usual.

ACUCOBOL has a special USAGE IS FLOAT / USAGE IS DOUBLE syntax which replaces COMP-2. This is the obvious choice, but these types are not supported in C function calls (as detailed in my first post).

So you're right, but the way we've been trying to use X(8) COMP-N (64 bit integer) is by using a value that has the same bit representation as the double we need (it's just a fixed number - 96). That number is 4636455816377925632.

I checked the value in the debugger, it does have the exact same hex value as 96 double. But it still doesn't work. After testing with a custom C function that just writes out the passed values to a text file I'm starting to think ACUCOBOL just passes the first 32 bits. This is what I'd like to see confirmed from someone who knows...

It seems like there's just no way for this to work, so we'll have to find some other way around it.


We're trying to call the following C function from COBOL:

unsigned int MagickSetResolution( MagickWand *wand, const double x_resolution,
                                  const double y_resolution );

This function is part of the GraphicsMagick Wand API. The problem is in the 'double' parameters. It's not possible to CALL using a variable declared as USAGE IS DOUBLE, this gives the following compiler error:

BY VALUE parameter WWK-RES-X illegal type

We tried a variety of different options, including PIC X(8) COMP-N, but nothing seems to work. Is calling this function even possible?

N.B. we're using the 32 bit runtime.

We're on a regular Windows system, so I assume the double type is 64 bit double precision like usual.

ACUCOBOL has a special USAGE IS FLOAT / USAGE IS DOUBLE syntax which replaces COMP-2. This is the obvious choice, but these types are not supported in C function calls (as detailed in my first post).

So you're right, but the way we've been trying to use X(8) COMP-N (64 bit integer) is by using a value that has the same bit representation as the double we need (it's just a fixed number - 96). That number is 4636455816377925632.

I checked the value in the debugger, it does have the exact same hex value as 96 double. But it still doesn't work. After testing with a custom C function that just writes out the passed values to a text file I'm starting to think ACUCOBOL just passes the first 32 bits. This is what I'd like to see confirmed from someone who knows...

It seems like there's just no way for this to work, so we'll have to find some other way around it.


We're trying to call the following C function from COBOL:

unsigned int MagickSetResolution( MagickWand *wand, const double x_resolution,
                                  const double y_resolution );

This function is part of the GraphicsMagick Wand API. The problem is in the 'double' parameters. It's not possible to CALL using a variable declared as USAGE IS DOUBLE, this gives the following compiler error:

BY VALUE parameter WWK-RES-X illegal type

We tried a variety of different options, including PIC X(8) COMP-N, but nothing seems to work. Is calling this function even possible?

N.B. we're using the 32 bit runtime.

The CALL documentation says:

"You may pass floating-point data to subroutines normally with the CALL verb. Note that you may not pass a floating-point item BY VALUE. This restriction exists for portability reasons (some machines pass floating-point using a convention different from that used for integer items). You should pass floating-point items BY REFERENCE. This will pass a pointer to the item, which the receiving routine can then retrieve by "de-referencing" the pointer."

I tried to fake out CALL by redefining my USAGE DOUBLE to another type, as you did, without any luck.  My guess is that we are running into this different parameter convention for floating point data items.  My suggestion is to write a shim C function that takes pointers to double and then calls the actual function.


We're trying to call the following C function from COBOL:

unsigned int MagickSetResolution( MagickWand *wand, const double x_resolution,
                                  const double y_resolution );

This function is part of the GraphicsMagick Wand API. The problem is in the 'double' parameters. It's not possible to CALL using a variable declared as USAGE IS DOUBLE, this gives the following compiler error:

BY VALUE parameter WWK-RES-X illegal type

We tried a variety of different options, including PIC X(8) COMP-N, but nothing seems to work. Is calling this function even possible?

N.B. we're using the 32 bit runtime.

There is no way to call this function without adding some extra C code somewhere. You can either relink the runtime (not recommended) or create a new DLL that will be your wrapper around this function.

Once you decide to write a new function, you can pass the double value as a pointer (by reference), or use a SUB85-style interface and do your own conversion.


We're trying to call the following C function from COBOL:

unsigned int MagickSetResolution( MagickWand *wand, const double x_resolution,
                                  const double y_resolution );

This function is part of the GraphicsMagick Wand API. The problem is in the 'double' parameters. It's not possible to CALL using a variable declared as USAGE IS DOUBLE, this gives the following compiler error:

BY VALUE parameter WWK-RES-X illegal type

We tried a variety of different options, including PIC X(8) COMP-N, but nothing seems to work. Is calling this function even possible?

N.B. we're using the 32 bit runtime.

Thans for your suggestions. Luckily we found a solution to this problem ourselves. Apparently, calling a 64 bit parameter in x86 involves two 32 bit values being pushed on the stack. We used this to our advantage by splitting the parameter into to 32 bit vars and calling the function with 4 instead of 2 parameters.

The code is now like this:

           MOVE 96                       TO wwk-cnv-double

           CALL "C$MEMCPY" USING

             BY REFERENCE wwk-cnv-bytes

             BY REFERENCE wwk-cnv-double

           CALL "C$MEMCPY" USING

             BY REFERENCE wwk-resolution-1

             BY REFERENCE wwk-cnv-bytes-1

           CALL "C$MEMCPY" USING

             BY REFERENCE wwk-resolution-2

             BY REFERENCE wwk-cnv-bytes-2

           CALL "MagickSetImageResolution" USING

             BY VALUE h-magick-wand2

             BY VALUE wwk-resolution-1

             BY VALUE wwk-resolution-2

             BY VALUE wwk-resolution-1

             BY VALUE wwk-resolution-2

             GIVING wwk-magick-pass-fail

With the following working storage definition:

     01 wwk-cnv-double

                USAGE IS DOUBLE.

     01 wwk-cnv-bytes.

         03 wwk-cnv-bytes-1  PIC  X(4).

         03 wwk-cnv-bytes-2  PIC  X(4).

     77 wwk-resolution-1 PIC  X(4)

                USAGE IS COMP-N.

     77 wwk-resolution-2 PIC  X(4)

                USAGE IS COMP-N.

This solution was actually triggered by a comment in callc.c (see lib folder) saying that on 16 bit systems two parameters are needed to pass a 'long' or 'pointer'. Apparently this also apples to 32 bit systems.


We're trying to call the following C function from COBOL:

unsigned int MagickSetResolution( MagickWand *wand, const double x_resolution,
                                  const double y_resolution );

This function is part of the GraphicsMagick Wand API. The problem is in the 'double' parameters. It's not possible to CALL using a variable declared as USAGE IS DOUBLE, this gives the following compiler error:

BY VALUE parameter WWK-RES-X illegal type

We tried a variety of different options, including PIC X(8) COMP-N, but nothing seems to work. Is calling this function even possible?

N.B. we're using the 32 bit runtime.

Thans for your suggestions. Luckily we found a solution to this problem ourselves. Apparently, calling a 64 bit parameter in x86 involves two 32 bit values being pushed on the stack. We used this to our advantage by splitting the parameter into to 32 bit vars and calling the function with 4 instead of 2 parameters.

The code is now like this:

           MOVE 96                       TO wwk-cnv-double

           CALL "C$MEMCPY" USING

             BY REFERENCE wwk-cnv-bytes

             BY REFERENCE wwk-cnv-double

           CALL "C$MEMCPY" USING

             BY REFERENCE wwk-resolution-1

             BY REFERENCE wwk-cnv-bytes-1

           CALL "C$MEMCPY" USING

             BY REFERENCE wwk-resolution-2

             BY REFERENCE wwk-cnv-bytes-2

           CALL "MagickSetImageResolution" USING

             BY VALUE h-magick-wand2

             BY VALUE wwk-resolution-1

             BY VALUE wwk-resolution-2

             BY VALUE wwk-resolution-1

             BY VALUE wwk-resolution-2

             GIVING wwk-magick-pass-fail

With the following working storage definition:

     01 wwk-cnv-double

                USAGE IS DOUBLE.

     01 wwk-cnv-bytes.

         03 wwk-cnv-bytes-1  PIC  X(4).

         03 wwk-cnv-bytes-2  PIC  X(4).

     77 wwk-resolution-1 PIC  X(4)

                USAGE IS COMP-N.

     77 wwk-resolution-2 PIC  X(4)

                USAGE IS COMP-N.

This solution was actually triggered by a comment in callc.c (see lib folder) saying that on 16 bit systems two parameters are needed to pass a 'long' or 'pointer'. Apparently this also apples to 32 bit systems.


We're trying to call the following C function from COBOL:

unsigned int MagickSetResolution( MagickWand *wand, const double x_resolution,
                                  const double y_resolution );

This function is part of the GraphicsMagick Wand API. The problem is in the 'double' parameters. It's not possible to CALL using a variable declared as USAGE IS DOUBLE, this gives the following compiler error:

BY VALUE parameter WWK-RES-X illegal type

We tried a variety of different options, including PIC X(8) COMP-N, but nothing seems to work. Is calling this function even possible?

N.B. we're using the 32 bit runtime.

Thans for your suggestions. Luckily we found a solution to this problem ourselves. Apparently, calling a 64 bit parameter in x86 involves two 32 bit values being pushed on the stack. We used this to our advantage by splitting the parameter into to 32 bit vars and calling the function with 4 instead of 2 parameters.

The code is now like this:

           MOVE 96                       TO wwk-cnv-double

           CALL "C$MEMCPY" USING

             BY REFERENCE wwk-cnv-bytes

             BY REFERENCE wwk-cnv-double

           CALL "C$MEMCPY" USING

             BY REFERENCE wwk-resolution-1

             BY REFERENCE wwk-cnv-bytes-1

           CALL "C$MEMCPY" USING

             BY REFERENCE wwk-resolution-2

             BY REFERENCE wwk-cnv-bytes-2

           CALL "MagickSetImageResolution" USING

             BY VALUE h-magick-wand2

             BY VALUE wwk-resolution-1

             BY VALUE wwk-resolution-2

             BY VALUE wwk-resolution-1

             BY VALUE wwk-resolution-2

             GIVING wwk-magick-pass-fail

With the following working storage definition:

     01 wwk-cnv-double

                USAGE IS DOUBLE.

     01 wwk-cnv-bytes.

         03 wwk-cnv-bytes-1  PIC  X(4).

         03 wwk-cnv-bytes-2  PIC  X(4).

     77 wwk-resolution-1 PIC  X(4)

                USAGE IS COMP-N.

     77 wwk-resolution-2 PIC  X(4)

                USAGE IS COMP-N.

This solution was actually triggered by a comment in callc.c (see lib folder) saying that on 16 bit systems two parameters are needed to pass a 'long' or 'pointer'. Apparently this also apples to 32 bit systems.


We're trying to call the following C function from COBOL:

unsigned int MagickSetResolution( MagickWand *wand, const double x_resolution,
                                  const double y_resolution );

This function is part of the GraphicsMagick Wand API. The problem is in the 'double' parameters. It's not possible to CALL using a variable declared as USAGE IS DOUBLE, this gives the following compiler error:

BY VALUE parameter WWK-RES-X illegal type

We tried a variety of different options, including PIC X(8) COMP-N, but nothing seems to work. Is calling this function even possible?

N.B. we're using the 32 bit runtime.

Thans for your suggestions. We did find a solution to this problem after all. Apparently, calling a 64 bit parameter in x86 involves two 32 bit values being pushed on the stack. We used this to our advantage by splitting the parameter ourselves and calling the function with 4 instead of 2 parameters.

The code is now like this:

           MOVE 96                       TO wwk-cnv-double

           CALL "C$MEMCPY" USING

             BY REFERENCE wwk-cnv-bytes

             BY REFERENCE wwk-cnv-double

           CALL "C$MEMCPY" USING

             BY REFERENCE wwk-resolution-1

             BY REFERENCE wwk-cnv-bytes-1

           CALL "C$MEMCPY" USING

             BY REFERENCE wwk-resolution-2

             BY REFERENCE wwk-cnv-bytes-2

           CALL "MagickSetImageResolution" USING

             BY VALUE h-magick-wand2

             BY VALUE wwk-resolution-1

             BY VALUE wwk-resolution-2

             BY VALUE wwk-resolution-1

             BY VALUE wwk-resolution-2

             GIVING wwk-magick-pass-fail

With the following working storage definition:

      01 wwk-cnv-double

                 USAGE IS DOUBLE.

      01 wwk-cnv-bytes.

          03 wwk-cnv-bytes-1  PIC  X(4).

          03 wwk-cnv-bytes-2  PIC  X(4).

      77 wwk-resolution-1 PIC  X(4)

                 USAGE IS COMP-N.

      77 wwk-resolution-2 PIC  X(4)

                 USAGE IS COMP-N.

This solution was triggered by a comment in call.c (see lib folder) stating that to pass a long parameter on 16-bit systems you need to code two parameters.

Apparently this also works for 32-bit systems.


We're trying to call the following C function from COBOL:

unsigned int MagickSetResolution( MagickWand *wand, const double x_resolution,
                                  const double y_resolution );

This function is part of the GraphicsMagick Wand API. The problem is in the 'double' parameters. It's not possible to CALL using a variable declared as USAGE IS DOUBLE, this gives the following compiler error:

BY VALUE parameter WWK-RES-X illegal type

We tried a variety of different options, including PIC X(8) COMP-N, but nothing seems to work. Is calling this function even possible?

N.B. we're using the 32 bit runtime.

Thans for your suggestions. We did find a solution to this problem after all. Apparently, calling a 64 bit parameter in x86 involves two 32 bit values being pushed on the stack. We used this to our advantage by splitting the parameter ourselves and calling the function with 4 instead of 2 parameters.

The code is now like this:

           MOVE 96                       TO wwk-cnv-double

           CALL "C$MEMCPY" USING

             BY REFERENCE wwk-cnv-bytes

             BY REFERENCE wwk-cnv-double

           CALL "C$MEMCPY" USING

             BY REFERENCE wwk-resolution-1

             BY REFERENCE wwk-cnv-bytes-1

           CALL "C$MEMCPY" USING

             BY REFERENCE wwk-resolution-2

             BY REFERENCE wwk-cnv-bytes-2

           CALL "MagickSetImageResolution" USING

             BY VALUE h-magick-wand2

             BY VALUE wwk-resolution-1

             BY VALUE wwk-resolution-2

             BY VALUE wwk-resolution-1

             BY VALUE wwk-resolution-2

             GIVING wwk-magick-pass-fail

With the following working storage definition:

      01 wwk-cnv-double

                 USAGE IS DOUBLE.

      01 wwk-cnv-bytes.

          03 wwk-cnv-bytes-1  PIC  X(4).

          03 wwk-cnv-bytes-2  PIC  X(4).

      77 wwk-resolution-1 PIC  X(4)

                 USAGE IS COMP-N.

      77 wwk-resolution-2 PIC  X(4)

                 USAGE IS COMP-N.

This solution was triggered by a comment in call.c (see lib folder) stating that to pass a long parameter on 16-bit systems you need to code two parameters.

Apparently this also works for 32-bit systems.


We're trying to call the following C function from COBOL:

unsigned int MagickSetResolution( MagickWand *wand, const double x_resolution,
                                  const double y_resolution );

This function is part of the GraphicsMagick Wand API. The problem is in the 'double' parameters. It's not possible to CALL using a variable declared as USAGE IS DOUBLE, this gives the following compiler error:

BY VALUE parameter WWK-RES-X illegal type

We tried a variety of different options, including PIC X(8) COMP-N, but nothing seems to work. Is calling this function even possible?

N.B. we're using the 32 bit runtime.

Thans for your suggestions. We did find a solution to this problem after all. Apparently, calling a 64 bit parameter in x86 involves two 32 bit values being pushed on the stack. We used this to our advantage by splitting the parameter ourselves and calling the function with 4 instead of 2 parameters.

The code is now like this:

            MOVE 96                       TO wwk-cnv-double
            
            CALL "C$MEMCPY" USING
              BY REFERENCE wwk-cnv-bytes
              BY REFERENCE wwk-cnv-double
            CALL "C$MEMCPY" USING
              BY REFERENCE wwk-resolution-1
              BY REFERENCE wwk-cnv-bytes-1
            CALL "C$MEMCPY" USING
              BY REFERENCE wwk-resolution-2
              BY REFERENCE wwk-cnv-bytes-2

            CALL "MagickSetImageResolution" USING
              BY VALUE h-magick-wand2
              BY VALUE wwk-resolution-1
              BY VALUE wwk-resolution-2
              BY VALUE wwk-resolution-1
              BY VALUE wwk-resolution-2
              GIVING wwk-magick-pass-fail

With the following working storage definition:

       01 wwk-cnv-double
                  USAGE IS DOUBLE.
       01 wwk-cnv-bytes.
           03 wwk-cnv-bytes-1  PIC  X(4).
           03 wwk-cnv-bytes-2  PIC  X(4).
       77 wwk-resolution-1 PIC  X(4)
                  USAGE IS COMP-N.
       77 wwk-resolution-2 PIC  X(4)
                  USAGE IS COMP-N.
                  
This solution was triggered by a comment in call.c (see lib folder) stating that to pass a long parameter on 16-bit systems you need to code two parameters.
Apparently this also works for 32-bit systems.