Repository : ssh://g...@git.haskell.org/bytestring On branch : ghc-head Link : http://git.haskell.org/packages/bytestring.git/commitdiff/1a0ede3a606ec8f3ae0c03ecc802557249753ca2
>--------------------------------------------------------------- commit 1a0ede3a606ec8f3ae0c03ecc802557249753ca2 Author: Simon Meier <simon.me...@erudify.com> Date: Tue Sep 17 18:40:54 2013 +0200 Remove unneeded and/or commented-out code. >--------------------------------------------------------------- 1a0ede3a606ec8f3ae0c03ecc802557249753ca2 Data/ByteString/Builder/Prim.hs | 29 -------- Data/ByteString/Builder/Prim/Internal.hs | 84 ----------------------- Data/ByteString/Builder/Prim/Internal/Base16.hs | 47 +------------ 3 files changed, 2 insertions(+), 158 deletions(-) diff --git a/Data/ByteString/Builder/Prim.hs b/Data/ByteString/Builder/Prim.hs index aec47f7..c3ceabb 100644 --- a/Data/ByteString/Builder/Prim.hs +++ b/Data/ByteString/Builder/Prim.hs @@ -450,7 +450,6 @@ module Data.ByteString.Builder.Prim ( import Data.ByteString.Builder.Internal import Data.ByteString.Builder.Prim.Internal.UncheckedShifts -import Data.ByteString.Builder.Prim.Internal.Base16 (lowerTable, encode4_as_8) import qualified Data.ByteString as S import qualified Data.ByteString.Internal as S @@ -736,31 +735,3 @@ encodeCharUtf8 f1 f2 f3 f4 c = case ord c of in f4 x1 x2 x3 x4 ------------------------------------------------------------------------------- --- Testing encodings ------------------------------------------------------------------------------- -{- --- | /For testing use only./ Evaluate a 'FixedPrim' on a given value. -evalF :: FixedPrim a -> a -> [Word8] -evalF fe = S.unpack . S.unsafeCreate (I.size fe) . runF fe - --- | /For testing use only./ Evaluate a 'BoundedPrim' on a given value. -evalB :: BoundedPrim a -> a -> [Word8] -evalB be x = S.unpack $ unsafePerformIO $ - S.createAndTrim (I.sizeBound be) $ \op -> do - op' <- runB be x op - return (op' `minusPtr` op) - --- | /For testing use only./ Show the result of a 'FixedPrim' of a given --- value as a 'String' by interpreting the resulting bytes as Unicode --- codepoints. -showF :: FixedPrim a -> a -> String -showF fe = map (chr . fromIntegral) . evalF fe - --- | /For testing use only./ Show the result of a 'BoundedPrim' of a given --- value as a 'String' by interpreting the resulting bytes as Unicode --- codepoints. -showB :: BoundedPrim a -> a -> String -showB be = map (chr . fromIntegral) . evalB be --} - diff --git a/Data/ByteString/Builder/Prim/Internal.hs b/Data/ByteString/Builder/Prim/Internal.hs index 607d380..772ed81 100644 --- a/Data/ByteString/Builder/Prim/Internal.hs +++ b/Data/ByteString/Builder/Prim/Internal.hs @@ -278,87 +278,3 @@ eitherB (BE b1 io1) (BE b2 io2) = condB :: (a -> Bool) -> BoundedPrim a -> BoundedPrim a -> BoundedPrim a condB p be1 be2 = contramapB (\x -> if p x then Left x else Right x) (eitherB be1 be2) - - -{- -{-# INLINE withSizeFB #-} -withSizeFB :: (Word -> FixedPrim Word) -> BoundedPrim a -> BoundedPrim a -withSizeFB feSize (BE b io) = - BE (lSize + b) - (\x op0 -> do let !op1 = op0 `plusPtr` lSize - op2 <- io x op1 - ioSize (fromIntegral $ op2 `minusPtr` op1) op0 - return op2) - where - FE lSize ioSize = feSize (fromIntegral b) - - -{-# INLINE withSizeBB #-} -withSizeBB :: BoundedPrim Word -> BoundedPrim a -> BoundedPrim a -withSizeBB (BE bSize ioSize) (BE b io) = - BE (bSize + 2*b) - (\x op0 -> do let !opTmp = op0 `plusPtr` (bSize + b) - opTmp' <- io x opTmp - let !s = opTmp' `minusPtr` opTmp - op1 <- ioSize (fromIntegral s) op0 - copyBytes op1 opTmp s - return $! op1 `plusPtr` s) - -{-# INLINE CONLIKE liftIOB #-} -liftIOB :: BoundedPrim a -> BoundedPrim (IO a) -liftIOB (BE l io) = BE l (\xWrapped op -> do x <- xWrapped; io x op) --} - ------------------------------------------------------------------------------- --- Builder primitives from 'ByteString's. ------------------------------------------------------------------------------- - -{- --- | A 'FixedPrim' that always results in the same byte sequence given as a --- strict 'S.ByteString'. We can use this primitive to insert fixed ... -{-# INLINE CONLIKE constByteStringF #-} -constByteStringF :: S.ByteString -> FixedPrim () -constByteStringF bs = - FE len io - where - (S.PS fp off len) = bs - io _ op = do - copyBytes op (unsafeForeignPtrToPtr fp `plusPtr` off) len - touchForeignPtr fp - --- | Encode a fixed-length prefix of a strict 'S.ByteString' as-is. We can use --- this function to -{-# INLINE byteStringPrefixB #-} -byteStringTakeB :: Int -- ^ Length of the prefix. It should be smaller than - -- 100 bytes, as otherwise - -> BoundedPrim S.ByteString -byteStringTakeB n0 = - BE n io - where - n = max 0 n0 -- sanitize - - io (S.PS fp off len) op = do - let !s = min len n - copyBytes op (unsafeForeignPtrToPtr fp `plusPtr` off) s - touchForeignPtr fp - return $! op `plusPtr` s --} - -{- - -httpChunkedTransfer :: Builder -> Builder -httpChunkedTransfer = - encodeChunked 32 (word64HexFixedBound '0') - ((\_ -> ('\r',('\n',('\r','\n')))) >$< char8x4) - where - char8x4 = toB (char8 >*< char8 >*< char8 >*< char8) - - - -chunked :: Builder -> Builder -chunked = encodeChunked 16 word64VarFixedBound emptyB - --} - - - diff --git a/Data/ByteString/Builder/Prim/Internal/Base16.hs b/Data/ByteString/Builder/Prim/Internal/Base16.hs index 9fbb59b..a88da67 100644 --- a/Data/ByteString/Builder/Prim/Internal/Base16.hs +++ b/Data/ByteString/Builder/Prim/Internal/Base16.hs @@ -17,11 +17,8 @@ -- module Data.ByteString.Builder.Prim.Internal.Base16 ( EncodingTable - -- , upperTable , lowerTable - , encode4_as_8 , encode8_as_16h - -- , encode8_as_8_8 ) where import qualified Data.ByteString as S @@ -35,8 +32,8 @@ import System.IO.Unsafe (unsafePerformIO) import Foreign #endif --- Creating the encoding tables -------------------------------- +-- Creating the encoding table +------------------------------ -- TODO: Use table from C implementation. @@ -56,19 +53,6 @@ base16EncodingTable alphabet = do where ix = unsafeIndex alphabet -{- -{-# NOINLINE upperAlphabet #-} -upperAlphabet :: EncodingTable -upperAlphabet = - tableFromList $ map (fromIntegral . fromEnum) $ ['0'..'9'] ++ ['A'..'F'] - --- | The encoding table for hexadecimal values with upper-case characters; --- e.g., DEADBEEF. -{-# NOINLINE upperTable #-} -upperTable :: EncodingTable -upperTable = unsafePerformIO $ base16EncodingTable upperAlphabet --} - {-# NOINLINE lowerAlphabet #-} lowerAlphabet :: EncodingTable lowerAlphabet = @@ -80,19 +64,6 @@ lowerAlphabet = lowerTable :: EncodingTable lowerTable = unsafePerformIO $ base16EncodingTable lowerAlphabet - --- Encoding nibbles and octets ------------------------------- - --- | Encode a nibble as an octet. --- --- > encode4_as_8 lowerTable 10 = fromIntegral (char 'a') --- -{-# INLINE encode4_as_8 #-} -encode4_as_8 :: EncodingTable -> Word8 -> IO Word8 -encode4_as_8 table x = unsafeIndex table (2 * fromIntegral x + 1) --- TODO: Use a denser table to reduce cache utilization. - -- | Encode an octet as 16bit word comprising both encoded nibbles ordered -- according to the host endianness. Writing these 16bit to memory will write -- the nibbles in the correct order (i.e. big-endian). @@ -100,17 +71,3 @@ encode4_as_8 table x = unsafeIndex table (2 * fromIntegral x + 1) encode8_as_16h :: EncodingTable -> Word8 -> IO Word16 encode8_as_16h (EncodingTable table) = peekElemOff (castPtr $ unsafeForeignPtrToPtr table) . fromIntegral - -{- --- | Encode an octet as a big-endian ordered tuple of octets; i.e., --- --- > encode8_as_8_8 lowerTable 10 --- > = (fromIntegral (chr '0'), fromIntegral (chr 'a')) --- -{-# INLINE encode8_as_8_8 #-} -encode8_as_8_8 :: EncodingTable -> Word8 -> IO (Word8, Word8) -encode8_as_8_8 table x = - (,) <$> unsafeIndex table i <*> unsafeIndex table (i + 1) - where - i = 2 * fromIntegral x --} _______________________________________________ ghc-commits mailing list ghc-commits@haskell.org http://www.haskell.org/mailman/listinfo/ghc-commits