Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

A Hex function for COBOL

2,090 views
Skip to first unread message

Pete Dashwood

unread,
Jun 4, 2015, 11:53:03 PM6/4/15
to
I was surprised when looking through the COBOL intrinsic functions to NOT
find anything that will convert to Hexadecimal.

(Yes, I can write something to do the necessary arithmetic, but, in this day
and age I wouldn't expect to have to.)

Does anybody have a routine that can take in a NUMBER (up to 10 digits) and
produce a Hex string from it?

Input can be any format you like, but probably pic 9(10) will ensure that
the actual positive integer value is represented correctly. (Sign is
irrelevant for this exercise...)

I need to use this for determining colours for both the web and the
desktop.

PowerCOBOL uses S9(9) comp-5 (but some of the numbers can be 10 digits, so
it doesn't work properly, and the numbers represent RGB values in
little-Endian so the position of them matters. I believe it is possible to
take the actual decimal value and convert that to hex so that the requisite
values for RG and B can be obtained.

But just having a function or subroutine to produce the Hex could be useful
in any case.

I can see several ways to do it, so I'll be interested if anyone here has a
really cool COBOL way.

Pete.
--
"I used to write COBOL...now I can do anything."


Doug Miller

unread,
Jun 5, 2015, 1:59:38 PM6/5/15
to
"Pete Dashwood" <dash...@removethis.enternet.co.nz> wrote in news:ctckosFicvaU1
@mid.individual.net:

> I was surprised when looking through the COBOL intrinsic functions to NOT
> find anything that will convert to Hexadecimal.
> [...]
> I can see several ways to do it, so I'll be interested if anyone here has a
> really cool COBOL way.

*** Caution: written off the top of my head and not tested at all ***

77 decimal-number PIC 9(9) COMP.
77 dec-remainder PIC 99 COMP.
77 dec-quotient PIC 9(9) COMP.
77 hex-digits PIC X(16) VALUE "0123456789ABCDEF".
77 hex-string PIC X(8) VALUE SPACES.

PERFORM WITH TEST AFTER UNTIL dec-quotient = ZERO
DIVIDE decimal-number BY 16
GIVING dec-quotient
REMAINDER dec-remainder
END-DIVIDE
STRING
hex-digits(dec-remainder + 1) DELIMITED BY SIZE
hex-string DELIMITED BY SPACES
INTO hex-string
END-STRING
MOVE dec-quotient TO decimal-number
END-PERFORM

Kerry Liles

unread,
Jun 5, 2015, 2:30:03 PM6/5/15
to
Looks promising... on my version of COBOL- PP 5686-068 IBM COBOL FOR
VSE/ESA 1.1.1 (on VSE under VM on z/OS IBM Mainframe) it looks like the
string into hex-string gets confused by the re-use of the field
HEX-STRING - although I don't know why - it made sense to me!!

I will post more shortly... likely will have to have a parallel field to
hex-string as a temporary target of the STRING verb




Kerry Liles

unread,
Jun 5, 2015, 2:39:55 PM6/5/15
to
On 6/5/2015 1:58 PM, Doug Miller wrote:
The following code worked fine for me:

MOVE 200063 TO DECIMAL-NUMBER
DISPLAY 'DECIMAL NUMBER= ' DECIMAL-NUMBER
PERFORM WITH TEST AFTER UNTIL DEC-QUOTIENT = ZERO
DIVIDE DECIMAL-NUMBER BY 16
GIVING DEC-QUOTIENT
REMAINDER DEC-REMAINDER
END-DIVIDE
STRING
HEX-DIGITS(DEC-REMAINDER + 1:1) DELIMITED
BY SIZE
HEX-OUTPUT DELIMITED BY SPACES
INTO HEX-STRING
END-STRING
MOVE HEX-STRING TO HEX-OUTPUT
MOVE DEC-QUOTIENT TO DECIMAL-NUMBER
END-PERFORM
DISPLAY 'HEX EQUIVALENT= ' HEX-STRING

The result was:

DECIMAL NUMBER= 0000200063
HEX EQUIVALENT= 30D7F

(for those wondering, 200063 was a licence plate number I had years ago
that I realized is a 6-digit prime number...)

Seems the "overlapping" re-use of the argument of STRING and its output
field causes my compiler to generate code that doesn't work as intended...

Also note the addition of the ":1" in the reference modification...

regards,

Kerry Liles

Pete Dashwood

unread,
Jun 5, 2015, 8:27:02 PM6/5/15
to
This is very close to how I wrote it, but I didn't use STRING to build the
output; rather just refmodded a single byte move.

Meantime (after actual testing) the goalposts have shifted, sorry... see
update to the topic.

I liked the END-DIVIDE. Not seen that before, although it makes perfect
sense...

Cheers,

Pete Dashwood

unread,
Jun 5, 2015, 10:37:32 PM6/5/15
to
Thanks to Doug and Kerry, who both posted interesting examples.

In the meantime, I had a shot at it myself and found that my specification
of the problem was inaccurate (and inadequate).

It would be very good to have a general hex function for COBOL but for the
specific reason I noted (dealing with color attributes), there needs to be
more.

I said that "sign is irrelevant" but I have since found out that I was
wrong.

(Experience is always the best teacher, but her fees are sometimes very
high...)

For the specifc requirement I have (which is about obtaining "color"
attributes from PowerCOBOL controls, by means of the COM/OLE interface), the
specs are as follows:
==================== start of description ===============================
OLE_COLOR
A four byte number defining a color.

COBOL equivalent: S9(9) COMP-5

The hexadecimal value of the four bytes (in the COMP-5 reverse order) is:
X"rrggbbss"

When ss (the most significant byte) is X"00", "rr" is Red, "gg" is Green,
"bb" is Blue.

When ss is X"80", "rr" contains a value indicating the system color value
(listed below),
and "gg" and "bb" should be zero.

Therefore, PowerCOBOL supports:
X"rrggbb00" (rr: Red, gg: Green, bb: Blue)
or
X"rr000080" (rr: as listed below)

00: Scroll bars
01: Desktop
02: Active title bar
03: Inactive title bar
04: Menu bar
05: Window background
06: Window frame
07: Menu text
08: Window Text
09: Active title bar text
0A: Active window border
0B: Inactive window border
0C: Application workspace
0D: Highlight
0E: Highlight text
0F: Button surface
10: Button shadow
11: Disabled text
12: Button text
13: Inactive title bar text
14: Button highlight
15: Button dark shadow
16: Button light shadow
17: Tool Tip text
18: Tool Tip background

You can set colors by using the color constants defined in PowerCOBOL (see
Color Constants for details) or by coding the following in COBOL:

01 COLOR-VALUE PIC S9(9) COMP-5.

01 COLOR REDEFINES COLOR-VALUE PIC X(4).

*> Make the text color blue.

MOVE X"0000FF00" TO COLOR.

MOVE COLOR-VALUE TO "ForeColor" OF StaticText1.

*> Make the character background color red.

MOVE 255 TO "HighlightColor" OF StaticText1.

*> Make the background color the button surface color.

MOVE X"0F000080" TO COLOR.

MOVE COLOR-VALUE TO "BackColor" OF StaticText1.

Notes:

1. The byte order is reversed on Intel 80x86 processors - hence the hex
values in the above examples.

2. You cannot store system color values in PIC S9(9) COMP-5 item because of
decimal truncation.
X"80xxxxxx" is equivalent to a 10 digit decimal number. Therefore, if you
want to store a system
color in a COBOL data item (e.g. in WORKING-STORAGE) you need to define it
as PIC S9(10) COMP-5.
This is not an issue if you move hex values to PowerCOBOL properties such as
the ForeColor property.
============================ end of description
=================================
Just before I get into the implications of the code I used and how it
evolved, here is some useful background for people who might want some...

USEFUL LINKS THAT HELP:

This one describes the process from the basics...
https://www.wisc-online.com/learn/formal-science/mathematics/tmh5406/an-algorithm-for-converting-a-decimal-number

This one gives a load of stuff about colours and is good for examples...(Bet
you didn't know there was Visual RPG... :-))
http://devnet.asna.com/documentation/Help110/AVR/_HTML/avrlrfSettingColors.htm

Now, MY CODE....

This is the first cut....

WORKING-STORAGE:

...
01 color pic s9(10) comp-5.
01 hex-color pic x(9).
01 quotient pic s9(10) comp.
01 rem pic s99 comp.
01 HV pic x(16) value "0123456789ABCDEF".
...
PROCEDURE DIVISION:

...
*----------------------------------------------------------
doColours section.
dsc000.

invoke objItem "GET-ForeColor"
returning color
end-invoke
move color to quotient
move zero to rem
move spaces to hex-color
move 1 to J
perform until quotient = 0
divide 16 into quotient
giving quotient
remainder rem
move HV (rem + 1: 1) to hex-color (J:1)
add 1 to J
end-perform
move hex-color to <a PIC X(9) field in a memory table, for subsequent
processing>
...

Guess what happened?

The refmodded reference threw an exception.
(The logic would indicate that it CAN'T, but it did... don't you love it
when that happens? :-))

Some investigation showed that the reason was because the passed color was
NEGATIVE and the rem was also negative.

(If the color is POSITIVE, the code works as intended)

Obviously, using the remainder as a direct base for the refmod when it is
negative, does not produce an index acceptable to COBOL...

The obvious solution was to make the remainder unsigned, possibly make the
color unsigned too. But if I do that, I probably WON'T get the value I need
as a base for the conversion to Hex...

I could check for negative color and divide by -16... but it all gets a bit
unwieldy.

(I messed around with it for an hour or so trying various ideas, but in the
end I just didn't like it so I'll look for another (better) solution.)

Currently, I'm looking at getting colours translated to hex as a separate
problem from just taking an integer and making its hex value.

I COULD pass the original signed integer returned as the attribute, to the
downstream C# code (which has all kinds of really cool functions to deal
with hex), but I'd like to solve this in COBOL and pass the HEX string to
the C# code...

I think a solution looking at the bytes and applying bitwise operations
might get me what I want. (Fujitsu provide the same COBOL subroutines that
Micro Focus do, so bitwise operations are possible.)

Meantime, if anyone manges to devise a hex routine that handles both signed
and unsigned integers in COMP-5 format correctly, I'd be very interested to
see it.

Cheers,

Pete Dashwood

unread,
Jun 6, 2015, 12:13:56 AM6/6/15
to
Normally, we would expect the compiler to create whatever work fields it
needed for this. If it really tries to use the same area of storage you
could certainly expect some odd results.

If you really must use STRING (and I don't recommend it here as refmodding
will achieve the same result with a fraction of the overhead) the you
probably need WITH POINTER to help it out.

For a very long time on System 360 we utilized the fact that storage was
fetched one byte at a time to do things like "ripple moves", where a
character would get propagated through a field, but you wouldn't expect the
same effect with STRING.
>
> Also note the addition of the ":1" in the reference modification...

Yes, it's required. :-)

I took the liberty of re-arranging your final code so as to obviate STRING
altogether, at the same time removing unnecessary work fields. The same
applies to Doug's.

...
01 HEX-OUTPUT-GROUP.
12 HEX-OUTPUT PIC X OCCURS 8
INDEXED BY HO-X1.
...
MOVE SPACES TO HEX-OUTPUT-GROUP
SET HO-X1 TO 8
MOVE 200063 TO DEC-QUOTIENT
DISPLAY 'DECIMAL NUMBER= ' DECIMAL-NUMBER
PERFORM UNTIL DEC-QUOTIENT = ZERO
DIVIDE DEC-QUOTIENT BY 16
GIVING DEC-QUOTIENT
REMAINDER DEC-REMAINDER
END-DIVIDE
MOVE HEX-DIGITS (DEC-REMAINDER + 1: 1) TO HEX-OUTPUT (HO-X1)
SET HO-X1 DOWN BY 1
END-PERFORM
...
The disadvantage of this is that it leaves the final hex string right
justified and it may have leading spaces in it. In languages where TRIM
functions are available this is no problem at all, but for COBOL you
probably need some code to remove them...

IF HEX-OUTPUT-GROUP IS NOT = SPACES
INSPECT HEX-OUTPUT-GROUP
TALLYING DEC-QUOTIENT *> DEC-QUOTIENT IS ALREADY ZERO
FOR LEADING SPACES
MOVE HEX-OUTPUT-GROUP (DEC-QUOTIENT + 1: 8 - DEC-QUOTIENT) TO
HEX-OUTPUT-GROUP
END-IF

This code is still much "tighter" than using STRING and much of it is
resolved at compile time.

Doug Miller

unread,
Jun 6, 2015, 10:45:10 AM6/6/15
to
"Pete Dashwood" <dash...@removethis.enternet.co.nz> wrote in news:ctet2kF5mjlU1
@mid.individual.net:

[...]
> I liked the END-DIVIDE. Not seen that before, although it makes perfect
> sense...

As soon as the END-xxxxxx scope delimiters became available in the language, I began
using them everywhere, whether needed or not.

Luuk

unread,
Jun 6, 2015, 1:01:19 PM6/6/15
to
After readin the above, i thought that this should be done by calling a
piece of c-code from cobol.

I have done some cobol back in 1990, and none after that,

And i want to learn coding c, but cannot find the time for it, since
before that...

;)


so here is my adapted code, 'stolen', and changed from:
http://www.opencobol.org/modules/bwiki/index.php?UserManual%2F2_3

luuk@opensuse:~/tmp/cobol> cat say.c
#include <stdio.h>
int say(char *hello, char *world)
{
int i;
for (i = 0; i < 6; i++)
putchar(hello[i]);
for (i = 0; i < 6; i++)
putchar(world[i]);
putchar('\n');
return 0;
}

int hex(int i)
{
int j;
char s[20];
sprintf(s, "%#010x", i);
for (j=0; j<10; j++)
putchar(s[j]);
putchar('\n');
return 0;
}

luuk@opensuse:~/tmp/cobol> cat hello.cob
IDENTIFICATION DIVISION.
PROGRAM-ID. hello.
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 HELLO PIC X(6) VALUE "Hello ".
01 WORLD PIC X(6) VALUE "World!".
01 INT1 PIC 9(6) VALUE 123456.
01 INT2 PIC 9(6) VALUE 1.
01 INT3 PIC 9(6) VALUE 10.
PROCEDURE DIVISION.
CALL "say" USING HELLO WORLD.
DISPLAY INT1.
CALL "hex" USING INT1.
DISPLAY INT2.
CALL "hex" USING INT2.
DISPLAY INT3.
CALL "hex" USING INT3.
STOP RUN.

and for the output:
luuk@opensuse:~/tmp/cobol> cc -shared -fPIC -o say.so say.c
luuk@opensuse:~/tmp/cobol> cobc -x -o hello hello.cob
luuk@opensuse:~/tmp/cobol> export COB_LIBRARY_PATH=.
luuk@opensuse:~/tmp/cobol> ./hello
Hello World!
123456
0x006021d0
000001
0x006021e0
000010
0x006021f0

hmmmz, time to call in the experts, to explain what i missed ;)



Pete Dashwood

unread,
Jun 6, 2015, 7:35:48 PM6/6/15
to
Yes, I'm a big fan of scope delimiters; remember the old days when a
misplaced full stop (or a smudge on printouts that did not have the clarity
they do today) could cause hours of debugging.

There is a certain elegance to keeping your code tidy with aligned verbs and
scope delimiters.

Pete Dashwood

unread,
Jun 6, 2015, 8:45:35 PM6/6/15
to
An interesting post, Luuk.

The Hello World stuff is a bit unnecessary but it does no harm.

So, you got the wrong results... (123456 in hex is 1E240, not 6021D0).

I don't claim to be an "expert" ('x' is the unknown quantity; a spurt is a
drip under pressure...) but I'll offer you my 2 cents anyway... :-)

It seems to me that the problem here is you are expecting the format string
in sprintf to magically convert your integer for you, as is usually the case
in C. As the format string you are using is correct (although I'd try
removing 010 for the width and just use %#x directly...also, a capital X
will upper case your hex and it just looks a bit neater...), the only
possibility I can see is that the function is NOT getting an integer (or
what it understands to be an integer in C). I messed around with a hex
calculator to see if I could work out exactly what is going wrong but I
can't get a definitive answer.

If we have a look at the COBOL we see the "integers" are actually character
strings.

Try making these pictures USAGE COMP and see if you get a better result.

HTH,

Pete Dashwood

unread,
Jun 6, 2015, 11:23:30 PM6/6/15
to
Pete Dashwood wrote:
<snipped>>
No, it actually didn't... I reversed the order of the hex digits by
incrementing instead of decrementing... :-)

There were a number of iterations of this code before I arrived at something
close to what I posted in response to Kerry and Doug.



<snipped>>
> (I messed around with it for an hour or so trying various ideas, but
> in the end I just didn't like it so I'll look for another (better)
> solution.)
> Currently, I'm looking at getting colours translated to hex as a
> separate problem from just taking an integer and making its hex value.

THAT was the key to solving this...stop focusing on the HEX stuff and deal
with the colours...

<snipped>
>
> I think a solution looking at the bytes and applying bitwise
> operations might get me what I want. (Fujitsu provide the same COBOL
> subroutines that Micro Focus do, so bitwise operations are possible.)

Unnecessary complexity.

Here's the final code:

WORKING-STORAGE:
...
01 color pic s9(9) comp-5.
01 colorX redefines color pic x(4).
01 hex-color-group pic X(6).
01 hex-value pic xx.
01 quotient pic s9(10) comp.
01 rem pic 99.
01 HV pic x(16) value "0123456789ABCDEF".
01 RR pic xx.
01 GG Pic xx.
01 BB pic xx.
01 littleComp pic s9(4) comp.
01 filler redefines littleComp.
12 lc-1 pic x.
12 lc-2 pic x.
...

PROCEDURE DIVISION:

...
*----------------------------------------------------------
doColours section.
dsc000.
*> this code caters for custom colours from PowerCOBOL as well as
*> the standard colours.
invoke objItem "GET-BackColor"
returning color
end-invoke
*> if colorX, byte 4 = x'80' it is a system colour and we can let it
*> default on the Windows Form. (set the value to DEFLT)
*> if colorX, byte 4 = x'00' it is a RGB color and we need to pass
*> the hex value for each of the first 3 bytes into the
*> in-memory collection for conversion to XML.
perform get-hex-value
move hex-color-group to ctlBackClr (efd-x1)

invoke objItem "GET-ForeColor"
returning color
end-invoke
*> if colorX, byte 4 = x'80' it is a system colour and we can let it
*> default on the Windows Form. (set the value to DEFT)
*> if colorX, byte 4 = x'00' it is a RGB color and we need to pass
*> the hex value for each of the first 3 bytes into the
*> in-memory collection for conversion to XML.
perform get-hex-value
move hex-color-group to ctlForeClr (efd-x1)
.
dsc999.
exit.
*----------------------------------------------------------
get-hex-value section.
ghv000.
move spaces to hex-color-group
move zero to RR
GG
BB

if colorX (4: 1) = X"00"
*> get hex values for the RGB Bytes...
move colorX (1: 1) to lc-2
move X"00" to lc-1
*> code to calc hex. input: littleComp, returns: hex-value
move zero to rem
hex-value
move 2 to M *> M is general purpose subscript
perform until littleComp = 0
divide 16 into littleComp
giving littleComp
remainder rem
move HV (rem + 1: 1) to hex-value (M: 1)
subtract 1 from M
end-perform
move hex-value to RR
move colorX (2: 1) to lc-2
move X"00" to lc-1
*> code to calc hex. input: littleComp, returns: hex-value
move zero to rem
hex-value
move 2 to M
perform until littleComp = 0
divide 16 into littleComp
giving littleComp
remainder rem
move HV (rem + 1: 1) to hex-value (M: 1)
subtract 1 from M
end-perform
move hex-value to GG
move colorX (3: 1) to lc-2
move X"00" to lc-1
*> code to calc hex. input: littleComp, returns: hex-value
move zero to rem
hex-value
move 2 to M
perform until littleComp = 0
divide 16 into littleComp
giving littleComp
remainder rem
move HV (rem + 1: 1) to hex-value (M: 1)
subtract 1 from M
end-perform
move hex-value to BB
*> RR,GG,BB now have hex values. String them together into
hex-color-group.
string
RR
delimited by size
GG
delimited by size
BB
delimited by size
into hex-color-group
end-string
else
move "DEFLT" to hex-color-group
end-if
.
ghv999.
exit.

And here is an extract of the end result:

<?xml version="1.0" encoding="utf-8" standalone="yes" ?>
- <!-- PowerCOBOL Form description generated by PRIMA Tool XPCForm.
-->
- <Project ProjName="PCOBSample">
- <Form FormName="PCOBSampleForm1">
<Text>A sample PowerCOBOL form</Text>
- <Dimensions>
<TopY>00000</TopY>
<TopX>00074</TopX>
<Height>00536</Height>
<Width>00669</Width>
</Dimensions>
- <Colors>
<Forecolor>DEFLT</Forecolor>
<Backcolor>FFFF00</Backcolor>
</Colors>
- <Controls>
- <Control CtlName="butOK">
<Type>Command button</Type>
<Text>OK - CloseMe</Text>
<Parent>PCOBSampleForm</Parent>
- <Dimensions>
<TopY>00494</TopY>
<TopX>00560</TopX>
<Height>00028</Height>
<Width>00100</Width>
</Dimensions>
- <Colors>
<Forecolor>DEFLT</Forecolor>
<Backcolor>DEFLT</Backcolor>
</Colors>
<TabNDX>001</TabNDX>
</Control>
...

You can see that the Form has a background colour of yellow (0xFFFF00) but
the button control is using sytem colours so it defaults.

All of the above information is derived using COBOL in a PowerCOBOL event
process (FormOpened), but the XML file is actually created by a C# COM
component that gets called by the COBOL and is passed an in-memory
collection (COBOL Table) after the detection and analysis of the controls on
the form is done.

Thanks to all who contributed to the thread. The interaction here gave me
some things to think about and helped me clarify my own thoughts. I got a
better result than I might have on my own.

Finally, I still think COBOL needs an intrinsinc function or a callable
module that can take in strings or integers and return a hex string.

If I get time I'll write one and make it public.

Luuk

unread,
Jun 7, 2015, 12:33:00 PM6/7/15
to
that's why i warned about the code being a 'copy'... ;)

>
> So, you got the wrong results... (123456 in hex is 1E240, not 6021D0).
>
> I don't claim to be an "expert" ('x' is the unknown quantity; a spurt is a
> drip under pressure...) but I'll offer you my 2 cents anyway... :-)
>
> It seems to me that the problem here is you are expecting the format string
> in sprintf to magically convert your integer for you, as is usually the case
> in C. As the format string you are using is correct (although I'd try
> removing 010 for the width and just use %#x directly...also, a capital X
> will upper case your hex and it just looks a bit neater...), the only
> possibility I can see is that the function is NOT getting an integer (or
> what it understands to be an integer in C). I messed around with a hex
> calculator to see if I could work out exactly what is going wrong but I
> can't get a definitive answer.
>

lol, i removed the '010', and got these results:
luuk@opensuse:~/tmp/cobol> ./hello_hex
0X1E240
0X1240
0XA240

so, i took the liberty of putting them back in my program ;)

> If we have a look at the COBOL we see the "integers" are actually character
> strings.
>
> Try making these pictures USAGE COMP and see if you get a better result.
>
> HTH,
>
> Pete.
>

Because 'USING COMP' did not make the difference (*), i went with the
statement "integers" are actually character strings.

(*) I had to open the book "COBOL", by W.B.C. Ebbinkhijsen, to know how
to do that ;)

$> cat hex.c
#include <stdio.h>
int hex(char *i)
{
int j;
int k = 0;
char s[20];
sscanf(i, "%d", &k);
sprintf(s, "%#010X", k);
for (j=0; j<10; j++)
putchar(s[j]);
putchar('\n');
return 0;
}


$> cat hello_hex.cob
IDENTIFICATION DIVISION.
PROGRAM-ID. hello_hex.
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 INT1 PIC 9(6) VALUE 123456.
01 INT2 PIC 9(6) VALUE 1.
01 INT3 PIC 9(6) VALUE 10.
PROCEDURE DIVISION.
CALL "hex" USING INT1.
CALL "hex" USING INT2.
CALL "hex" USING INT3.
STOP RUN.

$> cc -shared -fPIC -o hex.so hex.c
$> cobc -x -o hello_hex hello_hex.cob
$> export COB_LIBRARY_PATH=.
$> ./hello_hex
0X0001E240
0X00000001
0X0000000A
$>



docd...@panix.com

unread,
Jun 7, 2015, 7:35:53 PM6/7/15
to
In article <cthrpe...@mid.individual.net>,
Pete Dashwood <dash...@removethis.enternet.co.nz> wrote:

[snip]

>Finally, I still think COBOL needs an intrinsinc function or a callable
>module that can take in strings or integers and return a hex string.

My memory is, admittedly, porous... but didn't Mr Svalgaard include one in
ETKPAK?

DD

Pete Dashwood

unread,
Jun 7, 2015, 7:39:47 PM6/7/15
to
Sorry, Doc, not heard of that...

Pete Dashwood

unread,
Jun 7, 2015, 8:31:43 PM6/7/15
to
Luuk wrote:
<snipped>

My response was helpful, then?

Glad you cracked it.

I still think calling C is an overkill for this, but I agree it is a matter
of opinion and yours is every bit as valid as mine :-)

I think we've established that the calculations can be done in COBOL pretty
easily (it's just the negative integers I'm not sure about, and I'm sure
that could be resolved if I had some time to spend on it).

While I'm a firm believer in using the right tools for the job, sometimes
the "inconvenience" of calling into another language where a certain
facility is easily available, outweighs the effort required to do it in the
language where it is a bit more "difficult". Converting an integer to Hex is
readily available in a number of languages, just not in COBOL. (Doc
mentioned a library which may make it available to COBOL). This is a simple
function really and, unless I had a requirement to do a fair bit of this in
a given program I wouldn't be calling out for it. (in fact, it is SO simple
you'll notice that I duplicated it 3 times (for R,G, and B) in the final
code I posted. Normally, I consider it a failure if I have to duplicate code
in a program... Also, I agree that it is even simpler in C where the format
string does it for you, but there is some infrastructure you need to put in
place so you can use that format string...)

On the other hand, I have no qualms about calling to C# when I need to use
LINQ for creating and manipulating XML (even though you CAN do it (without
LINQ) in COBOL...).

For example, suppose I want to get the names of all the controls on a form,
from XML. (Typically, there will be at least a dozen...)

I would have to traverse the XML hierarchy reading each element, detecting
what is a control, and checking if the form is its parent. (Nested controls,
like options or check boxes within a group are NOT children of the form;
they are parented by their container). I can't find the parentage until I
already have the control name so it involves getting and remembering the
right elements, then continuing to read until parentage is encountered.
Tricky stuff (and one of the reasons that people in the COBOL community
generally roll their eyes when you say "XML").

But, if I use LINQ-to-XML, I can express my request in a simple, SQL-Like
way, and let LINQ take care of all the "grunt work"...

var FormKids = from x in xml.Descendants("Control")
where
x.Element("Parent").Value == FormName
select
x.Attribute("CtlName").Value;

foreach (string childControl in FormKids)
{ ...}

This creates a collection (list, if you like...) of qualifying control names
(FormKids) which I can then iterate over with foreach. (process one by
one...)

Part of the Programmer's art is balancing the effort required to use tools,
against the facility they provide.

To do that well, you need to have options, and that's why I have been
banging on here for the last 20 years to encourage people to expand their
skill sets. (It's not because I hate COBOL; quite the contrary.)

To a man with only a hammer, everything is a nail. Even if you are an
extremely good hammer wielder, there are times when a different tool might
be more appropriate.

Horses for courses.

Arnold Trembley

unread,
Jun 9, 2015, 3:04:40 AM6/9/15
to
It's also available on my website, with Leif Svalgaard's permission.

www.arnoldtrembley.com/ETKPAK.ZIP



--
http://www.arnoldtrembley.com/

docd...@panix.com

unread,
Jun 9, 2015, 8:20:57 AM6/9/15
to
In article <ctk63d...@mid.individual.net>,
Pete Dashwood <dash...@removethis.enternet.co.nz> wrote:

[snip]

>This is a simple
>function really and, unless I had a requirement to do a fair bit of this in
>a given program I wouldn't be calling out for it.

It should not be difficult to dig up a century's worth of experience
around these parts... you start, Mr Dashwood:

How many years' exposure do you have to COBOL and how many times has there
been a COmmon Business need to get something's value in hex?

(note the require for a Business need and not 'Gee, that'd be really
keen!'... and for 'value in hex' one may include 'value in octal')

DD

Pete Dashwood

unread,
Jun 9, 2015, 7:34:39 PM6/9/15
to
That's a very valid point and I would have to say "Never"... as far as
applications go.

But there is an infrastructure required to create those applications and
that infrastructure has a place for hex.

As a very young man, when tools were thin on the ground, I remember poring
over octal dumps on ICL 1900s (6 bit "bytes" as part of a 24 bit word) and
later over hex dumps on System 360. Certainly hex wasn't an application
requirement, but you got the application a lot quicker because hex was part
of the development infrastructure.

Being a "shorthand" form of binary, it has its uses on machines that are
fundamentally binary.

Sometimes you may be required to fix COBOL on an unfamiliar platform and you
decide that dropping a few DISPLAYs into the source and recompiling may get
you what you need quicker, and with less effort, than learning the details
of the tools available in that environment. (See my conclusion under "horses
for courses"...) If those displays could be in hex, it may have some value.

But the fact is that the world (including the world of commerce) has changed
and moved on. Different devices that can support colour displays are the
accepted norm; we are no longer limited to green lineflo and punched cards.
PowerCOBOL is an application development environment that provides a good
GUI for COBOL. You CAN limit yourself to the 16 standard colours (as you
might with MFS on a 3270) and address them by name, in which case you won't
care about hex, but if you want to cusomise your UI you need hex.

Nevertheless, it is true that applications generally don't need hex.

Applications don't need bitwise operations generally either, but most COBOL
implementations provide them. In fact, you could argue that applications
don't need any form of number other than display, and yet there is a
plethora of COMP and COMP-x formats on most COBOL platforms.

Developing applications may have requirements that exceed the actual
functional spec., or development may be facilitated with things that don't
apply directly to the application.

Clark F Morris

unread,
Jun 9, 2015, 9:18:42 PM6/9/15
to
The shop where I spent most of my time had bit switches on the
customer, product and open account files and I doubt we were the only
shop that had them. Saving bytes on tape and disk was important in
1966 when these files were designed. Unfortunately in 2015, IBM COBOL
for the z series still has not acknowledged there is a need for USAGE
BIT let alone for handling the Decimal Floating Point and added
rounding options that are built into the z series and that Mike
Cowlinshaw of Rexx fame did much to specify and work for. I might add
that because of intermodule overhead, I snitched COBOL means of
packing and unpacking bit switches from comp.lang.cobol postings, in
part because I needed them at another shop for dealing with IBM SMF
(System accounting) records. If on a z series I would take advantage
of the decimal usage and INSPECT ... CONVERTING to get a character
representation of a fixed length hex string, again to save intermodule
overhead and avoid the use of assembler. I have written both types of
routine in assembler and made them re-entrant.

Clark Morris

docd...@panix.com

unread,
Jun 10, 2015, 8:09:31 AM6/10/15
to
In article <ctpbgd...@mid.individual.net>,
Pete Dashwood <dash...@removethis.enternet.co.nz> wrote:
>docd...@panix.com wrote:

[snip]

>> It should not be difficult to dig up a century's worth of experience
>> around these parts... you start, Mr Dashwood:
>>
>> How many years' exposure do you have to COBOL and how many times has
>> there been a COmmon Business need to get something's value in hex?
>>
>> (note the require for a Business need and not 'Gee, that'd be really
>> keen!'... and for 'value in hex' one may include 'value in octal')
>
>That's a very valid point and I would have to say "Never"... as far as
>applications go.
>
>But there is an infrastructure required to create those applications and
>that infrastructure has a place for hex.

COBOL is, by architecture, creation and use, a language for
applications... unless something has changed last I checked. Using COBOL
for infrastructure would fall into the 'Golly, that'd be solid, Jackson!'
as mentioned above.

>
>As a very young man, when tools were thin on the ground, I remember poring
>over octal dumps on ICL 1900s (6 bit "bytes" as part of a 24 bit word) and
>later over hex dumps on System 360.

This sounds like the mid 1960s... so let's call it 50 years' experience
with never having 'a COmmon Business need to get something's value in hex'
(as asked above).

Fifty years down, fifty to go. Anyone else?

[snip]

>Nevertheless, it is true that applications generally don't need hex.

Gently, Mr Dashwood... listen to yourself; do you hear a difference
between 'generally don't need' and 'never in fifty years'?

DD

Pete Dashwood

unread,
Jun 10, 2015, 8:48:34 PM6/10/15
to
docd...@panix.com wrote:
> In article <ctpbgd...@mid.individual.net>,
> Pete Dashwood <dash...@removethis.enternet.co.nz> wrote:
>> docd...@panix.com wrote:
>
> [snip]
>
>> Nevertheless, it is true that applications generally don't need hex.
>
> Gently, Mr Dashwood... listen to yourself; do you hear a difference
> between 'generally don't need' and 'never in fifty years'?
>

Nope.

Both statements sound perfectly compatible to me.

I am currently working on a (Power)COBOL application that DOES require hex
(for customizing colours in the User Interface), hence the post here.

Who knows what tomorrow may bring?

There are no "perfect programs"; there are only programs that have not
crashed... yet.

docd...@panix.com

unread,
Jun 10, 2015, 9:11:45 PM6/10/15
to
In article <cts46v...@mid.individual.net>,
Pete Dashwood <dash...@removethis.enternet.co.nz> wrote:
>docd...@panix.com wrote:
>> In article <ctpbgd...@mid.individual.net>,
>> Pete Dashwood <dash...@removethis.enternet.co.nz> wrote:
>>> docd...@panix.com wrote:
>>
>> [snip]
>>
>>> Nevertheless, it is true that applications generally don't need hex.
>>
>> Gently, Mr Dashwood... listen to yourself; do you hear a difference
>> between 'generally don't need' and 'never in fifty years'?
>>
>
>Nope.

Perhaps others might.

[snip]

>Who knows what tomorrow may bring?

We both do. It may bring the sun rising in the east, the laughter of
children and doddering codgers insisting that they know best.

I've brewed a lovely pot of 50/50 jasmine/pouchong. Fancy a cup?

DD

Pete Dashwood

unread,
Jun 11, 2015, 9:42:24 PM6/11/15
to
Ah, you've been visiting the "COBOL programmers" group on LinkedIn again...
:-)
>
> I've brewed a lovely pot of 50/50 jasmine/pouchong. Fancy a cup?

It sounds delicious, Doc.

Thanks for the invite but distances preclude it at the moment. Maybe, if I'm
ever in your part of the world again...

I'm trying not to travel any more... :-)

Obviously, if any regulars here (including yourself) are visiting Aotearoa,
there is always a libation at my place. (I'm in the Tauranga phone book.)

Pete Dashwood

unread,
Jun 11, 2015, 9:56:36 PM6/11/15
to
They were also being accessed in BAL, where bits are really no problem.

As the landslide to "higher level" languages started to rumble, the
Assembler programming pebbles really didn't get to vote and the rest is
history.


> Unfortunately in 2015, IBM COBOL
> for the z series still has not acknowledged there is a need for USAGE
> BIT let alone for handling the Decimal Floating Point and added
> rounding options that are built into the z series and that Mike
> Cowlinshaw of Rexx fame did much to specify and work for.

You can see their point, though, Clark. The idea is to move people away from
the lower levels and there is a considerable cost in implementing such
support into what could only be a vendor extension to an increasingly less
relevant programming language. If you had to make a financial case for doing
it, it would be hard.

I ceded Doc's point that the majority of APPLICATIONS don't require hex
(and, by implication, bit flipping.) You have noted at first hand that some
ancient file structures actually DO need it, but I think you'd agree, it is
a very small minority of sites that would use it.

> I might add
> that because of intermodule overhead, I snitched COBOL means of
> packing and unpacking bit switches from comp.lang.cobol postings, in
> part because I needed them at another shop for dealing with IBM SMF
> (System accounting) records. If on a z series I would take advantage
> of the decimal usage and INSPECT ... CONVERTING to get a character
> representation of a fixed length hex string, again to save intermodule
> overhead and avoid the use of assembler.

It's an imaginative approach.


Pete

robin....@gmail.com

unread,
Jun 16, 2015, 9:48:33 AM6/16/15
to
On Friday, June 5, 2015 at 1:53:03 PM UTC+10, Pete Dashwood wrote:
> I was surprised when looking through the COBOL intrinsic functions to NOT
> find anything that will convert to Hexadecimal.
>
> (Yes, I can write something to do the necessary arithmetic, but, in this day
> and age I wouldn't expect to have to.)
>
> Does anybody have a routine that can take in a NUMBER (up to 10 digits) and
> produce a Hex string from it?

You should be able to write your own.
Won't take long.

Or you could call PL/I.

docd...@panix.com

unread,
Jun 16, 2015, 1:51:07 PM6/16/15
to
In article <624fe628-c6e7-4355...@googlegroups.com>,
<robin....@gmail.com> wrote:
>On Friday, June 5, 2015 at 1:53:03 PM UTC+10, Pete Dashwood wrote:
>> I was surprised when looking through the COBOL intrinsic functions to NOT
>> find anything that will convert to Hexadecimal.
>>
>> (Yes, I can write something to do the necessary arithmetic, but, in this day
>> and age I wouldn't expect to have to.)
>>
>> Does anybody have a routine that can take in a NUMBER (up to 10 digits) and
>> produce a Hex string from it?
>
>You should be able to write your own.
>Won't take long.
>
>Or you could call PL/I.

Henry IV, Part I, Act 3, scene i:

Glendower: I can call spirits from the vasty deep.

Hotspur: Why, so can I, or any other man, but will they come when you do
call for them?

DD

Pete Dashwood

unread,
Jun 16, 2015, 7:57:02 PM6/16/15
to
:-)

Precisely...

Pete.

Pete Dashwood

unread,
Jun 16, 2015, 8:01:36 PM6/16/15
to
robin....@gmail.com wrote:
> On Friday, June 5, 2015 at 1:53:03 PM UTC+10, Pete Dashwood wrote:
>> I was surprised when looking through the COBOL intrinsic functions
>> to NOT find anything that will convert to Hexadecimal.
>>
>> (Yes, I can write something to do the necessary arithmetic, but, in
>> this day and age I wouldn't expect to have to.)
>>
>> Does anybody have a routine that can take in a NUMBER (up to 10
>> digits) and produce a Hex string from it?
>
> You should be able to write your own.

Yes, Robin.
As noted above, I am more than capable of writing my own, did so, and posted
the code in this thread, but that was not the point.

> Won't take long.

"long" is a subjective term.

>
> Or you could call PL/I.

If I don't have a PL/1 compiler (and I don't...), results of such a call
might be disappointing...

>>
>> I can see several ways to do it, so I'll be interested if anyone
>> here has a really cool COBOL way.

If you'd like to post your PL/1 solution, I, for one, would be interested to
see it.

robin....@gmail.com

unread,
Jun 19, 2015, 4:56:02 AM6/19/15
to
On Wednesday, June 17, 2015 at 10:01:36 AM UTC+10, Pete Dashwood wrote:
> r.no...@gmail.com wrote:
> > On Friday, June 5, 2015 at 1:53:03 PM UTC+10, Pete Dashwood wrote:
> >> I was surprised when looking through the COBOL intrinsic functions
> >> to NOT find anything that will convert to Hexadecimal.
> >>
> >> (Yes, I can write something to do the necessary arithmetic, but, in
> >> this day and age I wouldn't expect to have to.)
> >>
> >> Does anybody have a routine that can take in a NUMBER (up to 10
> >> digits) and produce a Hex string from it?
> >
> > You should be able to write your own.
>
> Yes, Robin.
> As noted above, I am more than capable of writing my own, did so, and posted
> the code in this thread,

Yes, but only after you asked everyone for some code,
and folks posted theirs.

> but that was not the point.
>
> > Won't take long.
>
> "long" is a subjective term.
>
> >
> > Or you could call PL/I.
>
> If I don't have a PL/1 compiler (and I don't...), results of such a call
> might be disappointing...
>
> >>
> >> I can see several ways to do it, so I'll be interested if anyone
> >> here has a really cool COBOL way.
>
> If you'd like to post your PL/1 solution, I, for one, would be interested to
> see it.

hex: procedure (k) returns (character (8));
declare k fixed binary (31);
declare h character (8) varying initial ('');
declare (i, j) fixed binary;
declare hexdigits character (16) initial ('0123456789ABCDEF');
do i = 28 to 0 by -4;
j = iand(isrl(k, i), 15);
h = h || substr(hexdigits, j+1, 1);
end;
return (h);
end hex;

Pete Dashwood

unread,
Jun 21, 2015, 9:17:48 PM6/21/15
to
robin....@gmail.com wrote:
> On Wednesday, June 17, 2015 at 10:01:36 AM UTC+10, Pete Dashwood
> wrote:
>> r.no...@gmail.com wrote:
>>> On Friday, June 5, 2015 at 1:53:03 PM UTC+10, Pete Dashwood wrote:
>>>> I was surprised when looking through the COBOL intrinsic functions
>>>> to NOT find anything that will convert to Hexadecimal.
>>>>
>>>> (Yes, I can write something to do the necessary arithmetic, but, in
>>>> this day and age I wouldn't expect to have to.)
>>>>
>>>> Does anybody have a routine that can take in a NUMBER (up to 10
>>>> digits) and produce a Hex string from it?
>>>
>>> You should be able to write your own.
>>
>> Yes, Robin.
>> As noted above, I am more than capable of writing my own, did so,
>> and posted the code in this thread,
>
> Yes, but only after you asked everyone for some code,
> and folks posted theirs.

The nature of my enquiry was such that other people would post their ideas.

I posted the final solution I used as a matter of courtesy. You are not
suggesting that had nobody posted, I would have been unable to solve this
problem?

I didn't want to re-invent the wheel, but that doesn't mean I couldn't...

>
>> but that was not the point.
>>
>>> Won't take long.
>>
>> "long" is a subjective term.
>>
>>>
>>> Or you could call PL/I.
>>
>> If I don't have a PL/1 compiler (and I don't...), results of such a
>> call might be disappointing...
>>
>>>>
>>>> I can see several ways to do it, so I'll be interested if anyone
>>>> here has a really cool COBOL way.
>>
>> If you'd like to post your PL/1 solution, I, for one, would be
>> interested to see it.
>
> hex: procedure (k) returns (character (8));
> declare k fixed binary (31);
> declare h character (8) varying initial ('');
> declare (i, j) fixed binary;
> declare hexdigits character (16) initial ('0123456789ABCDEF');
> do i = 28 to 0 by -4;
> j = iand(isrl(k, i), 15);
> h = h || substr(hexdigits, j+1, 1);
> end;
> return (h);
> end hex;

Thanks for posting that. The bitwise operations make it different from the
COBOL solution and it is a tidy procedure.

Bruce M. Axtens

unread,
Oct 25, 2015, 1:48:07 AM10/25/15
to
Thought I'd have a go at this too even though it's a while back.

(Visual COBOL 2.3, Visual Studio 2015, Windows 10 Home 64bit.)

identification division.
function-id. HEX.

data division.
working-storage section.
01 hexa pic x(16) value "0123456789ABCDEF".
01 modu binary-char value 0.
01 hexc pic x value space.

linkage section.
01 decima binary-long.
88 is-zero value zero.
01 hexadecima pic x(16) value spaces.

procedure division using decima returning hexadecima.
if is-zero
set hexadecima to "0"
else
perform until is-zero
divide decima by 16 giving decima remainder modu
add 1 to modu
move hexa(modu:) to hexc
set hexadecima to hexc & hexadecima
end-perform
end-if.

goback.
end function HEX.

I do have GnuCOBOL 2.0 so I should try to make it work in that too.

Bruce/bugmagnet

Pete Dashwood

unread,
Oct 28, 2015, 11:19:58 PM10/28/15
to
An interesting solution, Bruce.

Thanks for posting it.

I was interested to see the use of SET in a way which I did not think was
valid.

(set hexadecima to hexc & hexadecima)

It is a nice shorthand way to concatenate a string from right to left
without using INSPECT or STRING...

Is this a vendor extension?

bruce....@gmail.com

unread,
Oct 29, 2015, 2:17:22 AM10/29/15
to
On Thursday, 29 October 2015 11:19:58 UTC+8, Pete Dashwood wrote:
> Bruce M. Axtens wrote:
> > Thought I'd have a go at this too even though it's a while back.
> An interesting solution, Bruce.
>
> Thanks for posting it.
>
> I was interested to see the use of SET in a way which I did not think was
> valid.
>
> (set hexadecima to hexc & hexadecima)
>
> It is a nice shorthand way to concatenate a string from right to left
> without using INSPECT or STRING...
>
> Is this a vendor extension?

I don't know. I did try to do the same in GnuCOBOL but got caught up in a discussion <https://sourceforge.net/p/open-cobol/discussion/help/thread/6eb2c325/> around problems I had with STRING. I should have a look sometime.

I don't get to do much COBOL at all and only downloaded MFCOBOL on a whim to answer <https://groups.google.com/forum/#!topic/comp.lang.cobol/UPDq2N0cHxk>. I'm programming language junkie.

Bruce/bugmagnet

bruce....@gmail.com

unread,
Oct 29, 2015, 5:38:43 AM10/29/15
to
This works in GnuCOBOL 2.0 but the SET stuff certainly doesn't

IDENTIFICATION DIVISION.
PROGRAM-ID. AMPER.
ENVIRONMENT DIVISION.
DATA DIVISION.
PROCEDURE DIVISION.
*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-*-
MAIN-PROCEDURE.
DISPLAY "Hello" & " world".
STOP RUN.
END PROGRAM AMPER.

Bruce/bugmagnet

bwti...@gmail.com

unread,
Dec 1, 2015, 2:40:37 AM12/1/15
to
On Thursday, June 4, 2015 at 11:53:03 PM UTC-4, Pete Dashwood wrote:
> I was surprised when looking through the COBOL intrinsic functions to NOT
> find anything that will convert to Hexadecimal.
>
> (Yes, I can write something to do the necessary arithmetic, but, in this day
> and age I wouldn't expect to have to.)
>
> Does anybody have a routine that can take in a NUMBER (up to 10 digits) and
> produce a Hex string from it?
>
> Input can be any format you like, but probably pic 9(10) will ensure that
> the actual positive integer value is represented correctly. (Sign is
> irrelevant for this exercise...)
>
> I need to use this for determining colours for both the web and the
> desktop.
>
> PowerCOBOL uses S9(9) comp-5 (but some of the numbers can be 10 digits, so
> it doesn't work properly, and the numbers represent RGB values in
> little-Endian so the position of them matters. I believe it is possible to
> take the actual decimal value and convert that to hex so that the requisite
> values for RG and B can be obtained.
>
> But just having a function or subroutine to produce the Hex could be useful
> in any case.
>
> I can see several ways to do it, so I'll be interested if anyone here has a
> really cool COBOL way.
>
> Pete.
> --
> "I used to write COBOL...now I can do anything."

This is really late to the party, but here's an x86_64 assembler version.

# Display 64 bit values as hexadecimal
# x86_64 ABI
# Author: Brian Tiffin
# Public Domain sample
# Modified: 2015-12-01/02:23-0500
# Tectonics:
# cobc -x program.cob ashex.s

.section .data
inval: .quad 0
hexbuf: .ascii " "
msglen: .quad . - hexbuf

# set the entry point
.section .text
.globl ashex
ashex:
pushq %rbx

# initialze the output buffer
mov %rdi, %rdx
lea hexbuf, %rdi
mov msglen, %ecx
mov $' ', %eax
rep stosb

# format the quad word in rdi for display
lea hexbuf, %rdi
mov %rdx, %rax
mov $16, %rbx
xor %rcx, %rcx

# divide by 16, saving digit, until zero
divide:
xor %rdx, %rdx
div %rbx
push %rdx
inc %rcx
or %rax, %rax
jnz divide

# store ASCII value of digits into buffer
digits:
pop %rdx
cmp $9, %dl
jle nothex
add $7, %dl
nothex:
add $'0', %dl
mov %dl, (%rdi)
inc %rdi
loop digits

# return the address of hexbuf
popq %rbx
lea hexbuf, %rax
ret

Called as

identification division.
program-id. hexer.
data division.

working-storage section.
01 hexbuf pic x(8) based.

procedure division.
call "ashex" using by value 42 returning address of hexbuf
display ":" hexbuf ":"

goback.
end program hexer.

and

prompt$ cobc -x shorter-hex.cob ashex.s
prompt$ ./shorter-hex
:2A :

But better with

*> Copyright 2015 Brian Tiffin
*> GNU Lesser General Public License, LGPL, 3.0 (or greater)
*> TECTONICS
*> cobc -x -g -debug hexer.cob ashex.s
*> ***************************************************************
identification division.
program-id. hexer.
author. Brian Tiffin.
date-written. 2015-11-25/20:42-0500.
date-modified. 2015-12-01/02:24-0500.
remarks. Display some values as hexadecimal.

environment division.
configuration section.
source-computer.
object-computer.
repository.
function all intrinsic.

data division.

working-storage section.
01 hexbuf pic x(8) based.
01 lot pic 99.
01 samples.
05 n usage binary-double occurs 8 times.

procedure division.

move -4 to n(1)
move -1 to n(2)
move 0 to n(3)
move 255 to n(4)
move factorial(19) to n(5)
move h"decafbad" to n(6)

perform varying lot from 1 by 1 until lot > 6
call "ashex" using
by value n(lot)
returning address of hexbuf
on exception
display "no ashex linkage" upon syserr
perform hard-exception
end-call
display n(lot) " :" trim(hexbuf) ":"
move spaces to hexbuf
end-perform

goback.
*> ***************************************************************

*> informational warnings and abends
soft-exception.
display space upon syserr
display "--Exception report-- " upon syserr
display "Time of excepion " current-date upon syserr
display "Module: " module-id upon syserr
display "Module-path: " module-path upon syserr
display "Module-source: " module-source upon syserr
display "Exception-file: " exception-file upon syserr
display "Exception-status: " exception-status upon syserr
display "Exception-location: " exception-location upon syserr
display "Exception-statement: " exception-statement upon syserr
.

hard-exception.
perform soft-exception
stop run returning 127
.

end program hexer.

and

prompt$ cobc -xj hexer.cob ashex.s
-00000000000000000004 :FFFFFFFC:
-00000000000000000001 :FFFFFFFF:
+00000000000000000000 :0:
+00000000000000000255 :FF:
+00121645100408832000 :6890000:
+00000000003737844653 :DECAFBAD:

Excuse the necro posting, I've been horsing around with an assembler integration entry in the GnuCOBOL FAQ.

The GNU lightning JIT assembly at run-time part of that entry was way too much fun. http://open-cobol.sourceforge.net/faq/#gnu-lightning

Robert Wessel

unread,
Dec 1, 2015, 3:56:19 AM12/1/15
to
That may be the least efficient assembler hex conversion routine ever
(for starters, a shift would be something like 50 times faster than a
divide). And the return of a pointer to a static buffer is almost
always problematic. Nor are hex numbers longer than 8 digits will be
deal with correctly.

bwti...@gmail.com

unread,
Dec 1, 2015, 4:19:59 AM12/1/15
to
On Tuesday, December 1, 2015 at 3:56:19 AM UTC-5, robert...@yahoo.com wrote:
Fair critique, Robert. I'm only a few days into a foray with assembly. Still very much the noob when it comes to gas programming.

More than willing to accept wisdoms and pointers.

Cheers

bwti...@gmail.com

unread,
Dec 1, 2015, 8:19:10 AM12/1/15
to

> >
> > That may be the least efficient assembler hex conversion routine ever
> > (for starters, a shift would be something like 50 times faster than a
> > divide). And the return of a pointer to a static buffer is almost
> > always problematic. Nor are hex numbers longer than 8 digits will be
> > deal with correctly.
>
> Fair critique, Robert. I'm only a few days into a foray with assembly. Still very much the noob when it comes to gas programming.
>
> More than willing to accept wisdoms and pointers.
>
> Cheers

And I couldn't handle it. Had to sit down and fix it this morning.

# Routine for base conversion
# x86_64 ABI
# Author: Brian Tiffin
# Public Domain sample
# Modified: 2015-12-01/08:14-0500
# Tectonics:
# cobc -x program.cob ashex.s

# set the entry point
.section .text
.globl ashex

ashex:
# value is %rdi, outbuffer is %rsi, buffer size in %rdx
pushq %rbx

# init to zeros
pushq %rdi
mov %rsi, %rdi
mov %rdx, %rcx
mov $'0', %rax
rep stosb
popq %rdi

mov %rdi, %rax
# isolate and store ascii of last hexdigit
doing:

# fence buffer
or %rdx, %rdx
jz done
dec %rdx

and $15, %rax
cmp $9, %rax
jle nothex
add $7, %rax
nothex:
add $'0', %rax
movb %al, (%rsi, %rdx, 1)

# divide by 16
shr $4, %rdi
mov %rdi, %rax
jz done
jmp doing
done:

popq %rbx
ret

And

working-storage section.
01 outbuf pic x(16).
01 lot pic 99.
01 samples.
05 n usage binary-double occurs 8 times.

procedure division.

move -7 to n(1)
move -1 to n(2)
move 0 to n(3)
move 255 to n(4)
move factorial(20) to n(5)
move h"01020304decafbad" to n(6)

perform varying lot from 1 by 1 until lot > 6
call "ashex" using
by value size 8 n(lot)
by reference outbuf
by value length(outbuf)
on exception
display "no ashex linkage" upon syserr
perform hard-exception
end-call
display n(lot) " :" trim(outbuf) ":"
end-perform

initialize outbuf
call "ashex" using
by value 32764 by reference outbuf by value 2
display "truncated :" trim(outbuf) ":"

Giving

-00000000000000000007 :FFFFFFFFFFFFFFF9:
-00000000000000000001 :FFFFFFFFFFFFFFFF:
+00000000000000000000 :0000000000000000:
+00000000000000000255 :00000000000000FF:
+02432902008176640000 :21C3677C82B40000:
+00072623863443946413 :01020304DECAFBAD:
truncated :FC:

Thanks for the honesty, Robert. Should be a better thing to put in the assembly integration entry now.

Rick Smith

unread,
Dec 1, 2015, 1:26:12 PM12/1/15
to
On Thursday, June 4, 2015 at 11:53:03 PM UTC-4, Pete Dashwood wrote:
> I was surprised when looking through the COBOL intrinsic functions to NOT
> find anything that will convert to Hexadecimal.
>
> (Yes, I can write something to do the necessary arithmetic, but, in this day
> and age I wouldn't expect to have to.)
>
> Does anybody have a routine that can take in a NUMBER (up to 10 digits) and
> produce a Hex string from it?

<snip>

> I can see several ways to do it, so I'll be interested if anyone here has a
> really cool COBOL way.

I'm not sure what you would consider cool! <g>

Since others are still posting about this topic, I thought I would
provide a little background, some code, and test results.

Based on
< http://documentation.microfocus.com/help/index.jsp?topic=%2Fcom.microfocus.eclipse.infocenter.studee60ux%2FGUID-C61923A3-E2C2-4AE9-A568-A7986156F3B3.html >

The PL/I HEX function has the form

HEX(x,y)

where x is a variable and y is an expression that must have a nonvarying
character type. Furthermore, y may be omitted.

To adapt that function to use a COBOL 85 CALL statement, it is necessary
to provide both a destination and the size of the source. Also, the
source must be arranged in the (so-called) big-endian form. Additionally,
the y parameter and its fixed insertion is inflexible and seems rather
silly to me.

So, I will stick with a simple conversion that allows for multiple types
with lengths up to 16 bytes, implemented as a standard conforming program.

-----
$set ans85 flag"ans85" flagas"s"
identification division.
program-id. cvthex.
data division.
working-storage section.
1 binary.
2 x pic 9(4).
2 y pic 9(4).
2 src-work pic 9(4).
2 first-digit pic 9(4).
2 second-digit pic 9(4).
1 hex-work pic x(2).
1 hex-table value "0123456789ABCDEF".
2 hex-entry pic x occurs 16.
linkage section.
1 src.
2 src-len pic 9(4) binary.
2 src-line.
3 src-char pic x occurs 0 to 16 depending src-len.
1 dest.
2 dest-len pic 9(4) binary.
2 dest-line.
3 dest-char pic x occurs 0 to 32 depending dest-len.
procedure division using src dest.
main section.
begin.
if src-len = 0 or > 16
continue
else
perform convert-source
end-if
exit program
.

convert-source section.
begin.
move 1 to y
perform varying x from 1 by 1 until x > src-len
compute src-work = function ord (src-char (x)) - 1
perform convert-char
string hex-work delimited size
into dest-line pointer y
end-string
end-perform
.

convert-char section.
begin.
divide src-work by 16 giving first-digit
remainder second-digit
move hex-entry (first-digit + 1) to hex-work (1:1)
move hex-entry (second-digit + 1) to hex-work (2:1)
.

end program cvthex.
-----

Output from test program (using report writer)
(reverse) means that FUNCTION REVERSE was used
(raw) means the native format was used for (so-called) little-endian

-----
pic x(16) value "The quick fox"
----------------------------------------
54686520717569636B20666F78202020

comp-5 pic s9(4) value +1234 (raw)
----------------------------------------
D204

comp-5 pic s9(4) value +1234 (reverse)
----------------------------------------
04D2

binary pic s9(4) value +1234
----------------------------------------
04D2

binary pic s9(9) value +1234
----------------------------------------
000004D2

binary pic s9(18) value +1234
----------------------------------------
00000000000004D2

comp-1 value +1234.0 (reverse)
----------------------------------------
449A4000

comp-2 value +1234.0 (reverse)
----------------------------------------
4093480000000000

packed-decimal pic s9(4) value +1234
----------------------------------------
01234C

pic s9(4) value +1234 leading separate
----------------------------------------
2B31323334

-----
0 new messages