HP3000-L Archives

December 2000, Week 1

HP3000-L@RAVEN.UTC.EDU

Options: Use Monospaced Font
Show Text Part by Default
Show All Mail Headers

Message: [<< First] [< Prev] [Next >] [Last >>]
Topic: [<< First] [< Prev] [Next >] [Last >>]
Author: [<< First] [< Prev] [Next >] [Last >>]

Print Reply
Subject:
From:
"Eric H. Sand" <[log in to unmask]>
Reply To:
Eric H. Sand
Date:
Mon, 4 Dec 2000 13:41:15 -0600
Content-Type:
text/plain
Parts/Attachments:
text/plain (150 lines)
Hi Ted,
    Your technique is almost exactly what I use in two small little Cobol
routines that I placed in an XL and forever have access to anytime I want to
create a "special" byte or discern the bit pattern in a byte.
    The source listing is below.

                          Eric Sand
                          [log in to unmask]

    1     $CONTROL NOWARN,DYNAMIC,POST85
    1.1    IDENTIFICATION DIVISION.
    1.2    PROGRAM-ID.                           DRAXL026.
    1.3   *AUTHOR.                               ERIC SAND.
    1.4   *INSTALLATION.                         DRA MONTEREY, CALIF.
    1.5   *DATE-WRITTEN.                         03-01-81.
    1.6    DATE-COMPILED.
    1.7   ***************************************************
    1.8   * PACK AND UNPACK BITS AND BYTE                   *
    1.9   ***************************************************
    2      ENVIRONMENT DIVISION.
    2.1    CONFIGURATION SECTION.
    2.2    SOURCE-COMPUTER.                      HP-3000.
    2.3    OBJECT-COMPUTER.                      HP-3000.
    2.4    SPECIAL-NAMES.
    2.5        CONDITION-CODE IS C-C.
    2.6    DATA DIVISION.
    2.7    WORKING-STORAGE SECTION.
    2.8    01  I                                 PIC S9(4) COMP VALUE +0.
    2.9    01  J                                 PIC S9(4) COMP VALUE +0.
    3      01  FORM-WORD.
    3.1        05  FORM-WORD-1                   PIC X
    3.2                  VALUE %0.
    3.3        05  FORM-BYTE9                    PIC 9.
    3.4        05  FORM-BYTE                     REDEFINES FORM-BYTE9
    3.5                                          PIC X.
    3.6    01  FORM-WORD9                        REDEFINES FORM-WORD
    3.7                                          PIC 9(4) COMP.
    3.8    LINKAGE SECTION.
    3.9    01  LS-BYTE                           PIC X.
    4      01  LS-BYTE9                          REDEFINES LS-BYTE
    4.1                                          PIC 9.
    4.2    01  LS-8BYTES.
    4.3        05  LS-8BYTE                      OCCURS 8 TIMES
    4.4                                          PIC X.
    4.5    PROCEDURE DIVISION USING LS-BYTE
    4.6                             LS-8BYTES.
    4.7   *
    4.8    BYTE-PACK.
    4.9    BP-1.
    5          ENTRY "BYTEPACK'026" USING LS-BYTE
    5.1                                   LS-8BYTES.
    5.2        MOVE LOW-VALUES TO FORM-WORD.
    5.3        MOVE 128 TO J.
    5.4        MOVE 1 TO I.
    5.5        PERFORM BP-2 8 TIMES.
    5.6        MOVE FORM-BYTE TO LS-BYTE.
    5.7        GOBACK.
    5.8    BP-2.
    5.9        IF LS-8BYTE(I) = "1"
    6              ADD J TO FORM-WORD9.
    6.1        DIVIDE 2 INTO J.
    6.2        ADD 1 TO I.
    6.3   *
    6.4    BYTE-UNPACK.
    6.5    BU-1.
    6.6        ENTRY "BYTEUNPACK'026" USING LS-BYTE
    6.7                                     LS-8BYTES.
    6.8        MOVE SPACES TO LS-8BYTES.
    6.9        MOVE LS-BYTE TO FORM-BYTE.
    7          PERFORM BU-2
    7.1            VARYING I FROM 8 BY -1 UNTIL I < 1.
    7.2        GOBACK.
    7.3    BU-2.
    7.4        DIVIDE 2 INTO FORM-WORD9
    7.5            GIVING FORM-WORD9 REMAINDER J.
    7.6        IF J > ZERO
    7.7            MOVE "1" TO LS-8BYTE(I)
    7.8        ELSE
    7.9            MOVE "0" TO LS-8BYTE(I).



> -----Original Message-----
> From: Ted Ashton [SMTP:[log in to unmask]]
> Sent: Friday, December 01, 2000 11:28 AM
> To:   [log in to unmask]
> Subject:      Re: [HP3000-L] Math Help
>
> Thus it was written in the epistle of Porter, Allen H,
> > OK, I'm trying to figure this out but I cannot remember how to do the
> math
> > behind it.
> >
> > If I have a series such as
> > 1
> > 2
> > 4
> > 8
> > 16
> > 32
> > 64
> > 128
> >
> > and I add any combination of these numbers together (4 + 16 = 20) the
> only
> > way I can come up with the number 20 is by adding 4 and 16.  Now how do
> I do
> > this in reverse?  If I know the sum is 81, how do I determine that the
> > numbers that make up this sum are 1 + 16 + 64?
> >
> > Thanks to anyone with the solution.
>
> As you've already heard the typical solution, here's another one for the
> amusement of it:
>
> Take your number, divide by 2 repeatedly until you reach 0, writing down
> the
> remainders.  Simultaneously, write down the successive powers of two:
>
>    81 / 2 = 40 r 1     1
>    40 / 2 = 20         2
>    20 / 2 = 10         4
>    10 / 2 =  5         8
>     5 / 2 =  2 r 1    16
>     2 / 2 =  1        32
>     1 / 2 =  0 r 1    64
>
> In the cases where there are remainders, multiply the remainders by the
> associated power of two and you have the desired 1 + 16 + 64.  This will
> also work for other powers:
>
>   81 / 5 = 16 r 1      1
>   16 / 5 =  3 r 1      5
>    3 / 5 =  0 r 3     25
>
> giving 81 = 1 + 5 + 75
>
> Oddly enough, there are times when going at it "backwards" like this is
> preferable.
>
> Ted
> --
> Ted Ashton ([log in to unmask]), Info Sys, Southern Adventist University
>           ==========================================================
> Men pass away, but their deeds abide.
>                                         -- Cauchy, Augustin-Louis (1789 -
> 1857)
>           ==========================================================
>          Deep thoughts to be found at http://www.southern.edu/~ashted

ATOM RSS1 RSS2