{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RankNTypes #-} module Main where import Control.Monad import Data.Binary qualified as Bin import Data.Binary.Get qualified as Bin import Data.Binary.Put qualified as Bin import Data.Bits import Data.ByteString qualified as B import Data.ByteString.Lazy qualified as BL import Data.ByteString.Short qualified as BS import Data.Fixed import Data.Foldable import Data.Int import Data.Map.Strict qualified as Map import Data.Scientific qualified as Sci import Data.Sequence qualified as Seq import Data.Set qualified as Set import Data.Text qualified as T import Data.Text.Encoding qualified as T import Data.Text.Lazy qualified as TL import Data.Text.Lazy.Encoding qualified as TL import Data.Word import GHC.Real import Hedgehog (MonadGen, MonadTest, forAll, property, (/==), (===)) import Hedgehog.Gen qualified as Gen import Hedgehog.Range qualified as Range import Numeric.Natural import Test.Tasty (TestTree, testGroup) import Test.Tasty qualified as Tasty import Test.Tasty.HUnit (Assertion, testCase, (@?=)) import Test.Tasty.Hedgehog (HedgehogTestLimit (..), testProperty) import Test.Tasty.Runners qualified as Tasty import Data.Binary.SLEB128 qualified as S import Data.Binary.ULEB128 qualified as U import Data.Binary.ZLEB128 qualified as Z -------------------------------------------------------------------------------- main :: IO () main = Tasty.defaultMainWithIngredients [Tasty.consoleTestReporter, Tasty.listingTests] $ Tasty.localOption (HedgehogTestLimit (Just 10000)) tt tt :: TestTree tt = testGroup "leb128-binary" [ tt_ZigZag , tt_ULEB128 , tt_ZLEB128 , tt_SLEB128 , tt_SLEB128_Scientific , tt_SLEB128_Rational ] tt_ZigZag :: TestTree tt_ZigZag = testGroup "ZigZag" [ testGroup "Round trip" [ testProperty "ZigZag(ZagZig(x))" $ property $ do n <- forAll $ Gen.integral rangeNatural512 n === zigZag (zagZig n) , testProperty "ZagZig(ZigZag(x))" $ property $ do i <- forAll $ Gen.integral rangeInteger512 i === zagZig (zigZag i) ] , testGroup "Not identity" [ testProperty "ZagZig" $ property $ do n <- forAll $ Gen.integral rangeNatural512 toInteger n /== zagZig n , testProperty "ZagZig" $ property $ do i <- forAll $ Gen.integral rangeInteger512 i /== toInteger (zigZag i) ] , testGroup "Known" [ testCase "0" $ zigZag 0 @?= 0 , testCase "1" $ zigZag 1 @?= 2 , testCase "2" $ zigZag 2 @?= 4 , testCase "127" $ zigZag 127 @?= 254 , testCase "32767" $ zigZag 32767 @?= 65534 , testCase "2147483647" $ zigZag 2147483647 @?= 4294967294 , testCase "9223372036854775807" $ zigZag 9223372036854775807 @?= 18446744073709551614 , testCase "170141183460469231731687303715884105727" $ zigZag 170141183460469231731687303715884105727 @?= 340282366920938463463374607431768211454 , testCase "111111111111111111111111111111111111111111" $ zigZag 111111111111111111111111111111111111111111 @?= 222222222222222222222222222222222222222222 , testCase "-1" $ zigZag (-1) @?= 1 , testCase "-2" $ zigZag (-2) @?= 3 , testCase "-127" $ zigZag (-127) @?= 253 , testCase "-128" $ zigZag (-128) @?= 255 , testCase "-32767" $ zigZag (-32767) @?= 65533 , testCase "-32768" $ zigZag (-32768) @?= 65535 , testCase "-2147483647" $ zigZag (-2147483647) @?= 4294967293 , testCase "-2147483648" $ zigZag (-2147483648) @?= 4294967295 , testCase "-9223372036854775808" $ zigZag (-9223372036854775808) @?= 18446744073709551615 , testCase "-9223372036854775807" $ zigZag (-9223372036854775807) @?= 18446744073709551613 , testCase "-170141183460469231731687303715884105728" $ zigZag (-170141183460469231731687303715884105728) @?= 340282366920938463463374607431768211455 , testCase "-170141183460469231731687303715884105727" $ zigZag (-170141183460469231731687303715884105727) @?= 340282366920938463463374607431768211453 , testCase "-111111111111111111111111111111111111111111" $ zigZag (-111111111111111111111111111111111111111111) @?= 222222222222222222222222222222222222222221 , testCase "-111111111111111111111111111111111111111112" $ zigZag (-111111111111111111111111111111111111111112) @?= 222222222222222222222222222222222222222223 ] ] tt_ZLEB128 :: TestTree tt_ZLEB128 = testGroup "ZLEB128" [ testGroup "Round trip" [ testProperty "putInt" $ property $ do n <- forAll $ Gen.integral Range.constantBounded Right n === dec Z.getInt (enc (Z.putInt n)) , testProperty "putInt8" $ property $ do n <- forAll $ Gen.integral Range.constantBounded Right n === dec Z.getInt8 (enc (Z.putInt8 n)) , testProperty "putInt16" $ property $ do n <- forAll $ Gen.integral Range.constantBounded Right n === dec Z.getInt16 (enc (Z.putInt16 n)) , testProperty "putInt32" $ property $ do n <- forAll $ Gen.integral Range.constantBounded Right n === dec Z.getInt32 (enc (Z.putInt32 n)) , testProperty "putInt64" $ property $ do n <- forAll $ Gen.integral Range.constantBounded Right n === dec Z.getInt64 (enc (Z.putInt64 n)) , testProperty "putWord" $ property $ do n <- forAll $ Gen.integral Range.constantBounded Right n === dec Z.getWord (enc (Z.putWord n)) , testProperty "putWord8" $ property $ do n <- forAll $ Gen.integral Range.constantBounded Right n === dec Z.getWord8 (enc (Z.putWord8 n)) , testProperty "putWord16" $ property $ do n <- forAll $ Gen.integral Range.constantBounded Right n === dec Z.getWord16 (enc (Z.putWord16 n)) , testProperty "putWord32" $ property $ do n <- forAll $ Gen.integral Range.constantBounded Right n === dec Z.getWord32 (enc (Z.putWord32 n)) , testProperty "putWord64" $ property $ do n <- forAll $ Gen.integral Range.constantBounded Right n === dec Z.getWord64 (enc (Z.putWord64 n)) , testProperty "putNatural" $ property $ do n <- forAll $ Gen.integral rangeNatural512 Right n === dec (Z.getNatural 74) (enc (Z.putNatural n)) , testProperty "putInteger" $ property $ do n <- forAll $ Gen.integral rangeInteger512 Right n === dec (Z.getInteger 74) (enc (Z.putInteger n)) ] , testGroup "unZLEB128(ULEB128(ZigZag(x))))" [ testProperty "putInt" $ property $ do n <- forAll $ Gen.integral Range.constantBounded Right n === dec Z.getInt (enc (U.putNatural (zigZag (toInteger n)))) , testProperty "putInt8" $ property $ do n <- forAll $ Gen.integral Range.constantBounded Right n === dec Z.getInt8 (enc (U.putNatural (zigZag (toInteger n)))) , testProperty "putInt16" $ property $ do n <- forAll $ Gen.integral Range.constantBounded Right n === dec Z.getInt16 (enc (U.putNatural (zigZag (toInteger n)))) , testProperty "putInt32" $ property $ do n <- forAll $ Gen.integral Range.constantBounded Right n === dec Z.getInt32 (enc (U.putNatural (zigZag (toInteger n)))) , testProperty "putInt64" $ property $ do n <- forAll $ Gen.integral Range.constantBounded Right n === dec Z.getInt64 (enc (U.putNatural (zigZag (toInteger n)))) , testProperty "putWord" $ property $ do n <- forAll $ Gen.integral Range.constantBounded Right n === dec Z.getWord (enc (U.putNatural (zigZag (toInteger n)))) , testProperty "putWord8" $ property $ do n <- forAll $ Gen.integral Range.constantBounded Right n === dec Z.getWord8 (enc (U.putNatural (zigZag (toInteger n)))) , testProperty "putWord16" $ property $ do n <- forAll $ Gen.integral Range.constantBounded Right n === dec Z.getWord16 (enc (U.putNatural (zigZag (toInteger n)))) , testProperty "putWord32" $ property $ do n <- forAll $ Gen.integral Range.constantBounded Right n === dec Z.getWord32 (enc (U.putNatural (zigZag (toInteger n)))) , testProperty "putWord64" $ property $ do n <- forAll $ Gen.integral Range.constantBounded Right n === dec Z.getWord64 (enc (U.putNatural (zigZag (toInteger n)))) , testProperty "putNatural" $ property $ do n <- forAll $ Gen.integral rangeNatural512 Right n === dec (Z.getNatural 74) (enc (U.putNatural (zigZag (toInteger n)))) , testProperty "putInteger" $ property $ do n <- forAll $ Gen.integral rangeInteger512 Right n === dec (Z.getInteger 74) (enc (U.putNatural (zigZag n))) ] , testGroup "ZigZag(unULEB128(ZLEB128(x)))" [ testProperty "putInt" $ property $ do n <- forAll $ Gen.integral Range.constantBounded Right (Just n) === dec (fmap (toIntegralSized . zagZig) (U.getNatural 10)) (enc (Z.putInt n)) , testProperty "putInt8" $ property $ do n <- forAll $ Gen.integral Range.constantBounded Right (Just n) === dec (fmap (toIntegralSized . zagZig) (U.getNatural 2)) (enc (Z.putInt8 n)) , testProperty "putInt16" $ property $ do n <- forAll $ Gen.integral Range.constantBounded Right (Just n) === dec (fmap (toIntegralSized . zagZig) (U.getNatural 3)) (enc (Z.putInt16 n)) , testProperty "putInt32" $ property $ do n <- forAll $ Gen.integral Range.constantBounded Right (Just n) === dec (fmap (toIntegralSized . zagZig) (U.getNatural 5)) (enc (Z.putInt32 n)) , testProperty "putInt64" $ property $ do n <- forAll $ Gen.integral Range.constantBounded Right (Just n) === dec (fmap (toIntegralSized . zagZig) (U.getNatural 10)) (enc (Z.putInt64 n)) , testProperty "putWord" $ property $ do n <- forAll $ Gen.integral Range.constantBounded Right (Just n) === dec (fmap (toIntegralSized . zagZig) (U.getNatural 10)) (enc (Z.putWord n)) , testProperty "putWord8" $ property $ do n <- forAll $ Gen.integral Range.constantBounded Right (Just n) === dec (fmap (toIntegralSized . zagZig) (U.getNatural 2)) (enc (Z.putWord8 n)) , testProperty "putWord16" $ property $ do n <- forAll $ Gen.integral Range.constantBounded Right (Just n) === dec (fmap (toIntegralSized . zagZig) (U.getNatural 3)) (enc (Z.putWord16 n)) , testProperty "putWord32" $ property $ do n <- forAll $ Gen.integral Range.constantBounded Right (Just n) === dec (fmap (toIntegralSized . zagZig) (U.getNatural 5)) (enc (Z.putWord32 n)) , testProperty "putWord64" $ property $ do n <- forAll $ Gen.integral Range.constantBounded Right (Just n) === dec (fmap (toIntegralSized . zagZig) (U.getNatural 10)) (enc (Z.putWord64 n)) , testProperty "putNatural" $ property $ do n <- forAll $ Gen.integral rangeNatural512 Right (Just n) === dec (fmap (toIntegralSized . zagZig) (U.getNatural 74)) (enc (Z.putNatural n)) , testProperty "putInteger" $ property $ do n <- forAll $ Gen.integral rangeInteger512 Right (Just n) === dec (fmap (toIntegralSized . zagZig) (U.getNatural 74)) (enc (Z.putInteger n)) ] ] tt_ULEB128 :: TestTree tt_ULEB128 = testGroup "ULEB128" [ testGroup "Too big" [ testCase "0, 0" $ dec (U.getNatural 0) "" @?= Left "input exceeds maximum allowed bytes\nULEB128" , testCase "0, 1" $ dec (U.getNatural 0) "\x00" @?= Left "input exceeds maximum allowed bytes\nULEB128" , testCase "0, 1.5" $ dec (U.getNatural 0) "\x80" @?= Left "input exceeds maximum allowed bytes\nULEB128" , testCase "1, 1.5" $ dec (U.getNatural 1) "\x80" @?= Left "input exceeds maximum allowed bytes\nULEB128" , testCase "1, 2" $ dec (U.getNatural 1) "\x80\x01" @?= Left "input exceeds maximum allowed bytes\nULEB128" , testCase "1, 3" $ dec (U.getNatural 1) "\xfd\x82\x01" @?= Left "input exceeds maximum allowed bytes\nULEB128" , testCase "2, 3" $ dec (U.getNatural 2) "\xfd\x82\x01" @?= Left "input exceeds maximum allowed bytes\nULEB128" ] , testGroup "Known" [ tt_ULEB128_known 0 "\x00" , tt_ULEB128_known 1 "\x01" , tt_ULEB128_known 6 "\x06" , tt_ULEB128_known 125 "\x7d" , tt_ULEB128_known 127 "\x7f" , tt_ULEB128_known 128 "\x80\x01" , tt_ULEB128_known 129 "\x81\x01" , tt_ULEB128_known 255 "\xff\x01" , tt_ULEB128_known 256 "\x80\x02" , tt_ULEB128_known 257 "\x81\x02" , tt_ULEB128_known 417 "\xa1\x03" , tt_ULEB128_known 670 "\x9e\x05" , tt_ULEB128_known 949 "\xb5\x07" , tt_ULEB128_known 1325 "\xad\x0a" , tt_ULEB128_known 1469 "\xbd\x0b" , tt_ULEB128_known 1860 "\xc4\x0e" , tt_ULEB128_known 1869 "\xcd\x0e" , tt_ULEB128_known 2316 "\x8c\x12" , tt_ULEB128_known 2765 "\xcd\x15" , tt_ULEB128_known 2842 "\x9a\x16" , tt_ULEB128_known 2994 "\xb2\x17" , tt_ULEB128_known 2995 "\xb3\x17" , tt_ULEB128_known 3178 "\xea\x18" , tt_ULEB128_known 3309 "\xed\x19" , tt_ULEB128_known 3723 "\x8b\x1d" , tt_ULEB128_known 3842 "\x82\x1e" , tt_ULEB128_known 4000 "\xa0\x1f" , tt_ULEB128_known 4101 "\x85\x20" , tt_ULEB128_known 4690 "\xd2\x24" , tt_ULEB128_known 4745 "\x89\x25" , tt_ULEB128_known 4892 "\x9c\x26" , tt_ULEB128_known 4932 "\xc4\x26" , tt_ULEB128_known 5181 "\xbd\x28" , tt_ULEB128_known 5723 "\xdb\x2c" , tt_ULEB128_known 6346 "\xca\x31" , tt_ULEB128_known 6416 "\x90\x32" , tt_ULEB128_known 6647 "\xf7\x33" , tt_ULEB128_known 6936 "\x98\x36" , tt_ULEB128_known 7074 "\xa2\x37" , tt_ULEB128_known 7409 "\xf1\x39" , tt_ULEB128_known 7492 "\xc4\x3a" , tt_ULEB128_known 7663 "\xef\x3b" , tt_ULEB128_known 8325 "\x85\x41" , tt_ULEB128_known 8585 "\x89\x43" , tt_ULEB128_known 8640 "\xc0\x43" , tt_ULEB128_known 8750 "\xae\x44" , tt_ULEB128_known 9014 "\xb6\x46" , tt_ULEB128_known 9220 "\x84\x48" , tt_ULEB128_known 9471 "\xff\x49" , tt_ULEB128_known 10256 "\x90\x50" , tt_ULEB128_known 10515 "\x93\x52" , tt_ULEB128_known 10697 "\xc9\x53" , tt_ULEB128_known 11413 "\x95\x59" , tt_ULEB128_known 11477 "\xd5\x59" , tt_ULEB128_known 11718 "\xc6\x5b" , tt_ULEB128_known 12035 "\x83\x5e" , tt_ULEB128_known 12136 "\xe8\x5e" , tt_ULEB128_known 12568 "\x98\x62" , tt_ULEB128_known 13026 "\xe2\x65" , tt_ULEB128_known 13054 "\xfe\x65" , tt_ULEB128_known 13508 "\xc4\x69" , tt_ULEB128_known 14012 "\xbc\x6d" , tt_ULEB128_known 14134 "\xb6\x6e" , tt_ULEB128_known 14713 "\xf9\x72" , tt_ULEB128_known 14744 "\x98\x73" , tt_ULEB128_known 15248 "\x90\x77" , tt_ULEB128_known 15436 "\xcc\x78" , tt_ULEB128_known 15638 "\x96\x7a" , tt_ULEB128_known 15674 "\xba\x7a" , tt_ULEB128_known 15937 "\xc1\x7c" , tt_ULEB128_known 16493 "\xed\x80\x01" , tt_ULEB128_known 16508 "\xfc\x80\x01" , tt_ULEB128_known 17033 "\x89\x85\x01" , tt_ULEB128_known 17383 "\xe7\x87\x01" , tt_ULEB128_known 17469 "\xbd\x88\x01" , tt_ULEB128_known 17684 "\x94\x8a\x01" , tt_ULEB128_known 17814 "\x96\x8b\x01" , tt_ULEB128_known 18370 "\xc2\x8f\x01" , tt_ULEB128_known 18538 "\xea\x90\x01" , tt_ULEB128_known 18918 "\xe6\x93\x01" , tt_ULEB128_known 18953 "\x89\x94\x01" , tt_ULEB128_known 19096 "\x98\x95\x01" , tt_ULEB128_known 19257 "\xb9\x96\x01" , tt_ULEB128_known 19303 "\xe7\x96\x01" , tt_ULEB128_known 19810 "\xe2\x9a\x01" , tt_ULEB128_known 19926 "\xd6\x9b\x01" , tt_ULEB128_known 20130 "\xa2\x9d\x01" , tt_ULEB128_known 21056 "\xc0\xa4\x01" , tt_ULEB128_known 21131 "\x8b\xa5\x01" , tt_ULEB128_known 21287 "\xa7\xa6\x01" , tt_ULEB128_known 21858 "\xe2\xaa\x01" , tt_ULEB128_known 22147 "\x83\xad\x01" , tt_ULEB128_known 22273 "\x81\xae\x01" , tt_ULEB128_known 22492 "\xdc\xaf\x01" , tt_ULEB128_known 22804 "\x94\xb2\x01" , tt_ULEB128_known 23342 "\xae\xb6\x01" , tt_ULEB128_known 23481 "\xb9\xb7\x01" , tt_ULEB128_known 23997 "\xbd\xbb\x01" , tt_ULEB128_known 24528 "\xd0\xbf\x01" , tt_ULEB128_known 24645 "\xc5\xc0\x01" , tt_ULEB128_known 25070 "\xee\xc3\x01" , tt_ULEB128_known 26661 "\xa5\xd0\x01" , tt_ULEB128_known 26673 "\xb1\xd0\x01" , tt_ULEB128_known 27427 "\xa3\xd6\x01" , tt_ULEB128_known 27684 "\xa4\xd8\x01" , tt_ULEB128_known 28569 "\x99\xdf\x01" , tt_ULEB128_known 28982 "\xb6\xe2\x01" , tt_ULEB128_known 29119 "\xbf\xe3\x01" , tt_ULEB128_known 29215 "\x9f\xe4\x01" , tt_ULEB128_known 29290 "\xea\xe4\x01" , tt_ULEB128_known 29383 "\xc7\xe5\x01" , tt_ULEB128_known 29944 "\xf8\xe9\x01" , tt_ULEB128_known 29969 "\x91\xea\x01" , tt_ULEB128_known 30328 "\xf8\xec\x01" , tt_ULEB128_known 30684 "\xdc\xef\x01" , tt_ULEB128_known 30720 "\x80\xf0\x01" , tt_ULEB128_known 31070 "\xde\xf2\x01" , tt_ULEB128_known 31846 "\xe6\xf8\x01" , tt_ULEB128_known 31905 "\xa1\xf9\x01" , tt_ULEB128_known 31907 "\xa3\xf9\x01" , tt_ULEB128_known 32143 "\x8f\xfb\x01" , tt_ULEB128_known 32369 "\xf1\xfc\x01" , tt_ULEB128_known 32436 "\xb4\xfd\x01" , tt_ULEB128_known 32715 "\xcb\xff\x01" , tt_ULEB128_known 32768 "\x80\x80\x02" , tt_ULEB128_known 32957 "\xbd\x81\x02" , tt_ULEB128_known 33215 "\xbf\x83\x02" , tt_ULEB128_known 33359 "\xcf\x84\x02" , tt_ULEB128_known 33438 "\x9e\x85\x02" , tt_ULEB128_known 33671 "\x87\x87\x02" , tt_ULEB128_known 33674 "\x8a\x87\x02" , tt_ULEB128_known 33749 "\xd5\x87\x02" , tt_ULEB128_known 33806 "\x8e\x88\x02" , tt_ULEB128_known 33938 "\x92\x89\x02" , tt_ULEB128_known 34042 "\xfa\x89\x02" , tt_ULEB128_known 34636 "\xcc\x8e\x02" , tt_ULEB128_known 35058 "\xf2\x91\x02" , tt_ULEB128_known 35077 "\x85\x92\x02" , tt_ULEB128_known 35229 "\x9d\x93\x02" , tt_ULEB128_known 35356 "\x9c\x94\x02" , tt_ULEB128_known 35514 "\xba\x95\x02" , tt_ULEB128_known 35572 "\xf4\x95\x02" , tt_ULEB128_known 35650 "\xc2\x96\x02" , tt_ULEB128_known 36807 "\xc7\x9f\x02" , tt_ULEB128_known 37064 "\xc8\xa1\x02" , tt_ULEB128_known 37202 "\xd2\xa2\x02" , tt_ULEB128_known 37498 "\xfa\xa4\x02" , tt_ULEB128_known 37589 "\xd5\xa5\x02" , tt_ULEB128_known 37710 "\xce\xa6\x02" , tt_ULEB128_known 37899 "\x8b\xa8\x02" , tt_ULEB128_known 38184 "\xa8\xaa\x02" , tt_ULEB128_known 38328 "\xb8\xab\x02" , tt_ULEB128_known 38948 "\xa4\xb0\x02" , tt_ULEB128_known 39149 "\xed\xb1\x02" , tt_ULEB128_known 39346 "\xb2\xb3\x02" , tt_ULEB128_known 39709 "\x9d\xb6\x02" , tt_ULEB128_known 39871 "\xbf\xb7\x02" , tt_ULEB128_known 39951 "\x8f\xb8\x02" , tt_ULEB128_known 40033 "\xe1\xb8\x02" , tt_ULEB128_known 40078 "\x8e\xb9\x02" , tt_ULEB128_known 40159 "\xdf\xb9\x02" , tt_ULEB128_known 40388 "\xc4\xbb\x02" , tt_ULEB128_known 40710 "\x86\xbe\x02" , tt_ULEB128_known 40782 "\xce\xbe\x02" , tt_ULEB128_known 41247 "\x9f\xc2\x02" , tt_ULEB128_known 41853 "\xfd\xc6\x02" , tt_ULEB128_known 42127 "\x8f\xc9\x02" , tt_ULEB128_known 42371 "\x83\xcb\x02" , tt_ULEB128_known 42714 "\xda\xcd\x02" , tt_ULEB128_known 43060 "\xb4\xd0\x02" , tt_ULEB128_known 43084 "\xcc\xd0\x02" , tt_ULEB128_known 43300 "\xa4\xd2\x02" , tt_ULEB128_known 43338 "\xca\xd2\x02" , tt_ULEB128_known 43930 "\x9a\xd7\x02" , tt_ULEB128_known 43942 "\xa6\xd7\x02" , tt_ULEB128_known 44189 "\x9d\xd9\x02" , tt_ULEB128_known 44381 "\xdd\xda\x02" , tt_ULEB128_known 44414 "\xfe\xda\x02" , tt_ULEB128_known 44510 "\xde\xdb\x02" , tt_ULEB128_known 44949 "\x95\xdf\x02" , tt_ULEB128_known 45100 "\xac\xe0\x02" , tt_ULEB128_known 45345 "\xa1\xe2\x02" , tt_ULEB128_known 45378 "\xc2\xe2\x02" , tt_ULEB128_known 45732 "\xa4\xe5\x02" , tt_ULEB128_known 45867 "\xab\xe6\x02" , tt_ULEB128_known 46111 "\x9f\xe8\x02" , tt_ULEB128_known 46337 "\x81\xea\x02" , tt_ULEB128_known 46769 "\xb1\xed\x02" , tt_ULEB128_known 46918 "\xc6\xee\x02" , tt_ULEB128_known 47501 "\x8d\xf3\x02" , tt_ULEB128_known 47545 "\xb9\xf3\x02" , tt_ULEB128_known 47662 "\xae\xf4\x02" , tt_ULEB128_known 47673 "\xb9\xf4\x02" , tt_ULEB128_known 47819 "\xcb\xf5\x02" , tt_ULEB128_known 48388 "\x84\xfa\x02" , tt_ULEB128_known 48432 "\xb0\xfa\x02" , tt_ULEB128_known 49063 "\xa7\xff\x02" , tt_ULEB128_known 49084 "\xbc\xff\x02" , tt_ULEB128_known 50004 "\xd4\x86\x03" , tt_ULEB128_known 50456 "\x98\x8a\x03" , tt_ULEB128_known 50918 "\xe6\x8d\x03" , tt_ULEB128_known 50940 "\xfc\x8d\x03" , tt_ULEB128_known 52310 "\xd6\x98\x03" , tt_ULEB128_known 52832 "\xe0\x9c\x03" , tt_ULEB128_known 53006 "\x8e\x9e\x03" , tt_ULEB128_known 53514 "\x8a\xa2\x03" , tt_ULEB128_known 53644 "\x8c\xa3\x03" , tt_ULEB128_known 53800 "\xa8\xa4\x03" , tt_ULEB128_known 54057 "\xa9\xa6\x03" , tt_ULEB128_known 54230 "\xd6\xa7\x03" , tt_ULEB128_known 54315 "\xab\xa8\x03" , tt_ULEB128_known 54743 "\xd7\xab\x03" , tt_ULEB128_known 55193 "\x99\xaf\x03" , tt_ULEB128_known 55219 "\xb3\xaf\x03" , tt_ULEB128_known 55375 "\xcf\xb0\x03" , tt_ULEB128_known 55376 "\xd0\xb0\x03" , tt_ULEB128_known 55492 "\xc4\xb1\x03" , tt_ULEB128_known 55732 "\xb4\xb3\x03" , tt_ULEB128_known 55875 "\xc3\xb4\x03" , tt_ULEB128_known 56084 "\x94\xb6\x03" , tt_ULEB128_known 56098 "\xa2\xb6\x03" , tt_ULEB128_known 56131 "\xc3\xb6\x03" , tt_ULEB128_known 56207 "\x8f\xb7\x03" , tt_ULEB128_known 56226 "\xa2\xb7\x03" , tt_ULEB128_known 56451 "\x83\xb9\x03" , tt_ULEB128_known 56941 "\xed\xbc\x03" , tt_ULEB128_known 57066 "\xea\xbd\x03" , tt_ULEB128_known 57261 "\xad\xbf\x03" , tt_ULEB128_known 57378 "\xa2\xc0\x03" , tt_ULEB128_known 57990 "\x86\xc5\x03" , tt_ULEB128_known 58289 "\xb1\xc7\x03" , tt_ULEB128_known 58457 "\xd9\xc8\x03" , tt_ULEB128_known 58497 "\x81\xc9\x03" , tt_ULEB128_known 58562 "\xc2\xc9\x03" , tt_ULEB128_known 58679 "\xb7\xca\x03" , tt_ULEB128_known 58680 "\xb8\xca\x03" , tt_ULEB128_known 58965 "\xd5\xcc\x03" , tt_ULEB128_known 59138 "\x82\xce\x03" , tt_ULEB128_known 59169 "\xa1\xce\x03" , tt_ULEB128_known 59441 "\xb1\xd0\x03" , tt_ULEB128_known 59480 "\xd8\xd0\x03" , tt_ULEB128_known 59649 "\x81\xd2\x03" , tt_ULEB128_known 60020 "\xf4\xd4\x03" , tt_ULEB128_known 60135 "\xe7\xd5\x03" , tt_ULEB128_known 60236 "\xcc\xd6\x03" , tt_ULEB128_known 60244 "\xd4\xd6\x03" , tt_ULEB128_known 60566 "\x96\xd9\x03" , tt_ULEB128_known 60998 "\xc6\xdc\x03" , tt_ULEB128_known 61490 "\xb2\xe0\x03" , tt_ULEB128_known 61495 "\xb7\xe0\x03" , tt_ULEB128_known 61840 "\x90\xe3\x03" , tt_ULEB128_known 62036 "\xd4\xe4\x03" , tt_ULEB128_known 62082 "\x82\xe5\x03" , tt_ULEB128_known 62223 "\x8f\xe6\x03" , tt_ULEB128_known 62946 "\xe2\xeb\x03" , tt_ULEB128_known 63475 "\xf3\xef\x03" , tt_ULEB128_known 63591 "\xe7\xf0\x03" , tt_ULEB128_known 63646 "\x9e\xf1\x03" , tt_ULEB128_known 64203 "\xcb\xf5\x03" , tt_ULEB128_known 64278 "\x96\xf6\x03" , tt_ULEB128_known 64439 "\xb7\xf7\x03" , tt_ULEB128_known 64493 "\xed\xf7\x03" , tt_ULEB128_known 64517 "\x85\xf8\x03" , tt_ULEB128_known 64900 "\x84\xfb\x03" , tt_ULEB128_known 65376 "\xe0\xfe\x03" , tt_ULEB128_known 65522 "\xf2\xff\x03" , tt_ULEB128_known 7424679 "\xa7\x95\xc5\x03" , tt_ULEB128_known 14100549 "\xc5\xd0\xdc\x06" , tt_ULEB128_known 68235555 "\xa3\xe2\xc4\x20" , tt_ULEB128_known 69098825 "\xc9\xba\xf9\x20" , tt_ULEB128_known 75674906 "\x9a\xea\x8a\x24" , tt_ULEB128_known 91177824 "\xe0\x86\xbd\x2b" , tt_ULEB128_known 153954905 "\xd9\xd4\xb4\x49" , tt_ULEB128_known 185527771 "\xdb\xdb\xbb\x58" , tt_ULEB128_known 220020303 "\xcf\xfc\xf4\x68" , tt_ULEB128_known 248856297 "\xe9\xfd\xd4\x76" , tt_ULEB128_known 263450205 "\xdd\xdc\xcf\x7d" , tt_ULEB128_known 275512216 "\x98\xf7\xaf\x83\x01" , tt_ULEB128_known 282020545 "\xc1\x95\xbd\x86\x01" , tt_ULEB128_known 297510487 "\xd7\xcc\xee\x8d\x01" , tt_ULEB128_known 331228009 "\xe9\xc6\xf8\x9d\x01" , tt_ULEB128_known 338637064 "\x88\xe2\xbc\xa1\x01" , tt_ULEB128_known 340593328 "\xb0\x95\xb4\xa2\x01" , tt_ULEB128_known 378543011 "\xa3\xb7\xc0\xb4\x01" , tt_ULEB128_known 383008357 "\xe5\xfc\xd0\xb6\x01" , tt_ULEB128_known 441168468 "\xd4\xe4\xae\xd2\x01" , tt_ULEB128_known 497717516 "\x8c\xa2\xaa\xed\x01" , tt_ULEB128_known 499253479 "\xe7\x81\x88\xee\x01" , tt_ULEB128_known 509345770 "\xea\xff\xef\xf2\x01" , tt_ULEB128_known 516942760 "\xa8\xd7\xbf\xf6\x01" , tt_ULEB128_known 524622237 "\x9d\xb3\x94\xfa\x01" , tt_ULEB128_known 539765297 "\xb1\xd4\xb0\x81\x02" , tt_ULEB128_known 603936895 "\xff\xb0\xfd\x9f\x02" , tt_ULEB128_known 632925525 "\xd5\xda\xe6\xad\x02" , tt_ULEB128_known 639957245 "\xfd\xf1\x93\xb1\x02" , tt_ULEB128_known 672284862 "\xbe\x81\xc9\xc0\x02" , tt_ULEB128_known 693267104 "\xa0\xd5\xc9\xca\x02" , tt_ULEB128_known 707821343 "\x9f\xfe\xc1\xd1\x02" , tt_ULEB128_known 710236774 "\xe6\xb4\xd5\xd2\x02" , tt_ULEB128_known 719183242 "\x8a\xbb\xf7\xd6\x02" , tt_ULEB128_known 732240829 "\xbd\xb7\x94\xdd\x02" , tt_ULEB128_known 742113873 "\xd1\x84\xef\xe1\x02" , tt_ULEB128_known 749077709 "\xcd\x89\x98\xe5\x02" , tt_ULEB128_known 780774180 "\xa4\xd6\xa6\xf4\x02" , tt_ULEB128_known 781087442 "\xd2\xe5\xb9\xf4\x02" , tt_ULEB128_known 790485926 "\xa6\xb7\xf7\xf8\x02" , tt_ULEB128_known 800833378 "\xe2\xfe\xee\xfd\x02" , tt_ULEB128_known 805343149 "\xad\x9f\x82\x80\x03" , tt_ULEB128_known 806936703 "\xff\xc0\xe3\x80\x03" , tt_ULEB128_known 813712125 "\xfd\x85\x81\x84\x03" , tt_ULEB128_known 830853841 "\xd1\xa5\x97\x8c\x03" , tt_ULEB128_known 837811858 "\x92\xfd\xbf\x8f\x03" , tt_ULEB128_known 845785612 "\x8c\xd4\xa6\x93\x03" , tt_ULEB128_known 869729327 "\xaf\x88\xdc\x9e\x03" , tt_ULEB128_known 875381905 "\x91\x89\xb5\xa1\x03" , tt_ULEB128_known 913118848 "\x80\xad\xb4\xb3\x03" , tt_ULEB128_known 922694503 "\xe7\xe6\xfc\xb7\x03" , tt_ULEB128_known 932838607 "\xcf\xf9\xe7\xbc\x03" , tt_ULEB128_known 961912600 "\x98\xbe\xd6\xca\x03" , tt_ULEB128_known 965674411 "\xab\x8b\xbc\xcc\x03" , tt_ULEB128_known 969765839 "\xcf\xe7\xb5\xce\x03" , tt_ULEB128_known 999371334 "\xc6\xe4\xc4\xdc\x03" , tt_ULEB128_known 1009980302 "\x8e\xa7\xcc\xe1\x03" , tt_ULEB128_known 1039207051 "\x8b\x95\xc4\xef\x03" , tt_ULEB128_known 1050278887 "\xe7\xf7\xe7\xf4\x03" , tt_ULEB128_known 1053226166 "\xb6\xe9\x9b\xf6\x03" , tt_ULEB128_known 1064623603 "\xf3\xbb\xd3\xfb\x03" , tt_ULEB128_known 1074553497 "\x99\xc5\xb1\x80\x04" , tt_ULEB128_known 1127625082 "\xfa\xe2\xd8\x99\x04" , tt_ULEB128_known 1139110863 "\xcf\xe7\x95\x9f\x04" , tt_ULEB128_known 1149278908 "\xbc\xb5\x82\xa4\x04" , tt_ULEB128_known 1158802511 "\xcf\xd8\xc7\xa8\x04" , tt_ULEB128_known 1163553324 "\xac\xd4\xe9\xaa\x04" , tt_ULEB128_known 1180182155 "\x8b\xcd\xe0\xb2\x04" , tt_ULEB128_known 1183276330 "\xaa\xba\x9d\xb4\x04" , tt_ULEB128_known 1190518037 "\x95\xba\xd7\xb7\x04" , tt_ULEB128_known 1202551545 "\xf9\xf5\xb5\xbd\x04" , tt_ULEB128_known 1248214829 "\xad\xfe\x98\xd3\x04" , tt_ULEB128_known 1256675466 "\x8a\xb1\x9d\xd7\x04" , tt_ULEB128_known 1313825099 "\xcb\xc2\xbd\xf2\x04" , tt_ULEB128_known 1314838143 "\xff\xac\xfb\xf2\x04" , tt_ULEB128_known 1402000705 "\xc1\xaa\xc3\x9c\x05" , tt_ULEB128_known 1414423930 "\xfa\xca\xb9\xa2\x05" , tt_ULEB128_known 1441945961 "\xe9\xb2\xc9\xaf\x05" , tt_ULEB128_known 1449454191 "\xef\xd4\x93\xb3\x05" , tt_ULEB128_known 1453144899 "\xc3\xf6\xf4\xb4\x05" , tt_ULEB128_known 1456639920 "\xb0\x9f\xca\xb6\x05" , tt_ULEB128_known 1457544425 "\xe9\xb9\x81\xb7\x05" , tt_ULEB128_known 1469203333 "\x85\x87\xc9\xbc\x05" , tt_ULEB128_known 1474946464 "\xa0\xcb\xa7\xbf\x05" , tt_ULEB128_known 1523966010 "\xba\xc0\xd7\xd6\x05" , tt_ULEB128_known 1528412212 "\xb4\xf0\xe6\xd8\x05" , tt_ULEB128_known 1531557470 "\xde\xec\xa6\xda\x05" , tt_ULEB128_known 1550196940 "\xcc\xc1\x98\xe3\x05" , tt_ULEB128_known 1553515984 "\xd0\x8b\xe3\xe4\x05" , tt_ULEB128_known 1560913891 "\xe3\xcf\xa6\xe8\x05" , tt_ULEB128_known 1576622459 "\xfb\xb2\xe5\xef\x05" , tt_ULEB128_known 1595762393 "\xd9\xcd\xf5\xf8\x05" , tt_ULEB128_known 1597034808 "\xb8\xa2\xc3\xf9\x05" , tt_ULEB128_known 1599194849 "\xe1\x8d\xc7\xfa\x05" , tt_ULEB128_known 1609605426 "\xb2\xc2\xc2\xff\x05" , tt_ULEB128_known 1641244705 "\xa1\xd0\xcd\x8e\x06" , tt_ULEB128_known 1661751507 "\xd3\xa1\xb1\x98\x06" , tt_ULEB128_known 1683329584 "\xb0\xa4\xd6\xa2\x06" , tt_ULEB128_known 1689190329 "\xb9\xff\xbb\xa5\x06" , tt_ULEB128_known 1691131815 "\xa7\xbf\xb2\xa6\x06" , tt_ULEB128_known 1706153109 "\x95\xa9\xc7\xad\x06" , tt_ULEB128_known 1716906204 "\xdc\xd1\xd7\xb2\x06" , tt_ULEB128_known 1733225139 "\xb3\xd5\xbb\xba\x06" , tt_ULEB128_known 1793703115 "\xcb\xf9\xa6\xd7\x06" , tt_ULEB128_known 1805517085 "\x9d\x82\xf8\xdc\x06" , tt_ULEB128_known 1870883730 "\x92\xd7\x8d\xfc\x06" , tt_ULEB128_known 1899187297 "\xe1\x98\xcd\x89\x07" , tt_ULEB128_known 1973360424 "\xa8\xae\xfc\xac\x07" , tt_ULEB128_known 1986252720 "\xb0\x9f\x8f\xb3\x07" , tt_ULEB128_known 2019542236 "\xdc\x89\xff\xc2\x07" , tt_ULEB128_known 2049800081 "\x91\xef\xb5\xd1\x07" , tt_ULEB128_known 2126356025 "\xb9\xbc\xf6\xf5\x07" , tt_ULEB128_known 2129105334 "\xb6\xa3\x9e\xf7\x07" , tt_ULEB128_known 2137829658 "\x9a\xe2\xb2\xfb\x07" , tt_ULEB128_known 2165033856 "\x80\x97\xaf\x88\x08" , tt_ULEB128_known 2172962693 "\x85\x8f\x93\x8c\x08" , tt_ULEB128_known 2178914725 "\xa5\xb3\xfe\x8e\x08" , tt_ULEB128_known 2197647374 "\x8e\xe0\xf5\x97\x08" , tt_ULEB128_known 2204900736 "\x80\xbb\xb0\x9b\x08" , tt_ULEB128_known 2206666819 "\xc3\xa0\x9c\x9c\x08" , tt_ULEB128_known 2245394147 "\xe3\xfd\xd7\xae\x08" , tt_ULEB128_known 2251211916 "\x8c\x89\xbb\xb1\x08" , tt_ULEB128_known 2285263560 "\xc8\xb5\xd9\xc1\x08" , tt_ULEB128_known 2296034148 "\xe4\xe6\xea\xc6\x08" , tt_ULEB128_known 2297733394 "\x92\xc2\xd2\xc7\x08" , tt_ULEB128_known 2308950307 "\xa3\x92\xff\xcc\x08" , tt_ULEB128_known 2353965320 "\x88\xd2\xba\xe2\x08" , tt_ULEB128_known 2376378142 "\x9e\xce\x92\xed\x08" , tt_ULEB128_known 2377899272 "\x88\xba\xef\xed\x08" , tt_ULEB128_known 2382104382 "\xbe\x8e\xf0\xef\x08" , tt_ULEB128_known 2387606507 "\xeb\xf7\xbf\xf2\x08" , tt_ULEB128_known 2399355301 "\xa5\x83\x8d\xf8\x08" , tt_ULEB128_known 2401253919 "\x9f\xf4\x80\xf9\x08" , tt_ULEB128_known 2405125211 "\xdb\x98\xed\xfa\x08" , tt_ULEB128_known 2428204406 "\xf6\xea\xed\x85\x09" , tt_ULEB128_known 2444829847 "\x97\xc9\xe4\x8d\x09" , tt_ULEB128_known 2450163298 "\xe2\x8c\xaa\x90\x09" , tt_ULEB128_known 2461047003 "\xdb\xb1\xc2\x95\x09" , tt_ULEB128_known 2494558124 "\xac\xdf\xbf\xa5\x09" , tt_ULEB128_known 2503664640 "\x80\xc8\xeb\xa9\x09" , tt_ULEB128_known 2505819863 "\xd7\x8d\xef\xaa\x09" , tt_ULEB128_known 2512858203 "\xdb\xd8\x9c\xae\x09" , tt_ULEB128_known 2521021176 "\xf8\xf5\x8e\xb2\x09" , tt_ULEB128_known 2567620135 "\xa7\x8c\xab\xc8\x09" , tt_ULEB128_known 2571092296 "\xc8\x82\xff\xc9\x09" , tt_ULEB128_known 2581410360 "\xb8\xe4\xf4\xce\x09" , tt_ULEB128_known 2581759998 "\xfe\x8f\x8a\xcf\x09" , tt_ULEB128_known 2589390623 "\x9f\xee\xdb\xd2\x09" , tt_ULEB128_known 2591128222 "\x9e\xf5\xc5\xd3\x09" , tt_ULEB128_known 2629767619 "\xc3\xa3\xfc\xe5\x09" , tt_ULEB128_known 2633373322 "\x8a\xad\xd8\xe7\x09" , tt_ULEB128_known 2641580787 "\xf3\xa5\xcd\xeb\x09" , tt_ULEB128_known 2645675237 "\xe5\x99\xc7\xed\x09" , tt_ULEB128_known 2649315202 "\x82\xaf\xa5\xef\x09" , tt_ULEB128_known 2681864530 "\xd2\x82\xe8\xfe\x09" , tt_ULEB128_known 2733002807 "\xb7\xa0\x99\x97\x0a" , tt_ULEB128_known 2745283454 "\xfe\xe6\x86\x9d\x0a" , tt_ULEB128_known 2761376567 "\xb7\x86\xdd\xa4\x0a" , tt_ULEB128_known 2787404081 "\xb1\xd2\x91\xb1\x0a" , tt_ULEB128_known 2791367114 "\xca\xc3\x83\xb3\x0a" , tt_ULEB128_known 2798865857 "\xc1\x9b\xcd\xb6\x0a" , tt_ULEB128_known 2813755235 "\xe3\xfe\xd9\xbd\x0a" , tt_ULEB128_known 2817817952 "\xe0\xfa\xd1\xbf\x0a" , tt_ULEB128_known 2839422414 "\xce\xcb\xf8\xc9\x0a" , tt_ULEB128_known 2870451344 "\x90\xb9\xde\xd8\x0a" , tt_ULEB128_known 2883096695 "\xf7\xa0\xe2\xde\x0a" , tt_ULEB128_known 2883179007 "\xff\xa3\xe7\xde\x0a" , tt_ULEB128_known 2905111067 "\x9b\xf4\xa1\xe9\x0a" , tt_ULEB128_known 2933694237 "\x9d\xbe\xf2\xf6\x0a" , tt_ULEB128_known 2936137684 "\xd4\xcf\x87\xf8\x0a" , tt_ULEB128_known 2950144350 "\xde\xc2\xde\xfe\x0a" , tt_ULEB128_known 2976345039 "\xcf\xd7\x9d\x8b\x0b" , tt_ULEB128_known 2986169099 "\x8b\xa6\xf5\x8f\x0b" , tt_ULEB128_known 2995829608 "\xe8\xf6\xc2\x94\x0b" , tt_ULEB128_known 3005775514 "\x9a\xfd\xa1\x99\x0b" , tt_ULEB128_known 3010530387 "\xd3\x98\xc4\x9b\x0b" , tt_ULEB128_known 3026902730 "\xca\xbd\xab\xa3\x0b" , tt_ULEB128_known 3049593858 "\x82\xb8\x94\xae\x0b" , tt_ULEB128_known 3069717007 "\x8f\xd4\xe0\xb7\x0b" , tt_ULEB128_known 3084835320 "\xf8\xb3\xfb\xbe\x0b" , tt_ULEB128_known 3137095172 "\x84\x8c\xf1\xd7\x0b" , tt_ULEB128_known 3148225718 "\xb6\xb9\x98\xdd\x0b" , tt_ULEB128_known 3175882084 "\xe4\xba\xb0\xea\x0b" , tt_ULEB128_known 3183785705 "\xe9\xed\x92\xee\x0b" , tt_ULEB128_known 3190934636 "\xec\x98\xc7\xf1\x0b" , tt_ULEB128_known 3207291398 "\x86\xc4\xad\xf9\x0b" , tt_ULEB128_known 3212735579 "\xdb\xe8\xf9\xfb\x0b" , tt_ULEB128_known 3233206445 "\xad\xa1\xdb\x85\x0c" , tt_ULEB128_known 3235504188 "\xbc\xc0\xe7\x86\x0c" , tt_ULEB128_known 3337222955 "\xab\xf6\xa7\xb7\x0c" , tt_ULEB128_known 3344176246 "\xf6\xa8\xd0\xba\x0c" , tt_ULEB128_known 3347759669 "\xb5\x84\xab\xbc\x0c" , tt_ULEB128_known 3349023016 "\xa8\x92\xf8\xbc\x0c" , tt_ULEB128_known 3400985995 "\x8b\xdb\xdb\xd5\x0c" , tt_ULEB128_known 3414245763 "\x83\x83\x85\xdc\x0c" , tt_ULEB128_known 3434162685 "\xfd\xd3\xc4\xe5\x0c" , tt_ULEB128_known 3475754455 "\xd7\x9b\xaf\xf9\x0c" , tt_ULEB128_known 3494374883 "\xe3\xdb\x9f\x82\x0d" , tt_ULEB128_known 3495457228 "\xcc\xe3\xe1\x82\x0d" , tt_ULEB128_known 3535907129 "\xb9\xd2\x86\x96\x0d" , tt_ULEB128_known 3537905033 "\x89\xcb\x80\x97\x0d" , tt_ULEB128_known 3580860466 "\xb2\xb0\xbe\xab\x0d" , tt_ULEB128_known 3597650236 "\xbc\x92\xbf\xb3\x0d" , tt_ULEB128_known 3660178372 "\xc4\xc7\xa7\xd1\x0d" , tt_ULEB128_known 3672796657 "\xf1\xdb\xa9\xd7\x0d" , tt_ULEB128_known 3674100778 "\xaa\xa8\xf9\xd7\x0d" , tt_ULEB128_known 3717759897 "\x99\x87\xe2\xec\x0d" , tt_ULEB128_known 3728526525 "\xbd\x99\xf3\xf1\x0d" , tt_ULEB128_known 3739660092 "\xbc\xde\x9a\xf7\x0d" , tt_ULEB128_known 3749882228 "\xf4\xd2\x8a\xfc\x0d" , tt_ULEB128_known 3749978539 "\xab\xc3\x90\xfc\x0d" , tt_ULEB128_known 3771544098 "\xa2\xe4\xb4\x86\x0e" , tt_ULEB128_known 3774432974 "\xce\x8d\xe5\x87\x0e" , tt_ULEB128_known 3774511384 "\x98\xf2\xe9\x87\x0e" , tt_ULEB128_known 3779422746 "\x9a\xd4\x95\x8a\x0e" , tt_ULEB128_known 3788467130 "\xba\xd7\xbd\x8e\x0e" , tt_ULEB128_known 3823824438 "\xb6\xdc\xab\x9f\x0e" , tt_ULEB128_known 3826295571 "\x93\xc6\xc2\xa0\x0e" , tt_ULEB128_known 3827909534 "\x9e\x87\xa5\xa1\x0e" , tt_ULEB128_known 3836660377 "\x99\x95\xbb\xa5\x0e" , tt_ULEB128_known 3841161226 "\x8a\xf0\xcd\xa7\x0e" , tt_ULEB128_known 3884454891 "\xeb\xa7\xa0\xbc\x0e" , tt_ULEB128_known 3884507512 "\xf8\xc2\xa3\xbc\x0e" , tt_ULEB128_known 3916312506 "\xba\xdf\xb8\xcb\x0e" , tt_ULEB128_known 3918895609 "\xf9\xb3\xd6\xcc\x0e" , tt_ULEB128_known 3950335172 "\xc4\xa9\xd5\xdb\x0e" , tt_ULEB128_known 3990487004 "\xdc\xff\xe7\xee\x0e" , tt_ULEB128_known 3994954592 "\xe0\xd6\xf8\xf0\x0e" , tt_ULEB128_known 3996089698 "\xe2\xfa\xbd\xf1\x0e" , tt_ULEB128_known 4007859466 "\x8a\xaa\x8c\xf7\x0e" , tt_ULEB128_known 4033383511 "\xd7\x98\xa2\x83\x0f" , tt_ULEB128_known 4039087780 "\xa4\xad\xfe\x85\x0f" , tt_ULEB128_known 4047558201 "\xb9\xac\x83\x8a\x0f" , tt_ULEB128_known 4055401811 "\xd3\x8a\xe2\x8d\x0f" , tt_ULEB128_known 4059618015 "\xdf\xb5\xe3\x8f\x0f" , tt_ULEB128_known 4079856829 "\xbd\xd9\xb6\x99\x0f" , tt_ULEB128_known 4083247540 "\xb4\xd3\x85\x9b\x0f" , tt_ULEB128_known 4092196862 "\xfe\xef\xa7\x9f\x0f" , tt_ULEB128_known 4103958027 "\x8b\xdc\xf5\xa4\x0f" , tt_ULEB128_known 4107691575 "\xb7\xcc\xd9\xa6\x0f" , tt_ULEB128_known 4111629699 "\x83\xfb\xc9\xa8\x0f" , tt_ULEB128_known 4126313733 "\x85\x9a\xca\xaf\x0f" , tt_ULEB128_known 4142098808 "\xf8\xd2\x8d\xb7\x0f" , tt_ULEB128_known 4142777074 "\xf2\x85\xb7\xb7\x0f" , tt_ULEB128_known 4189355970 "\xc2\xff\xd1\xcd\x0f" , tt_ULEB128_known 4203404220 "\xbc\xb7\xab\xd4\x0f" , tt_ULEB128_known 4219956182 "\xd6\xd7\x9d\xdc\x0f" , tt_ULEB128_known 4221874260 "\xd4\xe0\x92\xdd\x0f" , tt_ULEB128_known 4245632140 "\x8c\xe9\xbc\xe8\x0f" , tt_ULEB128_known 4250667884 "\xec\x96\xf0\xea\x0f" , tt_ULEB128_known 4258793638 "\xa6\x91\xe0\xee\x0f" , tt_ULEB128_known 4262615991 "\xb7\xb7\xc9\xf0\x0f" , tt_ULEB128_known 4272222672 "\xd0\xe3\x93\xf5\x0f" , tt_ULEB128_known 4273640298 "\xea\xa6\xea\xf5\x0f" , tt_ULEB128_known 4273706408 "\xa8\xab\xee\xf5\x0f" , tt_ULEB128_known 4285571791 "\xcf\xc5\xc2\xfb\x0f" , tt_ULEB128_known 227823842728710 "\x86\xb6\xde\xf9\xc5\xe6\x33" , tt_ULEB128_known 75261474164892201 "\xa9\xc4\xfb\xc6\x97\xbd\xd8\x85\x01" , tt_ULEB128_known 168485408808666162 "\xb2\x88\x82\xef\xe2\x92\xa5\xab\x02" , tt_ULEB128_known 717755936680095145 "\xa9\xdb\xfa\xc9\x8b\xe7\xfe\xfa\x09" , tt_ULEB128_known 734695070650939283 "\x93\xef\x84\x83\xe3\xa8\x8a\x99\x0a" , tt_ULEB128_known 990738819831151138 "\xa2\xf4\xe6\xe9\xd1\xf6\xf3\xdf\x0d" , tt_ULEB128_known 1050338103191410594 "\xa2\xaf\xa0\xf6\x89\x9e\xe3\xc9\x0e" , tt_ULEB128_known 1068136536003572080 "\xf0\xe2\xef\x80\xd3\x90\xb2\xe9\x0e" , tt_ULEB128_known 1075878753333237396 "\x94\xad\xc5\x8e\xea\xc0\x92\xf7\x0e" , tt_ULEB128_known 1113684928626427234 "\xe2\x8a\xf0\x93\xac\xd1\xa6\xba\x0f" , tt_ULEB128_known 1114278600321221100 "\xec\x83\xdd\xc7\xbb\xcf\xad\xbb\x0f" , tt_ULEB128_known 1152991407683701572 "\xc4\x96\xc2\xa0\xb9\xf2\x8f\x80\x10" , tt_ULEB128_known 1174735752806106832 "\xd0\x8d\xd6\x97\x97\xfe\xdf\xa6\x10" , tt_ULEB128_known 1236259003500982012 "\xfc\xdd\xb7\x90\xb8\xe0\x84\x94\x11" , tt_ULEB128_known 1280682687926913479 "\xc7\x93\x81\xdf\xe8\xc3\xf9\xe2\x11" , tt_ULEB128_known 1357168659508766305 "\xe1\xcc\xc0\xd2\xc8\xb6\xe8\xea\x12" , tt_ULEB128_known 1393366409401905860 "\xc4\xe5\xf2\x92\xdf\xeb\x8e\xab\x13" , tt_ULEB128_known 1406191118217599678 "\xbe\xb5\xad\xbd\xf2\xeb\xf2\xc1\x13" , tt_ULEB128_known 1427964220740374637 "\xed\xa0\xca\x89\xca\xbc\xc9\xe8\x13" , tt_ULEB128_known 1435843736633158116 "\xe4\xd3\xf4\x97\xd6\x88\xc9\xf6\x13" , tt_ULEB128_known 1475587601107919743 "\xff\xc6\x88\xf8\xae\xe3\x95\xbd\x14" , tt_ULEB128_known 1500959912189480795 "\xdb\x9e\x9f\xa1\xe7\xe2\x9e\xea\x14" , tt_ULEB128_known 1570152583066146974 "\x9e\xb1\xc7\xe6\xc8\xae\x93\xe5\x15" , tt_ULEB128_known 1740551343930355483 "\x9b\xde\xb0\xc2\x9b\xc7\xeb\x93\x18" , tt_ULEB128_known 1865654390810688288 "\xa0\xf6\xac\xaf\x8a\xd9\x88\xf2\x19" , tt_ULEB128_known 1873271405493943285 "\xf5\xf7\xf3\xa2\xb1\xcd\xcc\xff\x19" , tt_ULEB128_known 1874387577747180441 "\x99\x97\x9a\xf8\xa2\xb2\xca\x81\x1a" , tt_ULEB128_known 1885997661622250280 "\xa8\xd6\xd8\xe1\x97\x9c\x9a\x96\x1a" , tt_ULEB128_known 1895133965637192732 "\x9c\x98\xd4\xbc\xd0\xc9\xb7\xa6\x1a" , tt_ULEB128_known 1900119664317415511 "\xd7\x80\xff\xb2\xc7\x98\xa5\xaf\x1a" , tt_ULEB128_known 1988695039543172212 "\xf4\xb8\xb5\xb4\xa1\xf3\xd0\xcc\x1b" , tt_ULEB128_known 2018975808039210530 "\xa2\x9c\xa3\xc2\xce\xf9\xb5\x82\x1c" , tt_ULEB128_known 2191009178272376218 "\x9a\xcb\xae\xd4\xd3\xe7\x81\xb4\x1e" , tt_ULEB128_known 2286873011306353768 "\xe8\xa8\xdf\xea\xb2\xdc\xa6\xde\x1f" , tt_ULEB128_known 2359136898918748254 "\xde\xa0\xc6\xa4\xaa\xd0\xd5\xde\x20" , tt_ULEB128_known 2387629661863056173 "\xad\xa6\xa2\xd4\xef\x90\xa4\x91\x21" , tt_ULEB128_known 2458535091929179151 "\x8f\xc8\x95\xb2\xbe\x94\x9e\x8f\x22" , tt_ULEB128_known 2563897145003893317 "\xc5\xc4\xe1\xc4\xe8\xdb\xb2\xca\x23" , tt_ULEB128_known 2747545226467382795 "\x8b\xac\xa2\xdf\xb8\xba\xcf\x90\x26" , tt_ULEB128_known 2790287985116613059 "\xc3\x93\xaa\xef\xb8\x84\xc6\xdc\x26" , tt_ULEB128_known 2928980676484332701 "\x9d\xf9\xd3\xbe\x82\x8d\xf5\xd2\x28" , tt_ULEB128_known 2944295686823961901 "\xad\xca\xed\xf6\xbd\xaa\x8f\xee\x28" , tt_ULEB128_known 3022973414962426465 "\xe1\xe4\xa3\xa2\xdf\xc9\xf0\xf9\x29" , tt_ULEB128_known 3076345003319675583 "\xbf\x95\xab\xcb\xb3\xef\xd7\xd8\x2a" , tt_ULEB128_known 3133664910589528302 "\xee\x91\xae\x86\xa2\xf4\xc0\xbe\x2b" , tt_ULEB128_known 3144190332643264855 "\xd7\x92\xad\xdb\xae\x8e\x9a\xd1\x2b" , tt_ULEB128_known 3298539645723045748 "\xf4\xde\xf5\xa6\xcd\x8a\xb1\xe3\x2d" , tt_ULEB128_known 3384806410955606790 "\x86\x96\xe5\xf3\xf4\xef\xcf\xfc\x2e" , tt_ULEB128_known 3415009868491440130 "\x82\x80\x8b\x9f\x9c\xac\xa3\xb2\x2f" , tt_ULEB128_known 3449890764261488679 "\xa7\xf0\xd3\xed\xf2\xab\x9e\xf0\x2f" , tt_ULEB128_known 3563137885558970298 "\xba\xaf\xea\x93\xf5\xe0\xb3\xb9\x31" , tt_ULEB128_known 3657563100074945951 "\x9f\xdb\xac\xdc\xac\xc8\x91\xe1\x32" , tt_ULEB128_known 3700587972716690644 "\xd4\xf9\xf1\xae\xf9\xa4\xc8\xad\x33" , tt_ULEB128_known 3751617101016806029 "\x8d\xe5\x8c\xfb\x85\xfc\x9a\x88\x34" , tt_ULEB128_known 3782283879983012434 "\xd2\xb4\xcb\x90\xe4\xe4\xd7\xbe\x34" , tt_ULEB128_known 3841378177801331069 "\xfd\xc2\xa4\xbe\x9a\xa3\xd4\xa7\x35" , tt_ULEB128_known 3843212937304183130 "\xda\xa2\xce\xa1\xde\xb9\xf5\xaa\x35" , tt_ULEB128_known 3878245798820074584 "\xd8\xa8\xc9\xb2\x99\x80\x93\xe9\x35" , tt_ULEB128_known 3893609823214902851 "\xc3\xbc\xc8\xb5\x94\xb0\xb8\x84\x36" , tt_ULEB128_known 3956728337499169408 "\x80\xc5\xf0\xaa\xd9\xee\xc7\xf4\x36" , tt_ULEB128_known 3982128255237019230 "\xde\xac\xcb\xbb\xcc\x91\xd7\xa1\x37" , tt_ULEB128_known 4043542914206254024 "\xc8\x87\xbf\xda\xb5\x9b\xe3\x8e\x38" , tt_ULEB128_known 4045118881321648135 "\x87\x80\x9c\xdb\x8c\xc6\xc9\x91\x38" , tt_ULEB128_known 4134256720751534067 "\xf3\xbf\xaa\x95\xd5\x92\xf5\xaf\x39" , tt_ULEB128_known 4210079315543515777 "\x81\xc5\xc3\xf9\xcd\x9a\xcd\xb6\x3a" , tt_ULEB128_known 4278215864147998546 "\xd2\xee\xed\xb7\x95\xd5\xd1\xaf\x3b" , tt_ULEB128_known 4294505698158362143 "\x9f\xfc\xfa\x84\xde\xc5\xc9\xcc\x3b" , tt_ULEB128_known 4323175936829160300 "\xec\xf6\xdf\x81\xc0\xb3\xc0\xff\x3b" , tt_ULEB128_known 4437625949942147625 "\xa9\xd4\xed\xc2\xa3\xa9\xe7\xca\x3d" , tt_ULEB128_known 4444393973837935956 "\xd4\xea\xfc\xa3\xd9\x98\xea\xd6\x3d" , tt_ULEB128_known 4527576189882154517 "\x95\xfc\xc4\xdb\xe7\xd1\xcb\xea\x3e" , tt_ULEB128_known 4630711960513531005 "\xfd\x98\xbf\xbc\xe5\xff\xe5\xa1\x40" , tt_ULEB128_known 4738544158561718530 "\x82\xa2\xcb\xdc\xe6\x99\xac\xe1\x41" , tt_ULEB128_known 4823566444556896307 "\xb3\x90\xbb\xf2\xff\x83\xb0\xf8\x42" , tt_ULEB128_known 4969364902516834905 "\xd9\x84\xbd\xee\xcc\xe1\xae\xfb\x44" , tt_ULEB128_known 4999940398370050992 "\xb0\xa7\xe3\xf7\xd2\xe9\xd6\xb1\x45" , tt_ULEB128_known 5047528203842621028 "\xe4\x9c\xb8\xfe\x88\x85\x9b\x86\x46" , tt_ULEB128_known 5056090879529063593 "\xa9\xa9\xb0\xd3\xdd\xfb\xb5\x95\x46" , tt_ULEB128_known 5138682769057202779 "\xdb\x84\xcd\xb8\x8a\x98\x91\xa8\x47" , tt_ULEB128_known 5192771009703340673 "\x81\xd5\xc1\xca\x88\xb7\x9b\x88\x48" , tt_ULEB128_known 5203591044982965645 "\x8d\x8b\xf4\x84\xc5\xcf\xb7\x9b\x48" , tt_ULEB128_known 5205595947569509765 "\x85\xeb\xdf\x98\xf1\xbd\xff\x9e\x48" , tt_ULEB128_known 5245335121816452570 "\xda\xfb\xff\xbd\x89\x90\xcb\xe5\x48" , tt_ULEB128_known 5281614765525499435 "\xab\xfc\xeb\x9c\xd6\x94\x84\xa6\x49" , tt_ULEB128_known 5415006522766295924 "\xf4\x86\xa2\xaf\xe1\xf7\xfd\x92\x4b" , tt_ULEB128_known 5506039178247142939 "\x9b\xfc\xb7\xd6\xdd\xae\xd8\xb4\x4c" , tt_ULEB128_known 5510634334482130396 "\xdc\xcb\x83\xcf\xb0\x97\xed\xbc\x4c" , tt_ULEB128_known 5511632168482070686 "\x9e\xc1\xf5\xf7\x95\x88\xd0\xbe\x4c" , tt_ULEB128_known 5528732412273215974 "\xe6\x93\xef\x9d\xe2\x9a\x80\xdd\x4c" , tt_ULEB128_known 5542048674121246859 "\x8b\xd1\xaf\xa7\xff\xfc\xd3\xf4\x4c" , tt_ULEB128_known 5601897801686080844 "\xcc\xba\xa9\xcc\xed\x8b\xfc\xde\x4d" , tt_ULEB128_known 5609378649501280170 "\xaa\xcf\xbc\xb1\x97\x85\xa1\xec\x4d" , tt_ULEB128_known 5667120534244932029 "\xbd\xf3\xf6\xb7\x9a\x83\xea\xd2\x4e" , tt_ULEB128_known 5788166731354978227 "\xb3\xef\x96\x99\x9a\xdf\xec\xa9\x50" , tt_ULEB128_known 5835458901455749877 "\xf5\x85\xa5\xd5\xc0\xde\xed\xfd\x50" , tt_ULEB128_known 6045420329007298572 "\x8c\xf0\x9e\xe3\xa5\xb8\xe9\xf2\x53" , tt_ULEB128_known 6082603178276280450 "\x82\xb1\xc7\xb6\xd1\xeb\xef\xb4\x54" , tt_ULEB128_known 6271761304563999046 "\xc6\xc2\xcf\x94\xd6\xb5\xf1\x84\x57" , tt_ULEB128_known 6376283519002828267 "\xeb\xbb\xdd\xca\xbd\x82\xc7\xbe\x58" , tt_ULEB128_known 6617393968943300669 "\xbd\x80\xb6\xcd\x91\x98\xed\xea\x5b" , tt_ULEB128_known 6692377965772467354 "\x9a\xd9\x93\xc4\xd5\xc9\x86\xf0\x5c" , tt_ULEB128_known 6827839821837000505 "\xb9\xbe\xf1\xde\xc7\x84\xd7\xe0\x5e" , tt_ULEB128_known 6843499419089188695 "\xd7\xee\x9c\xbb\xe9\xce\xbf\xfc\x5e" , tt_ULEB128_known 6945363918775826385 "\xd1\xef\xca\xf3\xf9\xf5\xb8\xb1\x60" , tt_ULEB128_known 7003418245793840538 "\x9a\xfb\x9f\x90\x9f\xf9\xc8\x98\x61" , tt_ULEB128_known 7019050392006902605 "\xcd\x86\x8d\xe1\xc9\xa4\xab\xb4\x61" , tt_ULEB128_known 7074114660671564637 "\xdd\xd6\xd8\xcd\xdb\xb9\x93\x96\x62" , tt_ULEB128_known 7337278415349509923 "\xa3\xde\xb1\xe8\x81\xfb\xcf\xe9\x65" , tt_ULEB128_known 7363375970986704126 "\xfe\xf9\xbc\xd2\xec\xed\xfd\x97\x66" , tt_ULEB128_known 7442628686330531987 "\x93\xa1\xf4\x9e\xb8\xeb\xe1\xa4\x67" , tt_ULEB128_known 7485339658625876641 "\xa1\x85\xa8\xfc\xaa\x98\xd1\xf0\x67" , tt_ULEB128_known 7593087050568726701 "\xad\xf1\x91\xee\x94\x8e\x84\xb0\x69" , tt_ULEB128_known 7616993389808968746 "\xaa\xc8\xbf\xc0\x9a\xe4\xbf\xda\x69" , tt_ULEB128_known 7652912018846076278 "\xf6\x9a\x8d\xe5\xf2\xdd\xa6\x9a\x6a" , tt_ULEB128_known 7841396255184312349 "\x9d\xb0\xdb\xea\x93\x8b\x8f\xe9\x6c" , tt_ULEB128_known 7862375172691359479 "\xf7\xed\xf9\xd8\x81\x92\xb1\x8e\x6d" , tt_ULEB128_known 8002043003097211607 "\xd7\xc5\x89\xa8\xef\xf6\xbd\x86\x6f" , tt_ULEB128_known 8012357224138885541 "\xa5\x93\xd5\xf2\x9a\x8e\xe7\x98\x6f" , tt_ULEB128_known 8053099365893889619 "\xd3\xbc\x9d\xa8\xcc\xe6\x96\xe1\x6f" , tt_ULEB128_known 8069181957144908666 "\xfa\xa6\xf4\xbc\xcd\xc7\xdf\xfd\x6f" , tt_ULEB128_known 8070986252393944622 "\xae\xac\x82\x88\xc1\xe7\xf9\x80\x70" , tt_ULEB128_known 8092118975093648323 "\xc3\xd7\x9e\xf5\xd7\xea\xbe\xa6\x70" , tt_ULEB128_known 8127488305158606999 "\x97\xa1\xfb\x88\xd6\xf1\xa8\xe5\x70" , tt_ULEB128_known 8173669839824647064 "\x98\xe7\xc9\x90\x9d\xad\xad\xb7\x71" , tt_ULEB128_known 8204921825036634609 "\xf1\x93\xa2\xb9\xda\x9d\xef\xee\x71" , tt_ULEB128_known 8244731277729298875 "\xbb\xf3\xed\xac\xa2\xed\xca\xb5\x72" , tt_ULEB128_known 8327374118332948680 "\xc8\xc1\x91\xd8\xbe\xd4\xb1\xc8\x73" , tt_ULEB128_known 8444002472442420534 "\xb6\xba\xcd\xe3\xaa\xf0\xc7\x97\x75" , tt_ULEB128_known 8460080481274843743 "\xdf\xa4\xe9\x8c\xfd\xcb\x8f\xb4\x75" , tt_ULEB128_known 8558966579069034438 "\xc6\xbf\xe6\xee\x99\xd8\xe3\xe3\x76" , tt_ULEB128_known 8608031914317356491 "\xcb\xbb\xf2\xa0\xb3\xed\xf7\xba\x77" , tt_ULEB128_known 8717063203043061758 "\xfe\xdf\x8a\xb0\xc5\xd9\xce\xfc\x78" , tt_ULEB128_known 8731691902328862096 "\x90\xeb\xdd\xf3\xdc\xf0\xcc\x96\x79" , tt_ULEB128_known 8735249437125091689 "\xe9\xc2\x96\xe2\xce\xe2\xf5\x9c\x79" , tt_ULEB128_known 8765939449468784786 "\x92\xa1\xae\x81\xc4\xef\xb7\xd3\x79" , tt_ULEB128_known 8846810664494540287 "\xff\xcb\xd6\xe2\xd4\xed\x8b\xe3\x7a" , tt_ULEB128_known 8863797907167105568 "\xa0\xa4\xaf\x8c\xbf\xa7\xa2\x81\x7b" , tt_ULEB128_known 8874913961157715656 "\xc8\xcd\xd7\x97\x9f\xe7\x81\x95\x7b" , tt_ULEB128_known 9095902393560545338 "\xba\xf0\xb4\xbe\x8e\xe1\xc8\x9d\x7e" , tt_ULEB128_known 9278357653237088389 "\x85\x81\xe5\xa1\x87\xa4\xd6\xe1\x80\x01" , tt_ULEB128_known 9345651036153697948 "\x9c\xad\xcf\xe5\xa1\x83\x9b\xd9\x81\x01" , tt_ULEB128_known 9484121148456758217 "\xc9\xd7\xa3\xe4\xf7\xbd\x97\xcf\x83\x01" , tt_ULEB128_known 9488398371130531571 "\xf3\xbd\x85\xf5\xbf\x81\xe4\xd6\x83\x01" , tt_ULEB128_known 9740039616846814260 "\xb4\xb8\x8b\xa3\xd3\xcd\xe4\x95\x87\x01" , tt_ULEB128_known 9777013101649715726 "\x8e\xc4\xaf\xc1\xd7\xb3\xbb\xd7\x87\x01" , tt_ULEB128_known 9801441920966166937 "\x99\x93\xbe\x8e\xf3\xef\xed\x82\x88\x01" , tt_ULEB128_known 9897207218105991608 "\xb8\x83\x8f\xbd\xef\xb0\xfc\xac\x89\x01" , tt_ULEB128_known 10060108146541440626 "\xf2\xdc\xf6\xe4\xef\xe1\xab\xce\x8b\x01" , tt_ULEB128_known 10105846657260489569 "\xe1\x96\xd2\x84\xde\xbf\xcb\x9f\x8c\x01" , tt_ULEB128_known 10110759008783538163 "\xf3\xaf\xfe\xc0\xfd\xb7\xa8\xa8\x8c\x01" , tt_ULEB128_known 10186751003295074837 "\x95\x94\x87\xb6\x8d\x82\xa7\xaf\x8d\x01" , tt_ULEB128_known 10226525623380170998 "\xf6\xb1\x85\xe0\xf3\xdb\xfa\xf5\x8d\x01" , tt_ULEB128_known 10242529200753152505 "\xf9\xa3\xd4\xa3\xa7\xc1\xb1\x92\x8e\x01" , tt_ULEB128_known 10272916768788366883 "\xa3\x8c\xa3\xd6\xf7\xeb\xae\xc8\x8e\x01" , tt_ULEB128_known 10405418797642988611 "\xc3\xf8\xba\xa5\xc2\xa8\xde\xb3\x90\x01" , tt_ULEB128_known 10469894606496237985 "\xa1\x93\xf2\xbf\xc3\xb5\xa2\xa6\x91\x01" , tt_ULEB128_known 10485683442469938049 "\x81\xc7\xf6\xfc\x90\xb1\xa8\xc2\x91\x01" , tt_ULEB128_known 10514734800163341226 "\xaa\x87\xb2\xf9\xf5\xf2\xf5\xf5\x91\x01" , tt_ULEB128_known 10516557500424622678 "\xd6\xa4\x9e\xc6\xbd\xaa\x94\xf9\x91\x01" , tt_ULEB128_known 10532633304015060167 "\xc7\xf9\x90\xda\xf8\xc5\xdb\x95\x92\x01" , tt_ULEB128_known 10562228117401896415 "\xdf\x8b\x88\xf3\xaf\xd0\xa4\xca\x92\x01" , tt_ULEB128_known 10607748610367498417 "\xb1\xd1\xe4\xdc\x8a\xe5\x92\x9b\x93\x01" , tt_ULEB128_known 10715779747999238730 "\xca\x94\xc7\xd6\xff\x9c\x86\xdb\x94\x01" , tt_ULEB128_known 10794028799708388741 "\x85\xbb\xd1\xef\x90\x80\x86\xe6\x95\x01" , tt_ULEB128_known 11076654462981947196 "\xbc\xfe\xa2\xae\xc2\xd1\x8b\xdc\x99\x01" , tt_ULEB128_known 11112029803825057860 "\xc4\xa0\xaf\xb4\xb8\x87\xf7\x9a\x9a\x01" , tt_ULEB128_known 11204063524666424848 "\x90\xfc\x9c\xe5\x9f\x8d\xb5\xbe\x9b\x01" , tt_ULEB128_known 11217857190501866486 "\xf6\xb7\xb3\xa7\xe1\xb5\xf5\xd6\x9b\x01" , tt_ULEB128_known 11227690731560178118 "\xc6\xa3\xdc\xb4\xbc\xa7\xb1\xe8\x9b\x01" , tt_ULEB128_known 11233273182042669342 "\x9e\x82\xcd\x84\x95\xce\xa6\xf2\x9b\x01" , tt_ULEB128_known 11257190893642734044 "\xdc\xb3\xd9\x82\x98\xef\xe4\x9c\x9c\x01" , tt_ULEB128_known 11316140797099052479 "\xbf\x9b\x94\xbb\x97\xc3\xc0\x85\x9d\x01" , tt_ULEB128_known 11439500404765512453 "\x85\xa6\xf1\x8f\xa5\xa0\xd1\xe0\x9e\x01" , tt_ULEB128_known 11487841127191890497 "\xc1\x94\x95\xb3\xbd\xd4\xc0\xb6\x9f\x01" , tt_ULEB128_known 11573419706116713613 "\x8d\xd9\xde\x9c\xf7\xfc\xc2\xce\xa0\x01" , tt_ULEB128_known 11825700855638588116 "\xd4\xf5\xfb\x82\xde\x88\xd5\x8e\xa4\x01" , tt_ULEB128_known 11962454006436529282 "\x82\x89\xe4\xfc\x9f\x91\xcb\x81\xa6\x01" , tt_ULEB128_known 12094674477893877376 "\x80\xfd\xe3\xc6\xb7\xcb\xba\xec\xa7\x01" , tt_ULEB128_known 12095595652187308684 "\x8c\x85\x89\x9b\x91\x85\x8c\xee\xa7\x01" , tt_ULEB128_known 12117614803696436543 "\xbf\x8a\xdd\xda\xe4\xce\x9a\x95\xa8\x01" , tt_ULEB128_known 12348568270978276187 "\xdb\xb6\xc7\xe2\xab\xad\xbb\xaf\xab\x01" , tt_ULEB128_known 12530379333244790682 "\x9a\xcf\xce\x97\xd6\xb3\xb6\xf2\xad\x01" , tt_ULEB128_known 12535116550804629314 "\xc2\xce\xd1\xe6\xec\xc2\xeb\xfa\xad\x01" , tt_ULEB128_known 12590579628698639224 "\xf8\xb6\xe8\xe6\xee\xae\xae\xdd\xae\x01" , tt_ULEB128_known 12643216874244515033 "\xd9\xc9\xc6\xfc\xaa\xd8\xee\xba\xaf\x01" , tt_ULEB128_known 12665910134576977208 "\xb8\xaa\xec\xc3\x91\xc5\x96\xe3\xaf\x01" , tt_ULEB128_known 13025394675902087618 "\xc2\x83\xa2\xe3\xa3\xee\xdf\xe1\xb4\x01" , tt_ULEB128_known 13076173724363569287 "\x87\xf1\xf2\xaf\x8c\xd7\xf9\xbb\xb5\x01" , tt_ULEB128_known 13119112646413862286 "\x8e\x8b\xd5\x8e\x9a\xee\x9c\x88\xb6\x01" , tt_ULEB128_known 13179126492408335310 "\xce\x97\xc1\xaf\x80\xb7\xea\xf2\xb6\x01" , tt_ULEB128_known 13344414739953353340 "\xfc\x84\xa0\xb3\x91\xd0\xb8\x98\xb9\x01" , tt_ULEB128_known 13587730528178406622 "\xde\x89\xb8\xde\xca\x9d\xd4\xc8\xbc\x01" , tt_ULEB128_known 13590176164891917038 "\xee\xf5\xf3\xba\xfd\xa6\x80\xcd\xbc\x01" , tt_ULEB128_known 13601956848995391445 "\xd5\xaf\xbf\xd4\x81\xf6\xf6\xe1\xbc\x01" , tt_ULEB128_known 13609900213639311091 "\xf3\xdd\xef\xf3\xac\x84\x85\xf0\xbc\x01" , tt_ULEB128_known 13622021734351412017 "\xb1\xb6\xaa\xb5\x84\x93\xc9\x85\xbd\x01" , tt_ULEB128_known 13679751921386162979 "\xa3\x96\xc2\x8d\xce\xbc\x8f\xec\xbd\x01" , tt_ULEB128_known 13685618867296918967 "\xb7\xbb\xf7\xe4\x9a\xbb\xc5\xf6\xbd\x01" , tt_ULEB128_known 13715042894693961232 "\x90\x9c\xea\xcb\x8e\xdb\xe7\xaa\xbe\x01" , tt_ULEB128_known 13867437321366946997 "\xb5\x89\xc9\xe8\xd5\x98\xc2\xb9\xc0\x01" , tt_ULEB128_known 13884858018854964648 "\xa8\x9b\xd6\x94\xd9\x99\xbb\xd8\xc0\x01" , tt_ULEB128_known 14109693877532310998 "\xd6\xfb\xc4\x9e\xb4\xfa\xec\xe7\xc3\x01" , tt_ULEB128_known 14159978080673443788 "\xcc\xdf\xee\xae\xaa\xa1\x96\xc1\xc4\x01" , tt_ULEB128_known 14187365854017477836 "\xcc\xb9\xdf\xd9\xb8\xc2\xe9\xf1\xc4\x01" , tt_ULEB128_known 14299237009190957872 "\xb0\xe6\xc8\xdf\xc9\x89\xc6\xb8\xc6\x01" , tt_ULEB128_known 14440442733995446828 "\xac\xa4\xad\xb9\x86\xc5\xb0\xb3\xc8\x01" , tt_ULEB128_known 14474524103216191221 "\xf5\xad\x9f\xc8\xb8\xdf\xf5\xef\xc8\x01" , tt_ULEB128_known 14493564399040357302 "\xb6\xc7\xb1\xf0\xfd\x80\xdf\x91\xc9\x01" , tt_ULEB128_known 14495297497968030852 "\x84\xe9\xf8\xbf\xe6\x88\xe9\x94\xc9\x01" , tt_ULEB128_known 14536154376438558816 "\xe0\xe0\xf0\xbe\xbb\xec\xb2\xdd\xc9\x01" , tt_ULEB128_known 14738538189932390152 "\x88\xce\xcb\xbb\xd4\xcc\xf3\xc4\xcc\x01" , tt_ULEB128_known 14769995374197693954 "\x82\xbc\xdd\xe9\x9b\x91\xe4\xfc\xcc\x01" , tt_ULEB128_known 14863488181145897913 "\xb9\x97\xac\xc3\x82\xf8\xed\xa2\xce\x01" , tt_ULEB128_known 15068877586868647463 "\xa7\xec\x9a\x89\xbb\x8a\xda\x8f\xd1\x01" , tt_ULEB128_known 15075290977826340765 "\x9d\xff\xf5\x97\xda\xa8\x8c\x9b\xd1\x01" , tt_ULEB128_known 15097000880341691964 "\xbc\xdc\x9a\xb4\x83\xca\xd4\xc1\xd1\x01" , tt_ULEB128_known 15315359322966216613 "\xa5\x9f\xf9\xa6\x8f\xc5\xc5\xc5\xd4\x01" , tt_ULEB128_known 15332238884456094609 "\x91\xb7\xbf\xfb\x81\xc1\xc3\xe3\xd4\x01" , tt_ULEB128_known 15355656764698617296 "\xd0\xcb\xbd\x85\x84\x8f\x90\x8d\xd5\x01" , tt_ULEB128_known 15451913260127887220 "\xf4\xbe\xc8\xd0\xe0\xa7\x8e\xb8\xd6\x01" , tt_ULEB128_known 15469952299346770796 "\xec\xf6\xb4\xb6\xf2\xf4\x93\xd8\xd6\x01" , tt_ULEB128_known 15529439428856688579 "\xc3\xdf\xca\xef\x9c\xdc\xe9\xc1\xd7\x01" , tt_ULEB128_known 15561213538269371436 "\xac\xb8\xae\xb4\xc2\xa8\xa2\xfa\xd7\x01" , tt_ULEB128_known 15670949158519500554 "\x8a\xde\x8b\xf6\xb3\xa7\x99\xbd\xd9\x01" , tt_ULEB128_known 15768132723588903218 "\xb2\xe2\xea\x85\xb4\xa5\xea\xe9\xda\x01" , tt_ULEB128_known 15777457821124589455 "\x8f\xef\xdb\xb6\xbb\xc9\xb2\xfa\xda\x01" , tt_ULEB128_known 15948109888341212272 "\xf0\xf8\xe3\xeb\xa5\xae\xc4\xa9\xdd\x01" , tt_ULEB128_known 15989613841619609519 "\xaf\xcf\x9f\xab\xa8\xa2\xa1\xf3\xdd\x01" , tt_ULEB128_known 16017135281365759761 "\x91\xee\xba\xe9\xd0\xf5\x92\xa4\xde\x01" , tt_ULEB128_known 16318616824692571020 "\x8c\xf7\x8d\xac\xad\xf1\xd7\xbb\xe2\x01" , tt_ULEB128_known 16466066235311737763 "\xa3\x97\xbd\x9e\x80\x80\xce\xc1\xe4\x01" , tt_ULEB128_known 16488195901431596315 "\x9b\x8a\x87\xdf\x86\xda\xf5\xe8\xe4\x01" , tt_ULEB128_known 16497666429405569624 "\xd8\xc4\xec\xdc\xd8\x86\xdf\xf9\xe4\x01" , tt_ULEB128_known 16687025645117266970 "\x9a\xb8\xb1\xf8\x99\xad\x8e\xca\xe7\x01" , tt_ULEB128_known 16717941301969772540 "\xfc\xbf\xf5\xbd\x9e\xe1\x83\x81\xe8\x01" , tt_ULEB128_known 16732013103060218250 "\x8a\xe3\xd7\xc8\xc6\xa8\x83\x9a\xe8\x01" , tt_ULEB128_known 16732215193639573532 "\x9c\xb0\x9f\xd2\x94\xa2\xb1\x9a\xe8\x01" , tt_ULEB128_known 16823652378989721398 "\xb6\xee\xd9\x92\xc0\xd6\xe7\xbc\xe9\x01" , tt_ULEB128_known 16901939111747112304 "\xf0\x9a\xdf\x97\xa6\x82\xf0\xc7\xea\x01" , tt_ULEB128_known 16925540598690529784 "\xf8\x83\x9b\xc3\xfc\xaf\xe6\xf1\xea\x01" , tt_ULEB128_known 17253201377649926326 "\xb6\xc1\xea\xc8\xdd\xe7\xeb\xb7\xef\x01" , tt_ULEB128_known 17278784277645343305 "\xc9\xf4\x9e\xdd\x8e\xd8\xa4\xe5\xef\x01" , tt_ULEB128_known 17343838944915026409 "\xe9\xe3\xfb\xc9\x8f\xb4\xec\xd8\xf0\x01" , tt_ULEB128_known 17356087171625683816 "\xe8\x96\xda\xdb\xb7\xaa\xcd\xee\xf0\x01" , tt_ULEB128_known 17358307530478456555 "\xeb\x9d\xa0\x81\xb1\x97\xc6\xf2\xf0\x01" , tt_ULEB128_known 17375028618161701841 "\xd1\x87\x99\xde\x8a\x8f\xa0\x90\xf1\x01" , tt_ULEB128_known 17431587162243082439 "\xc7\xd1\x88\xa6\xae\x85\xdc\xf4\xf1\x01" , tt_ULEB128_known 17468619073700264256 "\xc0\xf2\x91\xe4\xea\x8f\xc0\xb6\xf2\x01" , tt_ULEB128_known 17677645154584602864 "\xf0\xd1\xae\x83\xba\x93\xe7\xa9\xf5\x01" , tt_ULEB128_known 17680852272158274921 "\xe9\xea\x9b\x81\xee\xae\xc0\xaf\xf5\x01" , tt_ULEB128_known 17760608059192644565 "\xd5\xa7\xf8\xd8\xe1\xdd\x96\xbd\xf6\x01" , tt_ULEB128_known 17790454869050497143 "\xf7\xb0\xfe\xf2\xa0\x8e\x99\xf2\xf6\x01" , tt_ULEB128_known 17844543005813556250 "\x9a\x88\xcb\x85\x9c\xaa\xa3\xd2\xf7\x01" , tt_ULEB128_known 18108784008520238429 "\xdd\x8a\xfe\xf0\xc7\xe3\xd4\xa7\xfb\x01" , tt_ULEB128_known 18140543185983641493 "\x95\xaf\xc0\xc9\xa3\xfd\x89\xe0\xfb\x01" , tt_ULEB128_known 18247503505561409945 "\x99\xb3\xbb\xb5\xa4\xf8\x89\x9e\xfd\x01" ] , testGroup "Round trip" [ testProperty "putWord8" $ property $ do n <- forAll $ Gen.integral Range.constantBounded propDecULEB128 n (enc (U.putWord8 n)) , testProperty "putWord16" $ property $ do n <- forAll $ Gen.integral Range.constantBounded propDecULEB128 n (enc (U.putWord16 n)) , testProperty "putWord32" $ property $ do n <- forAll $ Gen.integral Range.constantBounded propDecULEB128 n (enc (U.putWord32 n)) , testProperty "putWord64" $ property $ do n <- forAll $ Gen.integral Range.constantBounded propDecULEB128 n (enc (U.putWord64 n)) , testProperty "putWord" $ property $ do n <- forAll $ Gen.integral Range.constantBounded propDecULEB128 n (enc (U.putWord n)) , testProperty "putNatural" $ property $ do n <- forAll $ Gen.integral rangeNatural512 propDecULEB128 n (enc (U.putNatural n)) ] , testGroup "List" [ testProperty "Round trip" $ property $ do i <- forAll $ Gen.int $ Range.linearFrom 0 0 1000 let raw :: [Word8] = take i $ cycle [minBound .. maxBound] dec (U.getList Bin.getWord8) (enc (U.putList Bin.putWord8 raw)) === Right raw , testProperty "Known" $ property $ do i <- forAll $ Gen.int $ Range.linearFrom 0 0 1000 let raw :: [Word8] = take i $ cycle [minBound .. maxBound] pre = enc (U.putWord (fromIntegral i)) enc (U.putList Bin.putWord8 raw) === pre <> BL.pack raw ] , testGroup "Seq" [ testProperty "Round trip" $ property $ do i <- forAll $ Gen.int $ Range.linearFrom 0 0 1000 let raw :: Seq.Seq Word8 raw = Seq.fromList $ take i $ cycle [minBound .. maxBound] dec (U.getSeq Bin.getWord8) (enc (U.putSeq Bin.putWord8 raw)) === Right raw , testProperty "Known" $ property $ do i <- forAll $ Gen.int $ Range.linearFrom 0 0 1000 let raw :: Seq.Seq Word8 raw = Seq.fromList $ take i $ cycle [minBound .. maxBound] pre = enc (U.putWord (fromIntegral (Seq.length raw))) enc (U.putSeq Bin.putWord8 raw) === pre <> BL.pack (toList raw) ] , testGroup "Set" [ testProperty "Round trip" $ property $ do for_ [minBound .. maxBound] $ \(w :: Word8) -> do let raw :: Set.Set Word8 raw = Set.fromList $ take (fromIntegral w) [minBound .. maxBound] dec (U.getSet Bin.getWord8) (enc (U.putSet Bin.putWord8 raw)) === Right raw , testProperty "Known" $ property $ do for_ [minBound .. maxBound] $ \(w :: Word8) -> do let raw :: Set.Set Word8 raw = Set.fromList $ take (fromIntegral w) [minBound .. maxBound] pre = enc (U.putWord (fromIntegral (Set.size raw))) enc (U.putSet Bin.putWord8 raw) === pre <> BL.pack (Set.toAscList raw) ] , testGroup "Map" [ testProperty "Round trip" $ property $ do let kvs :: [(Word8, Int8)] kvs = zip [minBound .. maxBound] [minBound .. maxBound] for_ [minBound .. maxBound] $ \(w :: Word8) -> do let raw :: Map.Map Word8 Int8 raw = Map.fromList $ take (fromIntegral w) kvs Right raw === dec (U.getMap Bin.getWord8 Bin.getInt8) (enc (U.putMap Bin.putWord8 Bin.putInt8 raw)) , testProperty "Known" $ property $ do let kvs :: [(Word8, Int8)] kvs = zip [minBound .. maxBound] [minBound .. maxBound] for_ [minBound .. maxBound] $ \(w :: Word8) -> do let raw :: Map.Map Word8 Int8 raw = Map.fromList $ take (fromIntegral w) kvs blraw = Bin.runPut $ mapM_ Bin.put $ Map.toAscList raw blpre = enc $ U.putWord $ fromIntegral $ Map.size raw enc (U.putMap Bin.putWord8 Bin.putInt8 raw) === blpre <> blraw ] , testGroup "ByteString (strict)" [ testProperty "Round trip" $ property $ do i <- forAll $ Gen.integral $ Range.constantFrom 0 0 1000 let raw = B.replicate i 222 dec U.getByteString (enc (U.putByteString raw)) === Right raw , testProperty "Known" $ property $ do i <- forAll $ Gen.integral $ Range.constantFrom 0 0 1000 let pre = enc (U.putWord (fromIntegral (i :: Int))) raw = B.replicate i 222 enc (U.putByteString raw) === pre <> BL.fromStrict raw ] , testGroup "ByteString (lazy)" [ testProperty "Round trip" $ property $ do i <- forAll $ Gen.integral $ Range.constantFrom 0 0 1000 let raw = BL.replicate i 222 dec U.getLazyByteString (enc (U.putLazyByteString raw)) === Right raw , testProperty "Known" $ property $ do i <- forAll $ Gen.integral $ Range.constantFrom 0 0 1000 let pre = enc (U.putWord (fromIntegral (i :: Int64))) raw = BL.replicate i 222 enc (U.putLazyByteString raw) === pre <> raw ] , testGroup "ByteString (short)" [ testProperty "Round trip" $ property $ do i <- forAll $ Gen.integral $ Range.constantFrom 0 0 1000 let raw = BS.toShort (B.replicate i 222) dec U.getShortByteString (enc (U.putShortByteString raw)) === Right raw , testProperty "Known" $ property $ do i <- forAll $ Gen.integral $ Range.constantFrom 0 0 1000 let pre = enc (U.putWord (fromIntegral (i :: Int))) raw = BS.toShort (B.replicate i 222) enc (U.putShortByteString raw) === pre <> BL.fromStrict (BS.fromShort raw) ] , testGroup "Text (strict)" [ testProperty "Round trip" $ property $ do i <- forAll $ Gen.integral $ Range.constantFrom 0 0 1000 let traw = T.replicate i "È™" dec U.getText (enc (U.putText traw)) === Right traw , testProperty "Known" $ property $ do i <- forAll $ Gen.integral $ Range.constantFrom 0 0 1000 let traw = T.replicate i "È™" braw = T.encodeUtf8 traw blpre = enc (U.putWord (fromIntegral (B.length braw :: Int))) enc (U.putText traw) === blpre <> BL.fromStrict braw ] , testGroup "Text (lazy)" [ testProperty "Round trip" $ property $ do i <- forAll $ Gen.integral $ Range.constantFrom 0 0 1000 let raw = TL.replicate i "È™" dec U.getLazyText (enc (U.putLazyText raw)) === Right raw , testProperty "Known" $ property $ do i <- forAll $ Gen.integral $ Range.constantFrom 0 0 1000 let traw = TL.replicate i "È™" blraw = TL.encodeUtf8 traw blpre = enc (U.putWord (fromIntegral (BL.length blraw :: Int64))) enc (U.putLazyText traw) === blpre <> blraw ] ] tt_ULEB128_known :: Natural -> BL.ByteString -> TestTree tt_ULEB128_known n bl = testGroup (show n) [ testCase "put" $ enc (U.putNatural n) @?= bl , testCase "get" $ assertDecULEB128 n bl ] tt_SLEB128 :: TestTree tt_SLEB128 = testGroup "SLEB128" [ testGroup "Too big" [ testCase "0, 0" $ dec (S.getInteger 0) "" @?= Left "input exceeds maximum allowed bytes\nSLEB128" , testCase "0, 1" $ dec (S.getInteger 0) "\x00" @?= Left "input exceeds maximum allowed bytes\nSLEB128" , testCase "0, 1.5" $ dec (S.getInteger 0) "\x80" @?= Left "input exceeds maximum allowed bytes\nSLEB128" , testCase "1, 1.5" $ dec (S.getInteger 1) "\x80" @?= Left "input exceeds maximum allowed bytes\nSLEB128" , testCase "1, 2" $ dec (S.getInteger 1) "\x89\x3b" @?= Left "input exceeds maximum allowed bytes\nSLEB128" , testCase "1, 3" $ dec (S.getInteger 1) "\xc9\xc1\x00" @?= Left "input exceeds maximum allowed bytes\nSLEB128" , testCase "2, 3" $ dec (S.getInteger 2) "\xc9\xc1\x00" @?= Left "input exceeds maximum allowed bytes\nSLEB128" ] , testGroup "Known" [ tt_SLEB128_known (-9015451631251509835) "\xb5\xdb\xa6\xec\x9d\xd0\xab\xf1\x82\x7f" , tt_SLEB128_known (-8845873988257394623) "\xc1\xa0\xb3\x90\x9a\x8f\xc9\x9e\x85\x7f" , tt_SLEB128_known (-8842841274936780126) "\xa2\xb5\xec\xd1\xe3\xd6\xfa\xa3\x85\x7f" , tt_SLEB128_known (-8556157385587939139) "\xbd\xd1\xc8\xad\x8b\x86\x9b\xa1\x89\x7f" , tt_SLEB128_known (-8522800211221181049) "\x87\x9b\xa6\xb4\xd1\xcb\xbb\xdc\x89\x7f" , tt_SLEB128_known (-8485791988481748275) "\xcd\xa5\xc2\xc5\xd6\xa4\x9a\x9e\x8a\x7f" , tt_SLEB128_known (-8483754184008751867) "\x85\xca\xb2\xe3\xcb\xd0\xe9\xa1\x8a\x7f" , tt_SLEB128_known (-8276697308179582507) "\xd5\xe3\x98\xc4\xe6\xf4\xd0\x91\x8d\x7f" , tt_SLEB128_known (-8107645367689656885) "\xcb\x8b\x91\xb0\xe8\xef\xf6\xbd\x8f\x7f" , tt_SLEB128_known (-7897285947534482093) "\xd3\xca\x97\xbc\xdb\x88\xcd\xb3\x92\x7f" , tt_SLEB128_known (-7772703118602814481) "\xef\xf7\xee\xb8\x9f\xf6\xf3\x90\x94\x7f" , tt_SLEB128_known (-7701038245294958103) "\xe9\xb3\xfc\xdb\xc8\xd0\x9a\x90\x95\x7f" , tt_SLEB128_known (-7621567507177824854) "\xaa\xbb\x86\xb8\xba\x97\xb0\x9d\x96\x7f" , tt_SLEB128_known (-7496317180987688968) "\xf8\xef\xc8\xbc\xdb\xe7\xee\xfb\x97\x7f" , tt_SLEB128_known (-7478508143247252325) "\x9b\xc9\x86\xff\xf6\x8e\xc0\x9b\x98\x7f" , tt_SLEB128_known (-7429215717708838129) "\x8f\x96\xdd\xd1\xa9\xf5\x87\xf3\x98\x7f" , tt_SLEB128_known (-7322751059733054785) "\xbf\xf5\xfb\x8f\xd7\x96\x97\xb0\x9a\x7f" , tt_SLEB128_known (-7280002181293982082) "\xfe\xfc\x9c\x9f\xe5\x92\x8f\xfc\x9a\x7f" , tt_SLEB128_known (-7276726830436499218) "\xee\x81\x9d\x82\x86\xf0\xf7\x81\x9b\x7f" , tt_SLEB128_known (-7272820501303806738) "\xee\xe9\xee\x84\x98\x89\xf0\x88\x9b\x7f" , tt_SLEB128_known (-7271078635291017708) "\x94\xfc\xaf\xcc\x94\x90\xfc\x8b\x9b\x7f" , tt_SLEB128_known (-7224058460184500729) "\x87\xcc\xb0\xe0\xae\xa3\xbf\xdf\x9b\x7f" , tt_SLEB128_known (-7218513110023818091) "\x95\xe9\x9e\xf4\xa5\x92\xac\xe9\x9b\x7f" , tt_SLEB128_known (-7169700919810018527) "\xa1\xe6\xba\xc7\x80\xe0\x86\xc0\x9c\x7f" , tt_SLEB128_known (-6848037735711187469) "\xf3\xbb\xdb\xd3\xe3\xbe\xb8\xfb\xa0\x7f" , tt_SLEB128_known (-6779538613528389993) "\x97\xad\xe2\xfc\xce\xb1\x8f\xf5\xa1\x7f" , tt_SLEB128_known (-6573916454518439344) "\xd0\x84\xd5\x8a\x89\xba\xb0\xe2\xa4\x7f" , tt_SLEB128_known (-6554927559093407642) "\xe6\xe0\xc6\xfe\xd4\x83\x8e\x84\xa5\x7f" , tt_SLEB128_known (-6493158617924639365) "\xfb\xca\xd7\xa2\xba\xd4\xea\xf1\xa5\x7f" , tt_SLEB128_known (-6442875855316439363) "\xbd\xdd\xb0\xff\xb9\xd1\x93\xcb\xa6\x7f" , tt_SLEB128_known (-6374141538702420700) "\xa4\xaa\xd2\xec\xac\x81\xa0\xc5\xa7\x7f" , tt_SLEB128_known (-6296776333015610931) "\xcd\x93\x92\x84\x97\xe9\xd6\xce\xa8\x7f" , tt_SLEB128_known (-6211278320953137430) "\xea\xcd\x83\xf4\xe9\xe8\xc6\xe6\xa9\x7f" , tt_SLEB128_known (-6206032071712417024) "\x80\xb6\x99\xa7\xe3\xd6\xef\xef\xa9\x7f" , tt_SLEB128_known (-6190903940917779093) "\xeb\xca\x9e\x98\xaa\xb5\xdf\x8a\xaa\x7f" , tt_SLEB128_known (-6166955670678844237) "\xb3\x99\xed\xfc\xdc\xcf\xa4\xb5\xaa\x7f" , tt_SLEB128_known (-6147525758390505168) "\xb0\xe2\xc7\xdc\xcc\xbc\xe6\xd7\xaa\x7f" , tt_SLEB128_known (-5979470863740975152) "\xd0\x8f\xaf\xaf\xe1\xdd\xa9\x82\xad\x7f" , tt_SLEB128_known (-5956359947341419360) "\xa0\xd9\xe6\x82\xfa\xc5\xb0\xab\xad\x7f" , tt_SLEB128_known (-5935045008163866456) "\xa8\xf1\xbf\x93\xaa\x80\x9f\xd1\xad\x7f" , tt_SLEB128_known (-5787331914243643991) "\xa9\xcb\xe7\xf1\x95\x89\xd1\xd7\xaf\x7f" , tt_SLEB128_known (-5779439755263686250) "\x96\x93\xf3\x95\x9d\xc5\xd3\xe5\xaf\x7f" , tt_SLEB128_known (-5778280777440391568) "\xf0\x9c\xca\x81\xf6\x87\xdb\xe7\xaf\x7f" , tt_SLEB128_known (-5722955693957385186) "\x9e\xe8\xfb\xe2\xe2\xc3\xfe\xc9\xb0\x7f" , tt_SLEB128_known (-5678952082115941293) "\xd3\xd8\x8e\x88\xb7\xe5\x93\x98\xb1\x7f" , tt_SLEB128_known (-5635936467873333755) "\x85\xfc\xf5\xbd\xc9\xb4\xc8\xe4\xb1\x7f" , tt_SLEB128_known (-5622710758104924047) "\xf1\x80\x8e\xe3\xb1\xcb\x87\xfc\xb1\x7f" , tt_SLEB128_known (-5552306137205707020) "\xf4\xdd\x87\xfd\xc4\xdf\x8f\xf9\xb2\x7f" , tt_SLEB128_known (-5432329272797841740) "\xb4\xed\xb6\xff\xed\xa9\x9f\xce\xb4\x7f" , tt_SLEB128_known (-5409157020114747574) "\xca\xfe\xff\x8d\x96\x8b\xb4\xf7\xb4\x7f" , tt_SLEB128_known (-5377759596865526605) "\xb3\xc9\x87\xab\xba\x84\x97\xaf\xb5\x7f" , tt_SLEB128_known (-5293955917046730683) "\xc5\xe0\xe8\xde\xc5\xe4\x85\xc4\xb6\x7f" , tt_SLEB128_known (-5276524690623660565) "\xeb\xfb\xb1\xb6\x80\x98\x81\xe3\xb6\x7f" , tt_SLEB128_known (-5275542185978577043) "\xed\xfe\xa2\xb9\xd3\xca\xe0\xe4\xb6\x7f" , tt_SLEB128_known (-5080028964182223657) "\xd7\xa9\xe4\xe9\xa7\x92\x87\xc0\xb9\x7f" , tt_SLEB128_known (-4893379532346778144) "\xe0\xbb\xb6\xba\xdd\xa7\xce\x8b\xbc\x7f" , tt_SLEB128_known (-4844991702395721618) "\xee\xd0\xf3\xf7\xf6\xb6\xc8\xe1\xbc\x7f" , tt_SLEB128_known (-4594607936156968693) "\x8b\xb2\xb1\x99\xce\x8d\xab\x9e\x40" , tt_SLEB128_known (-4591896550820938510) "\xf2\xf9\xe7\xd7\xa7\xcd\x93\xa3\x40" , tt_SLEB128_known (-4589574099668352347) "\xa5\x85\xbd\xb7\xc4\xd5\xa3\xa7\x40" , tt_SLEB128_known (-4532775902251836953) "\xe7\xb3\xd0\x9e\xd2\x8a\x96\x8c\x41" , tt_SLEB128_known (-4531935102467665968) "\xd0\x9f\xaa\xc2\x91\xa1\xd5\x8d\x41" , tt_SLEB128_known (-4518171459184852569) "\xa7\x83\xea\xa7\xf0\xdf\x8e\xa6\x41" , tt_SLEB128_known (-4484711469774604056) "\xe8\xf1\xdb\x9f\xde\xd5\xc6\xe1\x41" , tt_SLEB128_known (-4323123947915954171) "\x85\xf0\xf0\xe3\xc9\xb5\xcb\x80\x44" , tt_SLEB128_known (-4291837239673002165) "\xcb\xce\xfd\xbb\xd0\x98\x95\xb8\x44" , tt_SLEB128_known (-4234243536084555642) "\x86\xd1\xbe\xd9\x81\xbe\xbc\x9e\x45" , tt_SLEB128_known (-4089601000917788115) "\xad\xb4\xda\xd9\xea\xb1\xb4\x9f\x47" , tt_SLEB128_known (-3998247270963412067) "\x9d\x87\xb4\xd0\xa6\xe9\xd7\xc1\x48" , tt_SLEB128_known (-3992189355246770035) "\x8d\xd1\xae\xa3\xed\x9d\xb9\xcc\x48" , tt_SLEB128_known (-3960425873444320581) "\xbb\x95\xd7\xf0\xeb\xb4\xef\x84\x49" , tt_SLEB128_known (-3920918428027768861) "\xe3\xdf\xfc\x80\xeb\xae\x86\xcb\x49" , tt_SLEB128_known (-3896772997752851503) "\xd1\xe7\xed\x94\xac\xb3\xf8\xf5\x49" , tt_SLEB128_known (-3830059077683584617) "\x97\xc3\xa3\xaf\xfb\xb1\xb9\xec\x4a" , tt_SLEB128_known (-3773749753308058581) "\xab\xd8\xeb\x96\xff\xd2\xbc\xd0\x4b" , tt_SLEB128_known (-3709363437631825438) "\xe2\xb3\x88\xa9\xb4\xb3\xec\xc2\x4c" , tt_SLEB128_known (-3551864614040605682) "\x8e\xd8\xd1\xee\xbb\xbe\xcf\xda\x4e" , tt_SLEB128_known (-3538458889709326407) "\xb9\xdf\xb5\xd4\xb2\xcc\xb7\xf2\x4e" , tt_SLEB128_known (-3510807628900196704) "\xa0\xbd\xb0\xa5\x80\xe2\xc6\xa3\x4f" , tt_SLEB128_known (-3493896362524734461) "\x83\x98\xbc\xed\xd0\xf8\xcb\xc1\x4f" , tt_SLEB128_known (-3480526772758105880) "\xe8\xe1\x90\xf4\xf3\xea\xab\xd9\x4f" , tt_SLEB128_known (-3446394694547916167) "\xf9\xf4\xb8\xdd\x8f\xc9\xfc\x95\x50" , tt_SLEB128_known (-3426262981006668988) "\xc4\x96\x9b\xf0\x8c\xff\xdd\xb9\x50" , tt_SLEB128_known (-3395109590119605005) "\xf3\xb9\x98\xdb\x8d\xba\x89\xf1\x50" , tt_SLEB128_known (-3349882385064699251) "\x8d\xb5\x85\xf7\x81\xf7\xb4\xc1\x51" , tt_SLEB128_known (-3194600936394437380) "\xfc\x99\xd1\x98\xfc\xeb\x9f\xd5\x53" , tt_SLEB128_known (-3182545557078683548) "\xe4\xa0\xcf\xe6\xd7\xf5\xd4\xea\x53" , tt_SLEB128_known (-3172377041564524708) "\xdc\xbe\xc4\xff\xb7\xfc\xdc\xfc\x53" , tt_SLEB128_known (-3001491593507913480) "\xf8\x81\x8f\xe5\xc5\xe9\xa3\xac\x56" , tt_SLEB128_known (-2978756232555591187) "\xed\x93\xac\xb0\xd1\x9f\xd5\xd4\x56" , tt_SLEB128_known (-2893347837054065560) "\xe8\xc8\xfd\xc5\x8c\xef\xb0\xec\x57" , tt_SLEB128_known (-2791206811152809932) "\xb4\x80\xd8\xb4\x99\x86\xe9\xa1\x59" , tt_SLEB128_known (-2750458018244304965) "\xbb\xbf\xb1\xa7\x94\xa0\x9a\xea\x59" , tt_SLEB128_known (-2672965747832870286) "\xf2\xd4\x8a\xbd\x87\xfa\xed\xf3\x5a" , tt_SLEB128_known (-2553681548773257126) "\xda\xa0\x9a\xff\x94\x85\xe0\xc7\x5c" , tt_SLEB128_known (-2543542719845913221) "\xfb\xda\xb6\x84\xf6\xab\xe1\xd9\x5c" , tt_SLEB128_known (-2540322427720969431) "\xa9\xa6\xef\x85\xe1\xc6\xbd\xdf\x5c" , tt_SLEB128_known (-2535716587620118949) "\xdb\x9c\xd9\xbe\xac\xe6\xd4\xe7\x5c" , tt_SLEB128_known (-2507055343404571362) "\x9e\xca\x80\xc1\xab\xce\xc9\x9a\x5d" , tt_SLEB128_known (-2504855703159012186) "\xa6\x89\xe2\xfc\xa5\xe0\xbd\x9e\x5d" , tt_SLEB128_known (-2342405984312446314) "\x96\xe5\xba\xca\xaf\xc5\x86\xbf\x5f" , tt_SLEB128_known (-2112449394162310082) "\xbe\xc8\xdd\xf7\xfd\xce\xc4\xd7\x62" , tt_SLEB128_known (-2085412304362508580) "\xdc\xdd\xf9\xa1\xee\x91\xc8\x87\x63" , tt_SLEB128_known (-2015802339231676599) "\xc9\x8e\xc7\x85\xbe\xce\x9b\x83\x64" , tt_SLEB128_known (-1991599610167483452) "\xc4\xc7\xa4\xe9\xcd\xd6\x9a\xae\x64" , tt_SLEB128_known (-1802299514279593542) "\xba\xf3\x85\xc4\xc0\xc4\xbc\xfe\x66" , tt_SLEB128_known (-1788025794814968433) "\x8f\xfb\xc5\x96\xb5\x80\xea\x97\x67" , tt_SLEB128_known (-1633568702721236735) "\x81\xc2\xeb\xf0\xb7\xbd\x99\xaa\x69" , tt_SLEB128_known (-1563953070423669007) "\xf1\x8d\x90\xc0\xff\x9e\xee\xa5\x6a" , tt_SLEB128_known (-1531343856302388803) "\xbd\x93\xfa\xc0\x84\xdc\xe4\xdf\x6a" , tt_SLEB128_known (-1443846670923883028) "\xec\xbb\xce\xab\xa4\xa3\x9b\xfb\x6b" , tt_SLEB128_known (-1324900659139526206) "\xc2\x83\xbb\x8a\xec\xbb\xc0\xce\x6d" , tt_SLEB128_known (-973503881282136363) "\xd5\xad\xdb\xc5\x8b\xec\xda\xbe\x72" , tt_SLEB128_known (-922574221217393149) "\x83\xac\x9e\x8b\xa4\xf4\x96\x99\x73" , tt_SLEB128_known (-827603766902525297) "\x8f\xe5\xff\x97\xa4\xd8\xf0\xc1\x74" , tt_SLEB128_known (-573796989413515899) "\x85\xbb\xc6\x86\xda\xd5\xdd\x84\x78" , tt_SLEB128_known (-569993810965739236) "\x9c\x92\xdd\xe9\xe1\xb4\xbe\x8b\x78" , tt_SLEB128_known (-466253085031555368) "\xd8\xbd\x8e\xda\xa1\xa9\xe2\xc3\x79" , tt_SLEB128_known (-232927486339319927) "\x89\xef\xc7\xf2\xf6\xb5\x9e\xe2\x7c" , tt_SLEB128_known (-171536181428024305) "\x8f\x98\xec\xbe\x87\x98\xa5\xcf\x7d" , tt_SLEB128_known (-62821989041134405) "\xbb\xc9\xfa\xd8\xbd\xf7\xb3\x90\x7f" , tt_SLEB128_known (-2140227152) "\xb0\xf3\xba\x83\x78" , tt_SLEB128_known (-2127666182) "\xfa\xc7\xb9\x89\x78" , tt_SLEB128_known (-2127550250) "\xd6\xd1\xc0\x89\x78" , tt_SLEB128_known (-2122511773) "\xe3\x94\xf4\x8b\x78" , tt_SLEB128_known (-2115766272) "\x80\xf0\x8f\x8f\x78" , tt_SLEB128_known (-2081080403) "\xad\xf7\xd4\x9f\x78" , tt_SLEB128_known (-2073690705) "\xaf\xfb\x97\xa3\x78" , tt_SLEB128_known (-2062501071) "\xb1\xf6\xc2\xa8\x78" , tt_SLEB128_known (-2048048916) "\xec\x81\xb5\xaf\x78" , tt_SLEB128_known (-1998164561) "\xaf\xdb\x99\xc7\x78" , tt_SLEB128_known (-1946109476) "\xdc\xf3\x82\xe0\x78" , tt_SLEB128_known (-1934574707) "\x8d\xf7\xc2\xe5\x78" , tt_SLEB128_known (-1910851719) "\xf9\xee\xea\xf0\x78" , tt_SLEB128_known (-1908171085) "\xb3\xbd\x8e\xf2\x78" , tt_SLEB128_known (-1876224949) "\xcb\xa8\xac\x81\x79" , tt_SLEB128_known (-1867480917) "\xab\x81\xc2\x85\x79" , tt_SLEB128_known (-1832114620) "\xc4\xcc\xb0\x96\x79" , tt_SLEB128_known (-1828819581) "\x83\xdb\xf9\x97\x79" , tt_SLEB128_known (-1818041564) "\xa4\xc6\x8b\x9d\x79" , tt_SLEB128_known (-1812464891) "\x85\xf6\xdf\x9f\x79" , tt_SLEB128_known (-1801863077) "\xdb\x80\xe7\xa4\x79" , tt_SLEB128_known (-1781899811) "\xdd\xbb\xa9\xae\x79" , tt_SLEB128_known (-1779805230) "\xd2\xa7\xa9\xaf\x79" , tt_SLEB128_known (-1774888330) "\xf6\xb4\xd5\xb1\x79" , tt_SLEB128_known (-1772085860) "\x9c\xbb\x80\xb3\x79" , tt_SLEB128_known (-1733093001) "\xf7\xb2\xcc\xc5\x79" , tt_SLEB128_known (-1729295792) "\xd0\x94\xb4\xc7\x79" , tt_SLEB128_known (-1701024960) "\xc0\xd6\xf1\xd4\x79" , tt_SLEB128_known (-1699416675) "\x9d\xeb\xd3\xd5\x79" , tt_SLEB128_known (-1696813956) "\xfc\xd8\xf2\xd6\x79" , tt_SLEB128_known (-1696023128) "\xa8\xfb\xa2\xd7\x79" , tt_SLEB128_known (-1680472232) "\xd8\x8e\xd8\xde\x79" , tt_SLEB128_known (-1673941798) "\xda\xd9\xe6\xe1\x79" , tt_SLEB128_known (-1672027781) "\xfb\xc2\xdb\xe2\x79" , tt_SLEB128_known (-1662424457) "\xf7\xd4\xa5\xe7\x79" , tt_SLEB128_known (-1624275774) "\xc2\x89\xbe\xf9\x79" , tt_SLEB128_known (-1617846754) "\x9e\xbc\xc6\xfc\x79" , tt_SLEB128_known (-1616451762) "\xce\xce\x9b\xfd\x79" , tt_SLEB128_known (-1610689836) "\xd4\xa5\xfb\xff\x79" , tt_SLEB128_known (-1608446160) "\xb0\x9e\x84\x81\x7a" , tt_SLEB128_known (-1606116365) "\xf3\xb7\x92\x82\x7a" , tt_SLEB128_known (-1604221749) "\xcb\x89\x86\x83\x7a" , tt_SLEB128_known (-1567520880) "\x90\x8f\xc6\x94\x7a" , tt_SLEB128_known (-1562827802) "\xe6\xc7\xe4\x96\x7a" , tt_SLEB128_known (-1552298105) "\x87\x9f\xe7\x9b\x7a" , tt_SLEB128_known (-1540724929) "\xbf\xce\xa9\xa1\x7a" , tt_SLEB128_known (-1526746287) "\xd1\xe6\xfe\xa7\x7a" , tt_SLEB128_known (-1524897325) "\xd3\xd3\xef\xa8\x7a" , tt_SLEB128_known (-1503022886) "\xda\xe1\xa6\xb3\x7a" , tt_SLEB128_known (-1502181668) "\xdc\x8d\xda\xb3\x7a" , tt_SLEB128_known (-1481127424) "\x80\x94\xdf\xbd\x7a" , tt_SLEB128_known (-1472651910) "\xfa\xba\xe4\xc1\x7a" , tt_SLEB128_known (-1448565203) "\xad\xcc\xa2\xcd\x7a" , tt_SLEB128_known (-1431958913) "\xff\x94\x98\xd5\x7a" , tt_SLEB128_known (-1431106751) "\xc1\x96\xcc\xd5\x7a" , tt_SLEB128_known (-1370603172) "\xdc\x82\xb9\xf2\x7a" , tt_SLEB128_known (-1356302298) "\xa6\xf0\xa1\xf9\x7a" , tt_SLEB128_known (-1307074103) "\xc9\xc3\xde\x90\x7b" , tt_SLEB128_known (-1262972701) "\xe3\xa1\xe2\xa5\x7b" , tt_SLEB128_known (-1229050970) "\xa6\xd7\xf8\xb5\x7b" , tt_SLEB128_known (-1224829917) "\xa3\xa8\xfa\xb7\x7b" , tt_SLEB128_known (-1191777396) "\x8c\xd7\xdb\xc7\x7b" , tt_SLEB128_known (-1148490108) "\x84\xdd\xad\xdc\x7b" , tt_SLEB128_known (-1117746188) "\xf4\x97\x82\xeb\x7b" , tt_SLEB128_known (-1111424379) "\x85\x85\x84\xee\x7b" , tt_SLEB128_known (-1102673542) "\xfa\x92\x9a\xf2\x7b" , tt_SLEB128_known (-1078535311) "\xf1\xb6\xdb\xfd\x7b" , tt_SLEB128_known (-1060201049) "\xa7\xbb\xba\x86\x7c" , tt_SLEB128_known (-1052806457) "\xc7\xe5\xfd\x89\x7c" , tt_SLEB128_known (-993557311) "\xc1\x89\x9e\xa6\x7c" , tt_SLEB128_known (-985922027) "\x95\x8c\xf0\xa9\x7c" , tt_SLEB128_known (-974571241) "\x97\xf2\xa4\xaf\x7c" , tt_SLEB128_known (-938132241) "\xef\xf9\xd4\xc0\x7c" , tt_SLEB128_known (-927436188) "\xe4\xe4\xe1\xc5\x7c" , tt_SLEB128_known (-902034296) "\x88\x99\xf0\xd1\x7c" , tt_SLEB128_known (-895774541) "\xb3\xa1\xee\xd4\x7c" , tt_SLEB128_known (-882683495) "\x99\xa3\x8d\xdb\x7c" , tt_SLEB128_known (-880130888) "\xb8\x89\xa9\xdc\x7c" , tt_SLEB128_known (-867929629) "\xe3\xe3\x91\xe2\x7c" , tt_SLEB128_known (-849861506) "\xfe\xc8\xe0\xea\x7c" , tt_SLEB128_known (-838720401) "\xef\xc8\x88\xf0\x7c" , tt_SLEB128_known (-829518712) "\x88\x99\xba\xf4\x7c" , tt_SLEB128_known (-828342709) "\xcb\xfc\x81\xf5\x7c" , tt_SLEB128_known (-818235523) "\xfd\xee\xea\xf9\x7c" , tt_SLEB128_known (-787077562) "\xc6\xcc\xd8\x88\x7d" , tt_SLEB128_known (-756372772) "\xdc\xd5\xaa\x97\x7d" , tt_SLEB128_known (-756100565) "\xab\xa4\xbb\x97\x7d" , tt_SLEB128_known (-753465411) "\xbd\x8f\xdc\x98\x7d" , tt_SLEB128_known (-746574635) "\xd5\xd9\x80\x9c\x7d" , tt_SLEB128_known (-744194014) "\xa2\x80\x92\x9d\x7d" , tt_SLEB128_known (-723379706) "\x86\xb4\x88\xa7\x7d" , tt_SLEB128_known (-716928155) "\xe5\x96\x92\xaa\x7d" , tt_SLEB128_known (-708523764) "\x8c\x92\x93\xae\x7d" , tt_SLEB128_known (-677366077) "\xc3\xed\x80\xbd\x7d" , tt_SLEB128_known (-665428015) "\xd1\xbf\xd9\xc2\x7d" , tt_SLEB128_known (-664005752) "\x88\xa7\xb0\xc3\x7d" , tt_SLEB128_known (-631537179) "\xe5\x83\xee\xd2\x7d" , tt_SLEB128_known (-629824963) "\xbd\xc4\xd6\xd3\x7d" , tt_SLEB128_known (-614546227) "\xcd\x89\xfb\xda\x7d" , tt_SLEB128_known (-613505955) "\xdd\xc8\xba\xdb\x7d" , tt_SLEB128_known (-590957484) "\xd4\xe8\x9a\xe6\x7d" , tt_SLEB128_known (-570346284) "\xd4\xe9\x84\xf0\x7d" , tt_SLEB128_known (-568014405) "\xbb\x93\x93\xf1\x7d" , tt_SLEB128_known (-558187008) "\x80\xfc\xea\xf5\x7d" , tt_SLEB128_known (-554930165) "\x8b\xe0\xb1\xf7\x7d" , tt_SLEB128_known (-524108653) "\x93\xf9\x8a\x86\x7e" , tt_SLEB128_known (-511003921) "\xef\xe5\xaa\x8c\x7e" , tt_SLEB128_known (-500617726) "\x82\xdc\xa4\x91\x7e" , tt_SLEB128_known (-462860973) "\xd3\x9a\xa5\xa3\x7e" , tt_SLEB128_known (-451523301) "\x9b\x9a\xd9\xa8\x7e" , tt_SLEB128_known (-439073323) "\xd5\x8b\xd1\xae\x7e" , tt_SLEB128_known (-417947106) "\x9e\xc4\xda\xb8\x7e" , tt_SLEB128_known (-396034016) "\xa0\x80\x94\xc3\x7e" , tt_SLEB128_known (-393498089) "\x97\xe4\xae\xc4\x7e" , tt_SLEB128_known (-385071153) "\xcf\x8f\xb1\xc8\x7e" , tt_SLEB128_known (-377531844) "\xbc\xa4\xfd\xcb\x7e" , tt_SLEB128_known (-370571987) "\xad\x8a\xa6\xcf\x7e" , tt_SLEB128_known (-354023403) "\x95\x90\x98\xd7\x7e" , tt_SLEB128_known (-341701040) "\xd0\x9c\x88\xdd\x7e" , tt_SLEB128_known (-324280602) "\xe6\xbd\xaf\xe5\x7e" , tt_SLEB128_known (-282781627) "\xc5\xb0\x94\xf9\x7e" , tt_SLEB128_known (-277891402) "\xb6\xed\xbe\xfb\x7e" , tt_SLEB128_known (-261722993) "\x8f\xd9\x99\x83\x7f" , tt_SLEB128_known (-255554825) "\xf7\x95\x92\x86\x7f" , tt_SLEB128_known (-236387687) "\x99\x85\xa4\x8f\x7f" , tt_SLEB128_known (-202528688) "\xd0\xd0\xb6\x9f\x7f" , tt_SLEB128_known (-190351805) "\xc3\xec\x9d\xa5\x7f" , tt_SLEB128_known (-123893637) "\xfb\x90\xf6\x44" , tt_SLEB128_known (-122140000) "\xa0\x95\xe1\x45" , tt_SLEB128_known (-119184036) "\xdc\xca\x95\x47" , tt_SLEB128_known (-108762683) "\xc5\xd3\x91\x4c" , tt_SLEB128_known (-98728904) "\xb8\x88\xf6\x50" , tt_SLEB128_known (-32534) "\xea\x81\x7e" , tt_SLEB128_known (-31605) "\x8b\x89\x7e" , tt_SLEB128_known (-31465) "\x97\x8a\x7e" , tt_SLEB128_known (-31435) "\xb5\x8a\x7e" , tt_SLEB128_known (-30949) "\x9b\x8e\x7e" , tt_SLEB128_known (-30595) "\xfd\x90\x7e" , tt_SLEB128_known (-30417) "\xaf\x92\x7e" , tt_SLEB128_known (-30351) "\xf1\x92\x7e" , tt_SLEB128_known (-30326) "\x8a\x93\x7e" , tt_SLEB128_known (-30256) "\xd0\x93\x7e" , tt_SLEB128_known (-29994) "\xd6\x95\x7e" , tt_SLEB128_known (-29932) "\x94\x96\x7e" , tt_SLEB128_known (-29474) "\xde\x99\x7e" , tt_SLEB128_known (-29117) "\xc3\x9c\x7e" , tt_SLEB128_known (-29068) "\xf4\x9c\x7e" , tt_SLEB128_known (-28526) "\x92\xa1\x7e" , tt_SLEB128_known (-28272) "\x90\xa3\x7e" , tt_SLEB128_known (-28262) "\x9a\xa3\x7e" , tt_SLEB128_known (-28014) "\x92\xa5\x7e" , tt_SLEB128_known (-27200) "\xc0\xab\x7e" , tt_SLEB128_known (-27049) "\xd7\xac\x7e" , tt_SLEB128_known (-26894) "\xf2\xad\x7e" , tt_SLEB128_known (-26876) "\x84\xae\x7e" , tt_SLEB128_known (-26864) "\x90\xae\x7e" , tt_SLEB128_known (-26360) "\x88\xb2\x7e" , tt_SLEB128_known (-25615) "\xf1\xb7\x7e" , tt_SLEB128_known (-25398) "\xca\xb9\x7e" , tt_SLEB128_known (-25368) "\xe8\xb9\x7e" , tt_SLEB128_known (-25220) "\xfc\xba\x7e" , tt_SLEB128_known (-25218) "\xfe\xba\x7e" , tt_SLEB128_known (-24927) "\xa1\xbd\x7e" , tt_SLEB128_known (-24911) "\xb1\xbd\x7e" , tt_SLEB128_known (-24044) "\x94\xc4\x7e" , tt_SLEB128_known (-24013) "\xb3\xc4\x7e" , tt_SLEB128_known (-23226) "\xc6\xca\x7e" , tt_SLEB128_known (-22569) "\xd7\xcf\x7e" , tt_SLEB128_known (-22456) "\xc8\xd0\x7e" , tt_SLEB128_known (-22438) "\xda\xd0\x7e" , tt_SLEB128_known (-22310) "\xda\xd1\x7e" , tt_SLEB128_known (-22005) "\x8b\xd4\x7e" , tt_SLEB128_known (-21951) "\xc1\xd4\x7e" , tt_SLEB128_known (-21723) "\xa5\xd6\x7e" , tt_SLEB128_known (-21339) "\xa5\xd9\x7e" , tt_SLEB128_known (-21202) "\xae\xda\x7e" , tt_SLEB128_known (-20914) "\xce\xdc\x7e" , tt_SLEB128_known (-20500) "\xec\xdf\x7e" , tt_SLEB128_known (-20424) "\xb8\xe0\x7e" , tt_SLEB128_known (-20363) "\xf5\xe0\x7e" , tt_SLEB128_known (-19962) "\x86\xe4\x7e" , tt_SLEB128_known (-19432) "\x98\xe8\x7e" , tt_SLEB128_known (-19214) "\xf2\xe9\x7e" , tt_SLEB128_known (-19202) "\xfe\xe9\x7e" , tt_SLEB128_known (-19006) "\xc2\xeb\x7e" , tt_SLEB128_known (-18671) "\x91\xee\x7e" , tt_SLEB128_known (-18544) "\x90\xef\x7e" , tt_SLEB128_known (-18487) "\xc9\xef\x7e" , tt_SLEB128_known (-17881) "\xa7\xf4\x7e" , tt_SLEB128_known (-17624) "\xa8\xf6\x7e" , tt_SLEB128_known (-17596) "\xc4\xf6\x7e" , tt_SLEB128_known (-17556) "\xec\xf6\x7e" , tt_SLEB128_known (-17481) "\xb7\xf7\x7e" , tt_SLEB128_known (-17174) "\xea\xf9\x7e" , tt_SLEB128_known (-15697) "\xaf\x85\x7f" , tt_SLEB128_known (-15692) "\xb4\x85\x7f" , tt_SLEB128_known (-15498) "\xf6\x86\x7f" , tt_SLEB128_known (-15227) "\x85\x89\x7f" , tt_SLEB128_known (-14692) "\x9c\x8d\x7f" , tt_SLEB128_known (-14512) "\xd0\x8e\x7f" , tt_SLEB128_known (-14136) "\xc8\x91\x7f" , tt_SLEB128_known (-13761) "\xbf\x94\x7f" , tt_SLEB128_known (-13595) "\xe5\x95\x7f" , tt_SLEB128_known (-12992) "\xc0\x9a\x7f" , tt_SLEB128_known (-12251) "\xa5\xa0\x7f" , tt_SLEB128_known (-12244) "\xac\xa0\x7f" , tt_SLEB128_known (-12170) "\xf6\xa0\x7f" , tt_SLEB128_known (-11996) "\xa4\xa2\x7f" , tt_SLEB128_known (-11761) "\x8f\xa4\x7f" , tt_SLEB128_known (-11700) "\xcc\xa4\x7f" , tt_SLEB128_known (-11677) "\xe3\xa4\x7f" , tt_SLEB128_known (-10743) "\x89\xac\x7f" , tt_SLEB128_known (-10561) "\xbf\xad\x7f" , tt_SLEB128_known (-10100) "\x8c\xb1\x7f" , tt_SLEB128_known (-10081) "\x9f\xb1\x7f" , tt_SLEB128_known (-9920) "\xc0\xb2\x7f" , tt_SLEB128_known (-9589) "\x8b\xb5\x7f" , tt_SLEB128_known (-9237) "\xeb\xb7\x7f" , tt_SLEB128_known (-9156) "\xbc\xb8\x7f" , tt_SLEB128_known (-9132) "\xd4\xb8\x7f" , tt_SLEB128_known (-9091) "\xfd\xb8\x7f" , tt_SLEB128_known (-7980) "\xd4\x41" , tt_SLEB128_known (-7979) "\xd5\x41" , tt_SLEB128_known (-7726) "\xd2\x43" , tt_SLEB128_known (-7666) "\x8e\x44" , tt_SLEB128_known (-7431) "\xf9\x45" , tt_SLEB128_known (-7297) "\xff\x46" , tt_SLEB128_known (-7009) "\x9f\x49" , tt_SLEB128_known (-6731) "\xb5\x4b" , tt_SLEB128_known (-6461) "\xc3\x4d" , tt_SLEB128_known (-6420) "\xec\x4d" , tt_SLEB128_known (-6278) "\xfa\x4e" , tt_SLEB128_known (-6059) "\xd5\x50" , tt_SLEB128_known (-6052) "\xdc\x50" , tt_SLEB128_known (-5743) "\x91\x53" , tt_SLEB128_known (-5526) "\xea\x54" , tt_SLEB128_known (-5496) "\x88\x55" , tt_SLEB128_known (-3247) "\xd1\x66" , tt_SLEB128_known (-3191) "\x89\x67" , tt_SLEB128_known (-3164) "\xa4\x67" , tt_SLEB128_known (-2584) "\xe8\x6b" , tt_SLEB128_known (-2483) "\xcd\x6c" , tt_SLEB128_known (-2242) "\xbe\x6e" , tt_SLEB128_known (-2029) "\x93\x70" , tt_SLEB128_known (-1976) "\xc8\x70" , tt_SLEB128_known (-1510) "\x9a\x74" , tt_SLEB128_known (-1500) "\xa4\x74" , tt_SLEB128_known (-1478) "\xba\x74" , tt_SLEB128_known (-1225) "\xb7\x76" , tt_SLEB128_known (-865) "\x9f\x79" , tt_SLEB128_known (-816) "\xd0\x79" , tt_SLEB128_known (-719) "\xb1\x7a" , tt_SLEB128_known (-473) "\xa7\x7c" , tt_SLEB128_known (-127) "\x81\x7f" , tt_SLEB128_known (-123) "\x85\x7f" , tt_SLEB128_known (-121) "\x87\x7f" , tt_SLEB128_known (-117) "\x8b\x7f" , tt_SLEB128_known (-116) "\x8c\x7f" , tt_SLEB128_known (-115) "\x8d\x7f" , tt_SLEB128_known (-114) "\x8e\x7f" , tt_SLEB128_known (-112) "\x90\x7f" , tt_SLEB128_known (-111) "\x91\x7f" , tt_SLEB128_known (-110) "\x92\x7f" , tt_SLEB128_known (-109) "\x93\x7f" , tt_SLEB128_known (-106) "\x96\x7f" , tt_SLEB128_known (-105) "\x97\x7f" , tt_SLEB128_known (-104) "\x98\x7f" , tt_SLEB128_known (-103) "\x99\x7f" , tt_SLEB128_known (-102) "\x9a\x7f" , tt_SLEB128_known (-101) "\x9b\x7f" , tt_SLEB128_known (-100) "\x9c\x7f" , tt_SLEB128_known (-99) "\x9d\x7f" , tt_SLEB128_known (-98) "\x9e\x7f" , tt_SLEB128_known (-97) "\x9f\x7f" , tt_SLEB128_known (-94) "\xa2\x7f" , tt_SLEB128_known (-92) "\xa4\x7f" , tt_SLEB128_known (-91) "\xa5\x7f" , tt_SLEB128_known (-90) "\xa6\x7f" , tt_SLEB128_known (-88) "\xa8\x7f" , tt_SLEB128_known (-87) "\xa9\x7f" , tt_SLEB128_known (-86) "\xaa\x7f" , tt_SLEB128_known (-83) "\xad\x7f" , tt_SLEB128_known (-82) "\xae\x7f" , tt_SLEB128_known (-81) "\xaf\x7f" , tt_SLEB128_known (-78) "\xb2\x7f" , tt_SLEB128_known (-77) "\xb3\x7f" , tt_SLEB128_known (-74) "\xb6\x7f" , tt_SLEB128_known (-73) "\xb7\x7f" , tt_SLEB128_known (-71) "\xb9\x7f" , tt_SLEB128_known (-70) "\xba\x7f" , tt_SLEB128_known (-69) "\xbb\x7f" , tt_SLEB128_known (-66) "\xbe\x7f" , tt_SLEB128_known (-65) "\xbf\x7f" , tt_SLEB128_known (-64) "\x40" , tt_SLEB128_known (-63) "\x41" , tt_SLEB128_known (-62) "\x42" , tt_SLEB128_known (-59) "\x45" , tt_SLEB128_known (-58) "\x46" , tt_SLEB128_known (-57) "\x47" , tt_SLEB128_known (-56) "\x48" , tt_SLEB128_known (-55) "\x49" , tt_SLEB128_known (-54) "\x4a" , tt_SLEB128_known (-52) "\x4c" , tt_SLEB128_known (-51) "\x4d" , tt_SLEB128_known (-50) "\x4e" , tt_SLEB128_known (-49) "\x4f" , tt_SLEB128_known (-48) "\x50" , tt_SLEB128_known (-46) "\x52" , tt_SLEB128_known (-44) "\x54" , tt_SLEB128_known (-43) "\x55" , tt_SLEB128_known (-42) "\x56" , tt_SLEB128_known (-41) "\x57" , tt_SLEB128_known (-38) "\x5a" , tt_SLEB128_known (-37) "\x5b" , tt_SLEB128_known (-36) "\x5c" , tt_SLEB128_known (-33) "\x5f" , tt_SLEB128_known (-32) "\x60" , tt_SLEB128_known (-31) "\x61" , tt_SLEB128_known (-30) "\x62" , tt_SLEB128_known (-29) "\x63" , tt_SLEB128_known (-28) "\x64" , tt_SLEB128_known (-27) "\x65" , tt_SLEB128_known (-26) "\x66" , tt_SLEB128_known (-23) "\x69" , tt_SLEB128_known (-21) "\x6b" , tt_SLEB128_known (-19) "\x6d" , tt_SLEB128_known (-18) "\x6e" , tt_SLEB128_known (-17) "\x6f" , tt_SLEB128_known (-11) "\x75" , tt_SLEB128_known (-10) "\x76" , tt_SLEB128_known (-9) "\x77" , tt_SLEB128_known (-8) "\x78" , tt_SLEB128_known (-5) "\x7b" , tt_SLEB128_known (-4) "\x7c" , tt_SLEB128_known (-3) "\x7d" , tt_SLEB128_known (-1) "\x7f" , tt_SLEB128_known 0 "\x00" , tt_SLEB128_known 1 "\x01" , tt_SLEB128_known 2 "\x02" , tt_SLEB128_known 5 "\x05" , tt_SLEB128_known 7 "\x07" , tt_SLEB128_known 10 "\x0a" , tt_SLEB128_known 12 "\x0c" , tt_SLEB128_known 13 "\x0d" , tt_SLEB128_known 14 "\x0e" , tt_SLEB128_known 15 "\x0f" , tt_SLEB128_known 16 "\x10" , tt_SLEB128_known 20 "\x14" , tt_SLEB128_known 21 "\x15" , tt_SLEB128_known 25 "\x19" , tt_SLEB128_known 26 "\x1a" , tt_SLEB128_known 27 "\x1b" , tt_SLEB128_known 28 "\x1c" , tt_SLEB128_known 30 "\x1e" , tt_SLEB128_known 31 "\x1f" , tt_SLEB128_known 32 "\x20" , tt_SLEB128_known 34 "\x22" , tt_SLEB128_known 36 "\x24" , tt_SLEB128_known 38 "\x26" , tt_SLEB128_known 41 "\x29" , tt_SLEB128_known 42 "\x2a" , tt_SLEB128_known 44 "\x2c" , tt_SLEB128_known 45 "\x2d" , tt_SLEB128_known 46 "\x2e" , tt_SLEB128_known 48 "\x30" , tt_SLEB128_known 49 "\x31" , tt_SLEB128_known 50 "\x32" , tt_SLEB128_known 52 "\x34" , tt_SLEB128_known 53 "\x35" , tt_SLEB128_known 54 "\x36" , tt_SLEB128_known 55 "\x37" , tt_SLEB128_known 56 "\x38" , tt_SLEB128_known 58 "\x3a" , tt_SLEB128_known 61 "\x3d" , tt_SLEB128_known 62 "\x3e" , tt_SLEB128_known 63 "\x3f" , tt_SLEB128_known 66 "\xc2\x00" , tt_SLEB128_known 69 "\xc5\x00" , tt_SLEB128_known 70 "\xc6\x00" , tt_SLEB128_known 71 "\xc7\x00" , tt_SLEB128_known 74 "\xca\x00" , tt_SLEB128_known 76 "\xcc\x00" , tt_SLEB128_known 77 "\xcd\x00" , tt_SLEB128_known 78 "\xce\x00" , tt_SLEB128_known 79 "\xcf\x00" , tt_SLEB128_known 80 "\xd0\x00" , tt_SLEB128_known 81 "\xd1\x00" , tt_SLEB128_known 83 "\xd3\x00" , tt_SLEB128_known 84 "\xd4\x00" , tt_SLEB128_known 85 "\xd5\x00" , tt_SLEB128_known 86 "\xd6\x00" , tt_SLEB128_known 89 "\xd9\x00" , tt_SLEB128_known 90 "\xda\x00" , tt_SLEB128_known 92 "\xdc\x00" , tt_SLEB128_known 94 "\xde\x00" , tt_SLEB128_known 96 "\xe0\x00" , tt_SLEB128_known 98 "\xe2\x00" , tt_SLEB128_known 99 "\xe3\x00" , tt_SLEB128_known 100 "\xe4\x00" , tt_SLEB128_known 101 "\xe5\x00" , tt_SLEB128_known 103 "\xe7\x00" , tt_SLEB128_known 107 "\xeb\x00" , tt_SLEB128_known 108 "\xec\x00" , tt_SLEB128_known 111 "\xef\x00" , tt_SLEB128_known 113 "\xf1\x00" , tt_SLEB128_known 115 "\xf3\x00" , tt_SLEB128_known 116 "\xf4\x00" , tt_SLEB128_known 117 "\xf5\x00" , tt_SLEB128_known 119 "\xf7\x00" , tt_SLEB128_known 127 "\xff\x00" , tt_SLEB128_known 233 "\xe9\x01" , tt_SLEB128_known 445 "\xbd\x03" , tt_SLEB128_known 634 "\xfa\x04" , tt_SLEB128_known 800 "\xa0\x06" , tt_SLEB128_known 1128 "\xe8\x08" , tt_SLEB128_known 1312 "\xa0\x0a" , tt_SLEB128_known 1689 "\x99\x0d" , tt_SLEB128_known 1748 "\xd4\x0d" , tt_SLEB128_known 1819 "\x9b\x0e" , tt_SLEB128_known 2021 "\xe5\x0f" , tt_SLEB128_known 2098 "\xb2\x10" , tt_SLEB128_known 2136 "\xd8\x10" , tt_SLEB128_known 2399 "\xdf\x12" , tt_SLEB128_known 2480 "\xb0\x13" , tt_SLEB128_known 2681 "\xf9\x14" , tt_SLEB128_known 2762 "\xca\x15" , tt_SLEB128_known 2836 "\x94\x16" , tt_SLEB128_known 2918 "\xe6\x16" , tt_SLEB128_known 2960 "\x90\x17" , tt_SLEB128_known 3004 "\xbc\x17" , tt_SLEB128_known 3059 "\xf3\x17" , tt_SLEB128_known 3536 "\xd0\x1b" , tt_SLEB128_known 3544 "\xd8\x1b" , tt_SLEB128_known 3714 "\x82\x1d" , tt_SLEB128_known 4088 "\xf8\x1f" , tt_SLEB128_known 4298 "\xca\x21" , tt_SLEB128_known 4597 "\xf5\x23" , tt_SLEB128_known 5055 "\xbf\x27" , tt_SLEB128_known 5401 "\x99\x2a" , tt_SLEB128_known 6328 "\xb8\x31" , tt_SLEB128_known 6625 "\xe1\x33" , tt_SLEB128_known 6812 "\x9c\x35" , tt_SLEB128_known 6818 "\xa2\x35" , tt_SLEB128_known 6971 "\xbb\x36" , tt_SLEB128_known 7495 "\xc7\x3a" , tt_SLEB128_known 7561 "\x89\x3b" , tt_SLEB128_known 8393 "\xc9\xc1\x00" , tt_SLEB128_known 8754 "\xb2\xc4\x00" , tt_SLEB128_known 8787 "\xd3\xc4\x00" , tt_SLEB128_known 9416 "\xc8\xc9\x00" , tt_SLEB128_known 9632 "\xa0\xcb\x00" , tt_SLEB128_known 9787 "\xbb\xcc\x00" , tt_SLEB128_known 9882 "\x9a\xcd\x00" , tt_SLEB128_known 10052 "\xc4\xce\x00" , tt_SLEB128_known 10097 "\xf1\xce\x00" , tt_SLEB128_known 10476 "\xec\xd1\x00" , tt_SLEB128_known 11119 "\xef\xd6\x00" , tt_SLEB128_known 11817 "\xa9\xdc\x00" , tt_SLEB128_known 11834 "\xba\xdc\x00" , tt_SLEB128_known 12060 "\x9c\xde\x00" , tt_SLEB128_known 12224 "\xc0\xdf\x00" , tt_SLEB128_known 12336 "\xb0\xe0\x00" , tt_SLEB128_known 12460 "\xac\xe1\x00" , tt_SLEB128_known 13280 "\xe0\xe7\x00" , tt_SLEB128_known 13399 "\xd7\xe8\x00" , tt_SLEB128_known 13532 "\xdc\xe9\x00" , tt_SLEB128_known 13550 "\xee\xe9\x00" , tt_SLEB128_known 13564 "\xfc\xe9\x00" , tt_SLEB128_known 13591 "\x97\xea\x00" , tt_SLEB128_known 13904 "\xd0\xec\x00" , tt_SLEB128_known 14459 "\xfb\xf0\x00" , tt_SLEB128_known 14630 "\xa6\xf2\x00" , tt_SLEB128_known 14725 "\x85\xf3\x00" , tt_SLEB128_known 14804 "\xd4\xf3\x00" , tt_SLEB128_known 14842 "\xfa\xf3\x00" , tt_SLEB128_known 15847 "\xe7\xfb\x00" , tt_SLEB128_known 16765 "\xfd\x82\x01" , tt_SLEB128_known 16861 "\xdd\x83\x01" , tt_SLEB128_known 17445 "\xa5\x88\x01" , tt_SLEB128_known 17461 "\xb5\x88\x01" , tt_SLEB128_known 17921 "\x81\x8c\x01" , tt_SLEB128_known 17927 "\x87\x8c\x01" , tt_SLEB128_known 18058 "\x8a\x8d\x01" , tt_SLEB128_known 18354 "\xb2\x8f\x01" , tt_SLEB128_known 18786 "\xe2\x92\x01" , tt_SLEB128_known 19166 "\xde\x95\x01" , tt_SLEB128_known 19211 "\x8b\x96\x01" , tt_SLEB128_known 19835 "\xfb\x9a\x01" , tt_SLEB128_known 19838 "\xfe\x9a\x01" , tt_SLEB128_known 19925 "\xd5\x9b\x01" , tt_SLEB128_known 20455 "\xe7\x9f\x01" , tt_SLEB128_known 21115 "\xfb\xa4\x01" , tt_SLEB128_known 21889 "\x81\xab\x01" , tt_SLEB128_known 21949 "\xbd\xab\x01" , tt_SLEB128_known 22522 "\xfa\xaf\x01" , tt_SLEB128_known 22666 "\x8a\xb1\x01" , tt_SLEB128_known 23093 "\xb5\xb4\x01" , tt_SLEB128_known 23293 "\xfd\xb5\x01" , tt_SLEB128_known 23336 "\xa8\xb6\x01" , tt_SLEB128_known 23957 "\x95\xbb\x01" , tt_SLEB128_known 23972 "\xa4\xbb\x01" , tt_SLEB128_known 24607 "\x9f\xc0\x01" , tt_SLEB128_known 24909 "\xcd\xc2\x01" , tt_SLEB128_known 25267 "\xb3\xc5\x01" , tt_SLEB128_known 25342 "\xfe\xc5\x01" , tt_SLEB128_known 25639 "\xa7\xc8\x01" , tt_SLEB128_known 25913 "\xb9\xca\x01" , tt_SLEB128_known 26116 "\x84\xcc\x01" , tt_SLEB128_known 26424 "\xb8\xce\x01" , tt_SLEB128_known 26852 "\xe4\xd1\x01" , tt_SLEB128_known 27098 "\xda\xd3\x01" , tt_SLEB128_known 27443 "\xb3\xd6\x01" , tt_SLEB128_known 27621 "\xe5\xd7\x01" , tt_SLEB128_known 28072 "\xa8\xdb\x01" , tt_SLEB128_known 28570 "\x9a\xdf\x01" , tt_SLEB128_known 28648 "\xe8\xdf\x01" , tt_SLEB128_known 28848 "\xb0\xe1\x01" , tt_SLEB128_known 29009 "\xd1\xe2\x01" , tt_SLEB128_known 29287 "\xe7\xe4\x01" , tt_SLEB128_known 29302 "\xf6\xe4\x01" , tt_SLEB128_known 29457 "\x91\xe6\x01" , tt_SLEB128_known 29483 "\xab\xe6\x01" , tt_SLEB128_known 29549 "\xed\xe6\x01" , tt_SLEB128_known 29595 "\x9b\xe7\x01" , tt_SLEB128_known 29674 "\xea\xe7\x01" , tt_SLEB128_known 29865 "\xa9\xe9\x01" , tt_SLEB128_known 30181 "\xe5\xeb\x01" , tt_SLEB128_known 30262 "\xb6\xec\x01" , tt_SLEB128_known 30373 "\xa5\xed\x01" , tt_SLEB128_known 30728 "\x88\xf0\x01" , tt_SLEB128_known 30845 "\xfd\xf0\x01" , tt_SLEB128_known 31065 "\xd9\xf2\x01" , tt_SLEB128_known 31185 "\xd1\xf3\x01" , tt_SLEB128_known 31251 "\x93\xf4\x01" , tt_SLEB128_known 31526 "\xa6\xf6\x01" , tt_SLEB128_known 31546 "\xba\xf6\x01" , tt_SLEB128_known 31757 "\x8d\xf8\x01" , tt_SLEB128_known 31828 "\xd4\xf8\x01" , tt_SLEB128_known 31920 "\xb0\xf9\x01" , tt_SLEB128_known 31972 "\xe4\xf9\x01" , tt_SLEB128_known 32327 "\xc7\xfc\x01" , tt_SLEB128_known 32527 "\x8f\xfe\x01" , tt_SLEB128_known 32557 "\xad\xfe\x01" , tt_SLEB128_known 32584 "\xc8\xfe\x01" , tt_SLEB128_known 30820535 "\xb7\x91\xd9\x0e" , tt_SLEB128_known 54185204 "\xf4\x99\xeb\x19" , tt_SLEB128_known 54452448 "\xe0\xc1\xfb\x19" , tt_SLEB128_known 67741227 "\xab\xcc\xa6\x20" , tt_SLEB128_known 76120615 "\xa7\x84\xa6\x24" , tt_SLEB128_known 146401541 "\x85\xd2\xe7\xc5\x00" , tt_SLEB128_known 152484912 "\xb0\xf8\xda\xc8\x00" , tt_SLEB128_known 155306425 "\xb9\x93\x87\xca\x00" , tt_SLEB128_known 156723024 "\xd0\xce\xdd\xca\x00" , tt_SLEB128_known 164568219 "\x9b\xb9\xbc\xce\x00" , tt_SLEB128_known 167643376 "\xf0\x91\xf8\xcf\x00" , tt_SLEB128_known 188951315 "\x93\xd6\x8c\xda\x00" , tt_SLEB128_known 194751635 "\x93\xd9\xee\xdc\x00" , tt_SLEB128_known 203976048 "\xf0\xda\xa1\xe1\x00" , tt_SLEB128_known 219074728 "\xa8\xa1\xbb\xe8\x00" , tt_SLEB128_known 223986788 "\xe4\x88\xe7\xea\x00" , tt_SLEB128_known 228027580 "\xbc\xd9\xdd\xec\x00" , tt_SLEB128_known 240746611 "\xf3\x80\xe6\xf2\x00" , tt_SLEB128_known 290782649 "\xb9\xfb\xd3\x8a\x01" , tt_SLEB128_known 310098077 "\x9d\xf1\xee\x93\x01" , tt_SLEB128_known 312108312 "\x98\xca\xe9\x94\x01" , tt_SLEB128_known 336286145 "\xc1\xa3\xad\xa0\x01" , tt_SLEB128_known 338630976 "\xc0\xb2\xbc\xa1\x01" , tt_SLEB128_known 356371619 "\xa3\x99\xf7\xa9\x01" , tt_SLEB128_known 387032757 "\xb5\xcd\xc6\xb8\x01" , tt_SLEB128_known 392861225 "\xa9\xac\xaa\xbb\x01" , tt_SLEB128_known 398347666 "\x92\x9b\xf9\xbd\x01" , tt_SLEB128_known 432698678 "\xb6\xea\xa9\xce\x01" , tt_SLEB128_known 437455786 "\xaa\x97\xcc\xd0\x01" , tt_SLEB128_known 451723339 "\xcb\x80\xb3\xd7\x01" , tt_SLEB128_known 491059828 "\xf4\xf4\x93\xea\x01" , tt_SLEB128_known 509843088 "\x90\xad\x8e\xf3\x01" , tt_SLEB128_known 512089466 "\xfa\xba\x97\xf4\x01" , tt_SLEB128_known 512628512 "\xa0\xae\xb8\xf4\x01" , tt_SLEB128_known 531971183 "\xef\xf8\xd4\xfd\x01" , tt_SLEB128_known 549155369 "\xa9\xe4\xed\x85\x02" , tt_SLEB128_known 557139109 "\xa5\x89\xd5\x89\x02" , tt_SLEB128_known 558423016 "\xe8\xb7\xa3\x8a\x02" , tt_SLEB128_known 565707053 "\xad\x82\xe0\x8d\x02" , tt_SLEB128_known 590553306 "\xda\xc1\xcc\x99\x02" , tt_SLEB128_known 594058808 "\xb8\xbc\xa2\x9b\x02" , tt_SLEB128_known 619078172 "\x9c\xc4\x99\xa7\x02" , tt_SLEB128_known 621854289 "\xd1\xfc\xc2\xa8\x02" , tt_SLEB128_known 623600501 "\xf5\xc6\xad\xa9\x02" , tt_SLEB128_known 637003915 "\x8b\xd1\xdf\xaf\x02" , tt_SLEB128_known 638074973 "\xdd\x80\xa1\xb0\x02" , tt_SLEB128_known 645964671 "\xff\xc6\x82\xb4\x02" , tt_SLEB128_known 671205267 "\x93\x8f\x87\xc0\x02" , tt_SLEB128_known 694740715 "\xeb\xcd\xa3\xcb\x02" , tt_SLEB128_known 719627570 "\xb2\xca\x92\xd7\x02" , tt_SLEB128_known 741239109 "\xc5\xd2\xb9\xe1\x02" , tt_SLEB128_known 746718307 "\xe3\x88\x88\xe4\x02" , tt_SLEB128_known 756645306 "\xba\xfb\xe5\xe8\x02" , tt_SLEB128_known 776700162 "\x82\x82\xae\xf2\x02" , tt_SLEB128_known 793517802 "\xea\xbd\xb0\xfa\x02" , tt_SLEB128_known 795680718 "\xce\xbf\xb4\xfb\x02" , tt_SLEB128_known 801015649 "\xe1\x8e\xfa\xfd\x02" , tt_SLEB128_known 808521482 "\x8a\x9e\xc4\x81\x03" , tt_SLEB128_known 828595710 "\xfe\xbb\x8d\x8b\x03" , tt_SLEB128_known 857769296 "\xd0\x8a\x82\x99\x03" , tt_SLEB128_known 877076572 "\xdc\xc0\x9c\xa2\x03" , tt_SLEB128_known 879441342 "\xbe\xeb\xac\xa3\x03" , tt_SLEB128_known 901069894 "\xc6\xf8\xd4\xad\x03" , tt_SLEB128_known 915051381 "\xf5\xa6\xaa\xb4\x03" , tt_SLEB128_known 988137529 "\xb9\x90\x97\xd7\x03" , tt_SLEB128_known 990901136 "\x90\xe7\xbf\xd8\x03" , tt_SLEB128_known 1061928252 "\xbc\xfa\xae\xfa\x03" , tt_SLEB128_known 1090995064 "\xf8\x86\x9d\x88\x04" , tt_SLEB128_known 1118264374 "\xb6\xb8\x9d\x95\x04" , tt_SLEB128_known 1131156210 "\xf2\xa5\xb0\x9b\x04" , tt_SLEB128_known 1140825765 "\xa5\xbd\xfe\x9f\x04" , tt_SLEB128_known 1144313454 "\xee\xac\xd3\xa1\x04" , tt_SLEB128_known 1150136681 "\xe9\xe2\xb6\xa4\x04" , tt_SLEB128_known 1177334242 "\xe2\xe3\xb2\xb1\x04" , tt_SLEB128_known 1183392887 "\xf7\xc8\xa4\xb4\x04" , tt_SLEB128_known 1198250140 "\x9c\xb1\xaf\xbb\x04" , tt_SLEB128_known 1222116657 "\xb1\x8a\xe0\xc6\x04" , tt_SLEB128_known 1253387367 "\xe7\xd8\xd4\xd5\x04" , tt_SLEB128_known 1302523980 "\xcc\xe0\x8b\xed\x04" , tt_SLEB128_known 1307163713 "\xc1\xf8\xa6\xef\x04" , tt_SLEB128_known 1311105462 "\xb6\xc3\x97\xf1\x04" , tt_SLEB128_known 1317018748 "\xfc\xb8\x80\xf4\x04" , tt_SLEB128_known 1317235197 "\xfd\xd3\x8d\xf4\x04" , tt_SLEB128_known 1335418030 "\xae\xb9\xe3\xfc\x04" , tt_SLEB128_known 1349151545 "\xb9\xd6\xa9\x83\x05" , tt_SLEB128_known 1376218739 "\xf3\xdc\x9d\x90\x05" , tt_SLEB128_known 1381938156 "\xec\xe7\xfa\x92\x05" , tt_SLEB128_known 1389006397 "\xbd\x9c\xaa\x96\x05" , tt_SLEB128_known 1396236313 "\x99\xc0\xe3\x99\x05" , tt_SLEB128_known 1422044246 "\xd6\xd8\x8a\xa6\x05" , tt_SLEB128_known 1424571991 "\xd7\xfc\xa4\xa7\x05" , tt_SLEB128_known 1431634128 "\xd0\x81\xd4\xaa\x05" , tt_SLEB128_known 1449079907 "\xe3\xe8\xfc\xb2\x05" , tt_SLEB128_known 1458536356 "\xa4\xff\xbd\xb7\x05" , tt_SLEB128_known 1463843218 "\x92\xf3\x81\xba\x05" , tt_SLEB128_known 1499620392 "\xa8\xc8\x89\xcb\x05" , tt_SLEB128_known 1503705467 "\xfb\xf2\x82\xcd\x05" , tt_SLEB128_known 1519963249 "\xf1\x98\xe3\xd4\x05" , tt_SLEB128_known 1522174627 "\xa3\x95\xea\xd5\x05" , tt_SLEB128_known 1524349890 "\xc2\xf7\xee\xd6\x05" , tt_SLEB128_known 1536793596 "\xfc\xb7\xe6\xdc\x05" , tt_SLEB128_known 1546599379 "\xd3\xf7\xbc\xe1\x05" , tt_SLEB128_known 1556052618 "\x8a\xf5\xfd\xe5\x05" , tt_SLEB128_known 1590192706 "\xc2\xd4\xa1\xf6\x05" , tt_SLEB128_known 1598896974 "\xce\xf6\xb4\xfa\x05" , tt_SLEB128_known 1616941558 "\xf6\xa3\x82\x83\x06" , tt_SLEB128_known 1625170515 "\xd3\xc4\xf8\x86\x06" , tt_SLEB128_known 1637346847 "\x9f\xdc\xdf\x8c\x06" , tt_SLEB128_known 1662854158 "\x8e\xc8\xf4\x98\x06" , tt_SLEB128_known 1663241193 "\xe9\x97\x8c\x99\x06" , tt_SLEB128_known 1689481187 "\xe3\xdf\xcd\xa5\x06" , tt_SLEB128_known 1700298502 "\x86\xfe\xe1\xaa\x06" , tt_SLEB128_known 1705384384 "\xc0\xb3\x98\xad\x06" , tt_SLEB128_known 1710097269 "\xf5\x86\xb8\xaf\x06" , tt_SLEB128_known 1715726890 "\xaa\xd4\x8f\xb2\x06" , tt_SLEB128_known 1737515212 "\xcc\xc1\xc1\xbc\x06" , tt_SLEB128_known 1761092444 "\xdc\xc6\xe0\xc7\x06" , tt_SLEB128_known 1866406765 "\xed\xb6\xfc\xf9\x06" , tt_SLEB128_known 1906660898 "\xa2\xac\x95\x8d\x07" , tt_SLEB128_known 1907500476 "\xbc\xcb\xc8\x8d\x07" , tt_SLEB128_known 1961805726 "\x9e\x8f\xbb\xa7\x07" , tt_SLEB128_known 2018201191 "\xe7\x9c\xad\xc2\x07" , tt_SLEB128_known 2104989848 "\x98\xb1\xde\xeb\x07" , tt_SLEB128_known 2141974662 "\x86\xe1\xaf\xfd\x07" , tt_SLEB128_known 77897111127919137 "\xa1\x94\xbc\xae\xa8\xe0\xaf\x8a\x01" , tt_SLEB128_known 262231303773617553 "\x91\xfb\xa7\xf3\xb3\xbf\xe8\xd1\x03" , tt_SLEB128_known 273922687615936246 "\xf6\xcd\x92\xda\xba\xe7\xca\xe6\x03" , tt_SLEB128_known 300937269882522802 "\xb2\x99\x98\xf8\xa3\x9b\xc9\x96\x04" , tt_SLEB128_known 536630527899226143 "\x9f\xa0\xc1\xb8\xf3\xd3\x9f\xb9\x07" , tt_SLEB128_known 752843520619383432 "\x88\x95\xe4\xcf\x97\xe6\xa8\xb9\x0a" , tt_SLEB128_known 762388058533688319 "\xff\xe7\x99\x8f\xe6\xfc\xa2\xca\x0a" , tt_SLEB128_known 789471440916181149 "\x9d\xe1\xff\xe0\xfb\x82\xb1\xfa\x0a" , tt_SLEB128_known 792640191116149912 "\x98\x89\xb4\x91\xde\xc1\x81\x80\x0b" , tt_SLEB128_known 821061612412789019 "\x9b\xc2\xcb\x94\xfb\xe5\xbf\xb2\x0b" , tt_SLEB128_known 851217854692026439 "\xc7\xd0\x8d\xfb\x8f\xc4\x88\xe8\x0b" , tt_SLEB128_known 1163598511564577811 "\x93\xb8\xeb\xb7\xe6\xd5\xfb\x92\x10" , tt_SLEB128_known 1315442208010158808 "\xd8\x85\x81\xd8\xff\xf6\xd8\xa0\x12" , tt_SLEB128_known 1331218022305811852 "\x8c\x9b\x8b\xd1\xcf\xf7\xdb\xbc\x12" , tt_SLEB128_known 1415057224764416882 "\xf2\xc6\xbb\x97\xc7\xe1\xd2\xd1\x13" , tt_SLEB128_known 1431719763524378113 "\x81\xbc\x9b\x96\xa1\xb1\x9f\xef\x13" , tt_SLEB128_known 1532600219281232624 "\xf0\xa5\xc6\xa7\xf8\xf8\xb8\xa2\x15" , tt_SLEB128_known 1567284526904680904 "\xc8\xc3\xfa\x80\x93\x9f\x87\xe0\x15" , tt_SLEB128_known 1617000314023815493 "\xc5\xd2\xd6\xb8\xfe\xa6\xaf\xb8\x16" , tt_SLEB128_known 1633954117999019776 "\x80\x8e\xf9\xf4\xcf\x93\xbe\xd6\x16" , tt_SLEB128_known 1684447867088912431 "\xaf\x80\xff\xc3\x91\x8d\x97\xb0\x17" , tt_SLEB128_known 1811240089168032013 "\x8d\xe2\xba\xae\xbc\xa8\xb4\x91\x19" , tt_SLEB128_known 1845000590005876091 "\xfb\xea\xbe\xcd\xae\xc8\xb0\xcd\x19" , tt_SLEB128_known 1850424091051842564 "\x84\xb8\xe1\xb7\x82\xdd\x81\xd7\x19" , tt_SLEB128_known 1990638717472956861 "\xbd\xc3\xf5\xf8\xdd\xeb\x8a\xd0\x1b" , tt_SLEB128_known 2031976714474610935 "\xf7\xc1\xff\x90\xe5\x81\xc2\x99\x1c" , tt_SLEB128_known 2052987474778287514 "\x9a\xdb\xf1\xd3\xb2\xa7\xeb\xbe\x1c" , tt_SLEB128_known 2174700203147877119 "\xff\xb5\xe5\xec\x80\xca\x85\x97\x1e" , tt_SLEB128_known 2238228741409014760 "\xe8\x87\x84\x8e\xe8\xa5\xf2\x87\x1f" , tt_SLEB128_known 2385151848139604305 "\xd1\x82\xe9\x9d\x80\xdf\xf0\x8c\x21" , tt_SLEB128_known 2423010991394925670 "\xe6\xd8\xd8\xa7\x8b\xf5\x90\xd0\x21" , tt_SLEB128_known 2481936201139769293 "\xcd\x9f\xf9\xc0\xb3\xfa\xe6\xb8\x22" , tt_SLEB128_known 2528043057117208223 "\x9f\xbd\xf4\xe2\xc2\xb8\xda\x8a\x23" , tt_SLEB128_known 2599353785506738716 "\x9c\xe4\xc8\xb5\xef\xcf\xb0\x89\x24" , tt_SLEB128_known 2617408687338066000 "\xd0\xa0\xba\x86\xd6\xea\xb9\xa9\x24" , tt_SLEB128_known 2654386888249066281 "\xa9\x86\xa9\x94\xfb\xd9\x91\xeb\x24" , tt_SLEB128_known 2681377212024914560 "\x80\x85\xca\xbc\xe2\xcb\x8a\x9b\x25" , tt_SLEB128_known 2686683925822690212 "\xa4\xa7\xa7\xf3\xbb\x99\xc1\xa4\x25" , tt_SLEB128_known 2771609536681578438 "\xc6\x9f\xf6\x8f\x86\x86\xaf\xbb\x26" , tt_SLEB128_known 2787605036686649034 "\xca\xcd\xb0\x8e\xaf\x80\xe4\xd7\x26" , tt_SLEB128_known 2847422287175818170 "\xba\xb7\x94\x85\xbe\xef\x84\xc2\x27" , tt_SLEB128_known 2889241843213539345 "\x91\xb0\xc0\xb7\xe0\xc4\xa9\x8c\x28" , tt_SLEB128_known 2921997595792207886 "\x8e\xe0\xf5\xdd\xcf\xaa\xc1\xc6\x28" , tt_SLEB128_known 2922611585456332576 "\xa0\xbe\xc3\xbc\x89\xf8\xcc\xc7\x28" , tt_SLEB128_known 2954022553703925616 "\xf0\x8e\x8f\xe0\xc8\xfb\xb2\xff\x28" , tt_SLEB128_known 3037843567655826805 "\xf5\xea\xd2\xea\x92\xd4\xa5\x94\x2a" , tt_SLEB128_known 3281306703837989327 "\xcf\x93\xfc\x8a\xfe\xe1\xe2\xc4\x2d" , tt_SLEB128_known 3328552264639739130 "\xfa\xe9\xb1\xb1\xe3\x94\xd9\x98\x2e" , tt_SLEB128_known 3508229690431827270 "\xc6\xda\xab\xc5\x8e\x8a\xef\xd7\x30" , tt_SLEB128_known 3579447585051565989 "\xa5\xbf\x83\xb9\xd2\x93\xb0\xd6\x31" , tt_SLEB128_known 3582844041345008027 "\x9b\x83\xfa\x8f\xc4\xb5\xb4\xdc\x31" , tt_SLEB128_known 3591864919434541601 "\xa1\xf4\xd4\xe0\xd1\xc3\xb7\xec\x31" , tt_SLEB128_known 3600247828980990210 "\x82\x82\xa2\xae\xb5\xca\xa9\xfb\x31" , tt_SLEB128_known 3623670621805681668 "\x84\xb8\xfc\x9d\xb4\xa7\xf7\xa4\x32" , tt_SLEB128_known 3644048037985052406 "\xf6\xcd\xbb\x84\xa3\xcc\x90\xc9\x32" , tt_SLEB128_known 3648434166598593390 "\xee\xd6\x87\xb4\xb5\xf1\xf5\xd0\x32" , tt_SLEB128_known 3741708248961789441 "\x81\xdc\x90\xc4\xbf\xfa\xcd\xf6\x33" , tt_SLEB128_known 3776760975322363109 "\xe5\xe9\x96\xfd\x8c\x83\xf0\xb4\x34" , tt_SLEB128_known 3856595619634880935 "\xa7\xc3\xa8\xf5\x86\xa9\xd8\xc2\x35" , tt_SLEB128_known 3944792956832413902 "\xce\xf1\xd5\xc3\xb3\x89\xae\xdf\x36" , tt_SLEB128_known 4103161484643623377 "\xd1\xc3\xfd\xe1\x97\xf4\xd6\xf8\x38" , tt_SLEB128_known 4132753277204215288 "\xf8\xeb\xda\xc0\xd9\xa6\x9f\xad\x39" , tt_SLEB128_known 4145633508785338927 "\xaf\xf4\xec\xa0\xe3\xf6\x8f\xc4\x39" , tt_SLEB128_known 4191926494068517598 "\xde\xd5\x82\x9c\xfc\xdd\xad\x96\x3a" , tt_SLEB128_known 4199347535970806966 "\xb6\xd9\xce\xcf\xdb\x8a\xc5\xa3\x3a" , tt_SLEB128_known 4419048529340123694 "\xae\x94\x9f\xe4\x96\xa7\xe7\xa9\x3d" , tt_SLEB128_known 4455083374148249713 "\xf1\xd0\xeb\xc6\x98\xd7\xe8\xe9\x3d" , tt_SLEB128_known 4556141255674613490 "\xf2\x9d\xf3\x97\xd2\xca\xaa\x9d\x3f" , tt_SLEB128_known 4901557005331034230 "\xf6\xe0\xd5\xa8\x87\x84\xf5\x82\xc4\x00" , tt_SLEB128_known 4953286460025105580 "\xac\xd9\xb1\x84\xab\xf9\xe6\xde\xc4\x00" , tt_SLEB128_known 5045167886354394053 "\xc5\xd7\xf2\x92\xe5\xae\x82\x82\xc6\x00" , tt_SLEB128_known 5096346593941490257 "\xd1\x94\x9e\x81\x9c\x87\xf7\xdc\xc6\x00" , tt_SLEB128_known 5110716740488584708 "\x84\xbc\xdb\xc3\xc3\xb9\xba\xf6\xc6\x00" , tt_SLEB128_known 5251537772479181262 "\xce\xe3\xab\xe9\xfb\xb8\xcd\xf0\xc8\x00" , tt_SLEB128_known 5424495271496989819 "\xfb\xf8\xf4\xfa\xd8\xb6\xeb\xa3\xcb\x00" , tt_SLEB128_known 5637155912369669356 "\xec\x89\xa6\xa2\xf7\xed\xcc\x9d\xce\x00" , tt_SLEB128_known 5656138666606963108 "\xa4\xd3\xd6\xbb\xe5\x84\xa9\xbf\xce\x00" , tt_SLEB128_known 5696576265281547238 "\xe6\xd7\x9c\xc0\xe7\xbd\x93\x87\xcf\x00" , tt_SLEB128_known 5822603727664217699 "\xe3\xfc\xa9\xba\xda\xe7\x82\xe7\xd0\x00" , tt_SLEB128_known 5861396459144691389 "\xbd\xfd\xb4\xd8\xe4\xa0\xf7\xab\xd1\x00" , tt_SLEB128_known 5872561561198404427 "\xcb\xc6\xe0\x86\x83\xf4\xe1\xbf\xd1\x00" , tt_SLEB128_known 5960960492615612805 "\x85\xf3\xf6\xd3\xc4\xbf\xe5\xdc\xd2\x00" , tt_SLEB128_known 5982527046032636480 "\xc0\xf4\xc4\xef\xec\x94\x8d\x83\xd3\x00" , tt_SLEB128_known 5995002221617381565 "\xbd\x81\xba\xb9\x9f\xd8\xa1\x99\xd3\x00" , tt_SLEB128_known 6041003950471360021 "\x95\xdc\xce\xd4\xe1\xa2\xfd\xea\xd3\x00" , tt_SLEB128_known 6078236340301084731 "\xbb\xf0\x90\xa4\xf6\xf7\x8e\xad\xd4\x00" , tt_SLEB128_known 6203547570860777324 "\xec\xbe\x93\xe3\xdd\xb4\xdb\x8b\xd6\x00" , tt_SLEB128_known 6355660132335479029 "\xf5\xd1\xdf\xa7\xf7\xe6\xf5\x99\xd8\x00" , tt_SLEB128_known 6387328730631759352 "\xf8\xcb\xcf\xa7\xb9\xb4\x96\xd2\xd8\x00" , tt_SLEB128_known 6394692322857845157 "\xa5\x83\xf0\xfe\x97\xd9\xa0\xdf\xd8\x00" , tt_SLEB128_known 6425964547531840549 "\xa5\xb8\x8e\x97\xdb\x96\xe7\x96\xd9\x00" , tt_SLEB128_known 6473112946808070161 "\x91\xc0\xe8\xcb\xdd\xbd\xc7\xea\xd9\x00" , tt_SLEB128_known 6485808696913935799 "\xb7\xfb\xc6\xa5\xd8\x94\x8e\x81\xda\x00" , tt_SLEB128_known 6571515130884375421 "\xfd\x86\xdf\xa3\x9b\xc6\xad\x99\xdb\x00" , tt_SLEB128_known 6638965462576089153 "\xc1\x90\xbd\xc7\x9d\xfd\x95\x91\xdc\x00" , tt_SLEB128_known 6890775738228699463 "\xc7\xe2\x81\xc0\xe6\x80\xbd\xd0\xdf\x00" , tt_SLEB128_known 6914526363952000407 "\x97\xdb\xba\x8b\xfe\xa2\xd5\xfa\xdf\x00" , tt_SLEB128_known 6933097952413144173 "\xed\xa8\xcb\xb4\xac\xfb\xd3\x9b\xe0\x00" , tt_SLEB128_known 7032181223721684836 "\xe4\x9e\xe9\xe0\x89\xf2\xd4\xcb\xe1\x00" , tt_SLEB128_known 7162922528771624224 "\xa0\x9a\xcd\x88\xed\x82\xf4\xb3\xe3\x00" , tt_SLEB128_known 7205322524829226382 "\x8e\xab\xc4\x84\x93\xd5\x9c\xff\xe3\x00" , tt_SLEB128_known 7238057873582600864 "\xa0\xe5\xf0\x94\x98\xe9\xaf\xb9\xe4\x00" , tt_SLEB128_known 7256629043231079705 "\x99\xfa\xc8\xa4\xae\xb5\xae\xda\xe4\x00" , tt_SLEB128_known 7357901855678698491 "\xfb\xa7\xaa\xff\x8f\x98\xa1\x8e\xe6\x00" , tt_SLEB128_known 7415482293595141532 "\x9c\xeb\xbf\xdf\xb6\xbb\xc5\xf4\xe6\x00" , tt_SLEB128_known 7464470122701447342 "\xae\xc1\x8b\xa1\xf3\x80\xc8\xcb\xe7\x00" , tt_SLEB128_known 7539467086860256510 "\xfe\x89\xb8\xa0\xea\xab\xe4\xd0\xe8\x00" , tt_SLEB128_known 7600297399029821247 "\xbf\xde\xfd\x83\xf6\xc6\xeb\xbc\xe9\x00" , tt_SLEB128_known 7617806199745078829 "\xad\xcc\xcb\xbc\x8b\xcc\xf8\xdb\xe9\x00" , tt_SLEB128_known 7767893289178425805 "\xcd\xd3\xfb\xd4\xa5\xb9\xc6\xe6\xeb\x00" , tt_SLEB128_known 7824309355749348443 "\xdb\xa8\xd2\x91\xf7\xfc\xe1\xca\xec\x00" , tt_SLEB128_known 7858694681180540595 "\xb3\x9d\x92\xb0\xce\xa5\xec\x87\xed\x00" , tt_SLEB128_known 7865586331763820127 "\xdf\x8c\xcd\xb7\x85\xa3\x8b\x94\xed\x00" , tt_SLEB128_known 7867379394904051495 "\xa7\x9e\xef\x93\x86\xfc\xa2\x97\xed\x00" , tt_SLEB128_known 7872131855186111995 "\xfb\xdb\x9e\xab\xec\xc6\xdb\x9f\xed\x00" , tt_SLEB128_known 8153330444982341041 "\xb1\x9b\xb3\xec\xf6\xda\x9c\x93\xf1\x00" , tt_SLEB128_known 8169316313223349691 "\xbb\x8b\xed\xdb\xf6\xbc\xcf\xaf\xf1\x00" , tt_SLEB128_known 8208923558131629487 "\xaf\xfb\x95\xf6\xbb\x8f\xfd\xf5\xf1\x00" , tt_SLEB128_known 8268349867323678312 "\xe8\xbc\xe7\x83\xd9\x8c\xc5\xdf\xf2\x00" , tt_SLEB128_known 8300371820353604781 "\xad\x99\xdb\xfe\x97\x86\xb6\x98\xf3\x00" , tt_SLEB128_known 8446794406616112204 "\xcc\xb8\xf0\x88\xa8\xd8\xc2\x9c\xf5\x00" , tt_SLEB128_known 8448831201312377775 "\xaf\x97\xd8\xcb\xeb\xe6\x91\xa0\xf5\x00" , tt_SLEB128_known 8565431986913687688 "\x88\xf1\x88\xfe\xaa\xe0\xa1\xef\xf6\x00" , tt_SLEB128_known 8629983544958868022 "\xb6\xb4\xf5\xf5\xf7\x89\xf7\xe1\xf7\x00" , tt_SLEB128_known 8668207299393572773 "\xa5\x9f\xb5\xbe\xcd\x93\xea\xa5\xf8\x00" , tt_SLEB128_known 8714610830351436396 "\xec\x94\xfa\x96\x8d\x8c\xa1\xf8\xf8\x00" , tt_SLEB128_known 8785404403908288579 "\xc3\xc0\xec\xf8\xa1\xd8\x81\xf6\xf9\x00" , tt_SLEB128_known 8843802306698213837 "\xcd\xf3\x9b\xd4\xf6\xea\xdf\xdd\xfa\x00" , tt_SLEB128_known 8850640218143925141 "\x95\xc7\x84\xea\xab\xcc\xf2\xe9\xfa\x00" , tt_SLEB128_known 8920698040007351562 "\x8a\xba\xa5\xf9\xa7\xf3\xab\xe6\xfb\x00" , tt_SLEB128_known 8923616810142251375 "\xef\xf2\xee\x81\xda\xc6\xc3\xeb\xfb\x00" , tt_SLEB128_known 9028981872620672023 "\x97\xa8\xfc\x87\xcf\xe5\xd8\xa6\xfd\x00" , tt_SLEB128_known 9040127731630765776 "\xd0\xed\x89\xc0\xe7\x88\xbf\xba\xfd\x00" , tt_SLEB128_known 9097620239540597421 "\xad\xe5\xe2\xb9\x81\xad\xcf\xa0\xfe\x00" , tt_SLEB128_known 9159289276857505834 "\xaa\xb0\x8b\xf1\x9b\xa2\x95\x8e\xff\x00" ] , testGroup "Round trip" [ testProperty "putInt8" $ property $ do n <- forAll $ Gen.integral Range.constantBounded propDecSLEB128 n (enc (S.putInt8 n)) , testProperty "putInt16" $ property $ do n <- forAll $ Gen.integral Range.constantBounded propDecSLEB128 n (enc (S.putInt16 n)) , testProperty "putInt32" $ property $ do n <- forAll $ Gen.integral Range.constantBounded propDecSLEB128 n (enc (S.putInt32 n)) , testProperty "putInt64" $ property $ do n <- forAll $ Gen.integral Range.constantBounded propDecSLEB128 n (enc (S.putInt64 n)) , testProperty "putInt" $ property $ do n <- forAll $ Gen.integral Range.constantBounded propDecSLEB128 n (enc (S.putInt n)) , testProperty "putInteger" $ property $ do i <- forAll $ Gen.integral rangeInteger512 propDecSLEB128 i (enc (S.putInteger i)) , testProperty "putWord8" $ property $ do n <- forAll $ Gen.integral Range.constantBounded propDecSLEB128 n (enc (S.putWord8 n)) , testProperty "putWord16" $ property $ do n <- forAll $ Gen.integral Range.constantBounded propDecSLEB128 n (enc (S.putWord16 n)) , testProperty "putWord32" $ property $ do n <- forAll $ Gen.integral Range.constantBounded propDecSLEB128 n (enc (S.putWord32 n)) , testProperty "putWord64" $ property $ do n <- forAll $ Gen.integral Range.constantBounded propDecSLEB128 n (enc (S.putWord64 n)) , testProperty "putWord" $ property $ do n <- forAll $ Gen.integral Range.constantBounded propDecSLEB128 n (enc (S.putWord n)) , testProperty "putNatural" $ property $ do n <- forAll $ Gen.integral rangeNatural512 propDecSLEB128 n (enc (S.putNatural n)) ] ] tt_SLEB128_known :: Integer -> BL.ByteString -> TestTree tt_SLEB128_known i bl = testGroup (show i) [ testCase "put" $ enc (S.putInteger i) @?= bl , testCase "get" $ assertDecSLEB128 i bl ] tt_SLEB128_Scientific :: TestTree tt_SLEB128_Scientific = testGroup "SLEB128/Scientific" [ testProperty "roundtrip" $ property $ do n <- forAll genScientificDefault Right n === dec (S.getScientific 16) (enc (S.putScientific n)) , testProperty "same as Fixed E0" $ property $ do f <- forAll $ genFixedDefault @E0 let s = realToFrac f Right f === dec (S.getFixed 16) (enc (S.putFixed f)) Right s === dec (S.getScientific 16) (enc (S.putFixed f)) Right f === dec (S.getFixed 16) (enc (S.putScientific s)) , testProperty "same as Fixed E1" $ property $ do f <- forAll $ genFixedDefault @E1 let s = realToFrac f Right f === dec (S.getFixed 16) (enc (S.putFixed f)) Right s === dec (S.getScientific 16) (enc (S.putFixed f)) Right f === dec (S.getFixed 16) (enc (S.putScientific s)) , testProperty "same as Fixed E9" $ property $ do f <- forAll $ genFixedDefault @E9 let s = realToFrac f Right f === dec (S.getFixed 16) (enc (S.putFixed f)) Right s === dec (S.getScientific 16) (enc (S.putFixed f)) Right f === dec (S.getFixed 16) (enc (S.putScientific s)) , tk 0 0 "\x00" , tk 0 1 "\x00" , tk 0 (-1) "\x00" , tk 1 0 "\x01\x00" , tk 1 1 "\x01\x02" , tk 1 2 "\x01\x04" , tk 1 3 "\x01\x06" , tk 1 (-1) "\x01\x7e" , tk 1 (-2) "\x01\x7c" , tk 1 (-3) "\x01\x7a" , tk (-1) 0 "\x01\x01" , tk (-1) 1 "\x01\x03" , tk (-1) 2 "\x01\x05" , tk (-1) 3 "\x01\x07" , tk (-1) (-1) "\x01\x7f" , tk (-1) (-2) "\x01\x7d" , tk (-1) (-2) "\x01\x7d" , tk (-1) (-3) "\x01\x7b" , tk 10 1 "\x01\x04" , tk 10 2 "\x01\x06" , tk 10 (-1) "\x01\x00" , tk 10 (-2) "\x01\x7e" , tk (-10) 1 "\x01\x05" , tk (-10) 2 "\x01\x07" , tk (-10) (-1) "\x01\x01" , tk (-10) (-2) "\x01\x7f" ] where tk :: Integer -> Int -> BL.ByteString -> TestTree tk c e bl = testGroup (show c <> "e" <> show e) [ testCase "put" $ enc (S.putScientific (Sci.scientific c e)) @?= bl , testCase "get" $ dec (S.getScientific 15) bl @?= Right (Sci.scientific c e) ] tt_SLEB128_Rational :: TestTree tt_SLEB128_Rational = testGroup "SLEB128/Rational" [ testProperty "roundtrip" $ property $ do n <- forAll genRationalDefault Right n === dec (S.getRational 16) (enc (S.putRational n)) , tk 0 1 "\x00" , tk 0 (-1) "\x00" , tk 1 1 "\x01\x00\x00\x00" , tk 1 2 "\x01\x00\x01\x00" , tk 1 3 "\x01\x00\x02\x00" , tk 2 2 "\x01\x00\x00\x00" , tk 2 4 "\x01\x00\x01\x00" , tk 2 6 "\x01\x00\x02\x00" , tk 1 (-1) "\x01\x7f\x00\x00" , tk 1 (-2) "\x01\x7f\x01\x00" , tk 1 (-3) "\x01\x7f\x02\x00" , tk 2 (-2) "\x01\x7f\x00\x00" , tk 2 (-4) "\x01\x7f\x01\x00" , tk 2 (-6) "\x01\x7f\x02\x00" , tk (-1) 1 "\x01\x7f\x00\x00" , tk (-1) 2 "\x01\x7f\x01\x00" , tk (-1) 3 "\x01\x7f\x02\x00" , tk (-2) 2 "\x01\x7f\x00\x00" , tk (-2) 4 "\x01\x7f\x01\x00" , tk (-2) 6 "\x01\x7f\x02\x00" , tk (-1) (-1) "\x01\x00\x00\x00" , tk (-1) (-2) "\x01\x00\x01\x00" , tk (-1) (-3) "\x01\x00\x02\x00" , tk (-2) (-2) "\x01\x00\x00\x00" , tk (-2) (-4) "\x01\x00\x01\x00" , tk (-2) (-6) "\x01\x00\x02\x00" ] where tk :: Integer -> Integer -> BL.ByteString -> TestTree tk n d bl = testGroup (show n <> ":%" <> show d) [ testCase "put" $ enc (S.putRational (n :% d)) @?= bl , testCase "get" $ dec (S.getRational 10) bl @?= Right (n % d) ] propDecULEB128 :: (Integral a, Bits a, MonadTest m) => a -> BL.ByteString -> m () propDecULEB128 = decULEB128 (===) assertDecULEB128 :: (Integral a, Bits a) => a -> BL.ByteString -> Assertion assertDecULEB128 = decULEB128 (@?=) decULEB128 :: (Integral a, Bits a, Monad m) => (forall x. (Eq x, Show x) => x -> x -> m ()) -> a -> BL.ByteString -> m () decULEB128 eq = \a bl -> do let l = ceiling (8 * fromIntegral (BL.length bl) / 7 :: Double) :: Int for_ (toIntegralSized a) $ \b -> eq (dec (U.getNatural l) bl) (Right b) for_ (toIntegralSized a) $ \b -> eq (dec (U.getInteger l) bl) (Right b) for_ (toIntegralSized a) $ \b -> eq (dec U.getWord bl) (Right b) for_ (toIntegralSized a) $ \b -> eq (dec U.getWord8 bl) (Right b) for_ (toIntegralSized a) $ \b -> eq (dec U.getWord16 bl) (Right b) for_ (toIntegralSized a) $ \b -> eq (dec U.getWord32 bl) (Right b) for_ (toIntegralSized a) $ \b -> eq (dec U.getWord64 bl) (Right b) for_ (toIntegralSized a) $ \b -> eq (dec U.getInt bl) (Right b) for_ (toIntegralSized a) $ \b -> eq (dec U.getInt8 bl) (Right b) for_ (toIntegralSized a) $ \b -> eq (dec U.getInt16 bl) (Right b) for_ (toIntegralSized a) $ \b -> eq (dec U.getInt32 bl) (Right b) for_ (toIntegralSized a) $ \b -> eq (dec U.getInt64 bl) (Right b) propDecSLEB128 :: (Integral a, Bits a, MonadTest m) => a -> BL.ByteString -> m () propDecSLEB128 = decSLEB128 (===) assertDecSLEB128 :: (Integral a, Bits a) => a -> BL.ByteString -> Assertion assertDecSLEB128 = decSLEB128 (@?=) decSLEB128 :: (Integral a, Bits a, Monad m) => (forall x. (Eq x, Show x) => x -> x -> m ()) -> a -> BL.ByteString -> m () decSLEB128 eq = \a bl -> do let i = toInteger a l = fromIntegral (BL.length bl) :: Int when (a >= 0) $ eq (dec (S.getNatural l) bl) (Right (fromInteger i)) for_ (toIntegralSized i) $ \b -> eq (dec (S.getInteger l) bl) (Right b) for_ (toIntegralSized i) $ \b -> eq (dec S.getWord bl) (Right b) for_ (toIntegralSized i) $ \b -> eq (dec S.getWord8 bl) (Right b) for_ (toIntegralSized i) $ \b -> eq (dec S.getWord16 bl) (Right b) for_ (toIntegralSized i) $ \b -> eq (dec S.getWord32 bl) (Right b) for_ (toIntegralSized i) $ \b -> eq (dec S.getWord64 bl) (Right b) for_ (toIntegralSized i) $ \b -> eq (dec S.getInt bl) (Right b) for_ (toIntegralSized i) $ \b -> eq (dec S.getInt8 bl) (Right b) for_ (toIntegralSized i) $ \b -> eq (dec S.getInt16 bl) (Right b) for_ (toIntegralSized i) $ \b -> eq (dec S.getInt32 bl) (Right b) for_ (toIntegralSized i) $ \b -> eq (dec S.getInt64 bl) (Right b) rangeInteger512 :: Range.Range Integer rangeInteger512 = let x = 2 ^ (512 :: Int) :: Integer in Range.constant (negate x) (x - 1) rangeNatural512 :: Range.Range Natural rangeNatural512 = Range.constant 0 ((2 ^ (512 :: Int)) - 1) enc :: Bin.Put -> BL.ByteString enc = Bin.runPut dec :: Bin.Get a -> BL.ByteString -> Either String a dec g b = case Bin.runGetOrFail g b of Left (_, _, e) -> Left e Right (l, _, a) | BL.null l -> Right a | otherwise -> Left "parsed successfully, but got leftovers" zigZag :: Integer -> Natural zigZag i = if i < 0 then fromInteger (i * (-2) - 1) else fromInteger (i * 2) zagZig :: Natural -> Integer zagZig n = if even n then toInteger (div n 2) else negate (toInteger (div (n + 1) 2)) genScientificDefault :: (MonadGen m) => m Sci.Scientific genScientificDefault = genScientific rangeScientificCoefficientDefault rangeScientificExponentDefault rangeScientificCoefficientDefault :: Range.Range Integer rangeScientificCoefficientDefault = let i = 2 ^ (112 :: Int) in Range.linearFrom 0 (negate i) (i - 1) rangeScientificExponentDefault :: Range.Range Int rangeScientificExponentDefault = Range.linearFrom 0 (negate 33) 33 genScientific :: (MonadGen m) => Range.Range Integer -- ^ 'S.coefficient'. -> Range.Range Int -- ^ 'S.base10Exponent'. -> m Sci.Scientific genScientific rc re = Sci.scientific <$> Gen.integral rc <*> Gen.int re genRationalDefault :: (MonadGen m) => m Rational genRationalDefault = do let i = 10 ^ (24 :: Int) :: Integer (%) <$> Gen.integral (Range.linearFrom 0 (negate i) (i - 1)) <*> Gen.integral (Range.linearFrom 1 1 (i - 1)) genFixedDefault :: (HasResolution r, MonadGen m) => m (Fixed r) genFixedDefault = fromRational <$> genRationalDefault