darcs-2.1.99.0: a distributed, interactive, smart revision control systemSource codeContentsIndex
ByteStringUtils
Portabilityportable
Stabilityexperimental
Maintainerdroundy@abridgegame.org
Description
GZIp and MMap IO for ByteStrings, and miscellaneous functions for Data.ByteString
Synopsis
unsafeWithInternals :: ByteString -> (Ptr Word8 -> Int -> IO a) -> IO a
unpackPSfromUTF8 :: ByteString -> String
gzReadFilePS :: FilePath -> IO ByteString
mmapFilePS :: FilePath -> IO ByteString
gzWriteFilePS :: FilePath -> ByteString -> IO ()
gzWriteFilePSs :: FilePath -> [ByteString] -> IO ()
ifHeadThenTail :: Word8 -> ByteString -> Maybe ByteString
dropSpace :: ByteString -> ByteString
breakSpace :: ByteString -> (ByteString, ByteString)
linesPS :: ByteString -> [ByteString]
unlinesPS :: [ByteString] -> ByteString
hashPS :: ByteString -> Int32
breakFirstPS :: Char -> ByteString -> Maybe (ByteString, ByteString)
breakLastPS :: Char -> ByteString -> Maybe (ByteString, ByteString)
substrPS :: ByteString -> ByteString -> Maybe Int
readIntPS :: ByteString -> Maybe (Int, ByteString)
is_funky :: ByteString -> Bool
fromHex2PS :: ByteString -> ByteString
fromPS2Hex :: ByteString -> ByteString
betweenLinesPS :: ByteString -> ByteString -> ByteString -> Maybe ByteString
break_after_nth_newline :: Int -> ByteString -> Maybe (ByteString, ByteString)
break_before_nth_newline :: Int -> ByteString -> (ByteString, ByteString)
intercalate
Documentation
unsafeWithInternals :: ByteString -> (Ptr Word8 -> Int -> IO a) -> IO aSource
Do something with the internals of a PackedString. Beware of altering the contents!
unpackPSfromUTF8 :: ByteString -> StringSource
gzReadFilePS :: FilePath -> IO ByteStringSource
mmapFilePS :: FilePath -> IO ByteStringSource
Like readFilePS, this reads an entire file directly into a ByteString, but it is even more efficient. It involves directly mapping the file to memory. This has the advantage that the contents of the file never need to be copied. Also, under memory pressure the page may simply be discarded, wile in the case of readFilePS it would need to be written to swap. If you read many small files, mmapFilePS will be less memory-efficient than readFilePS, since each mmapFilePS takes up a separate page of memory. Also, you can run into bus errors if the file is modified. NOTE: as with readFilePS, the string representation in the file is assumed to be ISO-8859-1.
gzWriteFilePS :: FilePath -> ByteString -> IO ()Source
gzWriteFilePSs :: FilePath -> [ByteString] -> IO ()Source
ifHeadThenTail :: Word8 -> ByteString -> Maybe ByteStringSource
dropSpace :: ByteString -> ByteStringSource

dropSpace efficiently returns the ByteString argument with white space Chars removed from the front. It is more efficient than calling dropWhile for removing whitespace. I.e.

 dropWhile isSpace == dropSpace
breakSpace :: ByteString -> (ByteString, ByteString)Source

breakSpace returns the pair of ByteStrings when the argument is broken at the first whitespace byte. I.e.

 break isSpace == breakSpace
linesPS :: ByteString -> [ByteString]Source
unlinesPS :: [ByteString] -> ByteStringSource

This function acts exactly like the Prelude unlines function, or like Data.ByteString.Char8 unlines, but with one important difference: it will produce a string which may not end with a newline! That is:

 unlinesPS ["foo", "bar"]

evaluates to "foo\nbar", not "foo\nbar\n"! This point should hold true for linesPS as well.

TODO: rename this function.

hashPS :: ByteString -> Int32Source
breakFirstPS :: Char -> ByteString -> Maybe (ByteString, ByteString)Source
breakLastPS :: Char -> ByteString -> Maybe (ByteString, ByteString)Source
substrPS :: ByteString -> ByteString -> Maybe IntSource
readIntPS :: ByteString -> Maybe (Int, ByteString)Source
readIntPS skips any whitespace at the beginning of its argument, and reads an Int from the beginning of the PackedString. If there is no integer at the beginning of the string, it returns Nothing, otherwise it just returns the int read, along with a B.ByteString containing the remainder of its input.
is_funky :: ByteString -> BoolSource
fromHex2PS :: ByteString -> ByteStringSource
fromPS2Hex :: ByteString -> ByteStringSource
betweenLinesPS :: ByteString -> ByteString -> ByteString -> Maybe ByteStringSource
betweenLinesPS returns the B.ByteString between the two lines given, or Nothing if they do not appear.
break_after_nth_newline :: Int -> ByteString -> Maybe (ByteString, ByteString)Source
break_before_nth_newline :: Int -> ByteString -> (ByteString, ByteString)Source
intercalate
Produced by Haddock version 2.4.2