aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn MacFarlane <[email protected]>2022-10-17 22:12:09 -0700
committerGitHub <[email protected]>2022-10-17 22:12:09 -0700
commitcca8eee58a23459afc74c32e1edbed829d64900c (patch)
tree4f4be5a80e714b2634838875c73e393cb42154b1
parentdbac9541b58a8034e279aff14197ac3bc7e8617f (diff)
T.P.Error: Remove PandocParsecError constructor from PandocError. (#8385)
Henceforth we just use `PandocParseError`. T.P.Parsing now exports `fromParsecError`, which can be used to turn a parsec ParseError into a regular PandocParseError (the appearance to the user should be unchanged in every case). [API change] Closes #8382.
-rw-r--r--MANUAL.txt1
-rw-r--r--src/Text/Pandoc/Error.hs29
-rw-r--r--src/Text/Pandoc/Parsing.hs4
-rw-r--r--src/Text/Pandoc/Parsing/General.hs38
-rw-r--r--src/Text/Pandoc/Readers/BibTeX.hs3
-rw-r--r--src/Text/Pandoc/Readers/CSV.hs4
-rw-r--r--src/Text/Pandoc/Readers/CommonMark.hs8
-rw-r--r--src/Text/Pandoc/Readers/DokuWiki.hs3
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs6
-rw-r--r--src/Text/Pandoc/Readers/LaTeX/Citation.hs3
-rw-r--r--src/Text/Pandoc/Readers/Man.hs13
-rw-r--r--src/Text/Pandoc/Readers/Muse.hs3
-rw-r--r--src/Text/Pandoc/Readers/RST.hs2
13 files changed, 57 insertions, 60 deletions
diff --git a/MANUAL.txt b/MANUAL.txt
index bdd3060cf..04eaa282f 100644
--- a/MANUAL.txt
+++ b/MANUAL.txt
@@ -1539,7 +1539,6 @@ Nonzero exit codes have the following meanings:
62 PandocShouldNeverHappenError
63 PandocSomeError
64 PandocParseError
- 65 PandocParsecError
66 PandocMakePDFError
67 PandocSyntaxMapError
83 PandocFilterError
diff --git a/src/Text/Pandoc/Error.hs b/src/Text/Pandoc/Error.hs
index b53e39ca3..434b37240 100644
--- a/src/Text/Pandoc/Error.hs
+++ b/src/Text/Pandoc/Error.hs
@@ -23,18 +23,13 @@ import Control.Exception (Exception, displayException)
import Data.Typeable (Typeable)
import Data.Word (Word8)
import Data.Text (Text)
-import Data.List (sortOn)
import qualified Data.Text as T
-import Data.Ord (Down(..))
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.Pandoc.Sources (Sources(..))
import Text.Printf (printf)
-import Text.Parsec.Error
-import Text.Parsec.Pos hiding (Line)
import Text.Pandoc.Shared (tshow)
import Citeproc (CiteprocError, prettyCiteprocError)
@@ -43,7 +38,6 @@ data PandocError = PandocIOError Text IOError
| PandocShouldNeverHappenError Text
| PandocSomeError Text
| PandocParseError Text
- | PandocParsecError Sources ParseError
| PandocMakePDFError Text
| PandocOptionError Text
| PandocSyntaxMapError Text
@@ -85,28 +79,6 @@ renderError e =
"Please report this to pandoc's developers: " <> s
PandocSomeError s -> s
PandocParseError s -> s
- PandocParsecError (Sources inputs) err' ->
- let errPos = errorPos err'
- errLine = sourceLine errPos
- errColumn = sourceColumn errPos
- errFile = sourceName errPos
- errorInFile =
- case sortOn (Down . sourceLine . fst)
- [ (pos,t)
- | (pos,t) <- inputs
- , sourceName pos == errFile
- , sourceLine pos <= errLine
- ] of
- [] -> ""
- ((pos,txt):_) ->
- let ls = T.lines txt <> [""]
- ln = (errLine - sourceLine pos) + 1
- in if length ls > ln && ln >= 1
- then T.concat ["\n", ls !! (ln - 1)
- ,"\n", T.replicate (errColumn - 1) " "
- ,"^"]
- else ""
- in "Error at " <> tshow err' <> errorInFile
PandocMakePDFError s -> s
PandocOptionError s -> s
PandocSyntaxMapError s -> s
@@ -198,7 +170,6 @@ handleError (Left e) =
PandocShouldNeverHappenError{} -> 62
PandocSomeError{} -> 63
PandocParseError{} -> 64
- PandocParsecError{} -> 65
PandocMakePDFError{} -> 66
PandocSyntaxMapError{} -> 67
PandocFilterError{} -> 83
diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs
index 83aad6104..501e8c74b 100644
--- a/src/Text/Pandoc/Parsing.hs
+++ b/src/Text/Pandoc/Parsing.hs
@@ -47,6 +47,7 @@ module Text.Pandoc.Parsing ( module Text.Pandoc.Sources,
mathDisplay,
withHorizDisplacement,
withRaw,
+ fromParsecError,
escaped,
characterReference,
upperRoman,
@@ -297,7 +298,8 @@ import Text.Pandoc.Parsing.General
trimInlinesF,
uri,
withHorizDisplacement,
- withRaw )
+ withRaw,
+ fromParsecError )
import Text.Pandoc.Parsing.GridTable
( gridTableWith,
gridTableWith',
diff --git a/src/Text/Pandoc/Parsing/General.hs b/src/Text/Pandoc/Parsing/General.hs
index d7c724694..e425c7408 100644
--- a/src/Text/Pandoc/Parsing/General.hs
+++ b/src/Text/Pandoc/Parsing/General.hs
@@ -58,6 +58,7 @@ module Text.Pandoc.Parsing.General
, uri
, withHorizDisplacement
, withRaw
+ , fromParsecError
)
where
@@ -82,7 +83,8 @@ import Data.Char
, toUpper
)
import Data.Functor (($>))
-import Data.List (intercalate)
+import Data.List (intercalate, sortOn)
+import Data.Ord (Down(..))
import Data.Maybe (fromMaybe)
import Data.Text (Text)
import Text.HTML.TagSoup.Entity (lookupEntity)
@@ -103,6 +105,11 @@ import Text.Parsec
( (<|>)
, ParsecT
, SourcePos
+ , sourceLine
+ , sourceColumn
+ , sourceName
+ , ParseError
+ , errorPos
, Stream(..)
, between
, choice
@@ -130,7 +137,7 @@ import Text.Parsec
import Text.Parsec.Pos (initialPos, newPos)
import Text.Parsec (Parsec)
import Text.Pandoc.Error
- ( PandocError(PandocParseError, PandocParsecError) )
+ ( PandocError(PandocParseError) )
import Text.Pandoc.Parsing.Capabilities
import Text.Pandoc.Parsing.State
import Text.Pandoc.Parsing.Future (Future (..))
@@ -623,7 +630,7 @@ readWithM :: (Monad m, ToSources t)
-> t -- ^ input
-> m (Either PandocError a)
readWithM parser state input =
- mapLeft (PandocParsecError sources)
+ mapLeft (fromParsecError sources)
<$> runParserT parser state (initialSourceName sources) sources
where
sources = toSources input
@@ -750,3 +757,28 @@ exciseLines mbstartline mbendline t =
Nothing -> numLines
Just x | x >= 0 -> x
| otherwise -> numLines + x -- negative from end
+
+fromParsecError :: Sources -> ParseError -> PandocError
+fromParsecError (Sources inputs) err' = PandocParseError msg
+ where
+ msg = "Error at " <> tshow err' <> errorContext
+ errPos = errorPos err'
+ errLine = sourceLine errPos
+ errColumn = sourceColumn errPos
+ errFile = sourceName errPos
+ errorContext =
+ case sortOn (Down . sourceLine . fst)
+ [ (pos,t)
+ | (pos,t) <- inputs
+ , sourceName pos == errFile
+ , sourceLine pos <= errLine
+ ] of
+ [] -> ""
+ ((pos,txt):_) ->
+ let ls = T.lines txt <> [""]
+ ln = (errLine - sourceLine pos) + 1
+ in if length ls > ln && ln >= 1
+ then T.concat ["\n", ls !! (ln - 1)
+ ,"\n", T.replicate (errColumn - 1) " "
+ ,"^"]
+ else ""
diff --git a/src/Text/Pandoc/Readers/BibTeX.hs b/src/Text/Pandoc/Readers/BibTeX.hs
index 63151c742..6d64e1adf 100644
--- a/src/Text/Pandoc/Readers/BibTeX.hs
+++ b/src/Text/Pandoc/Readers/BibTeX.hs
@@ -23,6 +23,7 @@ where
import Text.Pandoc.Options
import Text.Pandoc.Definition
import Text.Pandoc.Builder (setMeta, cite, str)
+import Text.Pandoc.Parsing (fromParsecError)
import Citeproc (Lang(..), parseLang)
import Citeproc.Locale (getLocale)
import Text.Pandoc.Error (PandocError(..))
@@ -63,7 +64,7 @@ readBibTeX' variant _opts t = do
Left _ -> throwError $ PandocCiteprocError e
Right l -> return l
case BibTeX.readBibtexString variant locale (const True) t of
- Left e -> throwError $ PandocParsecError (toSources t) e
+ Left e -> throwError $ fromParsecError (toSources t) e
Right refs -> return $ setMeta "references"
(map referenceToMetaValue refs)
. setMeta "nocite"
diff --git a/src/Text/Pandoc/Readers/CSV.hs b/src/Text/Pandoc/Readers/CSV.hs
index 23e0f7448..fd15a5510 100644
--- a/src/Text/Pandoc/Readers/CSV.hs
+++ b/src/Text/Pandoc/Readers/CSV.hs
@@ -21,11 +21,11 @@ import Text.Pandoc.CSV (parseCSV, defaultCSVOptions, CSVOptions(..))
import Text.Pandoc.Definition
import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Class (PandocMonad)
-import Text.Pandoc.Error
import Text.Pandoc.Sources (ToSources(..), sourcesToText)
import Text.Pandoc.Options (ReaderOptions)
import Control.Monad.Except (throwError)
import Data.Text (Text)
+import Text.Pandoc.Parsing (fromParsecError)
readCSV :: (PandocMonad m, ToSources a)
=> ReaderOptions -- ^ Reader options
@@ -68,4 +68,4 @@ readCSVWith csvopts txt = do
aligns = replicate numcols AlignDefault
widths = replicate numcols ColWidthDefault
Right [] -> return $ B.doc mempty
- Left e -> throwError $ PandocParsecError (toSources [("",txt)]) e
+ Left e -> throwError $ fromParsecError (toSources [("",txt)]) e
diff --git a/src/Text/Pandoc/Readers/CommonMark.hs b/src/Text/Pandoc/Readers/CommonMark.hs
index c2f21729e..71cf6f37e 100644
--- a/src/Text/Pandoc/Readers/CommonMark.hs
+++ b/src/Text/Pandoc/Readers/CommonMark.hs
@@ -25,7 +25,6 @@ import Text.Pandoc.Class.PandocMonad (PandocMonad)
import Text.Pandoc.Definition
import Text.Pandoc.Builder as B
import Text.Pandoc.Options
-import Text.Pandoc.Error
import Text.Pandoc.Readers.Metadata (yamlMetaBlock)
import Control.Monad.Except
import Data.Functor.Identity (runIdentity)
@@ -33,7 +32,8 @@ import Data.Typeable
import Text.Pandoc.Parsing (runParserT, getInput, getPosition,
runF, defaultParserState, option, many1, anyChar,
Sources(..), ToSources(..), ParsecT, Future,
- sourceName, sourceLine, incSourceLine)
+ sourceName, sourceLine, incSourceLine,
+ fromParsecError)
import Text.Pandoc.Walk (walk)
import qualified Data.Text as T
import qualified Data.Attoparsec.Text as A
@@ -95,10 +95,10 @@ readCommonMarkBody opts s toks =
else id) <$>
if isEnabled Ext_sourcepos opts
then case runIdentity (parseCommonmarkWith (specFor opts) toks) of
- Left err -> throwError $ PandocParsecError s err
+ Left err -> throwError $ fromParsecError s err
Right (Cm bls :: Cm SourceRange Blocks) -> return $ B.doc bls
else case runIdentity (parseCommonmarkWith (specFor opts) toks) of
- Left err -> throwError $ PandocParsecError s err
+ Left err -> throwError $ fromParsecError s err
Right (Cm bls :: Cm () Blocks) -> return $ B.doc bls
stripBlockComments :: Block -> Block
diff --git a/src/Text/Pandoc/Readers/DokuWiki.hs b/src/Text/Pandoc/Readers/DokuWiki.hs
index 1ed24bb34..d62ea970f 100644
--- a/src/Text/Pandoc/Readers/DokuWiki.hs
+++ b/src/Text/Pandoc/Readers/DokuWiki.hs
@@ -26,7 +26,6 @@ import qualified Data.Text as T
import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Class.PandocMonad (PandocMonad (..))
import Text.Pandoc.Definition
-import Text.Pandoc.Error (PandocError (PandocParsecError))
import Text.Pandoc.Options
import Text.Pandoc.Parsing hiding (enclosed, nested)
import Text.Pandoc.Shared (trim, stringify, tshow)
@@ -43,7 +42,7 @@ readDokuWiki opts s = do
res <- runParserT parseDokuWiki def {stateOptions = opts }
(initialSourceName sources) sources
case res of
- Left e -> throwError $ PandocParsecError sources e
+ Left e -> throwError $ fromParsecError sources e
Right d -> return d
type DWParser = ParsecT Sources ParserState
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index b077c92f4..58bf2becf 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -40,7 +40,7 @@ import Text.Pandoc.Class (PandocPure, PandocMonad (..), getResourcePath,
readFileFromDirs, report,
setResourcePath, getZonedTime)
import Data.Time (ZonedTime(..), LocalTime(..), showGregorian)
-import Text.Pandoc.Error (PandocError (PandocParseError, PandocParsecError))
+import Text.Pandoc.Error (PandocError (PandocParseError))
import Text.Pandoc.Highlighting (languagesByExtension)
import Text.Pandoc.ImageSize (numUnit, showFl)
import Text.Pandoc.Logging
@@ -87,7 +87,7 @@ readLaTeX opts ltx = do
(TokStream False (tokenizeSources sources))
case parsed of
Right result -> return result
- Left e -> throwError $ PandocParsecError sources e
+ Left e -> throwError $ fromParsecError sources e
parseLaTeX :: PandocMonad m => LP m Pandoc
parseLaTeX = do
@@ -669,7 +669,7 @@ opt = do
(TokStream False toks)
case parsed of
Right result -> return result
- Left e -> throwError $ PandocParsecError (toSources toks) e
+ Left e -> throwError $ fromParsecError (toSources toks) e
-- block elements:
diff --git a/src/Text/Pandoc/Readers/LaTeX/Citation.hs b/src/Text/Pandoc/Readers/LaTeX/Citation.hs
index 95629ce29..f26288c6e 100644
--- a/src/Text/Pandoc/Readers/LaTeX/Citation.hs
+++ b/src/Text/Pandoc/Readers/LaTeX/Citation.hs
@@ -15,7 +15,6 @@ import Control.Applicative ((<|>), optional, many)
import Control.Monad (mzero)
import Control.Monad.Trans (lift)
import Control.Monad.Except (throwError)
-import Text.Pandoc.Error (PandocError(PandocParsecError))
import Text.Pandoc.Parsing hiding (blankline, many, mathDisplay, mathInline,
optional, space, spaces, withRaw, (<|>))
@@ -121,7 +120,7 @@ simpleCiteArgs inline = try $ do
(TokStream False toks)
case parsed of
Right result -> return result
- Left e -> throwError $ PandocParsecError (toSources toks) e
+ Left e -> throwError $ fromParsecError (toSources toks) e
diff --git a/src/Text/Pandoc/Readers/Man.hs b/src/Text/Pandoc/Readers/Man.hs
index 715efff54..0f88b77b2 100644
--- a/src/Text/Pandoc/Readers/Man.hs
+++ b/src/Text/Pandoc/Readers/Man.hs
@@ -16,7 +16,7 @@ module Text.Pandoc.Readers.Man (readMan) where
import Data.Char (toLower)
import Data.Default (Default)
-import Control.Monad (liftM, mzero, guard, void)
+import Control.Monad (mzero, guard, void)
import Control.Monad.Trans (lift)
import Control.Monad.Except (throwError)
import Data.Maybe (catMaybes, isJust)
@@ -24,12 +24,10 @@ import Data.List (intersperse)
import qualified Data.Text as T
import Text.Pandoc.Builder as B
import Text.Pandoc.Class.PandocMonad (PandocMonad(..), report)
-import Text.Pandoc.Error (PandocError (PandocParsecError))
import Text.Pandoc.Logging (LogMessage(..))
import Text.Pandoc.Options
import Text.Pandoc.Parsing
import Text.Pandoc.Walk (query)
-import Text.Pandoc.Shared (mapLeft)
import Text.Pandoc.Readers.Roff -- TODO explicit imports
import qualified Text.Pandoc.Parsing as P
import qualified Data.Foldable as Foldable
@@ -56,21 +54,18 @@ readMan opts s = do
let Sources inps = toSources s
tokenz <- mconcat <$> mapM (uncurry lexRoff) inps
let state = def {readerOptions = opts} :: ManState
- let fixError (PandocParsecError _ e) = PandocParsecError (Sources inps) e
- fixError e = e
eitherdoc <- readWithMTokens parseMan state
(Foldable.toList . unRoffTokens $ tokenz)
- either (throwError . fixError) return eitherdoc
+ either (throwError . fromParsecError (Sources inps)) return eitherdoc
readWithMTokens :: PandocMonad m
=> ParsecT [RoffToken] ManState m a -- ^ parser
-> ManState -- ^ initial state
-> [RoffToken] -- ^ input
- -> m (Either PandocError a)
+ -> m (Either ParseError a)
readWithMTokens parser state input =
- let leftF = PandocParsecError mempty
- in mapLeft leftF `liftM` runParserT parser state "source" input
+ runParserT parser state "source" input
parseMan :: PandocMonad m => ManParser m Pandoc
diff --git a/src/Text/Pandoc/Readers/Muse.hs b/src/Text/Pandoc/Readers/Muse.hs
index c6a5ff06c..c18589728 100644
--- a/src/Text/Pandoc/Readers/Muse.hs
+++ b/src/Text/Pandoc/Readers/Muse.hs
@@ -33,7 +33,6 @@ import Text.Pandoc.Builder (Blocks, Inlines, underline)
import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Class.PandocMonad (PandocMonad (..))
import Text.Pandoc.Definition
-import Text.Pandoc.Error (PandocError (PandocParsecError))
import Text.Pandoc.Logging
import Text.Pandoc.Options
import Text.Pandoc.Parsing
@@ -49,7 +48,7 @@ readMuse opts s = do
res <- flip runReaderT def $ runParserT parseMuse def{ museOptions = opts }
(initialSourceName sources) sources
case res of
- Left e -> throwError $ PandocParsecError sources e
+ Left e -> throwError $ fromParsecError sources e
Right d -> return d
type F = Future MuseState
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index e9e53ae46..c1564eff5 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -871,7 +871,7 @@ csvTableDirective top fields rawcsv = do
let res = parseCSV opts rawcsv'
case (<>) <$> header' <*> res of
Left e ->
- throwError $ PandocParsecError "csv table" e
+ throwError $ fromParsecError (toSources rawcsv') e
Right rawrows -> do
let singleParaToPlain bs =
case B.toList bs of