Add possibility to use listings package for code blocks and

inline code in the LaTeX writer.
This commit is contained in:
Josef Svenningsson 2011-01-17 23:54:51 +01:00 committed by John MacFarlane
parent e2a5038be6
commit d8d0f46c4c
5 changed files with 57 additions and 9 deletions

3
README
View file

@ -273,6 +273,9 @@ Options
: Number section headings in LaTeX, ConTeXt, or HTML output.
By default, sections are not numbered.
`--listings`
: Use listings package for LaTeX code blocks
`--section-divs`
: Wrap sections in `<div>` tags (or `<section>` tags in HTML5),
and attach identifiers to the enclosing `<div>` (or `<section>`)

View file

@ -480,6 +480,7 @@ data WriterOptions = WriterOptions
, writerBiblioFiles :: [FilePath] -- ^ Biblio files to use for citations
, writerHtml5 :: Bool -- ^ Produce HTML5
, writerChapters :: Bool -- ^ Use "chapter" for top-level sects
, writerListings :: Bool -- ^ Use listings package for code
} deriving Show
-- | Default writer options.
@ -511,6 +512,7 @@ defaultWriterOptions =
, writerBiblioFiles = []
, writerHtml5 = False
, writerChapters = False
, writerListings = False
}
--

View file

@ -117,6 +117,7 @@ pandocToLaTeX options (Pandoc (Meta title authors date) blocks) = do
[ ("lhs", "yes") | stLHS st ] ++
[ ("graphics", "yes") | stGraphics st ] ++
[ ("book-class", "yes") | stBook st] ++
[ ("listings", "yes") | writerListings options ] ++
citecontext
return $ if writerStandalone options
then renderTemplate context template
@ -170,19 +171,47 @@ blockToLaTeX (Para lst) = do
blockToLaTeX (BlockQuote lst) = do
contents <- blockListToLaTeX lst
return $ "\\begin{quote}" $$ contents $$ "\\end{quote}"
blockToLaTeX (CodeBlock (_,classes,_) str) = do
blockToLaTeX (CodeBlock (_,classes,keyvalAttr) str) = do
st <- get
env <- if writerLiterateHaskell (stOptions st) && "haskell" `elem` classes &&
"literate" `elem` classes
then do
modify $ \s -> s{ stLHS = True }
return "code"
else if stInNote st
then do
modify $ \s -> s{ stVerbInNote = True }
return "Verbatim"
else return "verbatim"
return $ "\\begin{" <> text env <> "}" $$ flush (text str) $$
else if writerListings (stOptions st)
then return "lstlisting"
else if stInNote st
then do
modify $ \s -> s{ stVerbInNote = True }
return "Verbatim"
else return "verbatim"
let params = if writerListings (stOptions st)
then take 1
[ "language=" ++ lang | lang <- classes
, lang `elem` ["ABAP","IDL","Plasm","ACSL","inform"
,"POV","Ada","Java","Prolog","Algol"
,"JVMIS","Promela","Ant","ksh","Python"
,"Assembler","Lisp","R","Awk","Logo"
,"Reduce","bash","make","Rexx","Basic"
,"Mathematica","RSL","C","Matlab","Ruby"
,"C++","Mercury","S","Caml","MetaPost"
,"SAS","Clean","Miranda","Scilab","Cobol"
,"Mizar","sh","Comal","ML","SHELXL","csh"
,"Modula-2","Simula","Delphi","MuPAD"
,"SQL","Eiffel","NASTRAN","tcl","Elan"
,"Oberon-2","TeX","erlang","OCL"
,"VBScript","Euphoria","Octave","Verilog"
,"Fortran","Oz","VHDL","GCL","Pascal"
,"VRML","Gnuplot","Perl","XML","Haskell"
,"PHP","XSLT","HTML","PL/I"]
] ++
[ key ++ "=" ++ attr | (key,attr) <- keyvalAttr ]
else []
printParams
| null params = empty
| otherwise = "[" <> hsep (intersperse "," (map text params)) <>
"]"
return $ "\\begin{" <> text env <> "}" <> printParams $$ flush (text str) $$
"\\end{" <> text env <> "}" $$ cr -- final cr needed because of footnotes
blockToLaTeX (RawBlock "latex" x) = return $ text x <> blankline
blockToLaTeX (RawBlock _ _) = return empty
@ -335,7 +364,9 @@ inlineToLaTeX (Code _ str) = do
st <- get
when (stInNote st) $ modify $ \s -> s{ stVerbInNote = True }
let chr = ((enumFromTo '!' '~') \\ str) !! 0
return $ text $ "\\verb" ++ [chr] ++ str ++ [chr]
if writerListings (stOptions st)
then return $ text $ "\\lstinline" ++ [chr] ++ str ++ [chr]
else return $ text $ "\\verb" ++ [chr] ++ str ++ [chr]
inlineToLaTeX (Quoted SingleQuote lst) = do
contents <- inlineListToLaTeX lst
let s1 = if (not (null lst)) && (isQuoted (head lst))

View file

@ -122,6 +122,7 @@ data Opt = Opt
, optCiteMethod :: CiteMethod -- ^ Method to output cites
, optBibliography :: [String]
, optCslFile :: FilePath
, optListings :: Bool -- ^ Use listings package for code blocks
}
-- | Defaults for command-line options.
@ -164,6 +165,7 @@ defaultOpts = Opt
, optCiteMethod = Citeproc
, optBibliography = []
, optCslFile = ""
, optListings = False
}
-- | A list of functions, each transforming the options data structure
@ -318,6 +320,11 @@ options =
(\opt -> return opt { optNumberSections = True }))
"" -- "Number sections in LaTeX"
, Option "" ["listings"]
(NoArg
(\opt -> return opt { optListings = True }))
"" -- "Use listings package for LaTeX code blocks"
, Option "" ["section-divs"]
(NoArg
(\opt -> return opt { optSectionDivs = True }))
@ -674,6 +681,7 @@ main = do
, optBibliography = reffiles
, optCslFile = cslfile
, optCiteMethod = citeMethod
, optListings = listings
} = opts
when dumpArgs $
@ -802,7 +810,8 @@ main = do
writerUserDataDir = datadir,
writerHtml5 = html5 &&
"html" `isPrefixOf` writerName',
writerChapters = chapters }
writerChapters = chapters,
writerListings = listings }
when (isNonTextOutput writerName' && outputFile == "-") $
do UTF8.hPutStrLn stderr ("Error: Cannot write " ++ writerName ++ " output to stdout.\n" ++

View file

@ -71,6 +71,9 @@ $endif$
\usepackage[breaklinks=true,unicode=true,pdfborder={0 0 0}]{hyperref}
\setlength{\parindent}{0pt}
\setlength{\parskip}{6pt plus 2pt minus 1pt}
$if(listings)$
\usepackage{listings}
$endif$
$if(numbersections)$
$else$
\setcounter{secnumdepth}{0}