diff options
-rw-r--r-- | pandoc.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Options.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/PDF.hs | 11 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/EPUB.hs | 13 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Haddock.hs | 10 | ||||
-rw-r--r-- | tests/Tests/Readers/Docx.hs | 3 |
6 files changed, 16 insertions, 29 deletions
@@ -291,7 +291,6 @@ convertWithOpts opts args = do , readerIndentedCodeClasses = codeBlockClasses , readerApplyMacros = not laTeXOutput , readerDefaultImageExtension = defaultImageExtension - , readerVerbosity = verbosity , readerTrackChanges = trackChanges } @@ -328,7 +327,6 @@ convertWithOpts opts args = do writerEpubChapterLevel = epubChapterLevel, writerTOCDepth = epubTOCDepth, writerReferenceDoc = referenceDoc, - writerVerbosity = verbosity, writerLaTeXArgs = latexEngineArgs } @@ -406,7 +404,7 @@ convertWithOpts opts args = do err 41 $ pdfprog ++ " not found. " ++ pdfprog ++ " is needed for pdf output." - res <- makePDF pdfprog f writerOptions media doc' + res <- makePDF pdfprog f writerOptions verbosity media doc' case res of Right pdf -> writeFnBinary outputFile pdf Left err' -> liftIO $ do diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs index 262a0392d..cd525a3c1 100644 --- a/src/Text/Pandoc/Options.hs +++ b/src/Text/Pandoc/Options.hs @@ -62,7 +62,6 @@ data ReaderOptions = ReaderOptions{ , readerIndentedCodeClasses :: [String] -- ^ Default classes for -- indented code blocks , readerDefaultImageExtension :: String -- ^ Default extension for images - , readerVerbosity :: Verbosity -- ^ Verbosity level , readerTrackChanges :: TrackChanges } deriving (Show, Read, Data, Typeable, Generic) @@ -76,7 +75,6 @@ instance Default ReaderOptions , readerApplyMacros = True , readerIndentedCodeClasses = [] , readerDefaultImageExtension = "" - , readerVerbosity = ERROR , readerTrackChanges = AcceptChanges } @@ -186,7 +184,6 @@ 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 - , 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) @@ -228,7 +225,6 @@ instance Default WriterOptions where , writerEpubChapterLevel = 1 , writerTOCDepth = 3 , writerReferenceDoc = Nothing - , writerVerbosity = WARNING , writerLaTeXArgs = [] , writerReferenceLocation = EndOfDocument } diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs index cc523febf..b3bbcb4f5 100644 --- a/src/Text/Pandoc/PDF.hs +++ b/src/Text/Pandoc/PDF.hs @@ -74,10 +74,11 @@ makePDF :: MonadIO m -- xelatex, context, wkhtmltopdf) -> (WriterOptions -> Pandoc -> PandocIO String) -- ^ writer -> WriterOptions -- ^ options + -> Verbosity -- ^ verbosity level -> MediaBag -- ^ media -> Pandoc -- ^ document -> m (Either ByteString ByteString) -makePDF "wkhtmltopdf" writer opts _mediabag doc@(Pandoc meta _) = liftIO $ do +makePDF "wkhtmltopdf" writer opts verbosity _ doc@(Pandoc meta _) = liftIO $ do let mathArgs = case writerHTMLMathMethod opts of -- with MathJax, wait til all math is rendered: MathJax _ -> ["--run-script", "MathJax.Hub.Register.StartupHook('End Typeset', function() { window.status = 'mathjax_loaded' });", @@ -99,16 +100,16 @@ makePDF "wkhtmltopdf" writer opts _mediabag doc@(Pandoc meta _) = liftIO $ do (getField "margin-left" meta')) ] source <- runIOorExplode $ writer opts doc - html2pdf (writerVerbosity opts) args source -makePDF program writer opts mediabag doc = + html2pdf verbosity args source +makePDF program writer opts verbosity 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 (writerVerbosity opts) tmpdir source + "context" -> context2pdf verbosity tmpdir source prog | prog `elem` ["pdflatex", "lualatex", "xelatex"] - -> tex2pdf' (writerVerbosity opts) args tmpdir program source + -> tex2pdf' verbosity args tmpdir program source _ -> return $ Left $ UTF8.fromStringLazy $ "Unknown program " ++ program handleImages :: WriterOptions diff --git a/src/Text/Pandoc/Readers/EPUB.hs b/src/Text/Pandoc/Readers/EPUB.hs index 71a527f13..f24adb5b1 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(..), readerVerbosity, Verbosity(..)) +import Text.Pandoc.Options ( ReaderOptions(..), Verbosity(..)) import Text.Pandoc.Shared (escapeURI, collapseFilePath, addMetaField) import Network.URI (unEscapeString) import Text.Pandoc.MediaBag (MediaBag, insertMedia) @@ -26,18 +26,16 @@ import System.FilePath ( takeFileName, (</>), dropFileName, normalise , dropFileName , splitFileName ) import qualified Text.Pandoc.UTF8 as UTF8 (toStringLazy) -import Control.Monad (guard, liftM, when) +import Control.Monad (guard, liftM) import Data.List (isPrefixOf, isInfixOf) import Data.Maybe (mapMaybe, fromMaybe) import qualified Data.Map as M (Map, lookup, fromList, elems) import Data.Monoid ((<>)) import Control.DeepSeq (deepseq, NFData) import Text.Pandoc.Error -import Text.Pandoc.Class (PandocMonad) +import Text.Pandoc.Class (PandocMonad, report) import qualified Text.Pandoc.Class as P -import Debug.Trace (trace) - type Items = M.Map String (FilePath, MimeType) readEPUB :: PandocMonad m => ReaderOptions -> BL.ByteString -> m Pandoc @@ -71,7 +69,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 (readerVerbosity os == DEBUG) (traceM path) + report DEBUG ("parseSpineElem called with path " ++ show path) doc <- mimeToReader mime r path let docSpan = B.doc $ B.para $ B.spanWith (takeFileName path, [], []) mempty return $ docSpan <> doc @@ -241,9 +239,6 @@ foldM' f z (x:xs) = do uncurry3 :: (a -> b -> c -> d) -> (a, b, c) -> d uncurry3 f (a, b, c) = f a b c -traceM :: Monad m => String -> m () -traceM = flip trace (return ()) - -- Utility stripNamespace :: QName -> String diff --git a/src/Text/Pandoc/Readers/Haddock.hs b/src/Text/Pandoc/Readers/Haddock.hs index 575d99c77..310a04574 100644 --- a/src/Text/Pandoc/Readers/Haddock.hs +++ b/src/Text/Pandoc/Readers/Haddock.hs @@ -24,7 +24,6 @@ import Text.Pandoc.Definition import Text.Pandoc.Options import Documentation.Haddock.Parser import Documentation.Haddock.Types -import Debug.Trace (trace) import Text.Pandoc.Error import Control.Monad.Except (throwError) import Text.Pandoc.Class (PandocMonad) @@ -42,15 +41,12 @@ readHaddock opts s = case readHaddockEither opts s of readHaddockEither :: ReaderOptions -- ^ Reader options -> String -- ^ String to parse -> Either PandocError Pandoc -readHaddockEither opts = +readHaddockEither _opts = #if MIN_VERSION_haddock_library(1,2,0) - Right . B.doc . docHToBlocks . trace' . _doc . parseParas + Right . B.doc . docHToBlocks . _doc . parseParas #else - Right . B.doc . docHToBlocks . trace' . parseParas + Right . B.doc . docHToBlocks . parseParas #endif - where trace' x = if readerVerbosity opts == DEBUG - then trace (show x) x - else x docHToBlocks :: DocH String Identifier -> Blocks docHToBlocks d' = diff --git a/tests/Tests/Readers/Docx.hs b/tests/Tests/Readers/Docx.hs index 14bae19b0..8ced43907 100644 --- a/tests/Tests/Readers/Docx.hs +++ b/tests/Tests/Readers/Docx.hs @@ -62,7 +62,8 @@ testCompare = testCompareWithOpts defopts testForWarningsWithOptsIO :: ReaderOptions -> String -> FilePath -> [String] -> IO Test testForWarningsWithOptsIO opts name docxFile expected = do df <- B.readFile docxFile - warns <- runIOorExplode (readDocx opts df >> P.getWarnings) + logs <- runIOorExplode (readDocx opts df >> P.getLog) + let warns = [s | (WARNING, s) <- logs] return $ test id name (unlines warns, unlines expected) testForWarningsWithOpts :: ReaderOptions -> String -> FilePath -> [String] -> Test |