| Copyright | ©2020 James Alexander Feldman-Crough |
|---|---|
| License | MPL-2.0 |
| Maintainer | alex@fldcr.com |
| Safe Haskell | None |
| Language | Haskell2010 |
Prosidy.Compile.Error
Description
Synopsis
- data Error a
- = Custom a
- | ParseError Key String
- | Required Key
- | ExpectedTag TagKind Key
- | ExpectedParagraph
- | ExpectedText
- | ExpectedBreak
- | EmptyMatch
- | UnknownMetadata (HashSet (MetadataKind, Key))
- | Group (Maybe Location) (ErrorSet a)
- data TagKind
- data MetadataKind
- data ErrorSet e
- type Error' = Error Void
- type ErrorSet' = ErrorSet Void
- type IsError e = (Exception e, Hashable e, Eq e)
- class Applicative f => ApError e f | f -> e where
- type ApErrors e = ApError (ErrorSet e)
- singleError :: Hashable e => Error e -> ErrorSet e
- customError :: Hashable e => e -> ErrorSet e
- liftError1 :: (IsError e, ApErrors e m) => Error e -> m a
- allErrors :: ErrorSet e -> NonEmpty (Error e)
- groupErrors :: (IsError e, ApErrors e m, HasLocation l) => l -> m a -> m a
Documentation
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 |
| 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
A marker class for marking which type of tag ExpectedTag was expecting.
Constructors
| BlockKind | |
| InlineKind | |
| LiteralKind |
Instances
| Eq TagKind Source # | |
| Show TagKind Source # | |
| Generic TagKind Source # | |
| Hashable TagKind Source # | |
Defined in Prosidy.Compile.Error | |
| type Rep TagKind Source # | |
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
| Eq MetadataKind Source # | |
Defined in Prosidy.Compile.Error | |
| Show MetadataKind Source # | |
Defined in Prosidy.Compile.Error Methods showsPrec :: Int -> MetadataKind -> ShowS # show :: MetadataKind -> String # showList :: [MetadataKind] -> ShowS # | |
| Generic MetadataKind Source # | |
Defined in Prosidy.Compile.Error Associated Types type Rep MetadataKind :: Type -> Type # | |
| Hashable MetadataKind Source # | |
Defined in Prosidy.Compile.Error | |
| type Rep MetadataKind Source # | |
A non-empty set of errors.
Instances
| Eq e => Eq (ErrorSet e) Source # | |
| Show e => Show (ErrorSet e) Source # | |
| Generic (ErrorSet e) Source # | |
| IsError e => Semigroup (ErrorSet e) Source # | |
| Hashable e => Hashable (ErrorSet e) Source # | |
Defined in Prosidy.Compile.Error | |
| Exception e => Exception (ErrorSet e) Source # | |
Defined in Prosidy.Compile.Error Methods toException :: ErrorSet e -> SomeException # fromException :: SomeException -> Maybe (ErrorSet e) # displayException :: ErrorSet e -> String # | |
| type Rep (ErrorSet e) Source # | |
Defined in Prosidy.Compile.Error | |
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.
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.