bytezap-1.6.0: Bytestring builder with zero intermediate allocation
Safe HaskellNone
LanguageGHC2021

Bytezap.Poke

Synopsis

Documentation

type Poke# s Source #

Arguments

 = Addr#

buffer pointer

-> Int#

buffer offset

-> State# s

state token

-> (# State# s, Int# #)

(state token, next offset)

Unboxed buffer write operation.

The next offset must be greater than or equal to the input buffer offset. This is not checked.

Note that the only way to find out the length of a write is to perform it. But you can't perform a length without providing a correctly-sized buffer. Thus, you may only use a Poke# when you have a buffer large enough to fit its maximum write length-- which in turn means means you must track write lengths separately. (Write does this.)

I provide this highly unsafe, seemingly unhelpful type because it's a requirement for Write, and here I can guarantee performance better because I don't need to worry about laziness.

We cannot be polymorphic on the pointer type unless we box the pointer. We thus limit ourselves to writing to Addr#s, and not MutableByteArray#s. (I figure we're most interested in ByteStrings, which use Addr#.)

Note that if we did provide write length, then the next offset might appear superfluous. But that next offset is usually already calculated, and may be passed directly to sequenced writes, unlike if we returned a write length which would need to be added to the original offset.

newtype Poke s Source #

Poke newtype wrapper.

Constructors

Poke 

Fields

Instances

Instances details
Monoid (Poke s) Source #

The empty buffer write simply returns its state token and offset.

Instance details

Defined in Bytezap.Poke

Methods

mempty :: Poke s #

mappend :: Poke s -> Poke s -> Poke s #

mconcat :: [Poke s] -> Poke s #

Semigroup (Poke s) Source #

Sequence two buffer writes left-to-right.

Instance details

Defined in Bytezap.Poke

Methods

(<>) :: Poke s -> Poke s -> Poke s #

sconcat :: NonEmpty (Poke s) -> Poke s #

stimes :: Integral b => b -> Poke s -> Poke s #

unsafeRunPokeBS :: Int -> Poke RealWorld -> ByteString Source #

Execute a Poke at a fresh ByteString of the given length.

unsafeRunPokeBSUptoN :: Int -> Poke RealWorld -> ByteString Source #

Execute a Poke at a fresh ByteString of the given maximum length. Does not reallocate if final size is less than estimated.

unsafeRunPoke :: MonadPrim s m => Poke s -> Ptr Word8 -> m Int Source #

Execute a Poke at a pointer. Returns the number of bytes written.

The pointer must be a mutable buffer with enough space to hold the poke. Absolutely none of this is checked. Use with caution. Sensible uses:

  • implementing pokes to ByteStrings and the like
  • executing known-length (!!) pokes to known-length (!!) buffers e.g. together with allocaBytes

prim :: Prim' a => a -> Poke s Source #

Poke a type via its Prim' instance.

replicateByte :: Int -> Word8 -> Poke RealWorld Source #

essentially memset

fromStructPoke :: Int -> Poke s -> Poke s Source #

Use a struct poke as a regular poke.

To do this, we must associate a constant byte length with an existing poker. Note that pokers don't expose the type of the data they are serializing, so this is a very clumsy operation by itself. You should only be using this when you have such types in scope, and the constant length should be obtained in a sensible manner (e.g. KnownSizeOf for generic struct pokers, or your own constant size class if you're doing funky stuff).

toStructPoke :: Poke s -> Poke s Source #

Use a struct poke as a regular poke by throwing away the return offset.