Copyright | (c) 2010 Simon Meier (c) 2010 Jasper van der Jeugt |
---|---|
License | BSD3-style (see LICENSE) |
Maintainer | Simon Meier <iridcode@gmail.com> |
Stability | experimental |
Portability | tested on GHC only |
Safe Haskell | None |
Language | Haskell98 |
A general and efficient write type that allows for the easy construction of builders for (smallish) bounded size writes to a buffer.
FIXME: Improve documentation.
- data Poke
- runPoke :: Poke -> Ptr Word8 -> IO (Ptr Word8)
- pokeN :: Int -> (Ptr Word8 -> IO ()) -> Poke
- data Write
- runWrite :: Write -> Ptr Word8 -> IO (Ptr Word8)
- getBound :: Write -> Int
- getBound' :: String -> (a -> Write) -> Int
- getPoke :: Write -> Poke
- exactWrite :: Int -> (Ptr Word8 -> IO ()) -> Write
- boundedWrite :: Int -> Poke -> Write
- writeLiftIO :: (a -> Write) -> IO a -> Write
- writeIf :: (a -> Bool) -> (a -> Write) -> (a -> Write) -> a -> Write
- writeEq :: Eq a => a -> (a -> Write) -> (a -> Write) -> a -> Write
- writeOrdering :: (a -> Ordering) -> (a -> Write) -> (a -> Write) -> (a -> Write) -> a -> Write
- writeOrd :: Ord a => a -> (a -> Write) -> (a -> Write) -> (a -> Write) -> a -> Write
- fromWrite :: Write -> Builder
- fromWriteSingleton :: (a -> Write) -> a -> Builder
- fromWriteList :: (a -> Write) -> [a] -> Builder
- writeStorable :: Storable a => a -> Write
- fromStorable :: Storable a => a -> Builder
- fromStorables :: Storable a => [a] -> Builder
Poking a buffer
pokeN :: Int -> (Ptr Word8 -> IO ()) -> Poke Source
pokeN size io
creates a write that denotes the writing of size
bytes
to a buffer using the IO action io
. Note that io
MUST write EXACTLY size
bytes to the buffer!
Writing to abuffer
A write of a bounded number of bytes.
When defining a function write :: a -> Write
for some a
, then it is
important to ensure that the bound on the number of bytes written is
data-independent. Formally,
forall x y. getBound (write x) = getBound (write y)
The idea is that this data-independent bound is specified such that the compiler can optimize the check, if there are enough free bytes in the buffer, to a single subtraction between the pointer to the next free byte and the pointer to the end of the buffer with this constant bound of the maximal number of bytes to be written.
Extract the maximal number of bytes that this write could write in any case. Assumes that the bound of the write is data-independent.
exactWrite :: Int -> (Ptr Word8 -> IO ()) -> Write Source
exactWrite size io
creates a bounded write that can later be converted to
a builder that writes exactly size
bytes. Note that io
MUST write
EXACTLY size
bytes to the buffer!
boundedWrite :: Int -> Poke -> Write Source
boundedWrite size write
creates a bounded write from a write
that does
not write more than size
bytes.
writeLiftIO :: (a -> Write) -> IO a -> Write Source
writeLiftIO io write
creates a write executes the io
action to compute
the value that is then written.
writeEq :: Eq a => a -> (a -> Write) -> (a -> Write) -> a -> Write Source
Compare the value to a test value and use the first write action for the equal case and the second write action for the non-equal case.
writeOrdering :: (a -> Ordering) -> (a -> Write) -> (a -> Write) -> (a -> Write) -> a -> Write Source
TODO: Test this. It might well be too difficult to use. FIXME: Better name required!
writeOrd :: Ord a => a -> (a -> Write) -> (a -> Write) -> (a -> Write) -> a -> Write Source
A write combinator useful to build decision trees for deciding what value to write with a constant bound on the maximal number of bytes written.
Constructing builders from writes
fromWriteSingleton :: (a -> Write) -> a -> Builder Source
fromWriteList :: (a -> Write) -> [a] -> Builder Source
Construct a Builder
writing a list of data one element at a time.
Writing Storable
s
writeStorable :: Storable a => a -> Write Source
Write a storable value.
fromStorable :: Storable a => a -> Builder Source
A builder that serializes a storable value. No alignment is done.
fromStorables :: Storable a => [a] -> Builder Source
A builder that serializes a list of storable values by writing them consecutively. No alignment is done. Parsing information needs to be provided externally.