@@ -32,9 +32,6 @@ import qualified Data.Text
3232import qualified Data.Text.Encoding
3333import qualified Dhall.Crypto
3434import qualified Text.Megaparsec
35- #if !MIN_VERSION_megaparsec(7, 0, 0)
36- import qualified Text.Megaparsec.Char as Text.Megaparsec
37- #endif
3835
3936import Dhall.Parser.Combinators
4037import Dhall.Parser.Token
@@ -43,31 +40,19 @@ import Dhall.Parser.Token
4340getSourcePos :: Text.Megaparsec. MonadParsec e s m =>
4441 m Text.Megaparsec. SourcePos
4542getSourcePos =
46- #if MIN_VERSION_megaparsec(7, 0, 0)
4743 Text.Megaparsec. getSourcePos
48- #else
49- Text.Megaparsec. getPosition
50- #endif
5144{-# INLINE getSourcePos #-}
5245
5346-- | Get the current source offset (in tokens)
5447getOffset :: Text.Megaparsec. MonadParsec e s m => m Int
55- #if MIN_VERSION_megaparsec(7, 0, 0)
5648getOffset = Text.Megaparsec. stateOffset <$> Text.Megaparsec. getParserState
57- #else
58- getOffset = Text.Megaparsec. stateTokensProcessed <$> Text.Megaparsec. getParserState
59- #endif
6049{-# INLINE getOffset #-}
6150
6251-- | Set the current source offset
6352setOffset :: Text.Megaparsec. MonadParsec e s m => Int -> m ()
64- #if MIN_VERSION_megaparsec(7, 0, 0)
65- setOffset o = Text.Megaparsec. updateParserState $ \ (Text.Megaparsec. State s _ pst) ->
66- Text.Megaparsec. State s o pst
67- #else
68- setOffset o = Text.Megaparsec. updateParserState $ \ (Text.Megaparsec. State s p _ stw) ->
69- Text.Megaparsec. State s p o stw
70- #endif
53+ setOffset o = Text.Megaparsec. updateParserState $ \ state ->
54+ state
55+ { Text.Megaparsec. stateOffset = o }
7156{-# INLINE setOffset #-}
7257
7358{-| Wrap a `Parser` to still match the same text but return only the `Src`
0 commit comments