Skip to content
Snippets Groups Projects
Commit 555df32c authored by glguy's avatar glguy
Browse files

Eliminate some shadowing

parent c7685d7b
No related branches found
No related tags found
No related merge requests found
...@@ -56,17 +56,17 @@ import Codec.Binary.UTF8.Generic (buncons) ...@@ -56,17 +56,17 @@ import Codec.Binary.UTF8.Generic (buncons)
-- | Converts a Haskell string into a UTF8 encoded bytestring. -- | Converts a Haskell string into a UTF8 encoded bytestring.
fromString :: String -> B.ByteString fromString :: String -> B.ByteString
fromString [] = B.empty fromString [] = B.empty
fromString xs = packChunks 32 xs fromString xs0 = packChunks 32 xs0
where where
packChunks n xs = case packUptoLenBytes n xs of packChunks n xs = case packUptoLenBytes n xs of
(bs, []) -> B.chunk bs B.Empty (bs, [] ) -> B.chunk bs B.Empty
(bs, xs) -> B.Chunk bs (packChunks (min (n * 2) B.smallChunkSize) xs) (bs, xs') -> B.Chunk bs (packChunks (min (n * 2) B.smallChunkSize) xs')
packUptoLenBytes :: Int -> String -> (S.ByteString, String) packUptoLenBytes :: Int -> String -> (S.ByteString, String)
packUptoLenBytes len xs = unsafeCreateUptoN' len $ \ptr -> do packUptoLenBytes len xs = unsafeCreateUptoN' len $ \ptr -> do
(end, xs) <- go ptr (ptr `plusPtr` (len-4)) xs (end, xs') <- go ptr (ptr `plusPtr` (len-4)) xs
return (end `minusPtr` ptr, xs) return (end `minusPtr` ptr, xs')
-- end is the last position at which you can write a whole 4 byte sequence safely -- end is the last position at which you can write a whole 4 byte sequence safely
go :: Ptr Word8 -> Ptr Word8 -> String -> IO (Ptr Word8, String) go :: Ptr Word8 -> Ptr Word8 -> String -> IO (Ptr Word8, String)
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment