REBOL [
    Title: "Inflate"
    Date: 17-Jul-2010
    Author: "Christopher Ross-Gill"
    Version: 0.0.1
    Notes: {
        Original C Source and notices:
        http://cpansearch.perl.org/src/SREZIC/Tk-804.028/PNG/zlib/contrib/puff/
    }
]

max-bits: 15              ; maximum bits in a code
max-lcodes: 286           ; maximum number of literal/length codes
max-dcodes: 30            ; maximum number of distance codes
max-codes: max-lcodes + max-dcodes  ; maximum codes lengths to read
fix-lcodes: 288           ; number of fixed literal/length codes

; input and output state
stream!: context [
    out: context [
        buffer: #{}
        index: does [length? buffer]
        append: func [chunk [integer! char! any-string!]][
            if integer? chunk [chunk: to-char chunk]
            head insert tail buffer chunk
        ]
        duplicate: func [distance [integer!] part [integer!]][
            case [
                distance > length? buffer [make error! "Distance Code Error"]
                part > distance [make error! "Copying Too Much"]
            ]
            append buffer copy/part skip buffer negate distance part
        ]
    ]       ; output buffer

    ; input state
    in: context [
        buffer: #{}     ; input buffer
        tail?: func [/at ahead [integer!]][empty? skip buffer any [ahead 0]]
        next: has [chunk][chunk: pick buffer 1 buffer: system/words/next buffer 0 + chunk]
        copy: func [part [integer!] /local chunk][
            chunk: system/words/copy/part buffer buffer: skip buffer part
        ]
    ]

    chunk: 0        ; bit buffer
    chunk-length: 0     ; number of bits in bit buffer

    ; input limit error return state for bits() and decode()
    ; jmp_buf env;
]

reverse-chunk: func [len [integer!] chunk [integer!]][
    parse chunk: to-hex chunk [some ["00" end | "00" chunk: | 2 skip]]
    chunk: enbase/base debase/base chunk 16 2
    reverse skip tail chunk negate len
    to-integer debase/base chunk 2
]

bits: func [
    {
        Return 'need bits from the input stream.     This always leaves less than
        eight bits in the buffer.  bits() works properly for need == 0.

        Format notes:

        - Bits are stored in bytes from the least significant bit to the most
          significant bit.  Therefore bits are dropped from the bottom of the bit
          buffer, using shift right, and new bytes are appended to the top of the
          bit buffer, using shift left.
    }
    stream [object!] need [integer!]
    /local chunk
][
    chunk: stream/chunk

    while [stream/chunk-length < need][
        if stream/in/tail? [make error! "Source Corrupted or Incomplete"]   ; out of input
        chunk: chunk or shift/left stream/in/next stream/chunk-length ; load next eight bits

        stream/chunk-length: stream/chunk-length + 8
    ]

    ; drop 'need bits and update buffer, always zero to seven bits left
    stream/chunk: shift chunk need
    stream/chunk-length: stream/chunk-length - need

    ; return 'need bits, zeroing the bits above that
    ; need (shift/left 1 need) - 1 and chunk
    reverse-chunk need (shift/left 1 need) - 1 and chunk
]


stored: func [
    {
        Process a stored block.

        Format notes:

        - After the two-bit stored block type (00), the stored block length and
         stored bytes are byte-aligned for fast copying.  Therefore any leftover
         bits in the byte that has the last bit of the type, as many as seven, are
         discarded.  The value of the discarded bits are not defined and should not
         be checked against any expectation.

        - The second inverted copy of the stored block length does not have to be
         checked, but it's probably a good idea to do so anyway.

        - A stored block can have zero length.  This is sometimes used to byte-align
         subsets of the compressed data for random access or partial recovery.
    }
    stream [object!]
    /local length
][
    length: 0

    ; discard leftover bits from current byte (assumes s/bitcnt < 8)
    stream/chunk: 0
    stream/chunk-length: 0

    ; get length and check against its one's complement
    if stream/in/tail?/at 4 [make error! "Not Enough Input"];       ; not enough input
    length: stream/in/next or shift/left stream/in/next 8
    if any [
        stream/in/next <> (255 and complement length)
        stream/in/next <> (255 and shift complement length 8)
    ][
        make error! "Didn't Match Complement"
    ]

    ; copy len bytes from in to out
    if stream/in/tail?/at length [make error! "Not Enough Input"]
    stream/out/append stream/in/copy length

    0
]

comment {
    Huffman code decoding tables.  count[1..MAXBITS] is the number of symbols of
    each length, which for a canonical code are stepped through in order.
    symbol[] are the symbol values in canonical order, where the number of
    entries is the sum of the counts in count[].     The decoding process can be
    seen in the function decode() below.
}


make-huffman: func [count [integer!] symbol [integer!]][
    context compose [
        count: array/initial (count) 0      ; number of symbols of each length
        symbol: array/initial (symbol) 0    ; canonically ordered symbols
    ]
]


; #ifdef SLOW

decode: func [
    {
        Decode a code from the stream s using huffman table h.  Return the symbol or
        a negative value if there is an error.  If all of the lengths are zero, i.e.
        an empty code, or if the code is incomplete and an invalid code is received,
        then -9 is returned after reading MAXBITS bits.

        Format notes:

        - The codes as stored in the compressed data are bit-reversed relative to
         a simple integer ordering of codes of the same lengths.  Hence below the
         bits are pulled from the compressed data one at a time and used to
         build the code value reversed from what is in the stream in order to
         permit simple integer comparisons for decoding.  A table-based decoding
         scheme (as used in zlib) does not need to do this reversal.

        - The first code for the shortest length is all zeros.  Subsequent codes of
         the same length are simply integer increments of the previous code.  When
         moving up a length, a zero bit is appended to the code.  For a complete
         code, the last code of the longest length will be all ones.

        - Incomplete codes are handled by this decoder, since they are permitted
         in the deflate format.  See the format notes for fixed() and dynamic().
    }
    stream [object!] huffman [object!]
    /local count first index code
][
    code: first: index: 0;
    repeat length max-bits [
        code: code or bits stream 1             ; get next bit
        count: huffman/count/:length
        if first + count > code [       ; if length len, return symbol
            return huffman/symbol/(index + code - first)
        ]
        index: index + count;                   ; else update for next length
        first: first + count;
        first: shift/left first 1;
        code: shift/left code 1;
    ]

    make error! "Ran out of codes"
]

comment {
    A faster version of decode() for real applications of this code.      It's not
    as readable, but it makes puff() twice as fast. And it only makes the code
    a few percent larger.
}

comment {
#else ; !SLOW
local int decode(struct state *s, struct huffman *h)
[
    int len;            ; current number of bits in code
    int code;           ; len bits being decoded
    int first;          ; first code of length len
    int count;          ; number of codes of length len
    int index;          ; index of first code of length len in symbol table
    int bitbuf;         ; bits from stream
    int left;           ; bits left in next or left to process
    short *next;        ; next number of codes

    bitbuf = s/bitbuf;
    left = s/bitcnt;
    code = first = index = 0;
    len = 1;
    next = h/count + 1;
    while (1) [
        while (left--) [
            code |= bitbuf & 1;
            bitbuf >>= 1;
            count = *next++;
            if (code < first + count) [ ; if length len, return symbol
                s/bitbuf = bitbuf;
                s/bitcnt = (s/bitcnt - len) & 7;
                return h/symbol[index + (code - first)];
            ]
            index += count;             ; else update for next length
            first += count;
            first <<= 1;
            code <<= 1;
            len++;
        ]
        left = (MAXBITS+1) - len;
        if (left == 0) break;
        if (s/incnt == s/inlen) longjmp(s/env, 1);  ; out of input
        bitbuf = s/in[s/incnt++];
        if (left > 8) left = 8;
    ]
    return -9;                          ; ran out of codes
]
#endif ; SLOW
}

construct-table: func [
    {
        Given the list of code lengths length[0..n-1] representing a canonical
        Huffman code for n symbols, construct the tables required to decode those
        codes.  Those tables are the number of codes of each length, and the symbols
        sorted by length, retaining their original order within each length.     The
        return value is zero for a complete code set, negative for an over-
        subscribed code set, and positive for an incomplete code set.  The tables
        can be used if the return value is zero or positive, but they cannot be used
        if the return value is negative.     If the return value is zero, it is not
        possible for decode() using that table to return an error--any stream of
        enough bits will resolve to a symbol.  If the return value is positive, then
        it is possible for decode() using that table to return an error for received
        codes past the end of the incomplete lengths.

        Not used by decode(), but used for error checking, h/count[0] is the number
        of the n symbols not in the code.  So n - h/count[0] is the number of
        codes.  This is useful for checking for incomplete codes that have more than
        one symbol, which is an error in a dynamic block.

        Assumption: for all i in 0..n-1, 0 <= length[i] <= MAXBITS
        This is assured by the construction of the length arrays in dynamic() and
        fixed() and is not verified by construct().

        Format notes:

        - Permitted and expected examples of incomplete codes are one of the fixed
         codes and any code with a single symbol which in deflate is coded as one
         bit instead of zero bits.  See the format notes for fixed() and dynamic().

        - Within a given code length, the symbols are kept in ascending order for
         the code bits definition.
    }
    huffman [object!] lengths [block!] n [integer!]
    /local
    symbol "current symbol when stepping through length[]"
    length "current length when stepping through huffman/count[]"
    left "number of possible codes left of current length"
    offs "offsets in symbol table for each length"
][
    offs: array/initial max-bits + 1 1

    ; count number of codes of each length
    huffman/count: array/initial max-bits
    repeat symbol n [
        huffman/count/(lengths/:symbol): 1 + huffman/count/(lengths/:symbol)
    ]

        ;   ; assumes lengths are within bounds
    if huffman/count/1 = n [return 0]   ; complete, but decode() will fail

    ; check for an over-subscribed or incomplete set of lengths
    left: 1                                     ; one possible code of zero length
    repeat len max-bits [
        left: shift/left left 1                 ; one more bit, double codes left
        left: left - huffman/count/(len + 1)    ; deduct count from possible codes
        if left < 0 [return left]               ; over-subscribed--return negative
    ]                                           ; left > 0 means incomplete

    ; generate offsets into symbol table for each length for sorting
    offs/2: 0
    repeat length max-bits [
        offs/(length + 2): offs/(length + 1) + huffman/count/(length + 1)
    ]

    comment {
        put symbols in table sorted by length, by symbol order within each
        length
    }

    repeat symbol n [
        unless lengths/:symbol = 0 [
            offs/(lengths/:symbol): offs/(lengths/:symbol) + 1
            huffman/symbol/(offs/(lengths/:symbol)): symbol
        ]
    ]

    ; return zero for complete set, positive for incomplete set
    left
]

codes: func [
    {
        Decode literal/length and distance codes until an end-of-block code.

        Format notes:

        - Compressed data that is after the block type if fixed or after the code
         description if dynamic is a combination of literals and length/distance
         pairs terminated by and end-of-block code.  Literals are simply Huffman
         coded bytes.  A length/distance pair is a coded length followed by a
         coded distance to represent a string that occurs earlier in the
         uncompressed data that occurs again at the current location.

        - Literals, lengths, and the end-of-block code are combined into a single
         code of up to 286 symbols.  They are 256 literals (0..255), 29 length
         symbols (257..285), and the end-of-block symbol (256).

        - There are 256 possible lengths (3..258), and so 29 symbols are not enough
         to represent all of those.  Lengths 3..10 and 258 are in fact represented
         by just a length symbol.  Lengths 11..257 are represented as a symbol and
         some number of extra bits that are added as an integer to the base length
         of the length symbol.  The number of extra bits is determined by the base
         length symbol.  These are in the static arrays below, lens[] for the base
         lengths and lext[] for the corresponding number of extra bits.

        - The reason that 258 gets its own symbol is that the longest length is used
         often in highly redundant files.  Note that 258 can also be coded as the
         base value 227 plus the maximum extra value of 31.  While a good deflate
         should never do this, it is not an error, and should be decoded properly.

        - If a length is decoded, including its extra bits if any, then it is
         followed a distance code.  There are up to 30 distance symbols.  Again
         there are many more possible distances (1..32768), so extra bits are added
         to a base value represented by the symbol.  The distances 1..4 get their
         own symbol, but the rest require extra bits.  The base distances and
         corresponding number of extra bits are below in the static arrays dist[]
         and dext[].

        - Literal bytes are simply written to the output.  A length/distance pair is
         an instruction to copy previously uncompressed bytes to the output.  The
         copy is from distance bytes back in the output stream, copying for length
         bytes.

        - Distances pointing before the beginning of the output data are not
         permitted.

        - Overlapped copies, where the length is greater than the distance, are
         allowed and common.  For example, a distance of one and a length of 258
         simply copies the last byte 258 times.  A distance of four and a length of
         twelve copies the last four bytes three times.  A simple forward copy
         ignoring whether the length is greater than the distance or not implements
         this correctly.  You should not use memcpy() since its behavior is not
         defined for overlapped arrays.  You should not use memmove() or bcopy()
         since though their behavior -is- defined for overlapping arrays, it is
         defined to do the wrong thing in this case.
    }
    stream [object!] lencode [object!] distcode [object!]
    /local symbol len dist lens
][
    lens: [ ; Size base for length codes 257..285
        3 4 5 6 7 8 9 10 11 13 15 17 19 23 27 31,
        35 43 51 59 67 83 99 115 131 163 195 227 258
    ]
    lext: [ ; Extra bits for length codes 257..285
        0 0 0 0 0 0 0 0 1 1 1 1 2 2 2 2,
        3 3 3 3 4 4 4 4 5 5 5 5 0
    ]
    dists: [ ; Offset base for distance codes 0..29
        1 2 3 4 5 7 9 13 17 25 33 49 65 97 129 193,
        257 385 513 769 1025 1537 2049 3073 4097 6145,
        8193 12289 16385 24577
    ]
    dext: [ ; Extra bits for distance codes 0..29
        0 0 0 0 1 1 2 2 3 3 4 4 5 5 6 6
        7 7 8 8 9 9 10 10 11 11
        12 12 13 13
    ]

    ; decode literals and length/distance pairs
    until [
        symbol: decode stream lencode
        case [
            symbol < 0 [return symbol]              ; invalid symbol
            symbol < 256 [stream/out/append symbol] ; literal: symbol is the byte
            symbol > 256 [      ; length
                ; get and compute length
                symbol: symbol - 257;
                if (symbol >= 29) return -9;        ; invalid fixed code
                len: lens/:symbol + bits stream lext/:symbol

                ; get and check distance
                symbol: decode stream distcode
                if symbol < 0 [return symbol]       ; invalid symbol
                dist: dists/:symbol + bits stream dext/:symbol
                stream/out/duplicate dist part
            ]
        ]
        symbol = 256
    ] ; while (symbol != 256);          ; end of block symbol

    ; done with a valid fixed or dynamic block
    return 0;
]

fixed: func [
    {
        Process a fixed codes block.

        Format notes:

        - This block type can be useful for compressing small amounts of data for
         which the size of the code descriptions in a dynamic block exceeds the
         benefit of custom codes for that block.  For fixed codes, no bits are
         spent on code descriptions.  Instead the code lengths for literal/length
         codes and distance codes are fixed.  The specific lengths for each symbol
         can be seen in the "for" loops below.

        - The literal/length code is complete, but has two symbols that are invalid
         and should result in an error if received.  This cannot be implemented
         simply as an incomplete code since those two symbols are in the "middle"
         of the code.  They are eight bits long and the longest literal/length\
         code is nine bits.  Therefore the code must be constructed with those
         symbols, and the invalid symbols must be detected after decoding.

        - The fixed distance codes also have two invalid symbols that should result
         in an error if received.  Since all of the distance codes are the same
         length, this can be implemented as an incomplete code.  Then the invalid
         codes are detected while decoding.
    }
    stream [object!]
    /local virgin lencode distcode symbol lengths
][
    lencode: make-huffman max-bits + 1 fix-lcodes
    distcode: make-huffman max-bits + 1 max-dcodes

    unless value? virgin [
        lengths: make block! fix-lcodes
        repeat symbol fix-lcodes [
            append lengths case [
                symbol <= 144 [8]
                symbol <= 256 [9]
                symbol <= 280 [7]
                symbol [8]
            ]
        ]

        construct-table lencode lengths fix-lcodes

        repeat symbol max-dcodes [poke lengths symbol 5]
        construct-table distcode lengths max-dcodes

        virgin: true
    ]

    codes stream lencode distcode
] 

dynamic: func [
    {
        Process a dynamic codes block.

        Format notes:

        - A dynamic block starts with a description of the literal/length and
         distance codes for that block.  New dynamic blocks allow the compressor to
         rapidly adapt to changing data with new codes optimized for that data.

        - The codes used by the deflate format are "canonical", which means that
         the actual bits of the codes are generated in an unambiguous way simply
         from the number of bits in each code.  Therefore the code descriptions
         are simply a list of code lengths for each symbol.

        - The code lengths are stored in order for the symbols, so lengths are
         provided for each of the literal/length symbols, and for each of the
         distance symbols.

        - If a symbol is not used in the block, this is represented by a zero as
         as the code length.  This does not mean a zero-length code, but rather
         that no code should be created for this symbol.  There is no way in the
         deflate format to represent a zero-length code.

        - The maximum number of bits in a code is 15, so the possible lengths for
         any code are 1..15.

        - The fact that a length of zero is not permitted for a code has an
         interesting consequence.  Normally if only one symbol is used for a given
         code, then in fact that code could be represented with zero bits.  However
         in deflate, that code has to be at least one bit.  So for example, if
         only a single distance base symbol appears in a block, then it will be
         represented by a single code of length one, in particular one 0 bit.  This
         is an incomplete code, since if a 1 bit is received, it has no meaning,
         and should result in an error.  So incomplete distance codes of one symbol
         should be permitted, and the receipt of invalid codes should be handled.

        - It is also possible to have a single literal/length code, but that code
         must be the end-of-block code, since every dynamic block has one.  This
         is not the most efficient way to create an empty block (an empty fixed
         block is fewer bits), but it is allowed by the format.  So incomplete
         literal/length codes of one symbol should also be permitted.

        - If there are only literal codes and no lengths, then there are no distance
         codes.  This is represented by one distance code with zero bits.

        - The list of up to 286 length/literal lengths and up to 30 distance lengths
         are themselves compressed using Huffman codes and run-length encoding.  In
         the list of code lengths, a 0 symbol means no code, a 1..15 symbol means
         that length, and the symbols 16, 17, and 18 are run-length instructions.
         Each of 16, 17, and 18 are follwed by extra bits to define the length of
         the run.  16 copies the last length 3 to 6 times.  17 represents 3 to 10
         zero lengths, and 18 represents 11 to 138 zero lengths.  Unused symbols
         are common, hence the special coding for zero lengths.

        - The symbols for 0..18 are Huffman coded, and so that code must be
         described first.  This is simply a sequence of up to 19 three-bit values
         representing no code (0) or the code length for that symbol (1..7).

        - A dynamic block starts with three fixed-size counts from which is computed
         the number of literal/length code lengths, the number of distance code
         lengths, and the number of code length code lengths (ok, you come up with
         a better name!) in the code descriptions.  For the literal/length and
         distance codes, lengths after those provided are considered zero, i.e. no
         code.  The code length code lengths are received in a permuted order (see
         the order[] array below) to make a short code length code length list more
         likely.  As it turns out, very short and very long codes are less likely
         to be seen in a dynamic code description, hence what may appear initially
         to be a peculiar ordering.

        - Given the number of literal/length code lengths (nlen) and distance code
         lengths (ndist), then they are treated as one long list of nlen + ndist
         code lengths.  Therefore run-length coding can and often does cross the
         boundary between the two sets of lengths.

        - So to summarize, the code description at the start of a dynamic block is
         three counts for the number of code lengths for the literal/length codes,
         the distance codes, and the code length codes.  This is followed by the
         code length code lengths, three bits each.  This is used to construct the
         code length code which is used to read the remainder of the lengths.  Then
         the literal/length code lengths and distance lengths are read as a single
         set of lengths using the code length codes.  Codes are constructed from
         the resulting two sets of lengths, and then finally you can start
         decoding actual compressed data in the block.

        - For reference, a "typical" size for the code description in a dynamic
         block is around 80 bytes.
    }
    stream [object!]
    /local
    nlen ndist ncode "number of lengths in descriptor"
    err "construct() return value"
    index "index of lengths[]"
    lengths "descriptor code lengths"
    lencode "length code"
    distcode "distance code"
    order "permutation of code length codes"
][
    lencode: make-huffman max-bits + 1 fix-lcodes
    distcode: make-huffman max-bits + 1 max-dcodes

    lengths: array/initial max-codes 1
    order: [16 17 18 0 8 7 9 6 10 5 11 4 12 3 13 2 14 1 15]

    ; get number of lengths in each table, check lengths
    nlen: 257 + bits stream 5
    ndist: 1 + bits stream 5
    ncode: 4 + bits stream 4

    if any [nlen > max-lcodes ndist > max-dcodes][make error! "Bad Counts"]

    ; read code length code lengths (really), missing lengths are zero
    repeat index ncode [
        poke lengths 1 + order/:index 1 + bits stream 3
    ]

    ; build huffman table for code lengths codes (use lencode temporarily)
    err: construct-table lencode lengths 19
    unless err = 0 [return -4]          ; require complete code set here

    ; read length/literal and distance code length tables
    index: 1
    while [index < (nlen + ndist)][
        symbol: decode stream lencode
        either symbol < 16 [                ; length in 0..15
            index: index + 1
            poke lengths index symbol
        ][                          ; repeat instruction
            len: 0                  ; assume repeating zeros
            case [
                symbol = 16 [       ; repeat last length 3..6 times
                    if index = 0 [make error! "no last length!"]
                    len: lengths/(index - 1)        ; last length
                    symbol: 3 + bits stream 2
                ]
                symbol = 17 [       ; repeat zero 3..10 times
                    symbol: 3 + bits stream 3
                ]
                symbol [            ; == 18, repeat zero 11..138 times
                    symbol: 11 + bits stream 7
                ]
            ]

            if (index + symbol) > (nlen + ndist) [make error! "too many lengths!"]
            loop symbol - 1 [                   ; repeat last or zero 'symbol times
                poke lengths index: index + 1 len
            ]
            symbol: 0
        ]
    ]

    ; build huffman table for literal/length codes
    err: construct-table lencode lengths nlen
    if any [err < 0 all [err > 0 1 <> nlen - lencode/count/1]][
        return -7       ; only allow incomplete codes if just one code
    ]

    ; build huffman table for distance codes
    err: construct-table distcode lengths + nlen ndist
    if any [err < 0 all [err > 0 1 <> ndist - distcode/count/1]][
        return -8;      ; only allow incomplete codes if just one code
    ]

    ; decode data until end-of-block code
    codes stream lencode distcode
]


inflate: func [
    {
        Inflate source to dest. On return, destlen and sourcelen are updated to the
        size of the uncompressed data and the size of the deflate data respectively.
        On success, the return value of puff() is zero. If there is an error in the
        source data, i.e. it is not in the deflate format, then a negative value is
        returned.  If there is not enough input available or there is not enough
        output space, then a positive error is returned.     In that case, destlen and
        sourcelen are not updated to facilitate retrying from the beginning with the
        provision of more input data or more output space.  In the case of invalid
        inflate data (a negative error), the dest and source pointers are updated to
        facilitate the debugging of deflators.

        puff() also has a mode to determine the size of the uncompressed output with
        no output written.  For this dest must be (unsigned char *)0.  In this case,
        the input value of *destlen is ignored, and on return *destlen is set to the
        size of the uncompressed output.

        The return codes are:

         2:  available inflate data did not terminate
         1:  output space exhausted before completing inflate
         0:  successful inflate
        -1:  invalid block type (type == 3)
        -2:  stored block length did not match one's complement
        -3:  dynamic block code description: too many length or distance codes
        -4:  dynamic block code description: code lengths codes incomplete
        -5:  dynamic block code description: repeat lengths with no first length
        -6:  dynamic block code description: repeat more than specified lengths
        -7:  dynamic block code description: invalid literal/length code lengths
        -8:  dynamic block code description: invalid distance code lengths
        -9:  invalid literal/length or distance code in fixed or dynamic block
        -10:     distance is too far back in fixed or dynamic block

        Format notes:

        - Three bits are read for each block to determine the kind of block and
         whether or not it is the last block.  Then the block is decoded and the
         process repeated if it was not the last block.

        - The leftover bits in the last byte of the deflate data after the last
         block (if it was a fixed or dynamic block) are undefined and have no
         expected values to check.
    }
    series [any-string!]
    /local stream
    ; unsigned char *dest,          ; pointer to destination pointer
    ; unsigned long *destlen,       ; amount of output space
    ; unsigned char *source,            ; pointer to source data pointer
    ; unsigned long *sourcelen      ; amount of input available
][
    stream: make stream! [
        in: make in [buffer: to-binary series]
        out: make out [buffer: copy #{}]
    ]           ; input/output state

    last: type: 0               ; block information
    err: 0                      ; return value

    ; return if bits() or decode() tries to read past available input
    until [
        last: bits stream 1         ; one if last block
        type: bits stream 2         ; block type 0..3
        err: case [
            type = 0 [stored stream]
            type = 1 [fixed stream]
            type = 2 [dynamic stream]
        ]                       ; type == 3, invalid
        if err <> 0 [break]     ; return with error
        last = 1
    ]

    stream/out/buffer
]

; {00001011 01001010 01001101 11001010 11001111 00000001 00000000} ; normal
; {11010000 01010010 10110010 01010011 11110011 10000000 00000000} ; bytes reversed
; {1 10 10000 01010 0101 0110010 01010011 11110011 10000000 00000000} ; tracking bits

probe "Rebol" = probe to-string inflate #{0B4A4DCACF0100}