diff options
author | John MacFarlane <jgm@berkeley.edu> | 2017-01-22 12:19:46 +0100 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2017-01-25 17:07:43 +0100 |
commit | 8280d6a48958ef305e3dd29e2bb189fb1ea96b14 (patch) | |
tree | 07c88af7b2c814239f5be5c31ea8ac850e8ea70d /src/Text | |
parent | d1efc839f129d23fe8a6523e33a01b0b463ee409 (diff) | |
download | pandoc-8280d6a48958ef305e3dd29e2bb189fb1ea96b14.tar.gz |
Changes to verbosity in writer and reader options.
API changes: Text.Pandoc.Options:
* Added Verbosity.
* Added writerVerbosity.
* Added readerVerbosity.
* Removed writerVerbose.
* Removed readerTrace.
pandoc CLI: The `--trace` option sets verbosity to DEBUG;
the `--quiet` option sets it to ERROR, and the `--verbose`
option sets it to INFO. The default is WARNING.
Diffstat (limited to 'src/Text')
-rw-r--r-- | src/Text/Pandoc/Options.hs | 13 | ||||
-rw-r--r-- | src/Text/Pandoc/PDF.hs | 43 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/EPUB.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/HTML.hs | 6 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Haddock.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Markdown.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/MediaWiki.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/TWiki.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Textile.hs | 2 |
9 files changed, 41 insertions, 35 deletions
diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs index e7dec6492..262a0392d 100644 --- a/src/Text/Pandoc/Options.hs +++ b/src/Text/Pandoc/Options.hs @@ -37,6 +37,7 @@ module Text.Pandoc.Options ( module Text.Pandoc.Extensions , HTMLSlideVariant (..) , EPUBVersion (..) , WrapOption (..) + , Verbosity (..) , TopLevelDivision (..) , WriterOptions (..) , TrackChanges (..) @@ -61,7 +62,7 @@ data ReaderOptions = ReaderOptions{ , readerIndentedCodeClasses :: [String] -- ^ Default classes for -- indented code blocks , readerDefaultImageExtension :: String -- ^ Default extension for images - , readerTrace :: Bool -- ^ Print debugging info + , readerVerbosity :: Verbosity -- ^ Verbosity level , readerTrackChanges :: TrackChanges } deriving (Show, Read, Data, Typeable, Generic) @@ -75,7 +76,7 @@ instance Default ReaderOptions , readerApplyMacros = True , readerIndentedCodeClasses = [] , readerDefaultImageExtension = "" - , readerTrace = False + , readerVerbosity = ERROR , readerTrackChanges = AcceptChanges } @@ -141,6 +142,10 @@ data ReferenceLocation = EndOfBlock -- ^ End of block | EndOfDocument -- ^ at end of document deriving (Show, Read, Eq, Data, Typeable, Generic) +-- | Verbosity level. +data Verbosity = ERROR | WARNING | INFO | DEBUG + deriving (Show, Read, Eq, Data, Enum, Ord, Bounded, Typeable, Generic) + -- | Options for writers data WriterOptions = WriterOptions { writerTemplate :: Maybe String -- ^ Template to use @@ -181,7 +186,7 @@ data WriterOptions = WriterOptions , writerEpubChapterLevel :: Int -- ^ Header level for chapters (separate files) , writerTOCDepth :: Int -- ^ Number of levels to include in TOC , writerReferenceDoc :: Maybe FilePath -- ^ Path to reference document if specified - , writerVerbose :: Bool -- ^ Verbose debugging output + , writerVerbosity :: Verbosity -- ^ Verbose debugging output , writerLaTeXArgs :: [String] -- ^ Flags to pass to latex-engine , writerReferenceLocation :: ReferenceLocation -- ^ Location of footnotes and references for writing markdown } deriving (Show, Data, Typeable, Generic) @@ -223,7 +228,7 @@ instance Default WriterOptions where , writerEpubChapterLevel = 1 , writerTOCDepth = 3 , writerReferenceDoc = Nothing - , writerVerbose = False + , writerVerbosity = WARNING , writerLaTeXArgs = [] , writerReferenceLocation = EndOfDocument } diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs index be889c052..cc523febf 100644 --- a/src/Text/Pandoc/PDF.hs +++ b/src/Text/Pandoc/PDF.hs @@ -52,7 +52,8 @@ import Text.Pandoc.MediaBag import Text.Pandoc.Walk (walkM) import Text.Pandoc.Shared (warn, withTempDir, inDirectory, stringify) import Text.Pandoc.Writers.Shared (getField, metaToJSON) -import Text.Pandoc.Options (WriterOptions(..), HTMLMathMethod(..)) +import Text.Pandoc.Options (WriterOptions(..), HTMLMathMethod(..), + Verbosity(..)) import Text.Pandoc.MIME (extensionFromMimeType, getMimeType) import Text.Pandoc.Process (pipeProcess) import Control.Monad.Trans (MonadIO(..)) @@ -98,16 +99,16 @@ makePDF "wkhtmltopdf" writer opts _mediabag doc@(Pandoc meta _) = liftIO $ do (getField "margin-left" meta')) ] source <- runIOorExplode $ writer opts doc - html2pdf (writerVerbose opts) args source + html2pdf (writerVerbosity opts) args source makePDF program writer opts mediabag doc = liftIO $ withTempDir "tex2pdf." $ \tmpdir -> do doc' <- handleImages opts mediabag tmpdir doc source <- runIOorExplode $ writer opts doc' let args = writerLaTeXArgs opts case takeBaseName program of - "context" -> context2pdf (writerVerbose opts) tmpdir source + "context" -> context2pdf (writerVerbosity opts) tmpdir source prog | prog `elem` ["pdflatex", "lualatex", "xelatex"] - -> tex2pdf' (writerVerbose opts) args tmpdir program source + -> tex2pdf' (writerVerbosity opts) args tmpdir program source _ -> return $ Left $ UTF8.fromStringLazy $ "Unknown program " ++ program handleImages :: WriterOptions @@ -174,17 +175,17 @@ convertImage tmpdir fname = mime = getMimeType fname doNothing = return (Right fname) -tex2pdf' :: Bool -- ^ Verbose output +tex2pdf' :: Verbosity -- ^ Verbosity level -> [String] -- ^ Arguments to the latex-engine -> FilePath -- ^ temp directory for output -> String -- ^ tex program -> String -- ^ tex source -> IO (Either ByteString ByteString) -tex2pdf' verbose args tmpDir program source = do +tex2pdf' verbosity args tmpDir program source = do let numruns = if "\\tableofcontents" `isInfixOf` source then 3 -- to get page numbers else 2 -- 1 run won't give you PDF bookmarks - (exit, log', mbPdf) <- runTeXProgram verbose program args 1 numruns tmpDir source + (exit, log', mbPdf) <- runTeXProgram verbosity program args 1 numruns tmpDir source case (exit, mbPdf) of (ExitFailure _, _) -> do let logmsg = extractMsg log' @@ -222,9 +223,9 @@ extractConTeXtMsg log' = do -- Run a TeX program on an input bytestring and return (exit code, -- contents of stdout, contents of produced PDF if any). Rerun -- a fixed number of times to resolve references. -runTeXProgram :: Bool -> String -> [String] -> Int -> Int -> FilePath -> String - -> IO (ExitCode, ByteString, Maybe ByteString) -runTeXProgram verbose program args runNumber numRuns tmpDir source = do +runTeXProgram :: Verbosity -> String -> [String] -> Int -> Int -> FilePath + -> String -> IO (ExitCode, ByteString, Maybe ByteString) +runTeXProgram verbosity program args runNumber numRuns tmpDir source = do let file = tmpDir </> "input.tex" exists <- doesFileExist file unless exists $ UTF8.writeFile file source @@ -244,7 +245,7 @@ runTeXProgram verbose program args runNumber numRuns tmpDir source = do $ lookup "TEXINPUTS" env' let env'' = ("TEXINPUTS", texinputs) : [(k,v) | (k,v) <- env', k /= "TEXINPUTS"] - when (verbose && runNumber == 1) $ do + when (verbosity >= INFO && runNumber == 1) $ do putStrLn "[makePDF] temp dir:" putStrLn tmpDir' putStrLn "[makePDF] Command line:" @@ -257,12 +258,12 @@ runTeXProgram verbose program args runNumber numRuns tmpDir source = do B.readFile file' >>= B.putStr putStr "\n" (exit, out) <- pipeProcess (Just env'') program programArgs BL.empty - when verbose $ do + when (verbosity >= INFO) $ do putStrLn $ "[makePDF] Run #" ++ show runNumber B.hPutStr stdout out putStr "\n" if runNumber <= numRuns - then runTeXProgram verbose program args (runNumber + 1) numRuns tmpDir source + then runTeXProgram verbosity program args (runNumber + 1) numRuns tmpDir source else do let pdfFile = replaceDirectory (replaceExtension file ".pdf") tmpDir pdfExists <- doesFileExist pdfFile @@ -274,17 +275,17 @@ runTeXProgram verbose program args runNumber numRuns tmpDir source = do else return Nothing return (exit, out, pdf) -html2pdf :: Bool -- ^ Verbose output +html2pdf :: Verbosity -- ^ Verbosity level -> [String] -- ^ Args to wkhtmltopdf -> String -- ^ HTML5 source -> IO (Either ByteString ByteString) -html2pdf verbose args source = do +html2pdf verbosity args source = do file <- withTempFile "." "html2pdf.html" $ \fp _ -> return fp pdfFile <- withTempFile "." "html2pdf.pdf" $ \fp _ -> return fp UTF8.writeFile file source let programArgs = args ++ [file, pdfFile] env' <- getEnvironment - when verbose $ do + when (verbosity >= INFO) $ do putStrLn "[makePDF] Command line:" putStrLn $ "wkhtmltopdf" ++ " " ++ unwords (map show programArgs) putStr "\n" @@ -296,7 +297,7 @@ html2pdf verbose args source = do putStr "\n" (exit, out) <- pipeProcess (Just env') "wkhtmltopdf" programArgs BL.empty removeFile file - when verbose $ do + when (verbosity >= INFO) $ do B.hPutStr stdout out putStr "\n" pdfExists <- doesFileExist pdfFile @@ -314,11 +315,11 @@ html2pdf verbose args source = do (ExitSuccess, Nothing) -> Left "" (ExitSuccess, Just pdf) -> Right pdf -context2pdf :: Bool -- ^ Verbose output +context2pdf :: Verbosity -- ^ Verbosity level -> FilePath -- ^ temp directory for output -> String -- ^ ConTeXt source -> IO (Either ByteString ByteString) -context2pdf verbose tmpDir source = inDirectory tmpDir $ do +context2pdf verbosity tmpDir source = inDirectory tmpDir $ do let file = "input.tex" UTF8.writeFile file source #ifdef _WINDOWS @@ -334,7 +335,7 @@ context2pdf verbose tmpDir source = inDirectory tmpDir $ do $ lookup "TEXINPUTS" env' let env'' = ("TEXINPUTS", texinputs) : [(k,v) | (k,v) <- env', k /= "TEXINPUTS"] - when verbose $ do + when (verbosity >= INFO) $ do putStrLn "[makePDF] temp dir:" putStrLn tmpDir' putStrLn "[makePDF] Command line:" @@ -347,7 +348,7 @@ context2pdf verbose tmpDir source = inDirectory tmpDir $ do B.readFile file >>= B.putStr putStr "\n" (exit, out) <- pipeProcess (Just env'') "context" programArgs BL.empty - when verbose $ do + when (verbosity >= INFO) $ do B.hPutStr stdout out putStr "\n" let pdfFile = replaceExtension file ".pdf" diff --git a/src/Text/Pandoc/Readers/EPUB.hs b/src/Text/Pandoc/Readers/EPUB.hs index a76ed04ba..71a527f13 100644 --- a/src/Text/Pandoc/Readers/EPUB.hs +++ b/src/Text/Pandoc/Readers/EPUB.hs @@ -12,7 +12,7 @@ import Text.XML.Light import Text.Pandoc.Definition hiding (Attr) import Text.Pandoc.Readers.HTML (readHtml) import Text.Pandoc.Walk (walk, query) -import Text.Pandoc.Options ( ReaderOptions(..), readerTrace) +import Text.Pandoc.Options ( ReaderOptions(..), readerVerbosity, Verbosity(..)) import Text.Pandoc.Shared (escapeURI, collapseFilePath, addMetaField) import Network.URI (unEscapeString) import Text.Pandoc.MediaBag (MediaBag, insertMedia) @@ -71,7 +71,7 @@ archiveToEPUB os archive = do os' = os {readerParseRaw = True} parseSpineElem :: PandocMonad m => FilePath -> (FilePath, MimeType) -> m Pandoc parseSpineElem (normalise -> r) (normalise -> path, mime) = do - when (readerTrace os) (traceM path) + when (readerVerbosity os == DEBUG) (traceM path) doc <- mimeToReader mime r path let docSpan = B.doc $ B.para $ B.spanWith (takeFileName path, [], []) mempty return $ docSpan <> doc diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs index b66a712e0..d602f7303 100644 --- a/src/Text/Pandoc/Readers/HTML.hs +++ b/src/Text/Pandoc/Readers/HTML.hs @@ -45,8 +45,8 @@ import qualified Text.Pandoc.Builder as B import Text.Pandoc.Builder (Blocks, Inlines, trimInlines, HasMeta(..)) import Text.Pandoc.Shared ( extractSpaces, renderTags', addMetaField , escapeURI, safeRead ) -import Text.Pandoc.Options (ReaderOptions(readerParseRaw, readerTrace) - , Extension (Ext_epub_html_exts, +import Text.Pandoc.Options (ReaderOptions(readerParseRaw, readerVerbosity), + Verbosity(..), Extension (Ext_epub_html_exts, Ext_native_divs, Ext_native_spans)) import Text.Pandoc.Parsing hiding ((<|>)) import Text.Pandoc.Walk @@ -160,7 +160,7 @@ pHead = pInTags "head" $ pTitle <|> pMetaTag <|> pBaseTag <|> (mempty <$ pAnyTag block :: PandocMonad m => TagParser m Blocks block = do - tr <- getOption readerTrace + tr <- (== DEBUG) <$> getOption readerVerbosity pos <- getPosition res <- choice [ eSection diff --git a/src/Text/Pandoc/Readers/Haddock.hs b/src/Text/Pandoc/Readers/Haddock.hs index 987342bf7..575d99c77 100644 --- a/src/Text/Pandoc/Readers/Haddock.hs +++ b/src/Text/Pandoc/Readers/Haddock.hs @@ -48,7 +48,7 @@ readHaddockEither opts = #else Right . B.doc . docHToBlocks . trace' . parseParas #endif - where trace' x = if readerTrace opts + where trace' x = if readerVerbosity opts == DEBUG then trace (show x) x else x diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 9137ae4b6..e0036f708 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -490,7 +490,7 @@ parseBlocks = mconcat <$> manyTill block eof block :: PandocMonad m => MarkdownParser m (F Blocks) block = do - tr <- getOption readerTrace + tr <- (== DEBUG) <$> getOption readerVerbosity pos <- getPosition res <- choice [ mempty <$ blanklines , codeBlockFenced diff --git a/src/Text/Pandoc/Readers/MediaWiki.hs b/src/Text/Pandoc/Readers/MediaWiki.hs index 5bdf0ca4e..38a9e3f4f 100644 --- a/src/Text/Pandoc/Readers/MediaWiki.hs +++ b/src/Text/Pandoc/Readers/MediaWiki.hs @@ -194,7 +194,7 @@ parseMediaWiki = do block :: PandocMonad m => MWParser m Blocks block = do - tr <- getOption readerTrace + tr <- (== DEBUG) <$> getOption readerVerbosity pos <- getPosition res <- mempty <$ skipMany1 blankline <|> table diff --git a/src/Text/Pandoc/Readers/TWiki.hs b/src/Text/Pandoc/Readers/TWiki.hs index 3e547e5f4..b54eec735 100644 --- a/src/Text/Pandoc/Readers/TWiki.hs +++ b/src/Text/Pandoc/Readers/TWiki.hs @@ -127,7 +127,7 @@ parseTWiki = do block :: TWParser B.Blocks block = do - tr <- getOption readerTrace + tr <- (== DEBUG) <$> getOption readerVerbosity pos <- getPosition res <- mempty <$ skipMany1 blankline <|> blockElements diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs index 404913926..b3a1a208f 100644 --- a/src/Text/Pandoc/Readers/Textile.hs +++ b/src/Text/Pandoc/Readers/Textile.hs @@ -147,7 +147,7 @@ block :: PandocMonad m => ParserT [Char] ParserState m Blocks block = do res <- choice blockParsers <?> "block" pos <- getPosition - tr <- getOption readerTrace + tr <- (== DEBUG) <$> getOption readerVerbosity when tr $ trace (printf "line %d: %s" (sourceLine pos) (take 60 $ show $ B.toList res)) (return ()) |