diff options
Diffstat (limited to 'src/pandoc.hs')
| -rw-r--r-- | src/pandoc.hs | 93 |
1 files changed, 68 insertions, 25 deletions
diff --git a/src/pandoc.hs b/src/pandoc.hs index 3ef82accc..190248a29 100644 --- a/src/pandoc.hs +++ b/src/pandoc.hs @@ -33,19 +33,20 @@ 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 import System.Console.GetOpt import Data.Char ( toLower ) -import Data.List ( intercalate, isSuffixOf ) +import Data.List ( intercalate, isSuffixOf, isPrefixOf ) import System.Directory ( getAppUserDataDirectory, doesFileExist ) 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(..)) @@ -62,19 +63,20 @@ copyrightMessage = "\nCopyright (C) 2006-2011 John MacFarlane\n" ++ compileInfo :: String compileInfo = - "\nCompiled with citeproc support." ++ - "\nCompiled with syntax highlighting support for:\n" ++ - wrapWords 78 languages + "\nCompiled with citeproc-hs " ++ VERSION_citeproc_hs ++ " and " ++ + "highlighting-kate " ++ VERSION_highlighting_kate ++ + ".\nSyntax highlighting is supported for the following languages:\n " ++ + wrapWords 4 78 languages -- | Converts a list of strings into a single string with the items printed as -- comma separated words in lines with a maximum line length. -wrapWords :: Int -> [String] -> String -wrapWords c = wrap' c c where - wrap' _ _ [] = "" +wrapWords :: Int -> Int -> [String] -> String +wrapWords indent c = wrap' (c - indent) (c - indent) + where wrap' _ _ [] = "" wrap' cols remaining (x:xs) = if remaining == cols then x ++ wrap' cols (remaining - length x) xs else if (length x + 1) > remaining - then ",\n" ++ x ++ wrap' cols (cols - length x) xs + then ",\n" ++ replicate indent ' ' ++ x ++ wrap' cols (cols - length x) xs else ", " ++ x ++ wrap' cols (remaining - (length x + 2)) xs isNonTextOutput :: String -> Bool @@ -100,6 +102,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 +148,8 @@ defaultOpts = Opt , optXeTeX = False , optSmart = False , optHtml5 = False + , optHighlight = True + , optHighlightStyle = pygments , optChapters = False , optHTMLMathMethod = PlainMath , optReferenceODT = Nothing @@ -239,9 +245,34 @@ options = , Option "5" ["html5"] (NoArg - (\opt -> return opt { optHtml5 = True })) + (\opt -> do + UTF8.hPutStrLn stderr $ "pandoc: --html5 is deprecated. " + ++ "Use the html5 output format instead." + 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 -> @@ -590,8 +621,8 @@ options = usageMessage :: String -> [OptDescr (Opt -> IO Opt)] -> String usageMessage programName = usageInfo (programName ++ " [OPTIONS] [FILES]" ++ "\nInput formats: " ++ - (intercalate ", " $ map fst readers) ++ "\nOutput formats: " ++ - (intercalate ", " $ map fst writers ++ ["odt","epub"]) ++ "\nOptions:") + (wrapWords 16 78 $ map fst readers) ++ "\nOutput formats: " ++ + (wrapWords 16 78 $ map fst writers ++ ["odt","epub"]) ++ "\nOptions:") -- Determine default reader based on source file extensions defaultReaderName :: String -> [FilePath] -> String @@ -691,6 +722,8 @@ main = do , optSelfContained = selfContained , optSmart = smart , optHtml5 = html5 + , optHighlight = highlight + , optHighlightStyle = highlightStyle , optChapters = chapters , optHTMLMathMethod = mathMethod , optReferenceODT = referenceODT @@ -765,6 +798,12 @@ main = do (\_ -> throwIO e) else throwIO e) + let slideVariant = case writerName' of + "s5" -> S5Slides + "slidy" -> SlidySlides + "dzslides" -> DZSlides + _ -> NoSlides + variables' <- case mathMethod of LaTeXMathML Nothing -> do s <- readDataFile datadir $ "data" </> "LaTeXMathML.js" @@ -774,7 +813,15 @@ main = do return $ ("mathml-script", s) : variables _ -> return variables - refs <- mapM (\f -> catch (readBiblioFile f) $ \e -> do + variables'' <- case slideVariant of + DZSlides -> do + dztempl <- readDataFile datadir $ "dzslides" </> "template.html" + let dzcore = unlines $ dropWhile (not . isPrefixOf "<!-- {{{{ dzslides core") + $ lines dztempl + return $ ("dzslides-core", dzcore) : variables' + _ -> return variables' + + 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 @@ -783,30 +830,25 @@ main = do then "." else takeDirectory (head sources) - let slideVariant = case writerName' of - "s5" -> S5Slides - "slidy" -> SlidySlides - "dzslides" -> DZSlides - _ -> NoSlides - let startParserState = defaultParserState { stateParseRaw = parseRaw, stateTabStop = tabStop, 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"], + ["latex", "context", "latex+lhs", "beamer"], stateColumns = columns, stateStrict = strict, stateIndentedCodeClasses = codeBlockClasses, - stateApplyMacros = writerName' `notElem` ["latex", "latex+lhs"] } + stateApplyMacros = writerName' `notElem` + ["latex", "latex+lhs", "beamer"] } let writerOptions = defaultWriterOptions { writerStandalone = standalone', writerTemplate = templ, - writerVariables = variables', + writerVariables = variables'', writerEPUBMetadata = epubMetadata, writerTabStop = tabStop, writerTableOfContents = toc && @@ -835,7 +877,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" ++ |
