pandoc/src/Text/Pandoc/Error.hs

101 lines
3.6 KiB
Haskell
Raw Normal View History

{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
2015-02-18 21:00:46 +00:00
{-
Copyright (C) 2006-2016 John MacFarlane <jgm@berkeley.edu>
2015-02-18 21:00:46 +00:00
This program is free software; you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by
the Free Software Foundation; either version 2 of the License, or
(at your option) any later version.
This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU General Public License for more details.
You should have received a copy of the GNU General Public License
along with this program; if not, write to the Free Software
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
-}
{- |
Module : Text.Pandoc.Error
Copyright : Copyright (C) 2006-2016 John MacFarlane
2015-02-18 21:00:46 +00:00
License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley.edu>
Stability : alpha
Portability : portable
This module provides a standard way to deal with possible errors encounted
during parsing.
-}
module Text.Pandoc.Error (
PandocError(..),
handleError) where
import Control.Exception (Exception)
2015-10-11 17:27:00 -07:00
import Data.Generics (Typeable)
2016-12-10 23:30:42 +01:00
import GHC.Generics (Generic)
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
data PandocError = PandocIOError String IOError
2016-12-01 12:13:51 -05:00
| PandocShouldNeverHappenError String
| PandocSomeError String
| PandocParseError String
| PandocParsecError Input ParseError
2017-02-19 09:53:24 +01:00
| PandocMakePDFError String
2017-04-04 14:34:39 +02:00
| PandocOptionError String
| PandocSyntaxMapError String
| PandocFailOnWarningError
| PandocPDFProgramNotFoundError String
2017-04-13 17:38:42 +02:00
| PandocPDFError String
2017-04-13 19:24:50 +02:00
| PandocFilterError String String
| PandocAppError Int String
2016-12-10 23:30:42 +01:00
deriving (Show, Typeable, Generic)
2016-12-01 12:13:51 -05:00
instance Exception PandocError
-- | 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
PandocIOError _ err' -> ioError err'
PandocShouldNeverHappenError s -> err 62 s
PandocSomeError s -> err 63 s
PandocParseError s -> err 64 s
2016-12-01 12:13:51 -05:00
PandocParsecError input err' ->
let errPos = errorPos err'
errLine = sourceLine errPos
errColumn = sourceColumn errPos
ls = lines input ++ [""]
errorInFile = if length ls > errLine - 1
then concat ["\n", (ls !! (errLine - 1))
,"\n", replicate (errColumn - 1) ' '
,"^"]
else ""
in err 65 $ "\nError at " ++ show err' ++ errorInFile
2017-02-19 09:53:24 +01:00
PandocMakePDFError s -> err 65 s
2017-04-04 14:34:39 +02:00
PandocOptionError s -> err 2 s
PandocSyntaxMapError s -> err 67 s
PandocFailOnWarningError -> err 3 "Failing because there were warnings."
PandocPDFProgramNotFoundError pdfprog -> err 47 $
pdfprog ++ " not found. " ++ pdfprog ++ " is needed for pdf output."
2017-04-13 17:38:42 +02:00
PandocPDFError log -> err 43 $ "Error producing PDF.\n" ++ log
2017-04-13 19:24:50 +02:00
PandocFilterError filter msg -> err 83 $ "Error running filter " ++
filter ++ ":\n" ++ msg
PandocAppError ec s -> err ec s
err :: Int -> String -> IO a
err exitCode msg = do
UTF8.hPutStrLn stderr msg
exitWith $ ExitFailure exitCode
return undefined