home *** CD-ROM | disk | FTP | other *** search
Text File | 1991-07-11 | 47.2 KB | 1,636 lines |
- Newsgroups: alt.sources
- Subject: zoo 2.1 source part 04/15
- Message-ID: <12770@bsu-cs.bsu.edu>
- From: dhesi@bsu-cs.bsu.edu (Rahul Dhesi)
- Date: 10 Jul 91 09:18:52 GMT
-
- Checksum: 1481112143 (verify with "brik -cv")
- Submitted-by: dhesi@bsu-cs.bsu.edu
- Archive-name: zoo210/part04
-
- ---- Cut Here and feed the following to sh ----
- #!/bin/sh
- # This is part 04 of zoo210
- # ============= lzd.asm ==============
- if test -f 'lzd.asm' -a X"$1" != X"-c"; then
- echo 'x - skipping lzd.asm (File already exists)'
- else
- echo 'x - extracting lzd.asm (Text)'
- sed 's/^X//' << 'SHAR_EOF' > 'lzd.asm' &&
- title Lempel-Ziv Decompressor
- ; $Source: /usr/home/dhesi/zoo/RCS/lzd.asm,v $
- ; $Id: lzd.asm,v 1.3 91/07/07 09:36:23 dhesi Exp $
- X
- ;Derived from Tom Pfau's public domain assembly code.
- ;The contents of this file are hereby released to the public domain.
- ; -- Rahul Dhesi 1988/08/24
- X
- UNBUF_IO equ 1 ;use unbuffered I/O
- X
- public _lzd,memflag,docrc
- X
- X include asmconst.ai
- X include macros.ai
- X
- ;Hash table entry
- hash_rec struc
- next dw ? ; prefix code
- char db ? ; suffix char
- hash_rec ends
- X
- extrn _addbfcrc:near ;External C function for CRC
- X
- ifdef UNBUF_IO
- extrn _read:near
- extrn _blockwrite:near
- else
- extrn _zooread:near
- extrn _zoowrite:near
- endif
- X
- ;Declare segments
- _text segment byte public 'code'
- _text ends
- X
- dgroup group _data
- X assume ds:dgroup,es:dgroup
- _data segment word public 'data'
- extrn _out_buf_adr:word ;address of C output buffer
- extrn _in_buf_adr:word ;address of C input buffer
- X
- memflag db 0 ;Memory allocated? flag
- save_bp dw ?
- save_sp dw ?
- X
- input_handle dw ?
- output_handle dw ?
- hash_seg dw ?
- cur_code dw ?
- old_code dw ?
- in_code dw ?
- free_code dw first_free
- X
- ;Note: for re-entrancy, following 3 must be re-initialized each time
- stack_count dw 0
- nbits dw 9
- max_code dw 512
- X
- fin_char db ?
- k db ?
- masks dw 1ffh,3ffh,7ffh,0fffh,1fffh
- X
- ;Note: for re-entrancy, following 2 must be re-initialized each time
- bit_offset dw 0
- output_offset dw 0
- _data ends
- X
- memory segment para public 'memory'
- hash label hash_rec
- memory ends
- X
- call_index macro
- X mov bp,bx ;bx = bx * 3 (3 byte entries)
- X shl bx,1 ;bp = bx
- X add bx,bp ;bx = bx * 2 + bp
- X endm
- X
- call_write_char macro
- X local wc$1
- X mov di,output_offset ;Get offset in buffer
- X cmp di,outbufsiz ;Full?
- X jb wc$1 ;no
- X call write_char_partial
- X sub di,di ;so we add zero in next statement
- wc$1: add di,[_out_buf_adr] ;di <- buffer address + di
- X stosb ;Store char
- X inc output_offset ;Increment number of chars in buffer
- X endm
- X
- add_code macro
- X mov bx,free_code ;Get new code
- X ;call index ;convert to address
- X call_index
- X push es ;point to hash table
- X mov es,hash_seg
- X mov al,k ;get suffix char
- X mov es:[bx].char,al ;save it
- X mov ax,old_code ;get prefix code
- X mov es:[bx].next,ax ;save it
- X pop es
- X inc free_code ;set next code
- X endm
- X
- ;Start coding
- _text segment
- X assume cs:_text,ds:dgroup,es:dgroup,ss:nothing
- X
- write_char_partial proc near
- X push cx
- X mov cx,di ;byte count
- X call write_block
- X pop cx
- X mov output_offset,0 ;Restore buffer pointer
- X ret
- write_char_partial endp
- X
- _lzd proc near
- X
- X push bp ;Standard C entry code
- X mov bp,sp
- X push di
- X push si
- X
- X push ds ;Save ds to be sure
- X mov [save_bp],bp ;And bp too!
- X mov bx,ds
- X mov es,bx
- X
- ;Get two parameters, both integers, that are input file handle and
- ;output file handle
- X mov ax,[bp+4]
- X mov [input_handle],ax
- X mov ax,[bp+6]
- X mov [output_handle],ax
- X
- X call decompress ;Compress file & get status in AX
- X
- X mov bp,[save_bp] ;Restore bp
- X pop ds
- X pop si ;Standard C return code
- X pop di
- X mov sp,bp
- X pop bp
- X ret
- _lzd endp
- X
- ;Note: Procedure decompress returns AX=0 for successful decompression and
- ; AX=1 for I/O error and AX=2 for malloc failure.
- decompress proc near
- X mov [save_sp],sp ;Save SP in case of error return
- X
- ;Initialize variables -- required for serial re-entrancy
- X mov [nbits],9
- X mov [max_code],512
- X mov [free_code],first_free
- X mov [stack_count],0
- X mov [bit_offset],0
- X mov [output_offset],0
- X
- X test memflag,0ffH ;Memory allocated?
- X jnz gotmem ;If allocated, continue
- X malloc <((maxmax * 3) / 16 + 20)> ;allocate it
- X jnc here1
- X jmp MALLOC_err
- here1:
- X mov hash_seg,ax ;Save segment address of mem block
- X mov memflag,0ffh ;Set flag to remind us later
- gotmem:
- X
- X mov ax,inbufsiz
- X push ax ;byte count
- X push _in_buf_adr ;buffer address
- X push input_handle ;zoofile
- ifdef UNBUF_IO
- X call _read
- else
- X call _zooread
- endif
- X add sp,6
- X
- X cmp ax,-1
- X jz IO_err ;I/O error
- here2:
- X
- l1: call read_code ;Get a code
- X cmp ax,eof ;End of file?
- X jne l2 ;no
- X cmp output_offset,0 ;Data in output buffer?
- X je OK_ret ;no
- X mov cx,[output_offset] ;byte count
- X call write_block ;write block of cx bytes
- OK_ret:
- X xor ax,ax ;Normal return -- decompressed
- X ret ;done
- IO_err:
- X mov ax,2 ;I/O error return
- X mov sp,[save_sp] ;Restore stack pointer
- X ret
- X
- MALLOC_err:
- X mov ax,1 ;Malloc error return
- X mov sp,[save_sp] ;Restore stack pointer
- X ret
- X
- l2: cmp ax,clear ;Clear code?
- X jne l7 ;no
- X call init_tab ;Initialize table
- X call read_code ;Read next code
- X mov cur_code,ax ;Initialize variables
- X mov old_code,ax
- X mov k,al
- X mov fin_char,al
- X mov al,k
- X ;call write_char ;Write character
- X call_write_char
- X jmp l1 ;Get next code
- l7: mov cur_code,ax ;Save new code
- X mov in_code,ax
- X mov es,hash_seg ;Point to hash table
- X cmp ax,free_code ;Code in table? (k<w>k<w>k)
- X jb l11 ;yes
- X mov ax,old_code ;get previous code
- X mov cur_code,ax ;make current
- X mov al,fin_char ;get old last char
- X push ax ;push it
- X inc stack_count
- X
- ;old code -- two memory references
- ;l11:
- ; cmp cur_code,255 ;Code or character?
- ; jbe l15 ;Char
- ; mov bx,cur_code ;Convert code to address
- ;new code -- 0 or 1 memory references
- X mov ax,cur_code
- l11:
- X ;All paths in must have ax containing cur_code
- X cmp ax,255
- X jbe l15
- X mov bx,ax
- ;end code
- X ;call index
- X call_index
- X mov al,es:2[bx] ;Get suffix char
- X push ax ;push it
- X inc stack_count
- X mov ax,es:[bx] ;Get prefix code
- X mov cur_code,ax ;Save it
- X jmp l11 ;Translate again
- l15:
- ;old code
- ; push ds ;Restore seg reg
- ; pop es
- ;new code
- X mov ax,ds ;faster than push/pop
- X mov es,ax
- ;end code
- X mov ax,cur_code ;Get code
- X mov fin_char,al ;Save as final, k
- X mov k,al
- X push ax ;Push it
- X
- ;old code
- ; inc stack_count
- ; mov cx,stack_count ;Pop stack
- ;new code -- slightly faster because INC of memory is slow
- X mov cx,stack_count
- X inc cx
- X mov stack_count,cx
- ;end code
- X jcxz l18 ;If anything there
- l17: pop ax
- X ;call write_char
- X call_write_char
- X loop l17
- X
- ;old code
- ;l18:
- ; mov stack_count,cx ;Clear count on stack
- ;new code -- because stack_count is already zero on earlier "jcxz l18"
- X mov stack_count,cx
- l18:
- ;end code
- X
- X ;call add_code ;Add new code to table
- X add_code
- X mov ax,in_code ;Save input code
- X mov old_code,ax
- X mov bx,free_code ;Hit table limit?
- X cmp bx,max_code
- X jb l23 ;Less means no
- X cmp nbits,maxbits ;Still within maxbits?
- X je l23 ;no (next code should be clear)
- X inc nbits ;Increase code size
- X shl max_code,1 ;Double max code
- l23: jmp l1 ;Get next code
- decompress endp
- X
- read_code proc near
- X
- ;old code
- ; mov ax,bit_offset ;Get bit offset
- ; add ax,nbits ;Adjust by code size
- ; xchg bit_offset,ax ;Swap
- ; mov dx,ax ;dx <- ax
- ;new code
- X mov ax,bit_offset
- X mov dx,ax ;dx <- bit_offset
- X add ax,nbits
- X mov bit_offset,ax
- X mov ax,dx
- ;end code
- X
- X shr ax,1
- X shr ax,1
- X shr ax,1 ;ax <- ax div 8
- X and dx,07 ;dx <- ax mod 8
- X cmp ax,inbufsiz-3 ;Approaching end of buffer?
- X jb rd0 ;no
- X push dx ;Save offset in byte
- X add dx,nbits ;Calculate new bit offset
- X mov bit_offset,dx
- X mov cx,inbufsiz
- X mov bp,ax ;save byte offset
- X sub cx,ax ;Calculate bytes left
- X add ax,_in_buf_adr
- X mov si,ax
- X mov di,_in_buf_adr
- rep movsb ;Move last chars down
- X
- X push bp ;byte count
- X push di ;buffer address
- X push input_handle ;zoofile
- ifdef UNBUF_IO
- X call _read
- else
- X call _zooread
- endif
- X add sp,6
- X
- X cmp ax,-1
- X jnz here4
- X jmp IO_err ;I/O error
- X
- here4:
- X xor ax,ax ;Clear ax
- X pop dx ;Restore offset in byte
- rd0:
- X add ax,_in_buf_adr
- X mov si,ax
- X lodsw ;Get word
- X mov bx,ax ;Save in AX
- X lodsb ;Next byte
- X mov cx,dx ;Offset in byte
- X jcxz rd2 ;If zero, skip shifts
- rd1: shr al,1 ;Put code in low (code size) bits of BX
- X rcr bx,1
- X loop rd1
- rd2: mov ax,bx ;put code in ax
- X mov bx,nbits ;mask off unwanted bits
- X sub bx,9
- X shl bx,1
- X and ax,masks[bx]
- X ret
- read_code endp
- X
- init_tab proc near
- X mov nbits,9 ;Initialize variables
- X mov max_code,512
- X mov free_code,first_free
- X ret
- init_tab endp
- X
- comment #
- index proc near
- X mov bp,bx ;bx = bx * 3 (3 byte entries)
- X shl bx,1 ;bp = bx
- X add bx,bp ;bx = bx * 2 + bp
- X ret
- index endp
- #end comment
- X
- docrc proc near
- ;On entry, ax=char count, dx=buffer address.
- ;Do crc on character count, in buffer.
- ;****** Update CRC value -- call external C program
- X ;External program is: addbfcrc(buffer, count)
- X ; char *buffer;
- X ; int count;
- X
- X push ax ;SAVE AX
- X push bx ;SAVE BX
- X push cx
- X push dx
- X
- X push ax ;param 2: char count
- X push dx ;param 1: buffer address
- X call _addbfcrc
- X add sp,4 ;Restore 2 params from stack
- X
- X pop dx
- X pop cx
- X pop bx ;RESTORE BX
- X pop ax ;RESTORE AX
- X ret
- docrc endp
- X
- write_block proc near
- ;Input: CX=byte count to write
- X push ax
- X push bx
- X push cx
- X push dx
- X push si ;may not be necessary to save si & di
- X push di
- X
- X push cx ;save count
- X
- X push cx ;count
- X push _out_buf_adr ;buffer
- X push output_handle ;zoofile
- ifdef UNBUF_IO
- X call _blockwrite
- else
- X call _zoowrite
- endif
- X add sp,6
- X
- X pop cx ;restore count
- X
- X ;ax = actual number of bytes written
- X cmp ax,cx ;all bytes written?
- X je written ;if yes, OK
- X jmp IO_err
- written:
- X mov dx,_out_buf_adr
- X call docrc ;do crc on ax bytes in buffer dx
- X mov output_offset,0 ;restore buffer ptr to zero
- X
- X pop di
- X pop si
- X pop dx
- X pop cx
- X pop bx
- X pop ax
- X ret
- write_block endp
- X
- _text ends
- X
- X end
- SHAR_EOF
- chmod 0644 lzd.asm ||
- echo 'restore of lzd.asm failed'
- Wc_c="`wc -c < 'lzd.asm'`"
- test 9144 -eq "$Wc_c" ||
- echo 'lzd.asm: original size 9144, current size' "$Wc_c"
- fi
- # ============= lzd.c ==============
- if test -f 'lzd.c' -a X"$1" != X"-c"; then
- echo 'x - skipping lzd.c (File already exists)'
- else
- echo 'x - extracting lzd.c (Text)'
- sed 's/^X//' << 'SHAR_EOF' > 'lzd.c' &&
- #ifndef LINT
- static char sccsid[]="@(#) lzd.c 2.6 88/01/30 20:39:18";
- #endif /* LINT */
- X
- /*********************************************************************/
- /* This file contains two versions of the lzd() decompression routine.
- The default is to use a fast version coded by Ray Gardner. If the
- symbol SLOW_LZD is defined, the older slower one is used. I have tested
- Ray's code and it seems to be portable and reliable. But if you
- suspect any problems you can define SLOW_LZD for your system in
- options.h and cause the older code to be used. --R.D. */
- /*********************************************************************/
- X
- #include "options.h"
- #include "zoo.h"
- #include "zooio.h"
- #include "various.h"
- #include "zoofns.h" /* function definitions */
- #include "zoomem.h"
- #include "debug.h"
- #include "assert.h"
- #include "lzconst.h"
- X
- #ifndef SLOW_LZD
- X
- /* Extensive modifications for speed by Ray Gardner
- ** Public domain by Raymond D. Gardner 9/26/88
- **
- ** I apologize for the comments being so dense in places as to impair
- ** readability, but some of the stuff isn't very obvious and needs
- ** some explaining. I am also sorry for the messy control structure
- ** (quite a few labels and goto's) and very long lzd() function, but
- ** I don't know how to do this any other way without loss of speed.
- **
- ** Ray Gardner
- ** 6374 S. Monaco Ct.
- ** Englewood, CO 80111
- */
- X
- #ifdef ANSI_HDRS
- # include <string.h> /* to get memcpy */
- #else
- X VOIDPTR memcpy();
- #endif
- X
- #define STACKSIZE 4000 /* allows for about 8Mb string in worst case? */
- /* stack grows backwards in this version, using pointers, not counters */
- static char *stack;
- static char *stack_pointer;
- static char *stack_lim;
- X
- void init_dtab PARMS((void));
- unsigned rd_dcode PARMS((void));
- /* void wr_dchar (char); */ /* now a macro */
- void ad_dcode PARMS((void));
- X
- #ifdef FILTER
- /* to send data back to zoofilt */
- extern unsigned int filt_lzd_word;
- #endif /* FILTER */
- X
- void xwr_dchar PARMS ((char));
- static int firstchar PARMS ((int));
- static void cbfill PARMS ((void));
- X
- /* wr_dchar() is a macro for speed */
- #define wr_dchar(c) { \
- X if (outbufp<outbuflim) \
- X *outbufp++=(c); \
- X else \
- X xwr_dchar(c); \
- X }
- X
- extern char *out_buf_adr; /* output buffer */
- extern char *in_buf_adr; /* input buffer */
- X /* use pointers (not counters) for buffer (for speed) */
- static char *outbufp; /* output buffer pointer */
- static char *outbuflim; /* output buffer limit */
- static char *outbufguard; /* output buffer "guard" */
- X
- char memflag = 0; /* memory allocated? flag */
- int *head; /* lzw prefix codes */
- char *tail; /* lzw suffix codes */
- static unsigned cur_code;
- static unsigned old_code;
- static unsigned in_code;
- X
- static unsigned free_code;
- static int nbits;
- static unsigned max_code;
- X
- /* We use a buffer of codes to avoid a function call to unpack each
- ** one as needed. We allocate an extra slot past the end of the buffer
- ** and put a CLEAR code in it, to serve as a sentinel. This way we can
- ** fold the test for code buffer runout into the test for a clear code
- ** and avoid having an extra test on each code processed. Also, we don't
- ** always use the code buffer. We can only use it when the input buffer
- ** is at a byte boundary, and when we know that the codesize won't change
- ** before we fill the code buffer, and when we know we won't run out of
- ** bytes in the input buffer before filling the code buffer. So we start
- ** with the code buffer pointer pointing to the sentinel, and we always
- ** have it pointing at the sentinel when we can't (for one reason or
- ** another) be getting our codes from the code buffer. We check for this
- ** condition whenever we get a CLEAR code, and if so, we get the code
- ** via the good old rd_dcode() routine.
- **
- ** One other problem with the code buffer approach is that we might get
- ** a CLEAR code in the middle of the buffer. This means that the next
- ** code is only 9 bits, but we have probably already unpacked a number of
- ** larger codes from the input into the buffer before we discover this.
- ** So we remember where (in the input buffer) the code buffer was filled
- ** from, and when a CLEAR code is encountered in the buffer (not the
- ** sentinel at the end) we back up the bit_offset pointer in the input
- ** buffer, and reset things to start unpacking the 9-bit codes from there.
- */
- X
- #define CODEBUF_SIZE 64 /* must be multiple of 8, experiment for best */
- static unsigned codebuf[CODEBUF_SIZE+1]; /* code buffer */
- static unsigned *codebufp; /* code buffer pointer */
- static unsigned *codebuflim; /* code buffer limit */
- X /* bit offset within the input buffer of where the code buffer began */
- static unsigned codebufoffset;
- X
- static unsigned masks[] = { 0, 0, 0, 0, 0, 0, 0, 0, 0,
- X 0x1ff, 0x3ff, 0x7ff, 0xfff, 0x1fff };
- static unsigned bit_offset; /* note this only allows max 8K input buffer!!*/
- X
- #ifdef UNBUF_IO
- #define BLOCKFILE int
- #define BLOCKREAD read
- #define BLOCKWRITE blockwrite
- int read PARMS ((int, VOIDPTR, unsigned));
- int write PARMS ((int, VOIDPTR, unsigned));
- int blockwrite PARMS ((int, VOIDPTR, unsigned));
- #else
- #define BLOCKFILE ZOOFILE
- #define BLOCKREAD zooread
- #define BLOCKWRITE zoowrite
- #endif /* UNBUF_IO */
- X
- static BLOCKFILE in_f, out_f;
- X
- /* rd_dcode() reads a code from the input (compressed) file and returns
- its value. */
- unsigned rd_dcode()
- {
- X register char *ptra, *ptrb; /* miscellaneous pointers */
- X unsigned word; /* first 16 bits in buffer */
- X unsigned byte_offset;
- X char nextch; /* next 8 bits in buffer */
- X unsigned ofs_inbyte; /* offset within byte */
- X
- X ofs_inbyte = bit_offset % 8;
- X byte_offset = bit_offset / 8;
- X bit_offset = bit_offset + nbits;
- X
- X assert(nbits >= 9 && nbits <= 13);
- X
- X if (byte_offset >= INBUFSIZ - 5) {
- X int space_left;
- X
- X assert(byte_offset >= INBUFSIZ - 5);
- X debug((printf ("lzd: byte_offset near end of buffer\n")))
- X
- X bit_offset = ofs_inbyte + nbits;
- X space_left = INBUFSIZ - byte_offset;
- X ptrb = byte_offset + in_buf_adr; /* point to char */
- X ptra = in_buf_adr;
- X /* we now move the remaining characters down buffer beginning */
- X debug((printf ("rd_dcode: space_left = %d\n", space_left)))
- X while (space_left > 0) {
- X *ptra++ = *ptrb++;
- X space_left--;
- X }
- X assert(ptra - in_buf_adr == ptrb - (in_buf_adr + byte_offset));
- X assert(space_left == 0);
- X if (BLOCKREAD (in_f, ptra, byte_offset) == -1)
- X prterror ('f', "I/O error in lzd:rd_dcode.\n");
- X byte_offset = 0;
- X }
- X ptra = byte_offset + in_buf_adr;
- X /* NOTE: "word = *((int *) ptra)" would not be independent of byte order. */
- X word = (unsigned char) *ptra; ptra++;
- X word = word | ( ((unsigned char) *ptra) << 8 ); ptra++;
- X
- X nextch = *ptra;
- X if (ofs_inbyte != 0) {
- X /* shift nextch right by ofs_inbyte bits */
- X /* and shift those bits right into word; */
- X word = (word >> ofs_inbyte) | (((unsigned)nextch) << (16-ofs_inbyte));
- X }
- X return (word & masks[nbits]);
- } /* rd_dcode() */
- X
- void init_dtab()
- {
- X nbits = 9;
- X max_code = 512;
- X free_code = FIRST_FREE;
- }
- X
- /* By making wr_dchar() a macro and calling this routine only on buffer
- ** full condition, we save a lot of function call overhead.
- ** We also use pointers instead of counters for efficiency (in the macro).
- */
- void xwr_dchar (ch)
- char ch;
- {
- X if (outbufp >= outbuflim) { /* if buffer full */
- X if (BLOCKWRITE (out_f, out_buf_adr, outbufp - out_buf_adr)
- X != outbufp - out_buf_adr)
- X prterror ('f', "Write error in lzd:wr_dchar.\n");
- X addbfcrc(out_buf_adr, outbufp - out_buf_adr); /* update CRC */
- X outbufp = out_buf_adr; /* restore empty buffer */
- X }
- X assert(outbufp - out_buf_adr < OUTBUFSIZ);
- X *outbufp++ = ch;
- } /* wr_dchar() */
- X
- X
- /* Code buffer fill routines
- **
- ** We use a separate function for each code size.
- ** Each function unpacks 8 codes from a packed buffer (f)
- ** to an unpacked buffer (t)
- ** A lot of code space, but really speeds up bit picking.
- */
- static unsigned char f[13]; /* must be unsigned for right shifts */
- static unsigned t[8];
- X
- static void cb9fill ()
- {
- X t[0] = (f[0] ) | ((f[1] & 1) << 8);
- X t[1] = (f[1] >> 1) | ((f[2] & 3) << 7);
- X t[2] = (f[2] >> 2) | ((f[3] & 7) << 6);
- X t[3] = (f[3] >> 3) | ((f[4] & 15) << 5);
- X t[4] = (f[4] >> 4) | ((f[5] & 31) << 4);
- X t[5] = (f[5] >> 5) | ((f[6] & 63) << 3);
- X t[6] = (f[6] >> 6) | ((f[7] & 127) << 2);
- X t[7] = (f[7] >> 7) | ((f[8] ) << 1);
- }
- X
- static void cb10fill ()
- {
- X t[0] = (f[0] ) | ((f[1] & 3) << 8);
- X t[1] = (f[1] >> 2) | ((f[2] & 15) << 6);
- X t[2] = (f[2] >> 4) | ((f[3] & 63) << 4);
- X t[3] = (f[3] >> 6) | ((f[4] ) << 2);
- X t[4] = (f[5] ) | ((f[6] & 3) << 8);
- X t[5] = (f[6] >> 2) | ((f[7] & 15) << 6);
- X t[6] = (f[7] >> 4) | ((f[8] & 63) << 4);
- X t[7] = (f[8] >> 6) | ((f[9] ) << 2);
- }
- X
- static void cb11fill ()
- {
- X t[0] = (f[0] ) | ((f[1] & 7) << 8);
- X t[1] = (f[1] >> 3) | ((f[2] & 63) << 5);
- X t[2] = (f[2] >> 6) | (f[3] << 2) | ((f[4] & 1) << 10);
- X t[3] = (f[4] >> 1) | ((f[5] & 15) << 7);
- X t[4] = (f[5] >> 4) | ((f[6] & 127) << 4);
- X t[5] = (f[6] >> 7) | (f[7] << 1) | ((f[8] & 3) << 9);
- X t[6] = (f[8] >> 2) | ((f[9] & 31) << 6);
- X t[7] = (f[9] >> 5) | ((f[10] ) << 3);
- }
- X
- static void cb12fill ()
- {
- X t[0] = (f[0] ) | ((f[1] & 15) << 8);
- X t[1] = (f[1] >> 4) | ((f[2] ) << 4);
- X t[2] = (f[3] ) | ((f[4] & 15) << 8);
- X t[3] = (f[4] >> 4) | ((f[5] ) << 4);
- X t[4] = (f[6] ) | ((f[7] & 15) << 8);
- X t[5] = (f[7] >> 4) | ((f[8] ) << 4);
- X t[6] = (f[9] ) | ((f[10] & 15) << 8);
- X t[7] = (f[10] >> 4) | ((f[11] ) << 4);
- }
- X
- static void cb13fill ()
- {
- X t[0] = (f[0] ) | ((f[1] & 31) << 8);
- X t[1] = (f[1] >> 5) | (f[2] << 3) | ((f[3] & 3) << 11);
- X t[2] = (f[3] >> 2) | ((f[4] & 127) << 6);
- X t[3] = (f[4] >> 7) | (f[5] << 1) | ((f[6] & 15) << 9);
- X t[4] = (f[6] >> 4) | (f[7] << 4) | ((f[8] & 1) << 12);
- X t[5] = (f[8] >> 1) | ((f[9] & 63) << 7);
- X t[6] = (f[9] >> 6) | (f[10] << 2) | ((f[11] & 7) << 10);
- X t[7] = (f[11] >> 3) | (f[12] << 5);
- }
- X
- /* vector of code buffer fill routines
- */
- void (*cbfillvec[]) PARMS ((void)) = { 0, 0, 0, 0, 0, 0, 0, 0, 0,
- X cb9fill, cb10fill, cb11fill, cb12fill, cb13fill };
- X
- /* cbfill -- main code buffer fill routine
- **
- ** moves data from inbuf[] to f[]
- ** then calls via vector to unpack to t[]
- ** then moves from t[] to codebuf[]
- ** A lot of moving around, but still faster than a lot of shifting and
- ** masking via variables (at least on a micro -- don't know about VAXen)
- ** Uses memcpy() for block move
- */
- X
- static void cbfill ()
- {
- X char *inbp;
- X inbp = in_buf_adr + bit_offset / 8;
- X codebufp = codebuf;
- X while ( codebufp < codebuflim ) {
- X memcpy((VOIDPTR) f, inbp, nbits);
- X (*cbfillvec[nbits])();
- X memcpy((VOIDPTR) codebufp, (VOIDPTR) t, 8 * sizeof(unsigned int));
- X inbp += nbits;
- X codebufp += 8;
- X }
- X bit_offset += nbits * CODEBUF_SIZE;
- }
- X
- /* The following is used in the KwKwK case because it's a pretty rare
- ** case, and doing it this way avoids the overhead of remembering the
- ** "finchar" (first input character) of every string
- */
- static int firstchar(code) /* find first character of a code */
- int code;
- {
- X while ( code > 255 )
- X code = head[code];
- X return code;
- }
- X
- int lzd(input_f, output_f)
- BLOCKFILE input_f, output_f; /* input & output files */
- {
- X in_f = input_f; /* make it avail to other fns */
- X out_f = output_f; /* ditto */
- X nbits = 9;
- X max_code = 512;
- X free_code = FIRST_FREE;
- X bit_offset = 0;
- X outbuflim = out_buf_adr + OUTBUFSIZ; /* setup out buffer limit */
- X outbufguard = outbuflim - 12; /* for checking avail. room in outbuf */
- X /* note must allow for as many characters as we special-case (8) */
- X /* used 12 for extra fudge factor (Rahul does it, so I can too) */
- X outbufp = out_buf_adr; /* setup output buffer ptr */
- X codebufp = codebuflim = &codebuf[CODEBUF_SIZE]; /* code buf ptr & limit */
- X *codebuflim = CLEAR; /* phony CLEAR sentinel past end of code buffer */
- X
- X if (BLOCKREAD (in_f, in_buf_adr, INBUFSIZ) == -1) /* fill input buffer */
- X return(IOERR);
- X if (memflag == 0) {
- X head = (int *) ealloc((MAXMAX+10) * sizeof(int));
- X tail = (char *) ealloc((MAXMAX+10) * sizeof(char));
- X stack = (char *) ealloc (sizeof (unsigned) * STACKSIZE + 20);
- X memflag++;
- X }
- X
- X stack_pointer = stack_lim = stack + STACKSIZE; /* setup stack ptr, limit*/
- X init_dtab(); /* initialize table */
- X
- loop:
- X cur_code = *codebufp++; /* get code from code buffer */
- X
- goteof: /* special case for CLEAR then Z_EOF, for 0-length files */
- X if (cur_code == Z_EOF) {
- X debug((printf ("lzd: Z_EOF\n")))
- X
- X if (outbufp != out_buf_adr) {
- X if (BLOCKWRITE (out_f, out_buf_adr, outbufp - out_buf_adr)
- X != outbufp - out_buf_adr)
- X prterror ('f', "Output error in lzd().\n");
- X addbfcrc(out_buf_adr, outbufp - out_buf_adr);
- X
- X }
- #ifdef FILTER
- X /* get next two bytes and put them where zoofilt can find them */
- X /* nbits known to be in range 9..13 */
- X bit_offset = ((bit_offset + 7) / 8) * 8; /* round up to next byte */
- X filt_lzd_word = rd_dcode();
- X filt_lzd_word |= (rd_dcode() << nbits);
- X filt_lzd_word &= 0xffff;
- #endif
- X return (0);
- X }
- X
- X assert(nbits >= 9 && nbits <= 13);
- X
- X if (cur_code == CLEAR) { /* was it sentinel or real CLEAR ? */
- X if ( codebufp > codebuflim ) { /* it was the sentinel */
- X if ( bit_offset % 8 == 0 && /* if we're on byte boundary and */
- X /* codesize won't change before codebuf is filled and */
- X /* codebuf can be filled without running out of inbuf */
- X free_code + CODEBUF_SIZE < max_code &&
- X bit_offset / 8 + (CODEBUF_SIZE * 13 / 8) < INBUFSIZ - 10 ) {
- X codebufoffset = bit_offset; /* remember where we were when */
- X cbfill(); /* we filled the code buffer */
- X codebufp = codebuf; /* setup code buffer pointer */
- X goto loop; /* now go get codes from code buffer */
- X } /* otherwise, use rd_dcode to get code */
- X codebufp = codebuflim; /* reset codebuf ptr to sentinel */
- X cur_code = rd_dcode(); /* get code via rd_dcode() */
- X if ( cur_code != CLEAR ) /* if it's not CLEAR */
- X goto got_code; /* then go handle it */
- X } else { /* else it's really a CLEAR code, not sentinel */
- X /* reset bit_offset to get next code in input buf after CLEAR code */
- X bit_offset = codebufoffset + (codebufp - codebuf) * nbits;
- X }
- X codebufp = codebuflim; /* set code buf ptr to sentinel */
- X debug((printf ("lzd: CLEAR\n")))
- X init_dtab(); /* init decompression table, etc. */
- X old_code = cur_code = rd_dcode(); /* get next code after CLEAR */
- X if (cur_code == Z_EOF) /* special case for 0-length files */
- X goto goteof;
- X wr_dchar(cur_code); /* write it out */
- X goto loop; /* and get next code */
- X }
- X
- got_code: /* we got a code and it's not a CLEAR */
- X
- X if (cur_code == Z_EOF) {
- X debug((printf ("lzd: Z_EOF\n")))
- X if (outbufp != out_buf_adr) {
- X if (BLOCKWRITE (out_f, out_buf_adr, outbufp - out_buf_adr)
- X != outbufp - out_buf_adr)
- X prterror ('f', "Output error in lzd().\n");
- X addbfcrc(out_buf_adr, outbufp - out_buf_adr);
- X }
- X return (0);
- X }
- X
- X in_code = cur_code; /* save original code */
- X if (cur_code >= free_code) { /* if code not in table (k<w>k<w>k) */
- X cur_code = old_code; /* previous code becomes current */
- X /* push first character of old code */
- X *--stack_pointer = firstchar(old_code);
- X goto unwind; /* and go "unwind" the current code */
- X } /* (use general unwind because the stack isn't empty now) */
- X
- /* Unwind a code. The basic idea is to use a sort of loop-unrolling
- ** approach to really speed up the processing by treating the codes
- ** which represent short strings (the vast majority of codes) as
- ** special cases. Avoid a lot of stack overflow checking safely.
- */
- X
- X if (cur_code > 255) { /* if cur_code is not atomic */
- X *--stack_pointer = tail[cur_code]; /* push its tail code */
- X cur_code = head[cur_code]; /* and replace with its head code */
- X } else { /* else 1-byte string */
- X if ( outbufp > outbufguard ) /* if outbuf near end, */
- X goto write_stack; /* write via general routine */
- X *outbufp++ = cur_code; /* we got space, put char out */
- X goto add_code; /* add code to table */
- X }
- X
- X if (cur_code > 255) { /* if cur_code is not atomic */
- X *--stack_pointer = tail[cur_code]; /* push its tail code */
- X cur_code = head[cur_code]; /* and replace with its head code */
- X } else { /* else 2-byte string */
- X if ( outbufp > outbufguard ) /* if outbuf near end, */
- X goto write_stack; /* write via general routine */
- X *outbufp++ = cur_code; /* we got space, put char out, and */
- X goto move_1_char; /* go move rest of stack to outbuf */
- X }
- X if (cur_code > 255) { /* if cur_code is not atomic */
- X *--stack_pointer = tail[cur_code]; /* push its tail code */
- X cur_code = head[cur_code]; /* and replace with its head code */
- X } else { /* else 3-byte string */
- X if ( outbufp > outbufguard ) /* if outbuf near end, */
- X goto write_stack; /* write via general routine */
- X *outbufp++ = cur_code; /* we got space, put char out, and */
- X goto move_2_char; /* go move rest of stack to outbuf */
- X }
- X
- /* we handle codes representing strings of 4 thru 8 bytes similarly */
- X
- X if (cur_code > 255) {
- X *--stack_pointer = tail[cur_code];
- X cur_code = head[cur_code];
- X } else { /* 4-byte string */
- X if ( outbufp > outbufguard )
- X goto write_stack;
- X *outbufp++ = cur_code;
- X goto move_3_char;
- X }
- X if (cur_code > 255) {
- X *--stack_pointer = tail[cur_code];
- X cur_code = head[cur_code];
- X } else { /* 5-byte string */
- X if ( outbufp > outbufguard )
- X goto write_stack;
- X *outbufp++ = cur_code;
- X goto move_4_char;
- X }
- X if (cur_code > 255) {
- X *--stack_pointer = tail[cur_code];
- X cur_code = head[cur_code];
- X } else { /* 6-byte string */
- X if ( outbufp > outbufguard )
- X goto write_stack;
- X *outbufp++ = cur_code;
- X goto move_5_char;
- X }
- X if (cur_code > 255) {
- X *--stack_pointer = tail[cur_code];
- X cur_code = head[cur_code];
- X } else { /* 7-byte string */
- X if ( outbufp > outbufguard )
- X goto write_stack;
- X *outbufp++ = cur_code;
- X goto move_6_char;
- X }
- X if (cur_code > 255) {
- X *--stack_pointer = tail[cur_code];
- X cur_code = head[cur_code];
- X } else { /* 8-byte string */
- X if ( outbufp > outbufguard )
- X goto write_stack;
- X *outbufp++ = cur_code;
- X goto move_7_char;
- X }
- X
- /* Here for KwKwK case and strings longer than 8 bytes */
- /* Note we have to check stack here, but not elsewhere */
- X
- unwind:
- X while (cur_code > 255) { /* if code, not character */
- X *--stack_pointer = tail[cur_code]; /* push suffix char */
- X if (stack_pointer < stack+12)
- X prterror ('f', "Stack overflow in lzd().\n");
- X cur_code = head[cur_code]; /* head of code is new code */
- X }
- X
- /* General routine to write stack with check for output buffer full */
- X
- write_stack:
- X assert(nbits >= 9 && nbits <= 13);
- X wr_dchar(cur_code); /* write this code, don't need to stack it first */
- X while ( stack_pointer < stack_lim ) {
- X wr_dchar(*stack_pointer++);
- X }
- X goto add_code; /* now go add code to table */
- X
- /* Here to move strings from stack to output buffer */
- /* only if we know we have enough room in output buffer */
- /* because (outbufp <= outbufguard) */
- X
- move_7_char:
- X *outbufp++ = *stack_pointer++;
- move_6_char:
- X *outbufp++ = *stack_pointer++;
- move_5_char:
- X *outbufp++ = *stack_pointer++;
- move_4_char:
- X *outbufp++ = *stack_pointer++;
- move_3_char:
- X *outbufp++ = *stack_pointer++;
- move_2_char:
- X *outbufp++ = *stack_pointer++;
- move_1_char:
- X *outbufp++ = *stack_pointer++;
- X
- assert(stack_pointer == stack_lim); /* I haven't tested this! rdg */
- X
- /* add_code is now inline to avoid overhead of function call on */
- /* each code processed */
- X
- add_code:
- X assert(nbits >= 9 && nbits <= 13);
- X assert(free_code <= MAXMAX+1);
- X tail[free_code] = cur_code; /* save suffix char */
- X head[free_code] = old_code; /* save prefix code */
- X free_code++;
- X assert(nbits >= 9 && nbits <= 13);
- X if (free_code >= max_code) {
- X if (nbits < MAXBITS) {
- X debug((printf("lzd: nbits was %d\n", nbits)))
- X nbits++;
- X assert(nbits >= 9 && nbits <= 13);
- X debug((printf("lzd: nbits now %d\n", nbits)))
- X max_code = max_code << 1; /* double max_code */
- X debug((printf("lzd: max_code now %d\n", max_code)))
- X }
- X }
- X old_code = in_code;
- X
- X assert(nbits >= 9 && nbits <= 13);
- X
- X goto loop;
- } /* lzd() */
- X
- #else /* SLOW_LZD defined, so use following instead */
- X
- /*********************************************************************/
- /* Original slower lzd(). */
- /*********************************************************************/
- X
- /*
- Lempel-Ziv decompression. Mostly based on Tom Pfau's assembly language
- code. The contents of this file are hereby released to the public domain.
- X -- Rahul Dhesi 1986/11/14
- */
- X
- #define STACKSIZE 4000
- X
- struct tabentry {
- X unsigned next;
- X char z_ch;
- };
- X
- void init_dtab PARMS((void));
- unsigned rd_dcode PARMS((void));
- void wr_dchar PARMS((int));
- void ad_dcode PARMS((void));
- X
- #ifdef FILTER
- /* to send data back to zoofilt */
- extern unsigned int filt_lzd_word;
- #endif /* FILTER */
- X
- X
- static unsigned stack_pointer = 0;
- static unsigned *stack;
- X
- #define push(x) { \
- X stack[stack_pointer++] = (x); \
- X if (stack_pointer >= STACKSIZE) \
- X prterror ('f', "Stack overflow in lzd().\n");\
- X }
- #define pop() (stack[--stack_pointer])
- X
- extern char *out_buf_adr; /* output buffer */
- extern char *in_buf_adr; /* input buffer */
- X
- char memflag = 0; /* memory allocated? flag */
- extern struct tabentry *table; /* hash table from lzc.c */
- static unsigned cur_code;
- static unsigned old_code;
- static unsigned in_code;
- X
- static unsigned free_code;
- static int nbits;
- static unsigned max_code;
- X
- static char fin_char;
- static char k;
- static unsigned masks[] = { 0, 0, 0, 0, 0, 0, 0, 0, 0,
- X 0x1ff, 0x3ff, 0x7ff, 0xfff, 0x1fff };
- static unsigned bit_offset;
- static unsigned output_offset;
- X
- #ifdef UNBUF_IO
- #define BLOCKFILE int
- #define BLOCKREAD read
- #define BLOCKWRITE blockwrite
- int read PARMS ((int, VOIDPTR, unsigned));
- int write PARMS ((int, VOIDPTR, unsigned));
- #else
- #define BLOCKFILE ZOOFILE
- #define BLOCKREAD zooread
- #define BLOCKWRITE zoowrite
- #endif /* UNBUF_IO */
- X
- static BLOCKFILE in_f, out_f;
- X
- int lzd(input_f, output_f)
- BLOCKFILE input_f, output_f; /* input & output file handles */
- {
- X in_f = input_f; /* make it avail to other fns */
- X out_f = output_f; /* ditto */
- X nbits = 9;
- X max_code = 512;
- X free_code = FIRST_FREE;
- X stack_pointer = 0;
- X bit_offset = 0;
- X output_offset = 0;
- X
- X if (BLOCKREAD (in_f, in_buf_adr, INBUFSIZ) == -1)
- X return(IOERR);
- X if (memflag == 0) {
- X table = (struct tabentry *) ealloc((MAXMAX+10) * sizeof(struct tabentry));
- X stack = (unsigned *) ealloc (sizeof (unsigned) * STACKSIZE + 20);
- X memflag++;
- X }
- X
- X init_dtab(); /* initialize table */
- X
- loop:
- X cur_code = rd_dcode();
- goteof: /* special case for CLEAR then Z_EOF, for 0-length files */
- X if (cur_code == Z_EOF) {
- X debug((printf ("lzd: Z_EOF\n")))
- X if (output_offset != 0) {
- X if (BLOCKWRITE (out_f, out_buf_adr, output_offset) != output_offset)
- X prterror ('f', "Output error in lzd().\n");
- X addbfcrc(out_buf_adr, output_offset);
- X }
- #ifdef FILTER
- X /* get next two bytes and put them where zoofilt can find them */
- X /* nbits known to be in range 9..13 */
- X bit_offset = ((bit_offset + 7) / 8) * 8; /* round up to next byte */
- X filt_lzd_word = rd_dcode();
- X filt_lzd_word |= (rd_dcode() << nbits);
- X filt_lzd_word &= 0xffff;
- #endif
- X return (0);
- X }
- X
- X assert(nbits >= 9 && nbits <= 13);
- X
- X if (cur_code == CLEAR) {
- X debug((printf ("lzd: CLEAR\n")))
- X init_dtab();
- X fin_char = k = old_code = cur_code = rd_dcode();
- X if (cur_code == Z_EOF) /* special case for 0-length files */
- X goto goteof;
- X wr_dchar(k);
- X goto loop;
- X }
- X
- X in_code = cur_code;
- X if (cur_code >= free_code) { /* if code not in table (k<w>k<w>k) */
- X cur_code = old_code; /* previous code becomes current */
- X push(fin_char);
- X }
- X
- X while (cur_code > 255) { /* if code, not character */
- X push(table[cur_code].z_ch); /* push suffix char */
- X cur_code = table[cur_code].next; /* <w> := <w>.code */
- X }
- X
- X assert(nbits >= 9 && nbits <= 13);
- X
- X k = fin_char = cur_code;
- X push(k);
- X while (stack_pointer != 0) {
- X wr_dchar(pop());
- X }
- X assert(nbits >= 9 && nbits <= 13);
- X ad_dcode();
- X old_code = in_code;
- X
- X assert(nbits >= 9 && nbits <= 13);
- X
- X goto loop;
- } /* lzd() */
- X
- /* rd_dcode() reads a code from the input (compressed) file and returns
- its value. */
- unsigned rd_dcode()
- {
- X register char *ptra, *ptrb; /* miscellaneous pointers */
- X unsigned word; /* first 16 bits in buffer */
- X unsigned byte_offset;
- X char nextch; /* next 8 bits in buffer */
- X unsigned ofs_inbyte; /* offset within byte */
- X
- X ofs_inbyte = bit_offset % 8;
- X byte_offset = bit_offset / 8;
- X bit_offset = bit_offset + nbits;
- X
- X assert(nbits >= 9 && nbits <= 13);
- X
- X if (byte_offset >= INBUFSIZ - 5) {
- X int space_left;
- X
- #ifdef CHECK_BREAK
- X check_break();
- #endif
- X
- X assert(byte_offset >= INBUFSIZ - 5);
- X debug((printf ("lzd: byte_offset near end of buffer\n")))
- X
- X bit_offset = ofs_inbyte + nbits;
- X space_left = INBUFSIZ - byte_offset;
- X ptrb = byte_offset + in_buf_adr; /* point to char */
- X ptra = in_buf_adr;
- X /* we now move the remaining characters down buffer beginning */
- X debug((printf ("rd_dcode: space_left = %d\n", space_left)))
- X while (space_left > 0) {
- X *ptra++ = *ptrb++;
- X space_left--;
- X }
- X assert(ptra - in_buf_adr == ptrb - (in_buf_adr + byte_offset));
- X assert(space_left == 0);
- X if (BLOCKREAD (in_f, ptra, byte_offset) == -1)
- X prterror ('f', "I/O error in lzd:rd_dcode.\n");
- X byte_offset = 0;
- X }
- X ptra = byte_offset + in_buf_adr;
- X /* NOTE: "word = *((int *) ptra)" would not be independent of byte order. */
- X word = (unsigned char) *ptra; ptra++;
- X word = word | ( ((unsigned char) *ptra) << 8 ); ptra++;
- X
- X nextch = *ptra;
- X if (ofs_inbyte != 0) {
- X /* shift nextch right by ofs_inbyte bits */
- X /* and shift those bits right into word; */
- X word = (word >> ofs_inbyte) | (((unsigned)nextch) << (16-ofs_inbyte));
- X }
- X return (word & masks[nbits]);
- } /* rd_dcode() */
- X
- void init_dtab()
- {
- X nbits = 9;
- X max_code = 512;
- X free_code = FIRST_FREE;
- }
- X
- void wr_dchar (ch)
- int ch;
- {
- X if (output_offset >= OUTBUFSIZ) { /* if buffer full */
- #ifdef CHECK_BREAK
- X check_break();
- #endif
- X if (BLOCKWRITE (out_f, out_buf_adr, output_offset) != output_offset)
- X prterror ('f', "Write error in lzd:wr_dchar.\n");
- X addbfcrc(out_buf_adr, output_offset); /* update CRC */
- X output_offset = 0; /* restore empty buffer */
- X }
- X assert(output_offset < OUTBUFSIZ);
- X out_buf_adr[output_offset++] = ch; /* store character */
- } /* wr_dchar() */
- X
- /* adds a code to table */
- void ad_dcode()
- {
- X assert(nbits >= 9 && nbits <= 13);
- X assert(free_code <= MAXMAX+1);
- X table[free_code].z_ch = k; /* save suffix char */
- X table[free_code].next = old_code; /* save prefix code */
- X free_code++;
- X assert(nbits >= 9 && nbits <= 13);
- X if (free_code >= max_code) {
- X if (nbits < MAXBITS) {
- X debug((printf("lzd: nbits was %d\n", nbits)))
- X nbits++;
- X assert(nbits >= 9 && nbits <= 13);
- X debug((printf("lzd: nbits now %d\n", nbits)))
- X max_code = max_code << 1; /* double max_code */
- X debug((printf("lzd: max_code now %d\n", max_code)))
- X }
- X }
- }
- #endif /* ! SLOW_LZD */
- SHAR_EOF
- chmod 0644 lzd.c ||
- echo 'restore of lzd.c failed'
- Wc_c="`wc -c < 'lzd.c'`"
- test 29821 -eq "$Wc_c" ||
- echo 'lzd.c: original size 29821, current size' "$Wc_c"
- fi
- # ============= lzh.c ==============
- if test -f 'lzh.c' -a X"$1" != X"-c"; then
- echo 'x - skipping lzh.c (File already exists)'
- else
- echo 'x - extracting lzh.c (Text)'
- sed 's/^X//' << 'SHAR_EOF' > 'lzh.c' &&
- /* $Id: lzh.c,v 1.15 91/07/06 19:18:51 dhesi Exp $ */
- /*
- lzh compression and uncompression interface module
- */
- X
- #include "options.h"
- #include "zoo.h"
- #include "ar.h"
- #include "errors.i"
- X
- FILE *arcfile;
- X
- extern void prterror();
- X
- extern char *out_buf_adr; /* address of buffer */
- X
- int lzh_encode(infile, outfile)
- FILE *infile;
- FILE *outfile;
- {
- X extern void encode();
- X encode(infile, outfile);
- X return 0;
- }
- X
- /*
- lzh_decode decodes its input and sends it to output.
- Should return error status or byte count, but currently
- returns 0.
- */
- X
- #undef COUNT_BYTES /* define for debugging */
- X
- int lzh_decode(infile, outfile)
- FILE *infile;
- FILE *outfile;
- {
- X int n;
- X extern int decoded;
- #ifdef COUNT_BYTES
- X int bytes_decoded = 0; /*debug*/ /* count bytes after decoding */
- #endif
- X
- X arcfile = infile; /* stream to be decoded */
- X
- X decode_start();
- X while (!decoded) {
- X n = decode((uint) DICSIZ, out_buf_adr); /* n = count of chars decoded */
- #ifdef COUNT_BYTES
- X bytes_decoded += n; /*debug*/
- #endif
- #ifdef CHECK_BREAK
- X check_break();
- #endif
- X fwrite_crc(out_buf_adr, n, outfile);
- #ifdef SHOW_DOTS
- X (void) putc('.', stderr);
- X (void) fflush(stderr);
- #endif
- X }
- #ifdef COUNT_BYTES
- X (void) fprintf(stderr, "bytes decoded = %d\n", bytes_decoded);
- #endif
- X return 0;
- }
- SHAR_EOF
- chmod 0644 lzh.c ||
- echo 'restore of lzh.c failed'
- Wc_c="`wc -c < 'lzh.c'`"
- test 1255 -eq "$Wc_c" ||
- echo 'lzh.c: original size 1255, current size' "$Wc_c"
- fi
- # ============= lzh.h ==============
- if test -f 'lzh.h' -a X"$1" != X"-c"; then
- echo 'x - skipping lzh.h (File already exists)'
- else
- echo 'x - extracting lzh.h (Text)'
- sed 's/^X//' << 'SHAR_EOF' > 'lzh.h' &&
- /*$Source: /usr/home/dhesi/zoo/RCS/lzh.h,v $*/
- /*$Id: lzh.h,v 1.3 91/07/09 01:39:23 dhesi Exp $*/
- X
- /*
- Adapted from "ar" archiver written by Haruhiko Okumura.
- */
- X
- /* Define some things if they aren't defined in header files */
- #ifndef CHAR_BIT
- # define CHAR_BIT 8
- #endif
- X
- #ifndef UCHAR_MAX
- # define UCHAR_MAX 255
- #endif
- X
- /* io.c */
- X
- extern FILE *arcfile, *lzh_infile, *lzh_infile;
- extern t_uint16 bitbuf;
- #define BITBUFSIZ (CHAR_BIT * sizeof bitbuf)
- X
- /* encode.c and decode.c */
- X
- #define MATCHBIT 8 /* bits for MAXMATCH - THRESHOLD */
- #define MAXMATCH 256 /* formerly F (not more than UCHAR_MAX + 1) */
- #define THRESHOLD 3 /* choose optimal value */
- #define PERC_FLAG ((unsigned) 0x8000)
- X
- /* huf.c */
- X
- #define NC (UCHAR_MAX + MAXMATCH + 2 - THRESHOLD)
- X /* alphabet = {0, 1, 2, ..., NC - 1} */
- #define CBIT 9 /* $\lfloor \log_2 NC \rfloor + 1$ */
- #define CODE_BIT 16 /* codeword length */
- X
- extern ushort left[], right[];
- SHAR_EOF
- chmod 0644 lzh.h ||
- echo 'restore of lzh.h failed'
- Wc_c="`wc -c < 'lzh.h'`"
- test 934 -eq "$Wc_c" ||
- echo 'lzh.h: original size 934, current size' "$Wc_c"
- fi
- # ============= machine.c ==============
- if test -f 'machine.c' -a X"$1" != X"-c"; then
- echo 'x - skipping machine.c (File already exists)'
- else
- echo 'x - extracting machine.c (Text)'
- sed 's/^X//' << 'SHAR_EOF' > 'machine.c' &&
- #ifndef LINT
- /* @(#) machine.c 2.3 88/01/02 01:21:44 */
- static char sccsid[]="@(#) machine.c 2.3 88/01/02 01:21:44";
- #endif /* LINT */
- X
- /*
- The contents of this file are hereby released to the public domain.
- X
- X -- Rahul Dhesi 1986/12/31
- */
- X
- /* This file is in two parts. */
- X
- #include "options.h"
- #include "zooio.h"
- #include "zoo.h"
- #include "zoofns.h"
- #include "various.h"
- X
- /***********************************************************************/
- /* PART 1. FOR UNBUFFERED I/O ONLY. DO NOT CHANGE. */
- /***********************************************************************/
- X
- #ifdef UNBUF_IO
- int write PARMS ((int, VOIDPTR, unsigned));
- X
- /*
- blockwrite() is like write() except that it ignores all
- output to file descriptor -2, which stands for the null file.
- */
- int blockwrite (fd, buf, count)
- int fd;
- #ifdef VOIDPTR
- VOIDPTR buf;
- #else
- char *buf;
- #endif /* VOIDPTR */
- unsigned count;
- {
- X if (fd == -2)
- X return (count);
- X else
- X return (write (fd, buf, count));
- }
- #endif
- X
- /***********************************************************************/
- /* PART 2. FOR EACH SPECIFIC SYSTEM, INCLUDE A C FILE HERE. */
- /***********************************************************************/
- X
- #ifdef SYS_V
- #include "sysv.c"
- #endif
- X
- #ifdef GENERIC
- #include "generic.c"
- #endif
- X
- #ifdef BSD4_3
- #include "bsd.c"
- #endif
- X
- #ifdef DLC
- #include "generic.c"
- #endif
- X
- #ifdef VMS
- #include "vms.c"
- #endif
- X
- #ifdef MSC
- #include "ERROR -- NOT SUPPORTED"
- #endif
- X
- #ifdef TURBOC
- #ifdef PORTABLE
- #include "generic.c"
- #else
- #include "turboc.c"
- #endif
- #endif
- SHAR_EOF
- chmod 0644 machine.c ||
- echo 'restore of machine.c failed'
- Wc_c="`wc -c < 'machine.c'`"
- test 1589 -eq "$Wc_c" ||
- echo 'machine.c: original size 1589, current size' "$Wc_c"
- fi
- # ============= machine.h ==============
- if test -f 'machine.h' -a X"$1" != X"-c"; then
- echo 'x - skipping machine.h (File already exists)'
- else
- echo 'x - extracting machine.h (Text)'
- sed 's/^X//' << 'SHAR_EOF' > 'machine.h' &&
- /* @(#) machine.h 2.1 87/12/25 12:22:43 */
- X
- /*
- The contents of this file are hereby released to the public domain.
- X
- X -- Rahul Dhesi 1986/11/14
- */
- X
- /*
- This file holds definitions that usually do not change
- between different systems, except when using REALLY strange systems. But
- options.h and machine.c hold stuff that does change quite a bit.
- */
- X
- /*
- MAXLONG is the maximum size of a long integer. Right now it doesn't have to
- be accurate since it's only used within zooext() to fake infinite disk space.
- */
- #define MAXLONG ((unsigned long) (~0L))
- X
- /*
- Type BYTE must hold exactly 8 bits. The code will collapse badly if BYTE is
- anything other than exactly 8 bits. To avoid sign extension when casting
- BYTE to a longer size, it must be declared unsigned. For machine-
- independence, Zoo does all I/O of archive headers and directory entries
- in units of BYTE. The actual file data are not written in units of
- BYTE, however, so portability may not be absolute.
- */
- typedef unsigned char BYTE; /* type corresponding to an 8-bit byte */
- X
- SHAR_EOF
- chmod 0644 machine.h ||
- echo 'restore of machine.h failed'
- Wc_c="`wc -c < 'machine.h'`"
- test 1069 -eq "$Wc_c" ||
- echo 'machine.h: original size 1069, current size' "$Wc_c"
- fi
- # ============= macros.ai ==============
- if test -f 'macros.ai' -a X"$1" != X"-c"; then
- echo 'x - skipping macros.ai (File already exists)'
- else
- echo 'x - extracting macros.ai (Text)'
- sed 's/^X//' << 'SHAR_EOF' > 'macros.ai' &&
- ; $Source: /usr/home/dhesi/zoo/RCS/macros.ai,v $
- ; $Id: macros.ai,v 1.2 91/07/07 09:37:52 dhesi Exp $
- ;procedure index, used in-line to save some microseconds
- call_index macro
- X mov si,bx ;si = bx * 5 (5 byte hash entries)
- X shl si,1 ;si = bx * 2 * 2 + bx
- X shl si,1
- X add si,bx
- X endm
- X
- malloc macro siz
- X ifdif <bx>,<siz>
- X mov bx,siz
- X endif
- X mov ah,48h
- X int 21h
- X endm
- X
- SHAR_EOF
- chmod 0644 macros.ai ||
- echo 'restore of macros.ai failed'
- Wc_c="`wc -c < 'macros.ai'`"
- test 369 -eq "$Wc_c" ||
- echo 'macros.ai: original size 369, current size' "$Wc_c"
- fi
- true || echo 'restore of makefile failed'
- echo End of part 4, continue with part 5
- exit 0
-