Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Builder = Builder (forall s. MutableByteArray# s -> Int# -> Int# -> Commits s -> State# s -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #))
- data BuilderState s = BuilderState (MutableByteArray# s) Int# Int# !(Commits s)
- data Commits s
- = Mutable (MutableByteArray# s) Int# !(Commits s)
- | Immutable ByteArray# Int# Int# !(Commits s)
- | Initial
- pasteST :: Builder -> BuilderState s -> ST s (BuilderState s)
- pasteIO :: Builder -> BuilderState RealWorld -> IO (BuilderState RealWorld)
- fromEffect :: Int -> (forall s. MutableByteArray s -> Int -> ST s Int) -> Builder
- newBuilderState :: Int -> ST s (BuilderState s)
- closeBuilderState :: BuilderState s -> Commits s
- reverseCommitsOntoChunks :: Chunks -> Commits s -> ST s Chunks
- commitsOntoChunks :: Chunks -> Commits s -> ST s Chunks
- copyReverseCommits :: MutableByteArray s -> Int -> Commits s -> ST s Int
- addCommitsLength :: Int -> Commits s -> Int
- commitDistance :: MutableByteArray# s -> Int# -> Commits s -> Int#
- commitDistance1 :: MutableByteArray# s -> Int# -> MutableByteArray# s -> Int# -> Commits s -> Int#
- stringUtf8 :: String -> Builder
- cstring :: CString -> Builder
Types
An unmaterialized sequence of bytes that may be pasted into a mutable byte array.
Builder (forall s. MutableByteArray# s -> Int# -> Int# -> Commits s -> State# s -> (# State# s, MutableByteArray# s, Int#, Int#, Commits s #)) |
data BuilderState s Source #
A list of committed chunks along with the chunk currently being
written to. This is kind of like a non-empty variant of Commmits
but with the additional invariant that the head chunk is a mutable
byte array.
BuilderState (MutableByteArray# s) Int# Int# !(Commits s) |
Mutable | |
| |
Immutable | |
| |
Initial |
Execution
pasteST :: Builder -> BuilderState s -> ST s (BuilderState s) Source #
Run a builder, performing an in-place update on the state.
The BuilderState
argument must not be reused after being passed
to this function. That is, its use must be affine.
pasteIO :: Builder -> BuilderState RealWorld -> IO (BuilderState RealWorld) Source #
Construction
Builder State
newBuilderState :: Int -> ST s (BuilderState s) Source #
Create an empty BuilderState
with a buffer of the given size.
closeBuilderState :: BuilderState s -> Commits s Source #
Push the active chunk onto the top of the commits.
The BuilderState
argument must not be reused after being passed
to this function. That is, its use must be affine.
Finalization
reverseCommitsOntoChunks :: Chunks -> Commits s -> ST s Chunks Source #
Cons the chunks from a list of Commits
onto an initial
Chunks
list (this argument is often ChunksNil
). This reverses
the order of the chunks, which is desirable since builders assemble
Commits
with the chunks backwards. This performs an in-place shrink
and freezes any mutable byte arrays it encounters. Consequently,
these must not be reused.
commitsOntoChunks :: Chunks -> Commits s -> ST s Chunks Source #
Variant of reverseCommitsOntoChunks
that does not reverse
the order of the commits. Since commits are built backwards by
consing, this means that the chunks appended to the front will
be backwards. Within each chunk, however, the bytes will be in
the correct order.
Unlike reverseCommitsOntoChunks
, this function is not tail
recursive.
:: MutableByteArray s | Destination |
-> Int | Destination range successor |
-> Commits s | Source |
-> ST s Int |
Copy the contents of the chunks into a mutable array, reversing the order of the chunks. Precondition: The destination must have enough space to house the contents. This is not checked.
addCommitsLength :: Int -> Commits s -> Int Source #
Add the total number of bytes in the commits to first argument.
Commit Distance
commitDistance :: MutableByteArray# s -> Int# -> Commits s -> Int# Source #
Compute the number of bytes between the last byte and the offset
specified in a chunk. Precondition: the chunk must exist in the
list of committed chunks. This relies on mutable byte arrays having
identity (e.g. it uses sameMutableByteArray#
).
commitDistance1 :: MutableByteArray# s -> Int# -> MutableByteArray# s -> Int# -> Commits s -> Int# Source #
Variant of commitDistance where you get to supply a head of the commit list that has not yet been committed.
Safe Functions
These functions are actually completely safe, but they are defined
here because they are used by typeclass instances. Import them from
Data.Bytes.Builder
instead.