| Portability | portable |
|---|---|
| Stability | alpha |
| Maintainer | John MacFarlane <jgm@berkeley.edu> |
| Safe Haskell | Safe-Infered |
Text.Pandoc.Generic
Description
Generic functions for manipulating Pandoc documents.
Here's a simple example, defining a function that replaces all the level 3+ headers in a document with regular paragraphs in ALL CAPS:
import Text.Pandoc.Definition import Text.Pandoc.Generic import Data.Char (toUpper) modHeader :: Block -> Block modHeader (Header n xs) | n >= 3 = Para $ bottomUp allCaps xs modHeader x = x allCaps :: Inline -> Inline allCaps (Str xs) = Str $ map toUpper xs allCaps x = x changeHeaders :: Pandoc -> Pandoc changeHeaders = bottomUp modHeader
bottomUp is so called because it traverses the Pandoc structure from
bottom up. topDown goes the other way. The difference between them can be
seen from this example:
normal :: [Inline] -> [Inline]
normal (Space : Space : xs) = Space : xs
normal (Emph xs : Emph ys : zs) = Emph (xs ++ ys) : zs
normal xs = xs
myDoc :: Pandoc
myDoc = Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
[Para [Str "Hi",Space,Emph [Str "world",Space],Emph [Space,Str "emphasized"]]]
Here we want to use topDown to lift normal to Pandoc -> Pandoc.
The top down strategy will collapse the two adjacent Emphs first, then
collapse the resulting adjacent Spaces, as desired. If we used bottomUp,
we would end up with two adjacent Spaces, since the contents of the
two Emph inlines would be processed before the Emphs were collapsed
into one.
topDown normal myDoc ==
Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
[Para [Str "Hi",Space,Emph [Str "world",Space,Str "emphasized"]]]
bottomUp normal myDoc ==
Pandoc (Meta {docTitle = [], docAuthors = [], docDate = []})
[Para [Str "Hi",Space,Emph [Str "world",Space,Space,Str "emphasized"]]]
bottomUpM is a monadic version of bottomUp. It could be used,
for example, to replace the contents of delimited code blocks with
attribute include=FILENAME with the contents of FILENAME:
doInclude :: Block -> IO Block
doInclude cb@(CodeBlock (id, classes, namevals) contents) =
case lookup "include" namevals of
Just f -> return . (CodeBlock (id, classes, namevals)) =<< readFile f
Nothing -> return cb
doInclude x = return x
processIncludes :: Pandoc -> IO Pandoc
processIncludes = bottomUpM doInclude
queryWith can be used, for example, to compile a list of URLs
linked to in a document:
extractURL :: Inline -> [String] extractURL (Link _ (u,_)) = [u] extractURL (Image _ (u,_)) = [u] extractURL _ = [] extractURLs :: Pandoc -> [String] extractURLs = queryWith extractURL
- bottomUp :: (Data a, Data b) => (a -> a) -> b -> b
- topDown :: (Data a, Data b) => (a -> a) -> b -> b
- bottomUpM :: (Monad m, Data a, Data b) => (a -> m a) -> b -> m b
- queryWith :: (Data a, Monoid b, Data c) => (a -> b) -> c -> b
- processWith :: (Data a, Data b) => (a -> a) -> b -> b
- processWithM :: (Monad m, Data a, Data b) => (a -> m a) -> b -> m b
Documentation
bottomUp :: (Data a, Data b) => (a -> a) -> b -> bSource
Applies a transformation on as to matching elements in a b,
moving from the bottom of the structure up.
topDown :: (Data a, Data b) => (a -> a) -> b -> bSource
Applies a transformation on as to matching elements in a b,
moving from the top of the structure down.
bottomUpM :: (Monad m, Data a, Data b) => (a -> m a) -> b -> m bSource
Like bottomUp, but with monadic transformations.
queryWith :: (Data a, Monoid b, Data c) => (a -> b) -> c -> bSource
Runs a query on matching a elements in a c. The results
of the queries are combined using mappend.
processWith :: (Data a, Data b) => (a -> a) -> b -> bSource
Deprecated synonym for bottomUp.
processWithM :: (Monad m, Data a, Data b) => (a -> m a) -> b -> m bSource
Deprecated synonym for bottomUpM.