bytestring-0.10.10.0: Fast, compact, strict and lazy byte strings with a list interface

Copyright(c) Duncan Coutts 2012-2013
LicenseBSD-style
Maintainerduncan@community.haskell.org
Stabilitystable
Portabilityghc only
Safe HaskellTrustworthy
LanguageHaskell98

Data.ByteString.Short

Contents

Description

A compact representation suitable for storing short byte strings in memory.

In typical use cases it can be imported alongside Data.ByteString, e.g.

import qualified Data.ByteString       as B
import qualified Data.ByteString.Short as B
         (ShortByteString, toShort, fromShort)

Other ShortByteString operations clash with Data.ByteString or Prelude functions however, so they should be imported qualified with a different alias e.g.

import qualified Data.ByteString.Short as B.Short
Synopsis

The ShortByteString type

data ShortByteString Source #

A compact representation of a Word8 vector.

It has a lower memory overhead than a ByteString and and does not contribute to heap fragmentation. It can be converted to or from a ByteString (at the cost of copying the string data). It supports very few other operations.

It is suitable for use as an internal representation for code that needs to keep many short strings in memory, but it should not be used as an interchange type. That is, it should not generally be used in public APIs. The ByteString type is usually more suitable for use in interfaces; it is more flexible and it supports a wide range of operations.

Instances
Eq ShortByteString Source # 
Instance details

Defined in Data.ByteString.Short.Internal

Data ShortByteString Source # 
Instance details

Defined in Data.ByteString.Short.Internal

Methods

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

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

toConstr :: ShortByteString -> Constr #

dataTypeOf :: ShortByteString -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ShortByteString Source # 
Instance details

Defined in Data.ByteString.Short.Internal

Read ShortByteString Source # 
Instance details

Defined in Data.ByteString.Short.Internal

Show ShortByteString Source # 
Instance details

Defined in Data.ByteString.Short.Internal

IsString ShortByteString Source # 
Instance details

Defined in Data.ByteString.Short.Internal

Semigroup ShortByteString Source # 
Instance details

Defined in Data.ByteString.Short.Internal

Monoid ShortByteString Source # 
Instance details

Defined in Data.ByteString.Short.Internal

NFData ShortByteString Source # 
Instance details

Defined in Data.ByteString.Short.Internal

Methods

rnf :: ShortByteString -> () #

Memory overhead

With GHC, the memory overheads are as follows, expressed in words and in bytes (words are 4 and 8 bytes on 32 or 64bit machines respectively).

  • ByteString unshared: 9 words; 36 or 72 bytes.
  • ByteString shared substring: 5 words; 20 or 40 bytes.
  • ShortByteString: 4 words; 16 or 32 bytes.

For the string data itself, both ShortByteString and ByteString use one byte per element, rounded up to the nearest word. For example, including the overheads, a length 10 ShortByteString would take 16 + 12 = 28 bytes on a 32bit platform and 32 + 16 = 48 bytes on a 64bit platform.

These overheads can all be reduced by 1 word (4 or 8 bytes) when the ShortByteString or ByteString is unpacked into another constructor.

For example:

data ThingId = ThingId {-# UNPACK #-} !Int
                       {-# UNPACK #-} !ShortByteString

This will take 1 + 1 + 3 words (the ThingId constructor + unpacked Int + unpacked ShortByteString), plus the words for the string data.

Heap fragmentation

With GHC, the ByteString representation uses pinned memory, meaning it cannot be moved by the GC. This is usually the right thing to do for larger strings, but for small strings using pinned memory can lead to heap fragmentation which wastes space. The ShortByteString type (and the Text type from the text package) use unpinned memory so they do not contribute to heap fragmentation. In addition, with GHC, small unpinned strings are allocated in the same way as normal heap allocations, rather than in a separate pinned area.

Conversions

toShort :: ByteString -> ShortByteString Source #

O(n). Convert a ByteString into a ShortByteString.

This makes a copy, so does not retain the input string.

pack :: [Word8] -> ShortByteString Source #

O(n). Convert a list into a ShortByteString

unpack :: ShortByteString -> [Word8] Source #

O(n). Convert a ShortByteString into a list.

Other operations

null :: ShortByteString -> Bool Source #

O(1) Test whether a ShortByteString is empty.

length :: ShortByteString -> Int Source #

O(1) The length of a ShortByteString.

index :: ShortByteString -> Int -> Word8 Source #

O(1) ShortByteString index (subscript) operator, starting from 0.

Low level conversions

Packing CStrings and pointers

packCString :: CString -> IO ShortByteString Source #

O(n). Construct a new ShortByteString from a CString. The resulting ShortByteString is an immutable copy of the original CString, and is managed on the Haskell heap. The original CString must be null terminated.

Since: 0.10.10.0

packCStringLen :: CStringLen -> IO ShortByteString Source #

O(n). Construct a new ShortByteString from a CStringLen. The resulting ShortByteString is an immutable copy of the original CStringLen. The ShortByteString is a normal Haskell value and will be managed on the Haskell heap.

Since: 0.10.10.0

Using ByteStrings as CStrings

useAsCString :: ShortByteString -> (CString -> IO a) -> IO a Source #

O(n) construction. Use a ShortByteString with a function requiring a null-terminated CString. The CString is a copy and will be freed automatically; it must not be stored or used after the subcomputation finishes.

Since: 0.10.10.0

useAsCStringLen :: ShortByteString -> (CStringLen -> IO a) -> IO a Source #

O(n) construction. Use a ShortByteString with a function requiring a CStringLen. As for useAsCString this function makes a copy of the original ShortByteString. It must not be stored or used after the subcomputation finishes.

Since: 0.10.10.0