binrep-0.6.0: Encode precise binary representations directly in types
Safe HaskellSafe-Inferred
LanguageGHC2021

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
(TypeError ENoEmpty :: Constraint) => Get Void Source # 
Instance details

Defined in Binrep.Get

Methods

get :: Getter Void Source #

Get Int8 Source #

8-bit (1-byte) words do not require byte order in order to precisely define their representation.

Instance details

Defined in Binrep.Get

Methods

get :: Getter Int8 Source #

Get Word8 Source #

8-bit (1-byte) words do not require byte order in order to precisely define their representation.

Instance details

Defined in Binrep.Get

Methods

get :: Getter Word8 Source #

Get ByteString Source #

Return the rest of the input.

A plain unannotated bytestring isn't very useful -- you'll usually want to null-terminate or length-prefix it.

Note that this _does_ perform work: we make a new bytestring so we don't rely on the input bytestring. To use the input bytestring directly, see Binrep.Type.Thin.

Instance details

Defined in Binrep.Get

Get () Source #

Unit type parses nothing.

Instance details

Defined in Binrep.Get

Methods

get :: Getter () Source #

Get a => Get (Identity a) Source # 
Instance details

Defined in Binrep.Get

Methods

get :: Getter (Identity a) Source #

Prim' a => Get (ViaPrim a) Source # 
Instance details

Defined in Binrep.Get

Methods

get :: Getter (ViaPrim a) Source #

Get a => Get (NullTerminated a) Source #

We may parse any null-terminated data using a special flatparse combinator.

Instance details

Defined in Binrep.Type.NullTerminated

Get (Thin ByteString) Source # 
Instance details

Defined in Binrep.Type.Thin

Get a => Get [a] Source #

Parse elements until EOF. Sometimes used at the "top" of binary formats.

Instance details

Defined in Binrep.Get

Methods

get :: Getter [a] Source #

(TypeError ENoSum :: Constraint) => Get (Either a b) Source # 
Instance details

Defined in Binrep.Get

Methods

get :: Getter (Either a b) Source #

(bs ~ MagicBytes a, ReifyBytesW64 bs, KnownNat (Length bs)) => Get (Magic a) Source # 
Instance details

Defined in Binrep.Type.Magic

Methods

get :: Getter (Magic a) Source #

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

Defined in Binrep.Type.NullPadded

Methods

get :: Getter (NullPadded n a) Source #

(Prefix pfx, GetSize a, Get pfx) => Get (SizePrefixed pfx a) Source # 
Instance details

Defined in Binrep.Type.Prefix.Size

Methods

get :: Getter (SizePrefixed pfx 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 #

(Prim' a, ByteSwap a) => Get (ByteOrdered 'BigEndian a) Source # 
Instance details

Defined in Binrep.Get

(Prim' a, ByteSwap a) => Get (ByteOrdered 'LittleEndian a) Source # 
Instance details

Defined in Binrep.Get

Get (ByteOrdered end Int8) Source #

Byte order is irrelevant for 8-bit (1-byte) words.

Instance details

Defined in Binrep.Get

Methods

get :: Getter (ByteOrdered end Int8) Source #

Get (ByteOrdered end Word8) Source #

Byte order is irrelevant for 8-bit (1-byte) words.

Instance details

Defined in Binrep.Get

(Get l, Get r) => Get (l, r) Source #

Parse tuples left-to-right.

Instance details

Defined in Binrep.Get

Methods

get :: Getter (l, r) Source #

GenericTraverse Get Source # 
Instance details

Defined in Binrep.Get

Associated Types

type GenericTraverseF Get :: Type -> Type #

type GenericTraverseC Get a #

GenericTraverseSum Get Source # 
Instance details

Defined in Binrep.Get

(Prefix pfx, GetCount f, Get pfx, Get a) => Get (CountPrefixed pfx f a) Source # 
Instance details

Defined in Binrep.Type.Prefix.Count

Methods

get :: Getter (CountPrefixed pfx f a) Source #

type GenericTraverseF Get Source # 
Instance details

Defined in Binrep.Get

type GenericTraverseC Get a Source # 
Instance details

Defined in Binrep.Get

data E Source #

Structured parse error.

Constructors

E Int EMiddle 
EFail

Unhandled parse error.

You get this if you don't change a flatparse fail to an error.

Should not be set except by library code.

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

type Rep E

data EBase Source #

Constructors

EExpectedByte Word8 Word8

expected first, got second

EOverlong Int Int

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 Int

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

Actually a Natural, but we use Int because that's what flatparse uses internally.

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.6.0-inplace" 'False) ((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 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: 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 Int)))))

data EGeneric e Source #

A generic context layer for a parse error of type e.

Recursive: parse errors occurring in fields are wrapped up here. (Those errors may also have a generic context layer.)

Making this explicitly recursive may seem strange, but it clarifies that this data type is to be seen as a layer over a top-level type.

Constructors

EGenericSum (EGenericSum e)

Parse error relating to sum types (constructors).

EGenericField

Parse error in a constructor field.

Fields

Instances

Instances details
Generic (EGeneric e) Source # 
Instance details

Defined in Binrep.Get

Associated Types

type Rep (EGeneric e) :: Type -> Type #

Methods

from :: EGeneric e -> Rep (EGeneric e) x #

to :: Rep (EGeneric e) x -> EGeneric e #

Show e => Show (EGeneric e) Source # 
Instance details

Defined in Binrep.Get

Methods

showsPrec :: Int -> EGeneric e -> ShowS #

show :: EGeneric e -> String #

showList :: [EGeneric e] -> ShowS #

Eq e => Eq (EGeneric e) Source # 
Instance details

Defined in Binrep.Get

Methods

(==) :: EGeneric e -> EGeneric e -> Bool #

(/=) :: EGeneric e -> EGeneric e -> Bool #

type Rep (EGeneric e) Source # 
Instance details

Defined in Binrep.Get

data EGenericSum e Source #

Constructors

EGenericSumTag e

Parse error parsing prefix tag.

EGenericSumTagNoMatch

Unable to match a constructor to the parsed prefix tag.

Fields

  • [String]

    constructors tested

  • Text

    prettified prefix tag

Instances

Instances details
Generic (EGenericSum e) Source # 
Instance details

Defined in Binrep.Get

Associated Types

type Rep (EGenericSum e) :: Type -> Type #

Methods

from :: EGenericSum e -> Rep (EGenericSum e) x #

to :: Rep (EGenericSum e) x -> EGenericSum e #

Show e => Show (EGenericSum e) Source # 
Instance details

Defined in Binrep.Get

Eq e => Eq (EGenericSum e) Source # 
Instance details

Defined in Binrep.Get

type Rep (EGenericSum e) Source # 
Instance details

Defined in Binrep.Get

getPrim :: forall a. Prim' a => Getter a Source #

Parse any Prim'.