binrep
Safe HaskellNone
LanguageGHC2021

Binrep.Get

Synopsis

Documentation

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 SumType Source # 
Instance details

Defined in Binrep.Example.Sum

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 #

(Generic a, GTraverseNonSum Get (Rep a), GAssertNotVoid a, GAssertNotSum a) => Get (GenericallyNonSum a) Source # 
Instance details

Defined in Binrep.Get

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

Defined in Binrep.Get

Methods

get :: Getter (ViaPrim a) Source #

(GetC a, KnownNat (CBLen a)) => Get (ViaGetC a) Source # 
Instance details

Defined in Binrep.Get

Methods

get :: Getter (ViaGetC a) Source #

Get a => Get (NullTerminated a) Source #

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

The combinator doesn't permit distinguishing between the two possible failures: either there was no next null, or the inner parser didn't consume up to it.

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, ParseReifyBytesW64 0 bs, 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 #

(LenNat 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, Typeable a) => Get (ByteOrdered 'BigEndian a) Source # 
Instance details

Defined in Binrep.Get

(Prim' a, ByteSwap a, Typeable 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 #

(Num a, Ord a) => Get (Refined (AsciiNat 2) a) Source #

Parse a binary (base 2) ASCII natural to any Num type.

Instance details

Defined in Binrep.Type.AsciiNat

Methods

get :: Getter (Refined (AsciiNat 2) a) Source #

(Num a, Ord a) => Get (Refined (AsciiNat 8) a) Source #

Parse an octal (base 8) ASCII natural to any Num type.

Instance details

Defined in Binrep.Type.AsciiNat

Methods

get :: Getter (Refined (AsciiNat 8) a) Source #

(Num a, Ord a) => Get (Refined (AsciiNat 10) a) Source #

Parse a decimal (base 10) ASCII natural to any Num type.

Instance details

Defined in Binrep.Type.AsciiNat

Methods

get :: Getter (Refined (AsciiNat 10) a) Source #

(Num a, Ord a) => Get (Refined (AsciiNat 16) a) Source #

Parse a hex (base 16) ASCII natural to any Num type.

Parses lower and upper case (mixed permitted).

Instance details

Defined in Binrep.Type.AsciiNat

Methods

get :: Getter (Refined (AsciiNat 16) a) Source #

Get (Refined pr (Refined pl a)) => Get (Refined (And pl pr) a) Source # 
Instance details

Defined in Binrep.Get

Methods

get :: Getter (Refined (And pl pr) a) Source #

(LenNat 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 #

cutting1 :: forall (st :: ZeroBitType) text a. ParserT st (ParseError Pos text) a -> [text] -> ParserT st (ParseError Pos text) a Source #

Turn a Fail into a single error, or prepend it to any existing ones.

Use when wrapping other getters.

We reimplement cutting with a tweak. Otherwise, we'd have to join lists in the error case (instead of simply prepending).

getGenericSum :: forall {k} (sumtag :: k) pt a. (Generic a, GTraverseSum Get sumtag (Rep a), Get pt, GAssertNotVoid a, GAssertSum a) => ParseCstrTo sumtag pt -> (pt -> pt -> Bool) -> Getter a Source #

err1 :: forall text (st :: ZeroBitType) a. [text] -> ParserT st (ParseError Pos text) a Source #

Emit a single error. Use with flatparse primitives that only Fail.

getGenericSumRaw :: forall pt a. (Generic a, GTraverseSum Get Raw (Rep a), Get pt, GAssertNotVoid a, GAssertSum a) => (String -> pt) -> (pt -> pt -> Bool) -> Getter a Source #

cut1 :: forall (st :: ZeroBitType) text a. ParserT st (ParseError Pos text) a -> [text] -> ParserT st (ParseError Pos text) a Source #

Turn a Fail into a single error. (Re-emits existing Errors.)

Use when wrapping flatparse primitives that directly only Fail. (It's fine to use with combinators if the combinator itself doesn't Error.)

fpToBz :: forall (st :: ZeroBitType) text a r. ParserT st (ParseError Pos text) a -> Int# -> (a -> Int# -> ParserT st (ParseError Int text) r) -> ParserT st (ParseError Int text) r Source #

newtype ViaGetC a Source #

Constructors

ViaGetC 

Fields

Instances

Instances details
(GetC a, KnownNat (CBLen a)) => Get (ViaGetC a) Source # 
Instance details

Defined in Binrep.Get

Methods

get :: Getter (ViaGetC a) Source #

getPrim :: (Prim' a, Typeable a) => Getter a Source #

Parse any Prim'.

typeRep' :: forall {k} (a :: k). Typeable a => TypeRep Source #