prosidyc-0.2.0.0: A DSL for processing Prosidy documents.
Copyright©2020 James Alexander Feldman-Crough
LicenseMPL-2.0
Maintaineralex@fldcr.com
Safe HaskellNone
LanguageHaskell2010

Prosidy.Compile.Error

Description

 
Synopsis

Documentation

data Error a Source #

Enumerates the errors thrown when

Constructors

Custom a

A custom error, allowing extensibility.

ParseError Key String

Thrown when parsing a setting fails.

Required Key

Thrown when a setting was required to be set, but wasn't provided.

ExpectedTag TagKind Key

Thrown when matching against a Tag, and another node was found, or the input tag's Key didn't match the specified key.

ExpectedParagraph

Thrown when matching against paragraph and an unexpected node was encountered.

ExpectedText

Thrown when matching against text and an unexpected node was encountered.

ExpectedBreak

Thrown when matching against an explicit break and an unexpected node was encountered.

EmptyMatch

Thrown when a match has no cases to check against.

UnknownMetadata (HashSet (MetadataKind, Key))

Thrown when an unknown property or setting is encountered when checking that properties and settings conform to strictly known keys.

Group (Maybe Location) (ErrorSet a)

Used to group a set of errors thrown at the same point in a tree.

Instances

Instances details
Eq a => Eq (Error a) Source # 
Instance details

Defined in Prosidy.Compile.Error

Methods

(==) :: Error a -> Error a -> Bool #

(/=) :: Error a -> Error a -> Bool #

Show a => Show (Error a) Source # 
Instance details

Defined in Prosidy.Compile.Error

Methods

showsPrec :: Int -> Error a -> ShowS #

show :: Error a -> String #

showList :: [Error a] -> ShowS #

Generic (Error a) Source # 
Instance details

Defined in Prosidy.Compile.Error

Associated Types

type Rep (Error a) :: Type -> Type #

Methods

from :: Error a -> Rep (Error a) x #

to :: Rep (Error a) x -> Error a #

Hashable a => Hashable (Error a) Source # 
Instance details

Defined in Prosidy.Compile.Error

Methods

hashWithSalt :: Int -> Error a -> Int #

hash :: Error a -> Int #

(Typeable a, Exception a) => Exception (Error a) Source # 
Instance details

Defined in Prosidy.Compile.Error

type Rep (Error a) Source # 
Instance details

Defined in Prosidy.Compile.Error

type Rep (Error a) = D1 ('MetaData "Error" "Prosidy.Compile.Error" "prosidyc-0.2.0.0-inplace" 'False) (((C1 ('MetaCons "Custom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "ParseError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Key) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "Required" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Key)) :+: (C1 ('MetaCons "ExpectedTag" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TagKind) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Key)) :+: C1 ('MetaCons "ExpectedParagraph" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "ExpectedText" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExpectedBreak" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EmptyMatch" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "UnknownMetadata" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (MetadataKind, Key)))) :+: C1 ('MetaCons "Group" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Location)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ErrorSet a)))))))

data TagKind Source #

A marker class for marking which type of tag ExpectedTag was expecting.

Instances

Instances details
Eq TagKind Source # 
Instance details

Defined in Prosidy.Compile.Error

Methods

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

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

Show TagKind Source # 
Instance details

Defined in Prosidy.Compile.Error

Generic TagKind Source # 
Instance details

Defined in Prosidy.Compile.Error

Associated Types

type Rep TagKind :: Type -> Type #

Methods

from :: TagKind -> Rep TagKind x #

to :: Rep TagKind x -> TagKind #

Hashable TagKind Source # 
Instance details

Defined in Prosidy.Compile.Error

Methods

hashWithSalt :: Int -> TagKind -> Int #

hash :: TagKind -> Int #

type Rep TagKind Source # 
Instance details

Defined in Prosidy.Compile.Error

type Rep TagKind = D1 ('MetaData "TagKind" "Prosidy.Compile.Error" "prosidyc-0.2.0.0-inplace" 'False) (C1 ('MetaCons "BlockKind" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "InlineKind" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LiteralKind" 'PrefixI 'False) (U1 :: Type -> Type)))

data MetadataKind Source #

A marker class for marking which type of metadata (settings or property) a key corresponds to.

Constructors

PropertyKind 
SettingKind 

Instances

Instances details
Eq MetadataKind Source # 
Instance details

Defined in Prosidy.Compile.Error

Show MetadataKind Source # 
Instance details

Defined in Prosidy.Compile.Error

Generic MetadataKind Source # 
Instance details

Defined in Prosidy.Compile.Error

Associated Types

type Rep MetadataKind :: Type -> Type #

Hashable MetadataKind Source # 
Instance details

Defined in Prosidy.Compile.Error

type Rep MetadataKind Source # 
Instance details

Defined in Prosidy.Compile.Error

type Rep MetadataKind = D1 ('MetaData "MetadataKind" "Prosidy.Compile.Error" "prosidyc-0.2.0.0-inplace" 'False) (C1 ('MetaCons "PropertyKind" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SettingKind" 'PrefixI 'False) (U1 :: Type -> Type))

data ErrorSet e Source #

A non-empty set of errors.

Instances

Instances details
Eq e => Eq (ErrorSet e) Source # 
Instance details

Defined in Prosidy.Compile.Error

Methods

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

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

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

Defined in Prosidy.Compile.Error

Methods

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

show :: ErrorSet e -> String #

showList :: [ErrorSet e] -> ShowS #

Generic (ErrorSet e) Source # 
Instance details

Defined in Prosidy.Compile.Error

Associated Types

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

Methods

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

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

IsError e => Semigroup (ErrorSet e) Source # 
Instance details

Defined in Prosidy.Compile.Error

Methods

(<>) :: ErrorSet e -> ErrorSet e -> ErrorSet e #

sconcat :: NonEmpty (ErrorSet e) -> ErrorSet e #

stimes :: Integral b => b -> ErrorSet e -> ErrorSet e #

Hashable e => Hashable (ErrorSet e) Source # 
Instance details

Defined in Prosidy.Compile.Error

Methods

hashWithSalt :: Int -> ErrorSet e -> Int #

hash :: ErrorSet e -> Int #

Exception e => Exception (ErrorSet e) Source # 
Instance details

Defined in Prosidy.Compile.Error

type Rep (ErrorSet e) Source # 
Instance details

Defined in Prosidy.Compile.Error

type Rep (ErrorSet e) = D1 ('MetaData "ErrorSet" "Prosidy.Compile.Error" "prosidyc-0.2.0.0-inplace" 'True) (C1 ('MetaCons "ErrorSet" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet (Error e)))))

type Error' = Error Void Source #

A type alias for Errors that never throw a custom error.

type ErrorSet' = ErrorSet Void Source #

A type alias for ErrorSets which never contain empty errors.

type IsError e = (Exception e, Hashable e, Eq e) Source #

A constraint alias for errors throwable in a context admitting a ApErrors instance.

class Applicative f => ApError e f | f -> e where Source #

Similar to MonadError, but without the Monad constraint, and without a method to handle errors, only a method to map over them.

Methods

liftError :: e -> f a Source #

mapError :: (e -> e) -> f a -> f a Source #

type ApErrors e = ApError (ErrorSet e) Source #

A synonym for ApError when the underlying applicative is capable of accumulating errors in an ErrorSet.

singleError :: Hashable e => Error e -> ErrorSet e Source #

Lift a single Error into an ErrorSet.

customError :: Hashable e => e -> ErrorSet e Source #

Lift a custom error into an ErrorSet.

liftError1 :: (IsError e, ApErrors e m) => Error e -> m a Source #

Throw a single error.

allErrors :: ErrorSet e -> NonEmpty (Error e) Source #

Return the set of errors in an ErrorSet as a non-empty list.

groupErrors :: (IsError e, ApErrors e m, HasLocation l) => l -> m a -> m a Source #

Group errors together, attaching a location if one is available.