| Safe Haskell | None | 
|---|---|
| Language | Haskell98 | 
Util.Binary
Description
Library for converting types to and from binary, so that they can be written to and from files, stored compactly in memory, and so on.
This is a preliminary version of the library, hence I have decided not to optimise heavily, beyond putting in strictness annotations in where they seem appropriate.
A good place to start optimising would probably be the separate Bytes libary.
See also BinaryInstances, which declares instances for the standard types (and one or two others), BinaryUtils, which contains (mostly) material for declaring new instances, BinaryExtras, which contains other miscellaneous utilities, and finally BinaryAll which just imports and reexports everything.
Synopsis
- hWrite :: HasBinary a IO => Handle -> a -> IO ()
- hRead :: HasBinary a IO => Handle -> IO a
- writeToBytes :: HasBinary a StateBinArea => a -> IO (Bytes, Int)
- writeToBytes0 :: HasBinary a StateBinArea => Int -> a -> IO (Bytes, Int)
- readFromBytes :: HasBinary a StateBinArea => (Bytes, Int) -> IO a
- class HasBinary a m where
- data WriteBinary m = WriteBinary {- writeByte :: Byte -> m ()
- writeBytes :: Bytes -> Int -> m ()
 
- data ReadBinary m = ReadBinary {}
- toWriteBinaryHandle :: Handle -> WriteBinary IO
- toReadBinaryHandle :: Handle -> ReadBinary IO
- data BinArea
- type StateBinArea = StateT BinArea IO
- mkEmptyBinArea :: Int -> IO BinArea
- writeBinaryBinArea :: WriteBinary StateBinArea
- closeBinArea :: BinArea -> IO (Bytes, Int)
- mkBinArea :: (Bytes, Int) -> BinArea
- readBinaryBinArea :: ReadBinary StateBinArea
- checkFullBinArea :: BinArea -> IO ()
- liftWriteBinary :: (forall a. m a -> n a) -> WriteBinary m -> WriteBinary n
- liftReadBinary :: (forall a. m a -> n a) -> ReadBinary m -> ReadBinary n
Documentation
writeToBytes :: HasBinary a StateBinArea => a -> IO (Bytes, Int) Source #
Write an (a) to memory.  The Int is the length of the area.
writeToBytes0 :: HasBinary a StateBinArea => Int -> a -> IO (Bytes, Int) Source #
Write an (a) to memory. The integer argument is an initial guess at the number of bytes that will be needed. This should be greater than 0. If it is too small, there will be unnecessary reallocations; if too large, too much memory will be used.
readFromBytes :: HasBinary a StateBinArea => (Bytes, Int) -> IO a Source #
Read a value from binary data in memory.  The Int is the length,
and there will be an error if this is either too small or too large. 
class HasBinary a m where Source #
Methods
Arguments
| :: WriteBinary m | |
| -> a | |
| -> m () | Given a consumer of binary data, and an (a), write out the (a) | 
Arguments
| :: ReadBinary m | |
| -> m a | Given a source of binary data, provide an (a) | 
Instances
data WriteBinary m Source #
A consumer of binary data
Constructors
| WriteBinary | |
| Fields 
 | |
data ReadBinary m Source #
A source of binary data
toReadBinaryHandle :: Handle -> ReadBinary IO Source #
writeBinaryBinArea :: WriteBinary StateBinArea Source #
A BinArea as somewhere to put binary data.
mkBinArea :: (Bytes, Int) -> BinArea Source #
Turn binary data in memory into a BinArea (so that you can
read from it). 
readBinaryBinArea :: ReadBinary StateBinArea Source #
A BinArea as a source of binary data.
checkFullBinArea :: BinArea -> IO () Source #
liftWriteBinary :: (forall a. m a -> n a) -> WriteBinary m -> WriteBinary n Source #
Transform the monad used by a WriteBinary
liftReadBinary :: (forall a. m a -> n a) -> ReadBinary m -> ReadBinary n Source #
Transform the monad used by a ReadBinary