Copyright | ©2020 James Alexander Feldman-Crough |
---|---|
License | MPL-2.0 |
Maintainer | alex@fldcr.com |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data RuleF input error context output where
- Fail :: Error error -> RuleF input error context output
- Lift :: (input -> context (Either (Error error) output)) -> RuleF input error context output
- TestMatch :: CanMatch input => NonEmpty (Pattern input error context output) -> RuleF input error context output
- Traverse :: Traversable t => (input -> t i) -> (t o -> output) -> RuleT i error context o -> RuleF input error context output
- GetContent :: HasContent input => RuleT (Content input) error context output -> RuleF input error context output
- GetProperty :: HasMetadata input => (Bool -> a) -> Key -> RuleF input error context a
- GetSetting :: HasMetadata input => (Maybe x -> output) -> Key -> (Text -> Either String x) -> RuleF input error context output
- GetRequiredSetting :: HasMetadata input => Key -> (Text -> Either String output) -> RuleF input error context output
- GetSelf :: (input -> output) -> RuleF input error context output
- 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 where
- evalPattern :: Applicative g => Pattern t error context output -> Interpret error context g -> t -> Either (NoMatch t) (g output)
- noMatchError :: NoMatch t -> Error e
- type Interpret e f g = forall i a. i -> RuleF i e f a -> g a
- type BlockRegion = Region (Series Block)
- type InlineRegion = Region (Series Inline)
- type LiteralRegion = Region Text
- interpretWith :: Applicative g => RuleT i e f a -> Interpret e f g -> i -> g a
- evalPatterns :: (CanMatch i, IsError e, MonadErrors e g) => NonEmpty (Pattern i e f o) -> Interpret e f g -> i -> g o
- rule :: RuleF i e f o -> RuleT i e f o
Documentation
data RuleF input error context output where Source #
The control functor for compiling Prosidy elements. Each action
corresponds to an action to perform on the input
variable.
Fail :: Error error -> RuleF input error context output | Throw an error. |
Lift :: (input -> context (Either (Error error) output)) -> RuleF input error context output | Embed a raw action as a rule. Note: Please avoid using this if possible: it breaks static introspection! |
TestMatch :: CanMatch input => NonEmpty (Pattern input error context output) -> RuleF input error context output | Given a non-empty list of potential cases, construct a Rule that processes any items matching at least one of those cases. |
Traverse :: Traversable t => (input -> t i) -> (t o -> output) -> RuleT i error context o -> RuleF input error context output | |
GetContent :: HasContent input => RuleT (Content input) error context output -> RuleF input error context output | When |
GetProperty :: HasMetadata input => (Bool -> a) -> Key -> RuleF input error context a | Fetch a property from items with metadata. |
GetSetting :: HasMetadata input => (Maybe x -> output) -> Key -> (Text -> Either String x) -> RuleF input error context output | Fetch an optional setting from items with metadata. |
GetRequiredSetting :: HasMetadata input => Key -> (Text -> Either String output) -> RuleF input error context output | Fetch a required setting from items with metadata. |
GetSelf :: (input -> output) -> RuleF input error context output | Get the raw text from a |
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.Void
can be used to rely solely on the errors built into this library.context
: AMonad
for performing contextual computation beyond what is provided by this library. If additional contextual computation is not desired, useIdentity
as 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 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 where Source #
A (lawless) typeclass for enabling fallible matching on nodes.
Implementing new instances of this class in library code is *unneccessary* and *unsupported*.
:: Applicative g | |
=> Pattern t error context output | The |
-> Interpret error context g | An interpreter for evaluating the match. |
-> t | The value to attempt to match against |
-> Either (NoMatch t) (g output) |
Attempt to match a pattern against a value.
noMatchError :: NoMatch t -> Error e Source #
Lift a NoMatch
error into the Error
type.
Instances
CanMatch Block Source # | |
Defined in Prosidy.Compile.Core | |
CanMatch Inline Source # | |
Defined in Prosidy.Compile.Core |
type Interpret e f g = forall i a. i -> RuleF i e f a -> g a Source #
Runs a single RuleF
into an applicative g
. Passing this value to
interpretWith
will fully evaluate a RuleT
into the same functor.
type LiteralRegion = Region Text Source #
A LiteralTag
with the tag name removed.
interpretWith :: Applicative g => RuleT i e f a -> Interpret e f g -> i -> g a Source #
Build an interpreter into a functor g
.
evalPatterns :: (CanMatch i, IsError e, MonadErrors e g) => NonEmpty (Pattern i e f o) -> Interpret e f g -> i -> g o Source #
Match one or more patterns, in sequence, against a value. The result from the first successful pattern will be returned. Subsequent matches will not be tried.