]> wimlib.net Git - wimlib/blob - src/lzms-decompress.c
b56c4ffa728f0194d430e8233172eb6c0cddd0e0
[wimlib] / src / lzms-decompress.c
1 /*
2  * lzms-decompress.c
3  */
4
5 /*
6  * Copyright (C) 2013, 2014 Eric Biggers
7  *
8  * This file is free software; you can redistribute it and/or modify it under
9  * the terms of the GNU Lesser General Public License as published by the Free
10  * Software Foundation; either version 3 of the License, or (at your option) any
11  * later version.
12  *
13  * This file is distributed in the hope that it will be useful, but WITHOUT
14  * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
15  * FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public License for more
16  * details.
17  *
18  * You should have received a copy of the GNU Lesser General Public License
19  * along with this file; if not, see http://www.gnu.org/licenses/.
20  */
21
22 /*
23  * This is a decompressor for the LZMS compression format used by Microsoft.
24  * This format is not documented, but it is one of the formats supported by the
25  * compression API available in Windows 8, and as of Windows 8 it is one of the
26  * formats that can be used in WIM files.
27  *
28  * This decompressor only implements "raw" decompression, which decompresses a
29  * single LZMS-compressed block.  This behavior is the same as that of
30  * Decompress() in the Windows 8 compression API when using a compression handle
31  * created with CreateDecompressor() with the Algorithm parameter specified as
32  * COMPRESS_ALGORITHM_LZMS | COMPRESS_RAW.  Presumably, non-raw LZMS data is a
33  * container format from which the locations and sizes (both compressed and
34  * uncompressed) of the constituent blocks can be determined.
35  *
36  * An LZMS-compressed block must be read in 16-bit little endian units from both
37  * directions.  One logical bitstream starts at the front of the block and
38  * proceeds forwards.  Another logical bitstream starts at the end of the block
39  * and proceeds backwards.  Bits read from the forwards bitstream constitute
40  * binary range-encoded data, whereas bits read from the backwards bitstream
41  * constitute Huffman-encoded symbols or verbatim bits.  For both bitstreams,
42  * the ordering of the bits within the 16-bit coding units is such that the
43  * first bit is the high-order bit and the last bit is the low-order bit.
44  *
45  * From these two logical bitstreams, an LZMS decompressor can reconstitute the
46  * series of items that make up the LZMS data representation.  Each such item
47  * may be a literal byte or a match.  Matches may be either traditional LZ77
48  * matches or "delta" matches, either of which can have its offset encoded
49  * explicitly or encoded via a reference to a recently used (repeat) offset.
50  *
51  * A traditional LZ match consists of a length and offset; it asserts that the
52  * sequence of bytes beginning at the current position and extending for the
53  * length is exactly equal to the equal-length sequence of bytes at the offset
54  * back in the data buffer.  On the other hand, a delta match consists of a
55  * length, raw offset, and power.  It asserts that the sequence of bytes
56  * beginning at the current position and extending for the length is equal to
57  * the bytewise sum of the two equal-length sequences of bytes (2**power) and
58  * (raw_offset * 2**power) bytes before the current position, minus bytewise the
59  * sequence of bytes beginning at (2**power + raw_offset * 2**power) bytes
60  * before the current position.  Although not generally as useful as traditional
61  * LZ matches, delta matches can be helpful on some types of data.  Both LZ and
62  * delta matches may overlap with the current position; in fact, the minimum
63  * offset is 1, regardless of match length.
64  *
65  * For LZ matches, up to 3 repeat offsets are allowed, similar to some other
66  * LZ-based formats such as LZX and LZMA.  They must updated in an LRU fashion,
67  * except for a quirk: inserting anything to the front of the queue must be
68  * delayed by one LZMS item.  The reason for this is presumably that there is
69  * almost no reason to code the same match offset twice in a row, since you
70  * might as well have coded a longer match at that offset.  For this same
71  * reason, it also is a requirement that when an offset in the queue is used,
72  * that offset is removed from the queue immediately (and made pending for
73  * front-insertion after the following decoded item), and everything to the
74  * right is shifted left one queue slot.  This creates a need for an "overflow"
75  * fourth entry in the queue, even though it is only possible to decode
76  * references to the first 3 entries at any given time.  The queue must be
77  * initialized to the offsets {1, 2, 3, 4}.
78  *
79  * Repeat delta matches are handled similarly, but for them there are two queues
80  * updated in lock-step: one for powers and one for raw offsets.  The power
81  * queue must be initialized to {0, 0, 0, 0}, and the raw offset queue must be
82  * initialized to {1, 2, 3, 4}.
83  *
84  * Bits from the binary range decoder must be used to disambiguate item types.
85  * The range decoder must hold two state variables: the range, which must
86  * initially be set to 0xffffffff, and the current code, which must initially be
87  * set to the first 32 bits read from the forwards bitstream.  The range must be
88  * maintained above 0xffff; when it falls below 0xffff, both the range and code
89  * must be left-shifted by 16 bits and the low 16 bits of the code must be
90  * filled in with the next 16 bits from the forwards bitstream.
91  *
92  * To decode each bit, the binary range decoder requires a probability that is
93  * logically a real number between 0 and 1.  Multiplying this probability by the
94  * current range and taking the floor gives the bound between the 0-bit region of
95  * the range and the 1-bit region of the range.  However, in LZMS, probabilities
96  * are restricted to values of n/64 where n is an integer is between 1 and 63
97  * inclusively, so the implementation may use integer operations instead.
98  * Following calculation of the bound, if the current code is in the 0-bit
99  * region, the new range becomes the current code and the decoded bit is 0;
100  * otherwise, the bound must be subtracted from both the range and the code, and
101  * the decoded bit is 1.  More information about range coding can be found at
102  * https://en.wikipedia.org/wiki/Range_encoding.  Furthermore, note that the
103  * LZMA format also uses range coding and has public domain code available for
104  * it.
105  *
106  * The probability used to range-decode each bit must be taken from a table, of
107  * which one instance must exist for each distinct context in which a
108  * range-decoded bit is needed.  At each call of the range decoder, the
109  * appropriate probability must be obtained by indexing the appropriate
110  * probability table with the last 4 (in the context disambiguating literals
111  * from matches), 5 (in the context disambiguating LZ matches from delta
112  * matches), or 6 (in all other contexts) bits recently range-decoded in that
113  * context, ordered such that the most recently decoded bit is the low-order bit
114  * of the index.
115  *
116  * Furthermore, each probability entry itself is variable, as its value must be
117  * maintained as n/64 where n is the number of 0 bits in the most recently
118  * decoded 64 bits with that same entry.  This allows the compressed
119  * representation to adapt to the input and use fewer bits to represent the most
120  * likely data; note that LZMA uses a similar scheme.  Initially, the most
121  * recently 64 decoded bits for each probability entry are assumed to be
122  * 0x0000000055555555 (high order to low order); therefore, all probabilities
123  * are initially 48/64.  During the course of decoding, each probability may be
124  * updated to as low as 0/64 (as a result of reading many consecutive 1 bits
125  * with that entry) or as high as 64/64 (as a result of reading many consecutive
126  * 0 bits with that entry); however, probabilities of 0/64 and 64/64 cannot be
127  * used as-is but rather must be adjusted to 1/64 and 63/64, respectively,
128  * before being used for range decoding.
129  *
130  * Representations of the LZMS items themselves must be read from the backwards
131  * bitstream.  For this, there are 5 different Huffman codes used:
132  *
133  *  - The literal code, used for decoding literal bytes.  Each of the 256
134  *    symbols represents a literal byte.  This code must be rebuilt whenever
135  *    1024 symbols have been decoded with it.
136  *
137  *  - The LZ offset code, used for decoding the offsets of standard LZ77
138  *    matches.  Each symbol represents an offset slot, which corresponds to a
139  *    base value and some number of extra bits which must be read and added to
140  *    the base value to reconstitute the full offset.  The number of symbols in
141  *    this code is the number of offset slots needed to represent all possible
142  *    offsets in the uncompressed block.  This code must be rebuilt whenever
143  *    1024 symbols have been decoded with it.
144  *
145  *  - The length code, used for decoding length symbols.  Each of the 54 symbols
146  *    represents a length slot, which corresponds to a base value and some
147  *    number of extra bits which must be read and added to the base value to
148  *    reconstitute the full length.  This code must be rebuilt whenever 512
149  *    symbols have been decoded with it.
150  *
151  *  - The delta offset code, used for decoding the offsets of delta matches.
152  *    Each symbol corresponds to an offset slot, which corresponds to a base
153  *    value and some number of extra bits which must be read and added to the
154  *    base value to reconstitute the full offset.  The number of symbols in this
155  *    code is equal to the number of symbols in the LZ offset code.  This code
156  *    must be rebuilt whenever 1024 symbols have been decoded with it.
157  *
158  *  - The delta power code, used for decoding the powers of delta matches.  Each
159  *    of the 8 symbols corresponds to a power.  This code must be rebuilt
160  *    whenever 512 symbols have been decoded with it.
161  *
162  * Initially, each Huffman code must be built assuming that each symbol in that
163  * code has frequency 1.  Following that, each code must be rebuilt each time a
164  * certain number of symbols, as noted above, has been decoded with it.  The
165  * symbol frequencies for a code must be halved after each rebuild of that code;
166  * this makes the codes adapt to the more recent data.
167  *
168  * Like other compression formats such as XPRESS, LZX, and DEFLATE, the LZMS
169  * format requires that all Huffman codes be constructed in canonical form.
170  * This form requires that same-length codewords be lexicographically ordered
171  * the same way as the corresponding symbols and that all shorter codewords
172  * lexicographically precede longer codewords.  Such a code can be constructed
173  * directly from codeword lengths.
174  *
175  * Even with the canonical code restriction, the same frequencies can be used to
176  * construct multiple valid Huffman codes.  Therefore, the decompressor needs to
177  * construct the right one.  Specifically, the LZMS format requires that the
178  * Huffman code be constructed as if the well-known priority queue algorithm is
179  * used and frequency ties are always broken in favor of leaf nodes.
180  *
181  * Codewords in LZMS are guaranteed to not exceed 15 bits.  The format otherwise
182  * places no restrictions on codeword length.  Therefore, the Huffman code
183  * construction algorithm that a correct LZMS decompressor uses need not
184  * implement length-limited code construction.  But if it does (e.g. by virtue
185  * of being shared among multiple compression algorithms), the details of how it
186  * does so are unimportant, provided that the maximum codeword length parameter
187  * is set to at least 15 bits.
188  *
189  * After all LZMS items have been decoded, the data must be postprocessed to
190  * translate absolute address encoded in x86 instructions into their original
191  * relative addresses.
192  *
193  * Details omitted above can be found in the code.  Note that in the absence of
194  * an official specification there is no guarantee that this decompressor
195  * handles all possible cases.
196  */
197
198 #ifdef HAVE_CONFIG_H
199 #  include "config.h"
200 #endif
201
202 #include "wimlib/compress_common.h"
203 #include "wimlib/decompressor_ops.h"
204 #include "wimlib/decompress_common.h"
205 #include "wimlib/error.h"
206 #include "wimlib/lzms.h"
207 #include "wimlib/util.h"
208
209 /* The TABLEBITS values can be changed; they only affect decoding speed.  */
210 #define LZMS_LITERAL_TABLEBITS          10
211 #define LZMS_LENGTH_TABLEBITS           10
212 #define LZMS_LZ_OFFSET_TABLEBITS        10
213 #define LZMS_DELTA_OFFSET_TABLEBITS     10
214 #define LZMS_DELTA_POWER_TABLEBITS      8
215
216 struct lzms_range_decoder {
217
218         /* The relevant part of the current range.  Although the logical range
219          * for range decoding is a very large integer, only a small portion
220          * matters at any given time, and it can be normalized (shifted left)
221          * whenever it gets too small.  */
222         u32 range;
223
224         /* The current position in the range encoded by the portion of the input
225          * read so far.  */
226         u32 code;
227
228         /* Pointer to the next little-endian 16-bit integer in the compressed
229          * input data (reading forwards).  */
230         const le16 *next;
231
232         /* Pointer to the end of the compressed input data.  */
233         const le16 *end;
234 };
235
236 typedef u64 bitbuf_t;
237
238 struct lzms_input_bitstream {
239
240         /* Holding variable for bits that have been read from the compressed
241          * data.  The bit ordering is high to low.  */
242         bitbuf_t bitbuf;
243
244         /* Number of bits currently held in @bitbuf.  */
245         unsigned bitsleft;
246
247         /* Pointer to the one past the next little-endian 16-bit integer in the
248          * compressed input data (reading backwards).  */
249         const le16 *next;
250
251         /* Pointer to the beginning of the compressed input data.  */
252         const le16 *begin;
253 };
254
255 /* Bookkeeping information for an adaptive Huffman code  */
256 struct lzms_huffman_rebuild_info {
257         unsigned num_syms_until_rebuild;
258         unsigned rebuild_freq;
259         u16 *decode_table;
260         unsigned table_bits;
261         u32 *freqs;
262         u32 *codewords;
263         u8 *lens;
264         unsigned num_syms;
265 };
266
267 struct lzms_decompressor {
268
269         /* 'last_target_usages' is in union with everything else because it is
270          * only used for postprocessing.  */
271         union {
272         struct {
273
274         struct lzms_range_decoder rd;
275         struct lzms_input_bitstream is;
276
277         /* Match offset LRU queues  */
278         u32 recent_lz_offsets[LZMS_NUM_RECENT_OFFSETS + 1];
279         u64 recent_delta_offsets[LZMS_NUM_RECENT_OFFSETS + 1];
280         u32 pending_lz_offset;
281         u64 pending_delta_offset;
282         const u8 *lz_offset_still_pending;
283         const u8 *delta_offset_still_pending;
284
285         /* States and probabilities for range decoding  */
286
287         u32 main_state;
288         struct lzms_probability_entry main_prob_entries[
289                         LZMS_NUM_MAIN_STATES];
290
291         u32 match_state;
292         struct lzms_probability_entry match_prob_entries[
293                         LZMS_NUM_MATCH_STATES];
294
295         u32 lz_match_state;
296         struct lzms_probability_entry lz_match_prob_entries[
297                         LZMS_NUM_LZ_MATCH_STATES];
298
299         u32 delta_match_state;
300         struct lzms_probability_entry delta_match_prob_entries[
301                         LZMS_NUM_DELTA_MATCH_STATES];
302
303         u32 lz_repeat_match_states[LZMS_NUM_RECENT_OFFSETS - 1];
304         struct lzms_probability_entry lz_repeat_match_prob_entries[
305                         LZMS_NUM_RECENT_OFFSETS - 1][LZMS_NUM_LZ_REPEAT_MATCH_STATES];
306
307         u32 delta_repeat_match_states[LZMS_NUM_RECENT_OFFSETS - 1];
308         struct lzms_probability_entry delta_repeat_match_prob_entries[
309                         LZMS_NUM_RECENT_OFFSETS - 1][LZMS_NUM_DELTA_REPEAT_MATCH_STATES];
310
311         /* Huffman decoding  */
312
313         u16 literal_decode_table[(1 << LZMS_LITERAL_TABLEBITS) +
314                                  (2 * LZMS_NUM_LITERAL_SYMS)]
315                 _aligned_attribute(DECODE_TABLE_ALIGNMENT);
316         u32 literal_freqs[LZMS_NUM_LITERAL_SYMS];
317         struct lzms_huffman_rebuild_info literal_rebuild_info;
318
319         u16 length_decode_table[(1 << LZMS_LENGTH_TABLEBITS) +
320                                 (2 * LZMS_NUM_LENGTH_SYMS)]
321                 _aligned_attribute(DECODE_TABLE_ALIGNMENT);
322         u32 length_freqs[LZMS_NUM_LENGTH_SYMS];
323         struct lzms_huffman_rebuild_info length_rebuild_info;
324
325         u16 lz_offset_decode_table[(1 << LZMS_LZ_OFFSET_TABLEBITS) +
326                                    ( 2 * LZMS_MAX_NUM_OFFSET_SYMS)]
327                 _aligned_attribute(DECODE_TABLE_ALIGNMENT);
328         u32 lz_offset_freqs[LZMS_MAX_NUM_OFFSET_SYMS];
329         struct lzms_huffman_rebuild_info lz_offset_rebuild_info;
330
331         u16 delta_offset_decode_table[(1 << LZMS_DELTA_OFFSET_TABLEBITS) +
332                                       (2 * LZMS_MAX_NUM_OFFSET_SYMS)]
333                 _aligned_attribute(DECODE_TABLE_ALIGNMENT);
334         u32 delta_offset_freqs[LZMS_MAX_NUM_OFFSET_SYMS];
335         struct lzms_huffman_rebuild_info delta_offset_rebuild_info;
336
337         u16 delta_power_decode_table[(1 << LZMS_DELTA_POWER_TABLEBITS) +
338                                      (2 * LZMS_NUM_DELTA_POWER_SYMS)]
339                 _aligned_attribute(DECODE_TABLE_ALIGNMENT);
340         u32 delta_power_freqs[LZMS_NUM_DELTA_POWER_SYMS];
341         struct lzms_huffman_rebuild_info delta_power_rebuild_info;
342
343         u32 codewords[LZMS_MAX_NUM_SYMS];
344         u8 lens[LZMS_MAX_NUM_SYMS];
345
346         }; // struct
347
348         s32 last_target_usages[65536];
349
350         }; // union
351 };
352
353 /* Initialize the input bitstream @is to read backwards from the compressed data
354  * buffer @in that is @count 16-bit integers long.  */
355 static void
356 lzms_input_bitstream_init(struct lzms_input_bitstream *is,
357                           const le16 *in, size_t count)
358 {
359         is->bitbuf = 0;
360         is->bitsleft = 0;
361         is->next = in + count;
362         is->begin = in;
363 }
364
365 /* Ensure that at least @num_bits bits are in the bitbuffer variable.
366  * @num_bits cannot be more than 32.  */
367 static inline void
368 lzms_ensure_bits(struct lzms_input_bitstream *is, unsigned num_bits)
369 {
370         if (is->bitsleft >= num_bits)
371                 return;
372
373         if (likely(is->next != is->begin))
374                 is->bitbuf |= (bitbuf_t)le16_to_cpu(*--is->next)
375                                 << (sizeof(is->bitbuf) * 8 - is->bitsleft - 16);
376         is->bitsleft += 16;
377
378         if (likely(is->next != is->begin))
379                 is->bitbuf |= (bitbuf_t)le16_to_cpu(*--is->next)
380                                 << (sizeof(is->bitbuf) * 8 - is->bitsleft - 16);
381         is->bitsleft += 16;
382 }
383
384 /* Get @num_bits bits from the bitbuffer variable.  */
385 static inline bitbuf_t
386 lzms_peek_bits(struct lzms_input_bitstream *is, unsigned num_bits)
387 {
388         if (unlikely(num_bits == 0))
389                 return 0;
390         return is->bitbuf >> (sizeof(is->bitbuf) * 8 - num_bits);
391 }
392
393 /* Remove @num_bits bits from the bitbuffer variable.  */
394 static inline void
395 lzms_remove_bits(struct lzms_input_bitstream *is, unsigned num_bits)
396 {
397         is->bitbuf <<= num_bits;
398         is->bitsleft -= num_bits;
399 }
400
401 /* Remove and return @num_bits bits from the bitbuffer variable.  */
402 static inline bitbuf_t
403 lzms_pop_bits(struct lzms_input_bitstream *is, unsigned num_bits)
404 {
405         bitbuf_t bits = lzms_peek_bits(is, num_bits);
406         lzms_remove_bits(is, num_bits);
407         return bits;
408 }
409
410 /* Read @num_bits bits from the input bitstream.  */
411 static inline bitbuf_t
412 lzms_read_bits(struct lzms_input_bitstream *is, unsigned num_bits)
413 {
414         lzms_ensure_bits(is, num_bits);
415         return lzms_pop_bits(is, num_bits);
416 }
417
418 /* Initialize the range decoder @rd to read forwards from the compressed data
419  * buffer @in that is @count 16-bit integers long.  */
420 static void
421 lzms_range_decoder_init(struct lzms_range_decoder *rd,
422                         const le16 *in, size_t count)
423 {
424         rd->range = 0xffffffff;
425         rd->code = ((u32)le16_to_cpu(in[0]) << 16) | le16_to_cpu(in[1]);
426         rd->next = in + 2;
427         rd->end = in + count;
428 }
429
430 /* Decode and return the next bit from the range decoder.
431  *
432  * @prob is the chance out of LZMS_PROBABILITY_MAX that the next bit is 0.
433  */
434 static inline int
435 lzms_range_decoder_decode_bit(struct lzms_range_decoder *rd, u32 prob)
436 {
437         u32 bound;
438
439         /* Normalize if needed.  */
440         if (rd->range <= 0xffff) {
441                 rd->range <<= 16;
442                 rd->code <<= 16;
443                 if (likely(rd->next != rd->end))
444                         rd->code |= le16_to_cpu(*rd->next++);
445         }
446
447         /* Based on the probability, calculate the bound between the 0-bit
448          * region and the 1-bit region of the range.  */
449         bound = (rd->range >> LZMS_PROBABILITY_BITS) * prob;
450
451         if (rd->code < bound) {
452                 /* Current code is in the 0-bit region of the range.  */
453                 rd->range = bound;
454                 return 0;
455         } else {
456                 /* Current code is in the 1-bit region of the range.  */
457                 rd->range -= bound;
458                 rd->code -= bound;
459                 return 1;
460         }
461 }
462
463 /* Decode and return the next bit from the range decoder.  This wraps around
464  * lzms_range_decoder_decode_bit() to handle using and updating the appropriate
465  * state and probability entry.  */
466 static inline int
467 lzms_range_decode_bit(struct lzms_range_decoder *rd,
468                       u32 *state_p, u32 num_states,
469                       struct lzms_probability_entry prob_entries[])
470 {
471         struct lzms_probability_entry *prob_entry;
472         u32 prob;
473         int bit;
474
475         /* Load the probability entry corresponding to the current state.  */
476         prob_entry = &prob_entries[*state_p];
477
478         /* Get the probability that the next bit is 0.  */
479         prob = lzms_get_probability(prob_entry);
480
481         /* Decode the next bit.  */
482         bit = lzms_range_decoder_decode_bit(rd, prob);
483
484         /* Update the state and probability entry based on the decoded bit.  */
485         *state_p = ((*state_p << 1) | bit) & (num_states - 1);
486         lzms_update_probability_entry(prob_entry, bit);
487
488         /* Return the decoded bit.  */
489         return bit;
490 }
491
492 static int
493 lzms_decode_main_bit(struct lzms_decompressor *d)
494 {
495         return lzms_range_decode_bit(&d->rd, &d->main_state,
496                                      LZMS_NUM_MAIN_STATES,
497                                      d->main_prob_entries);
498 }
499
500 static int
501 lzms_decode_match_bit(struct lzms_decompressor *d)
502 {
503         return lzms_range_decode_bit(&d->rd, &d->match_state,
504                                      LZMS_NUM_MATCH_STATES,
505                                      d->match_prob_entries);
506 }
507
508 static int
509 lzms_decode_lz_match_bit(struct lzms_decompressor *d)
510 {
511         return lzms_range_decode_bit(&d->rd, &d->lz_match_state,
512                                      LZMS_NUM_LZ_MATCH_STATES,
513                                      d->lz_match_prob_entries);
514 }
515
516 static int
517 lzms_decode_delta_match_bit(struct lzms_decompressor *d)
518 {
519         return lzms_range_decode_bit(&d->rd, &d->delta_match_state,
520                                      LZMS_NUM_DELTA_MATCH_STATES,
521                                      d->delta_match_prob_entries);
522 }
523
524 static noinline int
525 lzms_decode_lz_repeat_match_bit(struct lzms_decompressor *d, int idx)
526 {
527         return lzms_range_decode_bit(&d->rd, &d->lz_repeat_match_states[idx],
528                                      LZMS_NUM_LZ_REPEAT_MATCH_STATES,
529                                      d->lz_repeat_match_prob_entries[idx]);
530 }
531
532 static noinline int
533 lzms_decode_delta_repeat_match_bit(struct lzms_decompressor *d, int idx)
534 {
535         return lzms_range_decode_bit(&d->rd, &d->delta_repeat_match_states[idx],
536                                      LZMS_NUM_DELTA_REPEAT_MATCH_STATES,
537                                      d->delta_repeat_match_prob_entries[idx]);
538 }
539
540 static void
541 lzms_init_huffman_rebuild_info(struct lzms_huffman_rebuild_info *info,
542                                unsigned rebuild_freq,
543                                u16 *decode_table, unsigned table_bits,
544                                u32 *freqs, u32 *codewords, u8 *lens,
545                                unsigned num_syms)
546 {
547         info->num_syms_until_rebuild = 1;
548         info->rebuild_freq = rebuild_freq;
549         info->decode_table = decode_table;
550         info->table_bits = table_bits;
551         info->freqs = freqs;
552         info->codewords = codewords;
553         info->lens = lens;
554         info->num_syms = num_syms;
555         lzms_init_symbol_frequencies(freqs, num_syms);
556 }
557
558 static noinline void
559 lzms_rebuild_huffman_code(struct lzms_huffman_rebuild_info *info)
560 {
561         make_canonical_huffman_code(info->num_syms, LZMS_MAX_CODEWORD_LEN,
562                                     info->freqs, info->lens, info->codewords);
563         make_huffman_decode_table(info->decode_table, info->num_syms,
564                                   info->table_bits, info->lens,
565                                   LZMS_MAX_CODEWORD_LEN);
566         for (unsigned i = 0; i < info->num_syms; i++)
567                 info->freqs[i] = (info->freqs[i] >> 1) + 1;
568         info->num_syms_until_rebuild = info->rebuild_freq;
569 }
570
571 static inline unsigned
572 lzms_decode_huffman_symbol(struct lzms_input_bitstream *is,
573                            u16 decode_table[], unsigned table_bits,
574                            struct lzms_huffman_rebuild_info *rebuild_info)
575 {
576         unsigned key_bits;
577         unsigned entry;
578         unsigned sym;
579
580         if (unlikely(--rebuild_info->num_syms_until_rebuild == 0))
581                 lzms_rebuild_huffman_code(rebuild_info);
582
583         lzms_ensure_bits(is, LZMS_MAX_CODEWORD_LEN);
584
585         /* Index the decode table by the next table_bits bits of the input.  */
586         key_bits = lzms_peek_bits(is, table_bits);
587         entry = decode_table[key_bits];
588         if (likely(entry < 0xC000)) {
589                 /* Fast case: The decode table directly provided the symbol and
590                  * codeword length.  The low 11 bits are the symbol, and the
591                  * high 5 bits are the codeword length.  */
592                 lzms_remove_bits(is, entry >> 11);
593                 sym = entry & 0x7FF;
594         } else {
595                 /* Slow case: The codeword for the symbol is longer than
596                  * table_bits, so the symbol does not have an entry directly in
597                  * the first (1 << table_bits) entries of the decode table.
598                  * Traverse the appropriate binary tree bit-by-bit in order to
599                  * decode the symbol.  */
600                 lzms_remove_bits(is, table_bits);
601                 do {
602                         key_bits = (entry & 0x3FFF) + lzms_pop_bits(is, 1);
603                 } while ((entry = decode_table[key_bits]) >= 0xC000);
604                 sym = entry;
605         }
606
607         /* Tally and return the decoded symbol.  */
608         rebuild_info->freqs[sym]++;
609         return sym;
610 }
611
612 static unsigned
613 lzms_decode_literal(struct lzms_decompressor *d)
614 {
615         return lzms_decode_huffman_symbol(&d->is,
616                                           d->literal_decode_table,
617                                           LZMS_LITERAL_TABLEBITS,
618                                           &d->literal_rebuild_info);
619 }
620
621 static u32
622 lzms_decode_length(struct lzms_decompressor *d)
623 {
624         unsigned slot = lzms_decode_huffman_symbol(&d->is,
625                                                    d->length_decode_table,
626                                                    LZMS_LENGTH_TABLEBITS,
627                                                    &d->length_rebuild_info);
628         u32 length = lzms_length_slot_base[slot];
629         unsigned num_extra_bits = lzms_extra_length_bits[slot];
630         /* Usually most lengths are short and have no extra bits.  */
631         if (num_extra_bits)
632                 length += lzms_read_bits(&d->is, num_extra_bits);
633         return length;
634 }
635
636 static u32
637 lzms_decode_lz_offset(struct lzms_decompressor *d)
638 {
639         unsigned slot = lzms_decode_huffman_symbol(&d->is,
640                                                    d->lz_offset_decode_table,
641                                                    LZMS_LZ_OFFSET_TABLEBITS,
642                                                    &d->lz_offset_rebuild_info);
643         return lzms_offset_slot_base[slot] +
644                lzms_read_bits(&d->is, lzms_extra_offset_bits[slot]);
645 }
646
647 static u32
648 lzms_decode_delta_offset(struct lzms_decompressor *d)
649 {
650         unsigned slot = lzms_decode_huffman_symbol(&d->is,
651                                                    d->delta_offset_decode_table,
652                                                    LZMS_DELTA_OFFSET_TABLEBITS,
653                                                    &d->delta_offset_rebuild_info);
654         return lzms_offset_slot_base[slot] +
655                lzms_read_bits(&d->is, lzms_extra_offset_bits[slot]);
656 }
657
658 static unsigned
659 lzms_decode_delta_power(struct lzms_decompressor *d)
660 {
661         return lzms_decode_huffman_symbol(&d->is,
662                                           d->delta_power_decode_table,
663                                           LZMS_DELTA_POWER_TABLEBITS,
664                                           &d->delta_power_rebuild_info);
665 }
666
667 /* Decode the series of literals and matches from the LZMS-compressed data.
668  * Return 0 if successful or -1 if the compressed data is invalid.  */
669 static int
670 lzms_decode_items(struct lzms_decompressor * const restrict d,
671                   u8 * const restrict out, const size_t out_nbytes)
672 {
673         u8 *out_next = out;
674         u8 * const out_end = out + out_nbytes;
675
676         while (out_next != out_end) {
677
678                 if (!lzms_decode_main_bit(d)) {
679
680                         /* Literal  */
681                         *out_next++ = lzms_decode_literal(d);
682
683                 } else if (!lzms_decode_match_bit(d)) {
684
685                         /* LZ match  */
686
687                         u32 offset;
688                         u32 length;
689
690                         if (d->pending_lz_offset != 0 &&
691                             out_next != d->lz_offset_still_pending)
692                         {
693                                 BUILD_BUG_ON(LZMS_NUM_RECENT_OFFSETS != 3);
694                                 d->recent_lz_offsets[3] = d->recent_lz_offsets[2];
695                                 d->recent_lz_offsets[2] = d->recent_lz_offsets[1];
696                                 d->recent_lz_offsets[1] = d->recent_lz_offsets[0];
697                                 d->recent_lz_offsets[0] = d->pending_lz_offset;
698                                 d->pending_lz_offset = 0;
699                         }
700
701                         if (!lzms_decode_lz_match_bit(d)) {
702                                 /* Explicit offset  */
703                                 offset = lzms_decode_lz_offset(d);
704                         } else {
705                                 /* Repeat offset  */
706
707                                 BUILD_BUG_ON(LZMS_NUM_RECENT_OFFSETS != 3);
708                                 if (!lzms_decode_lz_repeat_match_bit(d, 0)) {
709                                         offset = d->recent_lz_offsets[0];
710                                         d->recent_lz_offsets[0] = d->recent_lz_offsets[1];
711                                         d->recent_lz_offsets[1] = d->recent_lz_offsets[2];
712                                         d->recent_lz_offsets[2] = d->recent_lz_offsets[3];
713                                 } else if (!lzms_decode_lz_repeat_match_bit(d, 1)) {
714                                         offset = d->recent_lz_offsets[1];
715                                         d->recent_lz_offsets[1] = d->recent_lz_offsets[2];
716                                         d->recent_lz_offsets[2] = d->recent_lz_offsets[3];
717                                 } else {
718                                         offset = d->recent_lz_offsets[2];
719                                         d->recent_lz_offsets[2] = d->recent_lz_offsets[3];
720                                 }
721                         }
722
723                         if (d->pending_lz_offset != 0) {
724                                 BUILD_BUG_ON(LZMS_NUM_RECENT_OFFSETS != 3);
725                                 d->recent_lz_offsets[3] = d->recent_lz_offsets[2];
726                                 d->recent_lz_offsets[2] = d->recent_lz_offsets[1];
727                                 d->recent_lz_offsets[1] = d->recent_lz_offsets[0];
728                                 d->recent_lz_offsets[0] = d->pending_lz_offset;
729                         }
730                         d->pending_lz_offset = offset;
731
732                         length = lzms_decode_length(d);
733
734                         if (unlikely(length > out_end - out_next))
735                                 return -1;
736                         if (unlikely(offset > out_next - out))
737                                 return -1;
738
739                         lz_copy(out_next, length, offset, out_end, LZMS_MIN_MATCH_LEN);
740                         out_next += length;
741
742                         d->lz_offset_still_pending = out_next;
743                 } else {
744                         /* Delta match  */
745
746                         u32 power;
747                         u32 raw_offset, offset1, offset2, offset;
748                         const u8 *matchptr1, *matchptr2, *matchptr;
749                         u32 length;
750
751                         if (d->pending_delta_offset != 0 &&
752                             out_next != d->delta_offset_still_pending)
753                         {
754                                 BUILD_BUG_ON(LZMS_NUM_RECENT_OFFSETS != 3);
755                                 d->recent_delta_offsets[3] = d->recent_delta_offsets[2];
756                                 d->recent_delta_offsets[2] = d->recent_delta_offsets[1];
757                                 d->recent_delta_offsets[1] = d->recent_delta_offsets[0];
758                                 d->recent_delta_offsets[0] = d->pending_delta_offset;
759                                 d->pending_delta_offset = 0;
760                         }
761
762                         if (!lzms_decode_delta_match_bit(d)) {
763                                 /* Explicit offset  */
764                                 power = lzms_decode_delta_power(d);
765                                 raw_offset = lzms_decode_delta_offset(d);
766                         } else {
767                                 /* Repeat offset  */
768                                 u64 val;
769
770                                 BUILD_BUG_ON(LZMS_NUM_RECENT_OFFSETS != 3);
771                                 if (!lzms_decode_delta_repeat_match_bit(d, 0)) {
772                                         val = d->recent_delta_offsets[0];
773                                         d->recent_delta_offsets[0] = d->recent_delta_offsets[1];
774                                         d->recent_delta_offsets[1] = d->recent_delta_offsets[2];
775                                         d->recent_delta_offsets[2] = d->recent_delta_offsets[3];
776                                 } else if (!lzms_decode_delta_repeat_match_bit(d, 1)) {
777                                         val = d->recent_delta_offsets[1];
778                                         d->recent_delta_offsets[1] = d->recent_delta_offsets[2];
779                                         d->recent_delta_offsets[2] = d->recent_delta_offsets[3];
780                                 } else {
781                                         val = d->recent_delta_offsets[2];
782                                         d->recent_delta_offsets[2] = d->recent_delta_offsets[3];
783                                 }
784                                 power = val >> 32;
785                                 raw_offset = (u32)val;
786                         }
787
788                         if (d->pending_delta_offset != 0) {
789                                 BUILD_BUG_ON(LZMS_NUM_RECENT_OFFSETS != 3);
790                                 d->recent_delta_offsets[3] = d->recent_delta_offsets[2];
791                                 d->recent_delta_offsets[2] = d->recent_delta_offsets[1];
792                                 d->recent_delta_offsets[1] = d->recent_delta_offsets[0];
793                                 d->recent_delta_offsets[0] = d->pending_delta_offset;
794                                 d->pending_delta_offset = 0;
795                         }
796                         d->pending_delta_offset = raw_offset | ((u64)power << 32);
797
798                         length = lzms_decode_length(d);
799
800                         offset1 = (u32)1 << power;
801                         offset2 = raw_offset << power;
802                         offset = offset1 + offset2;
803
804                         /* raw_offset<<power overflowed?  */
805                         if (unlikely((offset2 >> power) != raw_offset))
806                                 return -1;
807
808                         /* offset1+offset2 overflowed?  */
809                         if (unlikely(offset < offset2))
810                                 return -1;
811
812                         if (unlikely(length > out_end - out_next))
813                                 return -1;
814
815                         if (unlikely(offset > out_next - out))
816                                 return -1;
817
818                         matchptr1 = out_next - offset1;
819                         matchptr2 = out_next - offset2;
820                         matchptr = out_next - offset;
821
822                         do {
823                                 *out_next++ = *matchptr1++ + *matchptr2++ - *matchptr++;
824                         } while (--length);
825
826                         d->delta_offset_still_pending = out_next;
827                 }
828         }
829         return 0;
830 }
831
832 static void
833 lzms_init_decompressor(struct lzms_decompressor *d, const void *in,
834                        size_t in_nbytes, unsigned num_offset_slots)
835 {
836         /* Match offset LRU queues  */
837         for (int i = 0; i < LZMS_NUM_RECENT_OFFSETS + 1; i++) {
838                 d->recent_lz_offsets[i] = i + 1;
839                 d->recent_delta_offsets[i] = i + 1;
840         }
841         d->pending_lz_offset = 0;
842         d->pending_delta_offset = 0;
843
844         /* Range decoding  */
845
846         lzms_range_decoder_init(&d->rd, in, in_nbytes / sizeof(le16));
847
848         d->main_state = 0;
849         lzms_init_probability_entries(d->main_prob_entries, LZMS_NUM_MAIN_STATES);
850
851         d->match_state = 0;
852         lzms_init_probability_entries(d->match_prob_entries, LZMS_NUM_MATCH_STATES);
853
854         d->lz_match_state = 0;
855         lzms_init_probability_entries(d->lz_match_prob_entries, LZMS_NUM_LZ_MATCH_STATES);
856
857         d->delta_match_state = 0;
858         lzms_init_probability_entries(d->delta_match_prob_entries, LZMS_NUM_DELTA_MATCH_STATES);
859
860         for (int i = 0; i < LZMS_NUM_RECENT_OFFSETS - 1; i++) {
861                 d->lz_repeat_match_states[i] = 0;
862                 lzms_init_probability_entries(d->lz_repeat_match_prob_entries[i],
863                                               LZMS_NUM_LZ_REPEAT_MATCH_STATES);
864
865                 d->delta_repeat_match_states[i] = 0;
866                 lzms_init_probability_entries(d->delta_repeat_match_prob_entries[i],
867                                               LZMS_NUM_DELTA_REPEAT_MATCH_STATES);
868         }
869
870         /* Huffman decoding  */
871
872         lzms_input_bitstream_init(&d->is, in, in_nbytes / sizeof(le16));
873
874         lzms_init_huffman_rebuild_info(&d->literal_rebuild_info,
875                                        LZMS_LITERAL_CODE_REBUILD_FREQ,
876                                        d->literal_decode_table,
877                                        LZMS_LITERAL_TABLEBITS,
878                                        d->literal_freqs,
879                                        d->codewords,
880                                        d->lens,
881                                        LZMS_NUM_LITERAL_SYMS);
882
883         lzms_init_huffman_rebuild_info(&d->length_rebuild_info,
884                                        LZMS_LENGTH_CODE_REBUILD_FREQ,
885                                        d->length_decode_table,
886                                        LZMS_LENGTH_TABLEBITS,
887                                        d->length_freqs,
888                                        d->codewords,
889                                        d->lens,
890                                        LZMS_NUM_LENGTH_SYMS);
891
892         lzms_init_huffman_rebuild_info(&d->lz_offset_rebuild_info,
893                                        LZMS_LZ_OFFSET_CODE_REBUILD_FREQ,
894                                        d->lz_offset_decode_table,
895                                        LZMS_LZ_OFFSET_TABLEBITS,
896                                        d->lz_offset_freqs,
897                                        d->codewords,
898                                        d->lens,
899                                        num_offset_slots);
900
901         lzms_init_huffman_rebuild_info(&d->delta_offset_rebuild_info,
902                                        LZMS_DELTA_OFFSET_CODE_REBUILD_FREQ,
903                                        d->delta_offset_decode_table,
904                                        LZMS_DELTA_OFFSET_TABLEBITS,
905                                        d->delta_offset_freqs,
906                                        d->codewords,
907                                        d->lens,
908                                        num_offset_slots);
909
910         lzms_init_huffman_rebuild_info(&d->delta_power_rebuild_info,
911                                        LZMS_DELTA_POWER_CODE_REBUILD_FREQ,
912                                        d->delta_power_decode_table,
913                                        LZMS_DELTA_POWER_TABLEBITS,
914                                        d->delta_power_freqs,
915                                        d->codewords,
916                                        d->lens,
917                                        LZMS_NUM_DELTA_POWER_SYMS);
918 }
919
920 static int
921 lzms_create_decompressor(size_t max_bufsize, void **d_ret)
922 {
923         struct lzms_decompressor *d;
924
925         if (max_bufsize > LZMS_MAX_BUFFER_SIZE)
926                 return WIMLIB_ERR_INVALID_PARAM;
927
928         d = ALIGNED_MALLOC(sizeof(struct lzms_decompressor),
929                            DECODE_TABLE_ALIGNMENT);
930         if (!d)
931                 return WIMLIB_ERR_NOMEM;
932
933         *d_ret = d;
934         return 0;
935 }
936
937 /* Decompress @in_nbytes bytes of LZMS-compressed data at @in and write the
938  * uncompressed data, which had original size @out_nbytes, to @out.  Return 0 if
939  * successful or -1 if the compressed data is invalid.  */
940 static int
941 lzms_decompress(const void *in, size_t in_nbytes, void *out, size_t out_nbytes,
942                 void *_d)
943 {
944         struct lzms_decompressor *d = _d;
945
946         /*
947          * Requirements on the compressed data:
948          *
949          * 1. LZMS-compressed data is a series of 16-bit integers, so the
950          *    compressed data buffer cannot take up an odd number of bytes.
951          * 2. To prevent poor performance on some architectures, we require that
952          *    the compressed data buffer is 2-byte aligned.
953          * 3. There must be at least 4 bytes of compressed data, since otherwise
954          *    we cannot even initialize the range decoder.
955          */
956         if ((in_nbytes & 1) || ((uintptr_t)in & 1) || (in_nbytes < 4))
957                 return -1;
958
959         lzms_init_decompressor(d, in, in_nbytes,
960                                lzms_get_num_offset_slots(out_nbytes));
961
962         if (lzms_decode_items(d, out, out_nbytes))
963                 return -1;
964
965         lzms_x86_filter(out, out_nbytes, d->last_target_usages, true);
966         return 0;
967 }
968
969 static void
970 lzms_free_decompressor(void *_d)
971 {
972         struct lzms_decompressor *d = _d;
973
974         ALIGNED_FREE(d);
975 }
976
977 const struct decompressor_ops lzms_decompressor_ops = {
978         .create_decompressor  = lzms_create_decompressor,
979         .decompress           = lzms_decompress,
980         .free_decompressor    = lzms_free_decompressor,
981 };