diff options
author | John MacFarlane <fiddlosopher@gmail.com> | 2013-08-10 18:13:38 -0700 |
---|---|---|
committer | John MacFarlane <fiddlosopher@gmail.com> | 2013-08-10 18:13:38 -0700 |
commit | 9152fa1a95346e26bc290b3f5018b2eeb5d4e077 (patch) | |
tree | b8bd47cb2cc6621c19b4f808aa9898dd7b8490af | |
parent | 210d7b7bce32d6160fbfd558ddab921f8c3506cb (diff) | |
download | pandoc-9152fa1a95346e26bc290b3f5018b2eeb5d4e077.tar.gz |
Use query instead of queryWith.
-rw-r--r-- | src/Text/Pandoc/Biblio.hs | 5 | ||||
-rw-r--r-- | src/Text/Pandoc/Shared.hs | 29 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/ConTeXt.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/LaTeX.hs | 7 |
4 files changed, 36 insertions, 9 deletions
diff --git a/src/Text/Pandoc/Biblio.hs b/src/Text/Pandoc/Biblio.hs index 755c779ea..206b38530 100644 --- a/src/Text/Pandoc/Biblio.hs +++ b/src/Text/Pandoc/Biblio.hs @@ -36,6 +36,7 @@ import Text.CSL hiding ( Cite(..), Citation(..), endWithPunct ) import qualified Text.CSL as CSL ( Cite(..) ) import Text.Pandoc.Definition import Text.Pandoc.Generic +import Text.Pandoc.Walk import Text.Pandoc.Shared (stringify) import Text.Parsec hiding (State) import Control.Monad @@ -48,7 +49,7 @@ processBiblio Nothing _ p = p processBiblio _ [] p = p processBiblio (Just style) r p = let p' = evalState (bottomUpM setHash p) 1 - grps = queryWith getCitation p' + grps = query getCitation p' result = citeproc procOpts style r (setNearNote style $ map (map toCslCite) grps) cits_map = M.fromList $ zip grps (citations result) @@ -121,7 +122,7 @@ isTextualCitation (c:_) = citationMode c == AuthorInText isTextualCitation _ = False -- | Retrieve all citations from a 'Pandoc' docuument. To be used with --- 'queryWith'. +-- 'query'. getCitation :: Inline -> [[Citation]] getCitation i | Cite t _ <- i = [t] | otherwise = [] diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 09874299d..2b692dc3c 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable, CPP #-} +{-# LANGUAGE DeriveDataTypeable, CPP, MultiParamTypeClasses #-} {- Copyright (C) 2006-2013 John MacFarlane <jgm@berkeley.edu> @@ -79,6 +79,7 @@ module Text.Pandoc.Shared ( ) where import Text.Pandoc.Definition +import Text.Pandoc.Walk import Text.Pandoc.Generic import Text.Pandoc.Builder (Blocks, ToMetaValue(..)) import qualified Text.Pandoc.Builder as B @@ -105,6 +106,7 @@ import Text.HTML.TagSoup (renderTagsOptions, RenderOptions(..), Tag(..), renderOptions) import qualified Data.ByteString as BS import qualified Data.ByteString.Char8 as B8 +import Text.Pandoc.Compat.Monoid #ifdef EMBED_DATA_FILES import Text.Pandoc.Data (dataFiles) @@ -383,7 +385,7 @@ consolidateInlines [] = [] -- | Convert list of inlines to a string with formatting removed. stringify :: [Inline] -> String -stringify = queryWith go +stringify = query go where go :: Inline -> [Char] go Space = " " go (Str x) = x @@ -433,6 +435,29 @@ data Element = Blk Block -- lvl num attributes label contents deriving (Eq, Read, Show, Typeable, Data) +instance Walkable Inline Element where + walk f (Blk x) = Blk (walk f x) + walk f (Sec lev nums attr ils elts) = Sec lev nums attr (walk f ils) (walk f elts) + walkM f (Blk x) = Blk `fmap` walkM f x + walkM f (Sec lev nums attr ils elts) = do + ils' <- walkM f ils + elts' <- walkM f elts + return $ Sec lev nums attr ils' elts' + query f (Blk x) = query f x + query f (Sec _ _ _ ils elts) = query f ils <> query f elts + +instance Walkable Block Element where + walk f (Blk x) = Blk (walk f x) + walk f (Sec lev nums attr ils elts) = Sec lev nums attr (walk f ils) (walk f elts) + walkM f (Blk x) = Blk `fmap` walkM f x + walkM f (Sec lev nums attr ils elts) = do + ils' <- walkM f ils + elts' <- walkM f elts + return $ Sec lev nums attr ils' elts' + query f (Blk x) = query f x + query f (Sec _ _ _ ils elts) = query f ils <> query f elts + + -- | Convert Pandoc inline list to plain text identifier. HTML -- identifiers must start with a letter, and may contain only -- letters, digits, and the characters _-. diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs index 40dc1deb5..0379f8b0a 100644 --- a/src/Text/Pandoc/Writers/ConTeXt.hs +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -33,7 +33,7 @@ import Text.Pandoc.Definition import Text.Pandoc.Shared import Text.Pandoc.Writers.Shared import Text.Pandoc.Options -import Text.Pandoc.Generic (queryWith) +import Text.Pandoc.Walk (query) import Text.Printf ( printf ) import Data.List ( intercalate, isPrefixOf ) import Control.Monad.State @@ -326,7 +326,7 @@ inlineToConTeXt (Note contents) = do contents' <- blockListToConTeXt contents let codeBlock x@(CodeBlock _ _) = [x] codeBlock _ = [] - let codeBlocks = queryWith codeBlock contents + let codeBlocks = query codeBlock contents return $ if null codeBlocks then text "\\footnote{" <> nest 2 contents' <> char '}' else text "\\startbuffer " <> nest 2 contents' <> diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index d09ccc3b8..860ca8349 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -30,6 +30,7 @@ Conversion of 'Pandoc' format into LaTeX. -} module Text.Pandoc.Writers.LaTeX ( writeLaTeX ) where import Text.Pandoc.Definition +import Text.Pandoc.Walk import Text.Pandoc.Generic import Text.Pandoc.Shared import Text.Pandoc.Writers.Shared @@ -86,7 +87,7 @@ pandocToLaTeX options (Pandoc meta blocks) = do -- see if there are internal links let isInternalLink (Link _ ('#':xs,_)) = [xs] isInternalLink _ = [] - modify $ \s -> s{ stInternalLinks = queryWith isInternalLink blocks } + modify $ \s -> s{ stInternalLinks = query isInternalLink blocks } let template = writerTemplate options -- set stBook depending on documentclass let bookClasses = ["memoir","book","report","scrreprt","scrbook"] @@ -248,9 +249,9 @@ elementToBeamer slideLevel (Sec lvl _num (ident,classes,kvs) tit elts) let hasCode (Code _ _) = [True] hasCode _ = [] opts <- gets stOptions - let fragile = not $ null $ queryWith hasCodeBlock elts ++ + let fragile = not $ null $ query hasCodeBlock elts ++ if writerListings opts - then queryWith hasCode elts + then query hasCode elts else [] let allowframebreaks = "allowframebreaks" `elem` classes let optionslist = ["fragile" | fragile] ++ |