DSN8HUFF

THIS SAMPLE IMPLEMENTS HUFFMAN ENCODING/DECODING AS AN EDITPROC .

         TITLE 'DSN8HUFF - SAMPLE DATA EDIT EXIT'
***********************************************************************
* MODULE NAME=  DSN8HUFF                                              *
*                                                                     *
* DESCRIPTIVE NAME= SAMPLE HUFFMAN COMPRESSION EDITPROC               *
*                                                                     *
*      COPYRIGHT = 5635-DB2 (C) COPYRIGHT IBM CORP 1982, 2006         *
*      SEE COPYRIGHT INSTRUCTIONS                                     *
*      LICENSED MATERIALS - PROPERTY OF IBM                           *
*                                                                     *
*      STATUS = VERSION 9                                             *
*                                                                     *
* FUNCTION=                                                           *
*     THIS SAMPLE IMPLEMENTS HUFFMAN ENCODING/DECODING AS AN EDITPROC *
*                                                                     *
*                                                                     *
* NOTES=                                                              *
*    DEPENDENCIES=  DB2 EDIT PROCEDURE INTERFACES                     *
*                                                                     *
*    RESTRICTIONS=  MAXIMUM ROW LENGTH OF TABLE MUST BE <= 4045 FOR   *
*                   4K PAGES AND <= 32704 FOR 32K PAGES.              *
*                                                                     *
*    REGISTER CONVENTIONS=                                            *
*         R0 =  EDITCODE PARM                                         *
*         R1 =  ON INVOCATION - POINTER TO PARMLIST                   *
*               DURING EXECUTION - POINTER TO DSNDEDIT                *
*         R2 =  EXECUTION WORK                                        *
*         R3 =  EXECUTION WORK                                        *
*         R4 =  EXECUTION WORK                                        *
*         R5 =  EXECUTION WORK                                        *
*         R6 =  EXECUTION WORK                                        *
*         R7 =  EXECUTION WORK                                        *
*         R8 =  EXECUTION WORK - BITSTR1                              *
*         R9 =  EXECUTION WORK - BITSTR2                              *
*         R10=  EXECUTION WORK - INPTR                                *
*         R11=  EXECUTION WORK - OPTR                                 *
*         R12=  EXECUTION WORK                                        *
*         R13=  POINTER TO REGISTER SAVE AREA                         *
*         R14=  AT ENTRY/EXIT - RETURN ADDRESS                        *
*               DURING EXECUTION - EXECUTION WORK                     *
*         R15=  EXECUTION WORK                                        *
*                                                                     *
*    PATCH LABEL= NONE                                                *
*                                                                     *
* MODULE TYPE=  DB2  EDITPROC                                         *
*                                                                     *
*    PROCESSOR=   ASSEMBLER H                                         *
*                                                                     *
*    MODULE SIZE= SEE ASSEMBLER LISTING                               *
*                                                                     *
*    ATTRIBUTES= RE-ENTRANT                                           *
*                                                                     *
* ENTRY POINT= DSN8HUFF                                               *
*                                                                     *
*    PURPOSE= SEE FUNCTION                                            *
*    LINKAGE = CALL DSN8HUFF(DSNDEXPL,DSNDEDIT)                       *
*                                                                     *
*    INPUT =                                                          *
*         DSNDEXPL  (not used)- EXIT ROUTINE PARAMETER LIST           *
*         DSNDEDIT            - INTERFACE BLOCK FOR EDIT EXITS        *
*                                                                     *
*    OUTPUT =                                                         *
*               SET EDITOLTH IN DSNDEDIT                              *
*               ENCODED/DECODED ROW OF DATA, EDITOPTR->DATA           *
*                                                                     *
*                                                                     *
* EXIT CONDITIONS=                                                    *
*                                                                     *
*  RETURN CODES= NONE                                                 *
*                                                                     *
*   REASON CODES GENERATED=  NONE                                     *
*                                                                     *
*   ABEND CODES GENERATED= NONE                                       *
*                                                                     *
*   ERROR-MESSAGES GENERATED= NONE                                    *
*                                                                     *
* MACROS=                                                             *
*   DSNDEDIT, DSNTIACN, DSN8TREE                                      *
***********************************************************************
* USAGE RECOMMENDATIONS:                                              *
***********************************************************************
* WHEN YOU USE THIS ROUTINE, BE AWARE OF THE FOLLOWING RESTRICTIONS   *
* AND CONCERNS:                                                       *
*                                                                     *
* o   The maximum  uncompressed record length  for 4K pages  is 4045  *
*     and  for 32K  pages is  32703. This  is one byte less than the  *
*     maximum allowed by DB2, due to the addition of  a flag byte to  *
*     the  front of  the record.  This added flag byte indicates      *
*     whether or not the actual row data has been compressed.         *
*                                                                     *
* o   The maximum encoded string length for any one byte is 24 bits   *
*     in this sample routine.  Another way to say this is that        *
*     the  maximum depth  of the  binary tree  used for  the Huffman  *
*     algorithm in this  routine is 24 levels.  Any customization of  *
*     this routine must stay within this 24 bit boundary due to code  *
*     constraints.                                                    *
*                                                                     *
* o   The static binary tree, which is a component of the Huffman     *
*     compression method used by this routine, will show better       *
*     results when used for tables containing a high percentage of    *
*     English text represented by single-byte EBCDIC, and worse       *
*     results for tables containing text from other languages or      *
*     non-text fields.                                                *
*                                                                     *
* o   CPU  overhead will  in general  increase with  the use  of any  *
*     edit routine, due to the increased record handling within DB2.  *
*     The CPU overhead of this sample is roughly  proportional to     *
*     the size of the compressed  record (better compression means    *
*     lower CPU cost).                                                *
*                                                                     *
*     Activity  requiring record  decoding, such  as an  SQL SELECT,  *
*     will accumulate  more overhead when this sample routine is used *
*     than will tasks such as INSERT.   This is due to the fact that  *
*     encoding  is a  simpler task  than decoding  with the  Huffman  *
*     compression algorithm.                                          *
*                                                                     *
* o   While CPU overhead will usually occur, it should be noted that  *
*     other benefits can  offset the impact of  this overhead. Since  *
*     the compressed record is logged, the frequency and quantity of  *
*     logging is potentially reduced.  Since each  log CI and  table  *
*     page can  potentially hold more data  rows (dependent on        *
*     the amount  of compression), each read I/O  effectively yields  *
*     more log records or rows.  The buffer pools for both log and    *
*     tablespaces can also contain more log records or table rows,    *
*     respectively.  As  with the  CPU  overhead, these benefits      *
*     increase as the compression ratio increases.                    *
*                                                                     *
* This sample  should be customized to each table with which it is    *
* used  to optimize  the compression  of the  table, reduce  the CPU  *
* overhead of accesses to the table, and maximize the I/O and buffer  *
* pool usage benefits that may be gained by compression.              *
*                                                                     *
* Customizing this routine:                                           *
*                                                                     *
* o   Familiarize yourself  with the Huffman  compression algorithm.  *
*     The  Huffman algorithm  was first  published in  the September  *
*     1952 Proceedings of  the IRE as "A Method  for Construction of  *
*     Minimum Redundancy Codes" and is described in various standard  *
*     references such as Knuth's  "Fundamental Algorithms" or         *
*     Horowitz and Sakhi's "Fundamentals of Computer Algorithms.      *
*                                                                     *
* o   Collect statistics on the byte frequencies of the code points   *
*     X'00' - X'FF' for the target table.  These statistics must be   *
*     collected on the stored DB2 format of the table rows.           *
*                                                                     *
* o   Prepare to  build the  Huffman tree by  associating each of the *
*     256 leaf nodes  with a code point in the range X'00' - X'FF'    *
*     and  the cardinality (weight) of  that code point, which was    *
*     determined during statistics collection.                        *
*                                                                     *
* o   Choose the two  nodes with the lowest cardinality and create a  *
*     parent node whose weight is the  sum of the two nodes' weights. *
*     In attaching  the two  children to  this newly  created parent  *
*     node, place the  child with the higher weight  (or lower depth  *
*     in the case of  ties) on the left and the node with the lower   *
*     weight (or higher depth in the case of ties) on the right.      *
*     Now combine the two nodes with the next lowest weights.  (One   *
*     of these may be the previously created parent node.)  Repeat    *
*     this process until you are left with a single root node in the  *
*     tree.   Note that nodes already combined into a parent node     *
*     are ineligible for combination with each other until all leaf   *
*     nodes have been used.                                           *
*                                                                     *
* o   You must  now shift the nodes to the right for each level of    *
*     the tree, starting at the root level and working down each      *
*     level of the tree.  More specifically, for each level of the    *
*     tree, you switch each right-hand parent node having more lower  *
*     levels with a left-hand node having fewer lower levels, while   *
*     leaving all the children attached to their respective parents.  *
*     Perform this process on a particular level until no more nodes  *
*     can be switched, and then progress to the next level of the     *
*     tree.  The effect of this is to unbalance the tree and skew it  *
*     to the right as much as possible.                               *
*                                                                     *
* o   Create the encoding strings for  each child by starting at the  *
*     root and  walking down the  tree to  the child. For  each left  *
*     path taken add a '0' bit to the right of the encode string and  *
*     for each right path  taken, add a '1' bit to  the right of the  *
*     encode string.                                                  *
*                                                                     *
* o   Create  the TABLE,  DFAST,  DFASTEND,  SKIPBITS, and  SKIPNODE  *
*     assembler DC statements for DSN8TREE in the formats documented  *
*     therein and save the file under a new name.                     *
*                                                                     *
* o   Update the DSN8HUFF  INCLUDE of DSN8TREE to  reference the new  *
*     member you created in the last step.                            *
*                                                                     *
* o   Compile and linkedit your new customized compression edit       *
*     routine.                                                        *
***********************************************************************
* PSEUDOCODE:                                                         *
***********************************************************************
* DSN8HUFF:                                                           *
*         SET ADDRESSABILITY PARAMETER LISTS                          *
*         IF EDITCODE = DECODE                                        *
*            GOTO DECODE                                              *
* ENCODE: SET FIRST OUTPUT BIT TO B'0'                                *
*         SET BARRIER TO ENSURE THAT ENCODED LENGTH < ORIGINAL LENGTH *
* ELOOP:  DO UNTIL END-OF-INPUT                                       *
*         GET NEXT INPUT CHAR                                         *
*         BITSTR2 = SUBSTR(TABLE(CHAR),2,3)                           *
*         IF SUBSTR(TABLE(CHAR),1,1) BITS WILL OVERFLOW BITSTR1 THEN  *
*            SHIFT BITSTR2 INTO BITSTR1 ENOUGH TO FILL BITSTR1        *
*            STORE BITSTR1 AS OUTPUT STRING                           *
*            IF OUTPUT LENGTH > BARRIER                               *
*               GO TO ENOHUFF                                         *
*            SHIFT BITSTR2 INTO BITSTR1 REMAINING BITS                *
*         ELSE                                                        *
*         SHIFT BITSTR2 INTO BITSTR1 BY SUBSTR(TABLE(CHAR),1,1) BITS  *
* END ELOOP                                                           *
* EEXIT:  DO                                                          *
*         PAD BITSTR1 WITH EENDSTR TO NEXT BYTE BOUNDARY              *
*         IF OUTPUT LENGTH > BARRIER THEN                             *
*           GO TO ENOHUFF                                             *
*         ELSE STORE BITSTR1 AS OUTPUT STRING                         *
*         RETURN                                                      *
* END EEXIT                                                           *
* ENOHUFF: DO                                                         *
*          ADD FIRST BYTE OF X'FF' TO OUTPUT STRING                   *
*          MOVE INPUT TO OUTPUT                                       *
*          RETURN                                                     *
* END ENOHUFF                                                         *
* END ENCODE                                                          *
***********************************************************************
* DECODE: DO                                                          *
*         IF FIRST BIT = B'1' THEN                                    *
*           GO TO DNOHUFF                                             *
*         ELSE DO                                                     *
*           GET FIRST BYTE AND STRIP OFF LEADING BIT                  *
*           GO TO DINIT1                                              *
* DLOAD1: DO                                                          *
*           LOAD BITSTR1||BITSTR2 WITH 8 BYTES FROM INPUT STRING      *
* DLFTOVR1: IF REMAINING INPUT STRING WAS LESS THAN 8 BYTES THEN,     *
*             ADJUST COUNTERS FOR END-OF-INPUT AND SETUP FOR EXIT     *
* END DLOAD1                                                          *
* DFASTLK:  IF LESS THAN 8 BITS TO DECODE ARE LEFT THEN               *
*              GO TO DINIT1                                           *
*           ELSE                                                      *
*             IF FIRST 8 BITS OF ENCODE STRING > DFASTEND             *
*                SET TREEWALK TO START FROM SKIPNODE                  *
*                TRUNICATE SKIPBITS FROM START OF ENCODE STRING       *
*                GO TO DINIT2                                         *
* DFASTFND:   ELSE DO                                                 *
*               OUTPUT CHAR = SUBSTR(DFAST(FIRST 8 ENCODE BITS),1,1)  *
*               SHIFT BITSRT1||BITSTR2 LEFT BY                        *
*                  SUBSTR(DFAST(FIRST 8 ENCODE BITS),2,1)             *
*               IF MORE ENCODE BITS ARE LEFT THEN                     *
*                  GO TO DFASTLK                                      *
*               ELSE                                                  *
*                  IF MORE INPUT AVAILABLE THEN                       *
*                     GO TO DLOAD1                                    *
*               ELSE                                                  *
*                  RETURN                                             *
* END DFASTFND                                                        *
* DLOAD2:   DO                                                        *
*             LOAD BITSTR1||BITSTR2 WITH 8 BYTES FROM INPUT STRING    *
* DLFTOVR2:   IF REMAINING INPUT STRING WAS LESS THAN 8 BYTES THEN,   *
*               ADJUST COUNTERS FOR END-OF-INPUT AND SETUP FOR EXIT   *
* END DLOAD2                                                          *
* DINIT1:   SET TREE TRAVERSAL AT ROOT NODE                           *
* DINIT2:   INITIALIZE LOOP REGISTER                                  *
* DLOOP:    DO                                                        *
*             IF FIRST ENCODE BIT = '0' THEN                          *
*                NEW TREE NODE = SUBSTR(CURRENT NODE,0,2)             *
*             ELSE                                                    *
*                NEW TREE NODE = SUBSTR(CURRENT NODE,2,2)             *
*             IF NEW NODE IS LEAF NODE THEN                           *
*                STORE SUBSTR(NODE,2,3) AS OUTPUT CHAR                *
*                SHIFT OUT USED ENCODE BIT                            *
*                IF MORE ENCODE BITS ARE LEFT THEN                    *
*                   GO TO DFASTLK                                     *
*                IF MORE INPUT IS AVAILABLE THEN                      *
*                   GO TO DLOAD1                                      *
*                ELSE                                                 *
*                   RETURN                                            *
*             ELSE                                                    *
*                SHIFT OUT USED ENCODE BIT                            *
*                IF MORE ENCODE BITS ARE LEFT THEN                    *
*                   GO TO DLOAD2                                      *
*                ELSE                                                 *
*                   RETURN                                            *
* END DLOOP                                                           *
* DNOHUFF: DO                                                         *
*            STRIP OFF FIRST BYTE OF INPUT STRING                     *
*            SAVE INPUT STRING AS OUTPUT STRING                       *
* END DNOHUFF                                                         *
* END DECODE                                                          *
***********************************************************************
*                                                                     *
* CHANGE ACTIVITY= NONE                                               *
          PRINT GEN
*                                                                     *
***********************************************************************
        EJECT
DSN8HUFF AMODE 31                      Address in 31 bits
DSN8HUFF RMODE ANY                     Reside anywhere
DSN8HUFF CSECT                         CONTROL SECTION NAME
         SAVE  (14,12),,*
         LR    R12,R15
         USING DSN8HUFF,R12
         USING PARMLIST,R1
         L     R1,PARMEDIT
         USING DSNDEDIT,R1
         LA    R0,EDITDEC
         C     R0,EDITCODE
         BE    DECODE
**********************************************************************
***                      E  N  C  O  D  E                          ***
**********************************************************************
BARRIER  EQU   2
CHAR     EQU   3
INEND1   EQU   4
INEND2   EQU   5
BITCNT1  EQU   6
BITCNT2  EQU   7
BITSTR1  EQU   8
BITSTR2  EQU   9
INPTR    EQU   10
OPTR     EQU   11
OCOUNT   EQU   14
TBLADDR  EQU   15
ENCODE   L     INPTR,EDITIPTR          GET INPUT PTR
         L     INEND2,EDITILTH         GET INPUT LENGTH
         AR    INEND2,INPTR            CALCULATE PTR TO END
         BCTR  INEND2,0                MOVE PTR TO LAST INPUT BYTE
         LA    INEND1,1(0,0)           SET INPUT INCREMENT TO 1
         L     OPTR,EDITOPTR           GET OUTPUT PTR
         L     BARRIER,EDITOPTR        SET OUTPUT BARRIER TO BE ...
         A     BARRIER,EDITILTH           ... NO LONGER THAN INPUT
         LA    OCOUNT,31(0,0)          LEAVE TOP BIT SET TO '0'
         LA    TBLADDR,TABLE           GET HUFF TABLE ADDR
         SLR   BITSTR1,BITSTR1         ZERO OUT BITSTR1
         SLR   BITCNT1,BITCNT1         ZERO OUT BITCNT1
         SLR   BITCNT2,BITCNT2         ZERO OUT BITCNT2
ELOOP    SLR   CHAR,CHAR               ZERO OUT CHAR REG
         IC    CHAR,0(INPTR)           GET CHAR
         SLA   CHAR,2(0)               CALCULATE OFFSET INTO TABLE
         IC    BITCNT2,0(CHAR,TBLADDR) GET ENCODE BIT COUNT
         L     BITSTR2,1(CHAR,TBLADDR) GET ENCODE BIT STRING
         BXH   OCOUNT,BITCNT1,ESHIFT2  IF REG WON'T OVERFLOW ....
*                                      GO TO ESHIFT2
ESHIFT1  SLDL  BITSTR1,0(OCOUNT)       SHIFT FOR REMAINDER OF OCOUNT
         ST    BITSTR1,0(OPTR)         STORE ENCODED BIT STRING
         LA    OPTR,4(OPTR)            MOVE OUTPUT PTR
         CR    OPTR,BARRIER            CHECK IF BEYOND BARRIER
         BH    ENOHUFF                 IF SO .... GO TO ENOHUFF
         SR    BITCNT2,OCOUNT          SET BITCNT2 TO BITS REMAINING
         LA    OCOUNT,32(0,0)          SET OCOUNT TO 32 BITS
ESHIFT2  SLDL  BITSTR1,0(BITCNT2)      SHIFT ENCODE BITS INTO BITSTR1
         SR    OCOUNT,BITCNT2          DECREMENT OCOUNT
         BXLE  INPTR,INEND1,ELOOP      IF MORE INPUT....GO TO ELOOP
EEXIT    L     BITSTR2,EENDSTR         GET END OF RECORD PADDING
         SLDL  BITSTR1,0(OCOUNT)       SHIFT PADDING INTO BITSTR1
         ST    BITSTR1,0(OPTR)         SAVE ENCODED STRING
         LA    OPTR,4(OPTR)            INCREMENT OUTPUT PTR
         SRA   OCOUNT,3(0)             CONVERT OVERFLOW BITS TO BYTES
         SR    OPTR,OCOUNT             SET PTR TO END
         CR    OPTR,BARRIER            CHECK IF BEYOND LENGTH BARRIER
         BH    ENOHUFF                 IF SO ... GO TO ENOHUFF
         S     OPTR,EDITOPTR           CALCULATE OUTPUT LENGTH
         ST    OPTR,EDITOLTH           STORE OUTPUT LENGTH
         B     EEND                    GO TO EEND
ENOHUFF  L     R4,EDITIPTR             GET INPUT PTR
         L     R5,EDITILTH             GET INPUT LENGTH
         L     R6,EDITOPTR             GET OUTPUT PTR
         L     R7,EDITILTH             GET OUTPUT LENGTH
         MVC   0(1,R6),HEXFF           PLACE 'FF' FLAG BYTE UP FRONT
         LA    R6,1(R6)                MOVE OUTPUT PTR
         MVCL  R6,R4                   MOVE INPUT TO OUTPUT
         L     R7,EDITILTH             GET LENGTH AGAIN AFTER MVCL
         LA    R7,1(R7)                ADD FLAG BYTE TO LENGTH
         ST    R7,EDITOLTH             STORE OUTPUT LENGTH
EEND     RETURN (14,12)                RETURN
         EJECT
**********************************************************************
***                      D  E  C  O  D  E                          ***
**********************************************************************
ICOUNT   EQU   2
BITCNT   EQU   3
INCRMNT1 EQU   4
COMPARE1 EQU   5
INCRMNT2 EQU   6
COMPARE2 EQU   7
TBLIDX   EQU   14
DECODE   L     INPTR,EDITIPTR
         CLC   0(1,INPTR),HEXFF        CHECK IF 1ST BYTE=X'FF'
         BE    DNOHUFF                 IF X'FF', NO HUFFMAN ENCODE
         L     ICOUNT,EDITILTH         GET INPUT STRING LENGTH
         L     OPTR,EDITOPTR           GET OUTPUT PTR
         LA    TBLADDR,TABLE           LOAD HUFF TABLE ADDR
DSKIP    EQU   *                       STRIP OFF LEADING BIT OF B'0'
         IC    BITSTR1,0(INPTR)        GET FIRST CHAR OF INPUT
         LA    INPTR,1(INPTR)          MOVE INPUT PTR
         BCTR  ICOUNT,0                DECREMENT INPUT COUNTER
         SLDL  BITSTR1,25(0)           SHIFT BYTE TO LOSE FIRST BIT
         LA    BITCNT,7(0,0)           SET BIT COUNT TO 7
         B     DINIT1                  GO TO DINIT1
DLOAD1   EQU   *                       GET 4 BYTES FOR DIRECT SCHEME
         LM    BITSTR1,BITSTR2,0(INPTR)
         LA    INPTR,8(INPTR)          MOVE INPUT PTR
         S     ICOUNT,DEC8             DECREMENT INPUT COUNTER
         BNP   DLFTOVR1                IF EXCEEDED...GO TO DLFTOVR1
         LA    BITCNT,64(0,0)          SET BIT COUNT TO 64
         B     DFASTLK                 GO TO DFASTLK
DLFTOVR1 EQU   *                       ADJUST FOR END OF INPUT
         LR    BITCNT,ICOUNT           SET COUNT TO NEGATIVE OVERFLOW
         A     BITCNT,DEC8             CALCULATE INPUT BYTES LEFTOVER
         SLL   BITCNT,3(0)             CALCULATE BITS FROM BYTES
         L     ICOUNT,MINUS1           SET INPUT COUNT FOR EXIT
DFASTLK  EQU   *                       DIRECT ADDR | TREE WALK
         C     BITCNT,DEC8             CHECK IF 8 BITS ARE LEFT
         BL    DINIT1                  IF < 8 BITS, GO TO TREE WALK
         LR    R4,BITSTR1              GET STRING
         SRL   R4,24(0)                RIGHT JUSTIFY FIRST 8 BITS
         C     R4,DFASTEND             CHECK IF DIRECT ADDR WILL WORK
         BNH   DFASTFND                YES .... GO TO DIRECT ADDR
         L     R6,SKIPBITS             NO  .... GET # TO STRIP OFF
         SLDL  BITSTR1,0(R6)           STRIP OFF BITS NOT NEEDED
         SR    BITCNT,R6               ADJUST BIT COUNT
         L     TBLIDX,SKIPNODE         SET TREE NODE FOR START
         B     DINIT2                  GO TO TREE WALK
DFASTFND EQU   *                       DIRECT ADDR SCHEME
         LA    R5,DFAST                GET DIRECT ADDR TABLE PTR
         SLL   R4,1(0)                 BITS * TABLE ENTRY LGTH
         AR    R4,R5                   R4 = TABLE ENTRY ADDR
         MVC   0(1,OPTR),0(R4)         MOVE CHAR TO OUTPUT
         LA    OPTR,1(OPTR)            INCREMENT OUTPUT PTR
         IC    R6,1(R4)                GET NUMBER OF BIT USED
         SLDL  BITSTR1,0(R6)           SHIFT OUT USED BITS
         SR    BITCNT,R6               ADJUST BIT COUNTER
         BNZ   DFASTLK                 IF NOT ZERO, TRY AGAIN
         LM    INCRMNT1,COMPARE2,DCHECKS LOAD BXH REGS
         BXH   ICOUNT,INCRMNT1,DLOAD1  IF MORE INPUT, GO TO DLOAD1
         B     DEXIT                   NO INPUT .... EXIT
DLOAD2   EQU   *                       LOAD 8 BYTES FOR TREE WALK
         LM    BITSTR1,BITSTR2,0(INPTR)
         LA    INPTR,8(INPTR)          MOVE INPUT PTR
         S     ICOUNT,DEC8             DECREMENT INPUT COUNT
         BNP   DLFTOVR2                IF EXCEEDED....GO TO DLFTOVR2
         LA    BITCNT,64(0,0)          SET BITCOUNT TO 64 BITS
         B     DLOOP                   GO TO DLOOP (TREE WALK)
DLFTOVR2 EQU   *                       ADJUST FOR END OF INPUT
         LR    BITCNT,ICOUNT           SET BITCNT TO NEGATIVE OVERFLOW
         A     BITCNT,DEC8             CALCULATE INPUT BYTES LEFTOVER
         SLL   BITCNT,3(0)             CALCULATE BITS FROM BYTES
         L     ICOUNT,MINUS1           SET INPUT COUNT FOR EXIT
         B     DLOOP                   GO TO DLOOP (TREE WALK)
DINIT1   LA    TBLIDX,2040(0,0)        SET INDEX FOR TREE ROOT
DINIT2   LM    INCRMNT1,COMPARE2,DCHECKS LOAD BXH REGS
DLOOP    EQU   *                       TREE WALK
         BXLE  BITSTR1,INCRMNT1,DBIT1  IF B'1', GO TO DBIT1
DBIT0    LH    TBLIDX,0(TBLADDR,TBLIDX) GET LEFT NODE
         B     DBITE
DBIT1    LH    TBLIDX,2(TBLADDR,TBLIDX) ELSE .... GET RIGHT NODE
DBITE    BXH   TBLIDX,INCRMNT2,DSHIFT   IF CHAR NOT FOUND, SHIFT
DCHAR    SRL   TBLIDX,2(0)             CHAR FOUND
         STC   TBLIDX,0(OPTR)          OUTPUT CHAR
         LA    OPTR,1(OPTR)            INCREMENT OUTPUT PTR
         SLDL  BITSTR1,1(0)            SHIFT OUT BIT
         BCT   BITCNT,DFASTLK          IF MORE, TRY FAST DECODE
         BXH   ICOUNT,INCRMNT1,DLOAD1  IF MORE, LOAD & FAST DECODE
         B     DEXIT                   ELSE .... EXIT
DSHIFT   SLDL  BITSTR1,1(0)            SHIFT FOR TREE WALK
         BCT   BITCNT,DLOOP            IF BITS ARE LEFT GO TO DLOOP
         BXH   ICOUNT,INCRMNT1,DLOAD2  IF MORE INPUT, GO TO DLOAD2
DEXIT    S     OPTR,EDITOPTR           DECODE EXIT
         ST    OPTR,EDITOLTH           SAVE OUTPUT STING LENGTH
         B     DEND                    GO TO DEND
DNOHUFF  EQU   *                       HUFFMAN NOT USED TO ENCODE
         L     R4,EDITIPTR             GET INPUT PTR
         LA    R4,1(R4)                SKIP FIRST 'FF' BYTE OF INPUT
         L     R5,EDITILTH             GET INPUT LENGTH
         BCTR  R5,R0                   SUBTRACT FOR 'FF' BYTE
         ST    R5,EDITOLTH             SAVE OUTPUT LENGTH
         L     R6,EDITOPTR             GET OUTPUT PTR
         LR    R7,R5                   GET OUTPUT LENGTH
         MVCL  R6,R4                   OVER STRING TO OUTPUT
DEND     RETURN (14,12)                RETURN
         EJECT
**********************************************************************
*                                                                    *
*   DECLARE THE CONSTANTS FOR THE PROGRAM                            *
*                                                                    *
**********************************************************************
DCHECKS  DC  F'0'
         DC  F'-1'
         DC  F'0'
         DC  F'1020'
MINUS1   DC  F'-1'
HEXFF    DC  X'FF'
DEC8     DC  F'8'
         DSNTIACN
         SPACE 5
         DS    0D
* INBED HUFFMAN TREE DECLARATION STATEMENTS
         COPY DSN8TREE
*
PATCH    DC    C'PATCH AREA - HUFF &SYSDATE &SYSTIME'
PSPACE   DC    25S(*)
**********************************************************************
*                                                                    *
*   DECLARE THE DUMMY SECTIONS                                       *
*                                                                    *
**********************************************************************
         SPACE 5
*
*                                      PARAMETER LIST PASSED TO EXIT
*
PARMLIST DSECT                         PARAMETER DSECT
PARMEXPL DS    A                       ADDRESS OF DSNDEXPL
PARMEDIT DS    A                       ADDRESS OF DSNDEDIT
         SPACE 5
*
*                                      PARAMETERS PASSED TO EDIT EXIT
*
         DSNDEDIT
         SPACE 5
*
         END   DSN8HUFF