uni-util-2.3.0.1: Utilities for the uniform workbench

Safe HaskellNone

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

Documentation

hWrite :: HasBinary a IO => Handle -> a -> IO ()Source

Write an (a) to a Handle

hRead :: HasBinary a IO => Handle -> IO aSource

Read an (a) from a Handle

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 aSource

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 whereSource

Methods

writeBinSource

Arguments

:: WriteBinary m 
-> a 
-> m ()

Given a consumer of binary data, and an (a), write out the (a)

readBinSource

Arguments

:: ReadBinary m 
-> m a

Given a source of binary data, provide an (a)

Instances

Monad m => HasBinary Bool m 
Monad m => HasBinary Char m 
Monad m => HasBinary Int m 
Monad m => HasBinary Int32 m 
Monad m => HasBinary Integer m 
Monad m => HasBinary Word m 
Monad m => HasBinary Word32 m 
Monad m => HasBinary () m 
Monad m => HasBinary CSize m 
Monad m => HasBinary ClockTime m 
HasBinary Byte m 
MonadIO m => HasBinary ICStringLen m 
(Monad m, HasBinary a m) => HasBinary [a] m 
(Monad m, HasBinary a m) => HasBinary (Maybe a) m 
HasBinary (WrapBinary m) m 
(Monad m, Enum a) => HasBinary (ViaEnum a) m 
(Read a, Show a, Monad m) => HasBinary (ReadShow a) m 
(Monad m, HasWrapper wrapper m) => HasBinary (Wrapped wrapper) m 
(Monad m, Integral integral, Bits integral) => HasBinary (Unsigned integral) m 
(Monad m, StringClass a) => HasBinary (Str a) m 
(Monad m, HasBinary a m, HasBinary b m) => HasBinary (Either a b) m 
(Monad m, HasBinary v1 m, HasBinary v2 m) => HasBinary (v1, v2) m 
Monad m => HasBinary (Bytes, Int) m 
(HasBinary (from, to) m, Ord from, MonadIO m) => HasBinary (Registry from to) m 
(Monad m, HasBinary v1 m, HasBinary (v2, v3) m) => HasBinary (v1, v2, v3) m 
(Monad m, HasBinary v1 m, HasBinary (v2, v3, v4) m) => HasBinary (v1, v2, v3, v4) m 
(Monad m, HasBinary v1 m, HasBinary (v2, v3, v4, v5) m) => HasBinary (v1, v2, v3, v4, v5) m 
(Monad m, HasBinary v1 m, HasBinary v2 m, HasBinary v3 m, HasBinary v4 m, HasBinary v5 m) => HasBinary (Choice5 v1 v2 v3 v4 v5) m 
(Monad m, HasBinary v1 m, HasBinary (v2, v3, v4, v5, v6) m) => HasBinary (v1, v2, v3, v4, v5, v6) m 
(Monad m, HasBinary v1 m, HasBinary (v2, v3, v4, v5, v6, v7) m) => HasBinary (v1, v2, v3, v4, v5, v6, v7) m 

data WriteBinary m Source

A consumer of binary data

Constructors

WriteBinary 

Fields

writeByte :: Byte -> m ()

write one byte

writeBytes :: Bytes -> Int -> m ()

write multiple bytes

data ReadBinary m Source

A source of binary data

Constructors

ReadBinary 

Fields

readByte :: m Byte

read one byte

readBytes :: Int -> m Bytes

read multiple bytes

data BinArea Source

Somewhere to where you write binary data in memory.

type StateBinArea = StateT BinArea IOSource

a state monad containing the BinArea.

mkEmptyBinArea :: Int -> IO BinAreaSource

Create an empty BinArea, given the initial size.

writeBinaryBinArea :: WriteBinary StateBinAreaSource

A BinArea as somewhere to put binary data.

closeBinArea :: BinArea -> IO (Bytes, Int)Source

Return all the data currently in the BinArea

mkBinArea :: (Bytes, Int) -> BinAreaSource

Turn binary data in memory into a BinArea (so that you can read from it).

readBinaryBinArea :: ReadBinary StateBinAreaSource

A BinArea as a source of binary data.

liftWriteBinary :: (forall a. m a -> n a) -> WriteBinary m -> WriteBinary nSource

Transform the monad used by a WriteBinary

liftReadBinary :: (forall a. m a -> n a) -> ReadBinary m -> ReadBinary nSource

Transform the monad used by a ReadBinary