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

Description

 
Synopsis

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.

self :: RuleT i e f i Source #

Access the contents of a node.

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. Void can be used to rely solely on the errors built into this library.
  • context: A Monad for performing contextual computation beyond what is provided by this library. If additional contextual computation is not desired, use Identity as the type.
  • output: The resulting output type.

Instances

Instances details
MonadTrans (RuleT input error) Source # 
Instance details

Defined in Prosidy.Compile.Core

Methods

lift :: Monad m => m a -> RuleT input error m a #

Functor (RuleT input error context) Source # 
Instance details

Defined in Prosidy.Compile.Core

Methods

fmap :: (a -> b) -> RuleT input error context a -> RuleT input error context b #

(<$) :: a -> RuleT input error context b -> RuleT input error context a #

Applicative (RuleT input error context) Source # 
Instance details

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 #

type Rule input error = RuleT input error Identity Source #

RuleT without a contextual environment.

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

evalPattern, noMatchError

Instances

Instances details
CanMatch Block Source # 
Instance details

Defined in Prosidy.Compile.Core

Associated Types

data Pattern Block :: Type -> (Type -> Type) -> Type -> Type

data NoMatch Block

Methods

evalPattern :: forall g error (context :: Type -> Type) output. Applicative g => Pattern Block error context output -> Interpret error context g -> Block -> Either (NoMatch Block) (g output) Source #

noMatchError :: NoMatch Block -> Error e Source #

CanMatch Inline Source # 
Instance details

Defined in Prosidy.Compile.Core

Associated Types

data Pattern Inline :: Type -> (Type -> Type) -> Type -> Type

data NoMatch Inline

Methods

evalPattern :: forall g error (context :: Type -> Type) output. Applicative g => Pattern Inline error context output -> Interpret error context g -> Inline -> Either (NoMatch Inline) (g output) Source #

noMatchError :: NoMatch Inline -> Error e Source #

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 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)))))

run :: IsError e => RuleT i e Identity a -> i -> Either (ErrorSet e) a Source #

Run a Rule against an input, returning a parse result.

runM :: (Monad context, IsError e) => RuleT i e context a -> i -> context (Either (ErrorSet e) a) Source #

Run a RuleT against an input, returning a contextual parse result.