zopen.c revision 146336
1/*-
2 * Copyright (c) 1985, 1986, 1992, 1993
3 *	The Regents of the University of California.  All rights reserved.
4 *
5 * This code is derived from software contributed to Berkeley by
6 * Diomidis Spinellis and James A. Woods, derived from original
7 * work by Spencer Thomas and Joseph Orost.
8 *
9 * Redistribution and use in source and binary forms, with or without
10 * modification, are permitted provided that the following conditions
11 * are met:
12 * 1. Redistributions of source code must retain the above copyright
13 *    notice, this list of conditions and the following disclaimer.
14 * 2. Redistributions in binary form must reproduce the above copyright
15 *    notice, this list of conditions and the following disclaimer in the
16 *    documentation and/or other materials provided with the distribution.
17 * 3. All advertising materials mentioning features or use of this software
18 *    must display the following acknowledgement:
19 *	This product includes software developed by the University of
20 *	California, Berkeley and its contributors.
21 * 4. Neither the name of the University nor the names of its contributors
22 *    may be used to endorse or promote products derived from this software
23 *    without specific prior written permission.
24 *
25 * THIS SOFTWARE IS PROVIDED BY THE REGENTS AND CONTRIBUTORS ``AS IS'' AND
26 * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
27 * IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
28 * ARE DISCLAIMED.  IN NO EVENT SHALL THE REGENTS OR CONTRIBUTORS BE LIABLE
29 * FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
30 * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
31 * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
32 * HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
33 * LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
34 * OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
35 * SUCH DAMAGE.
36 */
37
38#if defined(LIBC_SCCS) && !defined(lint)
39static char sccsid[] = "@(#)zopen.c	8.1 (Berkeley) 6/27/93";
40#endif /* LIBC_SCCS and not lint */
41
42#include <sys/cdefs.h>
43__FBSDID("$FreeBSD: head/usr.bin/compress/zopen.c 146336 2005-05-18 05:24:08Z kan $");
44
45/*-
46 * fcompress.c - File compression ala IEEE Computer, June 1984.
47 *
48 * Compress authors:
49 *		Spencer W. Thomas	(decvax!utah-cs!thomas)
50 *		Jim McKie		(decvax!mcvax!jim)
51 *		Steve Davies		(decvax!vax135!petsd!peora!srd)
52 *		Ken Turkowski		(decvax!decwrl!turtlevax!ken)
53 *		James A. Woods		(decvax!ihnp4!ames!jaw)
54 *		Joe Orost		(decvax!vax135!petsd!joe)
55 *
56 * Cleaned up and converted to library returning I/O streams by
57 * Diomidis Spinellis <dds@doc.ic.ac.uk>.
58 *
59 * zopen(filename, mode, bits)
60 *	Returns a FILE * that can be used for read or write.  The modes
61 *	supported are only "r" and "w".  Seeking is not allowed.  On
62 *	reading the file is decompressed, on writing it is compressed.
63 *	The output is compatible with compress(1) with 16 bit tables.
64 *	Any file produced by compress(1) can be read.
65 */
66
67#include <sys/param.h>
68#include <sys/stat.h>
69
70#include <ctype.h>
71#include <errno.h>
72#include <signal.h>
73#include <stdio.h>
74#include <stdlib.h>
75#include <string.h>
76#include <unistd.h>
77#include "zopen.h"
78
79#define	BITS		16		/* Default bits. */
80#define	HSIZE		69001		/* 95% occupancy */
81
82/* A code_int must be able to hold 2**BITS values of type int, and also -1. */
83typedef long code_int;
84typedef long count_int;
85
86typedef u_char char_type;
87static char_type magic_header[] =
88	{'\037', '\235'};		/* 1F 9D */
89
90#define	BIT_MASK	0x1f		/* Defines for third byte of header. */
91#define	BLOCK_MASK	0x80
92
93/*
94 * Masks 0x40 and 0x20 are free.  I think 0x20 should mean that there is
95 * a fourth header byte (for expansion).
96 */
97#define	INIT_BITS 9			/* Initial number of bits/code. */
98
99#define	MAXCODE(n_bits)	((1 << (n_bits)) - 1)
100
101struct s_zstate {
102	FILE *zs_fp;			/* File stream for I/O */
103	char zs_mode;			/* r or w */
104	enum {
105		S_START, S_MIDDLE, S_EOF
106	} zs_state;			/* State of computation */
107	u_int zs_n_bits;		/* Number of bits/code. */
108	u_int zs_maxbits;		/* User settable max # bits/code. */
109	code_int zs_maxcode;		/* Maximum code, given n_bits. */
110	code_int zs_maxmaxcode;		/* Should NEVER generate this code. */
111	count_int zs_htab [HSIZE];
112	u_short zs_codetab [HSIZE];
113	code_int zs_hsize;		/* For dynamic table sizing. */
114	code_int zs_free_ent;		/* First unused entry. */
115	/*
116	 * Block compression parameters -- after all codes are used up,
117	 * and compression rate changes, start over.
118	 */
119	int zs_block_compress;
120	int zs_clear_flg;
121	long zs_ratio;
122	count_int zs_checkpoint;
123	u_int zs_offset;
124	long zs_in_count;		/* Length of input. */
125	long zs_bytes_out;		/* Length of compressed output. */
126	long zs_out_count;		/* # of codes output (for debugging). */
127	char_type zs_buf[BITS];
128	union {
129		struct {
130			long zs_fcode;
131			code_int zs_ent;
132			code_int zs_hsize_reg;
133			int zs_hshift;
134		} w;			/* Write paramenters */
135		struct {
136			char_type *zs_stackp;
137			int zs_finchar;
138			code_int zs_code, zs_oldcode, zs_incode;
139			int zs_roffset, zs_size;
140			char_type zs_gbuf[BITS];
141		} r;			/* Read parameters */
142	} u;
143};
144
145/* Definitions to retain old variable names */
146#define	fp		zs->zs_fp
147#define	zmode		zs->zs_mode
148#define	state		zs->zs_state
149#define	n_bits		zs->zs_n_bits
150#define	maxbits		zs->zs_maxbits
151#define	maxcode		zs->zs_maxcode
152#define	maxmaxcode	zs->zs_maxmaxcode
153#define	htab		zs->zs_htab
154#define	codetab		zs->zs_codetab
155#define	hsize		zs->zs_hsize
156#define	free_ent	zs->zs_free_ent
157#define	block_compress	zs->zs_block_compress
158#define	clear_flg	zs->zs_clear_flg
159#define	ratio		zs->zs_ratio
160#define	checkpoint	zs->zs_checkpoint
161#define	offset		zs->zs_offset
162#define	in_count	zs->zs_in_count
163#define	bytes_out	zs->zs_bytes_out
164#define	out_count	zs->zs_out_count
165#define	buf		zs->zs_buf
166#define	fcode		zs->u.w.zs_fcode
167#define	hsize_reg	zs->u.w.zs_hsize_reg
168#define	ent		zs->u.w.zs_ent
169#define	hshift		zs->u.w.zs_hshift
170#define	stackp		zs->u.r.zs_stackp
171#define	finchar		zs->u.r.zs_finchar
172#define	code		zs->u.r.zs_code
173#define	oldcode		zs->u.r.zs_oldcode
174#define	incode		zs->u.r.zs_incode
175#define	roffset		zs->u.r.zs_roffset
176#define	size		zs->u.r.zs_size
177#define	gbuf		zs->u.r.zs_gbuf
178
179/*
180 * To save much memory, we overlay the table used by compress() with those
181 * used by decompress().  The tab_prefix table is the same size and type as
182 * the codetab.  The tab_suffix table needs 2**BITS characters.  We get this
183 * from the beginning of htab.  The output stack uses the rest of htab, and
184 * contains characters.  There is plenty of room for any possible stack
185 * (stack used to be 8000 characters).
186 */
187
188#define	htabof(i)	htab[i]
189#define	codetabof(i)	codetab[i]
190
191#define	tab_prefixof(i)	codetabof(i)
192#define	tab_suffixof(i)	((char_type *)(htab))[i]
193#define	de_stack	((char_type *)&tab_suffixof(1 << BITS))
194
195#define	CHECK_GAP 10000		/* Ratio check interval. */
196
197/*
198 * the next two codes should not be changed lightly, as they must not
199 * lie within the contiguous general code space.
200 */
201#define	FIRST	257		/* First free entry. */
202#define	CLEAR	256		/* Table clear output code. */
203
204static int	cl_block(struct s_zstate *);
205static void	cl_hash(struct s_zstate *, count_int);
206static code_int	getcode(struct s_zstate *);
207static int	output(struct s_zstate *, code_int);
208static int	zclose(void *);
209static int	zread(void *, char *, int);
210static int	zwrite(void *, const char *, int);
211
212/*-
213 * Algorithm from "A Technique for High Performance Data Compression",
214 * Terry A. Welch, IEEE Computer Vol 17, No 6 (June 1984), pp 8-19.
215 *
216 * Algorithm:
217 * 	Modified Lempel-Ziv method (LZW).  Basically finds common
218 * substrings and replaces them with a variable size code.  This is
219 * deterministic, and can be done on the fly.  Thus, the decompression
220 * procedure needs no input table, but tracks the way the table was built.
221 */
222
223/*-
224 * compress write
225 *
226 * Algorithm:  use open addressing double hashing (no chaining) on the
227 * prefix code / next character combination.  We do a variant of Knuth's
228 * algorithm D (vol. 3, sec. 6.4) along with G. Knott's relatively-prime
229 * secondary probe.  Here, the modular division first probe is gives way
230 * to a faster exclusive-or manipulation.  Also do block compression with
231 * an adaptive reset, whereby the code table is cleared when the compression
232 * ratio decreases, but after the table fills.  The variable-length output
233 * codes are re-sized at this point, and a special CLEAR code is generated
234 * for the decompressor.  Late addition:  construct the table according to
235 * file size for noticeable speed improvement on small files.  Please direct
236 * questions about this implementation to ames!jaw.
237 */
238static int
239zwrite(void *cookie, const char *wbp, int num)
240{
241	code_int i;
242	int c, disp;
243	struct s_zstate *zs;
244	const u_char *bp;
245	u_char tmp;
246	int count;
247
248	if (num == 0)
249		return (0);
250
251	zs = cookie;
252	count = num;
253	bp = (const u_char *)wbp;
254	if (state == S_MIDDLE)
255		goto middle;
256	state = S_MIDDLE;
257
258	maxmaxcode = 1L << maxbits;
259	if (fwrite(magic_header,
260	    sizeof(char), sizeof(magic_header), fp) != sizeof(magic_header))
261		return (-1);
262	tmp = (u_char)((maxbits) | block_compress);
263	if (fwrite(&tmp, sizeof(char), sizeof(tmp), fp) != sizeof(tmp))
264		return (-1);
265
266	offset = 0;
267	bytes_out = 3;		/* Includes 3-byte header mojo. */
268	out_count = 0;
269	clear_flg = 0;
270	ratio = 0;
271	in_count = 1;
272	checkpoint = CHECK_GAP;
273	maxcode = MAXCODE(n_bits = INIT_BITS);
274	free_ent = ((block_compress) ? FIRST : 256);
275
276	ent = *bp++;
277	--count;
278
279	hshift = 0;
280	for (fcode = (long)hsize; fcode < 65536L; fcode *= 2L)
281		hshift++;
282	hshift = 8 - hshift;	/* Set hash code range bound. */
283
284	hsize_reg = hsize;
285	cl_hash(zs, (count_int)hsize_reg);	/* Clear hash table. */
286
287middle:	for (i = 0; count--;) {
288		c = *bp++;
289		in_count++;
290		fcode = (long)(((long)c << maxbits) + ent);
291		i = ((c << hshift) ^ ent);	/* Xor hashing. */
292
293		if (htabof(i) == fcode) {
294			ent = codetabof(i);
295			continue;
296		} else if ((long)htabof(i) < 0)	/* Empty slot. */
297			goto nomatch;
298		disp = hsize_reg - i;	/* Secondary hash (after G. Knott). */
299		if (i == 0)
300			disp = 1;
301probe:		if ((i -= disp) < 0)
302			i += hsize_reg;
303
304		if (htabof(i) == fcode) {
305			ent = codetabof(i);
306			continue;
307		}
308		if ((long)htabof(i) >= 0)
309			goto probe;
310nomatch:	if (output(zs, (code_int) ent) == -1)
311			return (-1);
312		out_count++;
313		ent = c;
314		if (free_ent < maxmaxcode) {
315			codetabof(i) = free_ent++;	/* code -> hashtable */
316			htabof(i) = fcode;
317		} else if ((count_int)in_count >=
318		    checkpoint && block_compress) {
319			if (cl_block(zs) == -1)
320				return (-1);
321		}
322	}
323	return (num);
324}
325
326static int
327zclose(void *cookie)
328{
329	struct s_zstate *zs;
330	int rval;
331
332	zs = cookie;
333	if (zmode == 'w') {		/* Put out the final code. */
334		if (output(zs, (code_int) ent) == -1) {
335			(void)fclose(fp);
336			free(zs);
337			return (-1);
338		}
339		out_count++;
340		if (output(zs, (code_int) - 1) == -1) {
341			(void)fclose(fp);
342			free(zs);
343			return (-1);
344		}
345	}
346	rval = fclose(fp) == EOF ? -1 : 0;
347	free(zs);
348	return (rval);
349}
350
351/*-
352 * Output the given code.
353 * Inputs:
354 * 	code:	A n_bits-bit integer.  If == -1, then EOF.  This assumes
355 *		that n_bits =< (long)wordsize - 1.
356 * Outputs:
357 * 	Outputs code to the file.
358 * Assumptions:
359 *	Chars are 8 bits long.
360 * Algorithm:
361 * 	Maintain a BITS character long buffer (so that 8 codes will
362 * fit in it exactly).  Use the VAX insv instruction to insert each
363 * code in turn.  When the buffer fills up empty it and start over.
364 */
365
366static char_type lmask[9] =
367	{0xff, 0xfe, 0xfc, 0xf8, 0xf0, 0xe0, 0xc0, 0x80, 0x00};
368static char_type rmask[9] =
369	{0x00, 0x01, 0x03, 0x07, 0x0f, 0x1f, 0x3f, 0x7f, 0xff};
370
371static int
372output(struct s_zstate *zs, code_int ocode)
373{
374	int r_off;
375	u_int bits;
376	char_type *bp;
377
378	r_off = offset;
379	bits = n_bits;
380	bp = buf;
381	if (ocode >= 0) {
382		/* Get to the first byte. */
383		bp += (r_off >> 3);
384		r_off &= 7;
385		/*
386		 * Since ocode is always >= 8 bits, only need to mask the first
387		 * hunk on the left.
388		 */
389		*bp = (*bp & rmask[r_off]) | ((ocode << r_off) & lmask[r_off]);
390		bp++;
391		bits -= (8 - r_off);
392		ocode >>= 8 - r_off;
393		/* Get any 8 bit parts in the middle (<=1 for up to 16 bits). */
394		if (bits >= 8) {
395			*bp++ = ocode;
396			ocode >>= 8;
397			bits -= 8;
398		}
399		/* Last bits. */
400		if (bits)
401			*bp = ocode;
402		offset += n_bits;
403		if (offset == (n_bits << 3)) {
404			bp = buf;
405			bits = n_bits;
406			bytes_out += bits;
407			if (fwrite(bp, sizeof(char), bits, fp) != bits)
408				return (-1);
409			bp += bits;
410			bits = 0;
411			offset = 0;
412		}
413		/*
414		 * If the next entry is going to be too big for the ocode size,
415		 * then increase it, if possible.
416		 */
417		if (free_ent > maxcode || (clear_flg > 0)) {
418		       /*
419			* Write the whole buffer, because the input side won't
420			* discover the size increase until after it has read it.
421			*/
422			if (offset > 0) {
423				if (fwrite(buf, 1, n_bits, fp) != n_bits)
424					return (-1);
425				bytes_out += n_bits;
426			}
427			offset = 0;
428
429			if (clear_flg) {
430				maxcode = MAXCODE(n_bits = INIT_BITS);
431				clear_flg = 0;
432			} else {
433				n_bits++;
434				if (n_bits == maxbits)
435					maxcode = maxmaxcode;
436				else
437					maxcode = MAXCODE(n_bits);
438			}
439		}
440	} else {
441		/* At EOF, write the rest of the buffer. */
442		if (offset > 0) {
443			offset = (offset + 7) / 8;
444			if (fwrite(buf, 1, offset, fp) != offset)
445				return (-1);
446			bytes_out += offset;
447		}
448		offset = 0;
449	}
450	return (0);
451}
452
453/*
454 * Decompress read.  This routine adapts to the codes in the file building
455 * the "string" table on-the-fly; requiring no table to be stored in the
456 * compressed file.  The tables used herein are shared with those of the
457 * compress() routine.  See the definitions above.
458 */
459static int
460zread(void *cookie, char *rbp, int num)
461{
462	u_int count;
463	struct s_zstate *zs;
464	u_char *bp, header[3];
465
466	if (num == 0)
467		return (0);
468
469	zs = cookie;
470	count = num;
471	bp = (u_char *)rbp;
472	switch (state) {
473	case S_START:
474		state = S_MIDDLE;
475		break;
476	case S_MIDDLE:
477		goto middle;
478	case S_EOF:
479		goto eof;
480	}
481
482	/* Check the magic number */
483	if (fread(header,
484	    sizeof(char), sizeof(header), fp) != sizeof(header) ||
485	    memcmp(header, magic_header, sizeof(magic_header)) != 0) {
486		errno = EFTYPE;
487		return (-1);
488	}
489	maxbits = header[2];	/* Set -b from file. */
490	block_compress = maxbits & BLOCK_MASK;
491	maxbits &= BIT_MASK;
492	maxmaxcode = 1L << maxbits;
493	if (maxbits > BITS) {
494		errno = EFTYPE;
495		return (-1);
496	}
497	/* As above, initialize the first 256 entries in the table. */
498	maxcode = MAXCODE(n_bits = INIT_BITS);
499	for (code = 255; code >= 0; code--) {
500		tab_prefixof(code) = 0;
501		tab_suffixof(code) = (char_type) code;
502	}
503	free_ent = block_compress ? FIRST : 256;
504
505	finchar = oldcode = getcode(zs);
506	if (oldcode == -1)	/* EOF already? */
507		return (0);	/* Get out of here */
508
509	/* First code must be 8 bits = char. */
510	*bp++ = (u_char)finchar;
511	count--;
512	stackp = de_stack;
513
514	while ((code = getcode(zs)) > -1) {
515
516		if ((code == CLEAR) && block_compress) {
517			for (code = 255; code >= 0; code--)
518				tab_prefixof(code) = 0;
519			clear_flg = 1;
520			free_ent = FIRST - 1;
521			if ((code = getcode(zs)) == -1)	/* O, untimely death! */
522				break;
523		}
524		incode = code;
525
526		/* Special case for KwKwK string. */
527		if (code >= free_ent) {
528			*stackp++ = finchar;
529			code = oldcode;
530		}
531
532		/* Generate output characters in reverse order. */
533		while (code >= 256) {
534			*stackp++ = tab_suffixof(code);
535			code = tab_prefixof(code);
536		}
537		*stackp++ = finchar = tab_suffixof(code);
538
539		/* And put them out in forward order.  */
540middle:		do {
541			if (count-- == 0)
542				return (num);
543			*bp++ = *--stackp;
544		} while (stackp > de_stack);
545
546		/* Generate the new entry. */
547		if ((code = free_ent) < maxmaxcode) {
548			tab_prefixof(code) = (u_short) oldcode;
549			tab_suffixof(code) = finchar;
550			free_ent = code + 1;
551		}
552
553		/* Remember previous code. */
554		oldcode = incode;
555	}
556	state = S_EOF;
557eof:	return (num - count);
558}
559
560/*-
561 * Read one code from the standard input.  If EOF, return -1.
562 * Inputs:
563 * 	stdin
564 * Outputs:
565 * 	code or -1 is returned.
566 */
567static code_int
568getcode(struct s_zstate *zs)
569{
570	code_int gcode;
571	int r_off, bits;
572	char_type *bp;
573
574	bp = gbuf;
575	if (clear_flg > 0 || roffset >= size || free_ent > maxcode) {
576		/*
577		 * If the next entry will be too big for the current gcode
578		 * size, then we must increase the size.  This implies reading
579		 * a new buffer full, too.
580		 */
581		if (free_ent > maxcode) {
582			n_bits++;
583			if (n_bits == maxbits)	/* Won't get any bigger now. */
584				maxcode = maxmaxcode;
585			else
586				maxcode = MAXCODE(n_bits);
587		}
588		if (clear_flg > 0) {
589			maxcode = MAXCODE(n_bits = INIT_BITS);
590			clear_flg = 0;
591		}
592		size = fread(gbuf, 1, n_bits, fp);
593		if (size <= 0)			/* End of file. */
594			return (-1);
595		roffset = 0;
596		/* Round size down to integral number of codes. */
597		size = (size << 3) - (n_bits - 1);
598	}
599	r_off = roffset;
600	bits = n_bits;
601
602	/* Get to the first byte. */
603	bp += (r_off >> 3);
604	r_off &= 7;
605
606	/* Get first part (low order bits). */
607	gcode = (*bp++ >> r_off);
608	bits -= (8 - r_off);
609	r_off = 8 - r_off;	/* Now, roffset into gcode word. */
610
611	/* Get any 8 bit parts in the middle (<=1 for up to 16 bits). */
612	if (bits >= 8) {
613		gcode |= *bp++ << r_off;
614		r_off += 8;
615		bits -= 8;
616	}
617
618	/* High order bits. */
619	gcode |= (*bp & rmask[bits]) << r_off;
620	roffset += n_bits;
621
622	return (gcode);
623}
624
625static int
626cl_block(struct s_zstate *zs)		/* Table clear for block compress. */
627{
628	long rat;
629
630	checkpoint = in_count + CHECK_GAP;
631
632	if (in_count > 0x007fffff) {	/* Shift will overflow. */
633		rat = bytes_out >> 8;
634		if (rat == 0)		/* Don't divide by zero. */
635			rat = 0x7fffffff;
636		else
637			rat = in_count / rat;
638	} else
639		rat = (in_count << 8) / bytes_out;	/* 8 fractional bits. */
640	if (rat > ratio)
641		ratio = rat;
642	else {
643		ratio = 0;
644		cl_hash(zs, (count_int) hsize);
645		free_ent = FIRST;
646		clear_flg = 1;
647		if (output(zs, (code_int) CLEAR) == -1)
648			return (-1);
649	}
650	return (0);
651}
652
653static void
654cl_hash(struct s_zstate *zs, count_int cl_hsize)	/* Reset code table. */
655{
656	count_int *htab_p;
657	long i, m1;
658
659	m1 = -1;
660	htab_p = htab + cl_hsize;
661	i = cl_hsize - 16;
662	do {			/* Might use Sys V memset(3) here. */
663		*(htab_p - 16) = m1;
664		*(htab_p - 15) = m1;
665		*(htab_p - 14) = m1;
666		*(htab_p - 13) = m1;
667		*(htab_p - 12) = m1;
668		*(htab_p - 11) = m1;
669		*(htab_p - 10) = m1;
670		*(htab_p - 9) = m1;
671		*(htab_p - 8) = m1;
672		*(htab_p - 7) = m1;
673		*(htab_p - 6) = m1;
674		*(htab_p - 5) = m1;
675		*(htab_p - 4) = m1;
676		*(htab_p - 3) = m1;
677		*(htab_p - 2) = m1;
678		*(htab_p - 1) = m1;
679		htab_p -= 16;
680	} while ((i -= 16) >= 0);
681	for (i += 16; i > 0; i--)
682		*--htab_p = m1;
683}
684
685FILE *
686zopen(const char *fname, const char *mode, int bits)
687{
688	struct s_zstate *zs;
689
690	if ((mode[0] != 'r' && mode[0] != 'w') || mode[1] != '\0' ||
691	    bits < 0 || bits > BITS) {
692		errno = EINVAL;
693		return (NULL);
694	}
695
696	if ((zs = calloc(1, sizeof(struct s_zstate))) == NULL)
697		return (NULL);
698
699	maxbits = bits ? bits : BITS;	/* User settable max # bits/code. */
700	maxmaxcode = 1L << maxbits;	/* Should NEVER generate this code. */
701	hsize = HSIZE;			/* For dynamic table sizing. */
702	free_ent = 0;			/* First unused entry. */
703	block_compress = BLOCK_MASK;
704	clear_flg = 0;
705	ratio = 0;
706	checkpoint = CHECK_GAP;
707	in_count = 1;			/* Length of input. */
708	out_count = 0;			/* # of codes output (for debugging). */
709	state = S_START;
710	roffset = 0;
711	size = 0;
712
713	/*
714	 * Layering compress on top of stdio in order to provide buffering,
715	 * and ensure that reads and write work with the data specified.
716	 */
717	if ((fp = fopen(fname, mode)) == NULL) {
718		free(zs);
719		return (NULL);
720	}
721	switch (*mode) {
722	case 'r':
723		zmode = 'r';
724		return (funopen(zs, zread, NULL, NULL, zclose));
725	case 'w':
726		zmode = 'w';
727		return (funopen(zs, NULL, zwrite, NULL, zclose));
728	}
729	/* NOTREACHED */
730	return (NULL);
731}
732