prosidyc-0.3.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.Core

Description

 
Synopsis

Documentation

data Rules t f a Source #

A container for building up compilation rules.

  • The type parameter t specifies the input type of these rules. It will almost always be a Prosidy node type, such as Document or Tag.
  • The type parameter f is a contextual functor for implementing custom extensions on top of Rules.

Instances

Instances details
Functor (Rules t f) Source # 
Instance details

Defined in Prosidy.Compile.Core.Rules

Methods

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

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

Applicative (Rules t f) Source # 
Instance details

Defined in Prosidy.Compile.Core.Rules

Methods

pure :: a -> Rules t f a #

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

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

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

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

Alternative (Rules t f) Source # 
Instance details

Defined in Prosidy.Compile.Core.Rules

Methods

empty :: Rules t f a #

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

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

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

Semigroup (Rules t f a) Source # 
Instance details

Defined in Prosidy.Compile.Core.Rules

Methods

(<>) :: Rules t f a -> Rules t f a -> Rules t f a #

sconcat :: NonEmpty (Rules t f a) -> Rules t f a #

stimes :: Integral b => b -> Rules t f a -> Rules t f a #

Monoid (Rules t f a) Source # 
Instance details

Defined in Prosidy.Compile.Core.Rules

Methods

mempty :: Rules t f a #

mappend :: Rules t f a -> Rules t f a -> Rules t f a #

mconcat :: [Rules t f a] -> Rules t f a #

data Rule t f a Source #

An individual Rule in isolation.

Constructors

RuleFor (RuleFor t f a)

A rule specific to the input type t

Escape (f a)

An escape hatch, allowing arbitrary computation

Self (t -> a)

A rule which converts the input type to an output.

Instances

Instances details
(Functor f, Functor (RuleFor t f)) => Functor (Rule t f) Source # 
Instance details

Defined in Prosidy.Compile.Core.Rules

Methods

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

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

rule :: RuleFor t f a -> Rules t f a Source #

Lift a single rule into the Rules functor.

local :: Functor f => f a -> Rules t f a Source #

Lift a contextual item into Rules.

self :: Rules t f t Source #

Get the currently focused node as a value.

runRules :: Alternative g => (forall b. Rule t f b -> g b) -> Rules t f a -> g a Source #

Given an interpreter which can convert Rules into the functor g, convert Rules into the functor g.

mapRules Source #

Arguments

:: forall a a' t t' f. (Functor f, Functor (RuleFor t' f)) 
=> (forall x. RuleFor t f x -> RuleFor t' f x)

Maps over rules themselves, keeping the context and output types the same.

-> (t' -> t)

Maps over the input to rules.

-> (a -> a')

Maps over the output of rules.

-> Rules t f a 
-> Rules t' f a' 

Map over Rules.

hoist :: HoistRuleFor t => (forall b. f b -> g b) -> Rules t f a -> Rules t g a Source #

Map over the contextual functor f in Rules.

class HoistRuleFor t Source #

A class defining how to map over the contextual parameter f in a rule for the type t.

Minimal complete definition

hoistRuleFor

Instances

Instances details
HoistRuleFor Text Source # 
Instance details

Defined in Prosidy.Compile.Core.Rules

Methods

hoistRuleFor :: (forall b. f b -> g b) -> RuleFor Text f a -> RuleFor Text g a

HoistRuleFor Block Source # 
Instance details

Defined in Prosidy.Compile.Core.Rules

Methods

hoistRuleFor :: (forall b. f b -> g b) -> RuleFor Block f a -> RuleFor Block g a

HoistRuleFor Document Source # 
Instance details

Defined in Prosidy.Compile.Core.Rules

Methods

hoistRuleFor :: (forall b. f b -> g b) -> RuleFor Document f a -> RuleFor Document g a

HoistRuleFor Fragment Source # 
Instance details

Defined in Prosidy.Compile.Core.Rules

Methods

hoistRuleFor :: (forall b. f b -> g b) -> RuleFor Fragment f a -> RuleFor Fragment g a

HoistRuleFor Inline Source # 
Instance details

Defined in Prosidy.Compile.Core.Rules

Methods

hoistRuleFor :: (forall b. f b -> g b) -> RuleFor Inline f a -> RuleFor Inline g a

HoistRuleFor Metadata Source # 
Instance details

Defined in Prosidy.Compile.Core.Rules

Methods

hoistRuleFor :: (forall b. f b -> g b) -> RuleFor Metadata f a -> RuleFor Metadata g a

HoistRuleFor Paragraph Source # 
Instance details

Defined in Prosidy.Compile.Core.Rules

Methods

hoistRuleFor :: (forall b. f b -> g b) -> RuleFor Paragraph f a -> RuleFor Paragraph g a

HoistRuleFor t => HoistRuleFor (Region t) Source # 
Instance details

Defined in Prosidy.Compile.Core.Rules

Methods

hoistRuleFor :: (forall b. f b -> g b) -> RuleFor (Region t) f a -> RuleFor (Region t) g a

HoistRuleFor t => HoistRuleFor (Tag t) Source # 
Instance details

Defined in Prosidy.Compile.Core.Rules

Methods

hoistRuleFor :: (forall b. f b -> g b) -> RuleFor (Tag t) f a -> RuleFor (Tag t) g a

HoistRuleFor t => HoistRuleFor (Series t) Source # 
Instance details

Defined in Prosidy.Compile.Core.Rules

Methods

hoistRuleFor :: (forall b. f b -> g b) -> RuleFor (Series t) f a -> RuleFor (Series t) g a

HoistRuleFor t => HoistRuleFor (SeriesNE t) Source # 
Instance details

Defined in Prosidy.Compile.Core.Rules

Methods

hoistRuleFor :: (forall b. f b -> g b) -> RuleFor (SeriesNE t) f a -> RuleFor (SeriesNE t) g a

Context-aware ADT rules.

type family RuleFor t = (rule :: (* -> *) -> * -> *) | rule -> t where ... Source #

Defines a relationship between input types and rules specific to those input types.

data BlockRule f a Source #

Rules for matching specific types of Block nodes.

Instances

Instances details
Functor (BlockRule f) Source # 
Instance details

Defined in Prosidy.Compile.Core.Rules

Methods

fmap :: (a -> b) -> BlockRule f a -> BlockRule f b #

(<$) :: a -> BlockRule f b -> BlockRule f a #

newtype DocumentRule f a Source #

Rules applying to Documents.

Constructors

DocumentRule (RegionRule (Series Block) f a) 

Instances

Instances details
Functor (DocumentRule f) Source # 
Instance details

Defined in Prosidy.Compile.Core.Rules

Methods

fmap :: (a -> b) -> DocumentRule f a -> DocumentRule f b #

(<$) :: a -> DocumentRule f b -> DocumentRule f a #

data FragmentRule f a Source #

Rules applying to Fragments (i.e. plain text).

Instances

Instances details
Functor (FragmentRule f) Source # 
Instance details

Defined in Prosidy.Compile.Core.Rules

Methods

fmap :: (a -> b) -> FragmentRule f a -> FragmentRule f b #

(<$) :: a -> FragmentRule f b -> FragmentRule f a #

data InlineRule f a Source #

Rules for matching specific types of Inline nodes.

Instances

Instances details
Functor (InlineRule f) Source # 
Instance details

Defined in Prosidy.Compile.Core.Rules

Methods

fmap :: (a -> b) -> InlineRule f a -> InlineRule f b #

(<$) :: a -> InlineRule f b -> InlineRule f a #

data MetadataRule f a Source #

Rules for operating on properties and settings.

Instances

Instances details
Functor (MetadataRule f) Source # 
Instance details

Defined in Prosidy.Compile.Core.Rules

Methods

fmap :: (a -> b) -> MetadataRule f a -> MetadataRule f b #

(<$) :: a -> MetadataRule f b -> MetadataRule f a #

data ParagraphRule f a Source #

Rules for accessing paragraphs.

Instances

Instances details
Functor (ParagraphRule f) Source # 
Instance details

Defined in Prosidy.Compile.Core.Rules

Methods

fmap :: (a -> b) -> ParagraphRule f a -> ParagraphRule f b #

(<$) :: a -> ParagraphRule f b -> ParagraphRule f a #

data RegionRule t f a Source #

Rules for operating on a Region.

Instances

Instances details
Functor (RegionRule t f) Source # 
Instance details

Defined in Prosidy.Compile.Core.Rules

Methods

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

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

data SeriesNERule t f a Source #

Operates sequentially against a non-empty collection of nodes.

Constructors

forall b c. SeriesNERule (b -> c -> a) (Rules t f b) (Rules (Series t) f c) 

Instances

Instances details
Functor (SeriesNERule t f) Source # 
Instance details

Defined in Prosidy.Compile.Core.Rules

Methods

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

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

data SeriesRule t f a Source #

Operates sequentially against a collection of nodes.

Instances

Instances details
Functor (SeriesRule t f) Source # 
Instance details

Defined in Prosidy.Compile.Core.Rules

Methods

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

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

data TagRule t f a Source #

Rules for operating on Tags.

Constructors

TagRuleKey Key a 
TagRuleRegion (RegionRule t f a) 

Instances

Instances details
Functor (TagRule t f) Source # 
Instance details

Defined in Prosidy.Compile.Core.Rules

Methods

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

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

Reëxports

class Applicative f => Alternative (f :: Type -> Type) where #

A monoid on applicative functors.

If defined, some and many should be the least solutions of the equations:

Minimal complete definition

empty, (<|>)

Methods

empty :: f a #

The identity of <|>

(<|>) :: f a -> f a -> f a infixl 3 #

An associative binary operation

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

One or more.

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

Zero or more.

Instances

Instances details
Alternative []

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

empty :: [a] #

(<|>) :: [a] -> [a] -> [a] #

some :: [a] -> [[a]] #

many :: [a] -> [[a]] #

Alternative Maybe

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

empty :: Maybe a #

(<|>) :: Maybe a -> Maybe a -> Maybe a #

some :: Maybe a -> Maybe [a] #

many :: Maybe a -> Maybe [a] #

Alternative IO

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

empty :: IO a #

(<|>) :: IO a -> IO a -> IO a #

some :: IO a -> IO [a] #

many :: IO a -> IO [a] #

Alternative IResult 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

empty :: IResult a #

(<|>) :: IResult a -> IResult a -> IResult a #

some :: IResult a -> IResult [a] #

many :: IResult a -> IResult [a] #

Alternative Result 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

empty :: Result a #

(<|>) :: Result a -> Result a -> Result a #

some :: Result a -> Result [a] #

many :: Result a -> Result [a] #

Alternative Parser 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

empty :: Parser a #

(<|>) :: Parser a -> Parser a -> Parser a #

some :: Parser a -> Parser [a] #

many :: Parser a -> Parser [a] #

Alternative Option

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

empty :: Option a #

(<|>) :: Option a -> Option a -> Option a #

some :: Option a -> Option [a] #

many :: Option a -> Option [a] #

Alternative ZipList

Since: base-4.11.0.0

Instance details

Defined in Control.Applicative

Methods

empty :: ZipList a #

(<|>) :: ZipList a -> ZipList a -> ZipList a #

some :: ZipList a -> ZipList [a] #

many :: ZipList a -> ZipList [a] #

Alternative ReadP

Since: base-4.6.0.0

Instance details

Defined in Text.ParserCombinators.ReadP

Methods

empty :: ReadP a #

(<|>) :: ReadP a -> ReadP a -> ReadP a #

some :: ReadP a -> ReadP [a] #

many :: ReadP a -> ReadP [a] #

Alternative Seq

Since: containers-0.5.4

Instance details

Defined in Data.Sequence.Internal

Methods

empty :: Seq a #

(<|>) :: Seq a -> Seq a -> Seq a #

some :: Seq a -> Seq [a] #

many :: Seq a -> Seq [a] #

Alternative DList 
Instance details

Defined in Data.DList

Methods

empty :: DList a #

(<|>) :: DList a -> DList a -> DList a #

some :: DList a -> DList [a] #

many :: DList a -> DList [a] #

Alternative SmallArray 
Instance details

Defined in Data.Primitive.SmallArray

Alternative Array 
Instance details

Defined in Data.Primitive.Array

Methods

empty :: Array a #

(<|>) :: Array a -> Array a -> Array a #

some :: Array a -> Array [a] #

many :: Array a -> Array [a] #

Alternative Vector 
Instance details

Defined in Data.Vector

Methods

empty :: Vector a #

(<|>) :: Vector a -> Vector a -> Vector a #

some :: Vector a -> Vector [a] #

many :: Vector a -> Vector [a] #

Alternative P

Since: base-4.5.0.0

Instance details

Defined in Text.ParserCombinators.ReadP

Methods

empty :: P a #

(<|>) :: P a -> P a -> P a #

some :: P a -> P [a] #

many :: P a -> P [a] #

Alternative (U1 :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

empty :: U1 a #

(<|>) :: U1 a -> U1 a -> U1 a #

some :: U1 a -> U1 [a] #

many :: U1 a -> U1 [a] #

Alternative (Parser i) 
Instance details

Defined in Data.Attoparsec.Internal.Types

Methods

empty :: Parser i a #

(<|>) :: Parser i a -> Parser i a -> Parser i a #

some :: Parser i a -> Parser i [a] #

many :: Parser i a -> Parser i [a] #

MonadPlus m => Alternative (WrappedMonad m)

Since: base-2.1

Instance details

Defined in Control.Applicative

Methods

empty :: WrappedMonad m a #

(<|>) :: WrappedMonad m a -> WrappedMonad m a -> WrappedMonad m a #

some :: WrappedMonad m a -> WrappedMonad m [a] #

many :: WrappedMonad m a -> WrappedMonad m [a] #

ArrowPlus a => Alternative (ArrowMonad a)

Since: base-4.6.0.0

Instance details

Defined in Control.Arrow

Methods

empty :: ArrowMonad a a0 #

(<|>) :: ArrowMonad a a0 -> ArrowMonad a a0 -> ArrowMonad a a0 #

some :: ArrowMonad a a0 -> ArrowMonad a [a0] #

many :: ArrowMonad a a0 -> ArrowMonad a [a0] #

Alternative (Alt f) 
Instance details

Defined in Control.Alternative.Free.Final

Methods

empty :: Alt f a #

(<|>) :: Alt f a -> Alt f a -> Alt f a #

some :: Alt f a -> Alt f [a] #

many :: Alt f a -> Alt f [a] #

Monoid e => Alternative (Valid e) Source # 
Instance details

Defined in Data.Either.Valid

Methods

empty :: Valid e a #

(<|>) :: Valid e a -> Valid e a -> Valid e a #

some :: Valid e a -> Valid e [a] #

many :: Valid e a -> Valid e [a] #

Alternative f => Alternative (Rec1 f)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

empty :: Rec1 f a #

(<|>) :: Rec1 f a -> Rec1 f a -> Rec1 f a #

some :: Rec1 f a -> Rec1 f [a] #

many :: Rec1 f a -> Rec1 f [a] #

(ArrowZero a, ArrowPlus a) => Alternative (WrappedArrow a b)

Since: base-2.1

Instance details

Defined in Control.Applicative

Methods

empty :: WrappedArrow a b a0 #

(<|>) :: WrappedArrow a b a0 -> WrappedArrow a b a0 -> WrappedArrow a b a0 #

some :: WrappedArrow a b a0 -> WrappedArrow a b [a0] #

many :: WrappedArrow a b a0 -> WrappedArrow a b [a0] #

Alternative f => Alternative (Ap f)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

empty :: Ap f a #

(<|>) :: Ap f a -> Ap f a -> Ap f a #

some :: Ap f a -> Ap f [a] #

many :: Ap f a -> Ap f [a] #

Alternative f => Alternative (Alt f)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

empty :: Alt f a #

(<|>) :: Alt f a -> Alt f a -> Alt f a #

some :: Alt f a -> Alt f [a] #

many :: Alt f a -> Alt f [a] #

(Functor m, Monad m, Error e) => Alternative (ErrorT e m) 
Instance details

Defined in Control.Monad.Trans.Error

Methods

empty :: ErrorT e m a #

(<|>) :: ErrorT e m a -> ErrorT e m a -> ErrorT e m a #

some :: ErrorT e m a -> ErrorT e m [a] #

many :: ErrorT e m a -> ErrorT e m [a] #

(Profunctor p, ArrowPlus p) => Alternative (Tambara p a) 
Instance details

Defined in Data.Profunctor.Strong

Methods

empty :: Tambara p a a0 #

(<|>) :: Tambara p a a0 -> Tambara p a a0 -> Tambara p a a0 #

some :: Tambara p a a0 -> Tambara p a [a0] #

many :: Tambara p a a0 -> Tambara p a [a0] #

Alternative (Rules t f) Source # 
Instance details

Defined in Prosidy.Compile.Core.Rules

Methods

empty :: Rules t f a #

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

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

many :: Rules t f a -> Rules t f [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] #

(Alternative f, Alternative g) => Alternative (f :*: g)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

empty :: (f :*: g) a #

(<|>) :: (f :*: g) a -> (f :*: g) a -> (f :*: g) a #

some :: (f :*: g) a -> (f :*: g) [a] #

many :: (f :*: g) a -> (f :*: g) [a] #

(Alternative f, Alternative g) => Alternative (Product f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

empty :: Product f g a #

(<|>) :: Product f g a -> Product f g a -> Product f g a #

some :: Product f g a -> Product f g [a] #

many :: Product f g a -> Product f g [a] #

Alternative f => Alternative (M1 i c f)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

empty :: M1 i c f a #

(<|>) :: M1 i c f a -> M1 i c f a -> M1 i c f a #

some :: M1 i c f a -> M1 i c f [a] #

many :: M1 i c f a -> M1 i c f [a] #

(Alternative f, Applicative g) => Alternative (f :.: g)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

empty :: (f :.: g) a #

(<|>) :: (f :.: g) a -> (f :.: g) a -> (f :.: g) a #

some :: (f :.: g) a -> (f :.: g) [a] #

many :: (f :.: g) a -> (f :.: g) [a] #

(Alternative f, Applicative g) => Alternative (Compose f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

empty :: Compose f g a #

(<|>) :: Compose f g a -> Compose f g a -> Compose f g a #

some :: Compose f g a -> Compose f g [a] #

many :: Compose f g a -> Compose f g [a] #

class (forall i. Alternative (t i)) => Context t where Source #

A base class for interpreters of Rules.

Minimal complete definition

runSelf

Associated Types

type Local t :: * -> * Source #

A type for expressions that can be lifted by the interpreter.

This type defaults to an uninhabited type. Only override this type if you intend on overriding liftRule, as well.

type Local t = Void t Source #

Methods

runSelf :: t i i Source #

Access the current focus of an interpreter. This function is similar in purpose to ask.

liftRule :: Local t a -> t i a Source #

Lift an expression of type Local into the interpreter.

By default, Local is left as an uninhabted type and escaping via liftRule can never happen. Override both Local and liftRule to permit arbitrary computation.

default liftRule :: Local t a ~ Void t a => Local t a -> t i a Source #

Instances

Instances details
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 #

class Context t => Interpret t i where Source #

Instructs a Context how to interpret a single rule.

Minimal complete definition

Nothing

Methods

runRule :: RuleFor i (Local t) a -> t i a Source #

Evaluate a single rule into the context.

default runRule :: RuleFor i ~ Void i => RuleFor i (Local t) a -> t i a Source #

Instances

Instances details
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 #

interpret :: forall t i a. Interpret t i => Rules i (Local t) a -> t i a Source #

Evaluate Rules into a contextual interpreter.