Safe Haskell | None |
---|---|
Language | Haskell2010 |
Chunks of bytes. This is useful as a target for a builder
or as a way to read a large amount of whose size is unknown
in advance. Structurally, this type is similar to
Data.ByteString.Lazy.ByteString
. However, the type in this
module is strict in its spine. Additionally, none of the
Handle
functions perform lazy I/O.
Synopsis
- data Chunks
- = ChunksCons !Bytes !Chunks
- | ChunksNil
- length :: Chunks -> Int
- null :: Chunks -> Bool
- concat :: Chunks -> Bytes
- concatPinned :: Chunks -> Bytes
- concatU :: Chunks -> ByteArray
- concatPinnedU :: Chunks -> ByteArray
- reverse :: Chunks -> Chunks
- reverseOnto :: Chunks -> Chunks -> Chunks
- foldl' :: (a -> Word8 -> a) -> a -> Chunks -> a
- split :: Word8 -> Chunks -> [Bytes]
- fnv1a32 :: Chunks -> Word32
- fnv1a64 :: Chunks -> Word64
- fromBytes :: Bytes -> Chunks
- fromByteArray :: ByteArray -> Chunks
- unsafeCopy :: MutableByteArray s -> Int -> Chunks -> ST s Int
- hGetContents :: Handle -> IO Chunks
- readFile :: FilePath -> IO Chunks
- hPut :: Handle -> Chunks -> IO ()
- writeFile :: FilePath -> Chunks -> IO ()
Types
A cons-list of byte sequences.
Properties
Manipulate
concatPinned :: Chunks -> Bytes Source #
Variant of concat
that ensure that the resulting byte
sequence is pinned memory.
concatPinnedU :: Chunks -> ByteArray Source #
Variant of concatPinned
that returns an unsliced pinned byte sequence.
reverseOnto :: Chunks -> Chunks -> Chunks Source #
Variant of reverse
that allows the caller to provide
an initial list of chunks that the reversed chunks will
be pushed onto.
Folds
foldl' :: (a -> Word8 -> a) -> a -> Chunks -> a Source #
Left fold over all bytes in the chunks, strict in the accumulator.
Splitting
split :: Word8 -> Chunks -> [Bytes] Source #
Break chunks of bytes into contiguous pieces separated by the byte argument. This is a good producer for list fusion. For this function to perform well, each chunk should contain multiple separators. Any piece that spans multiple chunks must be copied.
Hashing
Create
fromByteArray :: ByteArray -> Chunks Source #
Variant of fromBytes
where the single chunk is unsliced.
Copy to buffer
:: MutableByteArray s | Destination |
-> Int | Destination offset |
-> Chunks | Source |
-> ST s Int | Returns the next index into the destination after the payload |
Copy the contents of the chunks into a mutable array. Precondition: The destination must have enough space to house the contents. This is not checked.
I/O with Handles
readFile :: FilePath -> IO Chunks Source #
Read an entire file strictly into chunks. If reading from a regular file, this makes an effort read the file into a single chunk.