diff options
author | John MacFarlane <jgm@berkeley.edu> | 2017-05-02 16:00:04 +0200 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2017-05-02 16:00:04 +0200 |
commit | cd2551c16c1da0404b8de182f17160aebb69219d (patch) | |
tree | b6e959c06a95cfb8f8ae1b9ea5ac4c2ac78dacea /src/Text | |
parent | 022d58e02a6276aa830639ad641aae1542731bbe (diff) | |
download | pandoc-cd2551c16c1da0404b8de182f17160aebb69219d.tar.gz |
Added PandocResourceNotFound error.
Use this instead of PandocIOError when a resource is not
found in path.
This improves the error message in this case, see #3629.
Diffstat (limited to 'src/Text')
-rw-r--r-- | src/Text/Pandoc/Class.hs | 12 | ||||
-rw-r--r-- | src/Text/Pandoc/Error.hs | 3 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Docx.hs | 11 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/ICML.hs | 6 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/ODT.hs | 6 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/RTF.hs | 5 |
6 files changed, 14 insertions, 29 deletions
diff --git a/src/Text/Pandoc/Class.hs b/src/Text/Pandoc/Class.hs index 1afa64c10..ad9901125 100644 --- a/src/Text/Pandoc/Class.hs +++ b/src/Text/Pandoc/Class.hs @@ -330,8 +330,7 @@ downloadOrRead sourceURL s = do convertSlash x = x withPaths :: PandocMonad m => [FilePath] -> (FilePath -> m a) -> FilePath -> m a -withPaths [] _ fp = throwError $ PandocIOError fp - (userError "file not found in resource path") +withPaths [] _ fp = throwError $ PandocResourceNotFound fp withPaths (p:ps) action fp = catchError (action (p </> fp)) (\_ -> withPaths ps action fp) @@ -433,20 +432,17 @@ instance PandocMonad PandocPure where modifyPureState $ \st -> st { stUniqStore = us } return u _ -> M.fail "uniq store ran out of elements" - openURL u = throwError $ PandocIOError u $ - userError "Cannot open URL in PandocPure" + openURL u = throwError $ PandocResourceNotFound u readFileLazy fp = do fps <- getsPureState stFiles case infoFileContents <$> getFileInfo fp fps of Just bs -> return (BL.fromStrict bs) - Nothing -> throwError $ PandocIOError fp - (userError "File not found in PureState") + Nothing -> throwError $ PandocResourceNotFound fp readFileStrict fp = do fps <- getsPureState stFiles case infoFileContents <$> getFileInfo fp fps of Just bs -> return bs - Nothing -> throwError $ PandocIOError fp - (userError "File not found in PureState") + Nothing -> throwError $ PandocResourceNotFound fp readDataFile Nothing "reference.docx" = do (B.concat . BL.toChunks . fromArchive) <$> getsPureState stReferenceDocx readDataFile Nothing "reference.odt" = do diff --git a/src/Text/Pandoc/Error.hs b/src/Text/Pandoc/Error.hs index 135cb3945..a6db5e047 100644 --- a/src/Text/Pandoc/Error.hs +++ b/src/Text/Pandoc/Error.hs @@ -58,6 +58,7 @@ data PandocError = PandocIOError String IOError | PandocPDFError String | PandocFilterError String String | PandocCouldNotFindDataFileError String + | PandocResourceNotFound String | PandocAppError String deriving (Show, Typeable, Generic) @@ -94,6 +95,8 @@ handleError (Left e) = filtername ++ ":\n" ++ msg PandocCouldNotFindDataFileError fn -> err 97 $ "Could not find data file " ++ fn + PandocResourceNotFound fn -> err 99 $ + "File " ++ fn ++ " not found in resource path" PandocAppError s -> err 1 s err :: Int -> String -> IO a diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index fddec91cc..620f9060e 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -55,7 +55,6 @@ import Text.Pandoc.Class (PandocMonad, report) import qualified Text.Pandoc.Class as P import Text.Pandoc.Compat.Time import Text.Pandoc.Definition -import Text.Pandoc.Error import Text.Pandoc.Generic import Text.Pandoc.Highlighting (highlight) import Text.Pandoc.ImageSize @@ -1303,12 +1302,10 @@ inlineToOpenXML' opts (Image attr alt (src, title)) = do M.insert src (ident, imgpath, mbMimeType, imgElt, img) $ stImages st } return [imgElt]) - (\e -> do case e of - PandocIOError _ e' -> - report $ CouldNotFetchResource src (show e') - e' -> report $ CouldNotFetchResource src (show e') - -- emit alt text - inlinesToOpenXML opts alt) + (\e -> do + report $ CouldNotFetchResource src (show e) + -- emit alt text + inlinesToOpenXML opts alt) br :: Element br = breakElement "textWrapping" diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs index cd3cac5a7..4d9998665 100644 --- a/src/Text/Pandoc/Writers/ICML.hs +++ b/src/Text/Pandoc/Writers/ICML.hs @@ -25,7 +25,6 @@ import Network.URI (isURI) import Text.Pandoc.Class (PandocMonad, report) import qualified Text.Pandoc.Class as P import Text.Pandoc.Definition -import Text.Pandoc.Error (PandocError (..)) import Text.Pandoc.ImageSize import Text.Pandoc.Logging import Text.Pandoc.Options @@ -550,10 +549,7 @@ imageICML opts style attr (src, _) = do report $ CouldNotDetermineImageSize src msg return def) (\e -> do - case e of - PandocIOError _ e' -> - report $ CouldNotFetchResource src (show e') - e' -> report $ CouldNotFetchResource src (show e') + report $ CouldNotFetchResource src (show e) return def) let (ow, oh) = sizeInPoints imgS (imgWidth, imgHeight) = desiredSizeInPoints opts attr imgS diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs index 395ef0a96..6c6f38dbe 100644 --- a/src/Text/Pandoc/Writers/ODT.hs +++ b/src/Text/Pandoc/Writers/ODT.hs @@ -39,7 +39,6 @@ import System.FilePath (takeDirectory, takeExtension, (<.>)) import Text.Pandoc.Class (PandocMonad, report) import qualified Text.Pandoc.Class as P import Text.Pandoc.Definition -import Text.Pandoc.Error (PandocError (..)) import Text.Pandoc.ImageSize import Text.Pandoc.Logging import Text.Pandoc.MIME (extensionFromMimeType, getMimeType) @@ -178,10 +177,7 @@ transformPicMath opts (Image attr@(id', cls, _) lab (src,t)) = catchError modify $ \st -> st{ stEntries = entry : entries } return $ Image newattr lab (newsrc, t)) (\e -> do - case e of - PandocIOError _ e' -> - report $ CouldNotFetchResource src (show e') - e' -> report $ CouldNotFetchResource src (show e') + report $ CouldNotFetchResource src (show e) return $ Emph lab) transformPicMath _ (Math t math) = do diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs index 67f0fc2e0..7aa2280dd 100644 --- a/src/Text/Pandoc/Writers/RTF.hs +++ b/src/Text/Pandoc/Writers/RTF.hs @@ -92,10 +92,7 @@ rtfEmbedImage opts x@(Image attr _ (src,_)) = catchError report $ CouldNotDetermineMimeType src return x) (\e -> do - case e of - PandocIOError _ e' -> - report $ CouldNotFetchResource src (show e') - e' -> report $ CouldNotFetchResource src (show e') + report $ CouldNotFetchResource src (show e) return x) rtfEmbedImage _ x = return x |