primal-memory-0.1.0.0: Unified interface for memory managemenet.

Copyright(c) Alexey Kuleshevich 2020
LicenseBSD3
MaintainerAlexey Kuleshevich <alexey@kuleshevi.ch>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Prim.Memory.ByteString

Contents

Description

 
Synopsis

Documentation

newtype MByteString s Source #

Mutable version of a ByteString

Constructors

MByteString ByteString 
Instances
MemWrite MByteString Source # 
Instance details

Defined in Data.Prim.Memory.Internal

Methods

readOffMem :: (MonadPrim s m, Prim e) => MByteString s -> Off e -> m e Source #

readByteOffMem :: (MonadPrim s m, Prim e) => MByteString s -> Off Word8 -> m e Source #

writeOffMem :: (MonadPrim s m, Prim e) => MByteString s -> Off e -> e -> m () Source #

writeByteOffMem :: (MonadPrim s m, Prim e) => MByteString s -> Off Word8 -> e -> m () Source #

moveByteOffToMBytesMem :: (MonadPrim s m, Prim e) => MByteString s -> Off Word8 -> MBytes p s -> Off Word8 -> Count e -> m () Source #

moveByteOffToPtrMem :: (MonadPrim s m, Prim e) => MByteString s -> Off Word8 -> Ptr e -> Off Word8 -> Count e -> m () Source #

copyByteOffMem :: (MonadPrim s m, MemRead r, Prim e) => r -> Off Word8 -> MByteString s -> Off Word8 -> Count e -> m () Source #

moveByteOffMem :: (MonadPrim s m, MemWrite w', Prim e) => w' s -> Off Word8 -> MByteString s -> Off Word8 -> Count e -> m () Source #

setMem :: (MonadPrim s m, Prim e) => MByteString s -> Off e -> Count e -> e -> m () Source #

MemAlloc MByteString Source # 
Instance details

Defined in Data.Prim.Memory.Internal

Associated Types

type FrozenMem MByteString = (fa :: Type) Source #

PtrAccess s (MByteString s) Source # 
Instance details

Defined in Data.Prim.Memory.ForeignPtr

Methods

toForeignPtr :: MonadPrim s m => MByteString s -> m (ForeignPtr a) Source #

withPtrAccess :: MonadPrim s m => MByteString s -> (Ptr a -> m b) -> m b Source #

withNoHaltPtrAccess :: MonadUnliftPrim s m => MByteString s -> (Ptr a -> m b) -> m b Source #

type FrozenMem MByteString Source # 
Instance details

Defined in Data.Prim.Memory.Internal

Conversion

data Builder #

Builders denote sequences of bytes. They are Monoids where mempty is the zero-length sequence and mappend is concatenation, which runs in O(1).

toBuilderBytes :: Bytes p -> Builder Source #

Convert Bytes into a bytestring Builder

fromBuilderBytes :: Builder -> Bytes Pin Source #

O(n) - Allocate Bytes and fill them using the supplied Builder

ByteString

data ByteString #

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

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 :: (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 #

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

MemRead ByteString Source # 
Instance details

Defined in Data.Prim.Memory.Internal

PtrAccess s ByteString Source #

Read-only access, but it is not enforced.

Instance details

Defined in Data.Prim.Memory.ForeignPtr

Methods

toForeignPtr :: MonadPrim s m => ByteString -> m (ForeignPtr a) Source #

withPtrAccess :: MonadPrim s m => ByteString -> (Ptr a -> m b) -> m b Source #

withNoHaltPtrAccess :: MonadUnliftPrim s m => ByteString -> (Ptr a -> m b) -> m b Source #

toByteStringBytes :: Bytes Pin -> ByteString Source #

O(1) - Cast an immutable Bytes to an immutable ByteString

Since: 0.1.0

fromByteStringBytes :: Typeable p => ByteString -> Bytes p Source #

O(n) - Allocate Bytes and fill them with the contents of a strict ByteString

fromLazyByteStringBytes :: ByteString -> Bytes Pin Source #

O(n) - Allocate Bytes and fill them with the contents of a lazy ByteString

withPtrByteString :: MonadPrim s m => ByteString -> (Ptr a -> m b) -> m b Source #

ShortByteString

data ShortByteString #

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.

Constructors

SBS ByteArray# 
Instances
Eq ShortByteString 
Instance details

Defined in Data.ByteString.Short.Internal

Data ShortByteString 
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 
Instance details

Defined in Data.ByteString.Short.Internal

Read ShortByteString 
Instance details

Defined in Data.ByteString.Short.Internal

Show ShortByteString 
Instance details

Defined in Data.ByteString.Short.Internal

IsString ShortByteString 
Instance details

Defined in Data.ByteString.Short.Internal

Semigroup ShortByteString 
Instance details

Defined in Data.ByteString.Short.Internal

Monoid ShortByteString 
Instance details

Defined in Data.ByteString.Short.Internal

NFData ShortByteString 
Instance details

Defined in Data.ByteString.Short.Internal

Methods

rnf :: ShortByteString -> () #

MemRead ShortByteString Source # 
Instance details

Defined in Data.Prim.Memory.Internal

toShortByteStringBytes :: Bytes p -> ShortByteString Source #

O(1) - Cast an immutable Bytes to an immutable ShortByteString

Since: 0.1.0

fromShortByteStringBytes :: ShortByteString -> Bytes Inc Source #

O(1) - Cast an immutable ShortByteString to an immutable Bytes

Since: 0.1.0