From d7583f365951373158a55ce344ba6b345ea481ec Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Sat, 3 Dec 2016 22:35:58 +0100 Subject: Error: change type of handleError. It now lives in IO and gives a proper message + exit instead of calling 'error'. We shouldn't be making it easier for people to raise error on pure code. And this is better for the main application in IO. --- src/Text/Pandoc.hs | 7 +++---- src/Text/Pandoc/Class.hs | 2 +- src/Text/Pandoc/Error.hs | 22 +++++++++++----------- 3 files changed, 15 insertions(+), 16 deletions(-) (limited to 'src/Text') diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs index 320af805a..4990a77fe 100644 --- a/src/Text/Pandoc.hs +++ b/src/Text/Pandoc.hs @@ -38,12 +38,11 @@ inline links: > module Main where > import Text.Pandoc > -> markdownToRST :: String -> String +> markdownToRST :: String -> Either PandocError String > markdownToRST = -> writeRST def {writerReferenceLinks = True} . -> handleError . readMarkdown def +> writeRST def {writerReferenceLinks = True} . readMarkdown def > -> main = getContents >>= putStrLn . markdownToRST +> main = getContents >>= either error return markdownToRST >>= putStrLn Note: all of the readers assume that the input text has @'\n'@ line endings. So if you get your input text from a web form, diff --git a/src/Text/Pandoc/Class.hs b/src/Text/Pandoc/Class.hs index 7227742b2..8d3a73d08 100644 --- a/src/Text/Pandoc/Class.hs +++ b/src/Text/Pandoc/Class.hs @@ -190,7 +190,7 @@ withWarningsToStderr f = do return x runIOorExplode :: PandocIO a -> IO a -runIOorExplode ma = handleError <$> runIO ma +runIOorExplode ma = runIO ma >>= handleError newtype PandocIO a = PandocIO { unPandocIO :: ExceptT PandocError (StateT CommonState IO) a diff --git a/src/Text/Pandoc/Error.hs b/src/Text/Pandoc/Error.hs index c001b279a..f76749a80 100644 --- a/src/Text/Pandoc/Error.hs +++ b/src/Text/Pandoc/Error.hs @@ -35,6 +35,7 @@ import Text.Parsec.Error import Text.Parsec.Pos hiding (Line) import Data.Generics (Typeable) import Control.Exception (Exception) +import Text.Pandoc.Shared (err) type Input = String @@ -54,15 +55,15 @@ data PandocError = PandocFileReadError FilePath instance Exception PandocError --- | An unsafe method to handle `PandocError`s. -handleError :: Either PandocError a -> a -handleError (Right r) = r -handleError (Left err) = - case err of - PandocFileReadError fp -> error $ "problem reading " ++ fp - PandocShouldNeverHappenError s -> error s - PandocSomeError s -> error s - PandocParseError s -> error s +-- | Handle PandocError by exiting with an error message. +handleError :: Either PandocError a -> IO a +handleError (Right r) = return r +handleError (Left e) = + case e of + PandocFileReadError fp -> err 61 $ "problem reading " ++ fp + PandocShouldNeverHappenError s -> err 62 s + PandocSomeError s -> err 63 s + PandocParseError s -> err 64 s PandocParsecError input err' -> let errPos = errorPos err' errLine = sourceLine errPos @@ -73,6 +74,5 @@ handleError (Left err) = ,"\n", replicate (errColumn - 1) ' ' ,"^"] else "" - in error $ "\nError at " ++ show err' - ++ errorInFile + in err 65 $ "\nError at " ++ show err' ++ errorInFile -- cgit v1.2.3