|
|
|
|
|
Description |
A module containing semi-public ByteString internals. This exposes
the ByteString representation and low level construction functions.
Modules which extend the ByteString system will need to use this module
while ideally most users will be able to make do with the public interface
modules.
|
|
Synopsis |
|
|
|
|
The ByteString type and representation
|
|
data ByteString |
A space-efficient representation of a Word8 vector, supporting many
efficient operations. A ByteString contains 8-bit characters only.
Instances of Eq, Ord, Read, Show, Data, Typeable
| Constructors | | Instances | |
|
|
newtype LazyByteString |
A space-efficient representation of a Word8 vector, supporting many
efficient operations. A ByteString contains 8-bit characters only.
Instances of Eq, Ord, Read, Show, Data, Typeable
| Constructors | | Instances | |
|
|
Unchecked access
|
|
unsafeHead :: ByteString -> Word8 |
A variety of head for non-empty ByteStrings. unsafeHead omits the
check for the empty case, so there is an obligation on the programmer
to provide a proof that the ByteString is non-empty.
|
|
unsafeTail :: ByteString -> ByteString |
A variety of tail for non-empty ByteStrings. unsafeTail omits the
check for the empty case. As with unsafeHead, the programmer must
provide a separate proof that the ByteString is non-empty.
|
|
unsafeIndex :: ByteString -> Int -> Word8 |
Unsafe ByteString index (subscript) operator, starting from 0, returning a Word8
This omits the bounds check, which means there is an accompanying
obligation on the programmer to ensure the bounds are checked in some
other way.
|
|
unsafeTake :: Int -> ByteString -> ByteString |
A variety of take which omits the checks on n so there is an
obligation on the programmer to provide a proof that 0 <= n <= length xs.
|
|
unsafeDrop :: Int -> ByteString -> ByteString |
A variety of drop which omits the checks on n so there is an
obligation on the programmer to provide a proof that 0 <= n <= length xs.
|
|
Low level introduction and elimination
|
|
empty :: ByteString |
O(1) The empty ByteString
|
|
create :: Int -> (Ptr Word8 -> IO ()) -> IO ByteString |
Create ByteString of size l and use action f to fill it's contents.
|
|
createAndTrim :: Int -> (Ptr Word8 -> IO Int) -> IO ByteString |
Given the maximum size needed and a function to make the contents
of a ByteString, createAndTrim makes the ByteString. The generating
function is required to return the actual final size (<= the maximum
size), and the resulting byte array is realloced to this size.
createAndTrim is the main mechanism for creating custom, efficient
ByteString functions, using Haskell or C functions to fill the space.
|
|
createAndTrim' :: Int -> (Ptr Word8 -> IO (Int, Int, a)) -> IO (ByteString, a) |
|
mallocByteString :: Int -> IO (ForeignPtr a) |
Wrapper of mallocForeignPtrBytes with faster implementation
for GHC 6.5 builds newer than 060606
|
|
unsafeCreate :: Int -> (Ptr Word8 -> IO ()) -> ByteString |
A way of creating ByteStrings outside the IO monad. The Int
argument gives the final size of the ByteString. Unlike
createAndTrim the ByteString is not reallocated if the final size
is less than the estimated size.
|
|
unsafeUseAsCString :: ByteString -> (CString -> IO a) -> IO a |
O(1) construction Use a ByteString with a function requiring a
CString. Warning: modifying the CString will affect the
ByteString. Why is this function unsafe? It relies on the null
byte at the end of the ByteString to be there. Unless you can
guarantee the null byte, you should use the safe version, which will
copy the string first.
|
|
unsafeUseAsCStringLen :: ByteString -> (CStringLen -> IO a) -> IO a |
O(1) construction Use a ByteString with a function requiring a
CStringLen.
|
|
fromForeignPtr :: ForeignPtr Word8 -> Int -> ByteString |
O(1) Build a ByteString from a ForeignPtr
|
|
toForeignPtr :: ByteString -> (ForeignPtr Word8, Int, Int) |
O(1) Deconstruct a ForeignPtr from a ByteString
|
|
packCStringFinalizer :: Ptr Word8 -> Int -> IO () -> IO ByteString |
O(1) Construct a ByteString given a C Ptr Word8 buffer, a
length, and an IO action representing a finalizer. This function is
not available on Hugs.
|
|
packAddress :: Addr# -> ByteString |
O(n) Pack a null-terminated sequence of bytes, pointed to by an
Addr# (an arbitrary machine address assumed to point outside the
garbage-collected heap) into a ByteString. A much faster way to
create an Addr# is with an unboxed string literal, than to pack a
boxed string. A unboxed string literal is compiled to a static char
[] by GHC. Establishing the length of the string requires a call to
strlen(3), so the Addr# must point to a null-terminated buffer (as
is the case with string# literals in GHC). Use unsafePackAddress
if you know the length of the string statically.
An example:
literalFS = packAddress "literal"#
|
|
unsafePackAddress :: Int -> Addr# -> ByteString |
O(1) unsafePackAddress provides constant-time construction of
ByteStrings -- which is ideal for string literals. It packs a
null-terminated sequence of bytes into a ByteString, given a raw
Addr to the string, and the length of the string. Make sure the
length is correct, otherwise use the safer packAddress (where the
length will be calculated once at runtime).
|
|
unsafeFinalize :: ByteString -> IO () |
Explicitly run the finaliser associated with a ByteString.
Further references to this value may generate invalid memory
references. This operation is unsafe, as there may be other
ByteStrings referring to the same underlying pages. If you use
this, you need to have a proof of some kind that all ByteStrings
ever generated from the underlying byte array are no longer live.
|
|
Utilities
|
|
inlinePerformIO :: IO a -> a |
Just like unsafePerformIO, but we inline it. Big performance gains as
it exposes lots of things to further inlining
|
|
nullForeignPtr :: ForeignPtr Word8 |
|
countOccurrences :: (Storable a, Num a) => Ptr a -> Ptr Word8 -> Int -> IO () |
Count the number of occurrences of each byte.
|
|
Standard C Functions
|
|
c_strlen :: CString -> IO CSize |
|
c_malloc :: CSize -> IO (Ptr Word8) |
|
c_free :: Ptr Word8 -> IO () |
|
c_free_finalizer :: FunPtr (Ptr Word8 -> IO ()) |
|
memchr :: Ptr Word8 -> Word8 -> CSize -> IO (Ptr Word8) |
|
memcmp :: Ptr Word8 -> Ptr Word8 -> CSize -> IO CInt |
|
memcpy :: Ptr Word8 -> Ptr Word8 -> CSize -> IO () |
|
memmove :: Ptr Word8 -> Ptr Word8 -> CSize -> IO () |
|
memset :: Ptr Word8 -> Word8 -> CSize -> IO (Ptr Word8) |
|
cbits functions
|
|
c_reverse :: Ptr Word8 -> Ptr Word8 -> CULong -> IO () |
|
c_intersperse :: Ptr Word8 -> Ptr Word8 -> CULong -> Word8 -> IO () |
|
c_maximum :: Ptr Word8 -> CULong -> IO Word8 |
|
c_minimum :: Ptr Word8 -> CULong -> IO Word8 |
|
c_count :: Ptr Word8 -> CULong -> Word8 -> IO CULong |
|
Internal GHC magic
|
|
memcpy_ptr_baoff :: Ptr a -> RawBuffer -> CInt -> CSize -> IO (Ptr ()) |
|
Chars
|
|
w2c :: Word8 -> Char |
Conversion between Word8 and Char. Should compile to a no-op.
|
|
c2w :: Char -> Word8 |
Unsafe conversion between Char and Word8. This is a no-op and
silently truncates to 8 bits Chars > '\255'. It is provided as
convenience for ByteString construction.
|
|
isSpaceWord8 :: Word8 -> Bool |
|
Produced by Haddock version 0.8 |