| Copyright | ©2020 James Alexander Feldman-Crough |
|---|---|
| License | MPL-2.0 |
| Maintainer | alex@fldcr.com |
| Safe Haskell | None |
| Language | Haskell2010 |
Prosidy.Compile
Description
Synopsis
- escapeHatch :: (i -> f (Either (Error e) a)) -> RuleT i e f a
- getContent :: HasContent i => RuleT (Content i) e f a -> RuleT i e f a
- matchContent :: (Traversable t, HasContent i, t x ~ Content i, CanMatch x) => Match x e f a -> RuleT i e f (t a)
- optParse :: HasMetadata i => Key -> (Text -> Either String a) -> RuleT i e f (Maybe a)
- prop :: HasMetadata i => Key -> RuleT i e f Bool
- reqParse :: HasMetadata i => Key -> (Text -> Either String a) -> RuleT i e f a
- traversing :: Traversable t => RuleT i e f a -> RuleT (t i) e f (t a)
- self :: RuleT i e f i
- data RuleT input error context output
- type Rule input error = RuleT input error Identity
- class (forall i e. Functor (Pattern t i e), HasLocation t) => CanMatch t
- data Error a
- = Custom a
- | ParseError Key String
- | Required Key
- | ExpectedTag TagKind Key
- | ExpectedParagraph
- | ExpectedText
- | ExpectedBreak
- | EmptyMatch
- | Group (Maybe Location) (ErrorSet a)
- data ErrorSet e
- module Prosidy.Compile.Match
- run :: IsError e => RuleT i e Identity a -> i -> Either (ErrorSet e) a
- runM :: (Monad context, IsError e) => RuleT i e context a -> i -> context (Either (ErrorSet e) a)
Accessors
escapeHatch :: (i -> f (Either (Error e) a)) -> RuleT i e f a Source #
Do anything you want with a node. This should be used sparingly! The actions you perform inside of this function are invisible to inspection.
getContent :: HasContent i => RuleT (Content i) e f a -> RuleT i e f a Source #
Access the inner Content of a node.
matchContent :: (Traversable t, HasContent i, t x ~ Content i, CanMatch x) => Match x e f a -> RuleT i e f (t a) Source #
Traverse over each item in a node's Content via fallible matches.
optParse :: HasMetadata i => Key -> (Text -> Either String a) -> RuleT i e f (Maybe a) Source #
Parse an optional setting from a node with attached Metadata.
prop :: HasMetadata i => Key -> RuleT i e f Bool Source #
Check if a property is set on a node with attached Metadata.
reqParse :: HasMetadata i => Key -> (Text -> Either String a) -> RuleT i e f a Source #
Parse an required setting from a node with attached Metadata.
traversing :: Traversable t => RuleT i e f a -> RuleT (t i) e f (t a) Source #
Lift a RuleT so that it operates on a traversable structure.
Reëxports
data RuleT input error context output Source #
A single compilation rule. Parameterized by the following types:
input: The type of the Prosidy node that is currently accessible.error: Allows users to specify a custom error type to be used for throwing errors.Voidcan be used to rely solely on the errors built into this library.context: AMonadfor performing contextual computation beyond what is provided by this library. If additional contextual computation is not desired, useIdentityas the type.output: The resulting output type.
Instances
| MonadTrans (RuleT input error) Source # | |
Defined in Prosidy.Compile.Core | |
| Functor (RuleT input error context) Source # | |
| Applicative (RuleT input error context) Source # | |
Defined in Prosidy.Compile.Core Methods pure :: a -> RuleT input error context a # (<*>) :: RuleT input error context (a -> b) -> RuleT input error context a -> RuleT input error context b # liftA2 :: (a -> b -> c) -> RuleT input error context a -> RuleT input error context b -> RuleT input error context c # (*>) :: RuleT input error context a -> RuleT input error context b -> RuleT input error context b # (<*) :: RuleT input error context a -> RuleT input error context b -> RuleT input error context a # | |
class (forall i e. Functor (Pattern t i e), HasLocation t) => CanMatch t Source #
A (lawless) typeclass for enabling fallible matching on nodes.
Implementing new instances of this class in library code is *unneccessary* and *unsupported*.
Minimal complete definition
Instances
| CanMatch Block Source # | |
Defined in Prosidy.Compile.Core | |
| CanMatch Inline Source # | |
Defined in Prosidy.Compile.Core | |
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. |
| 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
A non-empty set of errors.
module Prosidy.Compile.Match