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

Data.ByteString.Lazy.Internal

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 lazy ByteString type and representation

data ByteString Source #

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

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

Instances

Instances details
NFData ByteString Source # 
Instance details

Defined in Data.ByteString.Lazy.Internal

Methods

rnf :: ByteString -> () Source #

Monoid ByteString Source # 
Instance details

Defined in Data.ByteString.Lazy.Internal

Semigroup ByteString Source # 
Instance details

Defined in Data.ByteString.Lazy.Internal

Data ByteString Source # 
Instance details

Defined in Data.ByteString.Lazy.Internal

Methods

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

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

toConstr :: ByteString -> Constr #

dataTypeOf :: ByteString -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString ByteString Source #

Beware: fromString truncates multi-byte characters to octets. e.g. "枯朶に烏のとまりけり秋の暮" becomes �6k�nh~�Q��n�

Instance details

Defined in Data.ByteString.Lazy.Internal

IsList ByteString Source #

Since: bytestring-0.10.12.0

Instance details

Defined in Data.ByteString.Lazy.Internal

Associated Types

type Item ByteString 
Instance details

Defined in Data.ByteString.Lazy.Internal

Read ByteString Source # 
Instance details

Defined in Data.ByteString.Lazy.Internal

Show ByteString Source # 
Instance details

Defined in Data.ByteString.Lazy.Internal

Eq ByteString Source # 
Instance details

Defined in Data.ByteString.Lazy.Internal

Ord ByteString Source # 
Instance details

Defined in Data.ByteString.Lazy.Internal

Lift ByteString Source # 
Instance details

Defined in Data.ByteString.Lazy.Internal

Methods

lift :: Quote m => ByteString -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => ByteString -> Code m ByteString Source #

type Item ByteString Source # 
Instance details

Defined in Data.ByteString.Lazy.Internal

type LazyByteString = ByteString Source #

Type synonym for the lazy flavour of ByteString.

Since: bytestring-0.11.2.0

chunk :: StrictByteString -> ByteString -> ByteString Source #

Smart constructor for Chunk. Guarantees the data type invariant.

foldrChunks :: (StrictByteString -> a -> a) -> a -> ByteString -> a Source #

Consume the chunks of a lazy ByteString with a natural right fold.

foldlChunks :: (a -> StrictByteString -> a) -> a -> ByteString -> a Source #

Consume the chunks of a lazy ByteString with a strict, tail-recursive, accumulating left fold.

Data type invariant and abstraction function

invariant :: ByteString -> Bool Source #

The data type invariant: Every ByteString is either Empty or consists of non-null StrictByteStrings. All functions must preserve this.

checkInvariant :: ByteString -> ByteString Source #

Lazily checks that the given ByteString satisfies the data type's "no empty chunks" invariant, raising an exception in place of the first chunk that does not satisfy the invariant.

Chunk allocation sizes

defaultChunkSize :: Int Source #

The chunk size used for I/O. Currently set to 32k, less the memory management overhead

smallChunkSize :: Int Source #

The recommended chunk size. Currently set to 4k, less the memory management overhead

chunkOverhead :: Int Source #

The memory management overhead. Currently this is tuned for GHC only.

Conversion with lists: packing and unpacking

Conversions with strict ByteString

toStrict :: LazyByteString -> StrictByteString Source #

O(n) Convert a LazyByteString into a StrictByteString.

Note that this is an expensive operation that forces the whole LazyByteString into memory and then copies all the data. If possible, try to avoid converting back and forth between strict and lazy bytestrings.