prosidyc-0.3.0.0: A DSL for processing Prosidy documents.
LicenseMPL-2.0
Maintaineralex@fldcr.com
Safe HaskellNone
LanguageHaskell2010

Prosidy.Compile.Run

Description

 
Synopsis

Documentation

data RunError Source #

Errors that may be returned from the interpreter.

Constructors

Group Location (Set RunError)

Groups a set of errors with a location for more helpful error messages.

MatchError Text

Expected a different type. Thrown on failed matches of sum types.

ParseError Key String

The provided parser failed to parse a setting.

RequiredSetting Key

A setting was required, but not found on a node.

TooFewElements

Expected more elements when matching sequentially.

TooManyElements

Expected fewer elements when matching sequentially.

UnexpectedProperties (HashSet Key) (HashSet Key)

A property was found on a node, but not mentioned in its specification.

UnexpectedSettings (HashSet Key) (HashSet Key)

A setting was found on a node, but not mentioned in its specification.

Instances

Instances details
Eq RunError Source # 
Instance details

Defined in Prosidy.Compile.Run

Ord RunError Source # 
Instance details

Defined in Prosidy.Compile.Run

Show RunError Source # 
Instance details

Defined in Prosidy.Compile.Run

Exception RunError Source # 
Instance details

Defined in Prosidy.Compile.Run

Pretty RunError Source # 
Instance details

Defined in Prosidy.Compile.Run

Methods

pretty :: RunError -> Doc ann #

prettyList :: [RunError] -> Doc ann #

newtype RunErrors Source #

A newtype wrapper over a set of RunErrors.

This is defined to allow an instances of Exception and Pretty for error sets.

Constructors

RunErrors (Set RunError) 

Instances

Instances details
Eq RunErrors Source # 
Instance details

Defined in Prosidy.Compile.Run

Ord RunErrors Source # 
Instance details

Defined in Prosidy.Compile.Run

Show RunErrors Source # 
Instance details

Defined in Prosidy.Compile.Run

Semigroup RunErrors Source # 
Instance details

Defined in Prosidy.Compile.Run

Monoid RunErrors Source # 
Instance details

Defined in Prosidy.Compile.Run

Exception RunErrors Source # 
Instance details

Defined in Prosidy.Compile.Run

Pretty RunErrors Source # 
Instance details

Defined in Prosidy.Compile.Run

Methods

pretty :: RunErrors -> Doc ann #

prettyList :: [RunErrors] -> Doc ann #

data RunT f t a Source #

An interpreter over Rules.

Instances

Instances details
Functor f => Strong (RunT f) Source # 
Instance details

Defined in Prosidy.Compile.Run

Methods

first' :: RunT f a b -> RunT f (a, c) (b, c) #

second' :: RunT f a b -> RunT f (c, a) (c, b) #

Functor f => Profunctor (RunT f) Source # 
Instance details

Defined in Prosidy.Compile.Run

Methods

dimap :: (a -> b) -> (c -> d) -> RunT f b c -> RunT f a d #

lmap :: (a -> b) -> RunT f b c -> RunT f a c #

rmap :: (b -> c) -> RunT f a b -> RunT f a c #

(#.) :: forall a b c q. Coercible c b => q b c -> RunT f a b -> RunT f a c #

(.#) :: forall a b c q. Coercible b a => RunT f b c -> q a b -> RunT f a c #

Applicative f => Context (RunT f) Source # 
Instance details

Defined in Prosidy.Compile.Run

Associated Types

type Local (RunT f) :: Type -> Type Source #

Methods

runSelf :: RunT f i i Source #

liftRule :: Local (RunT f) a -> RunT f i a Source #

Applicative f => Interpret (RunT f) Text Source # 
Instance details

Defined in Prosidy.Compile.Run

Methods

runRule :: RuleFor Text (Local (RunT f)) a -> RunT f Text a Source #

Applicative f => Interpret (RunT f) Paragraph Source # 
Instance details

Defined in Prosidy.Compile.Run

Applicative f => Interpret (RunT f) Metadata Source # 
Instance details

Defined in Prosidy.Compile.Run

Applicative f => Interpret (RunT f) Inline Source # 
Instance details

Defined in Prosidy.Compile.Run

Methods

runRule :: RuleFor Inline (Local (RunT f)) a -> RunT f Inline a Source #

Applicative f => Interpret (RunT f) Fragment Source # 
Instance details

Defined in Prosidy.Compile.Run

Applicative f => Interpret (RunT f) Document Source # 
Instance details

Defined in Prosidy.Compile.Run

Applicative f => Interpret (RunT f) Block Source # 
Instance details

Defined in Prosidy.Compile.Run

Methods

runRule :: RuleFor Block (Local (RunT f)) a -> RunT f Block a Source #

(Applicative f, Interpret (RunT f) t) => Interpret (RunT f) (SeriesNE t) Source # 
Instance details

Defined in Prosidy.Compile.Run

Methods

runRule :: RuleFor (SeriesNE t) (Local (RunT f)) a -> RunT f (SeriesNE t) a Source #

(Applicative f, Interpret (RunT f) t) => Interpret (RunT f) (Series t) Source # 
Instance details

Defined in Prosidy.Compile.Run

Methods

runRule :: RuleFor (Series t) (Local (RunT f)) a -> RunT f (Series t) a Source #

(Applicative f, Interpret (RunT f) t) => Interpret (RunT f) (Tag t) Source # 
Instance details

Defined in Prosidy.Compile.Run

Methods

runRule :: RuleFor (Tag t) (Local (RunT f)) a -> RunT f (Tag t) a Source #

(Applicative f, Interpret (RunT f) t) => Interpret (RunT f) (Region t) Source # 
Instance details

Defined in Prosidy.Compile.Run

Methods

runRule :: RuleFor (Region t) (Local (RunT f)) a -> RunT f (Region t) a Source #

Functor f => Functor (RunT f t) Source # 
Instance details

Defined in Prosidy.Compile.Run

Methods

fmap :: (a -> b) -> RunT f t a -> RunT f t b #

(<$) :: a -> RunT f t b -> RunT f t a #

Applicative f => Applicative (RunT f t) Source # 
Instance details

Defined in Prosidy.Compile.Run

Methods

pure :: a -> RunT f t a #

(<*>) :: RunT f t (a -> b) -> RunT f t a -> RunT f t b #

liftA2 :: (a -> b -> c) -> RunT f t a -> RunT f t b -> RunT f t c #

(*>) :: RunT f t a -> RunT f t b -> RunT f t b #

(<*) :: RunT f t a -> RunT f t b -> RunT f t a #

Applicative f => Alternative (RunT f t) Source # 
Instance details

Defined in Prosidy.Compile.Run

Methods

empty :: RunT f t a #

(<|>) :: RunT f t a -> RunT f t a -> RunT f t a #

some :: RunT f t a -> RunT f t [a] #

many :: RunT f t a -> RunT f t [a] #

type Local (RunT f) Source # 
Instance details

Defined in Prosidy.Compile.Run

type Local (RunT f) = f

type Run = RunT Identity Source #

RunT specialized to Identity.

run :: i -> Run i a -> Either RunErrors a Source #

Run a Run interpreter to completion.

runT :: i -> RunT f i a -> Either RunErrors (f a) Source #

Run a RunT interpreter to completion.