diff options
Diffstat (limited to 'pandoc.hs')
-rw-r--r-- | pandoc.hs | 176 |
1 files changed, 90 insertions, 86 deletions
@@ -45,10 +45,10 @@ import Text.Pandoc.Process (pipeProcess) import Text.Highlighting.Kate ( languages, Style, tango, pygments, espresso, zenburn, kate, haddock, monochrome ) import System.Environment ( getArgs, getProgName ) -import System.Exit ( exitWith, ExitCode (..) ) +import System.Exit ( ExitCode (..), exitSuccess ) import System.FilePath import System.Console.GetOpt -import Data.Char ( toLower ) +import Data.Char ( toLower, toUpper ) import Data.List ( delete, intercalate, isPrefixOf, isSuffixOf, sort ) import System.Directory ( getAppUserDataDirectory, findExecutable, doesFileExist, Permissions(..), getPermissions ) @@ -58,7 +58,7 @@ import qualified Control.Exception as E import Control.Exception.Extensible ( throwIO ) import qualified Text.Pandoc.UTF8 as UTF8 import Control.Monad (when, unless, (>=>)) -import Data.Maybe (fromMaybe, isNothing) +import Data.Maybe (fromMaybe, isNothing, isJust) import Data.Foldable (foldrM) import Network.URI (parseURI, isURI, URI(..)) import qualified Data.ByteString.Lazy as B @@ -149,7 +149,7 @@ externalFilter f args' d = do show f' ++ " not found in path." (exitcode, outbs, errbs) <- E.handle filterException $ pipeProcess Nothing f' args'' $ encode d - when (not $ B.null errbs) $ B.hPutStr stderr errbs + unless (B.null errbs) $ B.hPutStr stderr errbs case exitcode of ExitSuccess -> return $ either error id $ eitherDecode' outbs ExitFailure ec -> err 83 $ "Error running filter " ++ f ++ "\n" ++ @@ -196,7 +196,8 @@ data Opt = Opt , optIgnoreArgs :: Bool -- ^ Ignore command-line arguments , optVerbose :: Bool -- ^ Verbose diagnostic output , optReferenceLinks :: Bool -- ^ Use reference links in writing markdown, rst - , optWrapText :: Bool -- ^ Wrap text + , optDpi :: Int -- ^ Dpi + , optWrapText :: WrapOption -- ^ Options for wrapping text , optColumns :: Int -- ^ Line length in characters , optFilters :: [FilePath] -- ^ Filters to apply , optEmailObfuscation :: ObfuscationMethod @@ -258,7 +259,8 @@ defaultOpts = Opt , optIgnoreArgs = False , optVerbose = False , optReferenceLinks = False - , optWrapText = True + , optDpi = 96 + , optWrapText = WrapAuto , optColumns = 72 , optFilters = [] , optEmailObfuscation = JavascriptObfuscation @@ -309,14 +311,6 @@ options = "DIRECTORY") -- "Directory containing pandoc data files." "" - , Option "" ["strict"] - (NoArg - (\opt -> do - err 59 $ "The --strict option has been removed.\n" ++ - "Use `markdown_strict' input or output format instead." - return opt )) - "" -- "Disable markdown syntax extensions" - , Option "R" ["parse-raw"] (NoArg (\opt -> return opt { optParseRaw = True })) @@ -396,7 +390,7 @@ options = , Option "" ["extract-media"] (ReqArg - (\arg opt -> do + (\arg opt -> return opt { optExtractMedia = Just arg }) "PATH") "" -- "Directory to which to extract embedded media" @@ -408,7 +402,7 @@ options = , Option "" ["template"] (ReqArg - (\arg opt -> do + (\arg opt -> return opt{ optTemplate = Just arg, optStandalone = True }) "FILENAME") @@ -442,7 +436,7 @@ options = case templ of Right t -> UTF8.hPutStr stdout t Left e -> error $ show e - exitWith ExitSuccess) + exitSuccess) "FORMAT") "" -- "Print default template for FORMAT" @@ -450,21 +444,42 @@ options = (ReqArg (\arg _ -> do readDataFile Nothing arg >>= BS.hPutStr stdout - exitWith ExitSuccess) + exitSuccess) "FILE") "" -- "Print default data file" + , Option "" ["dpi"] + (ReqArg + (\arg opt -> + case safeRead arg of + Just t | t > 0 -> return opt { optDpi = t } + _ -> err 31 + "dpi must be a number greater than 0") + "NUMBER") + "" -- "Dpi (default 96)" + , Option "" ["no-wrap"] (NoArg - (\opt -> return opt { optWrapText = False })) - "" -- "Do not wrap text in output" + (\opt -> do warn $ "--no-wrap is deprecated. " ++ + "Use --wrap=none or --wrap=preserve instead." + return opt { optWrapText = WrapNone })) + "" + + , Option "" ["wrap"] + (ReqArg + (\arg opt -> + case safeRead ("Wrap" ++ uppercaseFirstLetter arg) of + Just o -> return opt { optWrapText = o } + Nothing -> err 77 "--wrap must be auto, none, or preserve") + "[auto|none|preserve]") + "" -- "Option for wrapping text in output" , Option "" ["columns"] (ReqArg (\arg opt -> case safeRead arg of Just t | t > 0 -> return opt { optColumns = t } - _ -> err 33 $ + _ -> err 33 "columns must be a number greater than 0") "NUMBER") "" -- "Length of line in characters" @@ -476,11 +491,11 @@ options = , Option "" ["toc-depth"] (ReqArg - (\arg opt -> do + (\arg opt -> case safeRead arg of Just t | t >= 1 && t <= 6 -> return opt { optTOCDepth = t } - _ -> err 57 $ + _ -> err 57 "TOC level must be a number between 1 and 6") "NUMBER") "" -- "Number of levels to include in TOC" @@ -546,25 +561,9 @@ options = optStandalone = True })) "" -- "Make slide shows include all the needed js and css" - , Option "" ["offline"] - (NoArg - (\opt -> do warn $ "--offline is deprecated. Use --self-contained instead." - return opt { optSelfContained = True, - optStandalone = True })) - "" -- "Make slide shows include all the needed js and css" - -- deprecated synonym for --self-contained - - , Option "5" ["html5"] - (NoArg - (\opt -> do - warn $ "--html5 is deprecated. " - ++ "Use the html5 output format instead." - return opt { optHtml5 = True })) - "" -- "Produce HTML5 in HTML output" - , Option "" ["html-q-tags"] (NoArg - (\opt -> do + (\opt -> return opt { optHtmlQTags = True })) "" -- "Use <q> tags for quotes in HTML" @@ -620,11 +619,11 @@ options = , Option "" ["slide-level"] (ReqArg - (\arg opt -> do + (\arg opt -> case safeRead arg of Just t | t >= 1 && t <= 6 -> return opt { optSlideLevel = Just t } - _ -> err 39 $ + _ -> err 39 "slide level must be a number between 1 and 6") "NUMBER") "" -- "Force header level for slides" @@ -680,14 +679,14 @@ options = , Option "" ["reference-odt"] (ReqArg - (\arg opt -> do + (\arg opt -> return opt { optReferenceODT = Just arg }) "FILENAME") "" -- "Path of custom reference.odt" , Option "" ["reference-docx"] (ReqArg - (\arg opt -> do + (\arg opt -> return opt { optReferenceDocx = Just arg }) "FILENAME") "" -- "Path of custom reference.docx" @@ -718,18 +717,18 @@ options = , Option "" ["epub-embed-font"] (ReqArg - (\arg opt -> do + (\arg opt -> return opt{ optEpubFonts = arg : optEpubFonts opt }) "FILE") "" -- "Directory of fonts to embed" , Option "" ["epub-chapter-level"] (ReqArg - (\arg opt -> do + (\arg opt -> case safeRead arg of Just t | t >= 1 && t <= 6 -> return opt { optEpubChapterLevel = t } - _ -> err 59 $ + _ -> err 59 "chapter level must be a number between 1 and 6") "NUMBER") "" -- "Header level at which to split chapters in EPUB" @@ -817,9 +816,7 @@ options = , Option "" ["webtex"] (OptArg (\arg opt -> do - let url' = case arg of - Just u -> u - Nothing -> "http://chart.apis.google.com/chart?cht=tx&chl=" + let url' = fromMaybe "http://chart.apis.google.com/chart?cht=tx&chl=" arg return opt { optHTMLMathMethod = WebTeX url' }) "URL") "" -- "Use web service for HTML math" @@ -833,9 +830,7 @@ options = , Option "" ["mathjax"] (OptArg (\arg opt -> do - let url' = case arg of - Just u -> u - Nothing -> "https://cdn.mathjax.org/mathjax/latest/MathJax.js?config=TeX-AMS-MML_HTMLorMML" + let url' = fromMaybe "https://cdn.mathjax.org/mathjax/latest/MathJax.js?config=TeX-AMS-MML_HTMLorMML" arg return opt { optHTMLMathMethod = MathJax url'}) "URL") "" -- "Use MathJax for HTML math" @@ -893,7 +888,7 @@ options = (unwords (map fst readers)) (unwords ("pdf": map fst writers)) ddir - exitWith ExitSuccess )) + exitSuccess )) "" -- "Print bash completion script" , Option "v" ["version"] @@ -904,7 +899,7 @@ options = UTF8.hPutStrLn stdout (prg ++ " " ++ pandocVersion ++ compileInfo ++ "\nDefault user data directory: " ++ defaultDatadir ++ copyrightMessage) - exitWith ExitSuccess )) + exitSuccess )) "" -- "Print version" , Option "h" ["help"] @@ -912,7 +907,7 @@ options = (\_ -> do prg <- getProgName UTF8.hPutStr stdout (usageMessage prg options) - exitWith ExitSuccess )) + exitSuccess )) "" -- "Show help" ] @@ -936,10 +931,10 @@ readMetaValue s = case decode (UTF8.fromString s) of usageMessage :: String -> [OptDescr (Opt -> IO Opt)] -> String usageMessage programName = usageInfo (programName ++ " [OPTIONS] [FILES]" ++ "\nInput formats: " ++ - (wrapWords 16 78 $ readers'names) ++ + wrapWords 16 78 readers'names ++ '\n' : replicate 16 ' ' ++ "[ *only Pandoc's JSON version of native AST]" ++ "\nOutput formats: " ++ - (wrapWords 16 78 $ writers'names) ++ + wrapWords 16 78 writers'names ++ '\n' : replicate 16 ' ' ++ "[**for pdf output, use latex or beamer and -o FILENAME.pdf]\nOptions:") where @@ -1010,6 +1005,7 @@ defaultWriterName x = ".epub" -> "epub" ".org" -> "org" ".asciidoc" -> "asciidoc" + ".adoc" -> "asciidoc" ".pdf" -> "latex" ".fb2" -> "fb2" ".opml" -> "opml" @@ -1028,8 +1024,8 @@ extractMedia media dir d = return $ walk (adjustImagePath dir fps) d adjustImagePath :: FilePath -> [FilePath] -> Inline -> Inline -adjustImagePath dir paths (Image lab (src, tit)) - | src `elem` paths = Image lab (dir ++ "/" ++ src, tit) +adjustImagePath dir paths (Image attr lab (src, tit)) + | src `elem` paths = Image attr lab (dir ++ "/" ++ src, tit) adjustImagePath _ _ x = x adjustMetadata :: M.Map String MetaValue -> Pandoc -> IO Pandoc @@ -1042,31 +1038,28 @@ applyFilters :: [FilePath] -> [String] -> Pandoc -> IO Pandoc applyFilters filters args d = foldrM ($) d $ map (flip externalFilter args) filters +uppercaseFirstLetter :: String -> String +uppercaseFirstLetter (c:cs) = toUpper c : cs +uppercaseFirstLetter [] = [] + main :: IO () main = do rawArgs <- map UTF8.decodeArg <$> getArgs prg <- getProgName - let compatMode = (prg == "hsmarkdown") - let (actions, args, errors) = if compatMode - then ([], rawArgs, []) - else getOpt Permute options rawArgs + let (actions, args, errors) = getOpt Permute options rawArgs unless (null errors) $ err 2 $ concat $ errors ++ ["Try " ++ prg ++ " --help for more information."] - let defaultOpts' = if compatMode - then defaultOpts { optReader = "markdown_strict" - , optWriter = "html" - , optEmailObfuscation = - ReferenceObfuscation } - else defaultOpts - -- thread option data structure through all supplied option actions - opts <- foldl (>>=) (return defaultOpts') actions + opts <- foldl (>>=) (return defaultOpts) actions + convertWithOpts opts args +convertWithOpts :: Opt -> [FilePath] -> IO () +convertWithOpts opts args = do let Opt { optTabStop = tabStop , optPreserveTabs = preserveTabs , optStandalone = standalone @@ -1103,6 +1096,7 @@ main = do , optIgnoreArgs = ignoreArgs , optVerbose = verbose , optReferenceLinks = referenceLinks + , optDpi = dpi , optWrapText = wrap , optColumns = columns , optFilters = filters @@ -1128,8 +1122,8 @@ main = do when dumpArgs $ do UTF8.hPutStrLn stdout outputFile - mapM_ (\arg -> UTF8.hPutStrLn stdout arg) args - exitWith ExitSuccess + mapM_ (UTF8.hPutStrLn stdout) args + exitSuccess let csscdn = "https://cdnjs.cloudflare.com/ajax/libs/KaTeX/0.5.1/katex.min.css" let mathMethod = @@ -1139,7 +1133,7 @@ main = do -- --bibliography implies -F pandoc-citeproc for backwards compatibility: - let needsCiteproc = any ("--bibliography" `isPrefixOf`) rawArgs && + let needsCiteproc = isJust (M.lookup "bibliography" (optMetadata opts)) && optCiteMethod opts `notElem` [Natbib, Biblatex] && "pandoc-citeproc" `notElem` map takeBaseName filters let filters' = if needsCiteproc then "pandoc-citeproc" : filters @@ -1173,6 +1167,10 @@ main = do let laTeXOutput = "latex" `isPrefixOf` writerName' || "beamer" `isPrefixOf` writerName' + let conTeXtOutput = "context" `isPrefixOf` writerName' + + let laTeXInput = "latex" `isPrefixOf` readerName' || + "beamer" `isPrefixOf` readerName' writer <- if ".lua" `isSuffixOf` writerName' -- note: use non-lowercased version writerName @@ -1191,7 +1189,7 @@ main = do reader <- if "t2t" == readerName' then (mkStringReader . readTxt2Tags) <$> - (getT2TMeta sources outputFile) + getT2TMeta sources outputFile else case getReader readerName' of Right r -> return r Left e -> err 7 e' @@ -1255,8 +1253,10 @@ main = do uriFragment = "" } _ -> Nothing - let readerOpts = def{ readerSmart = smart || (texLigatures && - (laTeXOutput || "context" `isPrefixOf` writerName')) + let readerOpts = def{ readerSmart = if laTeXInput + then texLigatures + else smart || (texLigatures && + (laTeXOutput || conTeXtOutput)) , readerStandalone = standalone' , readerParseRaw = parseRaw , readerColumns = columns @@ -1288,7 +1288,7 @@ main = do let readFiles [] = error "Cannot read archive from stdin" readFiles [x] = B.readFile x - readFiles (x:xs) = mapM (warn . ("Ignoring: " ++)) xs >> B.readFile x + readFiles (x:xs) = mapM_ (warn . ("Ignoring: " ++)) xs >> B.readFile x let convertTabs = tabFilter (if preserveTabs || readerName' == "t2t" then 0 @@ -1320,6 +1320,7 @@ main = do writerNumberOffset = numberFrom, writerSectionDivs = sectionDivs, writerReferenceLinks = referenceLinks, + writerDpi = dpi, writerWrapText = wrap, writerColumns = columns, writerEmailObfuscation = obfuscationMethod, @@ -1367,21 +1368,24 @@ main = do PureStringWriter f | pdfOutput -> do -- make sure writer is latex or beamer - unless laTeXOutput $ + unless (laTeXOutput || conTeXtOutput) $ err 47 $ "cannot produce pdf output with " ++ writerName' ++ " writer" + let texprog = if conTeXtOutput + then "context" + else latexEngine -- check for latex program - mbLatex <- findExecutable latexEngine - when (mbLatex == Nothing) $ - err 41 $ latexEngine ++ " not found. " ++ - latexEngine ++ " is needed for pdf output." + mbLatex <- findExecutable texprog + when (isNothing mbLatex) $ + err 41 $ texprog ++ " not found. " ++ + texprog ++ " is needed for pdf output." - res <- makePDF latexEngine f writerOptions doc' + res <- makePDF texprog f writerOptions doc' case res of Right pdf -> writeBinary pdf Left err' -> do - B.hPutStr stderr $ err' + B.hPutStr stderr err' B.hPut stderr $ B.pack [10] err 43 "Error producing PDF from TeX source" | otherwise -> selfcontain (f writerOptions doc' ++ |