aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Error.hs
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2017-04-02 23:02:55 +0200
committerJohn MacFarlane <jgm@berkeley.edu>2017-04-02 23:04:48 +0200
commit913db947a9cb43b6f449db2cd4c85fd74aa1ac8f (patch)
tree48af245903a81e6d80f1e8b7f4c8f519d1e7571b /src/Text/Pandoc/Error.hs
parent9e78a9d26b73fa603025789a942f70306aaaad22 (diff)
downloadpandoc-913db947a9cb43b6f449db2cd4c85fd74aa1ac8f.tar.gz
Text.Pandoc.App: Throw errors rather than exiting.
These are caught (and lead to exit) in pandoc.hs, but other uses of Text.Pandoc.App may want to recover in another way. Added PandocAppError to PandocError (API change). This is a stopgap: later we should have a separate constructor for each type of error. Also fixed uses of 'exit' in Shared.readDataFile, and removed 'err' from Shared (API change). Finally, removed the dependency on extensible-exceptions. See #3548.
Diffstat (limited to 'src/Text/Pandoc/Error.hs')
-rw-r--r--src/Text/Pandoc/Error.hs11
1 files changed, 10 insertions, 1 deletions
diff --git a/src/Text/Pandoc/Error.hs b/src/Text/Pandoc/Error.hs
index 4b38348ac..252c469b1 100644
--- a/src/Text/Pandoc/Error.hs
+++ b/src/Text/Pandoc/Error.hs
@@ -37,9 +37,11 @@ module Text.Pandoc.Error (
import Control.Exception (Exception)
import Data.Generics (Typeable)
import GHC.Generics (Generic)
-import Text.Pandoc.Shared (err)
import Text.Parsec.Error
import Text.Parsec.Pos hiding (Line)
+import qualified Text.Pandoc.UTF8 as UTF8
+import System.Exit (exitWith, ExitCode(..))
+import System.IO (stderr)
type Input = String
@@ -49,6 +51,7 @@ data PandocError = PandocIOError String IOError
| PandocParseError String
| PandocParsecError Input ParseError
| PandocMakePDFError String
+ | PandocAppError Int String
deriving (Show, Typeable, Generic)
instance Exception PandocError
@@ -74,4 +77,10 @@ handleError (Left e) =
else ""
in err 65 $ "\nError at " ++ show err' ++ errorInFile
PandocMakePDFError s -> err 65 s
+ PandocAppError ec s -> err ec s
+err :: Int -> String -> IO a
+err exitCode msg = do
+ UTF8.hPutStrLn stderr msg
+ exitWith $ ExitFailure exitCode
+ return undefined