{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RecordWildCards #-}

module Network.HPACK.Table.Dynamic (
    DynamicTable (..),
    newDynamicTableForEncoding,
    newDynamicTableForDecoding,
    renewDynamicTable,
    huffmanDecoder,
    printDynamicTable,
    isDynamicTableEmpty,
    isSuitableSize,
    TableSizeAction (..),
    needChangeTableSize,
    setLimitForEncoding,
    resetLimitForEncoding,
    insertEntry,
    toDynamicEntry,
    CodeInfo (..),
    withDynamicTableForEncoding,
    withDynamicTableForDecoding,
    toIndexedEntry,
    fromHIndexToIndex,
    getRevIndex,
) where

import Control.Exception (throwIO)
import Data.Array.Base (unsafeRead, unsafeWrite)
import Data.Array.IO (IOArray, newArray)
import qualified Data.ByteString.Char8 as BS
import Data.IORef

import Imports
import Network.HPACK.Huffman
import Network.HPACK.Table.Entry
import Network.HPACK.Table.RevIndex
import Network.HPACK.Table.Static
import Network.HPACK.Types

----------------------------------------------------------------

-- For decoder
{-# INLINE toIndexedEntry #-}
toIndexedEntry :: DynamicTable -> Index -> IO Entry
toIndexedEntry :: DynamicTable -> Size -> IO Entry
toIndexedEntry DynamicTable
dyntbl Size
idx
    | Size
idx Size -> Size -> Bool
forall a. Ord a => a -> a -> Bool
<= Size
0 = DecodeError -> IO Entry
forall e a. Exception e => e -> IO a
throwIO (DecodeError -> IO Entry) -> DecodeError -> IO Entry
forall a b. (a -> b) -> a -> b
$ Size -> DecodeError
IndexOverrun Size
idx
    | Size
idx Size -> Size -> Bool
forall a. Ord a => a -> a -> Bool
<= Size
staticTableSize = Entry -> IO Entry
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Entry -> IO Entry) -> Entry -> IO Entry
forall a b. (a -> b) -> a -> b
$ Size -> Entry
toStaticEntry Size
idx
    | Bool
otherwise = DynamicTable -> Size -> IO Entry
toDynamicEntry DynamicTable
dyntbl Size
idx

-- For encoder
{-# INLINE fromHIndexToIndex #-}
fromHIndexToIndex :: DynamicTable -> HIndex -> IO Index
fromHIndexToIndex :: DynamicTable -> HIndex -> IO Size
fromHIndexToIndex DynamicTable
_ (SIndex Size
idx) = Size -> IO Size
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Size
idx
fromHIndexToIndex DynamicTable{IORef Size
IORef Table
CodeInfo
codeInfo :: CodeInfo
circularTable :: IORef Table
offset :: IORef Size
numOfEntries :: IORef Size
maxNumOfEntries :: IORef Size
dynamicTableSize :: IORef Size
maxDynamicTableSize :: IORef Size
codeInfo :: DynamicTable -> CodeInfo
circularTable :: DynamicTable -> IORef Table
offset :: DynamicTable -> IORef Size
numOfEntries :: DynamicTable -> IORef Size
maxNumOfEntries :: DynamicTable -> IORef Size
dynamicTableSize :: DynamicTable -> IORef Size
maxDynamicTableSize :: DynamicTable -> IORef Size
..} (DIndex Size
didx) = do
    Size
maxN <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
maxNumOfEntries
    Size
off <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
offset
    Size
x <- Size -> Size -> IO Size
adj Size
maxN (Size
didx Size -> Size -> Size
forall a. Num a => a -> a -> a
- Size
off)
    Size -> IO Size
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Size -> IO Size) -> Size -> IO Size
forall a b. (a -> b) -> a -> b
$ Size
x Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Size
staticTableSize

----------------------------------------------------------------

type Table = IOArray Index Entry

{-
        offset
        v
   +-+-+-+-+-+-+-+-+
   | | | |z|y|x| | |
   +-+-+-+-+-+-+-+-+
          1 2 3      (numOfEntries = 3)

After insertion:

      offset
      v
   +-+-+-+-+-+-+-+-+
   | | |w|z|y|x| | |
   +-+-+-+-+-+-+-+-+
        1 2 3 4      (numOfEntries = 4)
-}

data CodeInfo = CIE EncodeInfo | CID DecodeInfo
data EncodeInfo
    = EncodeInfo
        RevIndex -- Reverse index
        -- The value informed by SETTINGS_HEADER_TABLE_SIZE.
        -- If 'Nothing', dynamic table size update is not necessary.
        -- Otherwise, dynamic table size update is sent
        -- and this value should be set to 'Nothing'.
        (IORef (Maybe Size))
data DecodeInfo
    = DecodeInfo
        HuffmanDecoder
        (IORef Size) -- The limit size

toEncodeInfo :: CodeInfo -> EncodeInfo
toEncodeInfo :: CodeInfo -> EncodeInfo
toEncodeInfo (CIE EncodeInfo
x) = EncodeInfo
x
toEncodeInfo CodeInfo
_ = [Char] -> EncodeInfo
forall a. HasCallStack => [Char] -> a
error [Char]
"toEncodeInfo"

toDecodeInfo :: CodeInfo -> DecodeInfo
toDecodeInfo :: CodeInfo -> DecodeInfo
toDecodeInfo (CID DecodeInfo
x) = DecodeInfo
x
toDecodeInfo CodeInfo
_ = [Char] -> DecodeInfo
forall a. HasCallStack => [Char] -> a
error [Char]
"toDecodeInfo"

-- | Type for dynamic table.
data DynamicTable = DynamicTable
    { DynamicTable -> CodeInfo
codeInfo :: CodeInfo
    , DynamicTable -> IORef Table
circularTable :: IORef Table
    -- ^ An array
    , DynamicTable -> IORef Size
offset :: IORef Index
    -- ^ Start point
    , DynamicTable -> IORef Size
numOfEntries :: IORef Int
    -- ^ The current number of entries
    , DynamicTable -> IORef Size
maxNumOfEntries :: IORef Int
    -- ^ The size of the array
    , DynamicTable -> IORef Size
dynamicTableSize :: IORef Size
    -- ^ The current dynamic table size (defined in HPACK)
    , DynamicTable -> IORef Size
maxDynamicTableSize :: IORef Size
    -- ^ The max dynamic table size (defined in HPACK)
    }

{-# INLINE adj #-}
adj :: Int -> Int -> IO Int
adj :: Size -> Size -> IO Size
adj Size
maxN Size
x
    | Size
maxN Size -> Size -> Bool
forall a. Eq a => a -> a -> Bool
== Size
0 = DecodeError -> IO Size
forall e a. Exception e => e -> IO a
throwIO DecodeError
TooSmallTableSize
    | Bool
otherwise =
        let ret :: Size
ret = (Size
x Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Size
maxN) Size -> Size -> Size
forall a. Integral a => a -> a -> a
`mod` Size
maxN
         in Size -> IO Size
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Size
ret

huffmanDecoder :: DynamicTable -> HuffmanDecoder
huffmanDecoder :: DynamicTable -> HuffmanDecoder
huffmanDecoder DynamicTable{IORef Size
IORef Table
CodeInfo
codeInfo :: DynamicTable -> CodeInfo
circularTable :: DynamicTable -> IORef Table
offset :: DynamicTable -> IORef Size
numOfEntries :: DynamicTable -> IORef Size
maxNumOfEntries :: DynamicTable -> IORef Size
dynamicTableSize :: DynamicTable -> IORef Size
maxDynamicTableSize :: DynamicTable -> IORef Size
codeInfo :: CodeInfo
circularTable :: IORef Table
offset :: IORef Size
numOfEntries :: IORef Size
maxNumOfEntries :: IORef Size
dynamicTableSize :: IORef Size
maxDynamicTableSize :: IORef Size
..} = HuffmanDecoder
dec
  where
    DecodeInfo HuffmanDecoder
dec IORef Size
_ = CodeInfo -> DecodeInfo
toDecodeInfo CodeInfo
codeInfo

----------------------------------------------------------------

-- | Printing 'DynamicTable'.
printDynamicTable :: DynamicTable -> IO ()
printDynamicTable :: DynamicTable -> IO ()
printDynamicTable DynamicTable{IORef Size
IORef Table
CodeInfo
codeInfo :: DynamicTable -> CodeInfo
circularTable :: DynamicTable -> IORef Table
offset :: DynamicTable -> IORef Size
numOfEntries :: DynamicTable -> IORef Size
maxNumOfEntries :: DynamicTable -> IORef Size
dynamicTableSize :: DynamicTable -> IORef Size
maxDynamicTableSize :: DynamicTable -> IORef Size
codeInfo :: CodeInfo
circularTable :: IORef Table
offset :: IORef Size
numOfEntries :: IORef Size
maxNumOfEntries :: IORef Size
dynamicTableSize :: IORef Size
maxDynamicTableSize :: IORef Size
..} = do
    Size
maxN <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
maxNumOfEntries
    Size
off <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
offset
    Size
n <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
numOfEntries
    let beg :: Size
beg = Size
off Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Size
1
        end :: Size
end = Size
off Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Size
n
    Table
tbl <- IORef Table -> IO Table
forall a. IORef a -> IO a
readIORef IORef Table
circularTable
    [Entry]
es <- (Size -> IO Entry) -> [Size] -> IO [Entry]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (Size -> Size -> IO Size
adj Size
maxN (Size -> IO Size) -> (Size -> IO Entry) -> Size -> IO Entry
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> Table -> Size -> IO Entry
forall i. Ix i => IOArray i Entry -> Size -> IO Entry
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> Size -> m e
unsafeRead Table
tbl) [Size
beg .. Size
end]
    let ts :: [(Size, Entry)]
ts = [Size] -> [Entry] -> [(Size, Entry)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Size
1 ..] [Entry]
es
    ((Size, Entry) -> IO ()) -> [(Size, Entry)] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Size, Entry) -> IO ()
printEntry [(Size, Entry)]
ts
    Size
dsize <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
dynamicTableSize
    Size
maxdsize <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
maxDynamicTableSize
    [Char] -> IO ()
putStrLn ([Char] -> IO ()) -> [Char] -> IO ()
forall a b. (a -> b) -> a -> b
$ [Char]
"      Table size: " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Size -> [Char]
forall a. Show a => a -> [Char]
show Size
dsize [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"/" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Size -> [Char]
forall a. Show a => a -> [Char]
show Size
maxdsize

printEntry :: (Index, Entry) -> IO ()
printEntry :: (Size, Entry) -> IO ()
printEntry (Size
i, Entry
e) = do
    [Char] -> IO ()
putStr [Char]
"[ "
    [Char] -> IO ()
putStr ([Char] -> IO ()) -> [Char] -> IO ()
forall a b. (a -> b) -> a -> b
$ Size -> [Char]
forall a. Show a => a -> [Char]
show Size
i
    [Char] -> IO ()
putStr [Char]
"] (s = "
    [Char] -> IO ()
putStr ([Char] -> IO ()) -> [Char] -> IO ()
forall a b. (a -> b) -> a -> b
$ Size -> [Char]
forall a. Show a => a -> [Char]
show (Size -> [Char]) -> Size -> [Char]
forall a b. (a -> b) -> a -> b
$ Entry -> Size
entrySize Entry
e
    [Char] -> IO ()
putStr [Char]
") "
    ByteString -> IO ()
BS.putStr (ByteString -> IO ()) -> ByteString -> IO ()
forall a b. (a -> b) -> a -> b
$ Entry -> ByteString
entryHeaderName Entry
e
    [Char] -> IO ()
putStr [Char]
": "
    ByteString -> IO ()
BS.putStrLn (ByteString -> IO ()) -> ByteString -> IO ()
forall a b. (a -> b) -> a -> b
$ Entry -> ByteString
entryHeaderValue Entry
e

----------------------------------------------------------------

isDynamicTableEmpty :: DynamicTable -> IO Bool
isDynamicTableEmpty :: DynamicTable -> IO Bool
isDynamicTableEmpty DynamicTable{IORef Size
IORef Table
CodeInfo
codeInfo :: DynamicTable -> CodeInfo
circularTable :: DynamicTable -> IORef Table
offset :: DynamicTable -> IORef Size
numOfEntries :: DynamicTable -> IORef Size
maxNumOfEntries :: DynamicTable -> IORef Size
dynamicTableSize :: DynamicTable -> IORef Size
maxDynamicTableSize :: DynamicTable -> IORef Size
codeInfo :: CodeInfo
circularTable :: IORef Table
offset :: IORef Size
numOfEntries :: IORef Size
maxNumOfEntries :: IORef Size
dynamicTableSize :: IORef Size
maxDynamicTableSize :: IORef Size
..} = do
    Size
n <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
numOfEntries
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$ Size
n Size -> Size -> Bool
forall a. Eq a => a -> a -> Bool
== Size
0

isSuitableSize :: Size -> DynamicTable -> IO Bool
isSuitableSize :: Size -> DynamicTable -> IO Bool
isSuitableSize Size
siz DynamicTable{IORef Size
IORef Table
CodeInfo
codeInfo :: DynamicTable -> CodeInfo
circularTable :: DynamicTable -> IORef Table
offset :: DynamicTable -> IORef Size
numOfEntries :: DynamicTable -> IORef Size
maxNumOfEntries :: DynamicTable -> IORef Size
dynamicTableSize :: DynamicTable -> IORef Size
maxDynamicTableSize :: DynamicTable -> IORef Size
codeInfo :: CodeInfo
circularTable :: IORef Table
offset :: IORef Size
numOfEntries :: IORef Size
maxNumOfEntries :: IORef Size
dynamicTableSize :: IORef Size
maxDynamicTableSize :: IORef Size
..} = do
    let DecodeInfo HuffmanDecoder
_ IORef Size
limref = CodeInfo -> DecodeInfo
toDecodeInfo CodeInfo
codeInfo
    Size
lim <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
limref
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$ Size
siz Size -> Size -> Bool
forall a. Ord a => a -> a -> Bool
<= Size
lim

data TableSizeAction = Keep | Change Size | Ignore Size

needChangeTableSize :: DynamicTable -> IO TableSizeAction
needChangeTableSize :: DynamicTable -> IO TableSizeAction
needChangeTableSize DynamicTable{IORef Size
IORef Table
CodeInfo
codeInfo :: DynamicTable -> CodeInfo
circularTable :: DynamicTable -> IORef Table
offset :: DynamicTable -> IORef Size
numOfEntries :: DynamicTable -> IORef Size
maxNumOfEntries :: DynamicTable -> IORef Size
dynamicTableSize :: DynamicTable -> IORef Size
maxDynamicTableSize :: DynamicTable -> IORef Size
codeInfo :: CodeInfo
circularTable :: IORef Table
offset :: IORef Size
numOfEntries :: IORef Size
maxNumOfEntries :: IORef Size
dynamicTableSize :: IORef Size
maxDynamicTableSize :: IORef Size
..} = do
    let EncodeInfo RevIndex
_ IORef (Maybe Size)
limref = CodeInfo -> EncodeInfo
toEncodeInfo CodeInfo
codeInfo
    Maybe Size
mlim <- IORef (Maybe Size) -> IO (Maybe Size)
forall a. IORef a -> IO a
readIORef IORef (Maybe Size)
limref
    Size
maxsiz <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
maxDynamicTableSize
    TableSizeAction -> IO TableSizeAction
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (TableSizeAction -> IO TableSizeAction)
-> TableSizeAction -> IO TableSizeAction
forall a b. (a -> b) -> a -> b
$ case Maybe Size
mlim of
        Maybe Size
Nothing -> TableSizeAction
Keep
        Just Size
lim
            | Size
lim Size -> Size -> Bool
forall a. Ord a => a -> a -> Bool
< Size
maxsiz -> Size -> TableSizeAction
Change Size
lim
            | Bool
otherwise -> Size -> TableSizeAction
Ignore Size
maxsiz

-- | When SETTINGS_HEADER_TABLE_SIZE is received from a peer,
--   its value should be set by this function.
setLimitForEncoding :: Size -> DynamicTable -> IO ()
setLimitForEncoding :: Size -> DynamicTable -> IO ()
setLimitForEncoding Size
siz DynamicTable{IORef Size
IORef Table
CodeInfo
codeInfo :: DynamicTable -> CodeInfo
circularTable :: DynamicTable -> IORef Table
offset :: DynamicTable -> IORef Size
numOfEntries :: DynamicTable -> IORef Size
maxNumOfEntries :: DynamicTable -> IORef Size
dynamicTableSize :: DynamicTable -> IORef Size
maxDynamicTableSize :: DynamicTable -> IORef Size
codeInfo :: CodeInfo
circularTable :: IORef Table
offset :: IORef Size
numOfEntries :: IORef Size
maxNumOfEntries :: IORef Size
dynamicTableSize :: IORef Size
maxDynamicTableSize :: IORef Size
..} = do
    let EncodeInfo RevIndex
_ IORef (Maybe Size)
limref = CodeInfo -> EncodeInfo
toEncodeInfo CodeInfo
codeInfo
    IORef (Maybe Size) -> Maybe Size -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Maybe Size)
limref (Maybe Size -> IO ()) -> Maybe Size -> IO ()
forall a b. (a -> b) -> a -> b
$ Size -> Maybe Size
forall a. a -> Maybe a
Just Size
siz

resetLimitForEncoding :: DynamicTable -> IO ()
resetLimitForEncoding :: DynamicTable -> IO ()
resetLimitForEncoding DynamicTable{IORef Size
IORef Table
CodeInfo
codeInfo :: DynamicTable -> CodeInfo
circularTable :: DynamicTable -> IORef Table
offset :: DynamicTable -> IORef Size
numOfEntries :: DynamicTable -> IORef Size
maxNumOfEntries :: DynamicTable -> IORef Size
dynamicTableSize :: DynamicTable -> IORef Size
maxDynamicTableSize :: DynamicTable -> IORef Size
codeInfo :: CodeInfo
circularTable :: IORef Table
offset :: IORef Size
numOfEntries :: IORef Size
maxNumOfEntries :: IORef Size
dynamicTableSize :: IORef Size
maxDynamicTableSize :: IORef Size
..} = do
    let EncodeInfo RevIndex
_ IORef (Maybe Size)
limref = CodeInfo -> EncodeInfo
toEncodeInfo CodeInfo
codeInfo
    IORef (Maybe Size) -> Maybe Size -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Maybe Size)
limref Maybe Size
forall a. Maybe a
Nothing

----------------------------------------------------------------

-- | Creating 'DynamicTable' for encoding.
newDynamicTableForEncoding
    :: Size
    -- ^ The dynamic table size
    -> IO DynamicTable
newDynamicTableForEncoding :: Size -> IO DynamicTable
newDynamicTableForEncoding Size
maxsiz = do
    RevIndex
rev <- IO RevIndex
newRevIndex
    IORef (Maybe Size)
lim <- Maybe Size -> IO (IORef (Maybe Size))
forall a. a -> IO (IORef a)
newIORef Maybe Size
forall a. Maybe a
Nothing
    let info :: CodeInfo
info = EncodeInfo -> CodeInfo
CIE (EncodeInfo -> CodeInfo) -> EncodeInfo -> CodeInfo
forall a b. (a -> b) -> a -> b
$ RevIndex -> IORef (Maybe Size) -> EncodeInfo
EncodeInfo RevIndex
rev IORef (Maybe Size)
lim
    Size -> CodeInfo -> IO DynamicTable
newDynamicTable Size
maxsiz CodeInfo
info

-- | Creating 'DynamicTable' for decoding.
newDynamicTableForDecoding
    :: Size
    -- ^ The dynamic table size
    -> Size
    -- ^ The size of temporary buffer for Huffman decoding
    -> IO DynamicTable
newDynamicTableForDecoding :: Size -> Size -> IO DynamicTable
newDynamicTableForDecoding Size
maxsiz Size
huftmpsiz = do
    IORef Size
lim <- Size -> IO (IORef Size)
forall a. a -> IO (IORef a)
newIORef Size
maxsiz
    ForeignPtr Word8
buf <- Size -> IO (ForeignPtr Word8)
forall a. Size -> IO (ForeignPtr a)
mallocPlainForeignPtrBytes Size
huftmpsiz
    let decoder :: HuffmanDecoder
decoder = ForeignPtr Word8 -> Size -> HuffmanDecoder
decodeH ForeignPtr Word8
buf Size
huftmpsiz
        info :: CodeInfo
info = DecodeInfo -> CodeInfo
CID (DecodeInfo -> CodeInfo) -> DecodeInfo -> CodeInfo
forall a b. (a -> b) -> a -> b
$ HuffmanDecoder -> IORef Size -> DecodeInfo
DecodeInfo HuffmanDecoder
decoder IORef Size
lim
    Size -> CodeInfo -> IO DynamicTable
newDynamicTable Size
maxsiz CodeInfo
info

newDynamicTable :: Size -> CodeInfo -> IO DynamicTable
newDynamicTable :: Size -> CodeInfo -> IO DynamicTable
newDynamicTable Size
maxsiz CodeInfo
info = do
    Table
tbl <- (Size, Size) -> Entry -> IO Table
forall i. Ix i => (i, i) -> Entry -> IO (IOArray i Entry)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> e -> m (a i e)
newArray (Size
0, Size
end) Entry
dummyEntry
    CodeInfo
-> IORef Table
-> IORef Size
-> IORef Size
-> IORef Size
-> IORef Size
-> IORef Size
-> DynamicTable
DynamicTable CodeInfo
info
        (IORef Table
 -> IORef Size
 -> IORef Size
 -> IORef Size
 -> IORef Size
 -> IORef Size
 -> DynamicTable)
-> IO (IORef Table)
-> IO
     (IORef Size
      -> IORef Size
      -> IORef Size
      -> IORef Size
      -> IORef Size
      -> DynamicTable)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Table -> IO (IORef Table)
forall a. a -> IO (IORef a)
newIORef Table
tbl -- circularTable
        IO
  (IORef Size
   -> IORef Size
   -> IORef Size
   -> IORef Size
   -> IORef Size
   -> DynamicTable)
-> IO (IORef Size)
-> IO
     (IORef Size
      -> IORef Size -> IORef Size -> IORef Size -> DynamicTable)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Size -> IO (IORef Size)
forall a. a -> IO (IORef a)
newIORef Size
end -- offset
        IO
  (IORef Size
   -> IORef Size -> IORef Size -> IORef Size -> DynamicTable)
-> IO (IORef Size)
-> IO (IORef Size -> IORef Size -> IORef Size -> DynamicTable)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Size -> IO (IORef Size)
forall a. a -> IO (IORef a)
newIORef Size
0 -- numOfEntries
        IO (IORef Size -> IORef Size -> IORef Size -> DynamicTable)
-> IO (IORef Size) -> IO (IORef Size -> IORef Size -> DynamicTable)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Size -> IO (IORef Size)
forall a. a -> IO (IORef a)
newIORef Size
maxN -- maxNumOfEntries
        IO (IORef Size -> IORef Size -> DynamicTable)
-> IO (IORef Size) -> IO (IORef Size -> DynamicTable)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Size -> IO (IORef Size)
forall a. a -> IO (IORef a)
newIORef Size
0 -- dynamicTableSize
        IO (IORef Size -> DynamicTable)
-> IO (IORef Size) -> IO DynamicTable
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Size -> IO (IORef Size)
forall a. a -> IO (IORef a)
newIORef Size
maxsiz -- maxDynamicTableSize
  where
    maxN :: Size
maxN = Size -> Size
maxNumbers Size
maxsiz
    end :: Size
end = Size
maxN Size -> Size -> Size
forall a. Num a => a -> a -> a
- Size
1

-- | Renewing 'DynamicTable' with necessary entries copied.
renewDynamicTable :: Size -> DynamicTable -> IO ()
renewDynamicTable :: Size -> DynamicTable -> IO ()
renewDynamicTable Size
maxsiz dyntbl :: DynamicTable
dyntbl@DynamicTable{IORef Size
IORef Table
CodeInfo
codeInfo :: DynamicTable -> CodeInfo
circularTable :: DynamicTable -> IORef Table
offset :: DynamicTable -> IORef Size
numOfEntries :: DynamicTable -> IORef Size
maxNumOfEntries :: DynamicTable -> IORef Size
dynamicTableSize :: DynamicTable -> IORef Size
maxDynamicTableSize :: DynamicTable -> IORef Size
codeInfo :: CodeInfo
circularTable :: IORef Table
offset :: IORef Size
numOfEntries :: IORef Size
maxNumOfEntries :: IORef Size
dynamicTableSize :: IORef Size
maxDynamicTableSize :: IORef Size
..} = do
    Bool
renew <- DynamicTable -> Size -> IO Bool
shouldRenew DynamicTable
dyntbl Size
maxsiz
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
renew (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
        [Entry]
entries <- DynamicTable -> IO [Entry]
getEntries DynamicTable
dyntbl
        let maxN :: Size
maxN = Size -> Size
maxNumbers Size
maxsiz
            end :: Size
end = Size
maxN Size -> Size -> Size
forall a. Num a => a -> a -> a
- Size
1
        Table
newtbl <- (Size, Size) -> Entry -> IO Table
forall i. Ix i => (i, i) -> Entry -> IO (IOArray i Entry)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> e -> m (a i e)
newArray (Size
0, Size
end) Entry
dummyEntry
        IORef Table -> Table -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef Table
circularTable Table
newtbl
        IORef Size -> Size -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef Size
offset Size
end
        IORef Size -> Size -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef Size
numOfEntries Size
0
        IORef Size -> Size -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef Size
maxNumOfEntries Size
maxN
        IORef Size -> Size -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef Size
dynamicTableSize Size
0
        IORef Size -> Size -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef Size
maxDynamicTableSize Size
maxsiz
        case CodeInfo
codeInfo of
            CIE (EncodeInfo RevIndex
rev IORef (Maybe Size)
_) -> RevIndex -> IO ()
renewRevIndex RevIndex
rev
            CodeInfo
_ -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
        DynamicTable -> [Entry] -> IO ()
copyEntries DynamicTable
dyntbl [Entry]
entries

getEntries :: DynamicTable -> IO [Entry]
getEntries :: DynamicTable -> IO [Entry]
getEntries DynamicTable{IORef Size
IORef Table
CodeInfo
codeInfo :: DynamicTable -> CodeInfo
circularTable :: DynamicTable -> IORef Table
offset :: DynamicTable -> IORef Size
numOfEntries :: DynamicTable -> IORef Size
maxNumOfEntries :: DynamicTable -> IORef Size
dynamicTableSize :: DynamicTable -> IORef Size
maxDynamicTableSize :: DynamicTable -> IORef Size
codeInfo :: CodeInfo
circularTable :: IORef Table
offset :: IORef Size
numOfEntries :: IORef Size
maxNumOfEntries :: IORef Size
dynamicTableSize :: IORef Size
maxDynamicTableSize :: IORef Size
..} = do
    Size
maxN <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
maxNumOfEntries
    Size
off <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
offset
    Size
n <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
numOfEntries
    Table
table <- IORef Table -> IO Table
forall a. IORef a -> IO a
readIORef IORef Table
circularTable
    let readTable :: Size -> IO Entry
readTable Size
i = Size -> Size -> IO Size
adj Size
maxN (Size
off Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Size
i) IO Size -> (Size -> IO Entry) -> IO Entry
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Table -> Size -> IO Entry
forall i. Ix i => IOArray i Entry -> Size -> IO Entry
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> Size -> m e
unsafeRead Table
table
    [Size] -> (Size -> IO Entry) -> IO [Entry]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [Size
1 .. Size
n] Size -> IO Entry
readTable

copyEntries :: DynamicTable -> [Entry] -> IO ()
copyEntries :: DynamicTable -> [Entry] -> IO ()
copyEntries DynamicTable
_ [] = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
copyEntries dyntbl :: DynamicTable
dyntbl@DynamicTable{IORef Size
IORef Table
CodeInfo
codeInfo :: DynamicTable -> CodeInfo
circularTable :: DynamicTable -> IORef Table
offset :: DynamicTable -> IORef Size
numOfEntries :: DynamicTable -> IORef Size
maxNumOfEntries :: DynamicTable -> IORef Size
dynamicTableSize :: DynamicTable -> IORef Size
maxDynamicTableSize :: DynamicTable -> IORef Size
codeInfo :: CodeInfo
circularTable :: IORef Table
offset :: IORef Size
numOfEntries :: IORef Size
maxNumOfEntries :: IORef Size
dynamicTableSize :: IORef Size
maxDynamicTableSize :: IORef Size
..} (Entry
e : [Entry]
es) = do
    Size
dsize <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
dynamicTableSize
    Size
maxdsize <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
maxDynamicTableSize
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Size
dsize Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Entry -> Size
entrySize Entry
e Size -> Size -> Bool
forall a. Ord a => a -> a -> Bool
<= Size
maxdsize) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
        Entry -> DynamicTable -> IO ()
insertEnd Entry
e DynamicTable
dyntbl
        DynamicTable -> [Entry] -> IO ()
copyEntries DynamicTable
dyntbl [Entry]
es

-- | Is the size of 'DynamicTable' really changed?
shouldRenew :: DynamicTable -> Size -> IO Bool
shouldRenew :: DynamicTable -> Size -> IO Bool
shouldRenew DynamicTable{IORef Size
IORef Table
CodeInfo
codeInfo :: DynamicTable -> CodeInfo
circularTable :: DynamicTable -> IORef Table
offset :: DynamicTable -> IORef Size
numOfEntries :: DynamicTable -> IORef Size
maxNumOfEntries :: DynamicTable -> IORef Size
dynamicTableSize :: DynamicTable -> IORef Size
maxDynamicTableSize :: DynamicTable -> IORef Size
codeInfo :: CodeInfo
circularTable :: IORef Table
offset :: IORef Size
numOfEntries :: IORef Size
maxNumOfEntries :: IORef Size
dynamicTableSize :: IORef Size
maxDynamicTableSize :: IORef Size
..} Size
maxsiz = do
    Size
maxdsize <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
maxDynamicTableSize
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$ Size
maxdsize Size -> Size -> Bool
forall a. Eq a => a -> a -> Bool
/= Size
maxsiz

----------------------------------------------------------------

-- | Creating 'DynamicTable' for encoding,
--   performing the action and
--   clearing the 'DynamicTable'.
withDynamicTableForEncoding
    :: Size
    -- ^ The dynamic table size
    -> (DynamicTable -> IO a)
    -> IO a
withDynamicTableForEncoding :: forall a. Size -> (DynamicTable -> IO a) -> IO a
withDynamicTableForEncoding Size
maxsiz DynamicTable -> IO a
action =
    Size -> IO DynamicTable
newDynamicTableForEncoding Size
maxsiz IO DynamicTable -> (DynamicTable -> IO a) -> IO a
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= DynamicTable -> IO a
action

-- | Creating 'DynamicTable' for decoding,
--   performing the action and
--   clearing the 'DynamicTable'.
withDynamicTableForDecoding
    :: Size
    -- ^ The dynamic table size
    -> Size
    -- ^ The size of temporary buffer for Huffman
    -> (DynamicTable -> IO a)
    -> IO a
withDynamicTableForDecoding :: forall a. Size -> Size -> (DynamicTable -> IO a) -> IO a
withDynamicTableForDecoding Size
maxsiz Size
huftmpsiz DynamicTable -> IO a
action =
    Size -> Size -> IO DynamicTable
newDynamicTableForDecoding Size
maxsiz Size
huftmpsiz IO DynamicTable -> (DynamicTable -> IO a) -> IO a
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= DynamicTable -> IO a
action

----------------------------------------------------------------

-- | Inserting 'Entry' to 'DynamicTable'.
--   New 'DynamicTable', the largest new 'Index'
--   and a set of dropped OLD 'Index'
--   are returned.
insertEntry :: Entry -> DynamicTable -> IO ()
insertEntry :: Entry -> DynamicTable -> IO ()
insertEntry Entry
e dyntbl :: DynamicTable
dyntbl@DynamicTable{IORef Size
IORef Table
CodeInfo
codeInfo :: DynamicTable -> CodeInfo
circularTable :: DynamicTable -> IORef Table
offset :: DynamicTable -> IORef Size
numOfEntries :: DynamicTable -> IORef Size
maxNumOfEntries :: DynamicTable -> IORef Size
dynamicTableSize :: DynamicTable -> IORef Size
maxDynamicTableSize :: DynamicTable -> IORef Size
codeInfo :: CodeInfo
circularTable :: IORef Table
offset :: IORef Size
numOfEntries :: IORef Size
maxNumOfEntries :: IORef Size
dynamicTableSize :: IORef Size
maxDynamicTableSize :: IORef Size
..} = do
    Entry -> DynamicTable -> IO ()
insertFront Entry
e DynamicTable
dyntbl
    [Entry]
es <- DynamicTable -> IO [Entry]
adjustTableSize DynamicTable
dyntbl
    case CodeInfo
codeInfo of
        CIE (EncodeInfo RevIndex
rev IORef (Maybe Size)
_) -> [Entry] -> RevIndex -> IO ()
deleteRevIndexList [Entry]
es RevIndex
rev
        CodeInfo
_ -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

insertFront :: Entry -> DynamicTable -> IO ()
insertFront :: Entry -> DynamicTable -> IO ()
insertFront Entry
e DynamicTable{IORef Size
IORef Table
CodeInfo
codeInfo :: DynamicTable -> CodeInfo
circularTable :: DynamicTable -> IORef Table
offset :: DynamicTable -> IORef Size
numOfEntries :: DynamicTable -> IORef Size
maxNumOfEntries :: DynamicTable -> IORef Size
dynamicTableSize :: DynamicTable -> IORef Size
maxDynamicTableSize :: DynamicTable -> IORef Size
codeInfo :: CodeInfo
circularTable :: IORef Table
offset :: IORef Size
numOfEntries :: IORef Size
maxNumOfEntries :: IORef Size
dynamicTableSize :: IORef Size
maxDynamicTableSize :: IORef Size
..} = do
    Size
maxN <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
maxNumOfEntries
    Size
off <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
offset
    Size
n <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
numOfEntries
    Size
dsize <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
dynamicTableSize
    Table
table <- IORef Table -> IO Table
forall a. IORef a -> IO a
readIORef IORef Table
circularTable
    let i :: Size
i = Size
off
        dsize' :: Size
dsize' = Size
dsize Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Entry -> Size
entrySize Entry
e
    if Size
maxN Size -> Size -> Bool
forall a. Eq a => a -> a -> Bool
== Size
0
        then () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
        else do
            Size
off' <- Size -> Size -> IO Size
adj Size
maxN (Size
off Size -> Size -> Size
forall a. Num a => a -> a -> a
- Size
1)
            Table -> Size -> Entry -> IO ()
forall i. Ix i => IOArray i Entry -> Size -> Entry -> IO ()
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> Size -> e -> m ()
unsafeWrite Table
table Size
i Entry
e
            IORef Size -> Size -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef Size
offset Size
off'
            IORef Size -> Size -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef Size
numOfEntries (Size -> IO ()) -> Size -> IO ()
forall a b. (a -> b) -> a -> b
$ Size
n Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Size
1
            IORef Size -> Size -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef Size
dynamicTableSize Size
dsize'
            case CodeInfo
codeInfo of
                CIE (EncodeInfo RevIndex
rev IORef (Maybe Size)
_) -> Entry -> HIndex -> RevIndex -> IO ()
insertRevIndex Entry
e (Size -> HIndex
DIndex Size
i) RevIndex
rev
                CodeInfo
_ -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

adjustTableSize :: DynamicTable -> IO [Entry]
adjustTableSize :: DynamicTable -> IO [Entry]
adjustTableSize dyntbl :: DynamicTable
dyntbl@DynamicTable{IORef Size
IORef Table
CodeInfo
codeInfo :: DynamicTable -> CodeInfo
circularTable :: DynamicTable -> IORef Table
offset :: DynamicTable -> IORef Size
numOfEntries :: DynamicTable -> IORef Size
maxNumOfEntries :: DynamicTable -> IORef Size
dynamicTableSize :: DynamicTable -> IORef Size
maxDynamicTableSize :: DynamicTable -> IORef Size
codeInfo :: CodeInfo
circularTable :: IORef Table
offset :: IORef Size
numOfEntries :: IORef Size
maxNumOfEntries :: IORef Size
dynamicTableSize :: IORef Size
maxDynamicTableSize :: IORef Size
..} = [Entry] -> IO [Entry]
adjust []
  where
    adjust :: [Entry] -> IO [Entry]
    adjust :: [Entry] -> IO [Entry]
adjust [Entry]
es = do
        Size
dsize <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
dynamicTableSize
        Size
maxdsize <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
maxDynamicTableSize
        if Size
dsize Size -> Size -> Bool
forall a. Ord a => a -> a -> Bool
<= Size
maxdsize
            then [Entry] -> IO [Entry]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Entry]
es
            else do
                Entry
e <- DynamicTable -> IO Entry
removeEnd DynamicTable
dyntbl
                [Entry] -> IO [Entry]
adjust (Entry
e Entry -> [Entry] -> [Entry]
forall a. a -> [a] -> [a]
: [Entry]
es)

----------------------------------------------------------------

insertEnd :: Entry -> DynamicTable -> IO ()
insertEnd :: Entry -> DynamicTable -> IO ()
insertEnd Entry
e DynamicTable{IORef Size
IORef Table
CodeInfo
codeInfo :: DynamicTable -> CodeInfo
circularTable :: DynamicTable -> IORef Table
offset :: DynamicTable -> IORef Size
numOfEntries :: DynamicTable -> IORef Size
maxNumOfEntries :: DynamicTable -> IORef Size
dynamicTableSize :: DynamicTable -> IORef Size
maxDynamicTableSize :: DynamicTable -> IORef Size
codeInfo :: CodeInfo
circularTable :: IORef Table
offset :: IORef Size
numOfEntries :: IORef Size
maxNumOfEntries :: IORef Size
dynamicTableSize :: IORef Size
maxDynamicTableSize :: IORef Size
..} = do
    Size
maxN <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
maxNumOfEntries
    Size
off <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
offset
    Size
n <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
numOfEntries
    Size
dsize <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
dynamicTableSize
    Table
table <- IORef Table -> IO Table
forall a. IORef a -> IO a
readIORef IORef Table
circularTable
    Size
i <- Size -> Size -> IO Size
adj Size
maxN (Size
off Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Size
n Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Size
1)
    let dsize' :: Size
dsize' = Size
dsize Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Entry -> Size
entrySize Entry
e
    Table -> Size -> Entry -> IO ()
forall i. Ix i => IOArray i Entry -> Size -> Entry -> IO ()
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> Size -> e -> m ()
unsafeWrite Table
table Size
i Entry
e
    IORef Size -> Size -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef Size
numOfEntries (Size -> IO ()) -> Size -> IO ()
forall a b. (a -> b) -> a -> b
$ Size
n Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Size
1
    IORef Size -> Size -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef Size
dynamicTableSize Size
dsize'
    case CodeInfo
codeInfo of
        CIE (EncodeInfo RevIndex
rev IORef (Maybe Size)
_) -> Entry -> HIndex -> RevIndex -> IO ()
insertRevIndex Entry
e (Size -> HIndex
DIndex Size
i) RevIndex
rev
        CodeInfo
_ -> () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

----------------------------------------------------------------

removeEnd :: DynamicTable -> IO Entry
removeEnd :: DynamicTable -> IO Entry
removeEnd DynamicTable{IORef Size
IORef Table
CodeInfo
codeInfo :: DynamicTable -> CodeInfo
circularTable :: DynamicTable -> IORef Table
offset :: DynamicTable -> IORef Size
numOfEntries :: DynamicTable -> IORef Size
maxNumOfEntries :: DynamicTable -> IORef Size
dynamicTableSize :: DynamicTable -> IORef Size
maxDynamicTableSize :: DynamicTable -> IORef Size
codeInfo :: CodeInfo
circularTable :: IORef Table
offset :: IORef Size
numOfEntries :: IORef Size
maxNumOfEntries :: IORef Size
dynamicTableSize :: IORef Size
maxDynamicTableSize :: IORef Size
..} = do
    Size
maxN <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
maxNumOfEntries
    Size
off <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
offset
    Size
n <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
numOfEntries
    Size
i <- Size -> Size -> IO Size
adj Size
maxN (Size
off Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Size
n)
    Table
table <- IORef Table -> IO Table
forall a. IORef a -> IO a
readIORef IORef Table
circularTable
    Entry
e <- Table -> Size -> IO Entry
forall i. Ix i => IOArray i Entry -> Size -> IO Entry
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> Size -> m e
unsafeRead Table
table Size
i
    Table -> Size -> Entry -> IO ()
forall i. Ix i => IOArray i Entry -> Size -> Entry -> IO ()
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> Size -> e -> m ()
unsafeWrite Table
table Size
i Entry
dummyEntry -- let the entry GCed
    Size
dsize <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
dynamicTableSize
    let dsize' :: Size
dsize' = Size
dsize Size -> Size -> Size
forall a. Num a => a -> a -> a
- Entry -> Size
entrySize Entry
e
    IORef Size -> Size -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef Size
numOfEntries (Size
n Size -> Size -> Size
forall a. Num a => a -> a -> a
- Size
1)
    IORef Size -> Size -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef Size
dynamicTableSize Size
dsize'
    Entry -> IO Entry
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Entry
e

----------------------------------------------------------------

{-# INLINE toDynamicEntry #-}
toDynamicEntry :: DynamicTable -> Index -> IO Entry
toDynamicEntry :: DynamicTable -> Size -> IO Entry
toDynamicEntry DynamicTable{IORef Size
IORef Table
CodeInfo
codeInfo :: DynamicTable -> CodeInfo
circularTable :: DynamicTable -> IORef Table
offset :: DynamicTable -> IORef Size
numOfEntries :: DynamicTable -> IORef Size
maxNumOfEntries :: DynamicTable -> IORef Size
dynamicTableSize :: DynamicTable -> IORef Size
maxDynamicTableSize :: DynamicTable -> IORef Size
codeInfo :: CodeInfo
circularTable :: IORef Table
offset :: IORef Size
numOfEntries :: IORef Size
maxNumOfEntries :: IORef Size
dynamicTableSize :: IORef Size
maxDynamicTableSize :: IORef Size
..} Size
idx = do
    Size
maxN <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
maxNumOfEntries
    Size
off <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
offset
    Size
n <- IORef Size -> IO Size
forall a. IORef a -> IO a
readIORef IORef Size
numOfEntries
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Size
idx Size -> Size -> Bool
forall a. Ord a => a -> a -> Bool
> Size
n Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Size
staticTableSize) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ DecodeError -> IO ()
forall e a. Exception e => e -> IO a
throwIO (DecodeError -> IO ()) -> DecodeError -> IO ()
forall a b. (a -> b) -> a -> b
$ Size -> DecodeError
IndexOverrun Size
idx
    Size
didx <- Size -> Size -> IO Size
adj Size
maxN (Size
idx Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Size
off Size -> Size -> Size
forall a. Num a => a -> a -> a
- Size
staticTableSize)
    Table
table <- IORef Table -> IO Table
forall a. IORef a -> IO a
readIORef IORef Table
circularTable
    Table -> Size -> IO Entry
forall i. Ix i => IOArray i Entry -> Size -> IO Entry
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> Size -> m e
unsafeRead Table
table Size
didx

----------------------------------------------------------------

{-# INLINE getRevIndex #-}
getRevIndex :: DynamicTable -> RevIndex
getRevIndex :: DynamicTable -> RevIndex
getRevIndex DynamicTable{IORef Size
IORef Table
CodeInfo
codeInfo :: DynamicTable -> CodeInfo
circularTable :: DynamicTable -> IORef Table
offset :: DynamicTable -> IORef Size
numOfEntries :: DynamicTable -> IORef Size
maxNumOfEntries :: DynamicTable -> IORef Size
dynamicTableSize :: DynamicTable -> IORef Size
maxDynamicTableSize :: DynamicTable -> IORef Size
codeInfo :: CodeInfo
circularTable :: IORef Table
offset :: IORef Size
numOfEntries :: IORef Size
maxNumOfEntries :: IORef Size
dynamicTableSize :: IORef Size
maxDynamicTableSize :: IORef Size
..} = RevIndex
rev
  where
    EncodeInfo RevIndex
rev IORef (Maybe Size)
_ = CodeInfo -> EncodeInfo
toEncodeInfo CodeInfo
codeInfo