Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data PartialFilterM m p
- type PartialFilter = PartialFilterM Identity
- type PandocFilterM m = PartialFilterM m Pandoc
- type PandocFilter = PartialFilter Pandoc
- applyFilterM :: PartialFilterM m p -> p -> m p
- applyFilter :: PartialFilter p -> p -> p
- applyFiltersM :: (Foldable t, Monad m) => t (PartialFilterM m p) -> p -> m p
- applyFilters :: Foldable t => t (PartialFilter p) -> p -> p
- getFilterM :: (Monad m, Walkable a b) => PartialFilterM m a -> b -> m b
- getFilter :: Walkable a b => PartialFilter a -> b -> b
- getConcatedFilterM :: (Foldable t, Monad m) => t (PartialFilterM m p) -> p -> m p
- getConcatedFilter :: Foldable t => t (PartialFilter p) -> p -> p
- 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
- toFilterM :: Monad m => PartialFilter p -> PartialFilterM m p
Definitions
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.
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 PartialFilter = PartialFilterM Identity Source #
type PandocFilterM m = PartialFilterM m Pandoc Source #
An alias for PartialFilterM m Pandoc
, a monadic version of
PandocFilter
.
m
: a monad.
type PandocFilter = PartialFilter Pandoc Source #
Filter application
applyFilterM :: PartialFilterM m p -> p -> m p Source #
Apply a monadic filter to p
.
:: PartialFilter p | A wrapped partial filter. |
-> p |
|
-> p | Transformed node. |
Apply an ordinary filter to p
, which returns p
directly.
Filter composition
:: (Foldable t, Monad m) | |
=> t (PartialFilterM m p) | A list of monadic partial filters. |
-> p |
|
-> m p | Transformed node. |
Apply a list of monadic partial 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.
:: Foldable t | |
=> t (PartialFilter p) | A list of partial filter. |
-> p |
|
-> p | Transformed node. |
Apply a list of partial 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.
Filter conversion
:: (Monad m, Walkable a b) | |
=> PartialFilterM m a | A wrapped partial filter on |
-> b -> m b | Unwrapped filter function that can be directly applied to |
It is mostly the same as applyFilterM
and should be used when you don't
need to apply the filter immediately. The only difference is that it will
perform an implicit conversion if the requested filter function is of a
different type.
:: Walkable a b | |
=> PartialFilter a | A wrapped partial filter on |
-> b -> b | Unwrapped filter function that can be directly applied to |
It is mostly the same as applyFilter
and should be used when you don't
need to apply the filter immediately. The only difference is that it will
perform an implicit conversion if the requested filter function is of a
different type.
:: (Foldable t, Monad m) | |
=> t (PartialFilterM m p) | A list of monadic partial filters. |
-> p -> m p | Unwrapped monadic filter applicable to |
An alias for applyFiltersM
, used when the filter is not used
immediately.
:: Foldable t | |
=> t (PartialFilter p) | A list of partial filter. |
-> p -> p | Unwrapped filter applicable to |
An alias for applyFilters
, used when the filter is not used immediately.
class ToPartialFilter m f p where Source #
A helper typeclass used as a polymorphic constructor of PartialFilterM
.
:: f | A partial filter function, usually |
-> PartialFilterM m p | Wrapped partial Pandoc filter. |
The actual constructor of PartialFilterM
. It takes an ordinary filter
function a -> b
and wraps it as a 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 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.
:: Monad m | |
=> PartialFilter p | An ordinary filter. |
-> PartialFilterM m p | The monadic version. |
Convert an ordinary PartialFilter
to the monadic version
PartialFilterM
.