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

Binrep.Get

Synopsis

Documentation

type Getter a = Parser E a Source #

class Get a where Source #

Methods

get :: Getter a Source #

Parse from binary.

Instances

Instances details
Get Void Source #

Impossible to parse Void.

Instance details

Defined in Binrep.Get

Methods

get :: Getter Void Source #

Get Int8 Source # 
Instance details

Defined in Binrep.Get

Methods

get :: Getter Int8 Source #

Get Word8 Source # 
Instance details

Defined in Binrep.Get

Methods

get :: Getter Word8 Source #

Get DCS Source # 
Instance details

Defined in Binrep.Example

Methods

get :: Getter DCS Source #

Get DSS Source # 
Instance details

Defined in Binrep.Example

Methods

get :: Getter DSS Source #

Get DU Source # 
Instance details

Defined in Binrep.Example

Methods

get :: Getter DU Source #

Get DX Source # 
Instance details

Defined in Binrep.Example

Methods

get :: Getter DX Source #

Get Tar Source # 
Instance details

Defined in Binrep.Example.Tar

Methods

get :: Getter Tar Source #

Get Tiff Source # 
Instance details

Defined in Binrep.Example.Tiff

Methods

get :: Getter Tiff Source #

Get WavHeader Source # 
Instance details

Defined in Binrep.Example.Wav

Get ByteString Source # 
Instance details

Defined in Binrep.Get

(bs ~ MagicBytes (TiffMagic end), ReifyBytes bs, irep ~ I 'U 'I4 end, Get irep) => Get (TiffBody end) Source # 
Instance details

Defined in Binrep.Example.Tiff

Methods

get :: Getter (TiffBody end) Source #

Get (AsciiNat 8) Source # 
Instance details

Defined in Binrep.Type.AsciiNat

Methods

get :: Getter (AsciiNat 8) Source #

Get (AsByteString 'C) Source # 
Instance details

Defined in Binrep.Type.ByteString

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

Defined in Binrep.Type.ByteString

Methods

get :: Getter (AsByteString ('Pascal size end)) Source #

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

Defined in Binrep.Type.Magic.UTF8

Methods

get :: Getter (MagicUTF8 str) Source #

Get a => Get [a] Source #

Parse heterogeneous lists in order. No length indicator, so either fails or succeeds by reaching EOF. Probably not what you usually want, but sometimes used at the "top" of binary formats.

Instance details

Defined in Binrep.Get

Methods

get :: Getter [a] Source #

Get a => Get (Table 'Strong a) Source # 
Instance details

Defined in Binrep.Example.FileTable

Methods

get :: Getter (Table 'Strong a) Source #

KnownNat n => Get (TarNat n) Source # 
Instance details

Defined in Binrep.Example.Tar

Methods

get :: Getter (TarNat n) Source #

(bs ~ MagicBytes a, ReifyBytes bs) => Get (Magic a) Source # 
Instance details

Defined in Binrep.Type.Magic

Methods

get :: Getter (Magic a) Source #

(Get a, BLen a, KnownNat n) => Get (NullPadded n a) Source #

Safety: we assert actual length is within expected length (in order to calculate how much padding to parse).

Note that the consumer probably doesn't care about the content of the padding, just that the data is chunked correctly. I figure we care about correctness here, so it'd be nice to know about the padding well-formedness (i.e. that it's all nulls).

TODO maybe better definition via isolate

Instance details

Defined in Binrep.Type.NullPadded

Methods

get :: Getter (NullPadded n a) Source #

(Get a, KnownNat n) => Get (Sized n a) Source # 
Instance details

Defined in Binrep.Type.Sized

Methods

get :: Getter (Sized n a) Source #

(Get a, KnownNat n) => Get (Vector n a) Source # 
Instance details

Defined in Binrep.Type.Vector

Methods

get :: Getter (Vector n a) Source #

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

Defined in Binrep.Get

Methods

get :: Getter (a, b) Source #

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

Defined in Binrep.Type.Int

Methods

get :: Getter (I 'S 'I1 e) Source #

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

Defined in Binrep.Type.Int

Methods

get :: Getter (I 'S 'I2 'BE) Source #

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

Defined in Binrep.Type.Int

Methods

get :: Getter (I 'S 'I2 'LE) Source #

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

Defined in Binrep.Type.Int

Methods

get :: Getter (I 'S 'I4 'BE) Source #

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

Defined in Binrep.Type.Int

Methods

get :: Getter (I 'S 'I4 'LE) Source #

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

Defined in Binrep.Type.Int

Methods

get :: Getter (I 'S 'I8 'BE) Source #

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

Defined in Binrep.Type.Int

Methods

get :: Getter (I 'S 'I8 'LE) Source #

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

Defined in Binrep.Type.Int

Methods

get :: Getter (I 'U 'I1 e) Source #

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

Defined in Binrep.Type.Int

Methods

get :: Getter (I 'U 'I2 'BE) Source #

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

Defined in Binrep.Type.Int

Methods

get :: Getter (I 'U 'I2 'LE) Source #

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

Defined in Binrep.Type.Int

Methods

get :: Getter (I 'U 'I4 'BE) Source #

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

Defined in Binrep.Type.Int

Methods

get :: Getter (I 'U 'I4 'LE) Source #

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

Defined in Binrep.Type.Int

Methods

get :: Getter (I 'U 'I8 'BE) Source #

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

Defined in Binrep.Type.Int

Methods

get :: Getter (I 'U 'I8 'LE) Source #

(itype ~ I 'U size end, irep ~ IRep 'U size, Get itype, Integral irep, Get a, KnownNat (MaxBound irep)) => Get (LenPfx size end a) Source # 
Instance details

Defined in Binrep.Type.LenPfx

Methods

get :: Getter (LenPfx size end a) Source #

(VarintContinuation cont, Integral i, Bits i) => Get (Varnat 'Bijective cont 'BE i) Source #

TODO nothing to test against - unsure if correct

Instance details

Defined in Binrep.Type.Varint

Methods

get :: Getter (Varnat 'Bijective cont 'BE i) Source #

(VarintContinuation cont, Integral i, Bits i) => Get (Varnat 'Bijective cont 'LE i) Source #

Git varint (cont=on), BPS (beat patches) (cont=off)

Instance details

Defined in Binrep.Type.Varint

Methods

get :: Getter (Varnat 'Bijective cont 'LE i) Source #

(VarintContinuation cont, Integral i, Bits i) => Get (Varnat 'Redundant cont 'BE i) Source #

VLQ (cont=on)

Instance details

Defined in Binrep.Type.Varint

Methods

get :: Getter (Varnat 'Redundant cont 'BE i) Source #

(VarintContinuation cont, Integral i, Bits i) => Get (Varnat 'Redundant cont 'LE i) Source #

protobuf (cont=on), LEB128 (cont=on)

not truly infinite length since shifters take Int, but practically infinite

Instance details

Defined in Binrep.Type.Varint

Methods

get :: Getter (Varnat 'Redundant cont 'LE i) Source #

data E Source #

Constructors

EBase EBase 
EGeneric 

Fields

Instances

Instances details
Generic E Source # 
Instance details

Defined in Binrep.Get

Associated Types

type Rep E :: Type -> Type #

Methods

from :: E -> Rep E x #

to :: Rep E x -> E #

Show E Source # 
Instance details

Defined in Binrep.Get

Methods

showsPrec :: Int -> E -> ShowS #

show :: E -> String #

showList :: [E] -> ShowS #

Eq E Source # 
Instance details

Defined in Binrep.Get

Methods

(==) :: E -> E -> Bool #

(/=) :: E -> E -> Bool #

type Rep E Source # 
Instance details

Defined in Binrep.Get

data EBase Source #

Constructors

ENoVoid 
EFail 
EExpectedByte Word8 Word8

expected first, got second

EOverlong BLenT BLenT

expected first, got second

EExpected ByteString ByteString

expected first, got second

EFailNamed String

known fail

EFailParse String ByteString Word8

parse fail (where you parse a larger object, then a smaller one in it)

ERanOut Natural

ran out of input, needed precisely n bytes for this part (n > 0)

Instances

Instances details
Generic EBase Source # 
Instance details

Defined in Binrep.Get

Associated Types

type Rep EBase :: Type -> Type #

Methods

from :: EBase -> Rep EBase x #

to :: Rep EBase x -> EBase #

Show EBase Source # 
Instance details

Defined in Binrep.Get

Methods

showsPrec :: Int -> EBase -> ShowS #

show :: EBase -> String #

showList :: [EBase] -> ShowS #

Eq EBase Source # 
Instance details

Defined in Binrep.Get

Methods

(==) :: EBase -> EBase -> Bool #

(/=) :: EBase -> EBase -> Bool #

type Rep EBase Source # 
Instance details

Defined in Binrep.Get

type Rep EBase = D1 ('MetaData "EBase" "Binrep.Get" "binrep-0.3.1-inplace" 'False) (((C1 ('MetaCons "ENoVoid" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EFail" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EExpectedByte" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8)) :+: C1 ('MetaCons "EOverlong" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BLenT) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BLenT)))) :+: ((C1 ('MetaCons "EExpected" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)) :+: C1 ('MetaCons "EFailNamed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "EFailParse" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8))) :+: C1 ('MetaCons "ERanOut" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural)))))

data EGenericSum Source #

Instances

Instances details
Generic EGenericSum Source # 
Instance details

Defined in Binrep.Get

Associated Types

type Rep EGenericSum :: Type -> Type #

Show EGenericSum Source # 
Instance details

Defined in Binrep.Get

Eq EGenericSum Source # 
Instance details

Defined in Binrep.Get

type Rep EGenericSum Source # 
Instance details

Defined in Binrep.Get

getEWrap :: Get a => (E -> E) -> Getter a Source #

TODO confirm correct operation (error combination)

class GetWith (r :: TYPE rep) a | a -> r where Source #

A type that can be parsed from binary given some environment.

Making this levity polymorphic makes things pretty strange, but is useful. See Binrep.Example.FileTable.

Methods

getWith :: r -> Getter a Source #

Parse from binary with the given environment.

Instances

Instances details
Get a => GetWith Addr# (Entry 'Strong a) Source # 
Instance details

Defined in Binrep.Example.FileTable

Methods

getWith :: Addr# -> Getter (Entry 'Strong a) Source #