From: Arnold Trembley on
Bill,

I just looked a COBOL program in my shop that uses a table with 256
entries. The entries look something like this:

01 BYTE-TABLE-DATA.
05 FILLER PIC X(08) VALUE '00000001'.
05 FILLER PIC X(08) VALUE '00000010'.
05 FILLER PIC X(08) VALUE '00000011'.
05 FILLER PIC X(08) VALUE '00000100'.
And so forth, up to
05 FILLER PIC X(08) VALUE '11111111'.

01 BYTE-TABLE REDEFINES BYTE-TABLE-DATA.
05 DECODED-BYTE OCCURS 256 TIMES PIC X(08).

Then you simply take the byte you want to expand, coerce it into a PIC
S9(4) COMP field (or BINARY or COMP-5), add +1 to it, and use it as
an index to retrieve the 8 byte field that contains ones and zeros.

05 BYTE-SUB PIC S9(4) COMP VALUE ZERO.
05 FILLER REDEFINES BYTE-SUB.
10 FILLER PIC X(01).
10 BIT-MAP-BYTE PIC X(01).

MOVE ZERO TO BYTE-SUB
MOVE SOME-BYTE TO BIT-MAP-BYTE
ADD +1 TO BYTE-SUB
MOVE DECODED-BYTE (BYTE-SUB) TO ....

I haven't benchmarked this, but I suspect it ought to be faster than
division. It is relatively easy to understand and implement.

I'm not saying this is the best way, or the most efficient way. But
it is one way to do it entirely in COBOL.

With kindest regards,


William M. Klein wrote:
> Just a point of clarification (and explanation)
>
> Carl is aware of my OBJECTION to the way that CEE3INF returns its information
> (from other ways that we communicate).
>
> As far as the comp.lang.cobol thread goes, I really was interested in exactly
> HOW experienced COBOL programmers (both in and out of an IBM LE environment)
> would handle the requirement to "decode" the bits within a 1 byte (or larger)
> string of bits. I was also interested in how this would be solved in situations
> where one is interested in only the single value of a single bit vs the case
> where one might want to see the entire "layout" of the string of bits.
>
> I have been interested in responses that were related specially to the LE
> environment (z/OS *or* VSE). However, I have also been interested in responses
> that represent other (possibly more portable) solutions to the general problem.
>

--
http://arnold.trembley.home.att.net/

From: William M. Klein on
Actually, it might be interesting to put the "source" for such a problem in a
COPYBOOK and then do a COPY into a NESTED program with the code (where you
"pass" to it the byte you want to "decode" and pass back the decoded
PIC X(8) field.

If you did a COPY SUPPRESSING (IBM extension), you wouldn't even need to see all
the 256 FILLER definitions.

--
Bill Klein
wmklein <at> ix.netcom.com
"Arnold Trembley" <arnold.trembley(a)worldnet.att.net> wrote in message
news:uupJh.64692$as2.11483(a)bgtnsc05-news.ops.worldnet.att.net...
> Bill,
>
> I just looked a COBOL program in my shop that uses a table with 256 entries.
> The entries look something like this:
>
> 01 BYTE-TABLE-DATA.
> 05 FILLER PIC X(08) VALUE '00000001'.
> 05 FILLER PIC X(08) VALUE '00000010'.
> 05 FILLER PIC X(08) VALUE '00000011'.
> 05 FILLER PIC X(08) VALUE '00000100'.
> And so forth, up to
> 05 FILLER PIC X(08) VALUE '11111111'.
>
> 01 BYTE-TABLE REDEFINES BYTE-TABLE-DATA.
> 05 DECODED-BYTE OCCURS 256 TIMES PIC X(08).
>
> Then you simply take the byte you want to expand, coerce it into a PIC S9(4)
> COMP field (or BINARY or COMP-5), add +1 to it, and use it as an index to
> retrieve the 8 byte field that contains ones and zeros.
>
> 05 BYTE-SUB PIC S9(4) COMP VALUE ZERO.
> 05 FILLER REDEFINES BYTE-SUB.
> 10 FILLER PIC X(01).
> 10 BIT-MAP-BYTE PIC X(01).
>
> MOVE ZERO TO BYTE-SUB
> MOVE SOME-BYTE TO BIT-MAP-BYTE
> ADD +1 TO BYTE-SUB
> MOVE DECODED-BYTE (BYTE-SUB) TO ....
>
> I haven't benchmarked this, but I suspect it ought to be faster than division.
> It is relatively easy to understand and implement.
>
> I'm not saying this is the best way, or the most efficient way. But it is one
> way to do it entirely in COBOL.
>
> With kindest regards,
>
>
> William M. Klein wrote:
>> Just a point of clarification (and explanation)
>>
>> Carl is aware of my OBJECTION to the way that CEE3INF returns its
>> information (from other ways that we communicate).
>>
>> As far as the comp.lang.cobol thread goes, I really was interested in exactly
>> HOW experienced COBOL programmers (both in and out of an IBM LE environment)
>> would handle the requirement to "decode" the bits within a 1 byte (or larger)
>> string of bits. I was also interested in how this would be solved in
>> situations where one is interested in only the single value of a single bit
>> vs the case where one might want to see the entire "layout" of the string of
>> bits.
>>
>> I have been interested in responses that were related specially to the LE
>> environment (z/OS *or* VSE). However, I have also been interested in
>> responses that represent other (possibly more portable) solutions to the
>> general problem.
>>
>
> --
> http://arnold.trembley.home.att.net/
> 


From: Clark F Morris on
On Mon, 12 Mar 2007 02:36:10 -0500, "Rick Smith" <ricksmith(a)mfi.net>
wrote:

>
>"Pete Dashwood" <dashwood(a)removethis.enternet.co.nz> wrote in message
>news:55jmglF25132bU1(a)mid.individual.net...
>>
>> "Rick Smith" <ricksmith(a)mfi.net> wrote in message
>> news:12v6pek1atd1a64(a)corp.supernews.com...
>[snip]
>> > Extracting these bit fields directly seems a rather
>> > straight-forward process with intrinsic functions. The
>> > exponents below are 31 minus the low-order bit number
>> > of the field.
>> >
>> > -----
>> > compute c-bit = function mod
>> > (function integer (member-id / (2 ** 28)) 2)
>> > compute cobol-bit = function mod
>> > (function integer (member-id / (2 ** 26)) 2)
>> > compute amode = function mod
>> > (function integer (env-info / (2 ** 17)) 4)
>> > compute product-number = function integer
>> > (gpid / (2 ** 24))
>> > compute version = function mod
>> > (function integer (gpid / (2 ** 16)) 256)
>> > compute releasse = function mod
>> > (function integer (gpid / (2 ** 8)) 256)
>> > compute modification = function mod
>> > (gpid 256)
>> > -----
>> >
>> Excellent! Great stuff, Rick.
>
>Thank you for your kind words, here and elsewhere.
>
>This is little more than the implementation, in COBOL,
>of a few assembler instructions. The use of powers of 2
>translates to logical "shift" and "and". For IBM, the inline
>instruction sequence, for those with both functions (and
>this could be used for all), is:
> L
> SRL
> N
> STH
>
>Any who are truly uncomfortable with using COBOL
>to extract bit fields could write an equivalent assembler
>routine and call it.
>
>
When you take into account the inter module calling overhead on IBM z
series, especially with the DYNAM option the following conversion from
a bit switch to a byte-switch is probably quickest. I am assuming
that the field descriptions in the data division are obvious from the
code. I had a nice assembler routine that used UNPK - unpack, NC -
and character and TR to get the switch bytes but the savings in the
routine itself were eaten up by the overhead.

MOVE bit-switch TO binary-field-low-order-character.
MOVE ZERO TO switch-bytes
IF binary-field > 127
SUBTRACT 128 FROM binary-field
MOVE '1' TO switch-byte (1)
END-IF
IF binary-field > 63
SUBTRACT 64 FROM binary-field
MOVE '1' TO switch-byte (2)
END-IF
IF binary-field > 31
SUBTRACT 32 FROM binary-field
MOVE '1' TO switch-byte (3)
END-IF
IF binary-field > 15
SUBTRACT 16 FROM binary-field
MOVE '1' TO switch-byte (4)
END-IF
IF binary-field > 7
SUBTRACT 8 FROM binary-field
MOVE '1' TO switch-byte (5)
END-IF
IF binary-field > 3
SUBTRACT 4 FROM binary-field
MOVE '1' TO switch-byte (6)
END-IF
IF binary-field > 1
SUBTRACT 2 FROM binary-field
MOVE '1' TO switch-byte (7)
END-IF
IF binary-field = 1
MOVE '1' TO switch-byte (8)
END-IF