lib: cleanup up megaparsec 6 compat module, simplify error type (#594)

This commit is contained in:
Simon Michael 2017-07-28 07:53:02 -07:00
parent d7d5f8a064
commit ecfc8224dd

View File

@ -1,3 +1,6 @@
-- ^ Paper over some differences between megaparsec 5 and 6,
-- making it possible to write code that supports both.
{-# LANGUAGE CPP, FlexibleContexts #-}
module Text.Megaparsec.Compat
@ -24,7 +27,20 @@ import Data.List.NonEmpty (fromList)
import Data.Void (Void)
-- | A basic parse error type.
type MPErr = ErrorFancy Void
type MPErr = Void
-- | Make a simple parse error.
mpMkParseError :: FilePath -> String -> ParseError Char String
mpMkParseError f s = FancyError (fromList [initialPos f]) (S.singleton $ ErrorFail s)
-- | Make a Pos. With a negative argument, throws InvalidPosException (megaparsec >= 6)
-- or calls error (megaparsec < 6).
mpMkPos :: Int -> Pos
mpMkPos = mkPos
-- | Unmake a Pos.
mpUnPos :: Pos -> Int
mpUnPos = unPos
-- | Parse and return some Text.
mptext :: MonadParsec e Text m => Tokens Text -> m (Tokens Text)
@ -34,33 +50,24 @@ mptext = string
import Text.Megaparsec.Prim (MonadParsec)
-- | A basic parse error type.
type MPErr = Dec
-- | Make a simple parse error.
mpMkParseError :: FilePath -> String -> ParseError Char String
mpMkParseError f s = (mempty :: ParseError Char String){errorCustom = S.singleton $ f ++ ": " ++ s}
-- | Make a Pos. With a negative argument, throws InvalidPosException (megaparsec >= 6)
-- or calls error (megaparsec < 6).
mpMkPos :: Int -> Pos
mpMkPos = unsafePos . fromIntegral
-- | Unmake a Pos.
mpUnPos :: Pos -> Int
mpUnPos = fromIntegral . unPos
-- | Parse and return some Text.
mptext :: MonadParsec e Text m => Text -> m Text
mptext = fmap pack . string . unpack
#endif
mpMkPos :: Int -> Pos
mpMkPos =
#if MIN_VERSION_megaparsec(6,0,0)
mkPos
#else
unsafePos . fromIntegral
#endif
mpUnPos :: Pos -> Int
mpUnPos =
#if MIN_VERSION_megaparsec(6,0,0)
unPos
#else
fromIntegral . unPos
#endif
mpMkParseError :: FilePath -> String -> ParseError Char String
mpMkParseError f s =
#if MIN_VERSION_megaparsec(6,0,0)
FancyError (fromList [initialPos f]) (S.singleton $ ErrorFail s)
#else
(mempty :: ParseError Char String){errorCustom = S.singleton $ f ++ ": " ++ s}
#endif