pandoc/src/Text/Pandoc/Error.hs

126 lines
4.8 KiB
Haskell
Raw Normal View History

{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
2015-02-18 21:00:46 +00:00
{-
Copyright (C) 2006-2018 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-2018 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 Prelude
import Control.Exception (Exception)
import Data.Typeable (Typeable)
2016-12-10 23:30:42 +01:00
import GHC.Generics (Generic)
import Network.HTTP.Client (HttpException)
import System.Exit (ExitCode (..), exitWith)
import System.IO (stderr)
import qualified Text.Pandoc.UTF8 as UTF8
import Text.Parsec.Error
import Text.Parsec.Pos hiding (Line)
type Input = String
data PandocError = PandocIOError String IOError
| PandocHttpError String HttpException
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
| PandocCouldNotFindDataFileError String
| PandocResourceNotFound String
| PandocTemplateError String
2017-04-15 11:59:48 +02:00
| PandocAppError String
| PandocEpubSubdirectoryError String
2017-07-01 19:31:43 +02:00
| PandocMacroLoop 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'
PandocHttpError u err' -> err 61 $
"Could not fetch " ++ u ++ "\n" ++ show 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
2017-06-02 15:06:14 +02:00
then concat ["\n", ls !! (errLine - 1)
,"\n", replicate (errColumn - 1) ' '
,"^"]
else ""
in err 65 $ "\nError at " ++ show err' ++
-- if error comes from a chunk or included file,
-- then we won't get the right text this way:
if sourceName errPos == "source"
then errorInFile
else ""
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. Please select a different --pdf-engine or install " ++ pdfprog
2017-04-15 11:59:48 +02:00
PandocPDFError logmsg -> err 43 $ "Error producing PDF.\n" ++ logmsg
PandocFilterError filtername msg -> err 83 $ "Error running filter " ++
filtername ++ ":\n" ++ msg
PandocCouldNotFindDataFileError fn -> err 97 $
"Could not find data file " ++ fn
PandocResourceNotFound fn -> err 99 $
"File " ++ fn ++ " not found in resource path"
PandocTemplateError s -> err 5 s
2017-04-15 11:59:48 +02:00
PandocAppError s -> err 1 s
PandocEpubSubdirectoryError s -> err 31 $
"EPUB subdirectory name '" ++ s ++ "' contains illegal characters"
2017-07-01 19:31:43 +02:00
PandocMacroLoop s -> err 91 $
"Loop encountered in expanding macro " ++ s
err :: Int -> String -> IO a
err exitCode msg = do
UTF8.hPutStrLn stderr msg
exitWith $ ExitFailure exitCode
return undefined