Copyright | ©2020 James Alexander Feldman-Crough |
---|---|
License | MPL-2.0 |
Maintainer | alex@fldcr.com |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- content :: RegionLike t => Rules (Content t) f a -> Rules t f a
- (&>) :: Rules t f a -> Rules (Series t) f (Series a) -> Rules (Series t) f (Series a)
- (&>>) :: Rules t f a -> Rules (Series t) f (Series a) -> Rules (SeriesNE t) f (SeriesNE a)
- folded :: Monoid a => Rules t f a -> Rules (Series t) f a
- folded1 :: Monoid a => Rules t f a -> Rules (SeriesNE t) f a
- collect :: Rules t f a -> Rules (Series t) f (Series a)
- end :: Rules (Series t) f (Series a)
- endWith :: a -> Rules (Series t) f a
- prop :: RegionLike t => Key -> Rules t f Bool
- req :: forall a t f. (RegionLike t, FromSetting a) => Key -> Rules t f a
- opt :: forall a t f. (RegionLike t, FromSetting a) => Key -> Rules t f (Maybe a)
- lax :: RegionLike t => Rules t f ()
- type Match t f a = MatchM t f a ()
- match :: Match t f a -> Rules t f a
- blockTag :: Functor f => Key -> Rules BlockRegion f a -> Match Block f a
- inlineTag :: Functor f => Key -> Rules InlineRegion f a -> Match Inline f a
- literalTag :: Functor f => Key -> Rules LiteralRegion f a -> Match Block f a
- paragraph :: Rules (SeriesNE Inline) f a -> Match Block f a
- text :: (Text -> a) -> Match Inline f a
- breakWith :: a -> Match Inline f a
- local :: Functor f => f a -> Rules t f a
- self :: Rules t f t
- hoist :: HoistRuleFor t => (forall b. f b -> g b) -> Rules t f a -> Rules t g a
- class FromSetting a where
- parseSetting :: Text -> Either String a
- class HasContent t => RegionLike t
Documentation
content :: RegionLike t => Rules (Content t) f a -> Rules t f a Source #
Access the inner content of the RegionLike
value t
.
Series rules
(&>) :: Rules t f a -> Rules (Series t) f (Series a) -> Rules (Series t) f (Series a) infixr 3 Source #
(&>>) :: Rules t f a -> Rules (Series t) f (Series a) -> Rules (SeriesNE t) f (SeriesNE a) infixr 1 Source #
folded :: Monoid a => Rules t f a -> Rules (Series t) f a Source #
Lift a rule to operate on a Series
by folding the results of
evaluation against each element into a single result.
folded1 :: Monoid a => Rules t f a -> Rules (SeriesNE t) f a Source #
Like folded
, but operates on a non-empty series.
collect :: Rules t f a -> Rules (Series t) f (Series a) Source #
Lift a rule to collect many of that rule in series
endWith :: a -> Rules (Series t) f a Source #
Match the end of a Series
, returning the provided value.
Metadata rules
prop :: RegionLike t => Key -> Rules t f Bool Source #
Check if a Metadata
property is set on a node.
req :: forall a t f. (RegionLike t, FromSetting a) => Key -> Rules t f a Source #
Fetch a required Metadata
setting from a node.
opt :: forall a t f. (RegionLike t, FromSetting a) => Key -> Rules t f (Maybe a) Source #
Fetch an optional Metadata
setting from a node.
lax :: RegionLike t => Rules t f () Source #
Allow unknown properties and settings in this region.
Matchers
literalTag :: Functor f => Key -> Rules LiteralRegion f a -> Match Block f a Source #
Match a LiteralTag
with the provided Key
.
paragraph :: Rules (SeriesNE Inline) f a -> Match Block f a Source #
Match a paragraph which is not enclosed in a tag.
text :: (Text -> a) -> Match Inline f a Source #
Match textual content, transforming it with the provided function.
Get wild with actions
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
.
Convenience classes
class FromSetting a where Source #
A class for values which can be parsed from Text
.
Nothing
Instances
FromSetting Double Source # | |
Defined in Prosidy.Compile.DSL | |
FromSetting Float Source # | |
Defined in Prosidy.Compile.DSL | |
FromSetting Int Source # | |
Defined in Prosidy.Compile.DSL | |
FromSetting Integer Source # | |
Defined in Prosidy.Compile.DSL | |
FromSetting Natural Source # | |
Defined in Prosidy.Compile.DSL | |
FromSetting Word Source # | |
Defined in Prosidy.Compile.DSL | |
FromSetting String Source # | |
Defined in Prosidy.Compile.DSL | |
FromSetting Text Source # | |
Defined in Prosidy.Compile.DSL | |
FromSetting Text Source # | |
Defined in Prosidy.Compile.DSL |
class HasContent t => RegionLike t Source #
A class for recursive nodes in a document.
liftRegionRule
Instances
RegionLike Document Source # | |
Defined in Prosidy.Compile.DSL liftRegionRule :: forall (f :: Type -> Type) a. RegionRule (Content Document) f a -> RuleFor Document f a | |
RegionLike (Region t) Source # | |
Defined in Prosidy.Compile.DSL liftRegionRule :: forall (f :: Type -> Type) a. RegionRule (Content (Region t)) f a -> RuleFor (Region t) f a | |
RegionLike (Tag t) Source # | |
Defined in Prosidy.Compile.DSL liftRegionRule :: forall (f :: Type -> Type) a. RegionRule (Content (Tag t)) f a -> RuleFor (Tag t) f a |