Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module contains some utility functions to work with different levels
of Pandoc filters. For example, for the conversion from
to Inline
->
[Inline
]
filter.Pandoc
-> Pandoc
If you don't need to compose filters and only want to convert between Pandoc
filter functions, just use convertFilter
and convertFilterM
.
However, if you are working with multiple Pandoc filters of different type
and want to compose them, this module also provides a monoid wrapper type
PartialFilterM
, which I call a "wrapped filter", and a few functions to
apply, compose, and convert them.
Synopsis
- convertFilter :: ToPartialFilter Identity f p => f -> p -> p
- convertFilterM :: (Monad m, ToPartialFilter m f p) => f -> p -> m p
- type PartialFilter = PartialFilterM Identity
- type PandocFilter = PartialFilter Pandoc
- data PartialFilterM m p
- type PandocFilterM m = PartialFilterM m Pandoc
- class ToPartialFilter m f p where
- mkFilter :: f -> PartialFilterM m p
- mkConcatedFilter :: (Monad m, ToPartialFilter m f p, Foldable t) => t f -> PartialFilterM m p
- applyFilter :: PartialFilter p -> p -> p
- applyFilters :: Foldable t => t (PartialFilter p) -> p -> p
- applyFilterM :: PartialFilterM m p -> p -> m p
- applyFiltersM :: (Foldable t, Monad m) => t (PartialFilterM m p) -> p -> m p
- getFilter :: Walkable a b => PartialFilter a -> b -> b
- getConcatedFilter :: (Foldable t, Walkable a b) => t (PartialFilter a) -> b -> b
- getFilterM :: (Monad m, Walkable a b) => PartialFilterM m a -> b -> m b
- getConcatedFilterM :: (Foldable t, Monad m, Walkable a b) => t (PartialFilterM m a) -> b -> m b
- toFilterM :: Monad m => PartialFilter p -> PartialFilterM m p
Filter function conversion
:: ToPartialFilter Identity f p | |
=> f | A filter function. |
-> p -> p | Filter function acting on |
:: (Monad m, ToPartialFilter m f p) | |
=> f | A monadic filter function. |
-> p -> m p | Monadic filter function acting on |
Wrapped filter definitions
type PartialFilter = PartialFilterM Identity Source #
type PandocFilter = PartialFilter Pandoc Source #
data PartialFilterM m p Source #
PartialFilterM m p
is a wrapper for any monadic p -> m p
Pandoc
filters acting on a subnode (e.g. Inline
or Block
) of the Pandoc
abstract syntax tree. On this page, we will call it a "wrapped" filter to
distinguish it from filter functions a -> m b
.
Instances
(Monad m, Walkable a b) => ToPartialFilter m (PartialFilterM m a) b Source # | This instance can be used to convert |
Defined in Text.Pandoc.Filter.Utils mkFilter :: PartialFilterM m a -> PartialFilterM m b Source # | |
Monad m => Semigroup (PartialFilterM m p) Source # | The |
Defined in Text.Pandoc.Filter.Utils (<>) :: PartialFilterM m p -> PartialFilterM m p -> PartialFilterM m p # sconcat :: NonEmpty (PartialFilterM m p) -> PartialFilterM m p # stimes :: Integral b => b -> PartialFilterM m p -> PartialFilterM m p # | |
Monad m => Monoid (PartialFilterM m p) Source # | The |
Defined in Text.Pandoc.Filter.Utils mempty :: PartialFilterM m p # mappend :: PartialFilterM m p -> PartialFilterM m p -> PartialFilterM m p # mconcat :: [PartialFilterM m p] -> PartialFilterM m p # |
type PandocFilterM m = PartialFilterM m Pandoc Source #
An alias for PartialFilterM m Pandoc
, a monadic version of
PandocFilter
.
m
: a monad.
Filter function → Wrapped filter
class ToPartialFilter m f p where Source #
A helper typeclass used as a polymorphic constructor of PartialFilterM
.
:: f | A filter function, usually |
-> PartialFilterM m p | Wrapped Pandoc filter. |
The actual constructor of PartialFilterM
. It takes an ordinary filter
function a -> b
and wraps it as a wrapped filter PartialFilterM
. It
can also be used to convert between different types of
.PartialFilterM
m
Instances
(Monad m, Walkable a b) => ToPartialFilter m (PartialFilterM m a) b Source # | This instance can be used to convert |
Defined in Text.Pandoc.Filter.Utils mkFilter :: PartialFilterM m a -> PartialFilterM m b Source # | |
(Monad m, Walkable [a] p) => ToPartialFilter m (a -> m [a]) p Source # | |
Defined in Text.Pandoc.Filter.Utils mkFilter :: (a -> m [a]) -> PartialFilterM m p Source # | |
(Monad m, Walkable [a] p) => ToPartialFilter m (a -> [a]) p Source # | |
Defined in Text.Pandoc.Filter.Utils mkFilter :: (a -> [a]) -> PartialFilterM m p Source # | |
(Monad m, Walkable a p) => ToPartialFilter m (a -> m a) p Source # | |
Defined in Text.Pandoc.Filter.Utils mkFilter :: (a -> m a) -> PartialFilterM m p Source # | |
(Monad m, Walkable a p) => ToPartialFilter m (a -> a) p Source # | |
Defined in Text.Pandoc.Filter.Utils mkFilter :: (a -> a) -> PartialFilterM m p Source # |
:: (Monad m, ToPartialFilter m f p, Foldable t) | |
=> t f | A list of filter functions of the same type. |
-> PartialFilterM m p | Concatenated filter. |
Construct a wrapped filter PartialFilterM
from a list of filter
functions of the same type. The final filter is concatenated from left to
right such that the first element in the list will be applied first and the
last element will be applied at the end.
For example, it can be used to convert an list of filter functions
[
to a wrapped filter Inline
-> [Inline
]]
.PandocFilter
Wrapped filter application/composition
:: PartialFilter p | A wrapped filter. |
-> p |
|
-> p | Transformed node. |
Apply a wrapped filter to p
, which returns p
directly.
:: Foldable t | |
=> t (PartialFilter p) | A list of wrapped filter. |
-> p |
|
-> p | Transformed node. |
Apply a list of wrapped filters sequentially, from left to right, i.e. the first element in the list will be applied first and the last element will be applied at the end.
applyFilterM :: PartialFilterM m p -> p -> m p Source #
Apply a monadic filter to p
.
:: (Foldable t, Monad m) | |
=> t (PartialFilterM m p) | A list of monadic wrapped filters. |
-> p |
|
-> m p | Transformed node. |
Apply a list of monadic wrapped filters sequentially, from left to right, i.e. the first element in the list will be applied first and the last element will be applied at the end.
Wrapped filter → filter function
:: Walkable a b | |
=> PartialFilter a | A wrapped partial filter on |
-> b -> b | Filter function that can be directly applied to |
It is mostly the same as applyFilter
, which converts a wrapped filter to
a filter function, but it should be used when you don't need to apply the
filter immediately. There is a slight difference in that it will perform an
implicit conversion if the requested filter function is of a different type.
For example, it can be used to convert a wrapped filter
to filter function PartialFilter
Inline
.Block
-> Block
:: (Foldable t, Walkable a b) | |
=> t (PartialFilter a) | A list of wrapped filter acting on |
-> b -> b | Filter function applicable to |
It is mostly the same as applyFilters
, which converts a list of wrapped
filter to a filter function, but it should be used when you don't need to
apply the filter immediately. There is a slight difference in that it will
perform an implicit conversion if the requested filter function is of a
different type.
For example, it can be used to convert a list of wrapped filter
[
to a filter function PartialFilter
Inline
]
.Block
-> Block
:: (Monad m, Walkable a b) | |
=> PartialFilterM m a | A wrapped filter on |
-> b -> m b | Filter function that can be directly applied to |
It is mostly the same as applyFilterM
, which converts a wrapped monadic
filter to a monadic filter function, but it should be used when you don't
need to apply the filter immediately. There is a slight difference in that
it will perform an implicit conversion if the requested filter function is
of a different type.
For example, it can be used to convert a wrapped monadic filter
to monadic filter function PartialFilterM
IO
Inline
.Block
-> IO
Block
:: (Foldable t, Monad m, Walkable a b) | |
=> t (PartialFilterM m a) | A list of monadic partial filters on |
-> b -> m b | Monadic filter function applicable to |
It is mostly the same as applyFiltersM
, which converts a list of wrapped
monadic filter to a monadic filter function, but it should be used when you
don't need to apply the filter immediately. There is a slight difference in
that it will perform an implicit conversion if the requested filter function
is of a different type.
For example, it can be used to convert a list of wrapped monadic filter
[
to a filter function PartialFilterM
IO
Inline
]
.Block
-> IO
Block
Wrapped filter conversion
:: Monad m | |
=> PartialFilter p | An ordinary filter. |
-> PartialFilterM m p | The monadic version. |
Convert an ordinary wrapped filter PartialFilter
to the monadic version
PartialFilterM
.
For example, it can be used to convert an ordinary wrapped filter
to monadic wrapped filter PartialFilter
Inline
.PartialFilterM
IO
Inline