prosidyc-0.1.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.

Group (Maybe Location) (ErrorSet a)

Used to group a set of errors thrown at the same point in a tree. If a location is available, we attach it for debugging.

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.1.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 "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.1.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 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 #

type Rep (ErrorSet e) Source # 
Instance details

Defined in Prosidy.Compile.Error

type Rep (ErrorSet e) = D1 ('MetaData "ErrorSet" "Prosidy.Compile.Error" "prosidyc-0.1.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 MonadErrors instance.

type MonadErrors e = MonadError (ErrorSet e) Source #

A contraint alias for types returning at least one error.

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.

throwError1 :: Hashable e => MonadErrors 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.

attachLocation :: (IsError e, MonadErrors e m, HasLocation l) => l -> m a -> m a Source #

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

class Monad m => MonadError e (m :: Type -> Type) | m -> e where #

The strategy of combining computations that can throw exceptions by bypassing bound functions from the point an exception is thrown to the point that it is handled.

Is parameterized over the type of error information and the monad type constructor. It is common to use Either String as the monad type constructor for an error monad in which error descriptions take the form of strings. In that case and many other common cases the resulting monad is already defined as an instance of the MonadError class. You can also define your own error type and/or use a monad type constructor other than Either String or Either IOError. In these cases you will have to explicitly define instances of the MonadError class. (If you are using the deprecated Control.Monad.Error or Control.Monad.Trans.Error, you may also have to define an Error instance.)

Methods

throwError :: e -> m a #

Is used within a monadic computation to begin exception processing.

catchError :: m a -> (e -> m a) -> m a #

A handler function to handle previous errors and return to normal execution. A common idiom is:

do { action1; action2; action3 } `catchError` handler

where the action functions can call throwError. Note that handler and the do-block must have the same return type.

Instances

Instances details
MonadError () Maybe

Since: mtl-2.2.2

Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: () -> Maybe a #

catchError :: Maybe a -> (() -> Maybe a) -> Maybe a #

MonadError IOException IO 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: IOException -> IO a #

catchError :: IO a -> (IOException -> IO a) -> IO a #

MonadError e m => MonadError e (MaybeT m) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: e -> MaybeT m a #

catchError :: MaybeT m a -> (e -> MaybeT m a) -> MaybeT m a #

MonadError e m => MonadError e (ListT m) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: e -> ListT m a #

catchError :: ListT m a -> (e -> ListT m a) -> ListT m a #

MonadError e (Either e) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: e -> Either e a #

catchError :: Either e a -> (e -> Either e a) -> Either e a #

(Monoid w, MonadError e m) => MonadError e (WriterT w m) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: e -> WriterT w m a #

catchError :: WriterT w m a -> (e -> WriterT w m a) -> WriterT w m a #

(Monoid w, MonadError e m) => MonadError e (WriterT w m) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: e -> WriterT w m a #

catchError :: WriterT w m a -> (e -> WriterT w m a) -> WriterT w m a #

MonadError e m => MonadError e (StateT s m) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: e -> StateT s m a #

catchError :: StateT s m a -> (e -> StateT s m a) -> StateT s m a #

MonadError e m => MonadError e (StateT s m) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: e -> StateT s m a #

catchError :: StateT s m a -> (e -> StateT s m a) -> StateT s m a #

MonadError e m => MonadError e (ReaderT r m) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: e -> ReaderT r m a #

catchError :: ReaderT r m a -> (e -> ReaderT r m a) -> ReaderT r m a #

MonadError e m => MonadError e (IdentityT m) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: e -> IdentityT m a #

catchError :: IdentityT m a -> (e -> IdentityT m a) -> IdentityT m a #

Monad m => MonadError e (ExceptT e m)

Since: mtl-2.2

Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: e -> ExceptT e m a #

catchError :: ExceptT e m a -> (e -> ExceptT e m a) -> ExceptT e m a #

(Monad m, Error e) => MonadError e (ErrorT e m) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: e -> ErrorT e m a #

catchError :: ErrorT e m a -> (e -> ErrorT e m a) -> ErrorT e m a #

(Monoid w, MonadError e m) => MonadError e (RWST r w s m) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: e -> RWST r w s m a #

catchError :: RWST r w s m a -> (e -> RWST r w s m a) -> RWST r w s m a #

(Monoid w, MonadError e m) => MonadError e (RWST r w s m) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: e -> RWST r w s m a #

catchError :: RWST r w s m a -> (e -> RWST r w s m a) -> RWST r w s m a #