{-# LANGUAGE CPP, TupleSections, ScopedTypeVariables, PatternGuards #-} {- Copyright (C) 2006-2016 John MacFarlane This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} {- | Module : Main Copyright : Copyright (C) 2006-2016 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane Stability : alpha Portability : portable Parses command-line options and calls the appropriate readers and writers. -} module Main where import Text.Pandoc import Text.Pandoc.Builder (setMeta) import Text.Pandoc.PDF (makePDF) import Text.Pandoc.Walk (walk) import Text.Pandoc.Shared ( tabFilter, readDataFileUTF8, readDataFile, safeRead, headerShift, err, openURL ) import Text.Pandoc.MediaBag ( mediaDirectory, extractMediaBag, MediaBag ) import Text.Pandoc.XML ( toEntities ) import Text.Pandoc.SelfContained ( makeSelfContained ) import Text.Pandoc.Process (pipeProcess) import Skylighting ( defaultSyntaxMap, Syntax(..), Style, tango, pygments, espresso, zenburn, kate, haddock, breezeDark, monochrome ) import System.Environment ( getArgs, getProgName, getEnvironment ) import System.Exit ( ExitCode (..), exitSuccess ) import System.FilePath import System.Console.GetOpt import Data.Char ( toLower, toUpper ) import Data.List ( intercalate, isPrefixOf, isSuffixOf, sort ) import System.Directory ( getAppUserDataDirectory, findExecutable, doesFileExist, Permissions(..), getPermissions ) import System.IO ( stdout, stderr ) import System.IO.Error ( isDoesNotExistError ) 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, isJust) import Data.Foldable (foldrM) import Network.URI (parseURI, isURI, URI(..)) import qualified Data.ByteString.Lazy as B import qualified Data.ByteString as BS import Data.Aeson (eitherDecode', encode) import qualified Data.Map as M import Data.Yaml (decode) import qualified Data.Yaml as Yaml import qualified Data.Text as T import Control.Applicative ((<|>)) import Paths_pandoc (getDataDir) import Text.Printf (printf) #ifndef _WINDOWS import System.Posix.Terminal (queryTerminal) import System.Posix.IO (stdOutput) #endif import Control.Monad.Trans import Text.Pandoc.Class (withMediaBag, PandocIO, getLog, setVerbosity) main :: IO () main = do rawArgs <- map UTF8.decodeArg <$> getArgs prg <- getProgName let (actions, args, unrecognizedOpts, errors) = getOpt' Permute options rawArgs let unknownOptionErrors = foldr addDeprecationNote [] unrecognizedOpts unless (null errors && null unknownOptionErrors) $ err 2 $ concat errors ++ unlines unknownOptionErrors ++ ("Try " ++ prg ++ " --help for more information.") -- thread option data structure through all supplied option actions opts <- foldl (>>=) (return defaultOpts) actions convertWithOpts opts args addDeprecationNote :: String -> [String] -> [String] addDeprecationNote "--smart" = (("--smart has been removed. Use +smart or -smart extension instead.\n" ++ "For example: pandoc -f markdown+smart -t markdown-smart.") :) addDeprecationNote "-S" = addDeprecationNote "--smart" addDeprecationNote "--old-dashes" = ("--old-dashes has been removed. Use +old_dashes extension instead." :) addDeprecationNote "--no-wrap" = ("--no-wrap has been removed. Use --wrap=none instead." :) addDeprecationNote "--chapters" = ("--chapters has been removed. Use --top-level-division=chapter instead." :) addDeprecationNote "--reference-docx" = ("--reference-docx has been removed. Use --reference-doc instead." :) addDeprecationNote "--reference-odt" = ("--reference-odt has been removed. Use --reference-doc instead." :) addDeprecationNote x = (("Unknown option " ++ x ++ ".") :) convertWithOpts :: Opt -> [FilePath] -> IO () convertWithOpts opts args = do let Opt { optTabStop = tabStop , optPreserveTabs = preserveTabs , optStandalone = standalone , optReader = readerName , optWriter = writerName , optParseRaw = parseRaw , optVariables = variables , optMetadata = metadata , optTableOfContents = toc , optBaseHeaderLevel = baseHeaderLevel , optTemplate = templatePath , optOutputFile = outputFile , optNumberSections = numberSections , optNumberOffset = numberFrom , optSectionDivs = sectionDivs , optIncremental = incremental , optSelfContained = selfContained , optHtmlQTags = htmlQTags , optHighlightStyle = highlightStyle , optTopLevelDivision = topLevelDivision , optHTMLMathMethod = mathMethod' , optReferenceDoc = referenceDoc , optEpubStylesheet = epubStylesheet , optEpubMetadata = epubMetadata , optEpubFonts = epubFonts , optEpubChapterLevel = epubChapterLevel , optTOCDepth = epubTOCDepth , optDumpArgs = dumpArgs , optIgnoreArgs = ignoreArgs , optVerbosity = verbosity , optFailIfWarnings = failIfWarnings , optReferenceLinks = referenceLinks , optReferenceLocation = referenceLocation , optDpi = dpi , optWrapText = wrap , optColumns = columns , optFilters = filters , optEmailObfuscation = obfuscationMethod , optIdentifierPrefix = idPrefix , optIndentedCodeClasses = codeBlockClasses , optDataDir = mbDataDir , optCiteMethod = citeMethod , optListings = listings , optLaTeXEngine = latexEngine , optLaTeXEngineArgs = latexEngineArgs , optSlideLevel = slideLevel , optSetextHeaders = setextHeaders , optAscii = ascii , optDefaultImageExtension = defaultImageExtension , optExtractMedia = mbExtractMedia , optTrackChanges = trackChanges , optFileScope = fileScope , optKaTeXStylesheet = katexStylesheet , optKaTeXJS = katexJS } = opts when dumpArgs $ do UTF8.hPutStrLn stdout outputFile mapM_ (UTF8.hPutStrLn stdout) args exitSuccess let csscdn = "https://cdnjs.cloudflare.com/ajax/libs/KaTeX/0.6.0/katex.min.css" let mathMethod = case (katexJS, katexStylesheet) of (Nothing, _) -> mathMethod' (Just js, ss) -> KaTeX js (fromMaybe csscdn ss) -- --bibliography implies -F pandoc-citeproc for backwards compatibility: 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 else filters let sources = case args of [] -> ["-"] xs | ignoreArgs -> ["-"] | otherwise -> xs datadir <- case mbDataDir of Nothing -> E.catch (Just <$> getAppUserDataDirectory "pandoc") (\e -> let _ = (e :: E.SomeException) in return Nothing) Just _ -> return mbDataDir -- assign reader and writer based on options and filenames let readerName' = case map toLower readerName of [] -> defaultReaderName (if any isURI sources then "html" else "markdown") sources x -> x let writerName' = case map toLower writerName of [] -> defaultWriterName outputFile "epub2" -> "epub" x -> x let format = takeWhile (`notElem` ['+','-']) $ takeFileName writerName' -- in case path to lua script let pdfOutput = map toLower (takeExtension outputFile) == ".pdf" let laTeXOutput = format `elem` ["latex", "beamer"] let conTeXtOutput = format == "context" let html5Output = format == "html5" || format == "html" -- disabling the custom writer for now writer <- if ".lua" `isSuffixOf` format -- note: use non-lowercased version writerName then error "custom writers disabled for now" else case getWriter writerName' of Left e -> err 9 $ if format == "pdf" then e ++ "\nTo create a pdf with pandoc, use " ++ "the latex or beamer writer and specify\n" ++ "an output file with .pdf extension " ++ "(pandoc -t latex -o filename.pdf)." else e Right w -> return (w :: Writer PandocIO) -- TODO: we have to get the input and the output into the state for -- the sake of the text2tags reader. reader <- case getReader readerName' of Right r -> return (r :: Reader PandocIO) Left e -> err 7 e' where e' = case readerName' of "pdf" -> e ++ "\nPandoc can convert to PDF, but not from PDF." "doc" -> e ++ "\nPandoc can convert from DOCX, but not from DOC.\nTry using Word to save your DOC file as DOCX, and convert that with pandoc." _ -> e let standalone' = standalone || not (isTextFormat format) || pdfOutput templ <- case templatePath of _ | not standalone' -> return Nothing Nothing -> do deftemp <- getDefaultTemplate datadir format case deftemp of Left e -> throwIO e Right t -> return (Just t) Just tp -> do -- strip off extensions let tp' = case takeExtension tp of "" -> tp <.> format _ -> tp Just <$> E.catch (UTF8.readFile tp') (\e -> if isDoesNotExistError e then E.catch (readDataFileUTF8 datadir ("templates" tp')) (\e' -> let _ = (e' :: E.SomeException) in throwIO e') else throwIO e) variables' <- case mathMethod of LaTeXMathML Nothing -> do s <- readDataFileUTF8 datadir "LaTeXMathML.js" return $ ("mathml-script", s) : variables _ -> return variables variables'' <- if format == "dzslides" then do dztempl <- readDataFileUTF8 datadir ("dzslides" "template.html") let dzline = "