zfec-1.4.5/0000775000175100017510000000000011216213552011536 5ustar zookozookozfec-1.4.5/haskell/0000775000175100017510000000000011216213552013161 5ustar zookozookozfec-1.4.5/haskell/Codec/0000775000175100017510000000000011216213552014176 5ustar zookozookozfec-1.4.5/haskell/Codec/FEC.hs0000664000175100017510000002567411216211330015135 0ustar zookozooko{-# LANGUAGE ForeignFunctionInterface, EmptyDataDecls #-} -- | -- Module: Codec.FEC -- Copyright: Adam Langley -- License: BSD3 -- -- Stability: experimental -- -- The module provides k of n encoding - a way to generate (n - k) secondary -- blocks of data from k primary blocks such that any k blocks (primary or -- secondary) are sufficient to regenerate all blocks. -- -- All blocks must be the same length and you need to keep track of which -- blocks you have in order to tell decode. By convention, the blocks are -- numbered 0..(n - 1) and blocks numbered < k are the primary blocks. module Codec.FEC ( FECParams , fec , encode , decode -- * Utility functions , secureDivide , secureCombine , enFEC , deFEC ) where import qualified Data.ByteString as B import qualified Data.ByteString.Unsafe as BU import qualified Data.ByteString.Internal as BI import Data.Word (Word8) import Data.Bits (xor) import Data.List (sortBy, partition, (\\), nub) import Foreign.Ptr import Foreign.Storable (sizeOf, poke) import Foreign.ForeignPtr import Foreign.C.Types import Foreign.Marshal.Alloc import Foreign.Marshal.Array (withArray, advancePtr) import System.IO (withFile, IOMode(..)) import System.IO.Unsafe (unsafePerformIO) data CFEC data FECParams = FECParams (ForeignPtr CFEC) Int Int instance Show FECParams where show (FECParams _ k n) = "FEC (" ++ show k ++ ", " ++ show n ++ ")" foreign import ccall unsafe "fec_new" _new :: CUInt -- ^ k -> CUInt -- ^ n -> IO (Ptr CFEC) foreign import ccall unsafe "&fec_free" _free :: FunPtr (Ptr CFEC -> IO ()) foreign import ccall unsafe "fec_encode" _encode :: Ptr CFEC -> Ptr (Ptr Word8) -- ^ primary blocks -> Ptr (Ptr Word8) -- ^ (output) secondary blocks -> Ptr CUInt -- ^ array of secondary block ids -> CSize -- ^ length of previous -> CSize -- ^ block length -> IO () foreign import ccall unsafe "fec_decode" _decode :: Ptr CFEC -> Ptr (Ptr Word8) -- ^ input blocks -> Ptr (Ptr Word8) -- ^ output blocks -> Ptr CUInt -- ^ array of input indexes -> CSize -- ^ block length -> IO () -- | Return true if the given @k@ and @n@ values are valid isValidConfig :: Int -> Int -> Bool isValidConfig k n | k >= n = False | k < 1 = False | n < 1 = False | n > 255 = False | otherwise = True -- | Return a FEC with the given parameters. fec :: Int -- ^ the number of primary blocks -> Int -- ^ the total number blocks, must be < 256 -> FECParams fec k n = if not (isValidConfig k n) then error $ "Invalid FEC parameters: " ++ show k ++ " " ++ show n else unsafePerformIO (do cfec <- _new (fromIntegral k) (fromIntegral n) params <- newForeignPtr _free cfec return $ FECParams params k n) -- | Create a C array of unsigned from an input array uintCArray :: [Int] -> ((Ptr CUInt) -> IO a) -> IO a uintCArray xs f = withArray (map fromIntegral xs) f -- | Convert a list of ByteStrings to an array of pointers to their data byteStringsToArray :: [B.ByteString] -> ((Ptr (Ptr Word8)) -> IO a) -> IO a byteStringsToArray inputs f = do let l = length inputs allocaBytes (l * sizeOf (undefined :: Ptr Word8)) (\array -> do let inner _ [] = f array inner array' (bs : bss) = BU.unsafeUseAsCString bs (\ptr -> do poke array' $ castPtr ptr inner (advancePtr array' 1) bss) inner array inputs) -- | Return True iff all the given ByteStrings are the same length allByteStringsSameLength :: [B.ByteString] -> Bool allByteStringsSameLength [] = True allByteStringsSameLength (bs : bss) = all ((==) (B.length bs)) $ map B.length bss -- | Run the given function with a pointer to an array of @n@ pointers to -- buffers of size @size@. Return these buffers as a list of ByteStrings createByteStringArray :: Int -- ^ the number of buffers requested -> Int -- ^ the size of each buffer -> ((Ptr (Ptr Word8)) -> IO ()) -> IO [B.ByteString] createByteStringArray n size f = do allocaBytes (n * sizeOf (undefined :: Ptr Word8)) (\array -> do allocaBytes (n * size) (\ptr -> do mapM_ (\i -> poke (advancePtr array i) (advancePtr ptr (size * i))) [0..(n - 1)] f array mapM (\i -> B.packCStringLen (castPtr $ advancePtr ptr (i * size), size)) [0..(n - 1)])) -- | Generate the secondary blocks from a list of the primary blocks. The -- primary blocks must be in order and all of the same size. There must be -- @k@ primary blocks. encode :: FECParams -> [B.ByteString] -- ^ a list of @k@ input blocks -> [B.ByteString] -- ^ (n - k) output blocks encode (FECParams params k n) inblocks | length inblocks /= k = error "Wrong number of blocks to FEC encode" | not (allByteStringsSameLength inblocks) = error "Not all inputs to FEC encode are the same length" | otherwise = unsafePerformIO (do let sz = B.length $ head inblocks withForeignPtr params (\cfec -> do byteStringsToArray inblocks (\src -> do createByteStringArray (n - k) sz (\fecs -> do uintCArray [k..(n - 1)] (\block_nums -> do _encode cfec src fecs block_nums (fromIntegral (n - k)) $ fromIntegral sz))))) -- | A sort function for tagged assoc lists sortTagged :: [(Int, a)] -> [(Int, a)] sortTagged = sortBy (\a b -> compare (fst a) (fst b)) -- | Reorder the given list so that elements with tag numbers < the first -- argument have an index equal to their tag number (if possible) reorderPrimaryBlocks :: Int -> [(Int, a)] -> [(Int, a)] reorderPrimaryBlocks n blocks = inner (sortTagged pBlocks) sBlocks [] where (pBlocks, sBlocks) = partition (\(tag, _) -> tag < n) blocks inner [] sBlocks acc = acc ++ sBlocks inner pBlocks [] acc = acc ++ pBlocks inner pBlocks@((tag, a) : ps) sBlocks@(s : ss) acc = if length acc == tag then inner ps sBlocks (acc ++ [(tag, a)]) else inner pBlocks ss (acc ++ [s]) -- | Recover the primary blocks from a list of @k@ blocks. Each block must be -- tagged with its number (see the module comments about block numbering) decode :: FECParams -> [(Int, B.ByteString)] -- ^ a list of @k@ blocks and their index -> [B.ByteString] -- ^ a list the @k@ primary blocks decode (FECParams params k n) inblocks | length (nub $ map fst inblocks) /= length (inblocks) = error "Duplicate input blocks in FEC decode" | any (\f -> f < 0 || f >= n) $ map fst inblocks = error "Invalid block numbers in FEC decode" | length inblocks /= k = error "Wrong number of blocks to FEC decode" | not (allByteStringsSameLength $ map snd inblocks) = error "Not all inputs to FEC decode are same length" | otherwise = unsafePerformIO (do let sz = B.length $ snd $ head inblocks inblocks' = reorderPrimaryBlocks k inblocks presentBlocks = map fst inblocks' withForeignPtr params (\cfec -> do byteStringsToArray (map snd inblocks') (\src -> do b <- createByteStringArray (n - k) sz (\out -> do uintCArray presentBlocks (\block_nums -> do _decode cfec src out block_nums $ fromIntegral sz)) let blocks = [0..(n - 1)] \\ presentBlocks tagged = zip blocks b allBlocks = sortTagged $ tagged ++ inblocks' return $ take k $ map snd allBlocks))) -- | Break a ByteString into @n@ parts, equal in length to the original, such -- that all @n@ are required to reconstruct the original, but having less -- than @n@ parts reveals no information about the orginal. -- -- This code works in IO monad because it needs a source of random bytes, -- which it gets from /dev/urandom. If this file doesn't exist an -- exception results -- -- Not terribly fast - probably best to do it with short inputs (e.g. an -- encryption key) secureDivide :: Int -- ^ the number of parts requested -> B.ByteString -- ^ the data to be split -> IO [B.ByteString] secureDivide n input | n < 0 = error "secureDivide called with negative number of parts" | otherwise = withFile "/dev/urandom" ReadMode (\handle -> do let inner 1 bs = return [bs] inner n bs = do mask <- B.hGet handle (B.length bs) let masked = B.pack $ B.zipWith xor bs mask rest <- inner (n - 1) masked return (mask : rest) inner n input) -- | Reverse the operation of secureDivide. The order of the inputs doesn't -- matter, but they must all be the same length secureCombine :: [B.ByteString] -> B.ByteString secureCombine [] = error "Passed empty list of inputs to secureCombine" secureCombine [a] = a secureCombine [a, b] = B.pack $ B.zipWith xor a b secureCombine (a : rest) = B.pack $ B.zipWith xor a $ secureCombine rest -- | A utility function which takes an arbitary input and FEC encodes it into a -- number of blocks. The order the resulting blocks doesn't matter so long -- as you have enough to present to @deFEC@. enFEC :: Int -- ^ the number of blocks required to reconstruct -> Int -- ^ the total number of blocks -> B.ByteString -- ^ the data to divide -> [B.ByteString] -- ^ the resulting blocks enFEC k n input = taggedPrimaryBlocks ++ taggedSecondaryBlocks where taggedPrimaryBlocks = map (uncurry B.cons) $ zip [0..] primaryBlocks taggedSecondaryBlocks = map (uncurry B.cons) $ zip [(fromIntegral k)..] secondaryBlocks remainder = B.length input `mod` k paddingLength = if remainder >= 1 then (k - remainder) else k paddingBytes = (B.replicate (paddingLength - 1) 0) `B.append` (B.singleton $ fromIntegral paddingLength) divide a bs | B.null bs = [] | otherwise = (B.take a bs) : (divide a $ B.drop a bs) input' = input `B.append` paddingBytes blockSize = B.length input' `div` k primaryBlocks = divide blockSize input' secondaryBlocks = encode params primaryBlocks params = fec k n -- | Reverses the operation of @enFEC@. deFEC :: Int -- ^ the number of blocks required (matches call to @enFEC@) -> Int -- ^ the total number of blocks (matches call to @enFEC@) -> [B.ByteString] -- ^ a list of k, or more, blocks from @enFEC@ -> B.ByteString deFEC k n inputs | length inputs < k = error "Too few inputs to deFEC" | otherwise = B.take (B.length fecOutput - paddingLength) fecOutput where paddingLength = fromIntegral $ B.last fecOutput inputs' = take k inputs taggedInputs = map (\bs -> (fromIntegral $ B.head bs, B.tail bs)) inputs' fecOutput = B.concat $ decode params taggedInputs params = fec k n zfec-1.4.5/haskell/test/0000775000175100017510000000000011216213552014140 5ustar zookozookozfec-1.4.5/haskell/test/FECTest.hs0000664000175100017510000000340211216211330015720 0ustar zookozookomodule Main where import qualified Data.ByteString as B import qualified Codec.FEC as FEC import System.IO (withFile, IOMode(..)) import System.Random import Data.List (sortBy) import Test.QuickCheck -- | Return true if the given @k@ and @n@ values are valid isValidConfig :: Int -> Int -> Bool isValidConfig k n | k >= n = False | k < 1 = False | n < 1 = False | otherwise = True randomTake :: Int -> Int -> [a] -> [a] randomTake seed n values = map snd $ take n sortedValues where sortedValues = sortBy (\a b -> compare (fst a) (fst b)) taggedValues taggedValues = zip rnds values rnds :: [Float] rnds = randoms gen gen = mkStdGen seed testFEC k n len seed = FEC.decode fec someTaggedBlocks == origBlocks where origBlocks = map (\i -> B.replicate len $ fromIntegral i) [0..(k - 1)] fec = FEC.fec k n secondaryBlocks = FEC.encode fec origBlocks taggedBlocks = zip [0..] (origBlocks ++ secondaryBlocks) someTaggedBlocks = randomTake seed k taggedBlocks prop_FEC :: Int -> Int -> Int -> Int -> Property prop_FEC k n len seed = isValidConfig k n && n < 256 && len < 1024 ==> testFEC k n len seed checkDivide :: Int -> IO () checkDivide n = do let input = B.replicate 1024 65 parts <- FEC.secureDivide n input if FEC.secureCombine parts == input then return () else fail "checkDivide failed" checkEnFEC :: Int -> IO () checkEnFEC len = do testdata <- withFile "/dev/urandom" ReadMode (\handle -> B.hGet handle len) let [a, b, c, d, e] = FEC.enFEC 3 5 testdata if FEC.deFEC 3 5 [b, e, d] == testdata then return () else fail "deFEC failure" main = do mapM_ (check (defaultConfig { configMaxTest = 1000, configMaxFail = 10000 })) [prop_FEC] mapM_ checkDivide [1, 2, 3, 4, 10] mapM_ checkEnFEC [1, 2, 3, 4, 5, 1024 * 1024] zfec-1.4.5/PKG-INFO0000664000175100017510000000404711216213552012640 0ustar zookozookoMetadata-Version: 1.0 Name: zfec Version: 1.4.5 Summary: a fast erasure codec which can be used with the command-line, C, Python, or Haskell Home-page: http://allmydata.org/trac/zfec Author: Zooko O'Whielacronx Author-email: zooko@zooko.com License: GNU GPL Description: Fast, portable, programmable erasure coding a.k.a. "forward error correction": the generation of redundant blocks of information such that if some blocks are lost then the original data can be recovered from the remaining blocks. The zfec package includes command-line tools, C API, Python API, and Haskell API Platform: UNKNOWN Classifier: Development Status :: 5 - Production/Stable Classifier: Environment :: Console Classifier: License :: OSI Approved :: GNU General Public License (GPL) Classifier: License :: DFSG approved Classifier: License :: Other/Proprietary License Classifier: Intended Audience :: Developers Classifier: Intended Audience :: End Users/Desktop Classifier: Intended Audience :: System Administrators Classifier: Operating System :: Microsoft Classifier: Operating System :: Microsoft :: Windows Classifier: Operating System :: Unix Classifier: Operating System :: POSIX :: Linux Classifier: Operating System :: POSIX Classifier: Operating System :: MacOS :: MacOS X Classifier: Operating System :: Microsoft :: Windows :: Windows NT/2000 Classifier: Operating System :: OS Independent Classifier: Natural Language :: English Classifier: Programming Language :: C Classifier: Programming Language :: Python Classifier: Programming Language :: Python :: 2 Classifier: Programming Language :: Python :: 2.4 Classifier: Programming Language :: Python :: 2.5 Classifier: Topic :: Utilities Classifier: Topic :: System :: Systems Administration Classifier: Topic :: System :: Filesystems Classifier: Topic :: System :: Distributed Computing Classifier: Topic :: Software Development :: Libraries Classifier: Topic :: Communications :: Usenet News Classifier: Topic :: System :: Archiving :: Backup Classifier: Topic :: System :: Archiving :: Mirroring Classifier: Topic :: System :: Archiving zfec-1.4.5/setup.py0000664000175100017510000001434011216212157013252 0ustar zookozooko#!/usr/bin/env python # zfec -- fast forward error correction library with Python interface # # Copyright (C) 2007-2008 Allmydata, Inc. # Author: Zooko Wilcox-O'Hearn # # This file is part of zfec. # # See README.txt for licensing information. import os, re, sys miscdeps=os.path.join(os.getcwd(), 'misc', 'dependencies') try: from ez_setup import use_setuptools except ImportError: pass else: use_setuptools(min_version='0.6c9', download_delay=0, to_dir=miscdeps) from setuptools import Extension, find_packages, setup if "--debug" in sys.argv: DEBUGMODE=True sys.argv.remove("--debug") else: DEBUGMODE=False extra_compile_args=[] extra_link_args=[] extra_compile_args.append("-std=c99") define_macros=[] undef_macros=[] for arg in sys.argv: if arg.startswith("--stride="): stride = int(arg[len("--stride="):]) define_macros.append(('STRIDE', stride)) sys.argv.remove(arg) break if DEBUGMODE: extra_compile_args.append("-O0") extra_compile_args.append("-g") extra_compile_args.append("-Wall") extra_link_args.append("-g") undef_macros.append('NDEBUG') trove_classifiers=[ "Development Status :: 5 - Production/Stable", "Environment :: Console", "License :: OSI Approved :: GNU General Public License (GPL)", "License :: DFSG approved", "License :: Other/Proprietary License", "Intended Audience :: Developers", "Intended Audience :: End Users/Desktop", "Intended Audience :: System Administrators", "Operating System :: Microsoft", "Operating System :: Microsoft :: Windows", "Operating System :: Unix", "Operating System :: POSIX :: Linux", "Operating System :: POSIX", "Operating System :: MacOS :: MacOS X", "Operating System :: Microsoft :: Windows :: Windows NT/2000", "Operating System :: OS Independent", "Natural Language :: English", "Programming Language :: C", "Programming Language :: Python", "Programming Language :: Python :: 2", "Programming Language :: Python :: 2.4", "Programming Language :: Python :: 2.5", "Topic :: Utilities", "Topic :: System :: Systems Administration", "Topic :: System :: Filesystems", "Topic :: System :: Distributed Computing", "Topic :: Software Development :: Libraries", "Topic :: Communications :: Usenet News", "Topic :: System :: Archiving :: Backup", "Topic :: System :: Archiving :: Mirroring", "Topic :: System :: Archiving", ] PKG = "zfec" VERSIONFILE = os.path.join(PKG, "_version.py") verstr = "unknown" try: verstrline = open(VERSIONFILE, "rt").read() except EnvironmentError: pass # Okay, there is no version file. else: VSRE = r"^verstr = ['\"]([^'\"]*)['\"]" mo = re.search(VSRE, verstrline, re.M) if mo: verstr = mo.group(1) else: print "unable to find version in %s" % (VERSIONFILE,) raise RuntimeError("if %s.py exists, it is required to be well-formed" % (VERSIONFILE,)) dependency_links=[os.path.join(miscdeps, t) for t in os.listdir(miscdeps) if t.endswith(".tar")] setup_requires = [] # The darcsver command from the darcsver plugin is needed to initialize the # distribution's .version attribute correctly. (It does this either by # examining darcs history, or if that fails by reading the # zfec/_version.py file). darcsver will also write a new version # stamp in zfec/_version.py, with a version number derived from # darcs history. Note that the setup.cfg file has an "[aliases]" section # which enumerates commands that you might run and specifies that it will run # darcsver before each one. If you add different commands (or if I forgot # some that are already in use), you may need to add it to setup.cfg and # configure it to run darcsver before your command, if you want the version # number to be correct when that command runs. # http://pypi.python.org/pypi/darcsver setup_requires.append('darcsver >= 1.2.0') # setuptools_darcs is required to produce complete distributions (such as with # "sdist" or "bdist_egg"), unless there is a zfec.egg-info/SOURCE.txt file # present which contains a complete list of files that should be included. # http://pypi.python.org/pypi/setuptools_darcs setup_requires.append('setuptools_darcs >= 1.1.0') data_fnames=[ 'COPYING.GPL', 'changelog', 'COPYING.TGPPL.html', 'TODO', 'README.txt' ] # In case we are building for a .deb with stdeb's sdist_dsc command, we put the # docs in "share/doc/python-$PKG". doc_loc = "share/doc/python-" + PKG data_files = [(doc_loc, data_fnames)] def _setup(test_suite): setup(name=PKG, version=verstr, description='a fast erasure codec which can be used with the command-line, C, Python, or Haskell', long_description='Fast, portable, programmable erasure coding a.k.a. "forward error correction": the generation of redundant blocks of information such that if some blocks are lost then the original data can be recovered from the remaining blocks. The zfec package includes command-line tools, C API, Python API, and Haskell API', author='Zooko O\'Whielacronx', author_email='zooko@zooko.com', url='http://allmydata.org/trac/'+PKG, license='GNU GPL', dependency_links=dependency_links, install_requires=["argparse >= 0.8", "pyutil >= 1.3.19"], tests_require=["pyutil >= 1.3.19"], packages=find_packages(), include_package_data=True, data_files=data_files, setup_requires=setup_requires, classifiers=trove_classifiers, entry_points = { 'console_scripts': [ 'zfec = %s.cmdline_zfec:main' % PKG, 'zunfec = %s.cmdline_zunfec:main' % PKG ] }, ext_modules=[Extension(PKG+'._fec', [PKG+'/fec.c', PKG+'/_fecmodule.c',], extra_link_args=extra_link_args, extra_compile_args=extra_compile_args, undef_macros=undef_macros, define_macros=define_macros),], test_suite=test_suite, zip_safe=False, # I prefer unzipped for easier access. ) test_suite_name=PKG+".test" try: _setup(test_suite=test_suite_name) except Exception, le: # to work around a bug in Elisa v0.3.5 # https://bugs.launchpad.net/elisa/+bug/263697 if "test_suite must be a list" in str(le): _setup(test_suite=[test_suite_name]) else: raise zfec-1.4.5/README.txt0000664000175100017510000003134111216212136013233 0ustar zookozooko * Intro and Licence This package implements an "erasure code", or "forward error correction code". You may use this package under the GNU General Public License, version 2 or, at your option, any later version. You may use this package under the Transitive Grace Period Public Licence, version 1.0. (You may choose to use this package under the terms of either licence, at your option.) See the file COPYING.GPL for the terms of the GNU General Public License, version 2. See the file COPYING.TGPPL.html for the terms of the Transitive Grace Period Public Licence, version 1.0. In addition, Allmydata, Inc. offers other licensing terms. If you would like to inquire about a commercial relationship with Allmydata, Inc., please contact partnerships@allmydata.com and visit http://allmydata.com . The most widely known example of an erasure code is the RAID-5 algorithm which makes it so that in the event of the loss of any one hard drive, the stored data can be completely recovered. The algorithm in the zfec package has a similar effect, but instead of recovering from the loss of only a single element, it can be parameterized to choose in advance the number of elements whose loss it can tolerate. This package is largely based on the old "fec" library by Luigi Rizzo et al., which is a mature and optimized implementation of erasure coding. The zfec package makes several changes from the original "fec" package, including addition of the Python API, refactoring of the C API to support zero-copy operation, a few clean-ups and optimizations of the core code itself, and the addition of a command-line tool named "zfec". * Installation This package is managed with the "setuptools" package management tool. To build and install the package directly into your system, just run "python ./setup.py install". If you prefer to keep the package limited to a specific directory so that you can manage it yourself (perhaps by using the "GNU stow") tool, then give it these arguments: "python ./setup.py install --single-version-externally-managed --record=${specificdirectory}/zfec-install.log --prefix=${specificdirectory}" To run the self-tests, execute "python ./setup.py test" (or if you have Twisted Python installed, you can run "trial zfec" for nicer output and test options.) This will run the tests of the C API, the Python API, and the command-line tools. To run the tests of the Haskell API: % runhaskell haskell/test/FECTest.hs Note that in order to run the Haskell API tests you must have installed the library first due to the fact that the interpreter cannot process FEC.hs as it takes a reference to an FFI function. * Community The source is currently available via darcs on the web with the command: darcs get http://allmydata.org/source/zfec/trunk More information on darcs is available at http://darcs.net Please join the zfec mailing list and submit patches: * Overview This package performs two operations, encoding and decoding. Encoding takes some input data and expands its size by producing extra "check blocks", also called "secondary blocks". Decoding takes some data -- any combination of blocks of the original data (called "primary blocks") and "secondary blocks", and produces the original data. The encoding is parameterized by two integers, k and m. m is the total number of blocks produced, and k is how many of those blocks are necessary to reconstruct the original data. m is required to be at least 1 and at most 256, and k is required to be at least 1 and at most m. (Note that when k == m then there is no point in doing erasure coding -- it degenerates to the equivalent of the Unix "split" utility which simply splits the input into successive segments. Similarly, when k == 1 it degenerates to the equivalent of the unix "cp" utility -- each block is a complete copy of the input data.) Note that each "primary block" is a segment of the original data, so its size is 1/k'th of the size of original data, and each "secondary block" is of the same size, so the total space used by all the blocks is m/k times the size of the original data (plus some padding to fill out the last primary block to be the same size as all the others). In addition to the data contained in the blocks themselves there are also a few pieces of metadata which are necessary for later reconstruction. Those pieces are: 1. the value of K, 2. the value of M, 3. the sharenum of each block, 4. the number of bytes of padding that were used. The "zfec" command-line tool compresses these pieces of data and prepends them to the beginning of each share, so each the sharefile produced by the "zfec" command-line tool is between one and four bytes larger than the share data alone. The decoding step requires as input k of the blocks which were produced by the encoding step. The decoding step produces as output the data that was earlier input to the encoding step. * Command-Line Tool The bin/ directory contains two Unix-style, command-line tools "zfec" and "zunfec". Execute "zfec --help" or "zunfec --help" for usage instructions. Note: a Unix-style tool like "zfec" does only one thing -- in this case erasure coding -- and leaves other tasks to other tools. Other Unix-style tools that go well with zfec include "GNU tar" or "7z" a.k.a. "p7zip" for archiving multiple files and directories into one file, "7z" or "rzip" for compression, and "GNU Privacy Guard" for encryption or "sha256sum" for integrity. It is important to do things in order: first archive, then compress, then either encrypt or sha256sum, then erasure code. Note that if GNU Privacy Guard is used for privacy, then it will also ensure integrity, so the use of sha256sum is unnecessary in that case. Note that if 7z is used for archiving then it also does compression, so you don't need a separate compressor in that case. * Performance Measurements On my Athlon 64 2.4 GHz workstation (running Linux), the "zfec" command-line tool encoded a 160 MB file with m=100, k=94 (about 6% redundancy) in 3.9 seconds, where the "par2" tool encoded the file with about 6% redundancy in 27 seconds. zfec encoded the same file with m=12, k=6 (100% redundancy) in 4.1 seconds, where par2 encoded it with about 100% redundancy in 7 minutes and 56 seconds. The underlying C library in benchmark mode encoded from a file at about 4.9 million bytes per second and decoded at about 5.8 million bytes per second. On Peter's fancy Intel Mac laptop (2.16 GHz Core Duo), it encoded from a file at about 6.2 million bytes per second. On my even fancier Intel Mac laptop (2.33 GHz Core Duo), it encoded from a file at about 6.8 million bytes per second. On my old PowerPC G4 867 MHz Mac laptop, it encoded from a file at about 1.3 million bytes per second. * API Each block is associated with "blocknum". The blocknum of each primary block is its index (starting from zero), so the 0'th block is the first primary block, which is the first few bytes of the file, the 1'st block is the next primary block, which is the next few bytes of the file, and so on. The last primary block has blocknum k-1. The blocknum of each secondary block is an arbitrary integer between k and 255 inclusive. (When using the Python API, if you don't specify which secondary blocks you want when invoking encode(), then it will by default provide the blocks with ids from k to m-1 inclusive.) ** C API fec_encode() takes as input an array of k pointers, where each pointer points to a memory buffer containing the input data (i.e., the i'th buffer contains the i'th primary block). There is also a second parameter which is an array of the blocknums of the secondary blocks which are to be produced. (Each element in that array is required to be the blocknum of a secondary block, i.e. it is required to be >= k and < m.) The output from fec_encode() is the requested set of secondary blocks which are written into output buffers provided by the caller. Note that this fec_encode() is a "low-level" API in that it requires the input data to be provided in a set of memory buffers of exactly the right sizes. If you are starting instead with a single buffer containing all of the data then please see easyfec.py's "class Encoder" as an example of how to split a single large buffer into the appropriate set of input buffers for fec_encode(). If you are starting with a file on disk, then please see filefec.py's encode_file_stringy_easyfec() for an example of how to read the data from a file and pass it to "class Encoder". The Python interface provides these higher-level operations, as does the Haskell interface. If you implement functions to do these higher-level tasks in other languages than Python or Haskell, then please send a patch to zfec-dev@allmydata.org so that your API can be included in future releases of zfec. fec_decode() takes as input an array of k pointers, where each pointer points to a buffer containing a block. There is also a separate input parameter which is an array of blocknums, indicating the blocknum of each of the blocks which is being passed in. The output from fec_decode() is the set of primary blocks which were missing from the input and had to be reconstructed. These reconstructed blocks are written into output buffers provided by the caller. ** Python API encode() and decode() take as input a sequence of k buffers, where a "sequence" is any object that implements the Python sequence protocol (such as a list or tuple) and a "buffer" is any object that implements the Python buffer protocol (such as a string or array). The contents that are required to be present in these buffers are the same as for the C API. encode() also takes a list of desired blocknums. Unlike the C API, the Python API accepts blocknums of primary blocks as well as secondary blocks in its list of desired blocknums. encode() returns a list of buffer objects which contain the blocks requested. For each requested block which is a primary block, the resulting list contains a reference to the apppropriate primary block from the input list. For each requested block which is a secondary block, the list contains a newly created string object containing that block. decode() also takes a list of integers indicating the blocknums of the blocks being passed int. decode() returns a list of buffer objects which contain all of the primary blocks of the original data (in order). For each primary block which was present in the input list, then the result list simply contains a reference to the object that was passed in the input list. For each primary block which was not present in the input, the result list contains a newly created string object containing that primary block. Beware of a "gotcha" that can result from the combination of mutable data and the fact that the Python API returns references to inputs when possible. Returning references to its inputs is efficient since it avoids making an unnecessary copy of the data, but if the object which was passed as input is mutable and if that object is mutated after the call to zfec returns, then the result from zfec -- which is just a reference to that same object -- will also be mutated. This subtlety is the price you pay for avoiding data copying. If you don't want to have to worry about this then you can simply use immutable objects (e.g. Python strings) to hold the data that you pass to zfec. ** Haskell API The Haskell code is fully Haddocked, to generate the documentation, run % runhaskell Setup.lhs haddock * Utilities The filefec.py module has a utility function for efficiently reading a file and encoding it piece by piece. This module is used by the "zfec" and "zunfec" command-line tools from the bin/ directory. * Dependencies A C compiler is required. To use the Python API or the command-line tools a Python interpreter is also required. We have tested it with Python v2.4 and v2.5. For the Haskell interface, GHC >= 6.8.1 is required. * Acknowledgements Thanks to the author of the original fec lib, Luigi Rizzo, and the folks that contributed to it: Phil Karn, Robert Morelos-Zaragoza, Hari Thirumoorthy, and Dan Rubenstein. Thanks to the Mnet hackers who wrote an earlier Python wrapper, especially Myers Carpenter and Hauke Johannknecht. Thanks to Brian Warner and Amber O'Whielacronx for help with the API, documentation, debugging, compression, and unit tests. Thanks to Adam Langley for improving the C API and contributing the Haskell API. Thanks to the creators of GCC (starting with Richard M. Stallman) and Valgrind (starting with Julian Seward) for a pair of excellent tools. Thanks to my coworkers at Allmydata -- http://allmydata.com -- Fabrice Grinda, Peter Secor, Rob Kinninmont, Brian Warner, Zandr Milewski, Justin Boreta, Mark Meras for sponsoring this work and releasing it under a Free Software licence. Enjoy! Zooko Wilcox-O'Hearn 2008-01-20 Boulder, Colorado zfec-1.4.5/bench/0000775000175100017510000000000011216213552012615 5ustar zookozookozfec-1.4.5/bench/bench_zfec.py0000664000175100017510000000423011216211330015244 0ustar zookozookofrom zfec import easyfec, Encoder, filefec from pyutil import mathutil import os from pyutil import benchutil FNAME="benchrandom.data" def _make_new_rand_file(size): open(FNAME, "wb").write(os.urandom(size)) def donothing(results, reslenthing): pass K=3 M=10 d = "" ds = [] easyfecenc = None fecenc = None def _make_new_rand_data(size): global d, easyfecenc, fecenc d = os.urandom(size) del ds[:] ds.extend([None]*K) blocksize = mathutil.div_ceil(size, K) for i in range(K): ds[i] = d[i*blocksize:(i+1)*blocksize] ds[-1] = ds[-1] + "\x00" * (len(ds[-2]) - len(ds[-1])) easyfecenc = easyfec.Encoder(K,M) fecenc = Encoder(K,M) import sha hashers = [ sha.new() for i in range(M) ] def hashem(results, reslenthing): for i, result in enumerate(results): hashers[i].update(result) def _encode_file(N): filefec.encode_file(open(FNAME, "rb"), donothing, K, M) def _encode_file_stringy(N): filefec.encode_file_stringy(open(FNAME, "rb"), donothing, K, M) def _encode_file_stringy_easyfec(N): filefec.encode_file_stringy_easyfec(open(FNAME, "rb"), donothing, K, M) def _encode_file_not_really(N): filefec.encode_file_not_really(open(FNAME, "rb"), donothing, K, M) def _encode_file_not_really_and_hash(N): filefec.encode_file_not_really_and_hash(open(FNAME, "rb"), donothing, K, M) def _encode_file_and_hash(N): filefec.encode_file(open(FNAME, "rb"), hashem, K, M) def _encode_data_not_really(N): i = 0 for c in d: i += 1 assert len(d) == N == i pass def _encode_data_easyfec(N): easyfecenc.encode(d) def _encode_data_fec(N): fecenc.encode(ds) def bench(): # for f in [_encode_file_stringy_easyfec, _encode_file_stringy, _encode_file, _encode_file_not_really,]: # for f in [_encode_file,]: # for f in [_encode_file_not_really, _encode_file_not_really_and_hash, _encode_file, _encode_file_and_hash,]: # for f in [_encode_data_not_really, _encode_data_easyfec, _encode_data_fec,]: for f in [_encode_data_fec,]: for BSIZE in [2**22]: benchutil.rep_bench(f, n=BSIZE, initfunc=_make_new_rand_data, MAXREPS=64, MAXTIME=None) bench() zfec-1.4.5/NEWS.txt0000664000175100017510000000067011216213517013057 0ustar zookozookoUser visible changes in zfec. -*- outline -*- * Release 1.4.5 (2009-06-17) ** Bug fixes Fix seg fault if the Python classes Encoder or Decoder are constructed with k or m less than 1, greater than 256, or with k greater m. Fix several compiler warnings, add unit tests, improve Python packaging, set up more buildbots to run the unit tests on more platforms. For details about older releases, see the version control history. zfec-1.4.5/COPYING.TGPPL.html0000664000175100017510000002577211216211330014426 0ustar zookozooko transitive grace period public licence, v1.0

Transitive Grace Period Public Licence ("TGPPL") v. 1.0

This Transitive Grace Period Public Licence (the "License") applies to any original work of authorship (the "Original Work") whose owner (the "Licensor") has placed the following licensing notice adjacent to the copyright notice for the Original Work:

Licensed under the Transitive Grace Period Public Licence version 1.0

  1. Grant of Copyright License. Licensor grants You a worldwide, royalty-free, non-exclusive, sublicensable license, for the duration of the copyright, to do the following:

    1. to reproduce the Original Work in copies, either alone or as part of a collective work;

    2. to translate, adapt, alter, transform, modify, or arrange the Original Work, thereby creating derivative works ("Derivative Works") based upon the Original Work;

    3. to distribute or communicate copies of the Original Work and Derivative Works to the public, with the proviso that copies of Original Work or Derivative Works that You distribute or communicate shall be licensed under this Transitive Grace Period Public Licence no later than 12 months after You distributed or communicated said copies;

    4. to perform the Original Work publicly; and

    5. to display the Original Work publicly.

  2. Grant of Patent License. Licensor grants You a worldwide, royalty-free, non-exclusive, sublicensable license, under patent claims owned or controlled by the Licensor that are embodied in the Original Work as furnished by the Licensor, for the duration of the patents, to make, use, sell, offer for sale, have made, and import the Original Work and Derivative Works.

  3. Grant of Source Code License. The term "Source Code" means the preferred form of the Original Work for making modifications to it and all available documentation describing how to modify the Original Work. Licensor agrees to provide a machine-readable copy of the Source Code of the Original Work along with each copy of the Original Work that Licensor distributes. Licensor reserves the right to satisfy this obligation by placing a machine-readable copy of the Source Code in an information repository reasonably calculated to permit inexpensive and convenient access by You for as long as Licensor continues to distribute the Original Work.

  4. Exclusions From License Grant. Neither the names of Licensor, nor the names of any contributors to the Original Work, nor any of their trademarks or service marks, may be used to endorse or promote products derived from this Original Work without express prior permission of the Licensor. Except as expressly stated herein, nothing in this License grants any license to Licensor's trademarks, copyrights, patents, trade secrets or any other intellectual property. No patent license is granted to make, use, sell, offer for sale, have made, or import embodiments of any patent claims other than the licensed claims defined in Section 2. No license is granted to the trademarks of Licensor even if such marks are included in the Original Work. Nothing in this License shall be interpreted to prohibit Licensor from licensing under terms different from this License any Original Work that Licensor otherwise would have a right to license.

  5. External Deployment. The term "External Deployment" means the use, distribution, or communication of the Original Work or Derivative Works in any way such that the Original Work or Derivative Works may be used by anyone other than You, whether those works are distributed or communicated to those persons or made available as an application intended for use over a network. As an express condition for the grants of license hereunder, You must treat any External Deployment by You of the Original Work or a Derivative Work as a distribution under section 1(c).

  6. Attribution Rights. You must retain, in the Source Code of any Derivative Works that You create, all copyright, patent, or trademark notices from the Source Code of the Original Work, as well as any notices of licensing and any descriptive text identified therein as an "Attribution Notice." You must cause the Source Code for any Derivative Works that You create to carry a prominent Attribution Notice reasonably calculated to inform recipients that You have modified the Original Work.

  7. Warranty of Provenance and Disclaimer of Warranty. Licensor warrants that the copyright in and to the Original Work and the patent rights granted herein by Licensor are owned by the Licensor or are sublicensed to You under the terms of this License with the permission of the contributor(s) of those copyrights and patent rights. Except as expressly stated in the immediately preceding sentence, the Original Work is provided under this License on an "AS IS" BASIS and WITHOUT WARRANTY, either express or implied, including, without limitation, the warranties of non-infringement, merchantability or fitness for a particular purpose. THE ENTIRE RISK AS TO THE QUALITY OF THE ORIGINAL WORK IS WITH YOU. This DISCLAIMER OF WARRANTY constitutes an essential part of this License. No license to the Original Work is granted by this License except under this disclaimer.

  8. Limitation of Liability. Under no circumstances and under no legal theory, whether in tort (including negligence), contract, or otherwise, shall the Licensor be liable to anyone for any indirect, special, incidental, or consequential damages of any character arising as a result of this License or the use of the Original Work including, without limitation, damages for loss of goodwill, work stoppage, computer failure or malfunction, or any and all other commercial damages or losses. This limitation of liability shall not apply to the extent applicable law prohibits such limitation.

  9. Acceptance and Termination. If, at any time, You expressly assented to this License, that assent indicates your clear and irrevocable acceptance of this License and all of its terms and conditions. If You distribute or communicate copies of the Original Work or a Derivative Work, You must make a reasonable effort under the circumstances to obtain the express assent of recipients to the terms of this License. This License conditions your rights to undertake the activities listed in Section 1, including your right to create Derivative Works based upon the Original Work, and doing so without honoring these terms and conditions is prohibited by copyright law and international treaty. Nothing in this License is intended to affect copyright exceptions and limitations (including 'fair use' or 'fair dealing'). This License shall terminate immediately and You may no longer exercise any of the rights granted to You by this License upon your failure to honor the conditions in Section 1(c).

  10. Termination for Patent Action. This License shall terminate automatically and You may no longer exercise any of the rights granted to You by this License as of the date You commence an action, including a cross-claim or counterclaim, against Licensor or any licensee alleging that the Original Work infringes a patent. This termination provision shall not apply for an action alleging patent infringement by combinations of the Original Work with other software or hardware.

  11. Jurisdiction, Venue and Governing Law. Any action or suit relating to this License may be brought only in the courts of a jurisdiction wherein the Licensor resides or in which Licensor conducts its primary business, and under the laws of that jurisdiction excluding its conflict-of-law provisions. The application of the United Nations Convention on Contracts for the International Sale of Goods is expressly excluded. Any use of the Original Work outside the scope of this License or after its termination shall be subject to the requirements and penalties of copyright or patent law in the appropriate jurisdiction. This section shall survive the termination of this License.

  12. Attorneys' Fees. In any action to enforce the terms of this License or seeking damages relating thereto, the prevailing party shall be entitled to recover its costs and expenses, including, without limitation, reasonable attorneys' fees and costs incurred in connection with such action, including any appeal of such action. This section shall survive the termination of this License.

  13. Miscellaneous. If any provision of this License is held to be unenforceable, such provision shall be reformed only to the extent necessary to make it enforceable.

  14. Definition of "You" in This License. "You" throughout this License, whether in upper or lower case, means an individual or a legal entity exercising rights under, and complying with all of the terms of, this License. For legal entities, "You" includes any entity that controls, is controlled by, or is under common control with you. For purposes of this definition, "control" means (i) the power, direct or indirect, to cause the direction or management of such entity, whether by contract or otherwise, or (ii) ownership of fifty percent (50%) or more of the outstanding shares, or (iii) beneficial ownership of such entity.

  15. Right to Use. You may use the Original Work in all ways not otherwise restricted or conditioned by this License or by law, and Licensor promises not to interfere with or be responsible for such uses by You.

  16. Modification of This License. This License is Copyright 2007 Zooko Wilcox-O'Hearn. Permission is granted to copy, distribute, or communicate this License without modification. Nothing in this License permits You to modify this License as applied to the Original Work or to Derivative Works. However, You may modify the text of this License and copy, distribute or communicate your modified version (the "Modified License") and apply it to other original works of authorship subject to the following conditions: (i) You may not indicate in any way that your Modified License is the "Transitive Grace Period Public Licence" or "TGPPL" and you may not use those names in the name of your Modified License; and (ii) You must replace the notice specified in the first paragraph above with the notice "Licensed under " or with a notice of your own that is not confusingly similar to the notice in this License.

zfec-1.4.5/changelog0000664000175100017510000000353111216211330013402 0ustar zookozookoThu Dec 20 13:55:55 MST 2007 zooko@zooko.com * zfec: silence a warning when compiling on Mac OS X with gcc, and refactor a complicated #define stanza into the shared header file Thu Dec 20 13:55:32 MST 2007 zooko@zooko.com * zfec: setup: include _version.py so that the zfec package has a version number again Thu Dec 20 09:33:55 MST 2007 zooko@zooko.com tagged zfec-1.3.1 Thu Dec 20 09:31:13 MST 2007 zooko@zooko.com * zfec: dual-license under GPL and TGPPL Thu Dec 20 09:26:16 MST 2007 zooko@zooko.com tagged zfec-1.3.0 Thu Dec 20 09:25:31 MST 2007 zooko@zooko.com * zfec: add "changelog" file, which contains descriptions of the darcs patches since the last release that I think are interesting to users Thu Dec 20 09:23:41 MST 2007 zooko@zooko.com * zfec: setup: require setuptools_darcs >= 1.1.0 (fixes problem with building incomplete packages) Wed Nov 14 09:44:26 MST 2007 zooko@zooko.com * zfec: set STRIDE to 8192 after extensive experimentation on my PowerPC G4 867 MHz (256 KB L2 cache) Mon Nov 12 07:58:19 MST 2007 zooko@zooko.com * zfec: reorder the inner loop to be more cache-friendly Loop over this stride of each input block before looping over all strides of this input block. In theory, this should allow the strides of the input blocks to remain in cache while we produce all of the output blocks. Sun Nov 11 10:04:44 MST 2007 zooko@zooko.com * zfec: do encoding within a fixed window of memory in order to be cache friendly Tue Nov 13 13:13:52 MST 2007 zooko@zooko.com * zfec: conditionally-compile the right magic to use alloca() with gcc -mno-cygwin Tue Nov 13 13:11:33 MST 2007 zooko@zooko.com * zfec: setup: fix the spelling of "zfec.fec" package name Sun Nov 11 08:50:54 MST 2007 zooko@zooko.com * zfec: add a TODO note Fri Nov 9 11:17:04 MST 2007 zooko@zooko.com tagged zfec-1.2.0 zfec-1.4.5/misc/0000775000175100017510000000000011216213552012471 5ustar zookozookozfec-1.4.5/misc/dependencies/0000775000175100017510000000000011216213552015117 5ustar zookozookozfec-1.4.5/misc/dependencies/setuptools-0.6c10dev.egg0000664000175100017510000104452211216211367021342 0ustar zookozookoPK]X9\OEi~easy_install.pyUT tIxIUx-1@ D~Oa4 e\`dEYim#=1437Km-V]U)#uJ1{&:lrk6tg]} ]PKX9v=easy_install.pycUT IIUxUN1E! H)rx"! h(P.嬭G${%RI?c4Gkr3_u|L7 là^9Ls o¦3>FxiC~R )+.z+ I)U>ұrj!T!'iOV"ҜV۔W]L\,gvywۚݮ"T}Խ3E4 c>aWPK BY9 EGG-INFO/UT K8I`8IUxPK X92EGG-INFO/dependency_links.txtUT ~IxIUx PKX9Wd EGG-INFO/entry_points.txtUT ~IxIUxV  =LiMӤmBq;T HP&]H q|kb;iL? Ooc뢵wntbFjP[ N eoVJ] !g/ C$9e<6 %^>LAk#?~`J.F" )M|2W >{Eޱ ᳷LרVrX~U^XG>V{O#cAW+v*ۡO|DR*[7R&4hh~epBOzLg!9hb$0``it )&g(}**0zoވ  V#l/|8v~;* HCgš)#dS%xX_/{>qB@EҚSPĨ =AeNQC"v ݊Y{)#u[x^@E_(Mo"QZպC[~6UN8ⓔ2Bx!OBQ>B1lf[ QYs6M(H)cPKX9t #EGG-INFO/PKG-INFOUT ~IxIUxZmo6_wn8I6nsWJ\-ϒ(n~=CRg ,ygy',O߅6R 5/Ăa*ُwS?YEu`ԡO'lSdi, LTL/SV=[6vJVg° nd|u*ĴY[-r;fJgyEOz;bM^OEe`427S#ND-WoۓW$ZV~l̜zZlJ{XJ+Jk v~~7`j.Ms넞>2U#iS#cS ViHz=zz3lݲFiKU STh~kHaYV8R +q^g"*Y4>\mejUGXQ|kh4Z$VgD SYӖt#ܮœ7WW:=0E3{RZчCܲ7#YG)l#qUPQ켏jGy1SEߋBKaNVp [Z(A螨?eD57e"ڽޱAY{v@ 0k>As:]'B^e 7/#%)8wzKt:gP^jUjZR#z3^Zh] 6,U%NQGb%#I P5Nط;Rz!tM%%wSs#SunAgj'k-Qr+rmeR3V*ɡԝ_td7" G/(ld5 kA{fG!ڹJx*Oun Wڃ䈭d[/|欋SOӍsAl !~ }]٭su cn{dX:axnVV !<n'B!C4R(oy&f,>&6g :RiQF1iG~HK|!6AvF'Ӊ;ء=u0iȷQ&; aG#]cS>t\leQ L0b"ObqGZ O銤@ U VBmkhUBSB! %x&BNX3EȆ-jFȺb [;XU<`h񘑾InffI@24%@BϣeO'9IN;-ZY1։?q`:zR#8k8ܛ˽H35 hCB'g}"q'qZg4W.ל{^!a2(].vQuzc;1|U5q/ۿredSIZ'v<4"#_SME#tZ\1_ 1m.nrh2J}G]O!V[rk6R|qZϮ Hw$n\> uLv c=sةˁ<6˅w5E?qc|:\y=v S3gd]k`[|=%ip4Kt2FLRP, t"!FR3qшF(@l (nHD$WWw^ Wwpqҗ໺ žӂ`9WJHTV=&)lg4SuRn_׃yok2 yVAKkQLݕ.|.T%51KNccCd΁Nks^COhf!.@R@k@Iܘe!hMOy̹~Hix$@Qw _?;r%J/_0] m(=NY$I*;ط,u&j9BL4^ G(O7ǖw)?g+'[c uU2l#ͼ0{("yAvWTuP)cV JP(C5O} nNѤfIM (ˍ$g+'+dWaSi5C9HeAHMhLWW?zaU?&P*\5ry۔BEt0)VVQ9% *nmc Q<3%-]& q\HߧuB Y iИ~{Skvn& bK")(8s`[&]DcpwmQ<6PF5`W2[hF޸=JVi`;>/brAGMFh>!PCk9,OIi3 )Q-ԠطR=* nhGw-C.7jnnE (M%8.z. m(SG j0\ew[m.燛ndg & D*9eɕ>:NHݻ,8T&dfit5'&( 7T_x)xv .HU4Suh#",snS_o>\\X]E,\Y؀fMѵW;>XK Ţ&f6/Zq"W͘'gJ˖0+H:pzE@;p)[Іjd`魪p&uRĊ\J\u^d'mu gv OvN~TPKX9ȧFEGG-INFO/SOURCES.txtUT ~IxIUxN0 .@&,hYXyzRՅ:q,qY'VձĭڤzX9%reBVIoe `DPZB'|G`N`| 7eb j4~/O|.]CXz݁~K=beDǗ5^nkqYE[3e9Z@(/! CcǃOwH ?,# $Qi`. FTS/>GC+}~PK X90\&&EGG-INFO/top_level.txtUT ~IxIUxeasy_install pkg_resources setuptools PK ؕX92EGG-INFO/zip-safeUT zIxIUx PK`X9:VXaApkg_resources.pyUT tIxIUx}{Ƒ0uZdC{iz$9ϑ3 09#:}WwW7zhTWwWW׫|q_ISYɳ/GgQ&y/EJ.U,jULnUY Βq|Y6b[7d{U4E}1IW%)>nqVh:o P6 @[A$ϟY򨪷+xqS4 З Yˋ:ɮ-PzS@z^U٭Ek@h%EY]&m Ů`w0ˢ-/qۺf䫺Yv[m6&Kj*| ma1VYf(SGO冿!Xbnum_tˢ&n- n>,e|>X۫z9 \S3@GY-@ ?<ɒ͒n[A?i06A\4OEAqQlk퓦~ /=\w|U/I*0#!ځ%?%-+8 3*g0׫Β5rH.vLGҦl,i70ZɌqn1_W)A=ꀰ[ФH:PR ~38\j+2 )/L3" Dz`ږ4kc -p.Šl6X:zWU~sQ cޭaKX}3'x '؏.meƮ[uYLD``_Onj {NG0#86M->&I~wJn ؕ*Z\k\Z3j_W-H?jvU!]>1\>!xuWlИm*n/x-v l {Yp,-X7eبI]fMܶ6i  U ^eEYJE,j?1ea@ 9ߕ+M_%kxuF=7YڝƵ]x +XDd̛۲dGpQQ0&_ 'eq¾\6n32u[ONOrA.Y]jC\f3 =-.Z>_|$ c/57HHoj.r_s# ~ u1#13M =/ I2CQ2ZzH89MNh>^mfU;CE[mg8CmSsXk8W % "vG{;U^'oyLF12"-FHNzݼֻj U'8G;aNAYm&&2f*@&mYCO}VĞtx ,сdS£`R``AcMFZQBA[Ti(z(E(HHC1}7{؟?>xq߼ߦ[,CvST+RwS\"ɪwm[ǫF/ œf|g0Kzk>PlޭV@?_VՏܼ 0'"(m#qfW0#- ~S8>H\]G94͛e ʜpPAEhnrZ t`ۏ-[prrBɲؠP-tIZ#?H{wfX](IYR|: G$o.[Հ¨IQV+t[PCS[׈474`s$Z.{^~'XE[f;$^\9tC#^^7 ?RwvW`31x٫g;T@28=l` b1M((<O>hzcw&͜ ׅE蹂< ="mf W1|:nUʗ73*d7j1#(@K<i,.YS53Ij7ck^'6I-1Cuf A([ڏp2%t&{=UWc"޻AGG{>;(-?}#̄7O}}"x^֮/ި2Zg68䙀Nb*L:==uAďHQ lFɮmՓ q:!9 |F)b%7A،qY4u[ l(8Pih|GԘ D0M;ߝ`j vp91KgCowK5Ȓb Ѐ0gF>| tu0J)1wOltv8/`3Ahk6rrpydl<M{I ʡI@,kh#\9̈́u BݖUrXk{Ի˫D<9FH5tQ0M1A1tqcnqs4Ew8iٛ9 }W@X:.|5kӈp@ۉ^^iixB5M~Ek/H?v& 94,sFVx0vY'dCB %.Scd,Wjǎos#\^fAZD{AL˜}{'3$ B<_ޖji&ld]x/}SQ:`{nD>1xxz]y5=N5nGHxF8Kϣ 9^ R "'uQ!,'3Ʌ7Gs6{3WՊ"8QAIi:]s۰jOG5:'bhD|['9H;QU(fNc"DǶ['z ӛ@6uO3Q?:"qCȍc +r 0:} <#?f8m ls6O(`0^LJ¾X;F$%>ϙS>a#)B%YA$VG+ŨUh[b7&GvD =Qp4Mӂc}׈̟%ϨQBJ5.T_5\ G B  ^[ N& tFQA0'> De8DW9w`Qě;~~eYO&Iƫ$l°<%!޾ɴqЇT=`zJ>X,vBVNOöVet>ț=ulMǝm乶'@ήքWZfMُf); L/bs'#΋! )rdɧ!it}GD ab ;Ӱ{9 bZ!9Š>+cxu14ukXi\w 3i^8\->kLr[U!wB{FQYZ2BĝF>:̹DXSGj\49=Ϯx&bV Z4])ׁbaT_sR1;u}\R?6#?w4Y :]8H4vSsbY+g) x ἇ%a֑iܭ? Pڒ˛.\*Z,c,9s\0E xdQa&SK<5cv6&61𘜳M7ToqO` 6EMx#4y" ]yqE2 4oIm P /:؆"lEx'#E+%yy[56@i; /ҳ . : )h~N;?GF~`P-R65`. 7>P];lĒ3(ߔfdЃX\cM!S?H_NsV՟:gFu }hjKH-Es~A9=$ |M>A"K}sԷ9Mn'`v7 l k ׅVȰ+46T ݻp2k1劓( +0>Qj[ZUnc,==>>zz&Rnür |Py04/ IiJ nݺu"0\*(`r{uDPFx@v@]Ab juG/ъQVAh8Eq1P!:, d4Zb5+x{ɞV7WNxLS5g3Ә%^Np{@N7ިbݜnsӣQt x'_$C0i"o{b6pqy{h#")eNUuUJV,&@? tVH;d7۬v@|:GOA%(Jcw grԆŌpVt8usף:O>8ΙGF&a;Fv;M_ͪC{af#sZWmGxȡ8C;Kf幯ٻ!X9~5aN4 W[$ZG:/,J/1ϾJtMs#;ά|:O.Ven04څB:o YI'mx)_&jrȽL!#SVv%auȐj9{,`o^&_mw=ܛ9(8kji`Qٙۢvhx=8kMSоFJ5|ٌ0=U%#کTaZ" w*ȹ6j N5\"wcY/q NuJzӠ#vG 2 FthIq_ZEw+5uf ,6 _mbK.PLX*?J녆;1/ bSuj0\cWfX6,tm($ .+;V];eg,Ppk©r0L(fiۼs+]ȱ n $'%owIxg* wȌGF.w hzɝ#Ni<ܢLQ]vl0jڵjEI.kXw#IX:;Qm6͞XA7xC%>Dwsq眄vQnSP9Y+~kV6hi.I5р-%˼`;KXNҕ3ۚf3TixeT`Y|]H%%ɸ\N`F_L~1ӯ܆OiEQTVs> p)[s˾)WJ{6#ؓ5߿3Þf7 ގ7bnD/BP9:t lV%Zc;W(NyR.Olȁn@6jS~[DbWm@BƛøCE R۰k&&S7Zj'XϪʙ@*f?dͦS.)㸣y,<2ܺzu^e65a<$( YΕ@Ug}b; 0cE,Gkn'>Srŗr[bKNB?Pݠ" m{pl>LYV163bCѶ>BչN/mͣ1Dxi9Qgtӟ\ SWc8'6LAO&H? {QjmNl٠IS;femWn\87-iF>L 䨰n!?l/}Ɏ \)+aӳVtھVEOZ Rm5ixo60*8Vx? <=&ՊnB؅ř, +]v.OB_}f~ zޘ]? e1W;A4bF"!J*TC^-#5蠴(Fe8tl-wf6i'Ed۰3 w'^t͋NJF\g%xph^!vgbr-y[N]꽉-sQoܢN R-T֋@ARR1z2d^h2뀲YԎc9JѸV /5eN3^4B{&S8p4n`s,!g 81-#g=ױw&['o.w$Lwc}ǧ& JA=  Rox9v6mKڒ xXhC{DW >}kFdݸR;!xX@5Q#Ý]ƪ@s:@{ uŒr<8N1@Xw]K/ g}|0M_đlbre{U.^b<î52wp'}5m*cQ*,hM.Qsl]q,8ۿd0y6DBΒ4ټ'_ 0~g^¡E]P䭀vMDݔef4HTjS\D\ , ܀JIagbS4c UQF0K{s!^D#Kz4#iApLdɁi7~zrTsp Vvjޝ1s<O>a$;??)s@gg33a_1ZBKBt nP-T.mOFrN섞E^ WyuyBΩ1߿y=4ϟ=^ɛXB ,2%TjZjDٛI!S1#?L^ E3""a;_ºE`ކt1\z9`olvqgM| J}&6FB,zT]a4K7Щc<^[#Jܯ2-V5C 3?*B0k ]Sē& Ju:B8w_#|./G2ijK_t3ެMd+d#ϴ[U r*قȰV\3ɜ?Yĺ v-TJ+&X_2a27t1WʉjNz<:ڮf#;V%7"ՙSjrX SP`%rL >'@b.EʖVPŃ %5":t,R!mKIU-kuw4y޼R@bx1:~R' "ј[9|J&%;X\ho):NUbnfz¬ɲrky7`սd9U & !n [dS~%-^aug(t{Fpsz<6ߎͬb/,++?꥝,ѽ_;o"bݏ#]ttHtoN@c]'^Hsjb Ѓbyhͼ cۼf -09VqiCn>F8V ֻvA&BR2vL$]/v.4k]dYij'iHq5P]`>NsLឹ$h $I ;na'eqU-/" K! ;%)@bUH.c7H6Q<rYU6=.or8 ?L_g|9_☇#bLb3L5Ѻ,cHh8K n9EBgMaOHN店E5d,}>.RB(;cd(b8:LKZ>-R =0>'W&﫽822"XLI8}f\[.je[ivvnq97/$.^8Ym]y. b |cr" eo[HwlG9:lktl9pj_|Lg@l=JLCZq t{tGS7Ϧj;uCVXfͯ:q(Fn$i;TB9GXpA7$ ,5u \OǙLջ]5Z)GϢ%7؏Nw>>|k?l zCj9@djMlٜ[ /&у@fMov|fM \TД!ɮv5]8M$}}f˚ȤDz%04 G(M*#8UŻp!Hfᗇ|Z\ Ѥc{OBS&2a߁n,4bs{/7聉Ɲ\LjfOݤ[`أ{k+T&.?m)c}w { Rݣz$tp=bIuX4)J>=VDIqp׵鏽f[W#nDr ҟ|dӤg1/?M;\`YKcGf$w@SUv1-~V tCDXM0迟gތUTgSM(-7B1y@UtҔpdiu}ib#H+N ֍cWt"gaQa,*Q? s]>Jy:y_~2dl2@gJyHV6ddE[\pi:CeK zDnp#oJIdB LsVMl:GQlt?h WA sm8b ma"ܔTX)!_a>`juwm@Wm@LD+\r HEv4wG[}6Q'ElT#<+G}wjv0iw>!w>۠,Noߌ|82ttsR$0a O1A,+O@GE2މ nZu |އI36؃P}|gNr`va i!e/qDxzߗrLx@ħ,nM9SR&/< ~2|ڊcMC)e9\rE.{{!,jW9SmD2ܰ{N z8]~=)]OV7}rA !6*Kqi,1X12JmDlO/2/݇szCx׿_я_od ymϱ ٯ>-~_) /oQYGO ,$rw 1c$=Y_v4*b1"+e'JL ̧eKvQEL57ai,6xt\锈x1;K#>y2߅"E.$?`@  G|} fTă0qA/AHSO6:'C{FG{0b$ju:*Kw*pQϤ̕}r)^1:o}&UY!hVSmĀꂇ56* x4f6CcP9;޻3Z͕X%ؚ%yR)|hCeJꆰI 3ѡ(:Q( }lb2L(FǮ,R#v ]R[ѥwK|dwzA)Vsє^*ߣ"{ѽƀ4bt.P 3FjdI(QIiq:]SYfP?R=?T,s)':G7 ooX`:; MOœՁZG<;C1Ҟ:͟:r\wlɌP swJe!ey1/y ;]TaC㟊^S8">qDXaYP^x0+0ÜѬ`D_YIKK䔛H9;\R7qomldZ,%d8o^|! (D]NB0H1%PGC^F c*~> 7VJWvQ'r)7V' HjK_, 4eC*d)\Cݫ yu޵,@aj mEu-OHa gRȼ:]O:k2q9}hT4\-9ym.'N!m0IU:#1Y/CM[sP})̌z `L"v2#b\Z,T gei&_R V*b ޿]tU̪.O]ӆ.jm}J$t@6TKoM'm*uTe:eiنx/-_ Y֟j1Ҹ4TU*n'}:K]{5XHpG sM< Q碠brwcJfhHpkцՔY=6y㺅L?i_^F8?1*xeO;L781X#f3ƚua&j hw-dA,9>cge0x2TA}Tyn*dFbsPe1/,:*-qfcjJWOڨ0ff$n?$ᰛbU,&Q`|1׃>1(moP]>6B?FU \Pn0j$Ŀ$vȪN`bG0N{m)/N0@IOqԞKrZ]U (¡{P-&eԠgZ -L股N]gZH0`kFZdpcNz[-rz@:SV|(y)1Y$6HH4R|!@ kMݺ qeY>e[uifӿC[ϲMbr8jH_rM{ƁI/C-l4aΘl[}esEKd:!/g۴3ҍ'P{<`sa=BjI>IcЄ' s(N5PU$竼qf@԰?QTVW%@&0V0;R _Vp4KoA( xWuWf4$LAsMH+lOg^%rmL.fppx_' >vYgi:4 %<&U$ŵ`$8*Fɳ;VsܑL&|ʒKT]BMN+3 !z8KEFS9ʯ1|>S!1p 2 maSL1qrMp]rEkSkK;THxN2=ꬳN. ߒfMWfuUVT|,9_Mǩs/vțG1*G.Ѥ9qtPKPN ȑQjv>\[U%J_,b3WɄ)ˎ&"`B'YY㣕KnCUkD4ħ3*7DUXEZZ-Ϗs+qwӞ +p=|-.[HiYt=SG䉧mD34N;x5z2|QmM:Y{9<28:*ܧ]cF *AD4/G \?^!b +Qݻ/oc6D=V3KRz? Kiҳzb?(Wmր!˪n8h7%+cydlxvŖ<8j6ӀoW{TƠfF]bZ-|Wm: n~b]q>iGBt4:8NǹyQItոW l]1͛ 3v^q$R.Ik͇-Dr b^ٰ .iC❌=@5Ou)h9v w劊Omb=G zjcŊgn].VVd2y[73 {H+hᶪ:/YfuFY̜aM#Ro,GDnZF ~A%rO-=˂I0^bIa!qVnbNO[*4IL ~ʙapn*4-^1ČQ r.h&>lPfP"3 ь2u6&LŎ/=6C;>M--ǘFl&i}\0%w/WbQ^N# dm\^Z~{y7Hqɓ\;q.ԔFhvVWI͆Z' EJH#'' ٸRDq`0M9/?>{oQlq<`ⲹ;Ev8u=Mjx^Iь)G50<)#DAxIر~%HyfT̹+dؓN9`c퉊z~pcz@C^!_㳰0t#@+l30J7X/IÅ|M|}N(Q8_?,̈pۏ蒍ץL"çi67qU9כ̏WiJoG<@볠:9ǁ1 SnvL6)(;'g u7ǘKq"4kzJܩ;00߅&yC'~}oɫ+3-דlWQFyC,jꆐՍjm: LtJOݓdhM݊5+MӴ~%}Az)C@M(>n~M;6ψ|R?+I1S}|WbNbdMuNNGJE٣}Lmew="Ix"ƢzTUuҐ5b>(c{ A) /K㭇_[m,HQ]Hv ^`iDp7I@Jw@U$#br׵n-#ﶫ{;#1RUt{go跣gttApNGܓͷO{2'y?cx#1@GW <^ÀUC F' X1\s dHfOE; |`j\cr}>g{|nd(#O&cլɤ/6QF3O }mF9LքsRc tέH'v3պFS ɫ%:ƪŭ}ȇ&8g(ǙTOao4d.p(~ L Wwf& ~<<'g P0H̀\I<#aGU~Z$B2saKTqjq (;/7k%5*M : 9rdo@4ӠNje+vMYjSYtq5<ƃS Zƚ9>PPi1$STW 6&1 M Owj.-^ mX*܇s~Nd_>$K*6Py?/8uJWl53AdYZƑ|6353ªD+'A9DgzDe5Ӄn3ps"Xԙp!ojKa*tK G~r%Z=t\"-Ls*7&exծG_3E !tܯiMgLQaP,%'M>/pj'^ڰ4KΖC1;>*"ciNuguq85j;=]k<x'V#[<ȣ|۠]Q1BD9*i; X4y1hv lC jC}D^0[A9~y B3C!A.AsP D>4)ѥ1e=G,0+e /h0(mZMo,w){b  EҲI-E{͈.RS݆e:hDѠlJp49f$P$nf_adsV2%=uwU -š$7A2>XXf'gypf<ΐ3l#(8f\1`Ha.aeA " -l+8[66+C?; ܁P$א;A5du"M 6b+m Al qn{@~w= l8>q?@Qq$ @L(8(A<a.GA<qOxS x3 x 'Aq @< ^38n:]: pKɽ ˠz.'S| (AZvl pp| ^a$^Ah]-Q0ȃIàPN\S{8 r%^"|GAe:?D ݝlKdcE!1TfЧjRh=>pgy͝ A1_h<@X4'AN#:5̖̒Y3苼%1F?k_yFYOM1K ^tx. >O8<=ѡ@lѯƒ*7yPc|Q f %}2,/Dj< }Wqua|}ғj Y6 d@~` |d -@򉁴 G<̟Dh:6?N$r'pL>8@Oq38:ଂ?:(. ?M'<V*'eSŲl4̔4zlb{.*ÏS_KA0.>Iزg퇏>r}w0JZ!ptV+d E~?s% -ٌV'q| A(0Hy ||kE#=3U<۾JopG4h,-`ϸ+?9XEç\d%pb!/"aəc*A4'%Wew"YBk5Ҡ  \@,C@%P#~?:Gwr0^~hiAi4ƬjBr;VڇdT0y[`ȥbXM,AE2yӔbѢF@XWy*PYzD7`( .H7H$,ȤhXm:=n]:- 3-GfdX6\ИLe2It(u$~GvT8SD&g]>`_Жv|n;/wP졓&12%h ('Qc'; {M kJobHw) \#WJMHI{2b(S-&`ƇWJXF@aXQStL C!y6Fr=dwP pOlFvH?S;nCJbƔ-YŐLjcqӨ"P煑~887ZSAL)ucKʳw+vY^fO ݯjJ(koυLEnrl;.x9UMFf (:Uș( #R$LlVCrg\eIB:N6.+oM[[1cUj4L"^5"N(\UxS$)HR@I0D&Q&1$[ҕr atȨglc4WUm7DX&H'':Bc'k0 Ud t"X&.|vh@92@` Ix_O"ͻJ) :"Ru'Ud* ʋuY(κƇw_Ux:1Cg>f3eX a&Iv^w.L ;_ (3*ɘIFŲHb48 xܺ'3YqB"wd*IԪi  vVHA>`4RoHP 3?_==p;Q{^8JԌ~&O0ssV̫3gkY7dQv!f9摪 &hdDLt3Ē$H \5)t|ZGDAnUA[٪;uZMmYY]6+13 F(xbU>%gc '%pn1թy,p˄l)f㶗\,MUu ЮdKسDdI kWJʞPb`D,Uy|b1#Q#eֱ|jMBc)TFGyGzjEo9}L b:wnTV"O^[Ct1UH0t$%^bPC 7V$}ogw` (r0+S\w]uW-Bb.],6*f\K}kL=>1٣#tE${21EJaH6a̮Z|taEfFgҵWә =P/C͊ZMdjgVbT )o*.Lõ'5I;\ZO#wÍT1/\ؤ𮴃@IQ:*ub)M*MЧ zoY,i ͣF? w"t9%4&*`ܳ@5pw;`yFij݋$.rúf ,&!F +ůW^ 0!+Q7h!ՁnTd3}tȍ̕9h|;ln+ԏUQUH|stO˟BY!'$T1AiT⼱\9,~[6qi=Mqv&2D~/[Eu⪾ˁ..kgHC5DP2/qlIԉ[(j60ubY dAt#h|xbH',Hfsw#I3'+[Q#!uۦ^]qB̔FsVfF)ҝ< ma35KA6卫T-߲J)%m7ӨŰbr[,-˔z?M9T1=1vckd4]WϺzymaT7-i7_r51߯!Vݢ.!URKD֟a7qj}o\2z-%PGVu!KisC9g tcZX,0`KX8ț|{k#TN޵ {31Oj@I\կ7yi$G4l)Gf{Ue\۸<ҩ2u3AJ&ÖJR)vNTJM-"{yܶKZo_+kr*~vʸ<:=  HB (ɲ"MQ"%1@zH v$z0cg9A16Kv}ۛĉDIm&&M$4M[M4|Mgf(_C!롁c؏S/_H~c4B(Ṅ6+j5d<q}YvbaٔɊ\{URBA8l٧\/lA ):̾.)!묏??PMJ @3]?N:Lϴ_)dSP@ Ǜ7)'+$N>cZrS-Vk;r7v7g7dm觃;bzreo7;/3mÊ3gl8sH*կ`76pU+Vs^44VCsЂ AT%JRZ^ i\Dp<"԰j6U(*vB{~&{=Db,%R_eAa^FMo˺~FK,)uVNcgpc M8'G$B'NPDoRL~^WxUzXebtBc2z>G|ͺZ| kyS|OFȘ@sR$T[wظiҹ*b/(49$YOWU R D>1J𙣁ma &ICr"5F/ݖ̙gIzeg5l[^sﱈWتb6­Ķ=2!\*4O]|I5OCI[!$֩CbIy/o62<ٓ޻MSWbb`d,4dB"v/w`f$bza.uZ ]ͧ(ہqcyU2+McMnfy3c*֬;S`_ؕBncBʪV/ffT"jB =#yn͂P_划+kbmEʑN$]"%W<]GYڜl웍jtO+#p95K:uwC)$u#zHfsN6B ao%LE9ӂscA'Ƅ31`#džhI GG ڗ%L$kH .ZT)!d豶ZQ$I[+p0))yzmN]뭷ț0$R(m>wa^ږƋ{OF\ס;wq D̊*g԰ikv~[#*4hT=7S;vk5+a͍ˈn9If'D&2r^yEo6d^]8m'xl8=*j{_jюǙ4ҕR?X5l[HRGMѓSZb6daD}̇kUhklKf\6߬W"N"IXiV+˥* 0,`S̷7x4?e2hfyF˵;b< r;t$o Ӌ SuM3.pQ33eLɪc 0\ԕ̒g&b @a$];pmۥkDVdu\]EKG cJ@(zF榃EQML~X:;u %ԅzxUt5 77iڬYPTFaAO3u3_n3d!^Z2eQ"u ֢5`bPe\T4(Z]>D*f̑*`]KK'ݓR5 !w4HS3~&H'D63ijC6>V>tgN`8o-pQ1zl(a1 ڊنZ Y Ü`Ӷ:F%A.|w̹k"qQ"HY_.u=ch[zjٙ%GZ&1F"O=;k5NQ,C.|)-]T;sR`{#~4{tN:qU%qj UBUQ%J{;3\6WY]V 20ͤ]OQhJ,-q#@D01|Iͤ,18KGm 7}};b>ř2|GȀ~^(>!LRmC3K/ohH'dmn$;ȎFѻF=;vc>܉=y$jU~6, P@ YVЃ B{B0UF:cِ gNqO#l֍ͪ CDNʤxgdl'PNBAeN0Sf>VD.끔'n9EykD/~cu8(6tz6Yw{^xCZ^{\ǖEjn5zj\} :+$O)F6]j69"cya9=kg k =Ǣmlnc%f3f?Jai,cGvsU)j=ÝMkvpLKj('4B>G qC#;P(oc91L$G~D={nNN^{Y^;J/Qvd%iq)oX0; |bJ?wR4nOck Zzl`e0X;o *8o X=󂙳ԛHǀҖҠVS&sN;vb~[1eS#u /',q^#9ϊf` aFN":xK G#aQ.3gR$3R*2̏odt*y=qQ.Bfܤ'vη8 ׍Yv!{VS!u"b&U$б;G*p#b9\,b|d9N%a|~u-Obf`8^߬AԨI#r#)9[L?Sj 9.B6sQ7ᚌoI4)Urm[e ]ޟMY؂ |c.ı~^ԲG4XC{f:iƃ8^kjݼhl"Wj UUh';ý!L,G;3έAs٨Sb{,c EǖK^N "^:x/5%EUNhQK`TلN1JQ2^ KyRkmک ԡ83'韘<[/+4@#Q&:S3c󁑎qH0FvQ3:+b&1tq-c;02\Ʉ-eDiZC^9>O8*KQd/2gO~f+iV~QzaoT C_IFTc_?rLbj6G3MR,aG1 M?w'\~& 0?F)MKbj]2ULטQ6~@]; Jw. "@ޥ/ttD7I{4HwDQ=]l΃]F~GN]6g4)~ANK|"Kv5e/[1C*' q!_(*j9~%tu3,3|V/GXӡ(S,vk[XIz\FL檃*!_9Ct3R pF^)f9/N;qw%ԉ'ȄPvkXK Ŭ& G nx\x({X$F$QQ jqmu#*C!>$R zI-"~q\r(cSJ4o^hh"5UWzB-כ!YP3"o;1/f:#LSQ0ˏpRx)zjӛT^q۳v(tc^j)S7fM]#U^(Ek'.$ }̚UZ "j "46uQ>ZDBec!TSOd"Hx+P5| ?.],Sax¿O#7Xe'\ B,p*uy솏PĜ\ n.4Q2і@UW`DQ+$_BΥ*2S ;MLJQ}tHPR8p}ɂJu]rJә -Ѥ}.>|iHMl> U ɏv0{>g/̤!qJWrԊLg;VY+6C4[lLBe$lB/d%mUYI$'Nq L bamvŬ7FN Ttm*ʫ|ɼuapɳh6BB1Hc=0H쮋lr%QN ;kX%ef+0}!F4aT63#ESW= d3(9I~tctU?E{ht=cYTc^UH5YCUɳiNr_^Sͪ.v)?FDcnad\TNJ f9]hr$@ /̀客d8kZ x1"$rҍmZ%OW47tLw3g8e9քRX/JI:<]MT6IeBKu'tha='hmʽyZd Zj{f6UW661hkO?a^<ʳbȜ  )V;k۪HNXlwߕ Jµq$_le13h،X;-_S4E4DۮϮ hmwt:zm'$sKX3G`B 3#b.6zVkn1\*p!nA+_\$}BpԜ' a4ٜMP vȪ2B/rV'BEޜy|T0Hfln6;>uش<6'1™\>Jfe[s^Tfy]5e\L=^eRޯy8ԭ:CMjqCB$[1l`"bOyK16?-sT?Trpn|U1(ÜSFfƷ*IPX;6!-\%fU"34ƳʾHZҼ"%Kf鵵p*]u&%z.M;.0g܇x{tU gBqmsglΝ:y$Tϟ.+}̳N*y4stg ,:Shc5@}sFUтn"Bu8]q-.m>>s/Jn=.\1IfrWi$PHPlkW\Zmzj0ѸptMzWaorI ryF/1w^6 d)9`㍄LddqjZKVJuÊ2˛2ZL8AQӌiЪ.DEX B eCx)a^G.A} Jv-<9Zܯ穜H˩qٵvOÅ*q+%ԸNB?>B]=N)'1@D=TϹ2CPzzF^@^| }Vn& aCم?TYT]ʤcBzk lZvثlK^ȇm6+Sf%wS4Z'g @{&('zRI+>ÊQ)g$ג$ћ^eoJo&IY7{IY7D41ZD!2i*p؅u{=fel> zFB{+cci_,ۦ_T,A- klC?ҬlB'hŖ\b"J@r>h(}#HL1 JvCuZF f9 _c ۲jG9z)wpm`ꌪf]fmT 6GӶ/%ۥWk#] Mt x`m 'pLU/Zx~M"gH,]O@%ɈN葁?ѱ$o֋wXd}\MhrJ]ipvMݯ^(n_?[{*LkrGnWS).ϛˀ+P=`Mh/XI'TĐ֢'Mz$w&'] ۔L%D~5'X$*=qCx WMk-"5nd}JpU(ʃ,6~.0Ã!A`(}[ZuZf*] Q)0*SҪeRడ͸AaʘL@ؿ;P㇭wT+\PmL*@,|rҟBxLF⓿7:?Ƃx 6Z^4E9.(C0fgVر`m=octkRiZZUPɳВ+ z=:&uV Aҝ~-4/_Z#Q\s~x-aߐ7yM\LYyiw+5}u3=#Pr}VYxҶϱemz3:cݪE1 |=c2cп=s?M Ab6]XOA4w":I$Zpw |d|TKٰ7Mc٘w-cO:V/]YIAۨH Y2Oފ5'`ݰ M8\Gs`X@?{}Y.a@SAqXhD>=ѕ -N~!L{(՜gkmNq@~nEUNgN`̞j7km)Z4J%? <\U0 1+vrO3Gjv;obK{kbqAPp [*?L%BP wիv(^ i::bgi.x>%S󮤝 ;I%O%d[R):gf.GdR2þ&QS 𥶯&<R.FԕlT#N#+G;؟O›Jf:av7o6cIٚNAh.0fQ9YAosd(xyLO0Oz PKbamR:>l(:D:xG[D4E2K'GȰw}?RԘq6-e J!\še.g;#^ p!2w5X+pxpK۲]N19|d5K5)\CίY\#74/fZa1Պ-"HV |g\Lo9k!ɥ /E.K j|rHzD;S5I&DXΐrS륰mw$"WvT>eY\TMiP;^#z~as$Ş5B`ٮ}(ϕ]`| ~W˼ 3ԜnKw^遴~AqJyҩywhx%Zbtn]'E, GuOEjhұfNkKw| /7WzgJsMo+j (Lt,a/q@kRst6{Yz9 u7oy|e)%U壎KsR (қ9̞U ֎1$wηǒBQagrI[b%`{JJ&MG̠QAq Oz*KĨv_1E/.sEΌ$/0e#!={ZOnSMqûmK=oyM.ߟrP7a}AM"R88 NN.q@'n ه. v"NIyNJ qyY%u>6rmO3GI9nL:JoUQ+ub }- i*Zc"ZHDR^wιR_KIa{YեéW X FElNgs@̟Ѭ6KՖp!(ɮg(Ʋ،L;ckN ?)kli%|%?h8W k?9~-,_2z/_ltMA%+>W[ 4Y)mB+ِvj@ٮ1RPݶ'aK܌ZOU[v[xz9cȂ}V!l0wǔdx}>_OiĄ?aР?nDz9؉D!ٮśh(WfM/RA+*Buڀ\G%ղvgȖE>P0*0&N33+2 !Y@sSc]*%P]_k+mՀ6wrM`C))- VK[^ ($RJ8=Z Bίv(:pߺVt׎9b-v9a(q ',{ S)e"2 E/L`,NryBK}OauO~G9F@1uHT_ u g&E[?uqIsR^uB}M3⁄hJ:[ݙd6z$D0վ`Lʿ^Ɵ=KLoAIKE+VF-m1M3~=hQ\K:sF[:-hdN}^-->Erс%3}hJn=: gm5jKKxZ O׈M!^Zj8*.`đݤ "_1*},yfסNWKurhɕ~TLyw&teԫFhwQrmk$Y/=Է Gݱ z@kB TV >ƒa\-i~iytdqtokN"fKX'_"1R,ͥg_IяYl} F 4NaķHki-tCIF\ֆXY29 \ř1kǴkߨRhxfs>(Y+rLcd;@peEO=7fҲy(^_9 }C5;@XfT#FFB=s6pyhi)iIjߝSpKt(gx@ 8>M]~g d3\1c6`6L2 , fR T"䩋onWrR:2,Ai6:.Na N[2'^T"?''w }ޙ>Lqxf]^&ᩥ݀)G& ^=6 R:0a0v>z)<Rw33/]yq~|wǏ8>yT#<*.}w/];2҂y=|/3'#5L~Zmm K|U/ߺpdvDg^_,Ϳ|޼E?'=GB eR',U(埱 yg7=<#5TaoռPt@I+]DasKkt J\3hPͶT w*STTETrYV+TUQ$j&k 7mo"0Q2,$2Df2lMhy0ԍFc`HuȫR| |? m2Kg9ee !zQ#ts>ppN5(A+*Y;hB S W" "I LlF y"90x=eu/ӊް@| O[I١&ZN4~ڏ殌Kl6$0g''7kjV j(P'"])$M3쵢!7^,oъP+xK0kVr@C"~_ܴE2 Z2Rpib+|pFC *m1F%2aÌ61ρ8ȲKnzr-*%zT)5wҘƛFl毵poX#&W2-VF0\lm%^j81xL`s2+1`ܙh}A{l76]Tc_%q1Եa=?Lc>H$΂h/K1޻RfI _{'@YFX3צҿq>qJ GL &N^TzGb7IV/ OZ>lGV ~`ikRP]v. g70cU%,Qs0.M'R|j2 T^UV3 Q.Ig/|HuVȠbeTΔuid!#rD >G(U1|9/Ǽ]QpH O;zcZN>!=>\|AzGI˻$۫ŗo*fW›Wop%J \jEIn2$V`üb,򀌤͟mJxIGHeY$A?ȑx v^g'"ltYaYI?߸h^kq֡Yk#Y[YNd׵sJ+ %'C9H&cv/%Ef(Q#,pƇ$O0\+Θ-]7.\"ܢ6yJ؁k =XKzNjW<5s ,O-Ly{x7E주Bx<} `Oh"X;n2h0]pW?]~ SJ"1HPv72.-6lRwe@&b[͈>.6],vT+3Q#? q_HRpٳ*X'G2+Zy︥[\XL'Uwg HkeRZWU](nrXb':8-fDd-tAV6{>Nt=]eEm7xme5ou'=n+G)n-??5YY?`*ukCCŷp,92 O& de6U1-AylA:Q5\-$H=TEeRr!m_P$6 MM+L'5 ~LLIr,L}bfaA;lTjӕǒ׵|+3'7.+16_ ?e|[M[ax;?L94:":_(a.Ţ9%^]aH`-t⬑tvLgGJ~+cuEnso?UJe SHJ 4Eϳ1 с Υf\~Z(Ƿ|G] X4@ll߄-?\c&,;"ohQV?4)kV44P"<wbеb|{`gC^Wp I\|`8˭m8UvNX'J(fqMY6afa1}6+C:*$M("Fܹ~/X {fv#iwY{Y>x6T^]%XZR+Z9 xBoX66؍85>R;dA_9de4c{[\9΄ݬ \(͢$繎[n"~lvZyx́Df8*2ݮ0Gv}8?3> YǕ/YQ6T)W qd+ۢxez"G]-X U"ж Hl26 VJ ^#V NՀJ̾;Ҁ.j{8RƗoF׬S-*6EJT,ws *IAv{cnKWzWč"RLj e^ͧ"GX拮DzXWnڒ8}WA&.0t4j6o$crBfRM?D4X.*@]dNLQ%_|VjLfFa&BzzH+R/# jus/͛ƃ27C FJ3paU鱶fa@(b,Q,,sJ+)EQ$,PgTj-V JC T ҼX!1 DĮʘk1./rj6YոFH?0Ɵ.d:p6 v1`6iS0:2M֗+A/ Y#:@9 @7EY!Leo/ qZlV]Q'96%>+'ec(3ʸ "{ gY ;%2'(Տb]'dFlسBf&2PȼlW1D9\/")C3dTѬEEq_a,1V\Wo D& %TSD7ut|>?2~fxjtTciUfrqu73}( L39Y:QNT}7OzQ[s`^MCLFql2l~:HW*]Q qL8wS,Xm،*60`%Ya7O72,=y n~NO)b}[1#]zq)Th24ސv13,Km(Csh|su@H#zv™OQUjC=oT34/@\PFɳ=wF8ssxN;x_y S ǜm5^haķ ˥F7dGفA.FE>L`bu?}kD?WXc=pu͆mڱ9}Cu >ԙ gg(|m/K/.?sv?<{ft)qق>M] 6xuM eoi3ذTmƎзw2g*ɽ(]03 ɀ 2g4{7ޓqD&xPē;1DJ `O!Ea9'& C XgNxɠ 'Ƙ%KB[]z8>>ue[#OǷ{':Ogֆ Qy݋dGMR69QB+R+t ђzvtwO9TYyTuD#;$@N䇫%Ĭ\Y@r %eZˈeqo2g3̖J܏LQ/G+ -^KZlTX$s[[x=` %ֆכ+]jRp9kdXK6נOedcXcUvqվ%9b![%й9c瀔m+,f)ayIU \kԈkrv7fcby2hZ#ɴ}|Sm{n4(NzZura"ޫmdyx}m=S0O!yEKzJ /G,ؚEhD{# u@! ʃ-<@,_@FI"ax%"DKaGRbD#Vxn#}!aUxu]sgj

tf YϓDƸO??&ى7W(IV+YUXDVu+B5|#F~e[9yL/]2fd*RS$I6HbJ3YU^HZRxӴmxQ*I hV]u[ 9+߆FYBd ܬz:2B9bW7%N͑ xO }S+̾{2>,"9Q$aJXRV-9ԅ]$;y sZV0kB vvIH#^? .=P=}%[^=k0\u~KVE%YkPN|ӱmک(iNkayʀ,BLlgl<0tbhE v Q&۴)sgqz` /-^^8\w70Tgۙ(h)ZVʀL)2\8OZXK ;X[[6Nmlgr */c} _1$|3J֥!,z2ADFU.jh ~8`!;ڝ h& oFZwFH,1?iUF0oYHL9 @8F߫H`$,3A3eQ(cW[ 9SmNtsJdG Ʃ7RTu0Pi%%]{9/ѪY͡:D=隠{Fi!oo:dQVyp ^|b"sѼ,N4dEN t 0[P]:0xVuB A Y BBb̐ղ>Zk1 wTr`s!.6nXk6VZ Y 1⁧W:wZg{JmTX2K4hFRH`r˶k\~'k&=齾IF^FWݵ Qwj H:oB,IJ$:+ NDV#_(CEfm)5mZЌE8-uK6#n-E8|cNѴ<9 )9p: i".(>. P|oר,N5X~kרj7̽Mn =Ud]͡X 흁_Q>l5.-55l6v:Ia~@|٥|]~s#n~4EK-B{|%V4kȝﴅF,TU!гGJ=XL[oxձ+mgVWMm>ƴ.Y/%b60kȊ bH (m@)d`{um`=L7^k<27)Pm16\b3I65pPfkJ+Y{2|nlrz$tskvi@FntݓX>D\R Ƚ'*{1W>7xOM=W2U&N؈>E:Ky|$&cύc<B9{ʻ=n_?N`z_`[ {L1vCVjV=VoJ B6ՐG8*/ƨ Өęjf; lzbs;YA\\Ń~tT2mٟ:[ !q`!A`4Epb֮g:>1 M<5+G|]a2 MQ%JǟV#|B a0TI>.w/z키ǫ_|xet`[LvZ/td@hdI1?` "M;3k6kQ\l͹Vf~L|!h`n+ؐ =BY˟W^\pS8|->>&d'[ks' wO&pz#{򤑑OxL<~NN(mbqCyB#Rt/剓$b/w|F,b1Jnī A{em0Fc% 7(B'#,{9Y 誀X]0V6Tl?^ pI%;]2iElȰs๸_5MMk\Fi5hSgô77^qMZB͓aNN33>+Awbzs|dAjFP͚<=i "tJm|Qr#RuVjth)|^mM?(,uz~Ν?:GjPE~Km!Igu*>/z\؈讥х̢q9U7ZTCmۉ0ivpN0&,cqlTwep,QÌ=Y38{!) %=Q* GP J<ߩ cG_٠safSHՕY tUega&; jz|81ja$OhOW1:*S5y}ZXg8m|-6o}sdA?=vZosBok77f杬L@jmT@En_5ܳPX*M cCg߼:{P`X@ G?݇h[S{ī1iVlCnJq@V0ۭא-L=َd옧$eTx JGPo~RucR\\Ԍz!T .A mU54C]Gw!2 iԖe4]Mԥ)EI_'hl 齬݄O~ͅ_ʂiQ+ʸpz*Vq䙿1+a_ 8> \:.a2v<<]=ҭ7vařSsL a7^ Dh,OY/<9YkkUPBGf!iyQDڪJє GJQ*.g~,. VX: o '8)ug׋Nm(҇ahg )%՜?g&tv/:b"NAk/*+|>Ef3Xs4%qڏ tsEnHJu)12ϢJxir0Ұ}S!ŦNP(Lf|}L'].]M-n;S>.-@h$%c C9_k7Y /{yms@m.oA|Bd}O~"/ŏ?hhlYoq@҅`65{Ʈ-j&4!fn&ѴpS9!E;0چɫK.;+}/^!\tw8ṗ8[]nD^-͙<`Ni6h}?_3L|Df Z(˞qIJ'gzI->JG99tT{9N딠!X4}R /0 _${j?PK BY9 setuptools/UT L8I`8IUxPK]X95f< setuptools/__init__.pyUT tIxIUxVMo6W ܃D+,Ŷ9-"@OA (f#*I IYv99l|8:mFހ#v~zp9  =0 oLkd5p3&d%H*{àU Pb f'=vY4^֭a&> ';=.׀Auz6ɼ5Z}i\-Yi` ]YӪYyʀrWRb~UU˳, UMȒ2#fY=\8=Z5{;n"4D֎`6}{@4SHUzcO pC;7OӠQ `ZܧiPBX?>9=h/pGM<$vPÅifZyj?pѫxsVUǖArQPNM4&Vtv5Ze;)+iMy15y 'utn!f %}Yȯ!3琂'SגF&/q ab PvL]ذTpZ&:98CH <= KCACǹ29Lq~,yS_zJ؏Uk4tWc1kR"TVr-^m].orބ|+vIWkf+Zc !{@T>ʭhvpp8˄a]J`-$[IWB\2A9jδ"qiKGnh@L磡~GA ر:6yf?q;Yz`Gde=ԭ1)rkt ]"ΖWՃ{5Jh,/_rs"]B YJyJrwtyZ-jyTkq%5 ],pjy5,'B(؝Tw_WЋG[\o7jau@qM&Ifo_@4sePKX9|[Lsetuptools/__init__.pycUT IIUxWIoE~ճOq, $QXB,!EE MƮkUŹ"7ĉ{{l'D]m_ ݚ>?{C$#$l H=y`TA5خCڀQ&`*݆QyFxހ 0Z(D.¨_[24$(m؅E Yd>l3D9:$H :}F@@P*d#CoFpnX189 YHN#d^=dkLDZEfLOWvߏrp9mrς"d$SL jmLΣXdnKgy`wKjJU iL&rCI[LV, _sci9LɺP WKEIyԎjTIRʈLs9%SG)Ih6D;,N-ѨeYL]X?dMW[E\8HiaVIċvǬzEN mmqCMtc̔,*_򖣺\] @L0NMrIHdlBuGVTj2k"qtu:BWtXw%LH,Pds"y l=K$}47r,ovjcxoQ`nP7Nٕ׆7oyUmn^e79cR{j+$dDu⌨A %2bWKqydGw'@qKASuB7BD  Z Q}_@KT#yW΅};!sp퓋8;ª5edуe_"r12e Oȗ]n<>|J yo6sI,@Opǵ9A#C'<ԠjUwNMZfWCEܭ+2KGAqe"yʠsrbuW6O"q^5}P?LO٪^Ř c$E-KL\(E=wl=-G͜0+{Po:XTaoA(A^3`jbe=3݅rku^'X/ g&xe^A C9كyCl zsC4c1`o ;\dlT<;r5iZ rz~y j 㢢fa $QPO'mJAOznd7Ա1C_\%^dž]*{.v}^j&. IȰoTnUC06-'dD'EXj[[ C2Et!,)qOJQv J=eDwJ>-iE26N0K W6G"ٴ8t,L)\*6FXݙ e;#FL/ZJ̈́1 ?(*jn-;! &'եZ;6`n/c+(,6XlM֍Xba;^yaV@ʶA댲( NP^vt'=Fs0Fs2V"@ X#iOsHaK+X=#OșSTQP wX!kZ#\VF;IWWVp'$e\1=Z'`0IGX Qߊ>XybMg] GPea*>eg ?"Z~pS&jF;;sGf-, vd+a1g"CNѶFB`1&`a^@ f!ǡ&dl׶erz%tBAf" 9ꭧZS E3LH0S$2uՉ‘sd5QH}Q`L!fjI0;(O47C pT)=hv Z[&`/;nm}61otbmA q円ŠLuG\NA{0 eM)Ls}"zP2V{=Q#y4Bna!NPP E[FdLtUNPO{nVj OĀFT[_`ЧgXKk0bhRnanΡ;6_'盀|~"3q^Ƴ9&Jk h]KL`!F WZ[RH0ܝqcX#%n+cDT3Dz *efɼ6K熾o]vJnZ4G!ɓAN nd^8Sf[r"`OH^:2;7Wy}^Fkl62 |fHF\$v|+#fGN jBse6o/plx>7iE\0Z\E&<)M зȏ?EnzN:jqB{U=dCR\5N38`-\fݾꍢldz'| 8PKX9X^t setuptools/archive_util.pycUT IIUxXoY=|Y 6/8heb fzt<{1̙H8sB\8@UuI]x'Y^?~(i_EpA UUkȂCm8M%S/a 8WAP{ j0aeu"&x8\F x;ss^ 8z\z $aO -?h_!xICa:ThtGgFVzdQGbh,L.@l{ءe'Q*xg2nH7In-i!.q: !RGh뇡ʪi.ΚH9@=X|g ˅j,m6aETzidjV~צANAlvӻ߹ynۓў:KtO^q$3׉EE*i\@!c8 'IQ*ˏdjY)q88i{D*o%E[F.|_ ӟ܆B)?{K0Y/l  w_V)Y'~adp]zNYQw*sYhOb4Q6VqԗN1 #\ycwU2RO`gө͔S&ᜌe*P3u eqc 4S, !K';SoFhBe9zJ0a kSu&LJ=lӴ_LvFLT;1ʴΝxȌ,.v"Q~1v Ф:A6g& Vg\,p,I& vs5"]9MQ8,f9 B"P&d0r /v^5ɖswuHa1rkJH0'O WƊ,fHC>YfS  ͓drAvqg+]]y:PHs!;'CggNfq3p7ni/ @E1"GjEw7cU.@oGYe ^9ۊ}K^Flqlzm~ɯMl8\Y/w%aĆY5] ?І GlcLɏc¯GD^ pZ >)BQ[Zp^>yg=:̫06feרE{epA0 _y4`| ^ҠMeŌyt5!,O, s \\PF*C +,n i=q=KS_zVkr/xyy[]0F46{mJ4y4Y8eM s798\#d5&dDq24ۺMVR0\O<&8@7O_I Cȸ#y)= BL|Ul[E 6EKTSl⪨?rtՋ]+в.MiW/(A+! Mq +wu19EZ2TE!2 URVL1M)xJ[/"ti11$тn [$y".ڦ)lT"DweY"8mD` az0CZx'T&w}R.OaB4i20cNEʚ#Ik%i_;`EO84#c0#W HS(ra7xˠTa&y|VxTzWE')\''2ť-C2޺m8'B"Wk!718#Dd0 !ݲi1I GHmvl#h^B)ݗn}P1? `/,WӿQ?/q` lSBQ5FO+H]@]@_#Dwpf1HB`288]msX,ǷKb Ooc}]݀ӁJ Ԫ9~}+}(~!YW ӄ 36ž70ukEkES6.UL >U?U<5]5^P1 c/工Q'Pmrm*vO*2Իgd*L)xwv zq2"ϹX\D7٘VlnۢɩMQG{SRIG'IwͨÛ^ަںItr4%}xS♯GM_QGK`_.nD.ئ;FWJMi4eݰ7Q3_PK`X9? Asetuptools/depends.pyUT tIIUxXmsܶ_GS;sGήZYHJƮHPb#Xt]$ȻSڙ$ž>Q+$ykF& +Vj lQ܊^wce#)t419>X:_>. gAVhӚԳBUK.T)-W$(Kwή?B-cʒڒ>oq_I*mDepY>FfX n -:${{{Gnd0ŖmQfEuT /KMS,A!Ue@,20IjYq%V2FR%N؊ߩŭs23U8WJDAșffx*cn 8Q>qvM(yk'$ეhYdA:FJEh3=cy "E RVzFf:0<}>#ftv^z'4쌦mTv#UO4n3y2嚵Qhտn8v&  ;y~|Vz(;{ﰤ#f[J̝I'D[yO#P4mUZʆx1#;@P;^ ^JѤw;j,MݙZIL=CRݩMDaB3]˴ -e+Y**p)XF6  sZ34A6B ]!!Q`!0 D= ZG1kRP@ZN!ۺ.A 3߳F>fBy\"Prlj Gd,%Դps9 >ږO ;!/F5ȩ6 R8wli[+݊I?nm?xI]*NxH0mc:2Ykq`_.3w!2cҶi?r!P\wH:rڐ;jZE&d: 9 U6EC( $*L-a?x(9ajo_ǟ?-ήbr8;^e\`"KeT`P~JY=ڬM'Pi(%yEp͛QF|$GGhM/_߰w7|-,/`mz>ʹ (-77߿=8 GBDnѥ]'H?6z3r2oAhaeq/dTl:f]Gu⨏Z45 Eń|ƣР#~ jUM^cSwۿx׼E$pǁ L$l~! ދ =VM7SA *i׫*6$ "q7BaK ՘ֵT[ή2z)SݿDA{ s ; 2:c \91}Gy> $WNA^ON,lMFB =L&ShE%}Q-R'U2#Qӡ{ huIpLFB4ITYv[٥jUfNsO23fV+i(t;aBaqN!&d^kMGtpM=Ѷ̇metm.)c]/*qO}0P.p 忡X!mG&%̥v1VB8kYxSvRHy 펈ѨC0A8:*ۯ@ a{IM؊%v C#i^4.p[=Z`TKQd:=F6FKX & 5Pѧ'Lw O::1F =Nt|dp]3wDj7MS$wI5:#.p[`flKmRY# wc'rJ [Upte4lO`ᕷf̓c+X{5M{-:P|45)@ZC ތaV^{t^|=Hnmwg0wӡ+u !U<{wHe-/ؗ/_y^_J'iH68AB) jl6 )':Ρԃ 7£Ƕ=#PKX9ұI> setuptools/depends.pycUT IIUxYIsERr bfbSl"0H#k $="/*R /5r59圪}!Uh~ӿZ͊v6~~"BRH!wā#vaۮqvETb<;S"kb&ة*qqS4E|A\)VEXa]i96 !NKMtvfp\xA xAsSrDtIDE8#b4' gž#қB~qQ|1/Դ~iwqTӕOGFǤs2W lk3kem zgF9^ 5B[i)$$zQh8qr:F FRVaqoZ'P=*FjA ݁C.: i~֛oDoΚ[˕tZF* ёJDtj>l:-9-[rƹ$pBIkP }:Ƣ65G\ M6v=o0cokAJ5+B_W/AćWֿB#+  gN^}ǚjiD],nl+%DEK*b"=6smo`#Vt3#89HV Scz:cAY >K|D<%KnZeI%xk^/!Ġ|J7[@qZ4KI.Y8GȦ ={l„z~gf_NmTLloM*8L:By6iHvkӞ`AGEo=|~oc>1oloc#nMGҰ/f`1" +H!SW1V~7<Df1Ż'v#Mh{T:#1a$F:yꞟcɘ.d ='8+Z!jgquS^pԴǦo&ᑉMue]cfB|*0S1Qɒmz1]b(АEL_1C2x:7f~ \{qt6eՉ⵳Dsޥq i!" Go17FZZy&3sja(9|iS/xC8 %|XݨV%Y!{l\:VatEy+bar.e1We 0qE͘TQT1!?|ŗh.ζ7y_sd./'y`5nh=*X`Zka[hcD&.费 xD4#)>57r*m,y9l`J9K[n[XOmR!:$쌋 q frqO1] >GPr*SSX"zAM}Y(B+v/Ir?BDel35L+׸j9ɛrA^q/6KKK 0[PK`X9|I:vssetuptools/dist.pyUT tIIUx=nF 6Nc}0Vh̤g$$aXS$E {nu%eә n[*:::AmW4jprIu[wn# c!iڤI7K= 06$@krE?WJUX<_A?V"uLeKE|eަJ9=-4܂$Jiz v(^)($fǛS'v~a}Cfl."RVH@E RHa!g(6Z0J69'[Z7j`ćjUWZ-ҧuz+yн/xi!Yp_p&nݘ?$h0!K!^|1 7LܺN b`Wɂ0mpMHmD>V`㿨ڝX:QR{pv7m GݚMq[;يv|)]8(CeS3 Qb8@e'j8p D8߶ (A0eS1 b|!/Kr 1Ћ 7a4Ph*JojmI?oTzqPN#誳CU`2D;wQv$E^C 0OwI65'"OUcL=dM!O`}@jh|)bCBiC^ͧu9FHmїπ` h"ǒ4yK#/)Sŀ~i /ESZؐ[؅`P&F4WAȄkQ}T))Rsk}D41i)P -GV#cJX-uݬi8R'"+3rٔIso48X!$=eP,ɀD&9Զ蓬c8S =< VyûvE r@<ε3r %No0MTCvQ#68ho# 2ԗş o %z!yPJVD$ W 1"gi:8*-tV OOxxF%+̌ZIT̻كJd^Ef♔t`~t$2)o6(s`f˸XH yֆ-juFFBWrK.)ɜkJbPiDjρO#~?t=(Cs$+ Hu``EL0dnH+||}G6bBRS9| s^!%e |6U0,R8iwY?_O)A Fl3 q|ӣ?Et(8]gE&۱ kly -bV`v5H,{;=8~o`D#MĄA\CڏszgQ08W<'.l> HN(?zWݐ^7??y9DwE8 O,@`s 5k,N*D=Ǿ?M4"=oYNaiM_QbAQX8,*UM ;:wKr\4:I3j"cM>ȓn`VmnIy2qƳlYN||YLֳet9[fy^th\Q?',/Nk)+ba"6'\`U5Z49o+~7 `52=Ìr[;\LybCQxIY2ޕebo tElm65aF #<+$L|~A&|;wN8xjjFϯZ?m#_bRHyC>fKπ&5<*8bEudɮ.ˤLHvr`JyUJ&I9" _.=q@;8d.E޽B Knmȁ 4p*wftD>4lpg|͚q/)F~KT"?=ŒC昡!43+YtKk&SR)rMWLDI2{S_lH)Q{eO*$4< r)!8|EwǪL;[Ϩ6K3EgixR=90b .jykwASpF1J]6b=:%U {eG^/H*H~q{XB$ wxrbֱ3g{79GԮ^ D *FB<zF,[\͠ďTw;I7~MRYDڟTVN3f|KJFJG_ѩ4Si@?Tʈ::y$k:}4V~Ժ[Vl'!Ot1{t\VlŸSjE%yW[YV7:TOAԜ@1V k;94/U7sIԒ ~|'p9(ҐDXFKm3ty lP}n[LHC)u3Ҕ¼YɨB&rxct #Qt nil/\`)Ofgoֹ}YEGb^uRBeň3g'Eh!䳅C?WEo` ?R{|\o rqڡl|䓅(: / eaR:`5jѩ|).[1޽U:B+|ߏҥ\I 'ϘrJ>IM0vdZ8?ݵ!r̀ .mޝ֣F-Pfqz [l2tjj6UﰴF_`דFW fAMgnon\EbZT | !~sKz5O^ES?lHj]&VKmU\%{fik6$qW`a݃%GP fIqQӎO; G5KY½;)dY%A׈ڿ= D^Uչf1ߢX%n6Ԫ G$0W7׼>(MU<.`4/u}" d *arKj,& 7L`8F8:  ~,A4fGi2'ܟr>l5c72J;? W=q\%h]EmGz[frӍ ;/$xE@ARN8w8័;l@EC`ğ/j;LLGaLPia%8lK u;f᭭.k>FEŵJh R 6J&G #Z~%}2&۾z{qK&67N2Zm 8p8NDGдpݲqlrgqq8– B: .!m $;`pW8keJ6+ޓx #dJٗqNK(kb.z f$Ɛw~r}ˆFIe)|3K97߬ @IY"9vYΈ2u(*lwvcD_OĎKm:q]2"&Mxs@pn 4:! 8wOj$%&a^C0D6ccBxlSn8uFf5fZbϼ{'+ۭQǢڣDӶ @8x4a |RdҀg®wu۲7*$ƱC%%~ 3zs榞rfy2__bÏLg ^f` k8dkx8^[-o)0񥙉f)k QT~za>7UvKEW;*wU7honhoho|]]  DK<\Ck~uPgzW RtK 5%\/?|6IO<]Ŧagi?ISmi<8UC"Li##WAm6xE$F<ϳ^4 nP[p/w;x K:RQ<45Էzs2O}הWL,ujRl4 )bz~a9Ӟ_k?r\q^&YhnΧO:5\~}׾gu!,=#&qLbA,E%Dz٬?ǡ$a4N}7ȿD\h E4.zFzHOR2h/# $zpvva'3g~vяTx#!"CPފMx+f5e V3ieCr_'T<7E&Yr1nS=S{ʣbI;i(6w Cs/C#yxh%r}EnZ>lg$n NzYJ6;ڰ>O|4ӂm$)#CWF-~&C*ե G7 Q^҃KP2XwNJ$wJuꜨ -d :j:li"8ɷp@h:#qS8m%4?,޸Cۥk0w7*Yimc{  3o7pDU50؊jLxwY,}߃ot&=+=: ;Kt}BԈ}ٔʾX| }͉mMn).R4Nuݧ aocԩk0 Ž&뜄=0Pl@,jS N.%@k1 Hw1e-kA _s nٛVS2Ƃ p r6"TmL.=_V&!BS S8X8 B  LH0 @ҋX_SxV  z-"f hamC8 ϞIHްyB߲&Ԣ5fSS=O }z4Go=u0Hq3\7fe5\A% 7(f]kɕ]kŕת+q]s%5WJ\붲upCEk|sPN[wDhΖNf8 T[| Ө[ 3_qvMH#E2VYt4,pCr+n4EON)m1R2)Սӈ G 4Z״v*-R[=NqdX[%"X^ 5iT8:0*WճgvW1lto@`A^Diy bۥ6⦹/ O. ΐ1c> *a9y9>Wt( -o4qqx"D$[,<v%%#K:pŴ^oCq!%X;򚂄Ms`XkR- }N&DMAPfKC!n1e=AF"y&EnjR#bٕ[2*cy,_JV#8 وo_j:ֽ.h ;ɐ==jIE˜2lۙ4")T2"ZAɢs^Qnn}Y?2n}AziCn_Al˓,_DE$%SyIB#ᡟu?OR*}ZrV"8χ)خlZԟ1;qMK.`˸9:?D@=YOSdpDN[c`Lk `.$+dpJLUd$6!:9<.Rqk!$Zf -cS(A 0w/-&^d]Pg#l/cVcdH` ro|B`oL@H8EO #4%#.4U^GL[OIw3bGt-d*d6]d/@j[fΰ$PLf$Xsr%lt \Ntق҂YјɐV}Aؘ JB2,'6iTR@UYݹ߮ 8 aMT겹"NK$2J*9,@zg 4^8,L8oŗ4S T \YĦE˜*rѢw%JNUiXЗ$yJ˅k28`Q֔66VoW4qSx}^nX-@6lh=4;K )8ae- n}6 \sԒP6 ~EoJ-:@UKMT?e>6Æ0 YG(R` T@e5fqc'ܜwUQ.|c̹Of{Tdqv4 ȘӲv -8(?s)7N%hD.Z]B:Wiܠbu>r.g&7J(7>܎quW\ˆQsk ٞ<4mP[ʓP)/=g[it0?y`8;{|K)Kem٧8ϣJFm?ٝo2-VMoG K*^[+V*^1bM|\ޥkX-NγJkd$U>,F\QX! wV2ˇ9K4FŶAc{] [bK 䌸ՊK*Da/I"T?q }Rcg&YXfc\p/XE}RܩK@\_y-4ȅt[VSުi鶆mJ tVȈŢ@I,iu4rr%I"wmGXnޑRxEXH-)~KG!yjiL6Q/ 9RO+GQ5vvy)^ vjJds|uKm(}u>:9u5%9Q96<IA82vԔ HM$\ڐY戜MW@"mƪWhG| Ω- Cq,Q/M}QeO @tv%3(ˎ*̭QmcA*C@]U ɯI{kcCt u*r v'_F=O5S>.{Md$^M-r} }4OIC/ WG׼f4n2f:uT %>8ǥyl"ɦ% q5Z6\tWz߮ڛKd)9`Q-}s 1 罞K[B笧NsAyOj+FuJ,(e΍Hfmx!b:,Ur4Q`˔6\=uֶ<85uz"*JV*~%Oί,֜[`1PkR*ck"J k9t3Ρ]6knńD)@Sՙyj"70j 0]fZ=D`L 0HEf9GߢOgoPK_,9i ѩJCp"ۇluSFELsIsdvDW7.v \%V֜uR-wjҎ| 3x tp 5lݰ5;iځQ| .uuxD!oCWBF%=-LFHr/R rd9wKsBu@OTU"O>i*ǝiSΒ]NOk-jI9MHgQ/ & %xeK?ÏVVQ3X=dr=J:uBnQSW+ (IɃ\[HgZ9XM,,yYLFn$FL6ȸ221A]! 24{\I Jޞkq*>d .\8LԶ}7r9U:c!KЬg%O`O嬰F溅I#ON"+αyzˋK*ϵj3H*_F%~ל +p Fs9pH " |I1)1 =K?!*mgQ5%!K p_h=dU99aΪf0} l"}A[+azѾAX+Sܥ|: smܵ+|b*C5Sh+B0I K4a/:'"UWϲե@|H8MeKZUH ϨsG2S,{5/5(9|6)#/ጿq6b7.);_b0#f ^ v $ͫF{rl#+k-@p`}%Pq;mMm\2&~cY ڋ nRzw}K>eΛhP&bs6xtCn8±p :#~dμT- _I7^Ñ@!Hq"bb< )CAr5$:v$uTg@p@sZ{r#p vE^m=]Nu@ g?#FJ錒a @} nCژ$,JhCjYcG3… \;|3{kA7a= n@Cy K]JQ{5ktŌ֮xMnJz4hkI=mV:Nu oZG<]?|٨w*3ҝcF5;!-hȃtvq4uislZfҦV˱Q`;nWz2TE'_L>;(a\~569GUl1My}*h\] u[wJTŠeSrܹOoFFR%duR`X@PDG\H?XG1c^-E7R)R\Qn#|)n N!߇i21$ , Ci&j8K3(yG{18oԩb6yٯ>OcbaH]txfMC%Gk@-5k vu!)rPTQFsuo@+{=Qw7 / Ԫ/,ԒEv[n@@r ̠F6[Z@58tH. FL '556ƿ\ӴHDNBT(HL-o)N'Lq" ߖ3A zXyx9(sP, N޹!(Yrҁ 2}IRqʘbʦѲe*PBe{jkYg Ӕ7-U1n+}ڨ ժ 0̓[!Ih2f(]UWl'7%&ŔIpWxZ'+.o.|ȟݽ䳇!SqO4ٷ[,+Aܵb$IocĤp,C o)tQDF. J4+z5 d,5fK#hz!S4KW^l2$i0c3GY+~.mٽOYZp&ѓ z^%g'J^9G3KRIuo'֥HkTP:3uW"ðR=SMյ[$-#Cvj\NjmD;XY`q]{iVLXZa2ns؋Z DqHh2 Taɹfۦ\g[43I)]l&TܲH)O*Vۍd3򄤿R4FDJ\mv6(waDp\ Ώp;Ycl-~ |[(gG2b4ؐI%I=\iΖ]@S-v~ѵ28=ulY< [B~L 7̻wxɎڊpҁ(< ?O}ZF.To6>|Q&±]ѝPxgh?넚k ̊ oyo`.y#Hoz`gjTy6z1P3RWyhj0pSfn>aiuCjHtZI4KYIuPI|4n7pQRϭzؗ|ƤEb[>1V/ˤuaB"ɛ$T-Y"hnwPXhʅWJJ߳f^7|R HoJ%*Dؽ kh8aN+L9+Lm^jx*^TSB$*,99ˁ"/*d>f"ړuP?U+P8BUn,)>=JߏwH;b%VvP.(if{ҵ< }5cWwHsܜU"{ZQp/%1>g췳Es҅Dҁc( T h9 p" 9v<wFQqX,- 'j'; PK]X9<?setuptools/extension.pyUT tIIUxSM +FNrm5ZCoQXpagZ[Wt+ЪtVuxxlHW@ù"g5:VWSe8 5hx,EOL(.W^ z<\lm" =>T.q9'(8fI& e"=u fj[|eK{*b;Ih8upi`)!( & ߐUp. 0.0٤llVlv pTީS'$aUEp)ڛWJD,"N,R;x z…GYW*"FM:-Gv(j '{boiwMU$da.۠(5Mf2X:5AyaL]=QƇ:-@UB,X2N3?? &9Tv$wy\Tپ$ΦT#ťmQCz"҇ JD$t6f榌kl{]G8XsʪVP$SGYڏ$wkxk#sj/@ Y/ddSL@p+ɶ*[1,s{m|*?PK`X9i4!lsetuptools/package_index.pyUT tIIUx\{sFbBɦ]-'uld/G3$D ID \u<0xvrC{r e1+VDhYdiIug싼8",j."*&W&vu{U֗U ˽x=ٔeE^k.|'Ei< yYL_Op6aCvmz>v?yQ ͱ{,}Q+8HO&|~_e3JErt̛OL'~7e8.ΟGw%߼{',{_]IY'G%ptv&>Z :̯y˪%[vW&o~ybo݇C"flᶏC$z.{'߽`J\ 9Sߕ U>^{|$fb,Ń8rQw-tvz+.^./pyZzJ.~៹q'$9M_]D'2~d ?&|~tBQIrr oEb Xb%<~E'˛$K2Qd/WK9oE{I7l`#| ^eƼ8N,/*x aE.Drr2hP΄_ в8,sZ󒍜,7I\\U |};PoȘMO-SȦj-5-n0=Gg5C67mc!OUJ*R`$Zk/a8p<  [OC$yV77S>3y=\U{rp\Hϔج = NA`yԎ#eDqTE3)$<9taUf vJxLt3슃JW*6 gQ>ta;mӛD5;8ANh3fn8<=ط5ϦnʽpLƥmׅw76A1֨Oo^\m1ܓ YuJ133L-:]-aJ~gG ,@89O,eܩluF>GWɶkшc+?N"<ɭ#eRK;\DY^n+:gis*KM}Փ_H?搟vڊ*ޖxL0P֡<ڑq0VD<ԭ=|άJq@7ghufigBp$}&C7Y@a?OБBIuC$:iOOϕ {6i=x HE)Pvy7"1R_Al>Ce[irWhjU|rQK U+ ;|W+RqAth_,f+}4e_r:|u'R7 $'(FCmȜ(jg4i÷L\'QHsW/s6mQxڨ:0 Z&#`}4Tu"{aʲZ#(2 'قdy ڬ R%wȁ"IrZT_Vu0#B9I =;6'k3~B,H$T䚧M]Q0-tI|lYv O 09r)P9rYg̔&W 洗# wHф9 5^N2܄BJ#.0"FS@lib1 (pcN|zgN4"KfE+)Cw)w|$Iڗ1H- @`)!ID[e[=Z;Ihvo\q;oy֛ e,2rm~U^ P\UMz_-%OxҪ,}z?WPRpBQmd:N|,{yjnog\P!r"OϿMOꤒ%8%H(y!ؔK،rj獌pr<,ToäR[rOJ$ן[j!:wO09R1^9Q {)y)H8-ch8],.n1Jo]y{t.'-?@kYpuȇJm0aC.~ߟ%|i!{P!"Eu@6ِ=De9J*r70V% dN%.n<@W`7= %EF2{ Fnjo:&*vEfv#tFbô'~$m<G$f3ҥT i7Vb@]r;@ݻw{Ο'vu/K[M Z(J{ `\GdNFsDU*ʫJ2Uap-@J?bz1 $+^ȴtV`[sͺ:1wՠº-a$% ~ŰI!L4e N2F߇UTy"GF|O79lH3k?z?E-.V)npшLj{zwp@xYFɚbƽPW*#p(muxVU6 HqbM})N0lj+E}liIh:X֢;BA!d>C~&wSp q(IGR `NJSiש *}DIis ;MRGN UtŷwFذa]^vR:L-P}C7 BxZԵ0ڂu 0@|[kK.ueHQ?hMCW STbD s;hS0rˤcwF ;CdM.Byo҃6ФN.D w5sLyJekcIG T#撵`K@iܞ._fN(R1!@x+RMs$qVkÁE+Y V0ZF-H=Clf8f[| UӶˬ_ {ɮ[nI # X^02IzB!tӿD#] z潳N[9p(fR mrVTtX92mחZ^j^RlI海`D5Q;Qo{%-:̛= vL9^>!UKze-@Q;IZݗєZwt^KOW;Fտa%Cs1[Zɵ\0 x^пŀҼXn!8הxS`yeQ'U9œM7S"cekGSJ;ioGcR$b+IKk @ '3$:E4+"Dz4H4B :.JW iYlW`Ll$x2_QaP>Ķ>,:eB`%Z4v 1]sn$N;Ft4[^)H{cٔۺ.rӯPc3`-aM!`x2ںHU /_sֈnҍw0}^8lIkIF]-(w(}>h;j> Us{<_?U%i#@R*TXu`Kf|F>Eu D{ FjrHZ~^H1QrPp57I0VFlI#BFw&tW> B%͵s`KmPf nxWvzcFQ6"v5ul.7[GeG: bD}bf=(Y;\('e c%]j_N%@6Iٴ+4".U/az?„ѡ˰+I( t4i$F`tؿmek<6[e?zjmG0ox=Ur%GS8k %?4Tm=,jC@|8cH&,aڄ]|>猆 1YW) U mKG7r) \at^ ԑ6EA'"iSK1K?+(FbYM9~(g &Aj:v Qc S3)hrLKrpˤLfޠk$ѺL*KCj\gTNLzz)Hߧs4G9u쓋 x2MtNnyL՞2Cg%Y#h Yp[NåF k;Pm&Ƭӷm'->J\"+ z-lY DB&Ki3zRn,ZcntJ^o>E"m+j xQCz0K/604|d= RQ͡t:4eq>am*=X59q LQq_K J x_D$VD.GddMut q8K"Isp]ɶGͤ&2}Ov `_ᢓgՔ#[ 5-uG0@_Ah&J8?~aiBQȎ#JvbWX@_wV~\XeKĬ&}t栌a,usQ¸8)ހxX0Y_hoڠ!axin^:|O:?8 DO 9!\^V;#CaϊUS /Nai gTGN,(cTK=N'kហ;F'$30q $l߹i9 rWSYsz~0t3|C=Ef0jG~=kV\h}/ xh9D^8W_M/:ӏ_Byf<wՉ_<=vłK%.pw ]K+Pfȏwg_jNXg/^]:EArX 6_zrW~]hc& w}ON^ iT[j5r CKOᗻZl?ȠW;JzfjN p)s/tTvT (D{!{/$?eo0 (1T5&襑FyγtR>bEyxR@>"lx҅xETÛ=tn"7`Ó~d@l f?Rbn%Gc[<^*P5=JMFP oA\#ICBIOg'x6–@piЬOVPފtz&$ G͋5> LLכuϦDH6+zCYiU6])Y#P52iuQ'Y+?/cĔ DU.߃Գ0]<\ h\f@ !Y%Fs:xyF7q-3"Y- *z hH8V`.!26D&1{Wn!Vﴪ~׻PװbAQO4$lsdljj}]CK)io (&SАKA0ťD;qbS"w`4ܰTx^IYUe{d.›=.lA`Pa^t\G"ߏÜ x2!F&:xT+&I}vxK#&1]1%rȎXwW<&@byhGD7At =BQ=D5=m-% =ʭF@'PO%Wpt"8 go難w[m|Wysl`!utA~5bo[iW{JLw\^BЎU(tVG D|(zJ==i88.,Pr\҉N}]5[xxcJ :-5we~(UGb, ~k%+͛hy>K`1p#Ɣ1L Ca%~K6_KJz#"iY4'EmH=DV/RY`!Q'K>}B.QcWPVP)-HYB3Vd>˼A|VPW40ftZ s?t$NHNR?#ع~9HrY""OJŏJ9iF;آ=pOp͑?n 3Ǔnr=$%|h4pJ˺,xRԑBvBhng_#0B }h?gEC 4E9s]?aKʓ3pVfdpϠ`Aaۄ4)t(k0?bvi ڗx^ЦDcK X L6=hSFFw_J6~GOʖ{) !Ad2D&lYB2堠קpN N`xJF*J Ј}!CEC+G72 7)X{G b E.)z_V SD? ¼#szL%3=%CgգvJ!֤Q>PP6:4hGցۛxcf`(F'u)co%PCȃhEȞ}4O Égq-t+Oj( i(9Qp`ͼFm)cجe*_8<5;?JdžiJ=lff@ej Wtt4ToO9ZaLS9' ƬCh@&CXm?r Bf]#/'w9ƒv)u֙)wQM̈\ ݨxlA-;9EO,`>Nyz,j?b\w5 ƂkϠi9~șS 0YiTc:~YRL (~kΣXlU(mY1[V 勏Ugu={ H8R7P.~2o"CuR'2L*L֜$[tU~!hZ-5*4_`M h] rx)HPY#0gx)h m&']7,PK )H*J,Fg~m[t`hE.3'k)'cБpcC̲GLwšpCN%|bBB>AA9xJ)7O g4cao6~Ìe̡aM/'M ^6ܭw8LWkiTx *k܅C% <_?v*eC7L%9s~ Fx DH0>0M&0D<֪%RY턢͈eQpGi|bl#9 Ē_O_WWOp^%/}F<ܟ,Gї5`QǠ@foqPPPrZ&a.  HT傑Уdsv=wݹAxRƘ:~IlןkJ8:ʴpP95#:` |80Q"gd4ŒXa*h'GչJz[ (ʭCeRG=ji*2hg"[1ۊ[@i@ nz|T()ڝ*OU#@~dg /vbj)M4E|DJ[1rpA66% zǝ4d0΀WxGJn)pHt\[cP%CF":% |ro:\I$rf&s&:/˱U.?eg}>jYIv:8rT< M/=eZY8!XƏ7زfcv"z{8_aTsLJ-'t^f;k8r]3-c?b_{9z:+S&xLjYb[p&G\/'Cu-M&1p lk|# ?]C uqoiڳ%l"$0#y.}AhwY4Y+ B0YȖRU-d ™˽CINҥ‘BJT!" ;[Kg'w?؜8 g_}6ZT&Iu+L/O+NX79:Q+ُK9POz3Ub׊Z|r'qDRC0vG.FCAa)Z[D=Y͔wi=Bi@fb[4Oy{\*FEKzzGۮCV] En֜J ~Y⽔%g |x:;v4FOJS^?F#μhE^ AF&.Z2vD%nyhW[MJ@*'K\.A^x#yeKviWeaG^3T#f}q_q,2mEzhլ\mnbOWox1o9 BOnC`hK\o7=ʝ) )4\ "1*iִn|rtBbT=I_}HǼ%mAzkUU÷H& ڡZ>whЎus|ڍx/la?o?%br@ۇ#ՃJڸWadtS/<,t|Jms\z~?Yd̽ l[@}69s!L?#Ex'Wÿ!Yf N^)b|0v(UhsW$ŝKF-6-48(wE-*_k~5ìq"ҭ#%1مReGq(8 Xi[nɴ'mZւ\udOqfb xnRw5 : 8 7y炿#F<Ϊ˸FF`U>V_yo-3eAY/`U_P)gf#g/e)Ȼ(X%viT(=A*/Ri8q UOG $vy,PK`X9 Xmsetuptools/sandbox.pyUT tIIUxYmo8_AxѓU~+C>m^ZhNEI IIԋ춸5K!pfH}-&B%D+6 /5,!-/YBD$BP Iӽ({ҊjV$>{RpK2)T[iegqQZ\UO,>prP䍹qQREc2tS/`lK|g* AK+pX5ВVYI "\+ tRBEhJΏEE,a7|_G7ݜѶS)(|F0X[m"IhTBw\AԲ8;~7Ak% VIsQio^ Β"0Fi0:=>PlJtF]݊LW0ACIūV1:K<>87EXx>@6JC^WS( E~gHz6`84Uw|v8R+j0Hj oU EwL)( ,d6!_uP/֟Bd@lQfo$VÈax6~ 0Jѹh<BeEN4iB-|9ya:8kAuÝ r|dz!w!g{mb4Wpܿ{[fjFTcD -.M(F/v/3z #UHĴڮU 9}~P FGO0"< aǣ!|t^xL\{&"j)釨f]7V)WڃQrS̈́âlX{>LuYرXgq*8T ~ixԒm㟄ajtxQ{^> !d_F: qՋ1h+f.! exN dY$i"CJm7 ~qgZs]4J{k[4 5Qk6̴bPdv;u3da2ݐ)o|/9;O? ;gmy_l-Ksc`tygPy_E{6k,ےzr޾{Jq|S+1,odaEF~~@Ϧ+`1LqRKi W M.R!3[^Є`{cu_l ן>~;xޭܾ??}\]~].uJ]ĤJ ꛈ*%j|{"W)sݟPpإ yHǺ-+JWϚ;zA?ы@z8Fa)X"m \s),}rD4iofɆЍ #Eei6hx=o6ٲSs/6R3Y­I .qWs/c͏rHy)!JU0d>j# TY'4m"cB)Q)nJB+0#>?PKX9@SW(setuptools/sandbox.pycUT IIUxZs֙?(.lFuv-9N6n]_I Q6E ␂4;;uM_2;3;i:l;8 )91<<8w߹z%i}~@s/Ş\miض۶WvE())P3bwXb.Y=+d@UD0%s L_сs[4mV5/ڄ@\]jQO%E[ۧZPi̊'Xz_K ,m@WAfsx~N69oY(I_7v<[;aȷ'b1 L"?8bڏL^ˢY2 X=Dn<ЬTŧDL$q,ΈAN Zq-cYxOjpQwѮ7p;RK|Fq !ylSc`׌܊|Y<)|\rPi13t.B<1p@0׀^[$Š"'Tx=)Ue1Aus`o |HGn6 7ip;Qd4嗝L _N;aэ(BX`iU,j@KN\H*vl]v)+.~ߥXQ8[/7 !0`0Dfݢa+{Υ$h=tHq躧7/9P\`;I}¸3., & o){, skCyrvDb!E:Bb׫@6 ]9 L y#6O ,|ͮyi{eM6W? ܒ6IO 0+ kUr p-"%N?Cat68W"T@0 $b|Ȓ~Rkg& @8B:uGot1༉r[q&qDȽ QECX9ę"_j%*ūwR&]0i,B)Ǽ "L}<'}QU#&kEzc&L|֪EɶhEϐlZiohR&GV:0fTuv24Irޏ|B;l'a1!0S$$n~1Cm|֏$J/Th.kϿn}mzV:_cZWVVċgbJճK_ҷ~FFN*] 'ܐ185e)f} ._@ӡ@Hf >7.CwΐkљNKƛ~MA@h*(w)c{ KcdR4< Z7.\OtC peH $d@ d/5,5<&!1B삐_BS"\5Qijm˫살|*rG 6F ?>{e2׹E2q& Ds,oV9siY1犎ͤrN ^<Ͻ^zMQł{tH\b#crwvN0,?mH3 ~UYVZj5vc-3ܰZX52lR͛&տMTF/4itX3A/kL/;J@͠Kcd&LE ϡ kJY|DF}GZ'gge$k:/qb' Ȍ\= Hw0|a'H﬑̞=abPTLӊ)ֹB|b|U~e¥v8$|ҍ"qʭBKezj3#6W?(&00$eZ1kEsLR4gU{@ Kb&SCF3x`2'!B%3$ΥсXG4^Ơca0t1a1\7EtS ?<$o02cj.>$tJH^ l ]՛U G&Y5AR2WѸK1\Z|E9f6vX9Qw.yCkCHtT(fm1d4ωVev$? sF=~l4ތtG%kWdeN/0)Ӏr߹wۻ?ѷ˦4bo6S;;{01spv(S:ܣ2-GMͻ&eL.o0ΚSLjv>:e X徿񓏜=֖K_7޽q&77=M|~ HˮeW6J ns\+CE]/Qfax dq.]r{~ih0w" OMrJ2Ci72n/&kmfX{S])_qHRlY ] кȸ\T$I o&9i [A8MRϽjg֋œsa_w%xkEp]/uM.J%r{6]M+PK]X9@` setuptools/site-patch.pyUT tItIUxVQ6~ϯv8npDĖ6Hrl'٣PC-77[젮_ 蒃փ; Ў 可>|7PVr>ϦlusVBN*{ jAi?sJy@owa{XL3ylVȆ(s匊 (ں"['=n{T<٘pnUIOJ u'{X< گPcHH50q&y"(4h:a@w]HIk ZwZ5-l 2C IPz,rm~PEbeGSy(dYxPn@O} 'gxanD~_<|y{My ]d@eiwKdA oj{ 2Z>ǨoE.#RlӮx,;u#6!n٣M;<uMxB@7'5 :=7},/z˃O_>%^p {vy-p'd"?!c=~OEmubBegmޚG" Rmtj_Xïr~u"TS[!S~cQ(aS (m=sāɉ˚r@Ǻr}t (V-5U*Y*XP%,~H5mQXƲΡ^K}0VFC,|U\F(XKp fPK BY9setuptools/command/UT L8I`8IUxPK]X9O?v7ssetuptools/command/__init__.pyUT tIxIUxun <JIL^UC"0I!I].oR9'5YMM X oUW1XgUĩGt!6BM2QbمoKBKDz3=xTLfΗ( liOStMvKxc ue/o8 aRHخ,rD6c*ߚJyO_S8 З0b 9d  =~*HB&{ RW\d *DqZBuVK#ΟNa %K_I#z,ozPKX9(MQsetuptools/command/__init__.pycUT IIUxmRMs0]qIvRn:0: -=hԬʖڄOJhճ~|x 0lfM`pp<<lc>| wR'p& ۾ %@> 3&ܶ=c$bW`#p rqP(O{ƕ+?tN8'c}>qEJc*SN]](UO䢤*]0m(慚8y~ya.߼q#~^s֏֊#.2>zU8[6:qXvD/駽'bPK]X9_NL setuptools/command/alias.pyUT tIxIUxUˮ6+*.$նl@ts Gl%R%8A=Ç$$j![33gCR8qm[F47R!ߞ,J!/L3|!<_3RRM_w\Ғ͈79l :2kU[L6sM4MKС0H-3gJsql[\&/̙[d \@fkH^>/w`x9؂|^8#u ڄENnZti0g.(MʃD晑E$Q.TAfmt'Եvnd H—&u5ʭ4g`7y/H:d~䃠((! dڙ`7Ds{oG+d"rwW8497~klb._=WI`ޓˍrؚbtqƞdТȧ;_ĮocirN|7hǚ7Ϭ6ut X[G6jr8v R8ظ3LuɳeHH3jG81 {f|;\vvx ɍɲx M HpHR,Ȝ޲Un`ۘ,uҽƇF-ՓJ~֋ܿ:$% +\pgCjt;О5|Z{ _m: u?zQ\;F}:.#k蠎@6%S<`yV֏zƎFwO*[WVʮrwPKX9.uv setuptools/command/alias.pycUT IIUxV_oDҐBTV%E-()*Zg_뒠§/ۗE<%vgֳͬuuH_1ClhdСCq5RNqb^{qbޠ=ƨIm;4PܥA9[ӨMK{O3=uż0v9/=CbE:ɨP̳pB[cbqǃEvȯEcSp70Zi:ī?ul 8^1K^?AR09ZyHh<+:.Qx5>j7H Xw/8:sAfdf?fG[#|*[߆1Nea4 XŗSۋ_DMy6vG Lqѽ?ØOmf#,2Q`֧'>#J@ p봨zՂPds٣ aZ:db|u Z2j]1Ъ^bХsxcg|̆u~`(yjllLLጹz|?_M~>ׂrf' o ,(<4 "x4Q9c#S.Fg=,o 8_DUEK䁏0ށ'@:3>x(&jEuGEY- gկ͗,ɍuTމ'Yy3$5}^_Hʵ@@q_S+N71br0L0ߪ$|]ZplD2Н CСG_qձN:h39Yp~rT}v%C5: }:_α˅"W~WXod;e 3 ]>Ev7aZmiX6>'MMÙ(Tϕ"+% # ]vQuc^,ͱbDZ%Ն(ðL;-0 LVu|FrL}Cka*]kV:S)EKe@Ew9-y(k.Fofl\46X| -ppUTt7͢Z1idKl  =YQۙ|l#d e{Y\ZTW:e˭aY=1..\`NuE5cW_^Ʒ*楴@S D$a_6E,Sic_Wt:PK`X9:Esetuptools/command/bdist_egg.pyUT tIxIUx"84'CT/3.RG܈YC6oB0cFe@Ռ5*6%cj=9 0u`~9LZMfx9hټܲ+ Fnmif[1_}*lyɛeP0oJZ t!sɛ9.!S)T`iQ0 ¤Rt3\Z8HO$n8@ՂjRb8'6աXiy2hE`}s=GI:1. 'rzyq X^74!- BK)` "i\4T C;EsQF@?eݯ(Kïs8 I=É /TEB6Oܷ9ϓ0'N=?KTۻp/y33!BLD5y ~i0&8p|a nv 1юDc̢z[9c Is0}촾w5dpdm'( XC <(, ?]QE Dtk Y- $t8^~PH2'h0 |Jo{livqXdyuy_8@죚QyvP56[ $do߼7?5yqsKBjv4wN~ԋ&d1i|[M CGMBF4t 2 `GV 6%ahײ1 3 803[u '^)h M2@Dt^@g'5'5'>vnE %LT b||TN~4ZCq$ "^љwD'^e1Z*|CZM {'V5T8"nEd#˽0O { ]PĦ4c:2kc3;Y$=ӏ܂5NrL42Oeh@6B*u;Uz R[BLي8A+vFVnѡyKBuݕ`W:hô?.],QC:cYU-5ҲCVB姜?I*xLjiFOv[ #]V\"aIo~8]%LX%=Qitﴄ$*IpvEu4i2l<~ܜ=&x%^$ݣV@坛bvDqVHi+耨#+r.P;o/RwCۮo]XC_dC JÒQ ݷ8ͱk а֩)G=#> O.& % %Y.#8c<8q {KQa}H@kcB(Ă&d5yǥ o:/E" S#H &G9 (} $x.M%,ju?3h砮:|WOWyTC|Xv>վǁ&k I; $_3ٝDPy`=j)R ."t%})=2ÄP $}եn=}`;hF/AwPDG3(A!""ӧx4) o n$AVeEhj t4/Ga!7_uI'HvQahf_TICu;7Ae5vB)o}OT۝~YIlC@i%߾2Pu$F`(-]S.;RH$t؞" c;!Ii[*t{vcx\VW d8Б:@>#7bv;+-{>ɥGD@k LPv2>q2. 7/n*߼,r7;4>ԉ~4 Ҿ\ne##.Vh?2_րDH? lKgDh ˗ 0~O44hk0w( 𸬨X PK T Nly`o~/J Z_rBİ?_ӮT+pL!3WNj|\eͅS=*+>Ų;CǜwvFWUP$]#QGLE3$ 2\#dѦ$ٕ!5iޱF2@ ]+,݀D /XNCUҺinO bD!Y1>AXOA A&(“%!ΎlWV7\vWDKndGSk/xIK:#y 60H8W\@Iae?jͭPQ$cXi靋KM<R{CFzG N:SBoM8J񙼘F nS0WK_A۫o~"x@Sx7Pz!J[)}J{P.@\6F"kK3yDvpH5GuI~KS_*Ղ"c/==Bծ1w2se맒 XvA7SG4JYD4詎fAUSGE#/a #+}{B=99^x04ԕ+d: Hz3UXV/kR(WHtTaE{=0}ˤ)kgѻĩms;wַΗ9xyFgK)E$q PGʡp!D:?3+Rm)8j۩<Ŭ~^я!N3E4df鞕AfMaO<FXJ ڠFP/Cpi^R3M[1XEE,Ԧ .t [gkPNE%O$F'>~G*'h[c6k>;QnUb _\D43*qQʮ`(s)PZLdҬN);8(Zvuzĭ:*R\lTd/JXd=g'NX^o ˂Vg6"WysdX3}'[հ[%L1F,ի^]}ËW[Jp9;E@Jd#~[ ;Pe/5@Ii ) mDggPKX9: qF setuptools/command/bdist_egg.pycUT IIUx\[ly>3Hd(\JS'$(r\ZfF w˝P"m"M@/i6Eڇ(z OEھE}hH@[̙35XɧͺKb)(JGKڲԪemjZyNmUO) yUPZ-FIOmUV+ѯVTcPuQm ưZQQ:cjuL5+j\WքjLIW[SqRԴ  *VaZ#h?R*<'U0h:"8*'ϩ`OfTpOΫM j>Yuu)Lq9䓪 d^ ΨZ' ΪQQ%zz<aJ㸑 jkA^Q5Fn$ T}UiѪ~:~0L tM?F0ZfLzњC#ސq:,Jhdknj{5k5t=notf j4n:\o[qL[aߌ~{f@ϛ@{RVTdFRMKY5qӹ\іRLP SB8mThqd%'F{)_ ydo5¦V1**2s@mۯ3Wj-D};rY_ju 6HdP ȪA5b Yu,V14{ Rꀕ‘X6F".$$DIibVύwz٠&ɖr$8Vؙp8Ni~/& tqF7zo_Fa[A6Kv+nN\rZ[^;Lv=K(S˽j6M5۞O3Kq3| Ÿlq5y> ;'rV8ĭ dMF"z%yy>`7Ur&؃c==0NF`p2 1.W=Nc;ۡtf]gz5~aT˼k3t%Ud!hQsI7LJr^eVnvpIc'^ 'j:a3lLjJTIF3̳p{n..kMҽQQE%O [e t=]?t4aE`Jڎ<. GMѭquWlKzKz̦iP* n鹨 YhO"0ہ[Sw  IV4nьM4>w߽>%cBB#_-^sR1ߦx4J6pϙҍ0\l0c45i #֘u#6`A~0*f'Φa}R?a ! uhkܽ/+ 8Luߣ/SL0,S|, 렓>0>՚"6ӂ~4 5籝tBSgNXNɲv,ˈU4jV>R'!=1lkBEϰ(YVEv&9u!- 0; 3ᡙeG]`cu"gg!#6̣M2uS 9F0lIsbvU•jd%tn-oE 6pgWcY#[h`LMdW̊VV[@ ` {>gMEU[S$cָ5j_u:cg&2 GmX"h7u]2pѯkf`} t;p4$F|Af۴ST+EYdeF43+2KBO20py? 7uLyr~ÜpA&Hy^{v,K˷_yMo{wWnv_TX xG0抃+MsaX̨WM9}b~0G ljv+exl鹼 bp#X8ZG%\ҹ[&a`ޟwa ʋlG^V>IRyPf^dsد@wV #e4Zg֘o\sJ BkW$; %G/2F'AیV)d0I'u8pTV! Ne;^Q-%1΄KB$#>d' .G90dpZ0Xb(hHg p廟0`n3$IH$Ot;8a ߸ps鵷X%vJu-B7k<3Nﲏ $&-~8ҽ41(L@B>Hu1~MByvW^qn.xљ3GfpqꬅnBgm_Js fpg7jer-ky:։;~PcBױ?8DE( z{V#حwp`+Fs?n%LZXx+3) {asw-]hO7tcaCuYn<鶿z3حl2[Eνv˅ŽM=n{d}Fib. NrO8mkm0z`~MJdMXBzi-Obr~z-?6F if?:dyU]= vwL2{/Tͮ1cgDaŽT,l-t ظyo:L- D!;GGпB&lص9b E=/QCvt Uc<,n ܚ{L$%Iw`3\E {\7ca3ZWW \QXƯ㰙IYgD7 z4R1¬n9f]Zn}ꆷ|W<3jhplE5!ത=w8N+4k. z4W3ٴ6Aq#3dee4cuRCqsB'ɏBv O9KIT_ZʖUx87P*§o,y} HAum1 L9MfsdwfKh?`\|u$FcEcwtTLr9CF̣8o͑?\O}ܢ (^UǬq5 5lUXH8IZglBY~2%E-Q2\O˥c?wRE;5KK`{dt)W @آw#w )&~3+۹/fOx9"`O?M :FC`IWBNE.Яb")/Wg˧r-ty\b$vj~#ZY?:..;`|ʙЖ:D;8Xӯ=w&Z!UR&Wa$m\r+-&N,I eDqt!ֿ PcL84"a^pm-82vVK(* Vn[ȓлsl -Imm Ǘd۲3ȂZץ1ZJDU [4"o:{kwMYSyE#ئh2$:Kϫ8izZ NL?mRVgQI.wUDYGwdE^BfPc&D^ZI`[&&`zuq3ׯ)Ξđ8 3@vpQ)Ǯv|K0l:nӅM/1ڑDkLj0 $i3҅Pƌiu/?8ȼ 6&fs8*i5I1O÷??ɌF^R?e[ͻpO?SL|&^6t-߰ȇda5PǛqln_Ih^Fi]H]{Xʫ)=qH:b Q*:h(Baci-!.0߃NdWNJNWΠ"4ΏY~D̒;(mbdFQ @gM4Df+<&]LO0A9)O?şeEe"ka}ylXӊ$Zk#휐,ZЙHNxX e>@jE/Lqj~6yL!YglfN΀Sk-ٍFE=B8D mB\A|51M`eM&X"m/dPkf;qֳ$5=J~fmIY؞ӕ ={=˴OF^C$ɦFYH[Rmux VA ^Fz+`]P6@?o[? #ȓFrcY> МWMCbD% DB^dI1G=ȕms P`2|ҽI`xnE❷Xc)ʸp:g;&;GWeϠa!OaFa#pCS57.~oEi@V1x1k$qO,F6h5x]vqYƅsǽ;I6Wȴ:϶G2bOO`c Х,k.(JRjوoy$$ CͷOr~KRمɮ;s&<<0aJ9 &DD1Ivdf|'UߡAo(낍0W N7N`468t0>1Bꁦ}_Ifdud_#@B`SkH?G%T?XHgb clc=)h+lNi1(dl~;J!l ?+v Pl}^Y%Jޕ"'}fC)G,s2xz҇{3#*zea?x{4Lg>aIȭha}l1TPҌ<R5%WFřUFEiTkCgE. ˋHV V2[M]lTp' = Ou''xDK)MQd$)8o)=F@ mqDۄVtG 68 H -(* P6eR,@ U0Yx .sXA}PH]j1B$yϛ>eфgJ;]Lj&0V q~0qk]\J>gTUObS%gsZ?oĕ:dK)C<{ Ye~ Њ,@^Yux%SOӅQN?#}CMb:Hmq}VD6< R&M;pykY55T^Ӄ#:ܿ0ǧǼ) v״:2!>#1"m5h] ĖoÐaMЙXpw^6a{>ܝ|M̓)H|$Kk+PK`X9OE #setuptools/command/bdist_wininst.pyUT tIxIUxTn0D y*U/cOUe`nl~} xYr2yo<:C|Ҟ׶ix5oWeT?X ݔD4gY)H!S} P;aQ A;j}ZU*r8~ K9+B*a!Sc |K|Vf+ja@T.9OjN2|;aF9owSDK̕2OdgI= QNp& E%T AriBDf2}Ö- mD=CN/ګFmEV-pc-v^a@3.C@$*nuWi(lF?N8H%g;eX)hM*Hj eVY215K:v Z[@=^㞨`uQb.l0o 򷷸4x0H+Y{'rύ3giQ1kJxD{dŘ:C5ar W 8v* hr?E#?8|YVnypwAd27Wq-&zq`Wt |M$)"KaߥjDÜs eUuZڊɭ#2¿wɟY^kre_XzI3uPK`X9~3 ,setuptools/command/build_ext.pyUT tIxIUxk~ZṬǧ+@# lNq9+r%Gq:̾wI#Z{f4Gv~O\ۮؽ$Ij[X| wAHN_'>h@`hy/ nJێ;lTu,=Š ~~>h<NX_gشn]ùU )<$eA߷d >TٵXyin|9l4Tg|~r ;Fq`$}+[Q6B؂t|ab_Y5Ȯv-h*_ ҵky>0X6Q 'dĶ.ʞyziPg޿~{2 qq@X,'.+txlX?2;"mh.ñ6+Ot\~KhBՒ#smr`;J3FKi~4Ÿyp<ͽLh/S9thǡfj2Ks 20'B/۴D<`? F?zwNgVv=GQ*F 0fsysrX})]+bV9`_x Xi(Wyq&<ۨupEo`Ś sD dS8 $DBIAW >D0h B$;+ $hJ0HEv硙8 ]#Zs2Zs)SY k.صQH4ùWPGK[5Bǫ1WH4RGPqʑT"+h *z.N# *";`a|]d_|?6*0p(O{[׀N?~~w5 4X 2I]a jo8ʄX]%ݴ@l6V و\S]W(Z CْH;N@=m{dHX<_E Y{A] ڈ\݆Iq IZTu6}a )fcY&;@+;CAX-]9[w*5gmͦ)3̦Ț2{CFD| %5 ̊0L4jKXtpx&@7nnF_LڜAG=Z7Lw >RΕZzk>1R5 Yu^qh#,qABp`Pk:IJseG/;ݳ -tЃLzNv7)BztEvl0UF)b\=}? TSjp_G^J>1VI0JN;$ayk,GBn2;Пۺ&\ђK(Dx^:#Կ>| lΓOnRMH5VEbt<4T4PQ i;6pǼ}5iX%YЪ'~A2 LoHڢvsvI&IG F@VKA E\Z-{f|Q>?G!J>"2bP#ўҹ2WV˧Q5. wii'zWzEb`~g R-U 5mpxY~;s$`cQ77f9JS&,9>#ܫɊiˠJռq90mRqx!8)-(pd( 2S6j3BP_,)SB{Ŏ~O"$;5ùC&ЌOy$.7jdEXӄؘlK#%k5--^TܱoM0a^0Z`J{ۆܸ fj&npG G'fM;QGy8QndzރCb<|4fV5vHUVFxbp5K񀘝$iP NioVV[6<_" 5V񨧗*6"bI0Elߦ* 9z@Za>4nRQd.fiv-؄VׅՒnT& ѰIV.Q%#)Q#y[o"ƪZs.r|q_..৚7'!`d,m=j`n Uzn&cwDJR40rX-%D3@e %ȣ(Lidnn7ݪ$4mC-91"R}jxYnq +tndZ=x1MWګ(*QHq w{ϰmKs_^$Zȓ\$n7F6Y[|UwJݽ`j"%##8f}n/un ^i3zazj剩^!Ne$7isه#oY+D1cUtP_YE\Ոn$+˨MuR) |}uz N–,Mu 4x [`|Xp :@cLįĞkw "~z[$=+޿÷1/ŸeM,iUB(#DErAt`fglTƏ*iǠb#KgVbXIyb;˶j0A? ;'R/} D5]cTWQC0(՗{-t 'Q^LrBdA"GuxL~F 7H)(n g|6Q]_J'|ThD# M{= wݱٞM897; /D(ia%Mf6FOWTz?tmN#{)!ĩPKX9XLD( setuptools/command/build_ext.pycUT IIUxZsFv|goRX")\(^k%;R($AHrU"W%C>vs!**ܓ{69Rn`FDž"x}kz8]ߣ+£R Jk y>oJUr'Ze""n I??%b*t&vk.b!$));+%¶m8pZN+vB]+؝Q q<+9;x^<}IxeD"8D$W."X^[D|Vo;kOD%AIMؽ.b_ o=rW I ߣܥQ7;8'n][DD:?joitg٣o UWn{I?9W-Esw *YQ' ?uϨ#g$9l(R[[ɪ~{ (St`ҦEg*乺X@}<%@e3)L;+9̋`4n J*~>_.ْ遒1&x }OCF HI 87@(Ӆ{`m֎c0A?L}nk)6[) ^玉45۔ ?cf48a X[=e'>I^ǾYPuF(g#4/Ȧp _{C;ņ[7QIv=0DIk N$;f5ЋuP꡴eDhթVS< ZB0ɖ֔6.$"/(9Ryvmܛk4kU%pIhy cFϘѷh[^!b,% fY^ּPZxFk4ӬFsE^Ca_2bTsc [ڏ :9H 썝p}&Gko"'/Sz0GCChǪJw~{pc;c>yL(!h'NJl?~66zL #tlWB䎿QE^RM<$f޼fF4fe#wF8?9_6`YKѱQV15Tչ.#w ,=6Nb.HWPZ[VWd2 vմൺVSLug-'JS)uWA,LR)ZlP. lXkxwadnz~G+)C1dV\(kHLeuӫYY^,*k?"r( ˁEDh6I#U*Y!bH8U i*MG6Paz & UԥK)1 Y"Iy]iXm\ԿxV*# y?$@EUbR8)H¸,tP 0Ť*XɊOLb6RF;$d>wwfdg7ن"Pk Ίc;^UX$ɱ2vsK`(:<p@RM1~HLܰ.QyWfW2CnOE_Z~g JսxyK}ّT6@ U4HA; ;,? s!M]͎svZ2"4b.#+ ,eQ㘁A2'Xm<اD0}[nY.{Wω?ۢ.N6 oM^|+7yq/(wTt)lk)UÍ5]"{R`?M CF `qՖ@0^WoPbk@04;.Ya\l HqYx+`ƘSX7BzW*8#dNɻ*k»:ܣƷ6<5Qy{^|A 1^5"k3~%ONC Ě\u)6l0{~b(o˻Ni^zpb۞E) ٮma'_#RSr4؄a.r|n*:^^WC ;IM*.[OӺ&'rT(B֓b 9+%2a yr6ɡxaL1w傎+QL4x˚z%"!aj o괼gDmt^i( $ML )l)EŌ|kx^ZZ:P{Bm8g.L>KSO~0D"gNݸ ڏ;~O4 f5ʂ0$Ib}>pPeunYJ`P@*^"^= <2@<*.Ԋlwmp_14?9p,[ M !o9n սmu(t)t;KެFT=LEUӿcpOYAWUN3He(ÑQ/%PJqVzcծ7Zjc֨4ڍFuhcwLDTHUh)(\"㔸hWmU6CXT/)`|;i0AN};_')8$'&CW3O\2dȖȽeo1h\%į*g,ػ:3ac$dTHP:(m O6rZW5ޭi 2{Ὥ6V6y3zB^ OP7V.pb..d ;䃠mByn;۟3~۟FT]KLe])udTN8Yc3v8o]2 Avr( ,tCyݰ=>⪜ÉB$9 g݉>*7WQ+rc s{\,7rJCdˎu` hc3 U7FsJ%>.[lT-oPK]X9{ }psetuptools/command/build_py.pyUT tIxIUxYݏ_lpOn&>4HihEAn3/{Ճmp7_ rDj\uU%i y׎BPzҢSU#/ڳ8ÕKީ"Y'hd-S'~vMG HH/u T뱮zT#C=_; VL (<r_r9ε`y<mθp/dCQEF (BB8r# 9x #Fn="{٠HX>]t+W2"Vz:S=M\~]:q|$o=J yVeE{ޟ ! bRl+'kx%z>sw%珆O8 I-Ocل(ْ?[%=r AR=&#HZa=Ɋ5_RXBq*dKw}-qgG@%u =s,/PǨ|@yk}` @5%{=aA9N`]z{ڜâ3 PH5p|J@x(]Yq<`ݸEQ̛7fAȸELL`V{}泤~qqܯz6v]CbhS .-"/6Y:$&ܱx>0UIYK"%i(F^%>f+AFKmZcȯMϘWCk~@ra V.=AjiuMv[a~Qa U9F{8D@ԢEАk_JsϥߣS=XBטe͒Vv~AǾ86eUUG[?\f)ڄ=5s5Dy9T*_P Ѱ^ PpC;1 B/$Vy7.kiaXzrlqǁV t1N"$7_8 @n= :}Ҵ.X$awvZ&NK@=2ciJ|P7+>2h]z~yJ{-J6FQ9GeE T05!@\CD4C+=:,UVKSWm "W|~嘲BP"?ܛMkf~{Pv SߺpY7y:ӟNW3j aiFg  "xflW6OP8@]2 axP;?n`Hw?,A1˞QЅ5ưwK~AIl/BƇgd%mCӶ|W`(i-dٝi .^sBѣ[ϋv1!o|x Q( b$ >וֹ [A虠l3{74fpլeb¡/hKrs@}PXLAwPKX9Hx Csetuptools/command/build_py.pycUT IIUxYKo}ćmI#R4؎M%0(Pl`K9YJ܄r r99\| ߐ_SAR_.CKmQ_Wʹ|ŧEw?"R .m뎭Wzح&B] 7zӴb%XoQ&T]I`]|)c!>Yzr4w[Tho8#s^MBcq{^%x (Holvs[M2Ջ~nv7|АJS+=,tYؚREN8QTdPGiqi4KtyL rԔP7S[}8N(b f#w3,3{i8ji5XT`mf =`C@x}`!IqH$ # >hVŠ**5Syﳒ3m Xc6ؕoՏ ~tpdcRQ| @|?zǦ "Z&kq//v_k+jkkeB7+vȫ ,(䌜(f@EBNϚTC O3A:K^2 VQ. %},%4jY.d1KIC!V0TO+0;sU/ UG#gMjsidzc7f-21O:6OLJquFhC`ȣSغ`z' ~ k?+nk }vK#)( Q3at*N`NF]lI<"ӹҀ_*p/MP=+-C&8#<5qma y]5qQyXMѯܿ.NϏTWܘ Xt9zpes@͎Kl,! MF茣> fLise'f8d8Ҍ^Z #NHJnczʼn`TOoopy`y ' >%;ٖuyFԝʍ|sE$S1b$($<MQAgWy3uqٸLG 8ҏ~z9 Fȹo2:sUH@3SPyO'>_%ȕ]˄\CRi$̑qIH U?{21^(\g&abB9oH-Sań'>\&k-",슃db*eE\|\ YҚOPq|Ϭ g %bY>0Rs84nNdiB^l*lթDLX+,eaeE|NmȒT0P$2،&|1rcs{yՀt 9;eRH1ǰ^gJԝ#!'TS UuyzriHSBF(iMIꆩI7Aˀxd2>N۲m@og8 ɷ*7^313dž8Py{ġkJ,9Gs"Sa\\ ./=HΊ*6W$DOkT*wwqz0kt*u(n,?8UW9"|Mȏ3Q !r?;:D >h \!>wm'd})./aH6lWn'3BՋL@x#\l8ei ~fto䰋Ʌ-k@mEЕy%v{'xQ\%".D0? bw*sL-l/)=5T~FW8SCX;ni4mXiP] B5GU|އ6biXxy2l0-.FxS| ݬ9 ߯˖SuY9/+R9Cyޓח3[Iȱt^'BhK{KBd$1N!ϱ d 659mN8U{p`HW7 7M6b[/i 'Z\4rI+JOQWiM:rŔ"Y2`Y2s^{yoMp9{4gWl|IE؛oN8cP|Oa a^x'kQ9VoeޚoZ[mrlZݳ_vNPvtHCܭQd]8 䴆s⧕E]p 64jГ~7v!ueH1R? Fܕ[B~;wm.UFӛVݥD'ΉjS@(>:ANi)fYJnȏ7̵g/2XY#~8=xj ]+b@lG1{vF΅?PK`X96+Q{{ ֜b /:ǝƊ Mn鎟K*?G NX҈*(zĞxja>;(6%:2vCjƧX8IèDnM5YĎ++ל+HnCئ=6^VC{wV^@mU\kej&j<|$V" e4፦v5NJS<}:o.f#I't|A7^C+6lKLkql}ۓ[m5.͆Ɍ(,}KZi>9cqI(*+74ˊ&' ݈3HؠEglmgXXdXe_&$ *j5\"VwACrYD 10+wMKlG˹HXV#>Z5'@ww7IWqI qdE,\'AR]]~w -+s,^j6léƆE.^9׳uYK-d-.d ҿ%&n#g~iy+;3Z&b4Ԣo.>w*9(0Ҵe:?'>J~@ELi 7qaiH?w?cƭCB.`&x0GkRP9-Pϩ؈\8)L|FX17jz@$- Nu|ybU`Je'^kIX$`2Xav6D:Ue4%3KޓIzc si0yRă(N+X-M,<%qBpX,b7-1QgRE75f4G޸l3EYD== ˝kOMv:_Y"K1PR&&Ɏ~.i?-ucBG ݿH;ܡ0 ņHOwM` %dwQ H}*%QL)2k{xS_F:}6vJ5%:Zji*#Qс|%;s,,@W]÷oU, 6{4ӂ{K|?+oᨺ~;% 7<~E򘧌 .µkn&H$>멛q_@5#I[F+{(^`~yS _?!\9({Țz$Z{lxYoh!$SM[V*1De׽OZ\sF]!GYpG~aœ$TMg[\ PVg͑Yz<.BD^PKX9 setuptools/command/develop.pycUT IIUxX[o$G߽`{Mʳ<(A l@AډVl{zzww;/bGqx4 e0;FGő:O:2H£8]!<ڸ(o;mMo +_/+uFtQX& 4L~&6!8PnpA2X)&ӕ% ,F7%Qj_B OS([ Yęto(+Eva8K?쫢 umyIˢ3%Pթn൜5S>SL4ovS\n;*L^C{o}2@s,7Mc8(f/LG7i-2vU6 kbWtfpT!L#<+tߺupI;(KC~nHGϑAr9lBS.VmI\5ˢT=tms1KQBgiti&"-dV!,)m +vR%P YPe˩FE$%X9Q; )AAL.'e΃fU@"z8iF1گQ'C0GUntT M7^GNZI* xϹ|߁ֈU,Aeo>widf#IU$}(l^b) &Ȼ6[W ouoᆈQ1B\3$ŲNT*Xt9EL (jw6B-d)57:HTD8K.K13b2ɟmMZ3c4În!H%ZSFRUogNQO~-sa7 ['+*Fp9 ;"b~ 4F(^'2{djD,h^K7Y-o]*OHY^u@߶o~%fy)U`1A)Rul-EVGM?.7TϜ% >k2S" ^W# {Z%v?yԐ2U`3ݹSd碟"`=$ PEF\Ԩ+_a0 ,F8ݎI v6tcuq;W^^ޥ"cާ/{F|?bޏTZZѼ!#6#&hSk4e&2K,r^em] {oGwe~t }})h+k LlI]W8⽁EBZ|HImGPK`X9FH{B"setuptools/command/easy_install.pyUT tIyIUx}wƕ+z eytV&4: H*`PݏisgΝ;WC{Uh4d!<-6l/^mUmuU(/lV۬-mq~ٲ=^*h}[l"kUe2o&a۬׫je P2 <۫<̖j( ']g)Zj&y~'A0Wmzoe& \ C5]^oŎ?tpic_/5A:+W6X6TP@&o;\F~nד>\TwY/-7Tk/T)|ZSfuq9|S,y]WV~_EY> OǓN%olKXfPw]_뼩2W45wrfM$UMʪ/1 /P#,r e2mVwj|C"V:Że2~:ʚmX UwXp˄z_ ^I`4` O1=^& Xn UQ1+L3IbǢC+ XͲ.J ߋRBgB"pKw,xygEt}T͍S:fș|{1Gދ4 jFWltAx#|`nk!0ʒCq1vL|_䞯Ho.‚/ X^Mavr]qO½Ql6&,Fm*Z|*zf!^3M#s#ZkDz9NBnMᄤ9Dl Xa]+d{u?/pU(le<1wy-PE1/, .@T6߻hF+{8@̠E\dR}\b] c@ߦz E  @u􀡉UЪt:8 >E)xXu9mͭѨ[΀oV)`C$ۡwfk??鹪IE(i#: I&U}y&9*[ A4Χ VQRwo H$r-n穆jzϪ|(3Aqu)DFM꾝Hz_'EPbZ;mbʈ㧼D䤼)D}|lgw7m7LtI8krܥ2|"/غ.v5mDKZ j5׸<^:1@.rD6MArv=[cI I:Dhb~E'<KlV8FK{Wcn8Zo..1ɇ {`6 /fY)W\h-Wa 8eb^٥&/ΊiiWN^hL\^oKPcJ9u.@e_sM~ _CIxYyQ h(Ds)%:Ӌ "{w<3rNnkT;J aXP5(<y`X0,ATWnJZAgw ϮjRx݃9>7G&eSYHa~*.U܏@&9eV䯐гEeQtj!!m>0T G57}݇ןOk:R41oD0^EtiMGOMd'7 rH EYK}Z*\?g9$$G'45d6@4蹜3y 3ƖQ- Ӆ@[55t~ t!_mL8Lq#~n}OVXvΗn E'C4cKږ?~%{-7d=$8RHƶ D`gv]Cc]9n> [Uxő@MT;!qрy1#iخ$JfXFN L <`*lAjXΛ׹NӵOå!8*2>x(a '"H(eM~+1D֏(8m"6ɸ|Gѹu4ZfƈVp[]a/P XWP$%UkpjiԳ!A/`op݁ y\ݖMI6ف&z s[VۢD6Hu8'H":ƪ0A|- tC y`޳ 5Rk^y5H 5V࠹`7YML zˋ#KytDva_¬c1c]M$V|0-_^!͈w&`ּ79+lwE],IzҿJ WTXڡ>wmB^,9y92#}$#1e{:2􉦢" \=h'-pGh8rHgE^qz{<jyE,'%>$bp=#;({fQF~P6IQC:,ę1K>٦u_f[2J\AK[an"r@}$0TŊ( ĝ*r/Wm/,kam#Yv[J#ѕ\N %eM]ϓ sV1ٍ>} ?>;;y;f,5j$k %`%S}B:w-Շ^kS;К${ɻ]-=g /t$Ќ*$}WBp* o_iE9D~ז2SÆN*y63M$ݨ5=#ߦ%!g {^AzJ,3w2pjhs.bmiem${Q)'Oĝs+Xt6g @C Œ'%,(:x~PeVJ1cזڷS+r5'H%lzQa׫q<E~^7J5"~3$4|Zw+ ! uðqP͌@s:dC7O:VIWǞ%s4UZ ڻ6JTp {E0o¦3K (|f{لrïff;OkyԄ%XdWV / oG4\@U#Ȕ6|syS(XĽ8[mwj4 }-ڠy^VmWPT'@Tkk%@4hn]{Nc1 %/jz({ 7ڀ9`#D*d?W5YD,qwB`aG3k3=Uwi8&sӕMlS0jfz{#/T99xdZ7FgQ>(5JJX(v`ځQ#LOyb۱6?ZvCرM˼fM~-2X ƥ/lњuX] LL- ؓl$3'W@mCB$M#6Ql"Y.=չ\'˾޶9W*;xlكE 2Br{B&;uL@*#\̭ޝ`퍷bBљjÖx : *fWy S^Yfqu)M_3RvQFʌFy{!d;oc43HkλNTq;3څO>UwOk/ E?&9v'^~h/Oֹ$*nGpVSӖ]_m{#J~ cCbG뒢+ -ʐ^@[[W?wՄ狠cf.؈wyfBJ)t;Hx%*d |VjIܹ36on K`s|3@v A3 AĪs ^ܷ2G8*CK_8zmjO{&}`f=f9TKc}0ݣhYQ^M{Y#&>!5}K?GjAK*{(h}X?n[6"LJ`]hӻSPfQr]M.#{MjxCyL>U{iCu />/WOr{'J^(Pyjit?h3Հ~ryA[n`y z >FiP3K}2Qqd8aD왃:,0C: VMǶQJb&u41Uf{hڗT2:' 63,Gr([j ^ǣge dJρ^c,o=_3N1JG/ZPЎ!Jt@pKg?p^Cf @Tp9aӏΣk_Z4*7`Z=vooϹҎ+qSDW^õ,n}Y ( %=7r^z_}2 >^7>cP)j qQRmIF& Xۃmh悅1yj@q|*%~9D(eœ$ whvw/G>:qUBvyPx+YRR-jM|9vRclGE #H84O" y:ChвN> kWSP'IaN6}ٛb>p$_+aG!@X;9ֱ=o69iO2m.*HNk,euѻNołAo#V0HŞ`Q0:$]b-9Fɤ-ZP$鸬\~~r@^m}?Y~Wvj"Zxw›ĶHF:\nTi \9.]{33=_Xb&L̊ mygo9}myJݢd V6.Y,)L$fe̾)Y K.$)N&7ja1;^]rխR9f-RD{SN=3 g9ĶƘPQ'}D{1 ?%8=pVtuo7tQVO@h_ϩ>uV{,F*$PN[@Lq@ :}UY<uYaEl;;XS!^5` q (s:_cP~?ME\ bnbhK1DѨdifyqYQ;֘o0M"yq{e)5U4Y@Lyn"u,P γ4r:Lψd0.2 tX%p> .t%DQcKI6A0:o&6nu!ee9։&$ ’.y!dXF 60}["1mCgK]k%iǷQ#)ډM|I3̔Ӳ \#`=lQ* Ո EWuVa);X~I;GO.Wȥ,$'=:5 u$2a6a_&s;;"$DLpW[o"GXF@"[C,98 Unr̜F!֢g@3|vJnW54 ~?tIU DDpjg]W$ S]nu/9izq%v(kRIvnxzlA@}zP_T&i* qp?%["wI:䶕,<񆢥·߻SdE 0Jֲ :Ŷ!pR ygW0±5Ш6/=us1nն" \2(~zT_/xw?JMʇ{Tj2*0#i.r%"M<|ȁOLv G,OTǟ>\TumǃwrZH4jrKfc3K#1+^= 懿X5IONls~bNe/U`2`FLo{D+TQҏe 6:6M1UAas`OB"{fJJɓ1f${dG㷉mUJmSbz\JT6V)oxA`9Eu=H8?Vsk#>le0]oU7i1&QBYNW\de̊UqΒc4LGl|[76ykm2Undn(ђ&5JDg/$ 13i筀B|r9;P15-rS=NG:Ar{S2)8sf,%jđ,0(^j5_%52lZ%2&a[rnxDЪc *8zvxhB}0nE] nGXO<4Fl@0v\'Ӌ4^T&4c3vr7La ك9vsjG&F _X(K zrd:~:03q%=?Q <sm"ǩ{.rYy09-@1MIds̚-ʜ 1 -{lU˻N]E@V!'_npb=-垢 ⵀUK}Jt|z6 tr*f_$IVuő}RW´'X;}R>|$^n9z{K[>ʫ6{Psެ~.GPzR:EVn2h=( {OmW+SgշC%̀٬$|/rj߷ۊaϚ4Mӽɛ"-^F'(>j1q`Y`R2 +(T݋\KcWDo 'Ø9"tT'Y|!W2H;,̸]@R)%zɹ+LO>GMA:I4{K9}gT}  U+4INP7C6.("4&> c ¶:9N>|" o믿N>ל|3 ?߂ _"U0짼t /r8kw%%Ŷ-=OqC'{|a?= F/i w%ǔW6" ԪSM+٪[qOM/l@V/2MGEVԃHcT#U 4kr5'T8_fuCY( /A¨~'HQ8βq:R,^)QoiXLIjV5L4\Tɨ ݘá:,=C0%?mYNRų| _I FIbNCD֗ob:Wd.Q  9zO*vl"6\(J۸mz_@nu[w[GD^ݪڛ:U[xړQW!W*؍j me:{Hl(_iWF`/W#Py!FѓnQ٪e.K+ԶN)\;ƒ"<\Ջfث,)b>_TU'S(ft^HJ? wt>F~0ҫh'TG&繟P _$QH/ɟ;dH)؉AދrnCE} -yGpÂʀDͤ3{]SZ5voz=c6q.Ś 88bkoK[L=O?|xw" ׇ3gLi=MsV ЋJVًF8x!6tY*D b\@l^%PUo*?C^tor)5.KP ZB>βґHrt͒7fhZ4kq a8lq{zHjaI4 RsbX\&d-.G1򦅼rerH #s. oKyySҷPjq= Sh0 A5 p@1tVNOx(r401Q͖ddX򱾈5HJ? b4߿8vꏕp >#8cGtٲXbL ˹P-=O_Hxx+>ˍ#ub-`\>F5&C,ć޳"Ufi8^LhN1au2?Kҹ.DY_SMx.V G;Z9}疼ۺ+>bך?ŝ;VQ[GTZfZq03T'eUWU>-BZBJ΋ŅVӾ]TDߣ]9H8/r"ˁO6Nk=b-'C h!<Z{)'Se_ e/fsSẍ́,*)PX|nͿSeکHtoj` L'c|kCQ*{p, }?y4߄/^NEܫ\(ZBޛFb }~+p/M-xM}j2N m7tq_awGE1J׬^ݿ?&uJNFHp!ҧM#`n (ǀ'©w\̉%"U?O@|&G[ SO,o˥fPG Z̷%vn? AĵQXɌ.SN[̮D2%/eqH LH_G~xy^OvJ7g^f_Ѳcc䍐9obv5geM8OJ{7ul(.PP!'WKfߑ劳t8ӡJl7HbNJGL%܅g`fJP[M~+9Y3qѴ{` "p6[F4S[oxT¸zM4LFlfƯua!,BE[S4o>饝υ (a vNԠD寯:dv^ cā2HIrMɝ_taϤ=â/<>2 pHV֞gF0h۹妙NFk2"2N{jlL5ump#krVi=D[h yYY]viF PٜٓI|sL y!FKt`AE^`]<жYG)ENᴹ8YMߢeYלSܫ5Om_Ӈޡqv*#EC=$2ꁊnc=gYtGu.cY݆qKJ?dRVdHߓ-?@烪tVUxZty^?glk%u{+u6Jf;[kiKrڌƶ>p1Mɦ֠B^FX|ѮH8Ľut_*u鎚vogȹ?x鈬#|xLM1(}Ґv 0BaTWgԡ%E.(Diw xI *ʧ Ѡ϶p/,r GX*_,!U+~Θlȋpj9@84USiKеK}*<'|'gO~:fX5q|,{[ Бc`^2ny#_P[#|CXEw,۴lW/f&gaO]ƝL9d ߋ8rv ӛmghDb//.w+BH$RA!CWaƕM#tXDap)Pƹ,ѶzH+l.a8>H|bZR@M|9$4ɷ1}lG]l7Xy|̷rg7"<ӆseaQO|a0Jk4E7>;mvGj4tر5p_̯2ӷ%%J<`p\u"iնH[ǽ>,dwlxiR%yq^ʛbxOx ; ϱZ\s*) 岪W"xR Ce=~Tc*ZeK4--WyifDs>Nu0wG]4)>Q܌ya>vLt3ӕvj2AJU E91 ?yB[.=rb?\W;P ݾK@<|TkM).nH褸v8mk`쎿^U(4d crī|9^dq.'ߍX{-ow%^'E+=lCA9fCsC'p e[`ЃUl翊Sl'ˈMOS(Ga!,gy䮫QB6ք?Ƚ=, I2ԳSo'C0ky{(rA`Mt˟(B"eNa"I5JC_w`7{ElckXk2MJPߢf7Ls 'ԪjJQ*}LJ>P{DlŔV7gԓ i0*gUP񢮮'*S)g B o7a:3:,ބ2[0*2V6Nh}ŋٽ R!018/oBL~#v6ߗ(kV $ѢRD?"ZTP%FQY)5e-p5O9 kKj r_?49!szhp^mIx엱1Me:=ot7^\W3p=&έ ђ=mC;E{3ozBIYym:v'i6ȟfiK)Vn1f_ Ȝ3h|$83OV (jxܞ!&a-7 e'2UfEuQ*$['(H>0 r9"TV)J_4[kF ~r(AQ_I !#՚E=3Zmhr =c8٬<Չ4r3ZN 30hnXX(1xů/JI:r3ұ Wg)Y@*XŴ72,&C2A"+˛@ ߶i-?uW7TCV 7 'ʳ0N3K[xrfB J,,Cߩ e<,cHP(-mgMnjScj@e7>0 $l/3bX2 \w/ [T6[7_KTu DV;D `h[əsSHޞ~WZad9C͊D[o5eГqJ mg{ZjL};dႽ%Gt1V@tRѾ*`sTipט3\khRS_d~I>cPI x|= +T:ɫpx/Cӧ׷-0SL8382݈͙ZtO'Ts!X՛\Z/LyU&LΚ]| 2=9WFcG$ޘzOhp2xN$x󂇌MW7$U?A.ihɑ8š~N -CzÊ&6rloxːNPڈRtWq*k7vʦNXZG{]ѧ3}:kx` #S. DZ)Mt &WyNڤ=)dZPKX9v@Y%#setuptools/command/easy_install.pycUT IIUx}{py9{/psI "HzXLR)hK${A lzqw,qq^PI1[j=z6vL6manM63}vi;әL_Ikδ~w^g2b)aq8r1qՕw~>M?vZV6Z6쨕 Jц{J ^. >W+6\V+ej /AR+CQê1VF$ޫ6GUcLƸZԒڜPI2)>9jeZ5fʌjP+]ڜUjjjV+UZ9"zT<ZqUZ9.CjT TVz@?Q)\j'4x 5e )zwipirX@YPZ3*xJ*f9+(>cxA/*'SxIOrjojNmTZr*՝FSj:Jyse۫SܫO!PNs?>K?]z ei9{fxFW._r(jkQz$Nf#nNh8$a#zq7YnyMo=\* /lk?wfBF3nn^mEMݤF%ϸT0\w# Zm\܍$i?{x IN3L(tv1{j)]!RIhUb%z\/ hw8H:yIz4~a!è+Hj-Z#\Gdv.ׯQ;̧hap'ew׮ow =n$\k4mqP[ŜvfH.VׯyEjWJ`]>~Z$e8鱷`рƴʠ&E>'枘ud{QoyaKaȂݠjSջA\G\G'QJK<,{ 4$:OҜ4&]j4ZG0z]/U^bl$<4(1AlF-~i#uO2x_̓#0F<գx3 W_z,MY^ٺ,)Zhq\Te~ʙqϫx u!PɣNL-(2 k*?R~Ko+?V~*GS{ʿ_??R"Qy'DÉA=(C"  ̔oP_Os%/yQ.s"+ R}Sԙ90k8YAÇ0 >79_Q}ږor6b D_eB~\KP[xRos`N )k?5+e-+ k~Bgʁg_Mρ\S7t(M\ѤMC6싪4Iz58^\d-Q=+jH˖HBR،kL&c6ʋU6v2ښ\/Q.гxHݠSU\p+cJI[v )G:Geߊ'ztw>@5 Nl-x0j\O? 'תƹ[IV * oc[`RyŅv)y2qFƎWq8xv/SEfL5[ INUːp%af3FE+Kѵ5P|| 覫fH ͵FXOpM܉f6z6q+ơq j+^Rګx3$ԓ'=]ϢG㪰nAN;i1xrD`+|/zn 8rhպ;a\λBgܾD32b**U9?X}mk-Q9~'4 ;! 2odpė0fi!lNIۍe%>c_ixƥ @JЍ^<  YK)@1ӬF܅ ݉ڛkhC ~[ƭL_i `x>˶սF%nzx#5gZC6*wy-P ݵvr)hM}3$qEtT, 4OIŘփdzmd}6П-s| ʯ!NNG('k'mSil`4 pH%9pľ:gxL.G]=P'^2JTb= 'p=ja15tj$!y #5Zr4Gk[Y#@jLOt-%0& Җdƴ;ev5vcQW][5^P;[,I-\95 }a&UrFj%H-7 bݡ 4R(ܹߦ;MfCAcQqjkTעH7#Fx8udBe4>~o>xנ]YBҏoC+ d{f)'u:@ Y`O&HjI|J*BTm$6Iu5\O_iOx`$o.FBtcs;Zs{gn-=&J^]r*mM01H+lm?\R)в>#v ̪&dE qC$F ?dD@>^b q>,аBl ה^FJA`Sy9zauCǷz.ݻ^Q{l^=2'3c*0$(d5}"d@?f(Z!TVJZ2ZFǴMQ-Wp%pה pªk]s*>%I،Tw@Б;_Yƫv$ϙ,)I΍d)K~jj]#:W#[> .Mvy'SU e59κii:k1Wnd9TKR烮{PVt`N%O!ZWz"j:>c)"PqEݢhr.oW(R VR'YF;s*:(SϐqdVTtHB "kwg:Ztbx T/qXoG#\ebpVw&>AϹ؝'\DOQJ 0Ld!1#ދ芏@Cf4{pAĐM0j5:b-\dьAYpRxGj>s}ozV[HTED ͧK'@"1+;A)H!MjT*V3t g\Db*@iđy+: 0އ,~J (*(" +ւ2LxZ@ LVX `e $Uf)ı6V#L3`>Ѥ-aVt.;^Y-Y FXdJ dZե6P/49 I0jB~7׫^y# ;xCj ռ5:RW/i$E|;Ճvj{v KQ'P2][bQ=4`h0G{uQ=4'駠 GuY SxHR>sPq>RlBxY(ǩ̰r&)6T)AqȂImAz ) sڝS´orB8E sy?Ч ">*]6X3XHt Y}؉ℝf pclA&\ō 1BƅG g_퇾e6e5P=6p2%!#hN'!Woq#CԈ&{Y\N ,Ls:V\8ވ:I "0*"MlR=ݢ.E[WFd$xlNF<0`kcXNѣW`QAvjA5Z%i#0UwUysFRIdʳ|B &h"!,&ó6PվS`oơut:K')CgDK £kг)>ˁ 'e~2^Q?!jWtX5_]etj:5m{&R/ /z;hCD` ?T 9H#E@ig@ƒ |FB6 L0} ihf[UB׶TOY@h&{gӾ`2hU,$M|;{ oZ VJqScPH͸oCZTBHQS2-#8:Fbęp#Ns\sMwR)=iN0ATІy v?V> "E-Jgdl{D݊ t#/A"bEFz&̷ff0~$fÄ9{aP߈Qkk:]S xMfZ1yN2KD8`Rzu "HQvANSrgbc{bae/wA+l2%X&m nuQ\!}60fCrXA5!T5d<EvLPCrJd?}v5B#:IX|.KKxhȼF(c')f"չPa`΃άe,@XIڋ1t%j3 0\ >h c}X0"3D`aFQ= xxbP!S"`q>C^> j;Al  q.-"# 1O&Iq[|2PrZF޹8ja-mVCnq(6?>sr)'o|2{6F\Yv܌9=hNf+nW ^R֕[KKKWS?A~@6 ٥\t SQB(X ^>Z:oKx(HF =~eh?2CqHL/"ߟ+VH"uSD6:_yh9bO&ˑkn1PŸ:% CL=a>%e=rQ=LJA*q*=y;`02F>1 SVXI,}P6n?a{ DEC÷,`&[j#0p_8vpEK_az9eEwΪiZ_ۯ08aЯAKtpzx%mTO:R@xC2Nfil8{?f6G3mbUӖ G/ц BNz"MfN7P1Rrz;xk>u\<#zj"MMoU߈Ź4\cVBXb٢VhWV U?z<8ȺM7?x45$?i+drB *`DYkbRq92B9 S?rکY fIlR/M k;Kp1 ?qf>g#̿-eCi/oj){oEXߍo򊵃/毰5f<"rO|Ճo!h'[G(# l3'}}%kcEz뱾71#~ÐW/u3e;qqm|#^A9`|eXb]:栴zń'th߱ ˩PyJfsm|;Kƛa+˖~p7hD-&Upi>-50M3Ƕ.wh ݵZjjQ2Vj9'lD Tc kTǦu1 ,2);6gji0Ԣx7[IͿ[V.6SLPM6?z~  A0 /);E"~C^4 ?6U~ ɽnoӈ5㣲[SYE4oXᑴ.;h^X?O'$-VTkn0`-#r=\J֐t\_J؝E6wKX(c:9L _+\-̓]=lᢽ$PPAQ'ƒ)MØpVSPsߺi&ǟm;Wa)'62|4]P8&Lտg](R՞vg!C^g%AS))lZCEsUx/3_P =RJG3N;ףji QcpD0^6$:# %2%{&Q\]xegA;ƯNf*T4h!H5_ enbͥlq+8{kk#pϧ+ߧnOuR=(1iX\+؄k(,!μ1&ѓ|#Lo+@YȰI1 85lP6 KRΧu1$DGJ%Q]P)dNBfxFI͸r{y @w.7{Dw~#7X=ޭ~D?&ۖXOb=E=Q1xIYJ&e4w3E<19x윰mf_gTEaYH,TR3 ` %'E"W1bXE{ Z_Q xNq1$zil)qBӰ6`Y;ӕ#s>A/Oؿ46ֽ֞QFΚ&Q'+ޭ\toTH,]^y;7y}T\7ܗ|e>v\vux俐a˜*AæR-]>k@È76érՇ;eW]IaZS)^ս_K5^d #cK~] 1D\neǐR !Q٘ro<T[63jwqDg^?h9ݒ^9T0qSS`˶@7-t߄$+ +X$+ߦdzĂRA͠L ]9\dAng3\,bf(2 9w J%b~m&^e<[j,OZBx[򷳥ԫ?>kR3+eOLe :IyKBN.~枍a!™.o4F3 )^HA4b''y5NJܩ=݁-0'ffR|I!mLp ! oiN&j2^ ZS[023k{:}SfL;6y8߯>1U/|W. *&-x3m"QE1| *R-.Zx:(f<5܏"K@%{F;>TNa;%=~DA܏}qIcv.޾NeuZ*ù98&Fd|4M#OGok,dZq}J![xUCød_Kzq DSc3 >';,t^0ix8peP E; fd_^Kɗp5g W6l>>lx6Gn~V"∌^Y^\1 ϔdrEys1,Y5 AՉ1Ѣ/>LR֝Y} k#K H08Fj"[1Յ$a0,sK o`0?ҧ7.t dKИWӣl|2S.*ﮈHc5dOtP)dSG Bgq5.0E0|K(GlXQ7}/՗2 ˄/UQ~"8~S}U׌Wέ1`2F lJL_?#1c&!SIA@HHeFz8Ke\?Ti!gڇanh޽Bx—MDfFwyJ][u؁. ztoEh{%"ggkX&u/لg}a;m'Nb;聯b.ПNP0PSFLIf+EÑI<=<_bfd-j,%(|'.'kABiI|D9o-:!VtVSW1ü'h^&rO!#UAvYsvdϗhIԥ!= hk_;oR5Pr$ױx;]/ީmE~!`7\z:v?M>n;LqC]6 UkP_9q5?^R)s]Pէ%ꒂ-t(\1}&izIXwӐ2lM]_ q"kb2mLϊ~x#aRIgzu>ւdD-5{sjnR;VX}Y[WjL.jq \K\Wʡ&Vx!ŏc) j91qhq`f RCP $10Ku,t\ӣT/ &9j0-e6i飸CEI&tQ%uO2UL}Dbˈ;jywL'Vd/g N/Ua0 FÉ;lahEJcd8}?Ӫ TOInGm !\8 &1](5VÖt6(~Rn?ۿD \=iI:-'QJ5rbϱT24՞+;kLe! ^C`6EE8E8^F5l׵͜ *`OndukLo_cZ,;ݜym>kzotau܎2L)3vw6L& 8 -IkI?~m1 ̆vezBӫ8tYad"Pr >>so.InoM}:9MQq]GnM]7V`tuΨ$z9RœxVt?Dz-n*_?1/^)礼853HjJ[}vY ӫ W7Η/ 1^Zpw[KUpb̟ 5{@]^la?nq=qw9зP "12ۛ12i2mx y>dAR2v+ۃ.Iz+PEJ FBdŬ"ػ1-vId&$qHRwv&[7L'}4mZO;ǭ{} BᦒڽsϽ<}Knn_2$uѲbcɫ,$4J9mNh[ccOJ7J (GOJDi-8bDamtAB'a<;ᐱx18IUJ /W>ϋ nMn$.x9&&Y_J}{uv6slW bL40*tY$܈(3!N0 S9Q^rHc^Eo%2 Ŕa^%nc4XVY=)#LܔpA^ŦOfO͔T6(y@RƏS¹sǧp-w)(HXc^)eq 6j R:{,L 4.e(ry>:W^ڑ Xlmp"lo7vUk5!&j,01P'['bޅV\Қưd:8#vnF-Fa˧ioƳr~ƳI:h2]fr"#(V·?Bb]فΏ!@\!Ls~VaiaϘɲ=2.'wڕnBL0_ZS^uz-1IBIm}M2k3rA4sTZKri6Z٠HJ Nq"VnB4nh*]e8F1S,bF#>ο9D&Fr`pbP6vM~RD75q^9ń 5@%Z(,6O(]+&CdOC փ w8h9]Nm*u?zj~ogׄo vLh,dU|dX}AqYiJY #tu@Cktv]~d_NVuj.5wCrЎڕ9iK n߮Go E zr)2WjEAh[_Gs\i~/|oYxYEc r9_}s"(x &]^ [3Ro *e]A7A{*ong9ȗ!}5ve'f8\ҿVu58bziA;p&Rqבj61{(KJ6_x۶ACYv- {M]xi}Aˣ>پmLH9} z"x,k7J:! nFۿ- lfnnT}4~I}~ke慁+$E/ԯMj(1l1n(3x҄$KڡJvR*F{GE^`.<$QZAp&S\$s%#/I!`wAʛƐo:[inAϢM]o;/:}!o/ѩ#2'7|C/K#ZơFl {:nڮ|iirwX ÑaP 2OA)!cYN/tX;LJNX]K[^4(~7!oQ8ߕ"0 P$!aF?#Azڼ4AeB?n?iszy<ql2ʓ=(ADŮx)|HLs@A#HR)&GlUmlU3<XguTI wI;kT(K94\ʧrw-^u|ۅ7z%'"¬eMav ;W$2# d56abVU| v[vsW/D$i७cJiSjəhNﱅQF%"i?d@_wV V=Yx+_kdD(Kۏe uKK`mB^ْD6C (N9ɯ/mub'z.b313(Hzʼnb8'w1Į`vtrE%RehC\NAWz(?u-vKEy1P{JKd_̑2}Va.+ǮNyU{y-S*=AZ.RضyYnuvԇ(k[G#GҏM~ܘϝ9mMo^Rhqc׿qTy@6^v|Y;Xz'l]ݚx-rK@[8FIpnƿ ^[˝(Cp-J0=;rJ;C+%\@~l>Ƭ_YeUI:#WMKrb X瞪MSjaݓa%8█X=2Kvy3U/O"򏍰3nDkE/ak*t _ÜR\[rUjVdhoL8܂1/ @ s<' q, V'rx92Z1|f$i3O]8 ;K(JeN< ,=4UIiYܺY1x(x}i2H:K,9ZTÄ^d†e& I.kgf7e xjr>U 1&][#@h2.-?dlmōm<'UO'K;{kv<%M!'.ZM_l1"x:)6mZlE稲>N+ka|yH^$\x‚ j!_^Mkj5;X1l :3FzZ(GFZ7Wfuesu|'.8h^2#Bպфw5p@.=|Ze2[NVS |ʲ|;_9!Q~ͪޓ4?i\(V#=ߢL='~#zZBg'`.|䛷!y ;Y?=*D]"KPl/IsVg+FR!d݊b0EZD~o1RRu(p)^DQ#f|;XT꧘, >VFB $!);hvcBgρ@9}x`SUvBS6*s+;Ѭ+]Pgԩ & 9җ2Nj]ޑX-XM8>v^ӊ–2y&t۫IN. ?̥P'O&KNs˛]N AEfew&`TKy?bxEk e3,:dDžr7GÑ!;Z`D*R@v\ROƏeJv+ .fd(VQ qrFFg.h'tMTm+aiuTVNsmWUy}r9aL-(o{d4g{ķ+ӫUM#\тWU-r|n[_dh2/7ָu\9X]j` ;/5>p哌D`f[jkݧYcO;z VW0G ǎ6?o}gL̥AW,gZwaN6Y@V.IK $'?zJ"l.)S9C4Q_wTr"-.c s_RK7R씯 k`MCJ0uAT0Slm\y4u_'TC XSmU:Cڈy ZvE@G+ s j}tA^*s\-E 0ǧ]>N4 ԌQjyծkO .~hb~S/ЖH*} .;Ӝ*)P(2Cu)E?M{YdR߾ ;Ts|-E# h\޿Yaw.4ѵ5nJ ܪ妳:)-bv~ 2ڠ3&ZHLg$zB^Pwlt9b0ё_hz;=hRse Z iNKV2"Xo2dn% exCb e` tsFh/FN&1jv~rY浯 S73.yF/c I"u$AAJ3+Y]җ>2KBR "Y)OuÕ$9' ,e4mt]-0v3t뢴7H?eT7y<"6 *`x(kfCc1pIvao(~"H_5 ;/Щix؛ez.}7ɂ/0`u6] k%wCEߒ}%jx3)SRֻAb7 sK!o3@qVc_J J}5&ZVT Pr8k78 Iȼ΁Bci 'n@w+x|t1/b>-sޖ3ξ\q6\/2wJbhE!`-3UWح}N;=lɿG*ԒpK6y>dƱ'٩%1.mc!-3Qn멼UNHgd =F KH>oW WW}4 Nc Fּ~.$y2'[JN P"wciU*mkϕ:fJd~|59ѫHv R >yBlq؅剓<~}Vg()Eԟ`̓B}s57'n}vؖtf ;Xh#4-4$Gxb_C84ݦ \r< MeQNKVƖS-*h \t'Qm_fo}7l}ͽ'M~B@WY)Q~DN?üBa dL`9!׿퉝 >4!ӏmz΄ 3}\CqG>;9]8QcΧ_eF (iᏒoTVoVS>4z}(#I %2U͗[`U͔Aɘqͼ7uϪލKّա֑c?R?y5: ^ qN51)*^6G/| ޻T[a2bd13'xaZOɇpPxO1_,`m=O/eЯA088g⿵dψ#- tCWoDjrH%Y냔 ڌ%@σȣ$1s2AL fh9M5s\wE%~`>Қ|[l>9v_b7'˫1X+jsgG3O)íBщ*s_52pPrCj;vQ9;gIF#R16zmQ0j}0r^vmӲ nesխ ([1yA<LO?T$! SN_mua)nr r *PLCP̚1S!m't In@12} u?4Q  "TTJYx1˹7;#q1QY{,{WB/ -|`^"1Z(3_G'mSt'|?nu~a]gFKack.v=`u!ĝ iLFpk`$(wK>UWv19'Ix<]05wj':}ḵ^9g]FN3C[l^TbE*5u|.aŵ` s%%hyxYM11W ɬyg ^y 9BFݰSsZS~0/?i?>E'Gru9*BMbb"))2kXMq0Ύƛ[ܿu8%Qr 54\o@8(G7h4JK*>#`O|zly]L~ıAھm#V#HKIN[֢H[uϰ[{[v+ʵjT<#*2L05pko;П2q<~ſ7RdʦxrHx${8@CO+ϛ]썐9ہ?R0IM 57!m4f *A)i$Yݜ\s O W^F\I_htĸ RWzř3Oe 'I]鴺`Pfs^'C~7/B8/6&ZԍLgV;Waݸ| \~z] V9^|ε:qU?}4 hg9ڊ;||^aˮ~DwG޸]՗rx9"N@ haĮ}*Z6I;UjvsvZx91HZeI%%ͧ?d T]N8_MvV%Bq6fs 6IOY#['{`,؅F1 kf dQ毎" &6?n~z(X` m%C(9#:"XtaEN]p`jA+E!¹]agwog3W{$>'kiUθI3hj[;=B'H{ymk6xr9Zs`We^(1w G}um18{n #ZukZs<&:^\"9sܕI :Ύ p|-'b.O7W'{AySя}A_M^lf☟sn߬Ĝ Hjp:4m;QițE}xO&!D#2գDpȘj"Sb:w8ѯEg~$ԕ0yWqެq{ LtG(T;U*bih)RD|( cPK`X9Hum=*7setuptools/command/egg_info.pyUT tIyIUxksܶ ct&JgmEXE"%3hDBe*~Հ Nq5!>=D1_`rhnI^~wΥ 㻤+KDkoNI#^Y~)%$Ga#AFgx_eVX+\Lg 7D! ?0&ec.~ǠvyඈC|w`)4o z[UOX o& ߯L'Ң˸-e=[p`T9Q m"=} 3[Yy[_ryR?sCj yND RE.[Gw9H>2t` ֽ>Wb AʚlE}ǫu뤐_{n* pLܲdg:jS0.`ַ`Kr_|C9Q/+BZ$ Q uo-\12ȈSV Q9V->,OY| vË1tz\Τ=cKŁcS_c0&E$9+soKR%)ޛ6FrEAKv&gcg4Oq0/ f܀Fn.56# /h!G5H dGGx%EɹD`'!ư}!XHnzӻlK>pLHҽE@]lywpB5t)-ꦧd,b[i!WZfei/~B_H}=#̮3+->1 BmPsAGai5-=$jIPp`=FByKocSlDl96d}ѨiR@!4\->6V^8rY7=*8DL# +0U*DA8ytë`JRE-y`)df{-yЩJ($p0)yu7gdNnʞG#~s+ѷf ?85Av$5w mU5&MC7hT^JBNQ<%dAOê)١Mv)cHÄFJH*@(UcLFwHtV298sFgb $PKfk݄ 6iN ً?wLsn\ﰹcCZ!$?Bt8}x҇sש6CK=~wC-qVeiRBg1(VqcSAmWnCϷ bEC]/u=# -K g $3PJ0půW7Ż,b7:C4襤gN^QNV$P&=3ˤ byZj?Ez]+#+ 2 8fI 3"*+AvMHFDيw n >ܜd??Ŭ| HoU i$7i~+eF1T"CSY鶡fyaO} <^ͯQpkMՊ4Ҷnps;ܶN(^q~((*q(1ډY[is BjDeI|kT؞{VSl8#C77AAb\kPĩ Ѻ[z9iH֐c0 TolG6eJ@9w!Խxȋ|w25zWO:Ex1\3 LkW҈z[@#p;Ĝx~dt|FA \ CvU?S:B3 ݷLq Y]Յ0HZ ΠCe7C;Q"cwtwDiU ;з۵1{%_珺0MC؏pd0Nv0\b' ㅀ8a\}A_Y"!UbuK$KP.o_}A9ϻ:>|/ƫ D#>ܓF,Sjmǧp.Q tQmE&G#ãm=d:`e&kCPث:JfvyẽSƣj(91i^R1b,1*_g}C&LWjn7[LL ?"gA#d  wہc|4FXm=U&:N%o>YAw9ӫ #P@FccwLyKC5bc W4ο`}+r$ C}wKx7\ʽ v [R%{ɆGR;gU٥?"b¶7~).?v]F;1HFC5(QG^byp,_e?lDlC?&" KB{U.\hB'xMyrs4xdj%g{+ cqLc^pT3CŪ[;*$F{s:M\Icb"s_~>+?(r 珫|G2+C^?pU0R.J.`|y_:^+N ă=@#JP)풢v ;ό? xHRSožxוjpt?L )~"M&)&2SP\{0'Sx\N^D^zM.hwx)JG/}4iEۛə*hfCpHuXyakMPE*Λ5U_x|99]a+9V ZRr]oe'ŹW߾y%+3BJeE xReze^O4a6K^0\^7z8Ii 7!V *FXŃLrcz6!S_rxOǰ<]`_:7ו~ާy< C27ų3x_vlh˶.g 2w 33M؏^W~%J6 {4hbR\Xỗ&R)4q*">pآ= =}uN# vL5dElN>5(їp=ګ E7%K;' R.i! B*IG: pRm67䩒I1Шy3ux+4lZ/g;{eCXSc )$Z,21JLW&TQoTFV;i%QY +R?}g֑q ?7y zQɖٳg0Mr E W[ PṞ̑^N[kn=7I{A|N U@?AQt?_ P_翁Bh7`x1gPKX9tl8Asetuptools/command/egg_info.pycUT IIUx[oFzv][[ƉUΒ|%>IKE-)\\[Nt퇢 Z}(P(S{3+ڦmgy=34ܺş&C?)/:]-#źmK[.b,$bgDSQUWՓQM}UE4&i)֛&vE4!'D4)'E4%֧D4-֧E4#gD4+gEtBќXS3b&y>Oc"(-m q g'A{MoS"q=%)ܬ47g?ˍg?ǍgE` ^9?ō籅kOp ^7O([i'+~= <=< 7{yċ!BҠ'cf$΃8џ1QU\WU./f.QnFH6Biv˻a|qɧ,pA y[{ oAD/`\wQ0|7 t3'aStAsxR["G^C zӈ7::EO˷`~V@b1خ$|ۂL72=HjhhjtA@H(,_HGCKin 7&S?Ǎiᬵ ﲒԆ,ozY D}@׾4A0#Af`E;Ove;Kzi;4I^ĉw^};m h٤hA˧Od~v.;˽Nn++K^7S/lW_-uívۍv4 =zÓd&hFfFZ^~IJLHڡmjM38Q2R[BYbOaCR"Q!Acdjz@Әx~[639Y\hx[XU^Q.>9wO[xmPy1[Y-%[,RV,,6@2zt㶢o .A%_[#Oގ/2yu)tifz{$4nNpx묦;tIfc/~kUI=k"y4̱G&c 24jvlJ=L6;xB"ffTf1I6D]l'N 9aVGDB4Q z@ٍKd(!pSjcŽA (P9e4:dVS E:B(VݼRcܦV@K@jNÀᐃ YBB,ـ;xv]~Z21*߃l5dST]]($?eXV,$yoޠn b&Y2ug$'N>anNQ֝*˘Q$,u`,bXJ0t?|oqrY^lj&> b89\aGeP(DMV;}W_ W!#4E?/ˆW =9r_4 +L-͍mIZKzS. kDܯrH-pz"0 _RV%NBىܮBscDb&s<@]N[Yk_ǐw+D>%8Be1ܜJNPlxAAw[ߧ XB)U4a)W#n=+k ~'CoD2,d h :#_PCid~BARPmi$?dYkM$bSKη>,8%y~Qgw|<00|ofPzk0WD!FprA;َ)mX (w{vv ,0ይSڮո@юsY4$! UIQHf!yh_~if8*JCfJ1.]< x"%Ნ?:R`>}CCs48+NS0 dh fBk?zݛk?Z!Jٚ K7Jg0R" Uw^$dfęsW?D vuԟx=Kr87ĈU@2+q,6Ky@ZCSkcfԩin* %}Ū9ͪɋ"rh}at` sMτ*F. :]K3EepqؐsdZZM`ԡJXE40*epTIr$'d++eU1RSSu.TϊLV7 ^$D0D\1 ZK|6rqgԻ+4C35^د8:i :CŅlQ$!rU ZP[%ݠ#\tMKr%.|M44 C4t۝c>B|K79!r D5]80u ]ɞR1{UnA1\%8%)yoskvbGV8㰖s}mk{w\bfnl +Sjh&L_T;̠9T*Ldm[~9l~6'(VOsr"NV}3+~p}m2<%( l"/P*aMʵƓ+[$U1*[63 sCPG٪r8`^Կ@nc7zAYx;c:8:4M!Γ4c9I-% dV/ho  >;jpo#X~)ڻM:0NEX[( ʔ;֗ܥJuu"^YS$~L1$.;M]/UOׇΏ~v]* {'8C༁IS_ߧhXWT,YT՘E(b3Uyv1 lw"؞$_-&gů8|O6}\sTf!Z9B~ ԩ_ɀd9V߻b/tXTru`eן)[3пM]$ozׇl/%]`r+@Pg9Pd3KpzgF)UJYToHBeQ%>A^%tp"Чeq**{܇ X)gJ" ؎㆕rBv'ԦcKXׇsV.{|$2АyD!'o\F4 { t}kn5MDQt&3tbbC*E.jYIEAwX?JBѴMQ"{kAW.7 X 9ݙ @'d23sϽU#\FxK S-ZUb {>?E3`ap6[ݖAe/3l4dOMg;jр'8S5M"xnLx>q]*(E..MPVJ>@cs"$ 7ThW>ͳXcC`j; ]֍ 4:4!;LSk3V C}?AgBZ0=272PT{ڒRy`E8vp)۴0~orR*yyh! x-doMBZ|dI&`Fl NF*2Z!85ޣn`DSLq؆B4 [/X)UPWsVΟZFu7,ŕC\ _p.uIRYcsǚ2!qJH&fSG+0]jE5}JaMǢ_T7YⲨ)نK?{hhTK‘罸% 5+|>(ZPQ&uE"MY> Fz1z:ɸu-'3l Oe1$97Tv/gr}~rufɿ`ZZo$IUX=IuxoI$G@'󮹋=1bW`%5+u^43 O>v_0Χ%v#̋*[/ zc#ⅸRkPK`X9fsetuptools/command/install.pyUT tIyIUxWoF~_1qMO}dUwJTrtB ,6Kws_ߙ;PcQ7J[0ܶU2[0~*Jj(IrULƲ[f /%J/pԇ{zZ3#fsjk?7\\\9p % GO+TU]+hfYţ-$Y?10W67B*ƵA\Kzƒ2VD+ ( 0ZQE s͙x_gqL^w*45cI]S:d ]:H22*W W[>05xU^y*sY!{i2.TrL@ˇ.tLfbϸxHX*֎W$%UaJ>dt Y:좔TdD#FPk3ϏO|N?='A^MBsiGG+eogn(1FI^y7EPb=}J/$L`G8krAW fsQv Ie֗|07Sh,m=.C4ȅ I.v^̊LTvP{)"L\Q~4(+VTΏyI{u56=EFLRR=BhPQbܖQ{am9f1vaW) ,|tq.p1Qmn57{I%^| cT#pmhj(BGP##A41 efRx'sT(Q׼4m755`y='Sbýs:k˜zT^u\šA 5h2Oô'>nKjYH[W}Rt2t3 QJKhEg*̱~ꞯ ڟE*li#IJ=[P?Cg|cTk8bT%mf&Jp_~ ǒu?C+@|? "]-0uPP[SQ(- 1@7ǒ_@y?/wti܄*.My귓b)4O ܨ[v38Va1R$|I4T *Yvx@y8A5"sʝOJV-%َa#@W%191ZBqtCB&~響h49(Dr8-hگ$?@7E8;- ? frĚ~rm۷Γ2TcgPKX9setuptools/command/install.pycUT IIUxW_oGl'NDICEk A+҇ibJW绵sܮ\KsLD~~vfJ qn=;3;ΎTM>_c~&',`$JكDz'>UAP߇uձ_U .¯*WC7 maml%.l<\[Klޡ_ʇt ކhjd9ȯ F!kt^m+sQ:U@ njqt hl1||wԄ8 6M6!nqsmvhGbQ],ҵTwF'TjXeQku,/Yp*~mfڒGb$MznUei]kx5Kcլt;^$i+ImЪI]5Y+q74\>_#A=^uϨt&Pc`1eF<߾;0.VDzۉ oKKq> Rlθl<[.T)]}ySȚj@Wc.qgx pvJ'ɶkLA0=$xMo7A"NrTνz+&ƊkH']ŭʇJ!pH嶽L D!M ETA8wAl[.U%GK;  h#VbB hH 25);cm31ie$T!$(v:%Ypl$.-`879E}Cۍ} .ScOMek</(9GvtQsF1_ef+Yfʘ4\\7_IgL"Ǣ1.70cȔ9Cn.ZcPza 5U,b˸8j@43֚+f1:_^Fv5/ k=>Ugtީr2$88Rr2&z'!H յJ33ukL8,!OyYWSw:|EeнcCj wouQk4q]E.5\B #AH38}y߁L:2DGtPK]X9N &setuptools/command/install_egg_info.pyUT tIyIUxWMo6WZZfK-Ћ7H$ARh7dYEͼyy3d*gehm0L5ָug"6zm͋lԻksXunX4^0)sқvE{8k)]>Jw OE,,Ձ(,q2d0?I8:R),Jz2axEzx<>!,.'3fQ":ǑY*V{YWCk:wR(lj+-rd)W-I&<)A>xdPfE_4e.~O:o$< HzjDK5e"Lf<:W{-B#OmFi~]1,Ml:f pެ֧Gj}5>jD=́؞یl>c.Iϓ|]a;o}n^#R ^yF\?Й+D+ C1`}L=^%W*b LyׯY9>xisY2@§ܕqb*f<`7)TmBU҅ HbV8/3f㷿/4) U3a6kYɺjinPm^MKԞZybM}XMrʭ$|%;82tgQk|pO n 6[щ=Sj9şvW~#6D5LaD'+9#Ɉ`%#p qK=>!.G RufQ$m 7ws+k3< w6lѩǽ{lI&'g/2<<&=үMj:Haj4\UNh* 6ȮȈt[9s|I*M̤Ҽ^˞J\r3`Eet̲Ծ7 Ie֬RtD/m8ڦQT5,<>&px4(, oq'Yc8;M|f_Ң6^9oѸ]{i2Nx>n,y 3RV9^ZzԗglWP+Ǐ*NxB(ZiefpPKX9˟r>'setuptools/command/install_egg_info.pycUT IIUxXo%x,%%4@ .8ikE^@1z@Pis=>tb_Z>(K-Y0*SBwqH FOI˴4YiKGJ~8< o^$Zjī&;ͤ^_o=4DXC&wp!=P1Z5, 6vA]S2 Lo56Ԯp\: h-.hW6\h~(ܹpxnZc!hw6e^sYN*ïQS65afk~.݄,Sɤ ?e%a`Ca.泰:_ԆcT% fF/d Zz0rEdNy]2k+ˋJԇ4_bit EמDZҵ7'/bz%6'c\WC뗫B(UjZ`wYj]W0 R]|(DeswEҞϷUg;߹D*}PA1FF{(1f-ЁmC-J:E0)r1n_l9-v5ͮ!|i@&elV&)V92nh6 >DY$fֽir⒁Q-*,a+4B[tAx>զFKcNA>1/Zp}gp&zզ!{]ay&IE;Q1͜bc &ҾeLTc2u~TSnb Hg>r&>F$2s=Z2nyb[Zyi||q?/s}C?#jFbZRQ?M4T?H$=uC_+",^X!aI~:45E lXzeꃅ!YB1]tE Nʄ>x {w"sLTCmK!>>;խ߹jR6Rm=[qǚwM˲Vrڲ1|6Vܡo@:Ys=f)Ⱦbf\bXz^vr AdPCkqx*S[zZPlAi{Tkn *&?CDm?}cF˂8- ^%(!b?{w`\ {PNbP dԣISk"^1Q(/ʁ6믿C̔(͖g/ %[hu㗩1pKd,Nrr uм% U`챑hBD{n=umjg(}|#.]mh|} !qEvO|V{M(=V}dBkJqV"䢠Vty P$CB탈CsǙ{R-87ޥP7bA<W2(\l[]Fș}ZXbfI8U?>i+~8bָmsM8-A2Z:{s2]ycc gۊuΗ͂уA cpu钡n]qʼx;؍_teH] ;XH`,+(@a´gvbx<_o^l+)Rzs?1&Q? k`ty6PKX9=ÿ "setuptools/command/install_lib.pycUT IIUxVmoT>qKlPu˴hʴibx) TMР\Io7]:O|os47R799dʿ:>῀!@"`Ak 5ةAT؂Ȇg': u%ZI'ro#=~F ! !@P3%MOlRI:b3v\>u6HG8lQ a&8`;FuLXwTt쫔uhv|Nq,K `Vi $t" sA-C*@LgjgHxITnj%by25{$xd!4O7.])6΃,32#q :Nl11qcobPE1okZz4oo$hc/P{w7`Cfvi@ SvN*)pm%7ʇ– Yg3AC^4A]r8xl*pWNӥ֖JcFlKdVqP#È]6'7 IfnЁąְxns wKYPa3(LqhT>)NȓD ªFћyj: .% #ŶjWRJqոWl=Y< nNwNtF6W#kȧA2 $+:FEF${t"C#m> [h*Ҭ1Il1U47 sS"US% 4K<|DZYNYiy/ckDK7A;=6pQ?vR1uXi.na"ӡP$q\h>p,cˆ\yC0]jErf[p/~5H`&E?+g=_UoPǣ%u׎ֱgOeV3ۋ.oM*Dp62#zV/wv] =ZTJ"6PYR`eB'HpXj3qc5[MymhmRFoA hpm䏟\k#!PK`X9olu%setuptools/command/install_scripts.pyUT tIyIUxUM0 WVY BB 7LviR)qڤ_Ml??ϞƚjInpRQQ.&'*wuA3%FAh-T Rtc58qRCܙzE2p&l<1as,'tN䀚e--VKbL 4WiRh_\/~6M'N(L14^ B_ۖg+m$NFN %`iz_e P #B{xB. Fw~/42OLL~E`@wN pC#-9p lH4c!"o߯Uo60z#Yۚ\6xWxn:YxɲjN?&RnQsnI4{Inu]YW>1Eu i=,3 l6!xȷgV%p's8 ȂM1b/S!sXutqL/AaLю7/ >.A|k^%#Yݫ/{Y!w'+j"x܌tqgfYޮl￁]Յ< \nnۿ?3ک9A09}ƘY쭕2uNJo޽}~ PKX9 C&/ &setuptools/command/install_scripts.pycUT IIUxV͎DoΏX -DhwJ , y+,,dta&(eȅgIxPUgFsfcWwWW}d8ygחx_q(+` $z` @ ! 9}H A 5s,ǐg;'Lp.\@ч?$L)/~=z,˴Nm^٩M,kiV/{rT|tefOu2%weE2Yu-B2w޼hb!,b ;܇AУ_ 0>Rh3 DWd6Q6M$TsYUɺ]is La|MߡH3[Vpݥ>u‰2MoaoT/25dg Ie`B)a}ltq<+U{GO'~ru87UVǷB96]'b"8>^.߿prYi`Lԓo\pآ!Q{C.=q\0´> >izEfM@k`N0:760\*M:RIUG4}aqg7۴^hXLdDCV-|{Dy AK|v~H-;Ӓ^Z!g/:#e-P};#"#ߢm!i=!Q[ hO7c^R5PkFDșȝN+ezNq0 }{`|E>XPG~G R$9) uBv. N16HU" r,7Gl|H>B-Pe';$t !|;>j8@ri-Zc )0^G4"].{m]!mZG|F:22Ѩ ֬U(@7Oe]Mh-d;bPK]X9(wsetuptools/command/register.pyUT tIyIUxEOI K=$J}B߀,0!~I`grL&C@7`StJ&@I; FӓlTR^.V58CiBWywr)?M.i>"U΁5(.i h%I-zVhU2ڑq*tU= $#28!J7 yU. 0C76%ҮqfK;Of`aǠ,V2U,3XWrxZq,mƞ1 y_Czb=tcz.* b5^hX:wSkPZyU'ᰭ/|,xFcla {ﮑL9e_:r!|1r/¾,3E}hRg (0:CS%Ko/,)ΓNnMi&%4K/ ^=y{g~_%!뿳[t$ؠMSB(fp(xu#$!z!%4 j]*/,.)݄A2jez`exY4OR.{ho7LJ9lZsF~^\Шĸ]f9Ӎ7T.:)}L.QMH-˹wƊӝ]bC)eeVSKf wPs4gGW/9Q$UN.K2hQ!=i|*?#s5.lWkPW: ˔yOEtz PKX9vGQ| setuptools/command/rotate.pycUT IIUxVKoEٷd@bρ(^"  hvwt/#;//_rwɳ;WWU+ a}-0蟎PAmp? 퇯oO+z7:|- ƽjLCڱX,e 2>Y6:tqgx5©K9( ŞsħɡFȔ bm+gYo-y XƽhB6kܲo* s:ަa4e:R1]F?2<.Lb*% 2e1! Ӳ4eTUTHY1Se.CAf%=vV(0ny;3:#إsˑ2dByݽ'RE H#+Bv"Vao8>]PlDx' qU#!2o"o.pY#- gq iLlqjqs3<5bFK<ΡV j) #=>[06XWS UV.L`sUqxJ 76. xHn n.Uc*S˹NMnUHxD1"MgS(!e;y(R:G"IPN+:)ŭw '| gO-JgxVuSwX]!i{݁)EGtu\k2 s7.td%vᄮ5]1h)4|^д qJ쐪b4ʁJ7w*3]%+H]fڢXByC4Fb j]o_Vu:gܱQ. Je|>$,&PK]X9Xdsetuptools/command/saveopts.pyUT tIyIUxeRAn0-=$"qz*`jl5( !Oxvv8Ha hGnRasһaz%7$sVcϢc@gۓ eD@⬸L+QHoJF1+RQq< MhPr"i-Hecw) o䕘56ԅr-ʚuƃ:w8>ⓊW7k(/ұ9#UA”squV ڤ%iyePKX9,h}|kq ,9_`8ȧƷ=R`hdI+$uYsM- Qc~_Kzp*L23ƣ0fIfd($>vZ:*Xbbau7,YM"2+淫3^EDd~b")L3v=ʽχb: = Ws9_ۨӖcgtm1Mm6#y*jLKC*o v urZZGV-zpiz}gu o}0 $4ayLMh;_U%;PK`X9 K setuptools/command/sdist.pyUT tIyIUxX[o6~`UPEinزEѥ@1tm/+0esIx!,z%xw.L՞֊d,3KD-̐ܽ-)H %oyvFבjʤD4MQ.Y, nȒ8zV41JR^ϿZhDkq(:l߸gQX/%H+)XY\:Ji2I:c&>H OySǁ!qDVKGhWB\˵#+c/JI..lީD-WZ5\^J4[Wi*+jexg1a6H`dA6ZM|L(Dl:b)A$*!qw@JG'īF-At <. #bjao3v G:'@C^?|1Ymى<jneIj^Xt 8B\_|܄b'x"W|I%$zJ &%A}2Xȑ-3M-lzՋ5@D< P9N 昦NDs~D'ϯK^sedQBg `P;N{_Y<˝iBG6 L3Z_dߜ_d/'tqس&6VBbOⓤr=Ci]8J^-uoe# ;-DC#9?N3t<8H|~NIr"Q`qJ~#߼$dy0IhWCӷ\_y!4̏>;}tp??)cpVf<`LM5G0O:"_\<{ z;݂QvdBn !.7ӏC窱7Dĝ% P(l97iQ:3gC chBGptysmtGq 4j5iX$g;VrWb3S" 0x,ZNv]@"Mk lw4 ǥcXU%߀ͷEЭ Qgy Ɣo6:ȋ=vKGj9: ^Nr.c t2끳ӑ_:&3Ŗ8r?= +|wv<G~_pBܙ9R:tpCB=( D}<~%z=dJӥn)SXd'S~y [V0 \+wi .?2!>}P^ Bu(¯o(I[̄Nl5jµVzc&9ufor + =(ZPW;]50!wV/>^ÿa D3!h钊CL\tǍםx#,L;K?<U-L[ej=QTOpvc\^j'˴NJAjft2Y\x 5O]/V:ch}qW&lPoYQmd~2*2);fQ,r(;V+!̕gj)1BBwfk DQ ʖVH%e˒Dq@LhQ(p]B)l|T.9ʧ\sH`IũJZ4A_wӪ=Qu)§R Ii %v+"ͪWnMDuYm͆('9oͦ9o͖ / ŗBl̟_ң?i g4 ON؜_%!<+KL|$[9c/<g,їz.o7%^`3uɠ"~r=mKAhi(*\ro領RuL B^(-j,KR#Cmd% qgURZ,`C!4Iyk] ۜ!07hi.{6Io<f<4l_݆IV^Form9޻`|I^*p% @4Fl<#{VWk)!+/kkaQ/s w<ÛXlC.>s9/"$Qำu]VAUU k2ČsP+D@qE\>yGl4cKكf֍]^e{>c%d(~?0'@A<2ď0fx37EO2P?-N,"DϋOȧfsZeKΈ:5}0r|Ɇv *oTcD93@` 9E&8Np{E[8JJT tz&0f L'p 5(B B-FR: d'+b *^Y=],x0m<.`y-| !Y7 T2zB R|dnJ5J<_CfX=H ;IR?]^E?VD9:`&DLX$mvAG.zC G]£V3lR v K1}t $? C%[PΫ C1d,G~QnLԭnjo:eX 毒7l*˜lс}gZr"(\R}cȦ]1#O\zlQ6$wuqA&AV/j*joDtδ!INpEXLQ)SJMeC-jh1'DM΂yh V٥7g'ΓCi>fo!!Oڄ۶(McddEvW^ѭ7b3o.d+eT7_c4)ҙrPb#5q~vC@_&xϒB*b]=5ti@aoG|8Yh96~bmy~toij)R\wB 5g`}S\-d Nfhsm~^.qK woP@"Q$*cu8 G|y `=֕;ErˠG]XppH"1K29{؟:IЖ6a*a-Fw0>pJ_UpQ)# Z6U\y-o{@ =}R)RL=,! l ^W*whE DGZpB"4"& {`mc;XDt0jIFlog)%>HT'k'p{.{cYDuFtGAL%SpUo2 J,l/^@fs.eiU`WiPL&}uO7*E I8[Ұ \ C*`-vM5`/ _7D2%"2͘'r3>aO8}w}%L07q a#S!WL4p{)usc_~ z=Z˩R@? 2WQ7rEI'^X˱1ptkTyWA|֝xjh} e瘓:JKK5/[ܰvtoð?[SkBʢ:Θ\ f6 i7Oaٕ#*# fF\Bg}a31lSšmDFIN:8'\onIV䬬T/Ȳ} TԸ@uKL&t~ҡh+]qk#twv瓻 } RWu}/8!]N2|{#>Kb:_˫B ʹgJ^DN&)}:#tDm1{#*+Y,4)]);J>kL.Ջ*,Eb^(ݎ9Z4I"b%{ {ZoLD9n2(P/>o<2tY3:y}J 0Gg7L\rp 2̓O'B+/fUJGcUڏ(cD'-c;E⺜\w/ Iu-*$3 `@Ey&a.8!?]WP NG@֭۬t՜`>;TKSS;.NX˜P b+_] ptL[<*羀CF7&"i7ؕ?8L&R|>vGĹp -< J[6+ZݜjۓͳVs)_=-OPK]X9R/setuptools/command/setopt.pyUT tIyIUxXݏ6篰N@K׫)I%Rp:^0nX@6f{g %=ߌS߉T\!jѝd]HµtmFV'&q&gE0G`Bt MS<$YCQ%^׮x{*.8 +cE~mu7]I8&ûDi$C|$B*4R9!m6;t:PdEIEglfClWi }'@ݐ$O0$(܃~!ond  ʴ;rȟ{,)د n *9:"Hg֖W (J\ 1w?FރrFA|U#-bdgav;+^1ƙvߠv;|+؅UdQX>o$SZ D*ְSځ FFᝏ|S #m8+P`rwo14 VxJM_@fWl?Zen$Tͱ.82|Nj=ݻ$`N2ͦIlG#mݥ;d#}^n S # Z-y}rJ8-;NCe6>[5]uI^#~%ȉU=|f0Źy0~]Wfx&gT;E끯Pp=/땺LUKGӂt"˒s =aI]YKpM,h;gts%$Q>Kkx$ܛQT6TJ[~/AKZah%BfsSaf5{\rIeoh[ES{}_s jf"=3P5dUfPY ѿ>}i洇#Qh',[@zP n<g_❞COB<=zJlw+N޲g%atmNZ)snhaRGw%zlblmxtϱmVj, :FތupK!)GѨ#GG/39I_:jgՒZ5]<|l-=/bjXk $[̔j~ږ/?}M/W>5鰤,kM Mڮ륽~]v]f%;dr}u}dyczjخ;n7@&}B_7*Hݢ.Ů#nIHK,حv㢪حvEįj"!eK-/AFM_BOv[Z{mca;݋?Jf5*$E 4iXϖA8 ¬o:0VYRueFP}X┕I∝X yC;Bf )BG䕒"*}13C7CHUn&e3iaj"cJqqOh'BMT|27;T.t#&BM0.ouF>~7*uM>{Ga칣}‰kG/of2,c2XJhw2 YF\av-p>q|,[_[+z|27J`knv2VjWywyV hŕI a efZYedM~4Q4I@lAuA.=*'alc͑?Hw7;?|oK [,I"50.e xs|sWXi˺lˆMYR.ѰɆ R HBKmKgeqJ]F Q>#,aBpZaD@uc;Ʒ%T40KkpvHUF1Xـ-]Ej毁ۚR~n,]1i/H I(:A]`i(N<7>uO~Y ##xr.nit0OOE+T.M>5{'5C6]0wXcQ"jVH*T ;>?h׮ރC?2h1YMƻobkŚ^^ cA3C.PuK?%7ѧ OY!!bٜ!bu\ݞ1)T5'}dE6 Ãm䆵"CI?ļ,3Oux+xR-fxgV7!ȶh_ʼݐmH4Nؽܠ(ڢH !0Gy _!)CGABQ>N L`u BdIjy@W)>94~{yN5@QzaN6 t0I^ R5BM8+x`d)..$1c-@I" ԁ?{E M"9Ⱦe2rVJ0lwaijfW=o{COe\1KGjؕ;2,?n6\$H$[ 6C , \b=PE =y ,+UBs)0mD8 UEϑ_.W؈YYWjQg72QoqA)Dg Uw9;C@OJtsy:QRNI%ſ {wA=GlC&7FI0AA2z˺a }:JDl}ywikpAUV)#-Im[FU2~2$GK",+"7o)ZƉ?]S07]\Õ91_o/ C /6!$qBE:(0`#λ?IQLO 3$aΙy|I5n~jȰ`,:$&5/PyW2E(( Tg# gol-%Weل5xl`a9W# &IHF-n1ull{)13ryb0hYQgFV+YkYbڹqzY0 cgذ=ּ#xZպK}c}SV<~_yDk_P}qEiVl=.+En-1U(צhuVD;yܚ Cノ*̸8GFn3+( o xPcvhzjloIěyk* KƩJ)PtFQ^!.fSL 4kڙ{#\iu"۶JՆS%d\ c[+js~lP=WfΦnTsZ]AJa-7?T:#'&jUwђ-ݬVW*ۚ'@KEg0YKˆiDU5Ae )U %-K"$GNK~;&dÊvSc:{A`a+PGX߳_VSuOVx),p,ҝn9ʝ9<(ݒp$*MNd'Nm(E%>dt-mֿ.ym2&(6Ŀ t">ⅷϡ*KlZn>XBDf'9t%LeW۷ӻ}9@ba'ܫ:{9wfU*[RhΠO1"=k[Jg}7MH|$?~[Z|VY!M NKÚB !0KD;pMte6Qv9vg) @1ix!*VwQQ383Hzoyr93,0whlyo˔ ]G0d<zcOU\T Lǹ0e`qj]2.Np!bߢ&y|9^ zTʂať䲃EVϭ3T_ 2cKd1`}`TK񙑻 =rWsLr!rl&kIƅ:pE,8`317FPt ql1q*F/TI ~((4 +e[۬ZïYA^$JAL__ri\ at&۾Ma/@9HFQ =g׻nB7Ў4$< C:]p:sTkktN*Ѧy$$SX(aFKXkvڗ̽lgx2DZyߘ䆄j. Ce*ysY$g|3i,aR |SSUŬe27I9NC1CS+T&IpΩ1T+waMњ椖D&Ne$l@ҟ%?gqRc꘾ RW:IIE(2f"|D6 i.dYAHPrjkYx_B:RHGa@A *w0Y]Oxoᕽ֣=Ƌb,G$kf&l@SA(6-ob=a/RIb$,jY\r5ͫ^W/V=,yXɰ=ȯ8rj aR^ZlzP$ᢆS׳2aTLGF֘{"d'w(.ߊ;ˮC ;"Zr[OeF e=ϵ~uWܞr8FtIa?^N&\ |cxR,/ ŶAG~UJd.7/o^i̘7UZ2$ɍ'n p Ol|C8hE`aZUks@]*sJX_vPIM0tQx H=ޜ5×";2i9bf$=uAvǵ>DG9悫r>QeWsUp)EM( %yV 32IZtrTFym, KpqA._ I Uf)"p5>Rn3^mp_"4aTb@/6DlVTn!|%$^w^|,"9g GHa 6wa&*zs3ҲNd'W]P5yv[b#uv*:. X}j?#6L*wI]ʪX|ؓwmU`%8uȂ'ӷ,qXf#KLoL! SD`jJVȴ\MsrO=`cҪTI6Y^.;)!dZWOdf<r8EpCUD970w{bG,5((wC!j:/@GT2W((}e5UpNtsܢ$D|p}S 6YtWߎy}Je|g@.o{!qѢm&;N\h<|\9o`l60r`}:46-T[1CweqƮCwp Sҝ:֏Z+<7_ ԧFsNiZ~ LO ߙ]Ѡ{|r?{"DNY0x"?b[5H6Q[`uLC;IFRgb 6!"!}v7|aЏN>Λ C,;;Uv{uK'J%K3^\ӓqȚc6I\47j됏 f+׃w PK`X9]zsetuptools/command/upload.pyUT tIIUxX[o8~jPjI~L63M$,amsےTSbCYV  <7Cz K-Fy,"Y<\ESiEwPKA*)Xm99^yF)i4q)sH\jc9%wY}Uј[KD|BgHvLvi|>_#^href.и=iaHgW0e:6b{ˤ.f|JH{-E!L7L)EI|b̎(3 ^ȘYwozpR4te/DX.\n7|%lkU 8$|*y+s_)NEI&$ߐ<|DɉZzd`vLrUf >oi =ٔIBaÿpI26C[UV3K6" VyT-] "znY͢b҈l/h gY۫.]7DdB O6!+c)Rx`E4mUwA^q rHJ픅] $NĦ''uşdBH5UwLb^JclfK֪ v;" ums싐P38|74Y`z;p>Z%<Ģ :Va_aʗQO~oeyEܧGx-E=2f,l=`vY\}E$Cչj= wx2 z aj.jOrԾ6). VBU9})vo' zYRBuL\zu@`;QUw4"y2hg\kz,:'#dХ9xhepRr#?^B"xueupš, "Y[4VLx` Bp3=sA+>v\_]_oo.CykcfY.击7?ߛNWbf7X5im 4݁C7G4tڐ,)́ D|­S0I<G 7*|\4 8̠{vL35qm]nG ^/.7>a~|drZׇD.n#,F)FIl Bf8i:{4$'&!NyHƟq'%tE* i쫪) #ݛw_S5^Ok)SbW.o:6Evg?gR&XFiB*v0鷞'_x.5ݿgadCf(ug>L#K:1h@I¤~%W hNJ(>| g~ \LXP>C 9 jkms}Ÿ>p\uIY^VY@;>:{՘nzo^._Ds:AS Fw, }&0@V^^io+EРNPKX9Ѻ2 setuptools/command/upload.pycUT IIUx]SGw%{lvةIlp-|ť[+fl^vǼOԽu U|zzzfzori6 +O lN48$(':x)@qN AmH$0ԆA;8/ ,hvr&,hSd _QB 硖O <.B%xj <IGIA1Y39w)>ۻBv뉕Fn[ sv9mǗǎˊbxQQ8#'V1d`<{{gU4#Ƒ[هWXpsu5< ݕLJx,Fq>r@2Ξl"q<#hmiuT)MJ[ڴ 6MjZgL+ T7ˮtCH\ }(zb~"|"OAx"EE'b.b9tgFE,1X}8VNdw_ܣݑ!VMJ?r~+Y g9*?bCX5/J1DP?pPg~s0ss7͉z>ᘦXwJ8`Z7#4"^NoT$aP5|t$x커x~7Y]^^-C>DIEZOItY4s௨Ox H5N8U8@wteW;üӸ*ZfpIAC?Cۀ*7iIͫXzgcAWxܳ.,.{5r^'yUdJ#\ǃ;_|Ƶ1l)W#14rQ⢣FT5z2謎1\#X8}pNc ~4.%ՒD٥GV3ܗEFQ WOr.݉b 3&ϊ%.($=Kvi>nl5g|y~p>=XßϓdqI,r{#WJ UAlmIsw_9A/::GmWJN[H`Ҏ/:ae&V(q-I;qBA Hu%]%LV-[Xt`??Xt)te*&h`+Kb*l՛6-ݟb}ToYK hUJTO.ߤrĤr@Yo"L1sE,=Kyq w4k9v& 8.鬇\9~#@/BAIn-u)m f}G7PK BY9setuptools/tests/UT L8I`8IUxPK`X9&nq O0setuptools/tests/__init__.pyUT tIIUxn:=_q(edAz{>@Kt,"ع9\$jcg_y(N&ό ,KDU9ߺn@ $‚em X%\;;4tMC z':~ct4AM+Q:I&rGo .uߑ"MɽrӘIn@R[!d+J)ΕJ:Y2]STTZ%[Lct5!Z K#?X?&.l:1sLxFx`8s-zH9M[?S(ޤ+HX>d3̉&A[ES8 U(OAMHpgxA.(r"]RפBũO[+cɾA>2Yp\V: o;| +9w Ra4S{bY*:X\4%KʿSȑ,J LX$ٰ79_cS/;o2 #w N֍ڵtY*i5h;p)E0aq_U$"M"*Pw*PeAz jkP^9Vuw ۛрcmե.)1Rbm; NGI5SR͏*S$~e tpj)N{++KxHP5$iSUj|\ b 01{?%+GW_o~wHt2,(K!CCH0tNѷ0%oe Qw[u܏_;*-LYyMZ|GX6/dof EgUA!ZR xƂ" Q:݊r`6:1̗Igв𽘱.aĿSt_[+l,^KTET]er0Ga;&KMqux%m`%._[x{Ի*{Ja|,TKGo c1~&=(L™NӠ'<)ϼ} 鞐=Fa~j]4`\xTۊCp:{Uc/jfd샙'@Yeڧk7 9?'.G!IQEN=-Ӫz.!<Yn7QV4/ v\&>8Zᒨ/_hY+\U5uQ_ޤluM Mh3 !f›Sy }Sx )67xuדCV'NEa|k6?5(@ۤ,;O}zaU= M&qz~wwA^A'$;IvQ7YV< Vբ ;.dp1(n ="#Q8~6KC"0Ź fR HJ"CѪ0M%lA5{]"L;q; !kIL$"6C &HZ¬B;?9qtv:~(+zQ%JA/Pxy52Ǐwыݖ8 b+> ؑT]Cv dZbcnLTA BosFTn׶W~?8Lyw8,qjӤ7dl38l)c٪_77 N@Sgs")u c2"wio6 q'`KZovwq۷]?è'~ڵQ嶽,_ ӻ%& 8qpwc\I')P.˪C;quOp~"XJ2ٍ`E9P,HuDJ$Sւis&a贵5vx -I-*^)D`|( (=R zq(< jbeulsa9U]Z]Rnn{ sK5]%7O<4%UQmnm`80KM6J e̴F܃tF„vot4{|-l*i{۩H=Ǖj11nKoX!^*/HV|B5r @ !>,4L|PU^VMAr"]kG F6Ҹ Y:`ي{3h{N+z![Fv[Tv 3`ߢE Y"χ v?_L AJA -\Q$cmJSCGL̲%'p`q?bQdY9Dql;3ٗ"xSn=%D)jręaHxc+0*`@, >J1XIkJQR*1U *H@%I h JeTcneL lu7I)"?qVPD#yЬ!&1v@ޜFxaCzO{9К@0!ZCYۧ-i"`s(h@1<[/ ^E$k⼀~ 6S̡8 uLc9Ĩ?jD[[T6qn}෶Ek6k=۷Iަ't݄EC7T[ێ-:&z\ -K=@ux${I:_rc\SOl':Q=anž/mqRt"4** C?UQ;M bc\vaۨ;lT42:hTu{'6J`Y3^*u>zfE+j=II'sia\0dV% \y#}wxB;(wkX!ڿMٷ0Vd4my]?_蠴z$8k|(?x#1cV?lٶ&yPTxZAEgu4Qb2뮐vkВ^ tvJ=TB#S RwN%cj_ȧ&tŬ6E((ܱYU 2Y9/,B>ohiA%ך;v01Eo7MȄ#کXvƁM6얩:7:!V'1rl:KT a @&u e''d1OS^<0CW82-KƲlZV6f攁A6eqJ? "ٵ0Ns!MJs;@)-9Dd6`c>>dfzXW#I&鄚i>W" q[^\>`cNsئr# !rA1a:86tARΒSGɝ;?}ɠ6沊,,+m&cn^Q^sj e2lB/Nl+Kw aZ Q{F#YkyQ} MNC e/|7X=?#^TLMXSG-}XMJӧ/3 |+%(BLϱF< hSC,n#FˣP@8HĝMFrˉPL &M+xsJ& yH,;mx\Oo;胱H"c}elhg oB!$޺RĮGtn$] \4f:9,,rf8Suc Θ?Ags%$zĭ |YG}o:$0*e.i9V"-áj5Ư2bK0#ȃ߾R_c){}=~Ї%̃͜+9H{,؏} _AS<߽R4.f4tLCdz{MΫďyB^"Frf7" R&~?bOXi/Xl$ďz%r(xK]ʤ?? #Y*kx-tda ňX7\.>Z}Oev= L^޲))>9l,M(*h6¬ # ^9]H,莿1n,(+7C8NWCy=jq bcc`l^ikivk=rd:W"]?rgMȕ.5A^tO| $*܃O仢ʅ"B,1Od3 tjfJ5yH["ue٭]^.tbF\e 2m O58.?@4.E%.>Reۍs PvNF:NEc5&if}_%؇Oe!sPKX9&}&setuptools/tests/test_packageindex.pycUT IIUxTK@Mr9*BiAOyh@+EJXH@ 9mp 07f+ 5Yr [LЉzMvXw6vȥ㑇4uX6c)jFIK,L*.T=.:(eU=z9ŲĴȑɈhrcJsQK]B|Wo2UUQ9&ZNvflv 3~Pڨd4K$UNP7;ޛto'C~4̀ZAwk=NG 'R [bCMCn)UWD_[ڳnvtO5ө+gѤ̤I4!C{b>g}!>9vCiX5ც>+o,|l>mH"&TL*dQiA,~ϭk< +)|st.u)YpаhefPK`X9aLQK"setuptools/tests/test_resources.pyUT tIIUxR po竓y0;3<۝#5w,!OحҜk:˒_IQEzE.XN(W圼e9 hN4}Ȓmao$ߙ<,& rX$!&d/6yĀD ؒA,a>[EK燔/?lu+XQ>/a$`)hVu{4>hjݧ3kG26؅j(P ]ga"* 0V#JB$)W0& H%g5 @m%Ź5MF4ZO%1xSqcD,eC#+ lLg`4$ɇ+s樐4piX?+dhce1e~;\vue~6Hw|ބDDTPTN"G[nBY0GLl Ĉ8ڑ(տWeLeb#[qh8zS4"#.6 * 3l:9ķg*T*18c45 %[}@gF`~dTn:겼/`N6׈+ >Ȳf y"icd"`]#Cj(hV%~qOJ3` , Qwd4">D*2&\MN "tiFSjW`sk+ vff &/l$ 1hA#E.bF!_\і0,!UCH;3k"0Z$Ѹ9dJ(hr. qdwSb~{jiaU1Cj9n: C1*Y 39dNcOoVΎpkRfehT[z *BPF:-p WDL;T֭G8<]p^5 >U<9aZLE"K_xVkTgcsqϒܿ 눖BG@R[:U8NUg:Ɇ(-Crn:~#T(M9ց *u)QȽU>j9o CL:'7$^yq~xSBZY_+f+bln 1'bja(nswv 8 'ñ;{6a">F , d }˸x\kCh sG**g&m-ϤɩL[/Ĵ`X*V%oVC4L-]Lw[h ۳ s]yh-v`-B,݋è HȂMJ0M?yoI,:˥QznoOM!uza <#7MϏǤ"v~U]eWw +HnbҴՉn''//ӘՒMҐ _ $rJgL[tUXi)5@Fy&͚ '4B =bnY0 "f YkI[<,6vMN.ڄuÜe}޽XYk<`JLE Q0RC\ؓhhJlՋEi&nr9S׆CDk3,sdf b۾kC?nC?F{E}N+J f, Z&ƬT.o]z] t%sUJmZy% 2rpfm_aL+6ga ?q6v*K6)d1;t^TAxvgerLc`@deL3@}2k~K'Wn s, 05i>,TtY8=H1el+Zj0TWkZ:>*P)#G9+k}DL3 /4vhi8L\Qe>5왘'<]қ$X> ?} 4<ѣY|Vh^1L(QkV7&I?2m׉fϩɏyǬ~d;۳Az{e:䔎WI0>G^==4?Vm9-Xa@G#rCAhGGкsTG$b3] nqW㠥BzT͚^[,8hPy:<&yn⹏g9VK6Z̄1cD@w$?d Йmi¬d[[' #cW~?"ブZbP >yM}_޿ow{U><qs ΆHxxJ.j8-84 Xp "5W^3ZOh 7'8/#kcf>P |׶3>v7> tҌOoV2 o=;IɳOfOp:z8~h-b׽.ﵴb[ͷLi20Ԗ(NĩlfMT[cNgl'1ىj ZD"12fGjLY#W}? ܏[Q݈Vל˃7ͽﶵu۬#Yv,0l}#"A;mkk3wZe 4%7n Ӣa ~q^oQYУfnEN ]2|3q1W@\|UD@`ނv[z2B Υ&eڽa o)b'fu}ё(]Q)_L۾ {vψ7>>$ 7EYim8֫!&k`dgK겹elTE#}_ e$r1E.!H3Q :Je)ꕤے%: aUiO366q <16kzO& xh#~mg=m5zBX+;rx0`rGܩ{ƾX|2_%^!EG W{q=~|:ПH>Wڳb;o(j V쑱mn$L df8hђQb1i.-P]2%zEDTj&67qrRd4(gM4:k<~g0P¤*^<"Kz۷ѰLR  +ڪv/hl1JJڰ8`[$MU2Qs!`\^x.~zɓE`l<fOJS^ʋ+Vś5hά%yDyPTHѹz֖ЍPW/N9~-ȓ!lӿ&xY/^!\#cVf9 eNc'JkQ MȧUȉM*ȫ^Al(i2|F8ɟH<|bY/tF' nQD*EͿ1b1XdofVntِ҈f.,FY5&bZ9L%\!L pX-h :Sq NjO)贆Eҗ,6HQ|݋mo+X ଅM!ZTx~Ѝ/E$wco,1= |/zawq i)LLNg5ܮoz\ۥnv[mFmoVݚhI wݪ#)h0طā%m4<H΃SK٠xa7:$nϯ# mގz|a!v;q݌ǰ2ֺAփ٣ja+k DlӤmc,>"aNSnAQ!ЋLE55Uϣyi&P)B_>ڣu[`K M [AN|#?x2y%j5\Z-.Ra6߮j.Ev"ݩ/r7xqrv ܺmX&&)L>5f(xANn'9 rd4fRFARHr% f/la}e?-hؑ<m@/0@@՜Y"aidJC9 yU6,SMƍ)መ3Sh2 h*A/ӏ/>>@f9-ۏ-ygYT!Si<ͧnOPW$P!:x<!#}ڎAs~$"H >bvDjlmNӋv$fE;[єWʋJo 0٫B8l-VY]j vxQtB(K+R qCE&K/fફKГBRfQmVLjvPE`T#:I0L F P$@lxa^D GA7 Lu#nu [h̐F]ZGaMz:zapnjzh}qMD j5iDTdfq>)Tu eCv  $ k: _8.:ǬUuf-̏YqN35!nF }Di eoH2$_S, HZ&ſ2uO Ai^9}q;6qi9=4i$6XWpbR. 1L8@fP]=FFцtQRM#ԅ6N L6L.a?MTvJ=ː8EQJM"Y$6 vpś"Z(Ew$Dk\RGi͢pqWwcM л^֣e%0FzǬWOCKqBnYi:4'T! ̇FܞRZ>@qͬljyWfsp0}S[3rĩLꈚ_X9e[*oΩVцsvT-"=諌3" YOiCc-._C'|GMKIJΒ(=Y`-0P↿%_j|j|95H;ڇ@04ݰI55J>`YUuu|I"椚 |ZEEIIebo7Z hT4iFWx^74@NW3}s"=ˤ2IZ _iR/<#yHF:0杈3qj?nD}1O ҇uPD D,r#9k5.S wQh.CLG%]8_)rboSswV_}Ͱx05($nOبd8@q[gd?4kj@8LHRfc>gW |)I e+&VE} 9A`V^A R :][johR=仂Vc*(*q(ЄՋn⡩[R}Ͷ3d]È\ÑEȧR9حRY@և!p5G$gX3!mlϭ 0-y( Geu3.i-I 5Avpp'|\稸e˜Ip(?#8 gl")hrQ& lq(o: Y3̠Hf&A#duna#QF=)̉P^Z,JQ;nJ*j)AFIs(=n׷@ CXAAwT.Rև2nMYO-~ǘb-ŌɌY/ܧИTM+ġ>kȁ[|vo:\d#"BoΜ>iCK~)-U%:vz[FdFhs Rc[ZVZl63z|8^s7tqd?hH+:8ׁqЅvD{t|$G ^R@oywCDĘExn73`M2mщٸJqՎ7nYvA-CMHe%VMc7H" @XP=7J~[AIbJ6II#C!uӠUhe=*gmPEoGMʎRR\%:.sE#m|0DvXѽz>趁 ˃MJ.5n Ӕ$X3b*Q6L$BP%lT8%"G-sN/_hǫkER5ox0p=*ob+؋J{kxd՚%E)&x1wS'5CLhs?D_TVL!_?k֫yk\+I^կ󻼭vyA*HGLu9\`E׳.{ORrgU}S'j*UX2폳g6gM!< cKǖ.TAv' byiٟCv5 12o~ ǿXE#D1d-6_;+aC~ŒS i=&Id1),}PG9}87`]&G}\Wy"ڲKjo9AWr(0omN&LAq9\l0%#u߀X˹R1`i3*t /lEcfceC0 җڶy5PgX{\4X ̊ץ-^?5s/ j+ z|Q/ܮcȢ4e!_VW߷0չ%RG^+˹Ƴ ^Z,PFFK4ϛq!F<^zT5תbk7I6J퍌y{_]}JmӖ~gitc(a/ #.t,ީ`qz6i1þqo }e{}$k5^sE!.9d|1F'gzk6הdzE$9jtOVd`ZI.)ZoY&o%BE|Pܝrt|߾ˈ;$Qk^̳*mVUfŀgUI$^j4A/@ _t諨`&?O_.HXd|a 6QVY2+e.idb[qM*N0Cd%۝x 7usUPy̾CAUڰ(` #MF_غ>4S:ɛR| *>ۼRX#s#b5Yzbk8L{; [ލ`+oYrS7@|I]uGR1k]}68 F^h5J`D;B݈PRuJ$)C6'j{#?SmUݪ^:HA 'czښ ʡai|ZRћ/8?󋍴{/t<GU- |-Pv 2ez2ʏu]B"kNJj,#oHYy iE|%*p5;`SRK/ .V+ A/dlht\Ic ,V, &#Čeo-qGZ?&YRwp\Q ="ɄNN N$+#7#Lyw WL|GTJRnwt`*H_^/Er4T4aE}Juji@S|ezY)b.:4܉oFw*~T̃?1=IrgF 75Hi'uaF'nT!g6%mU՗? W1,EVU}E?#ƫ26 GLH(٬Q8UOKjߢ47,} q΢c}n"9ڕ? W93?ZBxdBTd; sGaB .)rKyE`+'r٣`d#e˜>pֈdƭ{9AX/}jI^Ft o3&o,!]$ mT8U+O·oS|wUt7~I?uco̝yΌ>N^i gݒFa*BBI촥!7pr$vd;i' $ w<$ nHܹ3k;MBAjP]gy7zo9u-ìfP%z%2vWc8w&Z1/ږ^2&s-M9nI0^j5q'iTmA`r+&~iDr,J/ARe ?b0#9ݑ'--x *4>YYɊ+ \..S ~zgt-kO]V\WniVhLI.=hFbԆ$vSDXz_aITSiFOb>x (`kLb!Fj,X@N%Lw K3(7W4Vi-ЅGnȥA?8ㅈ o3acGk:N/nn]F~۵!*8څeu*5c,6%LC`YФr4CxްW(#!J{8-yPaha="M.bn!]o88o_Lk')8nF)#>~ţLR4/Bw"߭b5*IH]9ݍLd`x3$+ȅt73DDLVp *Ca:--/F"ƽ5 ^|E3Y'%bE|0)A)YOJ ^piխVX Ve˽^œ~}龛' =^ڡ'(c6i7BafReT7eN7>u{0 o=G>soX><|.DJ<$_`%%(%VG0?3߆uq~0a`.<nNVfr n%\o$VD_+- i4 c:  %!=3vTΪSFR*jQ}s7PK+Y9ôW setuptools/cli.exeUT DIDIUxY lSWB[XCC6#Ud$` e`cL۲Rqӫ늦VM4MW&n"Z45h0^p&@s{Ǻi4W:~{y޼<|1B8 E!0Q*s?5܍۽a[0ٚ=~ڶylm\tRoBVud`\LJ@0 O+MΪ1n?k[T᪏y NI9 )*ɝDC=/8grdd#QRNWz^5Τ9?wK/tk/E]\y^nIrT"5߇YWGh |R\9gōL  -Lc 4q@7qqˑ}F98U3jfCaUưjc|fRN_y3ڨ18q Z:w@rs>!C>V> s@ tnȚCT G9|eⲣRx&2~- r@ȷqaN"M91fǜrv;+;|2'Bn+H0޲Z^ij~7@x7$+a*6z3Ag1NĜL>Lc E|g*8"JcG }r@IJr$׹!;'z6' <*K#tGQd7fڥ/ ? Zϒ-chMao> U$ fq_jL]IA? 1b t#I2O=ßOFg7 46ծo pk>}J51=Yiۅa`VŒ% HL:6Jfzj5y] .*XN6| %Kgͯ \Niv&cM:6㊀8s1cH#I(FLЏ0i.';O'-Tӌ;%MB3zv'M)Y`>l+w?gZLUkz7z,'{74,~@֌í0O Fg(U¥"V(\!~ycps(iE+0`{rEIċ%&5Wxz` `H}aY3"ːE.e ["-,+S"ˊTVzw[~fa^:?CCs0pt{W⓱A_TKǮ`B?AMɚUڏdD{+)XYlv8bem-FafIlV˅3(6DZs}!ws7dJռNfljw1RlGr]VB"7IS8螞,T~LZ%bEbgՆX\VZaX$NuO58q.UǗs!"@k芫o/^:n' }@JQr-dcgyKuAq>K}t8ݧhZ#,3Dn)s\}hE0t]*! u=}b}ۆKr>q.po2x׋`v5'XȺg|>C}8(~,%; ^iZܟNGtN+NN.vlɏd::٦ɋtb]'-u4YVFyMnwEM`~/IǭNH~pyho9&c;L@=[}/e heFkl|c5i+a\3e {=>83hGO{ʏ;ht&W6pcd0`c0hŒBܲLXE^(%M`6Be,(#1vnG)Йzof}gղԛW/\frc$N#/ b_w@S?~CԐk.';{dRgC(kuKU0Y?Q$.w謩 W^^凗`/`At|I[4E Qfo :\MF~Q)o& 8=wo,*Rq?bQ'pk zΛ]Egg݂rſuSݓxﺊSʃ GyCC/!oƏ^enU#I)S\ŏ9nF D?2AHthP殿IZOMi߰rE]6l:R/a T85eQ+u p LwPo[YBe!LѸl98NE "Z ".Qd\O~}.v*zR؇Nmi Fύv?oemp ?g>#A|S^8/N4vF>+NHuO{D^$iE Q +b.F kY` f4x[5 ^K4Yk4QkSiN vM2(پuOh|$j埴. L5y}Vg;^pom9ϮjUF+*n& ڶ9c[ 8wfB^; }5:}c@]dB>@v '  oz @lߌZ![O_%n܃p'PLJ{۽Z=^';D*n7PS[KڼAe n^<˹=kоvş$H]ܥsz<\3١s}B+֞>RYoi@㚀\ q>ΏF:H{:Ȳ5]AO(YrVcW@m7-jo JɦlcނayXkL}Өpc뷲\ktm`T3Rk!ȕ5L,r|ZزQCPK]X9\OEi~ easy_install.pyUTtIUxPKX9v= easy_install.pycUTIUxPK BY9 EEGG-INFO/UTK8IUxPK X92 EGG-INFO/dependency_links.txtUT~IUxPKX9Wd  aEGG-INFO/entry_points.txtUT~IUxPKX9t # EGG-INFO/PKG-INFOUT~IUxPKX9ȧF pEGG-INFO/SOURCES.txtUT~IUxPK X90\&& EGG-INFO/top_level.txtUT~IUxPK ؕX92 lEGG-INFO/zip-safeUTzIUxPK`X9:VXaA pkg_resources.pyUTtIUxPKX9]r tW Jlpkg_resources.pycUTIUxPKBY9c);H _pkgutil.pyUTR8IUxPK BY9 Esetuptools/UTL8IUxPK]X95f<  setuptools/__init__.pyUTtIUxPKX9|[L setuptools/__init__.pycUTIUxPK`X9F bsetuptools/archive_util.pyUTtIUxPKX9X^t  setuptools/archive_util.pycUTIUxPK`X9? A setuptools/depends.pyUTtIUxPKX9ұI>  setuptools/depends.pycUTIUxPK`X9|I:vs ;*setuptools/dist.pyUTtIUxPKX9*)u Isetuptools/dist.pycUTIUxPK]X9<? tsetuptools/extension.pyUTtIUxPKX9A"A vsetuptools/extension.pycUTIUxPK`X9i4!l $zsetuptools/package_index.pyUTtIUxPKX9Q5h+j setuptools/package_index.pycUTIUxPK`X9 Xm ]setuptools/sandbox.pyUTtIUxPKX9@SW( setuptools/sandbox.pycUTIUxPK]X9@`  Rsetuptools/site-patch.pyUTtIUxPKX9/  setuptools/site-patch.pycUTIUxPK BY9 EOsetuptools/command/UTL8IUxPK]X9O?v7s setuptools/command/__init__.pyUTtIUxPKX9(MQ setuptools/command/__init__.pycUTIUxPK]X9_NL  `setuptools/command/alias.pyUTtIUxPKX9.uv  setuptools/command/alias.pycUTIUxPK`X9:E setuptools/command/bdist_egg.pyUTtIUxPKX9: qF { setuptools/command/bdist_egg.pycUTIUxPK]X9'Y6 ?)setuptools/command/bdist_rpm.pyUTtIUxPKX9}q  ,setuptools/command/bdist_rpm.pycUTIUxPK`X9OE # 0setuptools/command/bdist_wininst.pyUTtIUxPKX9%#?3$ D3setuptools/command/bdist_wininst.pycUTIUxPK`X9~3 , 6setuptools/command/build_ext.pyUTtIUxPKX9XLD( HCsetuptools/command/build_ext.pycUTIUxPK]X9{ }p Tsetuptools/command/build_py.pyUTtIUxPKX9Hx C ]setuptools/command/build_py.pycUTIUxPK`X96' Usetuptools/command/install_egg_info.pycUTIUxPK]X9H3g ! 8]setuptools/command/install_lib.pyUTtIUxPKX9=ÿ " `setuptools/command/install_lib.pycUTIUxPK`X9olu% gsetuptools/command/install_scripts.pyUTtIUxPKX9 C&/ & jsetuptools/command/install_scripts.pycUTIUxPK]X9(w osetuptools/command/register.pyUTtIUxPKX9!aO osetuptools/command/register.pycUTIUxPK]X9+z qsetuptools/command/rotate.pyUTtIUxPKX9vGQ|  tsetuptools/command/rotate.pycUTIUxPK]X9Xd rzsetuptools/command/saveopts.pyUTtIUxPKX9>sys.stderr, ( "md5 validation of %s failed! (Possible download problem?)" % egg_name ) sys.exit(2) return data def use_setuptools( version=DEFAULT_VERSION, download_base=DEFAULT_URL, to_dir=os.curdir, min_version="0.6c10dev", download_delay=15 ): """Automatically find/download setuptools and make it available on sys.path `version` should be a valid setuptools version number that is available as an egg for download under the `download_base` URL (which should end with a '/'). `to_dir` is the directory where setuptools will be downloaded, if it is not already available. If `download_delay` is specified, it is the number of seconds that will be paused before initiating a download, should one be required. If an older version of setuptools is installed but hasn't been imported yet, this routine will go ahead and install the required version and then use it. If an older version of setuptools has already been imported then we can't upgrade to the new one, so this routine will print a message to ``sys.stderr`` and raise SystemExit in an attempt to abort the calling script. """ if min_version is None: min_version = version was_imported = 'pkg_resources' in sys.modules or 'setuptools' in sys.modules def do_download(): egg = download_setuptools(version, download_base, to_dir, download_delay) sys.path.insert(0, egg) import setuptools; setuptools.bootstrap_install_from = egg try: import pkg_resources except ImportError: return do_download() try: pkg_resources.require("setuptools>="+min_version); return except pkg_resources.VersionConflict, e: if was_imported: print >>sys.stderr, ( "The required version of setuptools (>=%s) is not available, and\n" "can't be installed while this script is running. Please install\n" " a more recent version first, using 'easy_install -U setuptools'." "\n\n(Currently using %r)" ) % (min_version, e.args[0]) sys.exit(2) else: del pkg_resources, sys.modules['pkg_resources'] # reload ok return do_download() except pkg_resources.DistributionNotFound: return do_download() def download_setuptools( version=DEFAULT_VERSION, download_base=DEFAULT_URL, to_dir=os.curdir, delay = 15 ): """Download setuptools from a specified location and return its filename `version` should be a valid setuptools version number that is available as an egg for download under the `download_base` URL (which should end with a '/'). `to_dir` is the directory where the egg will be downloaded. `delay` is the number of seconds to pause before an actual download attempt. """ import urllib2, shutil egg_name = "setuptools-%s.egg" % (version,) url = download_base + egg_name saveto = os.path.join(to_dir, egg_name) src = dst = None if not os.path.exists(saveto): # Avoid repeated downloads try: from distutils import log if delay: log.warn(""" --------------------------------------------------------------------------- This script requires setuptools version %s to run (even to display help). I will attempt to download it for you (from %s), but you may need to enable firewall access for this script first. I will start the download in %d seconds. (Note: if this machine does not have network access, please obtain the file %s and place it in this directory before rerunning this script.) ---------------------------------------------------------------------------""", version, download_base, delay, url ); from time import sleep; sleep(delay) log.warn("Downloading %s", url) src = urllib2.urlopen(url) # Read/write all in one block, so we don't create a corrupt file # if the download is interrupted. data = _validate_md5(egg_name, src.read()) dst = open(saveto,"wb"); dst.write(data) finally: if src: src.close() if dst: dst.close() return os.path.realpath(saveto) def main(argv, version=DEFAULT_VERSION): """Install or upgrade setuptools and EasyInstall""" try: import setuptools except ImportError: egg = None try: egg = download_setuptools(version, delay=0) sys.path.insert(0,egg) from setuptools.command.easy_install import main return main(list(argv)+[egg]) # we're done here finally: if egg and os.path.exists(egg): os.unlink(egg) else: if setuptools.__version__ == '0.0.1': print >>sys.stderr, ( "You have an obsolete version of setuptools installed. Please\n" "remove it from your system entirely before rerunning this script." ) sys.exit(2) req = "setuptools>="+version import pkg_resources try: pkg_resources.require(req) except pkg_resources.VersionConflict: try: from setuptools.command.easy_install import main except ImportError: from easy_install import main main(list(argv)+[download_setuptools(delay=0)]) sys.exit(0) # try to force an exit else: if argv: from setuptools.command.easy_install import main main(argv) else: print "Setuptools version",version,"or greater has been installed." print '(Run "ez_setup.py -U setuptools" to reinstall or upgrade.)' def update_md5(filenames): """Update our built-in md5 registry""" import re from md5 import md5 for name in filenames: base = os.path.basename(name) f = open(name,'rb') md5_data[base] = md5(f.read()).hexdigest() f.close() data = [" %r: %r,\n" % it for it in md5_data.items()] data.sort() repl = "".join(data) import inspect srcfile = inspect.getsourcefile(sys.modules[__name__]) f = open(srcfile, 'rb'); src = f.read(); f.close() match = re.search("\nmd5_data = {\n([^}]+)}", src) if not match: print >>sys.stderr, "Internal error!" sys.exit(2) src = src[:match.start(1)] + repl + src[match.end(1):] f = open(srcfile,'w') f.write(src) f.close() if __name__=='__main__': if len(sys.argv)>2 and sys.argv[1]=='--md5update': update_md5(sys.argv[2:]) else: main(sys.argv[1:]) zfec-1.4.5/Setup.lhs0000664000175100017510000000011411216211330013332 0ustar zookozooko#!/usr/bin/env runhaskell > import Distribution.Simple > main = defaultMain zfec-1.4.5/stridetune-dat.bash0000664000175100017510000000034411216211330015322 0ustar zookozooko#!/bin/bash DAT=stridetune.dat rm -f $DAT for F in benchresults/comp_0-stride_*; do NUM=${F:27} for M in `grep "^N: " benchresults/comp_0-stride_$NUM | cut -d':' -f10-` ; do echo "$NUM $M" >> $DAT done done zfec-1.4.5/setup.cfg0000664000175100017510000000064411216213552013363 0ustar zookozooko[easy_install] zip_ok = False [egg_info] tag_build = tag_date = 0 tag_svn_revision = 0 [aliases] sdist_dsc = darcsver --count-all-patches sdist_dsc sdist = darcsver --count-all-patches sdist trial = darcsver --count-all-patches trial build = darcsver --count-all-patches build install = darcsver --count-all-patches install test = darcsver --count-all-patches test bdist_egg = darcsver --count-all-patches bdist_egg zfec-1.4.5/COPYING.GPL0000664000175100017510000004351111216211330013206 0ustar zookozookoThis licence also comes with the added permission that you may link this program with the OpenSSL library and distribute executables, as long as you follow the requirements of this licence in regard to all of the software in the executable aside from OpenSSL. GNU GENERAL PUBLIC LICENSE Version 2, June 1991 Copyright (C) 1989, 1991 Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA Everyone is permitted to copy and distribute verbatim copies of this license document, but changing it is not allowed. Preamble The licenses for most software are designed to take away your freedom to share and change it. By contrast, the GNU General Public License is intended to guarantee your freedom to share and change free software--to make sure the software is free for all its users. This General Public License applies to most of the Free Software Foundation's software and to any other program whose authors commit to using it. (Some other Free Software Foundation software is covered by the GNU Lesser General Public License instead.) You can apply it to your programs, too. When we speak of free software, we are referring to freedom, not price. Our General Public Licenses are designed to make sure that you have the freedom to distribute copies of free software (and charge for this service if you wish), that you receive source code or can get it if you want it, that you can change the software or use pieces of it in new free programs; and that you know you can do these things. To protect your rights, we need to make restrictions that forbid anyone to deny you these rights or to ask you to surrender the rights. These restrictions translate to certain responsibilities for you if you distribute copies of the software, or if you modify it. For example, if you distribute copies of such a program, whether gratis or for a fee, you must give the recipients all the rights that you have. You must make sure that they, too, receive or can get the source code. And you must show them these terms so they know their rights. We protect your rights with two steps: (1) copyright the software, and (2) offer you this license which gives you legal permission to copy, distribute and/or modify the software. Also, for each author's protection and ours, we want to make certain that everyone understands that there is no warranty for this free software. If the software is modified by someone else and passed on, we want its recipients to know that what they have is not the original, so that any problems introduced by others will not reflect on the original authors' reputations. Finally, any free program is threatened constantly by software patents. We wish to avoid the danger that redistributors of a free program will individually obtain patent licenses, in effect making the program proprietary. To prevent this, we have made it clear that any patent must be licensed for everyone's free use or not licensed at all. The precise terms and conditions for copying, distribution and modification follow. GNU GENERAL PUBLIC LICENSE TERMS AND CONDITIONS FOR COPYING, DISTRIBUTION AND MODIFICATION 0. This License applies to any program or other work which contains a notice placed by the copyright holder saying it may be distributed under the terms of this General Public License. The "Program", below, refers to any such program or work, and a "work based on the Program" means either the Program or any derivative work under copyright law: that is to say, a work containing the Program or a portion of it, either verbatim or with modifications and/or translated into another language. (Hereinafter, translation is included without limitation in the term "modification".) Each licensee is addressed as "you". Activities other than copying, distribution and modification are not covered by this License; they are outside its scope. The act of running the Program is not restricted, and the output from the Program is covered only if its contents constitute a work based on the Program (independent of having been made by running the Program). Whether that is true depends on what the Program does. 1. You may copy and distribute verbatim copies of the Program's source code as you receive it, in any medium, provided that you conspicuously and appropriately publish on each copy an appropriate copyright notice and disclaimer of warranty; keep intact all the notices that refer to this License and to the absence of any warranty; and give any other recipients of the Program a copy of this License along with the Program. You may charge a fee for the physical act of transferring a copy, and you may at your option offer warranty protection in exchange for a fee. 2. You may modify your copy or copies of the Program or any portion of it, thus forming a work based on the Program, and copy and distribute such modifications or work under the terms of Section 1 above, provided that you also meet all of these conditions: a) You must cause the modified files to carry prominent notices stating that you changed the files and the date of any change. b) You must cause any work that you distribute or publish, that in whole or in part contains or is derived from the Program or any part thereof, to be licensed as a whole at no charge to all third parties under the terms of this License. c) If the modified program normally reads commands interactively when run, you must cause it, when started running for such interactive use in the most ordinary way, to print or display an announcement including an appropriate copyright notice and a notice that there is no warranty (or else, saying that you provide a warranty) and that users may redistribute the program under these conditions, and telling the user how to view a copy of this License. (Exception: if the Program itself is interactive but does not normally print such an announcement, your work based on the Program is not required to print an announcement.) These requirements apply to the modified work as a whole. If identifiable sections of that work are not derived from the Program, and can be reasonably considered independent and separate works in themselves, then this License, and its terms, do not apply to those sections when you distribute them as separate works. But when you distribute the same sections as part of a whole which is a work based on the Program, the distribution of the whole must be on the terms of this License, whose permissions for other licensees extend to the entire whole, and thus to each and every part regardless of who wrote it. Thus, it is not the intent of this section to claim rights or contest your rights to work written entirely by you; rather, the intent is to exercise the right to control the distribution of derivative or collective works based on the Program. In addition, mere aggregation of another work not based on the Program with the Program (or with a work based on the Program) on a volume of a storage or distribution medium does not bring the other work under the scope of this License. 3. You may copy and distribute the Program (or a work based on it, under Section 2) in object code or executable form under the terms of Sections 1 and 2 above provided that you also do one of the following: a) Accompany it with the complete corresponding machine-readable source code, which must be distributed under the terms of Sections 1 and 2 above on a medium customarily used for software interchange; or, b) Accompany it with a written offer, valid for at least three years, to give any third party, for a charge no more than your cost of physically performing source distribution, a complete machine-readable copy of the corresponding source code, to be distributed under the terms of Sections 1 and 2 above on a medium customarily used for software interchange; or, c) Accompany it with the information you received as to the offer to distribute corresponding source code. (This alternative is allowed only for noncommercial distribution and only if you received the program in object code or executable form with such an offer, in accord with Subsection b above.) The source code for a work means the preferred form of the work for making modifications to it. For an executable work, complete source code means all the source code for all modules it contains, plus any associated interface definition files, plus the scripts used to control compilation and installation of the executable. However, as a special exception, the source code distributed need not include anything that is normally distributed (in either source or binary form) with the major components (compiler, kernel, and so on) of the operating system on which the executable runs, unless that component itself accompanies the executable. If distribution of executable or object code is made by offering access to copy from a designated place, then offering equivalent access to copy the source code from the same place counts as distribution of the source code, even though third parties are not compelled to copy the source along with the object code. 4. You may not copy, modify, sublicense, or distribute the Program except as expressly provided under this License. Any attempt otherwise to copy, modify, sublicense or distribute the Program is void, and will automatically terminate your rights under this License. However, parties who have received copies, or rights, from you under this License will not have their licenses terminated so long as such parties remain in full compliance. 5. You are not required to accept this License, since you have not signed it. However, nothing else grants you permission to modify or distribute the Program or its derivative works. These actions are prohibited by law if you do not accept this License. Therefore, by modifying or distributing the Program (or any work based on the Program), you indicate your acceptance of this License to do so, and all its terms and conditions for copying, distributing or modifying the Program or works based on it. 6. Each time you redistribute the Program (or any work based on the Program), the recipient automatically receives a license from the original licensor to copy, distribute or modify the Program subject to these terms and conditions. You may not impose any further restrictions on the recipients' exercise of the rights granted herein. You are not responsible for enforcing compliance by third parties to this License. 7. If, as a consequence of a court judgment or allegation of patent infringement or for any other reason (not limited to patent issues), conditions are imposed on you (whether by court order, agreement or otherwise) that contradict the conditions of this License, they do not excuse you from the conditions of this License. If you cannot distribute so as to satisfy simultaneously your obligations under this License and any other pertinent obligations, then as a consequence you may not distribute the Program at all. For example, if a patent license would not permit royalty-free redistribution of the Program by all those who receive copies directly or indirectly through you, then the only way you could satisfy both it and this License would be to refrain entirely from distribution of the Program. If any portion of this section is held invalid or unenforceable under any particular circumstance, the balance of the section is intended to apply and the section as a whole is intended to apply in other circumstances. It is not the purpose of this section to induce you to infringe any patents or other property right claims or to contest validity of any such claims; this section has the sole purpose of protecting the integrity of the free software distribution system, which is implemented by public license practices. Many people have made generous contributions to the wide range of software distributed through that system in reliance on consistent application of that system; it is up to the author/donor to decide if he or she is willing to distribute software through any other system and a licensee cannot impose that choice. This section is intended to make thoroughly clear what is believed to be a consequence of the rest of this License. 8. If the distribution and/or use of the Program is restricted in certain countries either by patents or by copyrighted interfaces, the original copyright holder who places the Program under this License may add an explicit geographical distribution limitation excluding those countries, so that distribution is permitted only in or among countries not thus excluded. In such case, this License incorporates the limitation as if written in the body of this License. 9. The Free Software Foundation may publish revised and/or new versions of the General Public License from time to time. Such new versions will be similar in spirit to the present version, but may differ in detail to address new problems or concerns. Each version is given a distinguishing version number. If the Program specifies a version number of this License which applies to it and "any later version", you have the option of following the terms and conditions either of that version or of any later version published by the Free Software Foundation. If the Program does not specify a version number of this License, you may choose any version ever published by the Free Software Foundation. 10. If you wish to incorporate parts of the Program into other free programs whose distribution conditions are different, write to the author to ask for permission. For software which is copyrighted by the Free Software Foundation, write to the Free Software Foundation; we sometimes make exceptions for this. Our decision will be guided by the two goals of preserving the free status of all derivatives of our free software and of promoting the sharing and reuse of software generally. NO WARRANTY 11. BECAUSE THE PROGRAM IS LICENSED FREE OF CHARGE, THERE IS NO WARRANTY FOR THE PROGRAM, TO THE EXTENT PERMITTED BY APPLICABLE LAW. EXCEPT WHEN OTHERWISE STATED IN WRITING THE COPYRIGHT HOLDERS AND/OR OTHER PARTIES PROVIDE THE PROGRAM "AS IS" WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESSED OR IMPLIED, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE. THE ENTIRE RISK AS TO THE QUALITY AND PERFORMANCE OF THE PROGRAM IS WITH YOU. SHOULD THE PROGRAM PROVE DEFECTIVE, YOU ASSUME THE COST OF ALL NECESSARY SERVICING, REPAIR OR CORRECTION. 12. IN NO EVENT UNLESS REQUIRED BY APPLICABLE LAW OR AGREED TO IN WRITING WILL ANY COPYRIGHT HOLDER, OR ANY OTHER PARTY WHO MAY MODIFY AND/OR REDISTRIBUTE THE PROGRAM AS PERMITTED ABOVE, BE LIABLE TO YOU FOR DAMAGES, INCLUDING ANY GENERAL, SPECIAL, INCIDENTAL OR CONSEQUENTIAL DAMAGES ARISING OUT OF THE USE OR INABILITY TO USE THE PROGRAM (INCLUDING BUT NOT LIMITED TO LOSS OF DATA OR DATA BEING RENDERED INACCURATE OR LOSSES SUSTAINED BY YOU OR THIRD PARTIES OR A FAILURE OF THE PROGRAM TO OPERATE WITH ANY OTHER PROGRAMS), EVEN IF SUCH HOLDER OR OTHER PARTY HAS BEEN ADVISED OF THE POSSIBILITY OF SUCH DAMAGES. END OF TERMS AND CONDITIONS How to Apply These Terms to Your New Programs If you develop a new program, and you want it to be of the greatest possible use to the public, the best way to achieve this is to make it free software which everyone can redistribute and change under these terms. To do so, attach the following notices to the program. It is safest to attach them to the start of each source file to most effectively convey the exclusion of warranty; and each file should have at least the "copyright" line and a pointer to where the full notice is found. Copyright (C) This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA. Also add information on how to contact you by electronic and paper mail. If the program is interactive, make it output a short notice like this when it starts in an interactive mode: Gnomovision version 69, Copyright (C) year name of author Gnomovision comes with ABSOLUTELY NO WARRANTY; for details type `show w'. This is free software, and you are welcome to redistribute it under certain conditions; type `show c' for details. The hypothetical commands `show w' and `show c' should show the appropriate parts of the General Public License. Of course, the commands you use may be called something other than `show w' and `show c'; they could even be mouse-clicks or menu items--whatever suits your program. You should also get your employer (if you work as a programmer) or your school, if any, to sign a "copyright disclaimer" for the program, if necessary. Here is a sample; alter the names: Yoyodyne, Inc., hereby disclaims all copyright interest in the program `Gnomovision' (which makes passes at compilers) written by James Hacker. , 1 April 1989 Ty Coon, President of Vice This General Public License does not permit incorporating your program into proprietary programs. If your program is a subroutine library, you may consider it more useful to permit linking proprietary applications with the library. If this is what you want to do, use the GNU Lesser General Public License instead of this License. zfec-1.4.5/TODO0000664000175100017510000000110311216211330012211 0ustar zookozooko * INSTALL doc * catch EnvironmentError when writing sharefiles and clean up * try Duff's device in _addmul1()? * memory usage analysis * What Every Programmer Should Know About Memory by Ulrich Drepper * test handling of filesystem exceptional conditions (tricky) * Jerasure ** try multiplication without a lookup table? (to save cache pressure) * conditional compilation to handle a printf that doesn't understand %Zu * try malloc() instead of alloca() (more portable, possibly better for keeping stacks aligned?) * announce on lwn, p2p-hackers * streaming mode zfec-1.4.5/stridetune-bench.py0000664000175100017510000000221111216211330015337 0ustar zookozooko#!/usr/bin/env python import bisect, random, os, re from pyutil import fileutil assert not os.path.exists("benchresults") os.mkdir("benchresults") MIN=512 MAX=1024 results = {} R=re.compile("ave rate: ([1-9][0-9]*)") def measure(stride): fileutil.rm_dir("build") fileutil.rm_dir("instdir") fileutil.remove_if_possible(os.path.join("zfec", "_fec.so")) fileutil.make_dirs("instdir") fname = os.path.join("benchresults", "comp_0-stride_%d"%stride) os.system("PYTHONPATH=instdir ./setup.py develop --install-dir=instdir --stride=%d >/dev/null" % stride) os.system("PYTHONPATH=instdir python -OO ./bench/bench_zfec.py >> %s" % fname) inf = open(fname, "rU") for l in inf: m = R.search(l) if m: result = int(m.group(1)) if results.has_key(stride): print "stride: %d, results: %d (dup %d)" % (stride, result, results[stride]) else: print "stride: %d, results: %d" % (stride, result) results[stride] = result break measure(MIN) measure(MAX) while True: stride = random.randrange(MIN, MAX+1) measure(stride) zfec-1.4.5/stridetune-graph.py0000664000175100017510000000032411216211330015364 0ustar zookozooko#!/usr/bin/env python from pyx import * def g(f): g=graph.graphxy(width=16, x=graph.axis.linear(), y=graph.axis.linear()) g.plot([graph.data.file(f, x=1, y=2)]) g.writeEPSfile(f+'.eps') g('stridetune.dat') zfec-1.4.5/stridetune-bench.ba.sh0000664000175100017510000000073711216211330015715 0ustar zookozooko#!/bin/bash /bin/rm -rf ./benchresults mkdir benchresults STRIDE=32 while [ $(( $STRIDE < 32769 )) ] ; do /bin/rm -rf build rm zfec/_fec.so /bin/rm -rf instdir mkdir instdir PYTHONPATH=instdir ./setup.py develop --install-dir=instdir --stride=${STRIDE} >/dev/null echo $STRIDE PYTHONPATH=instdir python -OO ./bench/bench_zfec.py >> benchresults/comp_0-stride_$STRIDE tail -1 benchresults/comp_0-stride_$STRIDE STRIDE=$(( $STRIDE + 32 )) done zfec-1.4.5/zfec/0000775000175100017510000000000011216213552012465 5ustar zookozookozfec-1.4.5/zfec/fec.c0000664000175100017510000004365611216211367013406 0ustar zookozooko/** * zfec -- fast forward error correction library with Python interface */ #include "fec.h" #include #include #include #include /* * Primitive polynomials - see Lin & Costello, Appendix A, * and Lee & Messerschmitt, p. 453. */ static const char*const Pp="101110001"; /* * To speed up computations, we have tables for logarithm, exponent and * inverse of a number. We use a table for multiplication as well (it takes * 64K, no big deal even on a PDA, especially because it can be * pre-initialized an put into a ROM!), otherwhise we use a table of * logarithms. In any case the macro gf_mul(x,y) takes care of * multiplications. */ static gf gf_exp[510]; /* index->poly form conversion table */ static int gf_log[256]; /* Poly->index form conversion table */ static gf inverse[256]; /* inverse of field elem. */ /* inv[\alpha**i]=\alpha**(GF_SIZE-i-1) */ /* * modnn(x) computes x % GF_SIZE, where GF_SIZE is 2**GF_BITS - 1, * without a slow divide. */ static gf modnn(int x) { while (x >= 255) { x -= 255; x = (x >> 8) + (x & 255); } return x; } #define SWAP(a,b,t) {t tmp; tmp=a; a=b; b=tmp;} /* * gf_mul(x,y) multiplies two numbers. It is much faster to use a * multiplication table. * * USE_GF_MULC, GF_MULC0(c) and GF_ADDMULC(x) can be used when multiplying * many numbers by the same constant. In this case the first call sets the * constant, and others perform the multiplications. A value related to the * multiplication is held in a local variable declared with USE_GF_MULC . See * usage in _addmul1(). */ static gf gf_mul_table[256][256]; #define gf_mul(x,y) gf_mul_table[x][y] #define USE_GF_MULC register gf * __gf_mulc_ #define GF_MULC0(c) __gf_mulc_ = gf_mul_table[c] #define GF_ADDMULC(dst, x) dst ^= __gf_mulc_[x] /* * Generate GF(2**m) from the irreducible polynomial p(X) in p[0]..p[m] * Lookup tables: * index->polynomial form gf_exp[] contains j= \alpha^i; * polynomial form -> index form gf_log[ j = \alpha^i ] = i * \alpha=x is the primitive element of GF(2^m) * * For efficiency, gf_exp[] has size 2*GF_SIZE, so that a simple * multiplication of two numbers can be resolved without calling modnn */ static void _init_mul_table(void) { int i, j; for (i = 0; i < 256; i++) for (j = 0; j < 256; j++) gf_mul_table[i][j] = gf_exp[modnn (gf_log[i] + gf_log[j])]; for (j = 0; j < 256; j++) gf_mul_table[0][j] = gf_mul_table[j][0] = 0; } #define NEW_GF_MATRIX(rows, cols) \ (gf*)malloc(rows * cols) /* * initialize the data structures used for computations in GF. */ static void generate_gf (void) { int i; gf mask; mask = 1; /* x ** 0 = 1 */ gf_exp[8] = 0; /* will be updated at the end of the 1st loop */ /* * first, generate the (polynomial representation of) powers of \alpha, * which are stored in gf_exp[i] = \alpha ** i . * At the same time build gf_log[gf_exp[i]] = i . * The first 8 powers are simply bits shifted to the left. */ for (i = 0; i < 8; i++, mask <<= 1) { gf_exp[i] = mask; gf_log[gf_exp[i]] = i; /* * If Pp[i] == 1 then \alpha ** i occurs in poly-repr * gf_exp[8] = \alpha ** 8 */ if (Pp[i] == '1') gf_exp[8] ^= mask; } /* * now gf_exp[8] = \alpha ** 8 is complete, so can also * compute its inverse. */ gf_log[gf_exp[8]] = 8; /* * Poly-repr of \alpha ** (i+1) is given by poly-repr of * \alpha ** i shifted left one-bit and accounting for any * \alpha ** 8 term that may occur when poly-repr of * \alpha ** i is shifted. */ mask = 1 << 7; for (i = 9; i < 255; i++) { if (gf_exp[i - 1] >= mask) gf_exp[i] = gf_exp[8] ^ ((gf_exp[i - 1] ^ mask) << 1); else gf_exp[i] = gf_exp[i - 1] << 1; gf_log[gf_exp[i]] = i; } /* * log(0) is not defined, so use a special value */ gf_log[0] = 255; /* set the extended gf_exp values for fast multiply */ for (i = 0; i < 255; i++) gf_exp[i + 255] = gf_exp[i]; /* * again special cases. 0 has no inverse. This used to * be initialized to 255, but it should make no difference * since noone is supposed to read from here. */ inverse[0] = 0; inverse[1] = 1; for (i = 2; i <= 255; i++) inverse[i] = gf_exp[255 - gf_log[i]]; } /* * Various linear algebra operations that i use often. */ /* * addmul() computes dst[] = dst[] + c * src[] * This is used often, so better optimize it! Currently the loop is * unrolled 16 times, a good value for 486 and pentium-class machines. * The case c=0 is also optimized, whereas c=1 is not. These * calls are unfrequent in my typical apps so I did not bother. */ #define addmul(dst, src, c, sz) \ if (c != 0) _addmul1(dst, src, c, sz) #define UNROLL 16 /* 1, 4, 8, 16 */ static void _addmul1(register gf*restrict dst, const register gf*restrict src, gf c, size_t sz) { USE_GF_MULC; const gf* lim = &dst[sz - UNROLL + 1]; GF_MULC0 (c); #if (UNROLL > 1) /* unrolling by 8/16 is quite effective on the pentium */ for (; dst < lim; dst += UNROLL, src += UNROLL) { GF_ADDMULC (dst[0], src[0]); GF_ADDMULC (dst[1], src[1]); GF_ADDMULC (dst[2], src[2]); GF_ADDMULC (dst[3], src[3]); #if (UNROLL > 4) GF_ADDMULC (dst[4], src[4]); GF_ADDMULC (dst[5], src[5]); GF_ADDMULC (dst[6], src[6]); GF_ADDMULC (dst[7], src[7]); #endif #if (UNROLL > 8) GF_ADDMULC (dst[8], src[8]); GF_ADDMULC (dst[9], src[9]); GF_ADDMULC (dst[10], src[10]); GF_ADDMULC (dst[11], src[11]); GF_ADDMULC (dst[12], src[12]); GF_ADDMULC (dst[13], src[13]); GF_ADDMULC (dst[14], src[14]); GF_ADDMULC (dst[15], src[15]); #endif } #endif lim += UNROLL - 1; for (; dst < lim; dst++, src++) /* final components */ GF_ADDMULC (*dst, *src); } /* * computes C = AB where A is n*k, B is k*m, C is n*m */ static void _matmul(gf * a, gf * b, gf * c, unsigned n, unsigned k, unsigned m) { unsigned row, col, i; for (row = 0; row < n; row++) { for (col = 0; col < m; col++) { gf *pa = &a[row * k]; gf *pb = &b[col]; gf acc = 0; for (i = 0; i < k; i++, pa++, pb += m) acc ^= gf_mul (*pa, *pb); c[row * m + col] = acc; } } } /* * _invert_mat() takes a matrix and produces its inverse * k is the size of the matrix. * (Gauss-Jordan, adapted from Numerical Recipes in C) * Return non-zero if singular. */ static void _invert_mat(gf* src, unsigned k) { gf c, *p; unsigned irow = 0; unsigned icol = 0; unsigned row, col, i, ix; unsigned* indxc = (unsigned*) malloc (k * sizeof(unsigned)); unsigned* indxr = (unsigned*) malloc (k * sizeof(unsigned)); unsigned* ipiv = (unsigned*) malloc (k * sizeof(unsigned)); gf *id_row = NEW_GF_MATRIX (1, k); memset (id_row, '\0', k * sizeof (gf)); /* * ipiv marks elements already used as pivots. */ for (i = 0; i < k; i++) ipiv[i] = 0; for (col = 0; col < k; col++) { gf *pivot_row; /* * Zeroing column 'col', look for a non-zero element. * First try on the diagonal, if it fails, look elsewhere. */ if (ipiv[col] != 1 && src[col * k + col] != 0) { irow = col; icol = col; goto found_piv; } for (row = 0; row < k; row++) { if (ipiv[row] != 1) { for (ix = 0; ix < k; ix++) { if (ipiv[ix] == 0) { if (src[row * k + ix] != 0) { irow = row; icol = ix; goto found_piv; } } else assert (ipiv[ix] <= 1); } } } found_piv: ++(ipiv[icol]); /* * swap rows irow and icol, so afterwards the diagonal * element will be correct. Rarely done, not worth * optimizing. */ if (irow != icol) for (ix = 0; ix < k; ix++) SWAP (src[irow * k + ix], src[icol * k + ix], gf); indxr[col] = irow; indxc[col] = icol; pivot_row = &src[icol * k]; c = pivot_row[icol]; assert (c != 0); if (c != 1) { /* otherwhise this is a NOP */ /* * this is done often , but optimizing is not so * fruitful, at least in the obvious ways (unrolling) */ c = inverse[c]; pivot_row[icol] = 1; for (ix = 0; ix < k; ix++) pivot_row[ix] = gf_mul (c, pivot_row[ix]); } /* * from all rows, remove multiples of the selected row * to zero the relevant entry (in fact, the entry is not zero * because we know it must be zero). * (Here, if we know that the pivot_row is the identity, * we can optimize the addmul). */ id_row[icol] = 1; if (memcmp (pivot_row, id_row, k * sizeof (gf)) != 0) { for (p = src, ix = 0; ix < k; ix++, p += k) { if (ix != icol) { c = p[icol]; p[icol] = 0; addmul (p, pivot_row, c, k); } } } id_row[icol] = 0; } /* done all columns */ for (col = k; col > 0; col--) if (indxr[col-1] != indxc[col-1]) for (row = 0; row < k; row++) SWAP (src[row * k + indxr[col-1]], src[row * k + indxc[col-1]], gf); } /* * fast code for inverting a vandermonde matrix. * * NOTE: It assumes that the matrix is not singular and _IS_ a vandermonde * matrix. Only uses the second column of the matrix, containing the p_i's. * * Algorithm borrowed from "Numerical recipes in C" -- sec.2.8, but largely * revised for my purposes. * p = coefficients of the matrix (p_i) * q = values of the polynomial (known) */ void _invert_vdm (gf* src, unsigned k) { unsigned i, j, row, col; gf *b, *c, *p; gf t, xx; if (k == 1) /* degenerate case, matrix must be p^0 = 1 */ return; /* * c holds the coefficient of P(x) = Prod (x - p_i), i=0..k-1 * b holds the coefficient for the matrix inversion */ c = NEW_GF_MATRIX (1, k); b = NEW_GF_MATRIX (1, k); p = NEW_GF_MATRIX (1, k); for (j = 1, i = 0; i < k; i++, j += k) { c[i] = 0; p[i] = src[j]; /* p[i] */ } /* * construct coeffs. recursively. We know c[k] = 1 (implicit) * and start P_0 = x - p_0, then at each stage multiply by * x - p_i generating P_i = x P_{i-1} - p_i P_{i-1} * After k steps we are done. */ c[k - 1] = p[0]; /* really -p(0), but x = -x in GF(2^m) */ for (i = 1; i < k; i++) { gf p_i = p[i]; /* see above comment */ for (j = k - 1 - (i - 1); j < k - 1; j++) c[j] ^= gf_mul (p_i, c[j + 1]); c[k - 1] ^= p_i; } for (row = 0; row < k; row++) { /* * synthetic division etc. */ xx = p[row]; t = 1; b[k - 1] = 1; /* this is in fact c[k] */ for (i = k - 1; i > 0; i--) { b[i-1] = c[i] ^ gf_mul (xx, b[i]); t = gf_mul (xx, t) ^ b[i-1]; } for (col = 0; col < k; col++) src[col * k + row] = gf_mul (inverse[t], b[col]); } free (c); free (b); free (p); return; } static int fec_initialized = 0; static void init_fec (void) { generate_gf(); _init_mul_table(); fec_initialized = 1; } /* * This section contains the proper FEC encoding/decoding routines. * The encoding matrix is computed starting with a Vandermonde matrix, * and then transforming it into a systematic matrix. */ #define FEC_MAGIC 0xFECC0DEC void fec_free (fec_t *p) { assert (p != NULL && p->magic == (((FEC_MAGIC ^ p->k) ^ p->n) ^ (unsigned long) (p->enc_matrix))); free (p->enc_matrix); free (p); } fec_t * fec_new(unsigned short k, unsigned short n) { unsigned row, col; gf *p, *tmp_m; fec_t *retval; if (fec_initialized == 0) init_fec (); retval = (fec_t *) malloc (sizeof (fec_t)); retval->k = k; retval->n = n; retval->enc_matrix = NEW_GF_MATRIX (n, k); retval->magic = ((FEC_MAGIC ^ k) ^ n) ^ (unsigned long) (retval->enc_matrix); tmp_m = NEW_GF_MATRIX (n, k); /* * fill the matrix with powers of field elements, starting from 0. * The first row is special, cannot be computed with exp. table. */ tmp_m[0] = 1; for (col = 1; col < k; col++) tmp_m[col] = 0; for (p = tmp_m + k, row = 0; row < n - 1; row++, p += k) for (col = 0; col < k; col++) p[col] = gf_exp[modnn (row * col)]; /* * quick code to build systematic matrix: invert the top * k*k vandermonde matrix, multiply right the bottom n-k rows * by the inverse, and construct the identity matrix at the top. */ _invert_vdm (tmp_m, k); /* much faster than _invert_mat */ _matmul(tmp_m + k * k, tmp_m, retval->enc_matrix + k * k, n - k, k, k); /* * the upper matrix is I so do not bother with a slow multiply */ memset (retval->enc_matrix, '\0', k * k * sizeof (gf)); for (p = retval->enc_matrix, col = 0; col < k; col++, p += k + 1) *p = 1; free (tmp_m); return retval; } /* To make sure that we stay within cache in the inner loops of fec_encode(). (It would probably help to also do this for fec_decode(). */ #ifndef STRIDE #define STRIDE 8192 #endif void fec_encode(const fec_t* code, const gf*restrict const*restrict const src, gf*restrict const*restrict const fecs, const unsigned*restrict const block_nums, size_t num_block_nums, size_t sz) { unsigned char i, j; size_t k; unsigned fecnum; const gf* p; for (k = 0; k < sz; k += STRIDE) { size_t stride = ((sz-k) < STRIDE)?(sz-k):STRIDE; for (i=0; i= code->k); memset(fecs[i]+k, 0, stride); p = &(code->enc_matrix[fecnum * code->k]); for (j = 0; j < code->k; j++) addmul(fecs[i]+k, src[j]+k, p[j], stride); } } } /** * Build decode matrix into some memory space. * * @param matrix a space allocated for a k by k matrix */ void build_decode_matrix_into_space(const fec_t*restrict const code, const unsigned*const restrict index, const unsigned k, gf*restrict const matrix) { unsigned char i; gf* p; for (i=0, p=matrix; i < k; i++, p += k) { if (index[i] < k) { memset(p, 0, k); p[i] = 1; } else { memcpy(p, &(code->enc_matrix[index[i] * code->k]), k); } } _invert_mat (matrix, k); } void fec_decode(const fec_t* code, const gf*restrict const*restrict const inpkts, gf*restrict const*restrict const outpkts, const unsigned*restrict const index, size_t sz) { gf* m_dec = (gf*)alloca(code->k * code->k); unsigned char outix=0; unsigned char row=0; unsigned char col=0; build_decode_matrix_into_space(code, index, code->k, m_dec); for (row=0; rowk; row++) { assert ((index[row] >= code->k) || (index[row] == row)); /* If the block whose number is i is present, then it is required to be in the i'th element. */ if (index[row] >= code->k) { memset(outpkts[outix], 0, sz); for (col=0; col < code->k; col++) addmul(outpkts[outix], inpkts[col], m_dec[row * code->k + col], sz); outix++; } } } /** * zfec -- fast forward error correction library with Python interface * * Copyright (C) 2007 Allmydata, Inc. * Author: Zooko Wilcox-O'Hearn * * This file is part of zfec. * * See README.txt for licensing information. */ /* * This work is derived from the "fec" software by Luigi Rizzo, et al., the * copyright notice and licence terms of which are included below for reference. * fec.c -- forward error correction based on Vandermonde matrices 980624 (C) * 1997-98 Luigi Rizzo (luigi@iet.unipi.it) * * Portions derived from code by Phil Karn (karn@ka9q.ampr.org), * Robert Morelos-Zaragoza (robert@spectra.eng.hawaii.edu) and Hari * Thirumoorthy (harit@spectra.eng.hawaii.edu), Aug 1995 * * Modifications by Dan Rubenstein (see Modifications.txt for * their description. * Modifications (C) 1998 Dan Rubenstein (drubenst@cs.umass.edu) * * Redistribution and use in source and binary forms, with or without * modification, are permitted provided that the following conditions * are met: * * 1. Redistributions of source code must retain the above copyright * notice, this list of conditions and the following disclaimer. * 2. Redistributions in binary form must reproduce the above * copyright notice, this list of conditions and the following * disclaimer in the documentation and/or other materials * provided with the distribution. * * THIS SOFTWARE IS PROVIDED BY THE AUTHORS ``AS IS'' AND * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, * THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A * PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHORS * BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, * OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, * PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, * OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY * THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR * TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT * OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY * OF SUCH DAMAGE. */ zfec-1.4.5/zfec/cmdline_zunfec.py0000664000175100017510000000456411216211330016025 0ustar zookozooko#!/usr/bin/env python # zfec -- a fast C implementation of Reed-Solomon erasure coding with # command-line, C, and Python interfaces import os, sys import argparse import filefec from zfec import __version__ as libversion __version__ = libversion def main(): if '-V' in sys.argv or '--version' in sys.argv: print "zfec library version: ", libversion print "zunfec command-line tool version: ", __version__ return 0 parser = argparse.ArgumentParser(description="Decode data from share files.") parser.add_argument('-o', '--outputfile', required=True, help='file to write the resulting data to, or "-" for stdout', type=str, metavar='OUTF') parser.add_argument('sharefiles', nargs='*', help='shares file to read the encoded data from', type=unicode, metavar='SHAREFILE') parser.add_argument('-v', '--verbose', help='print out messages about progress', action='store_true') parser.add_argument('-f', '--force', help='overwrite any file which already in place of the output file', action='store_true') parser.add_argument('-V', '--version', help='print out version number and exit', action='store_true') args = parser.parse_args() if len(args.sharefiles) < 2: print "At least two sharefiles are required." return 1 if args.force: outf = open(args.outputfile, 'wb') else: try: flags = os.O_WRONLY|os.O_CREAT|os.O_EXCL | (hasattr(os, 'O_BINARY') and os.O_BINARY) outfd = os.open(args.outputfile, flags) except OSError: print "There is already a file named %r -- aborting. Use --force to overwrite." % (args.outputfile,) return 2 outf = os.fdopen(outfd, "wb") sharefs = [] # This sort() actually matters for performance (shares with numbers < k # are much faster to use than the others), as well as being important for # reproducibility. args.sharefiles.sort() for fn in args.sharefiles: sharefs.append(open(fn, 'rb')) try: ret = filefec.decode_from_files(outf, sharefs, args.verbose) except filefec.InsufficientShareFilesError, e: print str(e) return 3 return 0 # zfec -- fast forward error correction library with Python interface # # Copyright (C) 2007 Allmydata, Inc. # Author: Zooko Wilcox-O'Hearn # # This file is part of zfec. # # See README.txt for licensing information. zfec-1.4.5/zfec/filefec.py0000664000175100017510000004312211216211367014440 0ustar zookozookoimport easyfec, zfec from pyutil import fileutil from pyutil.mathutil import pad_size, log_ceil import array, os, struct CHUNKSIZE = 4096 from base64 import b32encode def ab(x): # debuggery if len(x) >= 3: return "%s:%s" % (len(x), b32encode(x[-3:]),) elif len(x) == 2: return "%s:%s" % (len(x), b32encode(x[-2:]),) elif len(x) == 1: return "%s:%s" % (len(x), b32encode(x[-1:]),) elif len(x) == 0: return "%s:%s" % (len(x), "--empty--",) class InsufficientShareFilesError(zfec.Error): def __init__(self, k, kb, *args, **kwargs): zfec.Error.__init__(self, *args, **kwargs) self.k = k self.kb = kb def __repr__(self): return "Insufficient share files -- %d share files are required to recover this file, but only %d were given" % (self.k, self.kb,) def __str__(self): return self.__repr__() class CorruptedShareFilesError(zfec.Error): pass def _build_header(m, k, pad, sh): """ @param m: the total number of shares; 1 <= m <= 256 @param k: the number of shares required to reconstruct; 1 <= k <= m @param pad: the number of bytes of padding added to the file before encoding; 0 <= pad < k @param sh: the shnum of this share; 0 <= k < m @return: a compressed string encoding m, k, pad, and sh """ assert m >= 1 assert m <= 2**8 assert k >= 1 assert k <= m assert pad >= 0 assert pad < k assert sh >= 0 assert sh < m bitsused = 0 val = 0 val |= (m - 1) bitsused += 8 # the first 8 bits always encode m kbits = log_ceil(m, 2) # num bits needed to store all possible values of k val <<= kbits bitsused += kbits val |= (k - 1) padbits = log_ceil(k, 2) # num bits needed to store all possible values of pad val <<= padbits bitsused += padbits val |= pad shnumbits = log_ceil(m, 2) # num bits needed to store all possible values of shnum val <<= shnumbits bitsused += shnumbits val |= sh assert bitsused >= 8, bitsused assert bitsused <= 32, bitsused if bitsused <= 16: val <<= (16-bitsused) cs = struct.pack('>H', val) assert cs[:-2] == '\x00' * (len(cs)-2) return cs[-2:] if bitsused <= 24: val <<= (24-bitsused) cs = struct.pack('>I', val) assert cs[:-3] == '\x00' * (len(cs)-3) return cs[-3:] else: val <<= (32-bitsused) cs = struct.pack('>I', val) assert cs[:-4] == '\x00' * (len(cs)-4) return cs[-4:] def MASK(bits): return (1<> b2_bits_left) + 1 shbits = log_ceil(m, 2) # num bits needed to store all possible values of shnum padbits = log_ceil(k, 2) # num bits needed to store all possible values of pad val = byte & (~kbitmask) needed_padbits = padbits - b2_bits_left if needed_padbits > 0: ch = inf.read(1) if not ch: raise CorruptedShareFilesError("Share files were corrupted -- share file %r didn't have a complete metadata header at the front. Perhaps the file was truncated." % (inf.name,)) byte = struct.unpack(">B", ch)[0] val <<= 8 val |= byte needed_padbits -= 8 assert needed_padbits <= 0 extrabits = -needed_padbits pad = val >> extrabits val &= MASK(extrabits) needed_shbits = shbits - extrabits if needed_shbits > 0: ch = inf.read(1) if not ch: raise CorruptedShareFilesError("Share files were corrupted -- share file %r didn't have a complete metadata header at the front. Perhaps the file was truncated." % (inf.name,)) byte = struct.unpack(">B", ch)[0] val <<= 8 val |= byte needed_shbits -= 8 assert needed_shbits <= 0 gotshbits = -needed_shbits sh = val >> gotshbits return (m, k, pad, sh,) FORMAT_FORMAT = "%%s.%%0%dd_%%0%dd%%s" RE_FORMAT = "%s.[0-9]+_[0-9]+%s" def encode_to_files(inf, fsize, dirname, prefix, k, m, suffix=".fec", overwrite=False, verbose=False): """ Encode inf, writing the shares to specially named, newly created files. @param fsize: calling read() on inf must yield fsize bytes of data and then raise an EOFError @param dirname: the name of the directory into which the sharefiles will be written """ mlen = len(str(m)) format = FORMAT_FORMAT % (mlen, mlen,) padbytes = pad_size(fsize, k) fns = [] fs = [] try: for shnum in range(m): hdr = _build_header(m, k, padbytes, shnum) fn = os.path.join(dirname, format % (prefix, shnum, m, suffix,)) if verbose: print "Creating share file %r..." % (fn,) if overwrite: f = open(fn, "wb") else: flags = os.O_WRONLY|os.O_CREAT|os.O_EXCL | (hasattr(os, 'O_BINARY') and os.O_BINARY) fd = os.open(fn, flags) f = os.fdopen(fd, "wb") f.write(hdr) fs.append(f) fns.append(fn) sumlen = [0] def cb(blocks, length): assert len(blocks) == len(fs) oldsumlen = sumlen[0] sumlen[0] += length if verbose: if int((float(oldsumlen) / fsize) * 10) != int((float(sumlen[0]) / fsize) * 10): print str(int((float(sumlen[0]) / fsize) * 10) * 10) + "% ...", if sumlen[0] > fsize: raise IOError("Wrong file size -- possibly the size of the file changed during encoding. Original size: %d, observed size at least: %s" % (fsize, sumlen[0],)) for i in range(len(blocks)): data = blocks[i] fs[i].write(data) length -= len(data) encode_file_stringy_easyfec(inf, cb, k, m, chunksize=4096) except EnvironmentError, le: print "Cannot complete because of exception: " print le print "Cleaning up..." # clean up while fs: f = fs.pop() f.close() ; del f fn = fns.pop() if verbose: print "Cleaning up: trying to remove %r..." % (fn,) fileutil.remove_if_possible(fn) return 1 if verbose: print print "Done!" return 0 # Note: if you really prefer base-2 and you change this code, then please # denote 2^20 as "MiB" instead of "MB" in order to avoid ambiguity. See: # http://en.wikipedia.org/wiki/Megabyte # Thanks. MILLION_BYTES=10**6 def decode_from_files(outf, infiles, verbose=False): """ Decode from the first k files in infiles, writing the results to outf. """ assert len(infiles) >= 2 infs = [] shnums = [] m = None k = None padlen = None byteswritten = 0 for f in infiles: (nm, nk, npadlen, shnum,) = _parse_header(f) if not (m is None or m == nm): raise CorruptedShareFilesError("Share files were corrupted -- share file %r said that m was %s but another share file previously said that m was %s" % (f.name, nm, m,)) m = nm if not (k is None or k == nk): raise CorruptedShareFilesError("Share files were corrupted -- share file %r said that k was %s but another share file previously said that k was %s" % (f.name, nk, k,)) if k > len(infiles): raise InsufficientShareFilesError(k, len(infiles)) k = nk if not (padlen is None or padlen == npadlen): raise CorruptedShareFilesError("Share files were corrupted -- share file %r said that pad length was %s but another share file previously said that pad length was %s" % (f.name, npadlen, padlen,)) padlen = npadlen infs.append(f) shnums.append(shnum) if len(infs) == k: break dec = easyfec.Decoder(k, m) while True: chunks = [ inf.read(CHUNKSIZE) for inf in infs ] if [ch for ch in chunks if len(ch) != len(chunks[-1])]: raise CorruptedShareFilesError("Share files were corrupted -- all share files are required to be the same length, but they weren't.") if len(chunks[-1]) == CHUNKSIZE: # Then this was a full read, so we're still in the sharefiles. resultdata = dec.decode(chunks, shnums, padlen=0) outf.write(resultdata) byteswritten += len(resultdata) if verbose: if ((byteswritten - len(resultdata)) / (10*MILLION_BYTES)) != (byteswritten / (10*MILLION_BYTES)): print str(byteswritten / MILLION_BYTES) + " MB ...", else: # Then this was a short read, so we've reached the end of the sharefiles. resultdata = dec.decode(chunks, shnums, padlen) outf.write(resultdata) return # Done. if verbose: print print "Done!" def encode_file(inf, cb, k, m, chunksize=4096): """ Read in the contents of inf, encode, and call cb with the results. First, k "input blocks" will be read from inf, each input block being of size chunksize. Then these k blocks will be encoded into m "result blocks". Then cb will be invoked, passing a list of the m result blocks as its first argument, and the length of the encoded data as its second argument. (The length of the encoded data is always equal to k*chunksize, until the last iteration, when the end of the file has been reached and less than k*chunksize bytes could be read from the file.) This procedure is iterated until the end of the file is reached, in which case the space of the input blocks that is unused is filled with zeroes before encoding. Note that the sequence passed in calls to cb() contains mutable array objects in its first k elements whose contents will be overwritten when the next segment is read from the input file. Therefore the implementation of cb() has to either be finished with those first k arrays before returning, or if it wants to keep the contents of those arrays for subsequent use after it has returned then it must make a copy of them to keep. @param inf the file object from which to read the data @param cb the callback to be invoked with the results @param k the number of shares required to reconstruct the file @param m the total number of shares created @param chunksize how much data to read from inf for each of the k input blocks """ enc = zfec.Encoder(k, m) l = tuple([ array.array('c') for i in range(k) ]) indatasize = k*chunksize # will be reset to shorter upon EOF eof = False ZEROES=array.array('c', ['\x00'])*chunksize while not eof: # This loop body executes once per segment. i = 0 while (i #include #include #if (PY_VERSION_HEX < 0x02050000) typedef int Py_ssize_t; #endif #include "fec.h" #include "stdarg.h" static PyObject *py_fec_error; static char fec__doc__[] = "\ FEC - Forward Error Correction \n\ "; static char Encoder__doc__[] = "\ Hold static encoder state (an in-memory table for matrix multiplication), and k and m parameters, and provide {encode()} method.\n\n\ @param k: the number of packets required for reconstruction \n\ @param m: the number of packets generated \n\ "; typedef struct { PyObject_HEAD /* expose these */ unsigned short kk; unsigned short mm; /* internal */ fec_t* fec_matrix; } Encoder; static PyObject * Encoder_new(PyTypeObject *type, PyObject *args, PyObject *kwdict) { Encoder *self; self = (Encoder*)type->tp_alloc(type, 0); if (self != NULL) { self->kk = 0; self->mm = 0; self->fec_matrix = NULL; } return (PyObject *)self; } static int Encoder_init(Encoder *self, PyObject *args, PyObject *kwdict) { static char *kwlist[] = { "k", "m", NULL }; int ink, inm; if (!PyArg_ParseTupleAndKeywords(args, kwdict, "ii:Encoder.__init__", kwlist, &ink, &inm)) return -1; if (ink < 1) { PyErr_Format(py_fec_error, "Precondition violation: first argument is required to be greater than or equal to 1, but it was %d", ink); return -1; } if (inm < 1) { PyErr_Format(py_fec_error, "Precondition violation: second argument is required to be greater than or equal to 1, but it was %d", inm); return -1; } if (inm > 256) { PyErr_Format(py_fec_error, "Precondition violation: second argument is required to be less than or equal to 256, but it was %d", inm); return -1; } if (ink > inm) { PyErr_Format(py_fec_error, "Precondition violation: first argument is required to be less than or equal to the second argument, but they were %d and %d respectively", ink, inm); return -1; } self->kk = (unsigned short)ink; self->mm = (unsigned short)inm; self->fec_matrix = fec_new(self->kk, self->mm); return 0; } static char Encoder_encode__doc__[] = "\ Encode data into m packets.\n\ \n\ @param inblocks: a sequence of k buffers of data to encode -- these are the k primary blocks, i.e. the input data split into k pieces (for best performance, make it a tuple instead of a list); All blocks are required to be the same length.\n\ @param desired_blocks_nums optional sequence of blocknums indicating which blocks to produce and return; If None, all m blocks will be returned (in order). (For best performance, make it a tuple instead of a list.)\n\ @returns: a list of buffers containing the requested blocks; Note that if any of the input blocks were 'primary blocks', i.e. their blocknum was < k, then the result sequence will contain a Python reference to the same Python object as was passed in. As long as the Python object in question is immutable (i.e. a string) then you don't have to think about this detail, but if it is mutable (i.e. an array), then you have to be aware that if you subsequently mutate the contents of that object then that will also change the contents of the sequence that was returned from this call to encode().\n\ "; static PyObject * Encoder_encode(Encoder *self, PyObject *args) { PyObject* inblocks; PyObject* desired_blocks_nums = NULL; /* The blocknums of the blocks that should be returned. */ PyObject* result = NULL; gf** check_blocks_produced = (gf**)alloca((self->mm - self->kk) * sizeof(PyObject*)); /* This is an upper bound -- we will actually use only num_check_blocks_produced of these elements (see below). */ PyObject** pystrs_produced = (PyObject**)alloca((self->mm - self->kk) * sizeof(PyObject*)); /* This is an upper bound -- we will actually use only num_check_blocks_produced of these elements (see below). */ unsigned num_check_blocks_produced = 0; /* The first num_check_blocks_produced elements of the check_blocks_produced array and of the pystrs_produced array will be used. */ const gf** incblocks = (const gf**)alloca(self->kk * sizeof(const gf*)); unsigned num_desired_blocks; PyObject* fast_desired_blocks_nums = NULL; PyObject** fast_desired_blocks_nums_items; unsigned* c_desired_blocks_nums = (unsigned*)alloca(self->mm * sizeof(unsigned)); unsigned* c_desired_checkblocks_ids = (unsigned*)alloca((self->mm - self->kk) * sizeof(unsigned)); unsigned i; PyObject* fastinblocks = NULL; PyObject** fastinblocksitems; Py_ssize_t sz, oldsz = 0; unsigned char check_block_index = 0; /* index into the check_blocks_produced and (parallel) pystrs_produced arrays */ if (!PyArg_ParseTuple(args, "O|O:Encoder.encode", &inblocks, &desired_blocks_nums)) return NULL; for (i=0; imm - self->kk; i++) pystrs_produced[i] = NULL; if (desired_blocks_nums) { fast_desired_blocks_nums = PySequence_Fast(desired_blocks_nums, "Second argument (optional) was not a sequence."); if (!fast_desired_blocks_nums) goto err; num_desired_blocks = PySequence_Fast_GET_SIZE(fast_desired_blocks_nums); fast_desired_blocks_nums_items = PySequence_Fast_ITEMS(fast_desired_blocks_nums); for (i=0; i= self->kk) num_check_blocks_produced++; } } else { num_desired_blocks = self->mm; for (i=0; imm - self->kk; } fastinblocks = PySequence_Fast(inblocks, "First argument was not a sequence."); if (!fastinblocks) goto err; if (PySequence_Fast_GET_SIZE(fastinblocks) != self->kk) { PyErr_Format(py_fec_error, "Precondition violation: Wrong length -- first argument (the sequence of input blocks) is required to contain exactly k blocks. len(first): %Zu, k: %d", PySequence_Fast_GET_SIZE(fastinblocks), self->kk); goto err; } /* Construct a C array of gf*'s of the input data. */ fastinblocksitems = PySequence_Fast_ITEMS(fastinblocks); if (!fastinblocksitems) goto err; for (i=0; ikk; i++) { if (!PyObject_CheckReadBuffer(fastinblocksitems[i])) { PyErr_Format(py_fec_error, "Precondition violation: %u'th item is required to offer the single-segment read character buffer protocol, but it does not.", i); goto err; } if (PyObject_AsReadBuffer(fastinblocksitems[i], (const void**)&(incblocks[i]), &sz)) goto err; if (oldsz != 0 && oldsz != sz) { PyErr_Format(py_fec_error, "Precondition violation: Input blocks are required to be all the same length. length of one block was: %Zu, length of another block was: %Zu", oldsz, sz); goto err; } oldsz = sz; } /* Allocate space for all of the check blocks. */ for (i=0; i= self->kk) { c_desired_checkblocks_ids[check_block_index] = c_desired_blocks_nums[i]; pystrs_produced[check_block_index] = PyString_FromStringAndSize(NULL, sz); if (pystrs_produced[check_block_index] == NULL) goto err; check_blocks_produced[check_block_index] = (gf*)PyString_AsString(pystrs_produced[check_block_index]); if (check_blocks_produced[check_block_index] == NULL) goto err; check_block_index++; } } assert (check_block_index == num_check_blocks_produced); /* Encode any check blocks that are needed. */ fec_encode(self->fec_matrix, incblocks, check_blocks_produced, c_desired_checkblocks_ids, num_check_blocks_produced, sz); /* Wrap all requested blocks up into a Python list of Python strings. */ result = PyList_New(num_desired_blocks); if (result == NULL) goto err; check_block_index = 0; for (i=0; ikk) { Py_INCREF(fastinblocksitems[c_desired_blocks_nums[i]]); if (PyList_SetItem(result, i, fastinblocksitems[c_desired_blocks_nums[i]]) == -1) { Py_DECREF(fastinblocksitems[c_desired_blocks_nums[i]]); goto err; } } else { if (PyList_SetItem(result, i, pystrs_produced[check_block_index]) == -1) goto err; pystrs_produced[check_block_index] = NULL; check_block_index++; } } goto cleanup; err: for (i=0; ifec_matrix) fec_free(self->fec_matrix); self->ob_type->tp_free((PyObject*)self); } static PyMethodDef Encoder_methods[] = { {"encode", (PyCFunction)Encoder_encode, METH_VARARGS, Encoder_encode__doc__}, {NULL}, }; static PyMemberDef Encoder_members[] = { {"k", T_SHORT, offsetof(Encoder, kk), READONLY, "k"}, {"m", T_SHORT, offsetof(Encoder, mm), READONLY, "m"}, {NULL} /* Sentinel */ }; static PyTypeObject Encoder_type = { PyObject_HEAD_INIT(NULL) 0, /*ob_size*/ "_fec.Encoder", /*tp_name*/ sizeof(Encoder), /*tp_basicsize*/ 0, /*tp_itemsize*/ (destructor)Encoder_dealloc, /*tp_dealloc*/ 0, /*tp_print*/ 0, /*tp_getattr*/ 0, /*tp_setattr*/ 0, /*tp_compare*/ 0, /*tp_repr*/ 0, /*tp_as_number*/ 0, /*tp_as_sequence*/ 0, /*tp_as_mapping*/ 0, /*tp_hash */ 0, /*tp_call*/ 0, /*tp_str*/ 0, /*tp_getattro*/ 0, /*tp_setattro*/ 0, /*tp_as_buffer*/ Py_TPFLAGS_DEFAULT | Py_TPFLAGS_BASETYPE, /*tp_flags*/ Encoder__doc__, /* tp_doc */ 0, /* tp_traverse */ 0, /* tp_clear */ 0, /* tp_richcompare */ 0, /* tp_weaklistoffset */ 0, /* tp_iter */ 0, /* tp_iternext */ Encoder_methods, /* tp_methods */ Encoder_members, /* tp_members */ 0, /* tp_getset */ 0, /* tp_base */ 0, /* tp_dict */ 0, /* tp_descr_get */ 0, /* tp_descr_set */ 0, /* tp_dictoffset */ (initproc)Encoder_init, /* tp_init */ 0, /* tp_alloc */ Encoder_new, /* tp_new */ }; static char Decoder__doc__[] = "\ Hold static decoder state (an in-memory table for matrix multiplication), and k and m parameters, and provide {decode()} method.\n\n\ @param k: the number of packets required for reconstruction \n\ @param m: the number of packets generated \n\ "; typedef struct { PyObject_HEAD /* expose these */ unsigned short kk; unsigned short mm; /* internal */ fec_t* fec_matrix; } Decoder; static PyObject * Decoder_new(PyTypeObject *type, PyObject *args, PyObject *kwdict) { Decoder *self; self = (Decoder*)type->tp_alloc(type, 0); if (self != NULL) { self->kk = 0; self->mm = 0; self->fec_matrix = NULL; } return (PyObject *)self; } static int Decoder_init(Encoder *self, PyObject *args, PyObject *kwdict) { static char *kwlist[] = { "k", "m", NULL }; int ink, inm; if (!PyArg_ParseTupleAndKeywords(args, kwdict, "ii:Decoder.__init__", kwlist, &ink, &inm)) return -1; if (ink < 1) { PyErr_Format(py_fec_error, "Precondition violation: first argument is required to be greater than or equal to 1, but it was %d", ink); return -1; } if (inm < 1) { PyErr_Format(py_fec_error, "Precondition violation: second argument is required to be greater than or equal to 1, but it was %d", inm); return -1; } if (inm > 256) { PyErr_Format(py_fec_error, "Precondition violation: second argument is required to be less than or equal to 256, but it was %d", inm); return -1; } if (ink > inm) { PyErr_Format(py_fec_error, "Precondition violation: first argument is required to be less than or equal to the second argument, but they were %d and %d respectively", ink, inm); return -1; } self->kk = (unsigned short)ink; self->mm = (unsigned short)inm; self->fec_matrix = fec_new(self->kk, self->mm); return 0; } #define SWAP(a,b,t) {t tmp; tmp=a; a=b; b=tmp;} static char Decoder_decode__doc__[] = "\ Decode a list blocks into a list of segments.\n\ @param blocks a sequence of buffers containing block data (for best performance, make it a tuple instead of a list)\n\ @param blocknums a sequence of integers of the blocknum for each block in blocks (for best performance, make it a tuple instead of a list)\n\ \n\ @return a list of strings containing the segment data (i.e. ''.join(retval) yields a string containing the decoded data)\n\ "; static PyObject * Decoder_decode(Decoder *self, PyObject *args) { PyObject*restrict blocks; PyObject*restrict blocknums; PyObject* result = NULL; const gf**restrict cblocks = (const gf**restrict)alloca(self->kk * sizeof(const gf*)); unsigned* cblocknums = (unsigned*)alloca(self->kk * sizeof(unsigned)); gf**restrict recoveredcstrs = (gf**)alloca(self->kk * sizeof(gf*)); /* self->kk is actually an upper bound -- we probably won't need all of this space. */ PyObject**restrict recoveredpystrs = (PyObject**restrict)alloca(self->kk * sizeof(PyObject*)); /* self->kk is actually an upper bound -- we probably won't need all of this space. */ unsigned i; PyObject*restrict fastblocknums = NULL; PyObject*restrict fastblocks; unsigned needtorecover=0; PyObject** fastblocksitems; PyObject** fastblocknumsitems; Py_ssize_t sz, oldsz = 0; long tmpl; unsigned nextrecoveredix=0; if (!PyArg_ParseTuple(args, "OO:Decoder.decode", &blocks, &blocknums)) return NULL; for (i=0; ikk; i++) recoveredpystrs[i] = NULL; fastblocks = PySequence_Fast(blocks, "First argument was not a sequence."); if (!fastblocks) goto err; fastblocknums = PySequence_Fast(blocknums, "Second argument was not a sequence."); if (!fastblocknums) goto err; if (PySequence_Fast_GET_SIZE(fastblocks) != self->kk) { PyErr_Format(py_fec_error, "Precondition violation: Wrong length -- first argument is required to contain exactly k blocks. len(first): %Zu, k: %d", PySequence_Fast_GET_SIZE(fastblocks), self->kk); goto err; } if (PySequence_Fast_GET_SIZE(fastblocknums) != self->kk) { PyErr_Format(py_fec_error, "Precondition violation: Wrong length -- blocknums is required to contain exactly k blocks. len(blocknums): %Zu, k: %d", PySequence_Fast_GET_SIZE(fastblocknums), self->kk); goto err; } /* Construct a C array of gf*'s of the data and another of C ints of the blocknums. */ fastblocknumsitems = PySequence_Fast_ITEMS(fastblocknums); if (!fastblocknumsitems) goto err; fastblocksitems = PySequence_Fast_ITEMS(fastblocks); if (!fastblocksitems) goto err; for (i=0; ikk; i++) { if (!PyInt_Check(fastblocknumsitems[i])) { PyErr_Format(py_fec_error, "Precondition violation: second argument is required to contain int."); goto err; } tmpl = PyInt_AsLong(fastblocknumsitems[i]); if (tmpl < 0 || tmpl > 255) { PyErr_Format(py_fec_error, "Precondition violation: block nums can't be less than zero or greater than 255. %ld\n", tmpl); goto err; } cblocknums[i] = (unsigned)tmpl; if (cblocknums[i] >= self->kk) needtorecover+=1; if (!PyObject_CheckReadBuffer(fastblocksitems[i])) { PyErr_Format(py_fec_error, "Precondition violation: %u'th item is required to offer the single-segment read character buffer protocol, but it does not.\n", i); goto err; } if (PyObject_AsReadBuffer(fastblocksitems[i], (const void**)&(cblocks[i]), &sz)) goto err; if (oldsz != 0 && oldsz != sz) { PyErr_Format(py_fec_error, "Precondition violation: Input blocks are required to be all the same length. length of one block was: %Zu, length of another block was: %Zu\n", oldsz, sz); goto err; } oldsz = sz; } /* Move src packets into position. At the end of this loop we want the i'th element of the arrays to be the block with block number i, if that block is among our inputs. */ for (i=0; ikk;) { if (cblocknums[i] >= self->kk || cblocknums[i] == i) i++; else { /* put pkt in the right position. */ unsigned c = cblocknums[i]; SWAP (cblocknums[i], cblocknums[c], int); SWAP (cblocks[i], cblocks[c], const gf*); SWAP (fastblocksitems[i], fastblocksitems[c], PyObject*); } } /* Allocate space for all of the recovered blocks. */ for (i=0; ifec_matrix, cblocks, recoveredcstrs, cblocknums, sz); /* Wrap up both original primary blocks and decoded blocks into a Python list of Python strings. */ result = PyList_New(self->kk); if (result == NULL) goto err; for (i=0; ikk; i++) { if (cblocknums[i] == i) { /* Original primary block. */ Py_INCREF(fastblocksitems[i]); if (PyList_SetItem(result, i, fastblocksitems[i]) == -1) { Py_DECREF(fastblocksitems[i]); goto err; } } else { /* Recovered block. */ if (PyList_SetItem(result, i, recoveredpystrs[nextrecoveredix]) == -1) goto err; recoveredpystrs[nextrecoveredix] = NULL; nextrecoveredix++; } } goto cleanup; err: for (i=0; ikk; i++) Py_XDECREF(recoveredpystrs[i]); Py_XDECREF(result); result = NULL; cleanup: Py_XDECREF(fastblocks); fastblocks=NULL; Py_XDECREF(fastblocknums); fastblocknums=NULL; return result; } static void Decoder_dealloc(Decoder * self) { if (self->fec_matrix) fec_free(self->fec_matrix); self->ob_type->tp_free((PyObject*)self); } static PyMethodDef Decoder_methods[] = { {"decode", (PyCFunction)Decoder_decode, METH_VARARGS, Decoder_decode__doc__}, {NULL}, }; static PyMemberDef Decoder_members[] = { {"k", T_SHORT, offsetof(Encoder, kk), READONLY, "k"}, {"m", T_SHORT, offsetof(Encoder, mm), READONLY, "m"}, {NULL} /* Sentinel */ }; static PyTypeObject Decoder_type = { PyObject_HEAD_INIT(NULL) 0, /*ob_size*/ "_fec.Decoder", /*tp_name*/ sizeof(Decoder), /*tp_basicsize*/ 0, /*tp_itemsize*/ (destructor)Decoder_dealloc, /*tp_dealloc*/ 0, /*tp_print*/ 0, /*tp_getattr*/ 0, /*tp_setattr*/ 0, /*tp_compare*/ 0, /*tp_repr*/ 0, /*tp_as_number*/ 0, /*tp_as_sequence*/ 0, /*tp_as_mapping*/ 0, /*tp_hash */ 0, /*tp_call*/ 0, /*tp_str*/ 0, /*tp_getattro*/ 0, /*tp_setattro*/ 0, /*tp_as_buffer*/ Py_TPFLAGS_DEFAULT | Py_TPFLAGS_BASETYPE, /*tp_flags*/ Decoder__doc__, /* tp_doc */ 0, /* tp_traverse */ 0, /* tp_clear */ 0, /* tp_richcompare */ 0, /* tp_weaklistoffset */ 0, /* tp_iter */ 0, /* tp_iternext */ Decoder_methods, /* tp_methods */ Decoder_members, /* tp_members */ 0, /* tp_getset */ 0, /* tp_base */ 0, /* tp_dict */ 0, /* tp_descr_get */ 0, /* tp_descr_set */ 0, /* tp_dictoffset */ (initproc)Decoder_init, /* tp_init */ 0, /* tp_alloc */ Decoder_new, /* tp_new */ }; void _hexwrite(unsigned char*s, size_t l) { for (size_t i = 0; i < l; i++) printf("%.2x", s[i]); } PyObject* test_from_agl(PyObject* self, PyObject* args) { unsigned char b0c[8], b1c[8]; unsigned char b0[8], b1[8], b2[8], b3[8], b4[8]; memset(b0, 1, 8); memset(b1, 2, 8); memset(b2, 3, 8); const unsigned char *blocks[3] = {b0, b1, b2}; unsigned char *outblocks[2] = {b3, b4}; unsigned block_nums[] = {3, 4}; /*printf("_from_c before encoding:\n"); printf("b0: "); _hexwrite(b0, 8); printf(", "); printf("b1: "); _hexwrite(b1, 8); printf(", "); printf("b2: "); _hexwrite(b2, 8); printf(", "); printf("\n");*/ fec_t *const fec = fec_new(3, 5); fec_encode(fec, blocks, outblocks, block_nums, 2, 8); /*printf("after encoding:\n"); printf("b3: "); _hexwrite(b3, 8); printf(", "); printf("b4: "); _hexwrite(b4, 8); printf(", "); printf("\n");*/ memcpy(b0c, b0, 8); memcpy(b1c, b1, 8); const unsigned char *inpkts[] = {b3, b4, b2}; unsigned char *outpkts[] = {b0, b1}; unsigned indexes[] = {3, 4, 2}; fec_decode(fec, inpkts, outpkts, indexes, 8); /*printf("after decoding:\n"); printf("b0: "); _hexwrite(b0, 8); printf(", "); printf("b1: "); _hexwrite(b1, 8); printf("\n");*/ if ((memcmp(b0, b0c,8) == 0) && (memcmp(b1, b1c,8) == 0)) Py_RETURN_TRUE; else Py_RETURN_FALSE; } static PyMethodDef fec_functions[] = { {"test_from_agl", test_from_agl, METH_NOARGS, NULL}, {NULL} }; #ifndef PyMODINIT_FUNC /* declarations for DLL import/export */ #define PyMODINIT_FUNC void #endif PyMODINIT_FUNC init_fec(void) { PyObject *module; PyObject *module_dict; if (PyType_Ready(&Encoder_type) < 0) return; if (PyType_Ready(&Decoder_type) < 0) return; module = Py_InitModule3("_fec", fec_functions, fec__doc__); if (module == NULL) return; Py_INCREF(&Encoder_type); Py_INCREF(&Decoder_type); PyModule_AddObject(module, "Encoder", (PyObject *)&Encoder_type); PyModule_AddObject(module, "Decoder", (PyObject *)&Decoder_type); module_dict = PyModule_GetDict(module); py_fec_error = PyErr_NewException("_fec.Error", NULL, NULL); PyDict_SetItemString(module_dict, "Error", py_fec_error); } /** * originally inspired by fecmodule.c by the Mnet Project, especially Myers * Carpenter and Hauke Johannknecht */ zfec-1.4.5/zfec/__init__.py0000664000175100017510000000160711216211367014604 0ustar zookozooko""" zfec -- fast forward error correction library with Python interface maintainer web site: U{http://allmydata.com/source/zfec} zfec web site: U{http://allmydata.com/source/zfec} """ __version__ = "unknown" try: from _version import __version__ except ImportError: # We're running in a tree that hasn't run darcsver, and didn't come with a # _version.py, so we don't know what our version is. This should not happen # very often. pass from _fec import Encoder, Decoder, Error import easyfec, filefec, cmdline_zfec, cmdline_zunfec quiet_pyflakes=[__version__, Error, Encoder, Decoder, cmdline_zunfec, filefec, cmdline_zfec, easyfec] # zfec -- fast forward error correction library with Python interface # # Copyright (C) 2007 Allmydata, Inc. # Author: Zooko Wilcox-O'Hearn # mailto:zooko@zooko.com # # This file is part of zfec. # # See README.txt for licensing information. zfec-1.4.5/zfec/fec.h0000664000175100017510000001016111216211367013374 0ustar zookozooko/** * zfec -- fast forward error correction library with Python interface * * See README.txt for documentation. */ #include typedef unsigned char gf; typedef struct { unsigned long magic; unsigned short k, n; /* parameters of the code */ gf* enc_matrix; } fec_t; #if defined(_MSC_VER) // actually, some of the flavors (i.e. Enterprise) do support restrict //#define restrict __restrict #define restrict #endif /** * param k the number of blocks required to reconstruct * param m the total number of blocks created */ fec_t* fec_new(unsigned short k, unsigned short m); void fec_free(fec_t* p); /** * @param inpkts the "primary blocks" i.e. the chunks of the input data * @param fecs buffers into which the secondary blocks will be written * @param block_nums the numbers of the desired check blocks (the id >= k) which fec_encode() will produce and store into the buffers of the fecs parameter * @param num_block_nums the length of the block_nums array * @param sz size of a packet in bytes */ void fec_encode(const fec_t* code, const gf*restrict const*restrict const src, gf*restrict const*restrict const fecs, const unsigned*restrict const block_nums, size_t num_block_nums, size_t sz); /** * @param inpkts an array of packets (size k); If a primary block, i, is present then it must be at index i. Secondary blocks can appear anywhere. * @param outpkts an array of buffers into which the reconstructed output packets will be written (only packets which are not present in the inpkts input will be reconstructed and written to outpkts) * @param index an array of the blocknums of the packets in inpkts * @param sz size of a packet in bytes */ void fec_decode(const fec_t* code, const gf*restrict const*restrict const inpkts, gf*restrict const*restrict const outpkts, const unsigned*restrict const index, size_t sz); #if defined(_MSC_VER) #define alloca _alloca #else #ifdef __GNUC__ #ifndef alloca #define alloca(x) __builtin_alloca(x) #endif #else #include #endif #endif /** * zfec -- fast forward error correction library with Python interface * * Copyright (C) 2007-2008 Allmydata, Inc. * Author: Zooko Wilcox-O'Hearn * * This file is part of zfec. * * See README.txt for licensing information. */ /* * Much of this work is derived from the "fec" software by Luigi Rizzo, et * al., the copyright notice and licence terms of which are included below * for reference. * * fec.h -- forward error correction based on Vandermonde matrices * 980614 * (C) 1997-98 Luigi Rizzo (luigi@iet.unipi.it) * * Portions derived from code by Phil Karn (karn@ka9q.ampr.org), * Robert Morelos-Zaragoza (robert@spectra.eng.hawaii.edu) and Hari * Thirumoorthy (harit@spectra.eng.hawaii.edu), Aug 1995 * * Modifications by Dan Rubenstein (see Modifications.txt for * their description. * Modifications (C) 1998 Dan Rubenstein (drubenst@cs.umass.edu) * * Redistribution and use in source and binary forms, with or without * modification, are permitted provided that the following conditions * are met: * 1. Redistributions of source code must retain the above copyright * notice, this list of conditions and the following disclaimer. * 2. Redistributions in binary form must reproduce the above * copyright notice, this list of conditions and the following * disclaimer in the documentation and/or other materials * provided with the distribution. * * THIS SOFTWARE IS PROVIDED BY THE AUTHORS ``AS IS'' AND * ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, * THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A * PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHORS * BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, * OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, * PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, * OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY * THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR * TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT * OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY * OF SUCH DAMAGE. */ zfec-1.4.5/zfec/test/0000775000175100017510000000000011216213552013444 5ustar zookozookozfec-1.4.5/zfec/test/test_zfec.py0000664000175100017510000003021611216211367016010 0ustar zookozooko#!/usr/bin/env python import cStringIO, os, random, re import unittest global VERBOSE VERBOSE=False import zfec from pyutil import fileutil from base64 import b32encode def ab(x): # debuggery if len(x) >= 3: return "%s:%s" % (len(x), b32encode(x[-3:]),) elif len(x) == 2: return "%s:%s" % (len(x), b32encode(x[-2:]),) elif len(x) == 1: return "%s:%s" % (len(x), b32encode(x[-1:]),) elif len(x) == 0: return "%s:%s" % (len(x), "--empty--",) def randstr(n): return ''.join(map(chr, map(random.randrange, [0]*n, [256]*n))) def _h(k, m, ss): encer = zfec.Encoder(k, m) nums_and_blocks = list(enumerate(encer.encode(ss))) assert isinstance(nums_and_blocks, list), nums_and_blocks assert len(nums_and_blocks) == m, (len(nums_and_blocks), m,) nums_and_blocks = random.sample(nums_and_blocks, k) blocks = [ x[1] for x in nums_and_blocks ] nums = [ x[0] for x in nums_and_blocks ] decer = zfec.Decoder(k, m) decoded = decer.decode(blocks, nums) assert len(decoded) == len(ss), (len(decoded), len(ss),) assert tuple([str(s) for s in decoded]) == tuple([str(s) for s in ss]), (tuple([ab(str(s)) for s in decoded]), tuple([ab(str(s)) for s in ss]),) def _help_test_random(): m = random.randrange(1, 257) k = random.randrange(1, m+1) l = random.randrange(0, 2**9) ss = [ randstr(l/k) for x in range(k) ] _h(k, m, ss) def _help_test_random_with_l(l): m = random.randrange(1, 257) k = random.randrange(1, m+1) ss = [ randstr(l/k) for x in range(k) ] _h(k, m, ss) def _h_easy(k, m, s): encer = zfec.easyfec.Encoder(k, m) nums_and_blocks = list(enumerate(encer.encode(s))) assert isinstance(nums_and_blocks, list), nums_and_blocks assert len(nums_and_blocks) == m, (len(nums_and_blocks), m,) nums_and_blocks = random.sample(nums_and_blocks, k) blocks = [ x[1] for x in nums_and_blocks ] nums = [ x[0] for x in nums_and_blocks ] decer = zfec.easyfec.Decoder(k, m) decodeds = decer.decode(blocks, nums, padlen=k*len(blocks[0]) - len(s)) assert len(decodeds) == len(s), (ab(decodeds), ab(s), k, m) assert decodeds == s, (ab(decodeds), ab(s),) def _help_test_random_easy(): m = random.randrange(1, 257) k = random.randrange(1, m+1) l = random.randrange(0, 2**9) s = randstr(l) _h_easy(k, m, s) def _help_test_random_with_l_easy(l): m = random.randrange(1, 257) k = random.randrange(1, m+1) s = randstr(l) _h_easy(k, m, s) class ZFecTest(unittest.TestCase): def test_from_agl_c(self): self.failUnless(zfec._fec.test_from_agl()) def test_from_agl_py(self): e = zfec.Encoder(3, 5) b0 = '\x01'*8 ; b1 = '\x02'*8 ; b2 = '\x03'*8 # print "_from_py before encoding:" # print "b0: %s, b1: %s, b2: %s" % tuple(base64.b16encode(x) for x in [b0, b1, b2]) b3, b4 = e.encode([b0, b1, b2], (3, 4)) # print "after encoding:" # print "b3: %s, b4: %s" % tuple(base64.b16encode(x) for x in [b3, b4]) d = zfec.Decoder(3, 5) r0, r1, r2 = d.decode((b2, b3, b4), (1, 2, 3)) # print "after decoding:" # print "b0: %s, b1: %s" % tuple(base64.b16encode(x) for x in [b0, b1]) def test_small(self): for i in range(16): _help_test_random_with_l(i) if VERBOSE: print "%d randomized tests pass." % (i+1) def test_random(self): for i in range(3): _help_test_random() if VERBOSE: print "%d randomized tests pass." % (i+1) def test_bad_args_construct_decoder(self): try: zfec.Decoder(-1, -1) except zfec.Error, e: assert "argument is required to be greater than or equal to 1" in str(e), e else: self.fail("Should have gotten an exception from out-of-range arguments.") try: zfec.Decoder(1, 257) except zfec.Error, e: assert "argument is required to be less than or equal to 256" in str(e), e else: self.fail("Should have gotten an exception from out-of-range arguments.") try: zfec.Decoder(3, 2) except zfec.Error, e: assert "first argument is required to be less than or equal to the second argument" in str(e), e else: self.fail("Should have gotten an exception from out-of-range arguments.") def test_bad_args_construct_encoder(self): try: zfec.Encoder(-1, -1) except zfec.Error, e: assert "argument is required to be greater than or equal to 1" in str(e), e else: self.fail("Should have gotten an exception from out-of-range arguments.") try: zfec.Encoder(1, 257) except zfec.Error, e: assert "argument is required to be less than or equal to 256" in str(e), e else: self.fail("Should have gotten an exception from out-of-range arguments.") def test_bad_args_dec(self): decer = zfec.Decoder(2, 4) try: decer.decode(98, []) # first argument is not a sequence except TypeError, e: assert "First argument was not a sequence" in str(e), e else: self.fail("Should have gotten TypeError for wrong type of second argument.") try: decer.decode(["a", "b", ], ["c", "d",]) except zfec.Error, e: assert "Precondition violation: second argument is required to contain int" in str(e), e else: self.fail("Should have gotten zfec.Error for wrong type of second argument.") try: decer.decode(["a", "b", ], 98) # not a sequence at all except TypeError, e: assert "Second argument was not a sequence" in str(e), e else: self.fail("Should have gotten TypeError for wrong type of second argument.") class EasyFecTest(unittest.TestCase): def test_small(self): for i in range(16): _help_test_random_with_l_easy(i) if VERBOSE: print "%d randomized tests pass." % (i+1) def test_random(self): for i in range(3): _help_test_random_easy() if VERBOSE: print "%d randomized tests pass." % (i+1) def test_bad_args_dec(self): decer = zfec.easyfec.Decoder(2, 4) try: decer.decode(98, [0, 1], 0) # first argument is not a sequence except TypeError, e: assert "First argument was not a sequence" in str(e), e else: self.fail("Should have gotten TypeError for wrong type of second argument.") try: decer.decode("ab", ["c", "d",], 0) except zfec.Error, e: assert "Precondition violation: second argument is required to contain int" in str(e), e else: self.fail("Should have gotten zfec.Error for wrong type of second argument.") try: decer.decode("ab", 98, 0) # not a sequence at all except TypeError, e: assert "Second argument was not a sequence" in str(e), e else: self.fail("Should have gotten TypeError for wrong type of second argument.") class FileFec(unittest.TestCase): def test_filefec_header(self): for m in [1, 2, 3, 5, 7, 9, 11, 17, 19, 33, 35, 65, 66, 67, 129, 130, 131, 254, 255, 256,]: for k in [1, 2, 3, 5, 9, 17, 33, 65, 129, 255, 256,]: if k >= m: continue for pad in [0, 1, k-1,]: if pad >= k: continue for sh in [0, 1, m-1,]: if sh >= m: continue h = zfec.filefec._build_header(m, k, pad, sh) hio = cStringIO.StringIO(h) (rm, rk, rpad, rsh,) = zfec.filefec._parse_header(hio) assert (rm, rk, rpad, rsh,) == (m, k, pad, sh,), h def _help_test_filefec(self, teststr, k, m, numshs=None): if numshs == None: numshs = m TESTFNAME = "testfile.txt" PREFIX = "test" SUFFIX = ".fec" fsize = len(teststr) tempdir = fileutil.NamedTemporaryDirectory(cleanup=True) try: tempf = tempdir.file(TESTFNAME, 'w+b') tempf.write(teststr) tempf.flush() tempf.seek(0) # encode the file zfec.filefec.encode_to_files(tempf, fsize, tempdir.name, PREFIX, k, m, SUFFIX, verbose=VERBOSE) # select some share files RE=re.compile(zfec.filefec.RE_FORMAT % (PREFIX, SUFFIX,)) fns = os.listdir(tempdir.name) assert len(fns) >= m, (fns, tempdir, tempdir.name,) sharefs = [ open(os.path.join(tempdir.name, fn), "rb") for fn in fns if RE.match(fn) ] for sharef in sharefs: tempdir.register_file(sharef) random.shuffle(sharefs) del sharefs[numshs:] # decode from the share files outf = tempdir.file('recovered-testfile.txt', 'w+b') zfec.filefec.decode_from_files(outf, sharefs, verbose=VERBOSE) outf.flush() outf.seek(0) recovereddata = outf.read() assert recovereddata == teststr, (ab(recovereddata), ab(teststr),) finally: tempdir.shutdown() def test_filefec_all_shares(self): return self._help_test_filefec("Yellow Whirled!", 3, 8) def test_filefec_all_shares_1_b(self): return self._help_test_filefec("Yellow Whirled!", 4, 16) def test_filefec_all_shares_2(self): return self._help_test_filefec("Yellow Whirled", 3, 8) def test_filefec_all_shares_2_b(self): return self._help_test_filefec("Yellow Whirled", 4, 16) def test_filefec_all_shares_3(self): return self._help_test_filefec("Yellow Whirle", 3, 8) def test_filefec_all_shares_3_b(self): return self._help_test_filefec("Yellow Whirle", 4, 16) def test_filefec_all_shares_with_padding(self, noisy=VERBOSE): return self._help_test_filefec("Yellow Whirled!A", 3, 8) def test_filefec_min_shares_with_padding(self, noisy=VERBOSE): return self._help_test_filefec("Yellow Whirled!A", 3, 8, numshs=3) def test_filefec_min_shares_with_crlf(self, noisy=VERBOSE): return self._help_test_filefec("llow Whirled!A\r\n", 3, 8, numshs=3) def test_filefec_min_shares_with_lf(self, noisy=VERBOSE): return self._help_test_filefec("Yellow Whirled!A\n", 3, 8, numshs=3) def test_filefec_min_shares_with_lflf(self, noisy=VERBOSE): return self._help_test_filefec("Yellow Whirled!A\n\n", 3, 8, numshs=3) def test_filefec_min_shares_with_crcrlflf(self, noisy=VERBOSE): return self._help_test_filefec("Yellow Whirled!A\r\r\n\n", 3, 8, numshs=3) class Cmdline(unittest.TestCase): def test_basic(self, noisy=VERBOSE): tempdir = fileutil.NamedTemporaryDirectory(cleanup=True) fo = tempdir.file("test.data", "w+b") fo.write("WHEHWHJEKWAHDLJAWDHWALKDHA") import sys realargv = sys.argv try: DEFAULT_M=8 DEFAULT_K=3 sys.argv = ["zfec", os.path.join(tempdir.name, "test.data"),] retcode = zfec.cmdline_zfec.main() assert retcode == 0, retcode RE=re.compile(zfec.filefec.RE_FORMAT % ('test.data', ".fec",)) fns = os.listdir(tempdir.name) assert len(fns) >= DEFAULT_M, (fns, DEFAULT_M, tempdir, tempdir.name,) sharefns = [ os.path.join(tempdir.name, fn) for fn in fns if RE.match(fn) ] random.shuffle(sharefns) del sharefns[DEFAULT_K:] sys.argv = ["zunfec",] sys.argv.extend(sharefns) sys.argv.extend(['-o', os.path.join(tempdir.name, 'test.data-recovered'),]) retcode = zfec.cmdline_zunfec.main() assert retcode == 0, retcode import filecmp assert filecmp.cmp(os.path.join(tempdir.name, 'test.data'), os.path.join(tempdir.name, 'test.data-recovered')) finally: sys.argv = realargv if __name__ == "__main__": unittest.main() zfec-1.4.5/zfec/test/__init__.py0000664000175100017510000000000011216211327015541 0ustar zookozookozfec-1.4.5/zfec/cmdline_zfec.py0000664000175100017510000000727611216211330015465 0ustar zookozooko#!/usr/bin/env python # zfec -- a fast C implementation of Reed-Solomon erasure coding with # command-line, C, and Python interfaces import sys import argparse import filefec from zfec import __version__ as libversion __version__ = libversion DEFAULT_K=3 DEFAULT_M=8 def main(): if '-V' in sys.argv or '--version' in sys.argv: print "zfec library version: ", libversion print "zfec command-line tool version: ", __version__ sys.exit(0) parser = argparse.ArgumentParser(description="Encode a file into a set of share files, a subset of which can later be used to recover the original file.") parser.add_argument('inputfile', help='file to encode or "-" for stdin', type=argparse.FileType('rb'), metavar='INF') parser.add_argument('-d', '--output-dir', help='directory in which share file names will be created (default ".")', default='.', metavar='D') parser.add_argument('-p', '--prefix', help='prefix for share file names; If omitted, the name of the input file will be used.', metavar='P') parser.add_argument('-s', '--suffix', help='suffix for share file names (default ".fec")', default='.fec', metavar='S') parser.add_argument('-m', '--totalshares', help='the total number of share files created (default %d)' % DEFAULT_M, default=DEFAULT_M, type=int, metavar='M') parser.add_argument('-k', '--requiredshares', help='the number of share files required to reconstruct (default %d)' % DEFAULT_K, default=DEFAULT_K, type=int, metavar='K') parser.add_argument('-f', '--force', help='overwrite any file which already in place an output file (share file)', action='store_true') parser.add_argument('-v', '--verbose', help='print out messages about progress', action='store_true') parser.add_argument('-q', '--quiet', help='quiet progress indications and warnings about silly choices of K and M', action='store_true') parser.add_argument('-V', '--version', help='print out version number and exit', action='store_true') args = parser.parse_args() if args.prefix is None: args.prefix = args.inputfile.name if args.prefix == "": args.prefix = "" if args.verbose and args.quiet: print "Please choose only one of --verbose and --quiet." sys.exit(1) if args.totalshares > 256 or args.totalshares < 1: print "Invalid parameters, totalshares is required to be <= 256 and >= 1\nPlease see the accompanying documentation." sys.exit(1) if args.requiredshares > args.totalshares or args.requiredshares < 1: print "Invalid parameters, requiredshares is required to be <= totalshares and >= 1\nPlease see the accompanying documentation." sys.exit(1) if not args.quiet: if args.requiredshares == 1: print "warning: silly parameters: requiredshares == 1, which means that every share will be a complete copy of the file. You could use \"cp\" for the same effect. But proceeding to do it anyway..." if args.requiredshares == args.totalshares: print "warning: silly parameters: requiredshares == totalshares, which means that all shares will be required in order to reconstruct the file. You could use \"split\" for the same effect. But proceeding to do it anyway..." args.inputfile.seek(0, 2) fsize = args.inputfile.tell() args.inputfile.seek(0, 0) return filefec.encode_to_files(args.inputfile, fsize, args.output_dir, args.prefix, args.requiredshares, args.totalshares, args.suffix, args.force, args.verbose) # zfec -- fast forward error correction library with Python interface # # Copyright (C) 2007 Allmydata, Inc. # Author: Zooko Wilcox-O'Hearn # # This file is part of zfec. # # See README.txt for licensing information. zfec-1.4.5/zfec/easyfec.py0000664000175100017510000000405311216211330014450 0ustar zookozooko# zfec -- a fast C implementation of Reed-Solomon erasure coding with # command-line, C, and Python interfaces import zfec # div_ceil() was copied from the pyutil library. def div_ceil(n, d): """ The smallest integer k such that k*d >= n. """ return (n/d) + (n%d != 0) from base64 import b32encode def ab(x): # debuggery if len(x) >= 3: return "%s:%s" % (len(x), b32encode(x[-3:]),) elif len(x) == 2: return "%s:%s" % (len(x), b32encode(x[-2:]),) elif len(x) == 1: return "%s:%s" % (len(x), b32encode(x[-1:]),) elif len(x) == 0: return "%s:%s" % (len(x), "--empty--",) class Encoder(object): def __init__(self, k, m): self.fec = zfec.Encoder(k, m) def encode(self, data): """ @param data: string @return: a sequence of m blocks -- any k of which suffice to reconstruct the input data """ chunksize = div_ceil(len(data), self.fec.k) l = [ data[i*chunksize:(i+1)*chunksize] + "\x00" * min(chunksize, (((i+1)*chunksize)-len(data))) for i in range(self.fec.k) ] assert len(l) == self.fec.k, (len(l), self.fec.k,) assert (not l) or (not [ x for x in l if len(x) != len(l[0]) ], (len(l), [ ab(x) for x in l ], chunksize, self.fec.k, len(data),)) return self.fec.encode(l) class Decoder(object): def __init__(self, k, m): self.fec = zfec.Decoder(k, m) def decode(self, blocks, sharenums, padlen): """ @param padlen: the number of bytes of padding to strip off; Note that the padlen is always equal to (blocksize times k) minus the length of data. (Therefore, padlen can be 0.) """ data = ''.join(self.fec.decode(blocks, sharenums)) if padlen: return data[:-padlen] else: return data # zfec -- fast forward error correction library with Python interface # # Copyright (C) 2007 Allmydata, Inc. # Author: Zooko Wilcox-O'Hearn # # This file is part of zfec. # # See README.txt for licensing information. zfec-1.4.5/fec.cabal0000664000175100017510000000240711216211330013252 0ustar zookozookoname: fec version: 0.1.1 license: GPL license-file: README.txt author: Adam Langley maintainer: Adam Langley description: This code, based on zfec by Zooko, based on code by Luigi Rizzo implements an erasure code, or forward error correction code. The most widely known example of an erasure code is the RAID-5 algorithm which makes it so that in the event of the loss of any one hard drive, the stored data can be completely recovered. The algorithm in the zfec package has a similar effect, but instead of recovering from the loss of only a single element, it can be parameterized to choose in advance the number of elements whose loss it can tolerate. build-type: Simple homepage: http://allmydata.org/source/zfec synopsis: Forward error correction of ByteStrings category: Codec build-depends: base, bytestring>=0.9 stability: provisional tested-with: GHC == 6.8.2 exposed-modules: Codec.FEC extensions: ForeignFunctionInterface hs-source-dirs: haskell ghc-options: -Wall c-sources: zfec/fec.c cc-options: -std=c99 include-dirs: zfec extra-source-files: zfec/fec.h, COPYING.GPL, COPYING.TGPPL.html zfec-1.4.5/zfec.egg-info/0000775000175100017510000000000011216213552014157 5ustar zookozookozfec-1.4.5/zfec.egg-info/PKG-INFO0000664000175100017510000000404711216213552015261 0ustar zookozookoMetadata-Version: 1.0 Name: zfec Version: 1.4.5 Summary: a fast erasure codec which can be used with the command-line, C, Python, or Haskell Home-page: http://allmydata.org/trac/zfec Author: Zooko O'Whielacronx Author-email: zooko@zooko.com License: GNU GPL Description: Fast, portable, programmable erasure coding a.k.a. "forward error correction": the generation of redundant blocks of information such that if some blocks are lost then the original data can be recovered from the remaining blocks. The zfec package includes command-line tools, C API, Python API, and Haskell API Platform: UNKNOWN Classifier: Development Status :: 5 - Production/Stable Classifier: Environment :: Console Classifier: License :: OSI Approved :: GNU General Public License (GPL) Classifier: License :: DFSG approved Classifier: License :: Other/Proprietary License Classifier: Intended Audience :: Developers Classifier: Intended Audience :: End Users/Desktop Classifier: Intended Audience :: System Administrators Classifier: Operating System :: Microsoft Classifier: Operating System :: Microsoft :: Windows Classifier: Operating System :: Unix Classifier: Operating System :: POSIX :: Linux Classifier: Operating System :: POSIX Classifier: Operating System :: MacOS :: MacOS X Classifier: Operating System :: Microsoft :: Windows :: Windows NT/2000 Classifier: Operating System :: OS Independent Classifier: Natural Language :: English Classifier: Programming Language :: C Classifier: Programming Language :: Python Classifier: Programming Language :: Python :: 2 Classifier: Programming Language :: Python :: 2.4 Classifier: Programming Language :: Python :: 2.5 Classifier: Topic :: Utilities Classifier: Topic :: System :: Systems Administration Classifier: Topic :: System :: Filesystems Classifier: Topic :: System :: Distributed Computing Classifier: Topic :: Software Development :: Libraries Classifier: Topic :: Communications :: Usenet News Classifier: Topic :: System :: Archiving :: Backup Classifier: Topic :: System :: Archiving :: Mirroring Classifier: Topic :: System :: Archiving zfec-1.4.5/zfec.egg-info/SOURCES.txt0000664000175100017510000000127311216213552016046 0ustar zookozookoCOPYING.GPL COPYING.TGPPL.html NEWS.txt README.txt Setup.lhs TODO changelog ez_setup.py fec.cabal setup.cfg setup.py stridetune-bench.ba.sh stridetune-bench.py stridetune-dat.bash stridetune-graph.py bench/bench_zfec.py haskell/Codec/FEC.hs haskell/test/FECTest.hs misc/dependencies/setuptools-0.6c10dev.egg zfec/__init__.py zfec/_fecmodule.c zfec/_version.py zfec/cmdline_zfec.py zfec/cmdline_zunfec.py zfec/easyfec.py zfec/fec.c zfec/fec.h zfec/filefec.py zfec.egg-info/PKG-INFO zfec.egg-info/SOURCES.txt zfec.egg-info/dependency_links.txt zfec.egg-info/entry_points.txt zfec.egg-info/not-zip-safe zfec.egg-info/requires.txt zfec.egg-info/top_level.txt zfec/test/__init__.py zfec/test/test_zfec.pyzfec-1.4.5/zfec.egg-info/not-zip-safe0000664000175100017510000000000111216211377016410 0ustar zookozooko zfec-1.4.5/zfec.egg-info/top_level.txt0000664000175100017510000000000511216213552016704 0ustar zookozookozfec zfec-1.4.5/zfec.egg-info/requires.txt0000664000175100017510000000004011216213552016551 0ustar zookozookoargparse >= 0.8 pyutil >= 1.3.19zfec-1.4.5/zfec.egg-info/entry_points.txt0000664000175100017510000000012311216213552017451 0ustar zookozooko[console_scripts] zfec = zfec.cmdline_zfec:main zunfec = zfec.cmdline_zunfec:main zfec-1.4.5/zfec.egg-info/dependency_links.txt0000664000175100017510000000000111216213552020225 0ustar zookozooko