aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2017-02-10 23:59:47 +0100
committerJohn MacFarlane <jgm@berkeley.edu>2017-02-11 00:14:44 +0100
commit76c55466d3087224eccdc47c804ab2904be50df5 (patch)
tree8e605c9a6ab89569d8b51898f31487ac0c005a22 /src/Text/Pandoc/Writers
parent8ad7e2c21fd00d8225c5f243bf3383c956b6c83b (diff)
downloadpandoc-76c55466d3087224eccdc47c804ab2904be50df5.tar.gz
Use new warnings throughout the code base.
Diffstat (limited to 'src/Text/Pandoc/Writers')
-rw-r--r--src/Text/Pandoc/Writers/Docx.hs5
-rw-r--r--src/Text/Pandoc/Writers/EPUB.hs8
-rw-r--r--src/Text/Pandoc/Writers/FB2.hs10
-rw-r--r--src/Text/Pandoc/Writers/ICML.hs8
-rw-r--r--src/Text/Pandoc/Writers/Math.hs6
-rw-r--r--src/Text/Pandoc/Writers/ODT.hs8
-rw-r--r--src/Text/Pandoc/Writers/RTF.hs15
7 files changed, 29 insertions, 31 deletions
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index 6a53485c4..235358bf6 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -65,8 +65,9 @@ import Text.Pandoc.MIME (MimeType, getMimeType, getMimeTypeDef,
import Control.Applicative ((<|>))
import Data.Maybe (fromMaybe, mapMaybe, maybeToList, isNothing)
import Data.Char (ord, isSpace, toLower)
-import Text.Pandoc.Class (PandocMonad)
+import Text.Pandoc.Class (PandocMonad, report)
import qualified Text.Pandoc.Class as P
+import Text.Pandoc.Logging
data ListMarker = NoMarker
| BulletMarker
@@ -1173,7 +1174,7 @@ inlineToOpenXML' opts (Image attr alt (src, title)) = do
res <- runExceptT $ lift (P.fetchItem (writerSourceURL opts) src)
case res of
Left (_ :: PandocError) -> do
- P.warning ("Could not find image `" ++ src ++ "', skipping...")
+ report $ CouldNotFetchResource src ""
-- emit alt text
inlinesToOpenXML opts alt
Right (img, mt) -> do
diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs
index 7e9a20a0c..247014c20 100644
--- a/src/Text/Pandoc/Writers/EPUB.hs
+++ b/src/Text/Pandoc/Writers/EPUB.hs
@@ -29,6 +29,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
Conversion of 'Pandoc' documents to EPUB.
-}
module Text.Pandoc.Writers.EPUB ( writeEPUB2, writeEPUB3 ) where
+import Text.Pandoc.Logging
import qualified Data.Map as M
import qualified Data.Set as Set
import Data.Maybe ( fromMaybe, catMaybes )
@@ -65,7 +66,7 @@ import Text.Pandoc.MIME (MimeType, getMimeType, extensionFromMimeType)
import Text.HTML.TagSoup (Tag(TagOpen), fromAttrib, parseTags)
import Control.Monad.Except (throwError, catchError)
import Text.Pandoc.Error
-import Text.Pandoc.Class (PandocMonad)
+import Text.Pandoc.Class (PandocMonad, report)
import qualified Text.Pandoc.Class as P
-- A Chapter includes a list of blocks and maybe a section
@@ -415,7 +416,7 @@ pandocToEPUB version opts doc@(Pandoc meta _) = do
let matchingGlob f = do
xs <- lift $ P.glob f
when (null xs) $
- lift $ P.warning $ f ++ " did not match any font files."
+ report $ CouldNotFetchResource f "glob did not match any font files"
return xs
let mkFontEntry f = mkEntry (takeFileName f) `fmap` (lift $ P.readFileLazy f)
fontFiles <- concat <$> mapM matchingGlob (writerEpubFonts opts')
@@ -883,8 +884,7 @@ modifyMediaRef opts oldsrc = do
(oldsrc, (new, Just entry)):media}
return new)
(\e -> do
- P.warning $ "Could not find media `" ++ oldsrc ++
- "', skipping...\n" ++ show e
+ report $ CouldNotFetchResource oldsrc (show e)
return oldsrc)
transformBlock :: PandocMonad m
diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs
index 600d34499..6325b5f73 100644
--- a/src/Text/Pandoc/Writers/FB2.hs
+++ b/src/Text/Pandoc/Writers/FB2.hs
@@ -41,13 +41,13 @@ import qualified Text.XML.Light.Cursor as XC
import qualified Data.ByteString.Char8 as B8
import Control.Monad.Except (throwError, catchError)
-
+import Text.Pandoc.Logging
import Text.Pandoc.Definition
import Text.Pandoc.Options (WriterOptions(..), HTMLMathMethod(..), def)
import Text.Pandoc.Shared (orderedListMarkers, isHeaderBlock, capitalize,
linesToPara)
import Text.Pandoc.Error
-import Text.Pandoc.Class (PandocMonad)
+import Text.Pandoc.Class (PandocMonad, report)
import qualified Text.Pandoc.Class as P
-- | Data to be written at the end of the document:
@@ -244,14 +244,12 @@ fetchImage href link = do
catchError (do (bs, mbmime) <- P.fetchItem Nothing link
case mbmime of
Nothing -> do
- P.warning ("Could not determine mime type for "
- ++ link)
+ report $ CouldNotDetermineMimeType link
return Nothing
Just mime -> return $ Just (mime,
B8.unpack $ encode bs))
(\e ->
- do P.warning ("Could not fetch " ++ link ++
- ":\n" ++ show e)
+ do report $ CouldNotFetchResource link (show e)
return Nothing)
case mbimg of
Just (imgtype, imgdata) -> do
diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs
index 41bca11b2..50edc1865 100644
--- a/src/Text/Pandoc/Writers/ICML.hs
+++ b/src/Text/Pandoc/Writers/ICML.hs
@@ -30,7 +30,8 @@ import Control.Monad.State
import Control.Monad.Except (runExceptT)
import Network.URI (isURI)
import qualified Data.Set as Set
-import Text.Pandoc.Class (PandocMonad)
+import Text.Pandoc.Class (PandocMonad, report)
+import Text.Pandoc.Logging
import qualified Text.Pandoc.Class as P
type Style = [String]
@@ -538,14 +539,13 @@ imageICML opts style attr (src, _) = do
res <- runExceptT $ lift $ P.fetchItem (writerSourceURL opts) src
imgS <- case res of
Left (_ :: PandocError) -> do
- lift $ P.warning $ "Could not find image `" ++ src ++ "', skipping..."
+ report $ CouldNotFetchResource src ""
return def
Right (img, _) -> do
case imageSize img of
Right size -> return size
Left msg -> do
- lift $ P.warning $ "Could not determine image size in `" ++
- src ++ "': " ++ msg
+ report $ CouldNotDetermineImageSize src msg
return def
let (ow, oh) = sizeInPoints imgS
(imgWidth, imgHeight) = desiredSizeInPoints opts attr imgS
diff --git a/src/Text/Pandoc/Writers/Math.hs b/src/Text/Pandoc/Writers/Math.hs
index b959ce972..b7419ddf9 100644
--- a/src/Text/Pandoc/Writers/Math.hs
+++ b/src/Text/Pandoc/Writers/Math.hs
@@ -6,6 +6,7 @@ where
import Text.Pandoc.Class
import Text.Pandoc.Definition
+import Text.Pandoc.Logging
import Text.TeXMath (Exp, writePandoc, DisplayType(..), readTeX)
-- | Converts a raw TeX math formula to a list of 'Pandoc' inlines.
@@ -20,7 +21,7 @@ texMathToInlines mt inp = do
case res of
Right (Just ils) -> return ils
Right (Nothing) -> do
- warning $ "Could not render TeX math as unicode, rendering as raw TeX:\n" ++ inp
+ report $ CouldNotConvertTeXMath inp ""
return [mkFallback mt inp]
Left il -> return [il]
@@ -40,8 +41,7 @@ convertMath writer mt str = do
case writer dt <$> readTeX str of
Right r -> return (Right r)
Left e -> do
- warning $ "Could not convert TeX math, rendering as raw TeX:\n" ++
- str ++ "\n" ++ e
+ report $ CouldNotConvertTeXMath str e
return (Left $ mkFallback mt str)
where dt = case mt of
DisplayMath -> DisplayBlock
diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs
index 5672719f9..ee5fa4c24 100644
--- a/src/Text/Pandoc/Writers/ODT.hs
+++ b/src/Text/Pandoc/Writers/ODT.hs
@@ -50,8 +50,9 @@ import Text.Pandoc.Error (PandocError)
import Text.Pandoc.XML
import Text.Pandoc.Pretty
import System.FilePath ( takeExtension, takeDirectory, (<.>))
-import Text.Pandoc.Class ( PandocMonad )
+import Text.Pandoc.Class ( PandocMonad, report )
import qualified Text.Pandoc.Class as P
+import Text.Pandoc.Logging
data ODTState = ODTState { stEntries :: [Entry]
}
@@ -149,14 +150,13 @@ transformPicMath opts (Image attr@(id', cls, _) lab (src,t)) = do
res <- runExceptT $ lift $ P.fetchItem (writerSourceURL opts) src
case res of
Left (_ :: PandocError) -> do
- lift $ P.warning $ "Could not find image `" ++ src ++ "', skipping..."
+ report $ CouldNotFetchResource src ""
return $ Emph lab
Right (img, mbMimeType) -> do
(ptX, ptY) <- case imageSize img of
Right s -> return $ sizeInPoints s
Left msg -> do
- lift $ P.warning $ "Could not determine image size in `" ++
- src ++ "': " ++ msg
+ report $ CouldNotDetermineImageSize src msg
return (100, 100)
let dims =
case (getDim Width, getDim Height) of
diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs
index 77f01e4a1..25c631b9f 100644
--- a/src/Text/Pandoc/Writers/RTF.hs
+++ b/src/Text/Pandoc/Writers/RTF.hs
@@ -37,7 +37,7 @@ import Text.Pandoc.Writers.Shared
import Text.Pandoc.Writers.Math
import Text.Pandoc.Templates (renderTemplate')
import Text.Pandoc.Walk
-import Text.Pandoc.Class (warning)
+import Text.Pandoc.Logging
import Data.List ( isSuffixOf, intercalate )
import Data.Char ( ord, chr, isDigit )
import qualified Data.ByteString as B
@@ -46,7 +46,7 @@ import Text.Printf ( printf )
import Text.Pandoc.ImageSize
import Control.Monad.Except (throwError, runExceptT, lift)
import Text.Pandoc.Error
-import Text.Pandoc.Class (PandocMonad)
+import Text.Pandoc.Class (PandocMonad, report)
import qualified Text.Pandoc.Class as P
-- | Convert Image inlines into a raw RTF embedded image, read from a file,
@@ -65,8 +65,7 @@ rtfEmbedImage opts x@(Image attr _ (src,_)) = do
_ -> throwError $ PandocSomeError "Unknown file type"
sizeSpec <- case imageSize imgdata of
Left msg -> do
- warning $ "Could not determine image size in `" ++
- src ++ "': " ++ msg
+ report $ CouldNotDetermineImageSize src msg
return ""
Right sz -> return $ "\\picw" ++ show xpx ++
"\\pich" ++ show ypx ++
@@ -79,17 +78,17 @@ rtfEmbedImage opts x@(Image attr _ (src,_)) = do
concat bytes ++ "}"
if B.null imgdata
then do
- warning $ "Image " ++ src ++ " contained no data, skipping."
+ report $ CouldNotFetchResource src "image contained no data"
return x
else return $ RawInline (Format "rtf") raw
| otherwise -> do
- warning $ "Image " ++ src ++ " is not a jpeg or png, skipping."
+ report $ CouldNotFetchResource src "image is not a jpeg or png"
return x
Right (_, Nothing) -> do
- warning $ "Could not determine image type for " ++ src ++ ", skipping."
+ report $ CouldNotDetermineMimeType src
return x
Left ( e :: PandocError ) -> do
- warning $ "Could not fetch image " ++ src ++ "\n" ++ show e
+ report $ CouldNotFetchResource src (show e)
return x
rtfEmbedImage _ x = return x