bytestring-0.10.10.0: Fast, compact, strict and lazy byte strings with a list interface
Copyright(c) Don Stewart 2006-2008
(c) Duncan Coutts 2006-2012
LicenseBSD-style
Maintainerdons00@gmail.com, duncan@community.haskell.org
Stabilityunstable
Portabilitynon-portable
Safe HaskellUnsafe
LanguageHaskell98

Data.ByteString.Internal

Description

A module containing semi-public ByteString internals. This exposes the ByteString representation and low level construction functions. As such all the functions in this module are unsafe. The API is also not stable.

Where possible application should instead use the functions from the normal public interface modules, such as Data.ByteString.Unsafe. Packages that extend the ByteString system at a low level will need to use this module.

Synopsis

The ByteString type and representation

data ByteString Source #

A space-efficient representation of a Word8 vector, supporting many efficient operations.

A ByteString contains 8-bit bytes, or by using the operations from Data.ByteString.Char8 it can be interpreted as containing 8-bit characters.

Constructors

PS !(ForeignPtr Word8) !Int !Int 

Instances

Instances details
Eq ByteString # 
Instance details

Defined in Data.ByteString.Internal

Data ByteString # 
Instance details

Defined in Data.ByteString.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ByteString -> c ByteString Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ByteString Source #

toConstr :: ByteString -> Constr Source #

dataTypeOf :: ByteString -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ByteString) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteString) Source #

gmapT :: (forall b. Data b => b -> b) -> ByteString -> ByteString Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ByteString -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ByteString -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ByteString -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ByteString -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString Source #

Ord ByteString # 
Instance details

Defined in Data.ByteString.Internal

Read ByteString # 
Instance details

Defined in Data.ByteString.Internal

Show ByteString # 
Instance details

Defined in Data.ByteString.Internal

IsString ByteString # 
Instance details

Defined in Data.ByteString.Internal

Semigroup ByteString # 
Instance details

Defined in Data.ByteString.Internal

Monoid ByteString # 
Instance details

Defined in Data.ByteString.Internal

NFData ByteString # 
Instance details

Defined in Data.ByteString.Internal

Methods

rnf :: ByteString -> () Source #

Conversion with lists: packing and unpacking

unsafePackAddress :: Addr# -> IO ByteString Source #

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 unsafePackAddressLen if you know the length of the string statically.

An example:

literalFS = unsafePackAddress "literal"#

This function is unsafe. If you modify the buffer pointed to by the original Addr# this modification will be reflected in the resulting ByteString, breaking referential transparency.

Note this also won't work if your Addr# has embedded '\0' characters in the string, as strlen will return too short a length.

Low level imperative construction

create :: Int -> (Ptr Word8 -> IO ()) -> IO ByteString Source #

Create ByteString of size l and use action f to fill it's contents.

createUptoN :: Int -> (Ptr Word8 -> IO Int) -> IO ByteString Source #

Create ByteString of up to size size l and use action f to fill it's contents which returns its true size.

createAndTrim :: Int -> (Ptr Word8 -> IO Int) -> IO ByteString Source #

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) Source #

unsafeCreate :: Int -> (Ptr Word8 -> IO ()) -> ByteString Source #

A way of creating ByteStrings outside the IO monad. The Int argument gives the final size of the ByteString.

unsafeCreateUptoN :: Int -> (Ptr Word8 -> IO Int) -> ByteString Source #

Like unsafeCreate but instead of giving the final size of the ByteString, it is just an upper bound. The inner action returns the actual size. Unlike createAndTrim the ByteString is not reallocated if the final size is less than the estimated size.

mallocByteString :: Int -> IO (ForeignPtr a) Source #

Wrapper of mallocForeignPtrBytes with faster implementation for GHC

Conversion to and from ForeignPtrs

fromForeignPtr Source #

Arguments

:: ForeignPtr Word8 
-> Int

Offset

-> Int

Length

-> ByteString 

O(1) Build a ByteString from a ForeignPtr.

If you do not need the offset parameter then you do should be using unsafePackCStringLen or unsafePackCStringFinalizer instead.

toForeignPtr Source #

Arguments

:: ByteString 
-> (ForeignPtr Word8, Int, Int)

(ptr, offset, length)

O(1) Deconstruct a ForeignPtr from a ByteString

Utilities

nullForeignPtr :: ForeignPtr Word8 Source #

The 0 pointer. Used to indicate the empty Bytestring.

checkedAdd :: String -> Int -> Int -> Int Source #

Add two non-negative numbers. Errors out on overflow.

Standard C Functions

memcpy :: Ptr Word8 -> Ptr Word8 -> Int -> IO () Source #

cbits functions

Chars

w2c :: Word8 -> Char Source #

Conversion between Word8 and Char. Should compile to a no-op.

c2w :: Char -> Word8 Source #

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 Source #

Selects words corresponding to white-space characters in the Latin-1 range ordered by frequency.

isSpaceChar8 :: Char -> Bool Source #

Selects white-space characters in the Latin-1 range

Deprecated and unmentionable

accursedUnutterablePerformIO :: IO a -> a Source #

This "function" has a superficial similarity to unsafePerformIO but it is in fact a malevolent agent of chaos. It unpicks the seams of reality (and the IO monad) so that the normal rules no longer apply. It lulls you into thinking it is reasonable, but when you are not looking it stabs you in the back and aliases all of your mutable buffers. The carcass of many a seasoned Haskell programmer lie strewn at its feet.

Witness the trail of destruction:

Do not talk about "safe"! You do not know what is safe!

Yield not to its blasphemous call! Flee traveller! Flee or you will be corrupted and devoured!

inlinePerformIO :: IO a -> a Source #

Deprecated: If you think you know what you are doing, use unsafePerformIO. If you are sure you know what you are doing, use unsafeDupablePerformIO. If you enjoy sharing an address space with a malevolent agent of chaos, try accursedUnutterablePerformIO.