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

Binrep.Get.Error

Description

Error data type definitions (shared between parsers).

Synopsis

Documentation

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.Error

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.Error

Methods

showsPrec :: Int -> E -> ShowS #

show :: E -> String #

showList :: [E] -> ShowS #

Eq E Source # 
Instance details

Defined in Binrep.Get.Error

Methods

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

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

type Rep E Source # 
Instance details

Defined in Binrep.Get.Error

data EMiddle Source #

Constructors

EBase EBase

Parse error with no further context.

EAnd E EBase

Somehow, we got two parse errors.

I have a feeling that seeing this indicates a problem in your code.

EGeneric

Parse error decorated with generic info.

Should not be set except by library code.

Fields

Instances

Instances details
Generic EMiddle Source # 
Instance details

Defined in Binrep.Get.Error

Associated Types

type Rep EMiddle :: Type -> Type #

Methods

from :: EMiddle -> Rep EMiddle x #

to :: Rep EMiddle x -> EMiddle #

Show EMiddle Source # 
Instance details

Defined in Binrep.Get.Error

Eq EMiddle Source # 
Instance details

Defined in Binrep.Get.Error

Methods

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

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

type Rep EMiddle Source # 
Instance details

Defined in Binrep.Get.Error

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.Error

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.Error

Methods

showsPrec :: Int -> EBase -> ShowS #

show :: EBase -> String #

showList :: [EBase] -> ShowS #

Eq EBase Source # 
Instance details

Defined in Binrep.Get.Error

Methods

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

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

type Rep EBase Source # 
Instance details

Defined in Binrep.Get.Error

type Rep EBase = D1 ('MetaData "EBase" "Binrep.Get.Error" "binrep-0.8.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.Error

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.Error

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.Error

Methods

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

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

type Rep (EGeneric e) Source # 
Instance details

Defined in Binrep.Get.Error

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.Error

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.Error

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

Defined in Binrep.Get.Error

type Rep (EGenericSum e) Source # 
Instance details

Defined in Binrep.Get.Error