Reinstated dependence on fancyvrb. It is compatible with examplep.
fancyvrb is needed for verbatim environments in footnotes. git-svn-id: https://pandoc.googlecode.com/svn/trunk@808 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
parent
b29f221cba
commit
d488dd0f66
3 changed files with 29 additions and 13 deletions
3
README
3
README
|
@ -59,7 +59,8 @@ The wrapper script `markdown2pdf` requires
|
||||||
- the following LaTeX packages (available from [CTAN], if they
|
- the following LaTeX packages (available from [CTAN], if they
|
||||||
are not already included in your LaTeX distribution):
|
are not already included in your LaTeX distribution):
|
||||||
+ `unicode` (for UTF8 characters)
|
+ `unicode` (for UTF8 characters)
|
||||||
+ `examplep` (for verbatim text in footnotes and definition lists)
|
+ `examplep` (for verbatim text in definition lists, etc.)
|
||||||
|
+ `fancyhdr` (for verbatim text in footnotes)
|
||||||
+ `graphicx` (for images)
|
+ `graphicx` (for images)
|
||||||
+ `array` (for tables)
|
+ `array` (for tables)
|
||||||
+ `ulem` (for strikeout text)
|
+ `ulem` (for strikeout text)
|
||||||
|
|
|
@ -29,9 +29,9 @@ output through `iconv`:
|
||||||
iconv -t utf-8 input.txt | pandoc | iconv -f utf-8
|
iconv -t utf-8 input.txt | pandoc | iconv -f utf-8
|
||||||
|
|
||||||
`markdown2pdf` assumes that the `unicode`, `examplep`, `array`,
|
`markdown2pdf` assumes that the `unicode`, `examplep`, `array`,
|
||||||
`graphicx`, and `ulem` packages are in latex's search path. If these
|
`fancyvrb`, `graphicx`, and `ulem` packages are in latex's search path.
|
||||||
packages are not included in your latex setup, they can be obtained from
|
If these packages are not included in your latex setup, they can be
|
||||||
<http://ctan.org>.
|
obtained from <http://ctan.org>.
|
||||||
|
|
||||||
# OPTIONS
|
# OPTIONS
|
||||||
|
|
||||||
|
|
|
@ -38,17 +38,22 @@ import Data.Char ( isAlphaNum )
|
||||||
import qualified Data.Set as S
|
import qualified Data.Set as S
|
||||||
import Control.Monad.State
|
import Control.Monad.State
|
||||||
|
|
||||||
type WriterState = S.Set String -- set of strings to include in header
|
data WriterState =
|
||||||
-- constructed based on content of document
|
WriterState { stIncludes :: S.Set String -- strings to include in header
|
||||||
|
, stInNote :: Bool } -- @True@ if we're in a note
|
||||||
|
|
||||||
-- | Add line to header.
|
-- | Add line to header.
|
||||||
addToHeader :: String -> State WriterState ()
|
addToHeader :: String -> State WriterState ()
|
||||||
addToHeader str = modify (S.insert str)
|
addToHeader str = do
|
||||||
|
st <- get
|
||||||
|
let includes = stIncludes st
|
||||||
|
put st {stIncludes = S.insert str includes}
|
||||||
|
|
||||||
-- | Convert Pandoc to LaTeX.
|
-- | Convert Pandoc to LaTeX.
|
||||||
writeLaTeX :: WriterOptions -> Pandoc -> String
|
writeLaTeX :: WriterOptions -> Pandoc -> String
|
||||||
writeLaTeX options document =
|
writeLaTeX options document =
|
||||||
evalState (pandocToLaTeX options document) S.empty
|
evalState (pandocToLaTeX options document) $
|
||||||
|
WriterState { stIncludes = S.empty, stInNote = False }
|
||||||
|
|
||||||
pandocToLaTeX :: WriterOptions -> Pandoc -> State WriterState String
|
pandocToLaTeX :: WriterOptions -> Pandoc -> State WriterState String
|
||||||
pandocToLaTeX options (Pandoc meta blocks) = do
|
pandocToLaTeX options (Pandoc meta blocks) = do
|
||||||
|
@ -75,7 +80,10 @@ latexHeader options (Meta title authors date) = do
|
||||||
then return ""
|
then return ""
|
||||||
else do title' <- inlineListToLaTeX title
|
else do title' <- inlineListToLaTeX title
|
||||||
return $ "\\title{" ++ title' ++ "}\n"
|
return $ "\\title{" ++ title' ++ "}\n"
|
||||||
extras <- get >>= (return . unlines . S.toList)
|
extras <- get >>= (return . unlines . S.toList. stIncludes)
|
||||||
|
let verbatim = if "\\usepackage{fancyvrb}" `isInfixOf` extras
|
||||||
|
then "\\VerbatimFootnotes % allows verbatim text in footnotes\n"
|
||||||
|
else ""
|
||||||
let authorstext = "\\author{" ++ (joinWithSep "\\\\"
|
let authorstext = "\\author{" ++ (joinWithSep "\\\\"
|
||||||
(map stringToLaTeX authors)) ++ "}\n"
|
(map stringToLaTeX authors)) ++ "}\n"
|
||||||
let datetext = if date == ""
|
let datetext = if date == ""
|
||||||
|
@ -87,7 +95,7 @@ latexHeader options (Meta title authors date) = do
|
||||||
else "\\setcounter{secnumdepth}{0}\n"
|
else "\\setcounter{secnumdepth}{0}\n"
|
||||||
let baseHeader = writerHeader options
|
let baseHeader = writerHeader options
|
||||||
let header = baseHeader ++ extras
|
let header = baseHeader ++ extras
|
||||||
return $ header ++ secnumline ++ titletext ++ authorstext ++
|
return $ header ++ secnumline ++ verbatim ++ titletext ++ authorstext ++
|
||||||
datetext ++ "\\begin{document}\n" ++ maketitle ++ "\n"
|
datetext ++ "\\begin{document}\n" ++ maketitle ++ "\n"
|
||||||
|
|
||||||
-- escape things as needed for LaTeX
|
-- escape things as needed for LaTeX
|
||||||
|
@ -120,8 +128,11 @@ blockToLaTeX (Para lst) = (inlineListToLaTeX lst) >>= (return . (++ "\n\n"))
|
||||||
blockToLaTeX (BlockQuote lst) = do
|
blockToLaTeX (BlockQuote lst) = do
|
||||||
contents <- blockListToLaTeX lst
|
contents <- blockListToLaTeX lst
|
||||||
return $ "\\begin{quote}\n" ++ contents ++ "\\end{quote}\n"
|
return $ "\\begin{quote}\n" ++ contents ++ "\\end{quote}\n"
|
||||||
blockToLaTeX (CodeBlock str) = return $
|
blockToLaTeX (CodeBlock str) = do
|
||||||
"\\begin{verbatim}\n" ++ str ++ "\n\\end{verbatim}\n"
|
st <- get
|
||||||
|
let verbEnv = if stInNote st then "Verbatim" else "verbatim"
|
||||||
|
return $ "\\begin{" ++ verbEnv ++ "}\n" ++ str ++
|
||||||
|
"\n\\end{" ++ verbEnv ++ "}\n"
|
||||||
blockToLaTeX (RawHtml str) = return ""
|
blockToLaTeX (RawHtml str) = return ""
|
||||||
blockToLaTeX (BulletList lst) = do
|
blockToLaTeX (BulletList lst) = do
|
||||||
items <- mapM listItemToLaTeX lst
|
items <- mapM listItemToLaTeX lst
|
||||||
|
@ -243,6 +254,10 @@ inlineToLaTeX (Image alternate (source, tit)) = do
|
||||||
addToHeader "\\usepackage{graphicx}"
|
addToHeader "\\usepackage{graphicx}"
|
||||||
return $ "\\includegraphics{" ++ source ++ "}"
|
return $ "\\includegraphics{" ++ source ++ "}"
|
||||||
inlineToLaTeX (Note contents) = do
|
inlineToLaTeX (Note contents) = do
|
||||||
|
st <- get
|
||||||
|
put (st {stInNote = True})
|
||||||
contents' <- blockListToLaTeX contents
|
contents' <- blockListToLaTeX contents
|
||||||
|
st <- get
|
||||||
|
put (st {stInNote = False})
|
||||||
|
addToHeader "\\usepackage{fancyvrb}"
|
||||||
return $ "\\footnote{" ++ stripTrailingNewlines contents' ++ "}"
|
return $ "\\footnote{" ++ stripTrailingNewlines contents' ++ "}"
|
||||||
|
|
||||||
|
|
Loading…
Reference in a new issue