aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--README23
-rw-r--r--src/Text/Pandoc/Highlighting.hs6
-rw-r--r--src/Text/Pandoc/Shared.hs3
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs5
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs5
-rw-r--r--src/pandoc.hs40
6 files changed, 67 insertions, 15 deletions
diff --git a/README b/README
index 7790c4c8d..fa3a4e818 100644
--- a/README
+++ b/README
@@ -217,6 +217,15 @@ Options
: Produce HTML5 instead of HTML4. This option has no effect for writers
other than `html`.
+`--no-highlight`
+: Disables syntax highlighting for code blocks and inlines, even when
+ a language attribute is given.
+
+`--highlight-style`=*STYLE*
+: Specifies the coloring style to be used in highlighted source code.
+ Options are `pygments` (the default), `kate`, `monochrome`,
+ `espresso`, `haddock`, and `tango`.
+
`-m` [*URL*], `--latexmathml`[=*URL*]
: Use the [LaTeXMathML] script to display embedded TeX math in HTML output.
To insert a link to a local copy of the `LaTeXMathML.js` script,
@@ -837,15 +846,15 @@ this syntax:
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ {.haskell .numberLines}
qsort [] = []
qsort (x:xs) = qsort (filter (< x) xs) ++ [x] ++
- qsort (filter (>= x) xs)
+ qsort (filter (>= x) xs)
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Some output formats can use this information to do syntax highlighting.
-Currently, the only output format that uses this information is HTML.
-If highlighting is supported for your output format and language, then the
-code block above will appear highlighted, with numbered lines. (To see
-which languages are supported, do `pandoc --version`.) Otherwise, the
-code block above will appear as follows:
+Currently, the only output formats that uses this information are HTML
+and LaTeX. If highlighting is supported for your output format and language,
+then the code block above will appear highlighted, with numbered lines. (To
+see which languages are supported, do `pandoc --version`.) Otherwise, the code
+block above will appear as follows:
<pre class="haskell">
<code>
@@ -853,6 +862,8 @@ code block above will appear as follows:
</code>
</pre>
+To prevent all highlighting, use the `--no-highlight` flag.
+To set the highlighting style, use `--highlight-style`.
Lists
-----
diff --git a/src/Text/Pandoc/Highlighting.hs b/src/Text/Pandoc/Highlighting.hs
index 0570fb2d2..276d98529 100644
--- a/src/Text/Pandoc/Highlighting.hs
+++ b/src/Text/Pandoc/Highlighting.hs
@@ -38,6 +38,12 @@ module Text.Pandoc.Highlighting ( languages
, formatHtmlBlock
, styleToHtml
, pygments
+ , espresso
+ , tango
+ , kate
+ , monochrome
+ , haddock
+ , Style
) where
import Text.Pandoc.Definition
import Text.Highlighting.Kate
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index 301848d6e..81a5e6875 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -81,6 +81,7 @@ import System.FilePath ( (</>) )
import Data.Generics (Typeable, Data)
import qualified Control.Monad.State as S
import Paths_pandoc (getDataFileName)
+import Text.Pandoc.Highlighting (Style, pygments)
--
-- List processing
@@ -479,6 +480,7 @@ data WriterOptions = WriterOptions
, writerChapters :: Bool -- ^ Use "chapter" for top-level sects
, writerListings :: Bool -- ^ Use listings package for code
, writerHighlight :: Bool -- ^ Highlight source code
+ , writerHighlightStyle :: Style -- ^ Style to use for highlighting
} deriving Show
{-# DEPRECATED writerXeTeX "writerXeTeX no longer does anything" #-}
@@ -513,6 +515,7 @@ defaultWriterOptions =
, writerChapters = False
, writerListings = False
, writerHighlight = False
+ , writerHighlightStyle = pygments
}
--
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index e3ade3c9e..3b926cf06 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -35,7 +35,7 @@ import Text.Pandoc.CharacterReferences ( decodeCharacterReferences )
import Text.Pandoc.Shared
import Text.Pandoc.Templates
import Text.Pandoc.Readers.TeXMath
-import Text.Pandoc.Highlighting ( highlight, pygments, styleToHtml,
+import Text.Pandoc.Highlighting ( highlight, styleToHtml,
formatHtmlInline, formatHtmlBlock )
import Text.Pandoc.XML (stripTags, escapeStringForXML)
import Network.HTTP ( urlEncode )
@@ -154,7 +154,8 @@ pandocToHtml opts (Pandoc (Meta title' authors' date') blocks) = do
("/*<![CDATA[*/\n" ++ s ++ "/*]]>*/\n")
Nothing -> mempty
else mempty
- let newvars = [("highlighting-css", renderHtml $ styleToHtml pygments) |
+ let newvars = [("highlighting-css", renderHtml $ styleToHtml
+ $ writerHighlightStyle opts) |
stHighlighting st] ++
[("math", renderHtml math) | stMath st]
return (tit, auths, date, toc, thebody, newvars)
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index dd11cd2fe..b0e880bae 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -41,7 +41,7 @@ import Data.Char ( toLower, isPunctuation )
import Control.Monad.State
import Text.Pandoc.Pretty
import System.FilePath (dropExtension)
-import Text.Pandoc.Highlighting (highlight, pygments, styleToLaTeX,
+import Text.Pandoc.Highlighting (highlight, styleToLaTeX,
formatLaTeXInline, formatLaTeXBlock)
data WriterState =
@@ -132,7 +132,8 @@ pandocToLaTeX options (Pandoc (Meta title authors date) blocks) = do
[ ("graphics", "yes") | stGraphics st ] ++
[ ("book-class", "yes") | stBook st] ++
[ ("listings", "yes") | writerListings options || stLHS st ] ++
- [ ("highlighting-macros", styleToLaTeX pygments) | stHighlighting st ] ++
+ [ ("highlighting-macros", styleToLaTeX
+ $ writerHighlightStyle opts ) | stHighlighting st ] ++
citecontext
return $ if writerStandalone options
then renderTemplate context template
diff --git a/src/pandoc.hs b/src/pandoc.hs
index 3ef82accc..2aeebdbcf 100644
--- a/src/pandoc.hs
+++ b/src/pandoc.hs
@@ -33,7 +33,8 @@ import Text.Pandoc
import Text.Pandoc.Shared ( tabFilter, ObfuscationMethod (..), readDataFile,
headerShift, findDataFile, normalize )
import Text.Pandoc.SelfContained ( makeSelfContained )
-import Text.Pandoc.Highlighting ( languages )
+import Text.Pandoc.Highlighting ( languages, Style, tango, pygments,
+ espresso, kate, haddock, monochrome )
import System.Environment ( getArgs, getProgName )
import System.Exit ( exitWith, ExitCode (..) )
import System.FilePath
@@ -45,7 +46,7 @@ import System.IO ( stdout, stderr )
import System.IO.Error ( isDoesNotExistError )
import Control.Exception.Extensible ( throwIO )
import qualified Text.Pandoc.UTF8 as UTF8
-import Text.CSL
+import qualified Text.CSL as CSL
import Text.Pandoc.Biblio
import Control.Monad (when, unless, liftM)
import Network.HTTP (simpleHTTP, mkRequest, getResponseBody, RequestMethod(..))
@@ -100,6 +101,8 @@ data Opt = Opt
, optXeTeX :: Bool -- ^ Format latex for xetex
, optSmart :: Bool -- ^ Use smart typography
, optHtml5 :: Bool -- ^ Produce HTML5 in HTML
+ , optHighlight :: Bool -- ^ Highlight source code
+ , optHighlightStyle :: Style -- ^ Style to use for highlighted code
, optChapters :: Bool -- ^ Use chapter for top-level sects
, optHTMLMathMethod :: HTMLMathMethod -- ^ Method to print HTML math
, optReferenceODT :: Maybe FilePath -- ^ Path of reference.odt
@@ -144,6 +147,8 @@ defaultOpts = Opt
, optXeTeX = False
, optSmart = False
, optHtml5 = False
+ , optHighlight = True
+ , optHighlightStyle = pygments
, optChapters = False
, optHTMLMathMethod = PlainMath
, optReferenceODT = Nothing
@@ -242,6 +247,28 @@ options =
(\opt -> return opt { optHtml5 = True }))
"" -- "Produce HTML5 in HTML output"
+ , Option "" ["no-highlight"]
+ (NoArg
+ (\opt -> return opt { optHighlight = False }))
+ "" -- "Don't highlight source code"
+
+ , Option "" ["highlight-style"]
+ (ReqArg
+ (\arg opt -> do
+ newStyle <- case map toLower arg of
+ "pygments" -> return pygments
+ "tango" -> return tango
+ "espresso" -> return espresso
+ "kate" -> return kate
+ "monochrome" -> return monochrome
+ "haddock" -> return haddock
+ _ -> UTF8.hPutStrLn stderr
+ ("Unknown style: " ++ arg) >>
+ exitWith (ExitFailure 39)
+ return opt{ optHighlightStyle = newStyle })
+ "STYLE")
+ "" -- "Style for highlighted code"
+
, Option "m" ["latexmathml", "asciimathml"]
(OptArg
(\arg opt ->
@@ -691,6 +718,8 @@ main = do
, optSelfContained = selfContained
, optSmart = smart
, optHtml5 = html5
+ , optHighlight = highlight
+ , optHighlightStyle = highlightStyle
, optChapters = chapters
, optHTMLMathMethod = mathMethod
, optReferenceODT = referenceODT
@@ -774,7 +803,7 @@ main = do
return $ ("mathml-script", s) : variables
_ -> return variables
- refs <- mapM (\f -> catch (readBiblioFile f) $ \e -> do
+ refs <- mapM (\f -> catch (CSL.readBiblioFile f) $ \e -> do
UTF8.hPutStrLn stderr $ "Error reading bibliography `" ++ f ++ "'"
UTF8.hPutStrLn stderr $ show e
exitWith (ExitFailure 23)) reffiles >>= \rs -> return $ concat rs
@@ -795,7 +824,7 @@ main = do
stateLiterateHaskell = "+lhs" `isSuffixOf` readerName' ||
lhsExtension sources,
stateStandalone = standalone',
- stateCitations = map refId refs,
+ stateCitations = map CSL.refId refs,
stateSmart = smart || writerName' `elem`
["latex", "context", "latex+lhs", "man"],
stateColumns = columns,
@@ -835,7 +864,8 @@ main = do
slideVariant == DZSlides,
writerChapters = chapters,
writerListings = listings,
- writerHighlight = True }
+ writerHighlight = highlight,
+ writerHighlightStyle = highlightStyle }
when (isNonTextOutput writerName' && outputFile == "-") $
do UTF8.hPutStrLn stderr ("Error: Cannot write " ++ writerName' ++ " output to stdout.\n" ++