Safe Haskell | None |
---|---|
Language | GHC2021 |
Binrep.Get
Synopsis
- class Get a where
- runGet :: Get a => ByteString -> Either (ParseError Int Builder) (a, ByteString)
- cutting1 :: forall (st :: ZeroBitType) text a. ParserT st (ParseError Pos text) a -> [text] -> ParserT st (ParseError Pos text) a
- type Getter = Parser (ParseError Pos Builder)
- runGetter :: Getter a -> ByteString -> Either (ParseError Int Builder) (a, ByteString)
- getGenericNonSum :: (Generic a, GTraverseNonSum Get (Rep a), GAssertNotVoid a, GAssertNotSum a) => Getter a
- 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
- err1 :: forall text (st :: ZeroBitType) a. [text] -> ParserT st (ParseError Pos text) a
- getGenericSumRaw :: forall pt a. (Generic a, GTraverseSum Get Raw (Rep a), Get pt, GAssertNotVoid a, GAssertSum a) => (String -> pt) -> (pt -> pt -> Bool) -> Getter a
- cut1 :: forall (st :: ZeroBitType) text a. ParserT st (ParseError Pos text) a -> [text] -> ParserT st (ParseError Pos text) a
- 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
- newtype ViaGetC a = ViaGetC {
- unViaGetC :: a
- bzToFp :: KnownNat (CBLen a) => GetterC a -> Getter a
- getPrim :: (Prim' a, Typeable a) => Getter a
- typeRep' :: forall {k} (a :: k). Typeable a => TypeRep
- module Binrep.Get.Error
Documentation
Instances
(TypeError ENoEmpty :: Constraint) => Get Void Source # | |
Get Int8 Source # | 8-bit (1-byte) words do not require byte order in order to precisely define their representation. |
Get Word8 Source # | 8-bit (1-byte) words do not require byte order in order to precisely define their representation. |
Get SumType 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. |
Defined in Binrep.Get Methods get :: Getter ByteString Source # | |
Get () Source # | Unit type parses nothing. |
Defined in Binrep.Get | |
(Generic a, GTraverseNonSum Get (Rep a), GAssertNotVoid a, GAssertNotSum a) => Get (GenericallyNonSum a) Source # | |
Defined in Binrep.Get Methods get :: Getter (GenericallyNonSum a) Source # | |
(Prim' a, Typeable a) => Get (ViaPrim a) Source # | |
(GetC a, KnownNat (CBLen a)) => Get (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. |
Defined in Binrep.Type.NullTerminated Methods get :: Getter (NullTerminated a) Source # | |
Get (Thin ByteString) Source # | |
Defined in Binrep.Type.Thin | |
Get a => Get [a] Source # | Parse elements until EOF. Sometimes used at the "top" of binary formats. |
Defined in Binrep.Get | |
(TypeError ENoSum :: Constraint) => Get (Either a b) Source # | |
(bs ~ MagicBytes a, ParseReifyBytesW64 0 bs, ReifyBytesW64 bs, KnownNat (Length bs)) => Get (Magic a) Source # | |
(Get a, KnownNat n) => Get (NullPadded n a) Source # | |
Defined in Binrep.Type.NullPadded Methods get :: Getter (NullPadded n a) Source # | |
(LenNat pfx, GetSize a, Get pfx) => Get (SizePrefixed pfx a) Source # | |
Defined in Binrep.Type.Prefix.Size Methods get :: Getter (SizePrefixed pfx a) Source # | |
(Get a, KnownNat n) => Get (Sized n a) Source # | |
(Prim' a, ByteSwap a, Typeable a) => Get (ByteOrdered 'BigEndian a) Source # | |
Defined in Binrep.Get | |
(Prim' a, ByteSwap a, Typeable a) => Get (ByteOrdered 'LittleEndian a) Source # | |
Defined in Binrep.Get Methods get :: Getter (ByteOrdered 'LittleEndian a) Source # | |
Get (ByteOrdered end Int8) Source # | Byte order is irrelevant for 8-bit (1-byte) words. |
Defined in Binrep.Get | |
Get (ByteOrdered end Word8) Source # | Byte order is irrelevant for 8-bit (1-byte) words. |
Defined in Binrep.Get | |
(Get l, Get r) => Get (l, r) Source # | Parse tuples left-to-right. |
Defined in Binrep.Get | |
(Num a, Ord a) => Get (Refined (AsciiNat 2) a) Source # | Parse a binary (base 2) ASCII natural to any |
(Num a, Ord a) => Get (Refined (AsciiNat 8) a) Source # | Parse an octal (base 8) ASCII natural to any |
(Num a, Ord a) => Get (Refined (AsciiNat 10) a) Source # | Parse a decimal (base 10) ASCII natural to any |
(Num a, Ord a) => Get (Refined (AsciiNat 16) a) Source # | Parse a hex (base 16) ASCII natural to any Parses lower and upper case (mixed permitted). |
Get (Refined pr (Refined pl a)) => Get (Refined (And pl pr) a) Source # | |
(LenNat pfx, GetCount f, Get pfx, Get a) => Get (CountPrefixed pfx f a) Source # | |
Defined in Binrep.Type.Prefix.Count Methods get :: Getter (CountPrefixed pfx f a) Source # |
runGet :: Get a => ByteString -> Either (ParseError Int Builder) (a, ByteString) Source #
cutting1 :: forall (st :: ZeroBitType) text a. ParserT st (ParseError Pos text) a -> [text] -> ParserT st (ParseError Pos text) a Source #
runGetter :: Getter a -> ByteString -> Either (ParseError Int Builder) (a, ByteString) Source #
getGenericNonSum :: (Generic a, GTraverseNonSum Get (Rep a), GAssertNotVoid a, GAssertNotSum a) => Getter a Source #
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 #
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 #
module Binrep.Get.Error