binrep-0.2.0: Encode precise binary representations directly in types
Safe HaskellSafe-Inferred
LanguageHaskell2010

Binrep.Put

Synopsis

Documentation

class Put a where Source #

Methods

put :: a -> Builder Source #

Serialize to binary.

Instances

Instances details
Put Int8 Source # 
Instance details

Defined in Binrep.Put

Methods

put :: Int8 -> Builder Source #

Put Word8 Source # 
Instance details

Defined in Binrep.Put

Methods

put :: Word8 -> Builder Source #

Put DCS Source # 
Instance details

Defined in Binrep.Example

Methods

put :: DCS -> Builder Source #

Put DSS Source # 
Instance details

Defined in Binrep.Example

Methods

put :: DSS -> Builder Source #

Put DU Source # 
Instance details

Defined in Binrep.Example

Methods

put :: DU -> Builder Source #

Put Tar Source # 
Instance details

Defined in Binrep.Example.Tar

Methods

put :: Tar -> Builder Source #

Put Tiff Source # 
Instance details

Defined in Binrep.Example.Tiff

Methods

put :: Tiff -> Builder Source #

Put WavHeader Source # 
Instance details

Defined in Binrep.Example.Wav

Put ByteString Source #

Serialize the bytestring as-is.

Careful -- the only way you're going to be able to parse this is to read until EOF.

Instance details

Defined in Binrep.Put

(bs ~ MagicVals (TiffMagic end), ByteVals bs, irep ~ I 'U 'I4 end, Put irep) => Put (TiffBody end) Source # 
Instance details

Defined in Binrep.Example.Tiff

Methods

put :: TiffBody end -> Builder Source #

Put (AsciiNat 8) Source # 
Instance details

Defined in Binrep.Type.AsciiNat

Methods

put :: AsciiNat 8 -> Builder Source #

Put (AsByteString 'C) Source # 
Instance details

Defined in Binrep.Type.ByteString

(itype ~ I 'U size end, irep ~ IRep 'U size, Put itype, Num irep) => Put (AsByteString ('Pascal size end)) Source # 
Instance details

Defined in Binrep.Type.ByteString

Methods

put :: AsByteString ('Pascal size end) -> Builder Source #

KnownSymbol str => Put (MagicUTF8 str) Source # 
Instance details

Defined in Binrep.Type.Magic.UTF8

Methods

put :: MagicUTF8 str -> Builder Source #

Put a => Put [a] Source #

Serialize each element in order. No length indicator, so parse until either error or EOF. Usually not what you want, but sometimes used at the "top" of binary formats.

Instance details

Defined in Binrep.Put

Methods

put :: [a] -> Builder Source #

(Put a, BLen a) => Put (Table 'Strong a) Source # 
Instance details

Defined in Binrep.Example.FileTable

Methods

put :: Table 'Strong a -> Builder Source #

KnownNat n => Put (TarNat n) Source #

No need to check for underflow etc. as TarNat guarantees good sizing.

Instance details

Defined in Binrep.Example.Tar

Methods

put :: TarNat n -> Builder Source #

(bs ~ MagicVals a, ByteVals bs) => Put (Magic a) Source #

Forces magic values to be individual bytes.

Instance details

Defined in Binrep.Type.Magic

Methods

put :: Magic a -> Builder Source #

(Put a, BLen a, KnownNat n) => Put (NullPadded n a) Source # 
Instance details

Defined in Binrep.Type.NullPadded

Methods

put :: NullPadded n a -> Builder Source #

Put a => Put (Sized n a) Source # 
Instance details

Defined in Binrep.Type.Sized

Methods

put :: Sized n a -> Builder Source #

Put a => Put (Vector n a) Source # 
Instance details

Defined in Binrep.Type.Vector

Methods

put :: Vector n a -> Builder Source #

(Put a, Put b) => Put (a, b) Source # 
Instance details

Defined in Binrep.Put

Methods

put :: (a, b) -> Builder Source #

Put (I 'S 'I1 e) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: I 'S 'I1 e -> Builder Source #

Put (I 'S 'I2 'BE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: I 'S 'I2 'BE -> Builder Source #

Put (I 'S 'I2 'LE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: I 'S 'I2 'LE -> Builder Source #

Put (I 'S 'I4 'BE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: I 'S 'I4 'BE -> Builder Source #

Put (I 'S 'I4 'LE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: I 'S 'I4 'LE -> Builder Source #

Put (I 'S 'I8 'BE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: I 'S 'I8 'BE -> Builder Source #

Put (I 'S 'I8 'LE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: I 'S 'I8 'LE -> Builder Source #

Put (I 'U 'I1 e) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: I 'U 'I1 e -> Builder Source #

Put (I 'U 'I2 'BE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: I 'U 'I2 'BE -> Builder Source #

Put (I 'U 'I2 'LE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: I 'U 'I2 'LE -> Builder Source #

Put (I 'U 'I4 'BE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: I 'U 'I4 'BE -> Builder Source #

Put (I 'U 'I4 'LE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: I 'U 'I4 'LE -> Builder Source #

Put (I 'U 'I8 'BE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: I 'U 'I8 'BE -> Builder Source #

Put (I 'U 'I8 'LE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: I 'U 'I8 'LE -> Builder Source #

(itype ~ I 'U size end, irep ~ IRep 'U size, Put a, Put itype, Num irep) => Put (LenPfx size end a) Source # 
Instance details

Defined in Binrep.Type.LenPfx

Methods

put :: LenPfx size end a -> Builder Source #

runPut :: Put a => a -> ByteString Source #

Run the serializer.

class PutWith r a where Source #

Put with inlined checks via an environment.

Minimal complete definition

Nothing

Methods

putWith :: r -> a -> Either String Builder Source #

Attempt to serialize to binary with the given environment.

default putWith :: Put a => r -> a -> Either String Builder Source #

Instances

Instances details
Put a => PutWith r [a] Source # 
Instance details

Defined in Binrep.Put

Methods

putWith :: r -> [a] -> Either String Builder Source #

putWithout :: Put a => a -> Either String Builder Source #

Helper for wrapping a BinRep into a BinRepWith (for encoding).

runPutWith :: PutWith r a => r -> a -> Either String ByteString Source #

Run the serializer with the given environment.