From 63a1e05dd1eb041aee55a5c5c4d0d84a035348b2 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sat, 28 Sep 2019 13:42:37 -0700 Subject: Replace some more fails with throwErrors. --- src/Text/Pandoc/Writers/Docx.hs | 7 +++++-- src/Text/Pandoc/Writers/Muse.hs | 3 ++- src/Text/Pandoc/Writers/Powerpoint/Output.hs | 3 ++- 3 files changed, 9 insertions(+), 4 deletions(-) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index 1c5dda84c..30c604058 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -3,6 +3,7 @@ {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ViewPatterns #-} +{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE OverloadedStrings #-} {- | Module : Text.Pandoc.Writers.Docx @@ -19,7 +20,7 @@ module Text.Pandoc.Writers.Docx ( writeDocx ) where import Prelude import Codec.Archive.Zip import Control.Applicative ((<|>)) -import Control.Monad.Except (catchError) +import Control.Monad.Except (catchError, throwError) import Control.Monad.Reader import Control.Monad.State.Strict import qualified Data.ByteString as B @@ -43,6 +44,7 @@ import Text.Pandoc.UTF8 (fromStringLazy) import Text.Pandoc.Definition import Text.Pandoc.Generic import Text.Pandoc.Highlighting (highlight) +import Text.Pandoc.Error import Text.Pandoc.ImageSize import Text.Pandoc.Logging import Text.Pandoc.MIME (MimeType, extensionFromMimeType, getMimeType, @@ -580,7 +582,8 @@ writeDocx opts doc@(Pandoc meta _) = do settingsEntry <- copyChildren refArchive distArchive settingsPath epochtime settingsList let entryFromArchive arch path = - maybe (Prelude.fail $ path ++ " missing in reference docx") + maybe (throwError $ PandocSomeError + $ path ++ " missing in reference docx") return (findEntryByPath path arch `mplus` findEntryByPath path distArchive) docPropsAppEntry <- entryFromArchive refArchive "docProps/app.xml" diff --git a/src/Text/Pandoc/Writers/Muse.hs b/src/Text/Pandoc/Writers/Muse.hs index 336520634..43f7f3b14 100644 --- a/src/Text/Pandoc/Writers/Muse.hs +++ b/src/Text/Pandoc/Writers/Muse.hs @@ -620,7 +620,8 @@ inlineToMuse (Quoted DoubleQuote lst) = do modify $ \st -> st { stUseTags = False } return $ "“" <> contents <> "”" inlineToMuse Cite {} = - Prelude.fail "Citations should be expanded before normalization" + throwError $ PandocShouldNeverHappenError + $ "Citations should be expanded before normalization" inlineToMuse (Code _ str) = do useTags <- gets stUseTags modify $ \st -> st { stUseTags = False } diff --git a/src/Text/Pandoc/Writers/Powerpoint/Output.hs b/src/Text/Pandoc/Writers/Powerpoint/Output.hs index 4a8dc1528..6b43fa34a 100644 --- a/src/Text/Pandoc/Writers/Powerpoint/Output.hs +++ b/src/Text/Pandoc/Writers/Powerpoint/Output.hs @@ -173,7 +173,8 @@ copyFileToArchive arch fp = do refArchive <- asks envRefArchive distArchive <- asks envDistArchive case findEntryByPath fp refArchive `mplus` findEntryByPath fp distArchive of - Nothing -> Prelude.fail $ fp ++ " missing in reference file" + Nothing -> throwError $ PandocSomeError + $ fp ++ " missing in reference file" Just e -> return $ addEntryToArchive e arch alwaysInheritedPatterns :: [Pattern] -- cgit v1.2.3