-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Monadic parser combinators -- -- This is industrial-strength monadic parser combinator library. -- Megaparsec is a fork of Parsec library originally written by Daan -- Leijen. @package megaparsec @version 5.0.1 -- | Textual source position. The position includes name of file, line -- number, and column number. List of such positions can be used to model -- stack of include files. module Text.Megaparsec.Pos -- | Positive integer that is used to represent line number, column number, -- and similar things like indentation level. Semigroup instance -- can be used to safely and purely add Poses together. data Pos -- | Construction of Pos from an instance of Integral. The -- function throws InvalidPosException when given non-positive -- argument. Note that the function is polymorphic with respect to -- MonadThrow m, so you can get result inside of -- Maybe, for example. mkPos :: (Integral a, MonadThrow m) => a -> m Pos -- | Extract Word from Pos. unPos :: Pos -> Word -- | Dangerous construction of Pos. Use when you know for sure that -- argument is positive. unsafePos :: Word -> Pos -- | The exception is thrown by mkPos when its argument is not a -- positive number. data InvalidPosException InvalidPosException :: InvalidPosException -- | The data type SourcePos represents source positions. It -- contains the name of the source file, a line number, and a column -- number. Source line and column positions change intensively during -- parsing, so we need to make them strict to avoid memory leaks. data SourcePos SourcePos :: FilePath -> !Pos -> !Pos -> SourcePos -- | Name of source file [sourceName] :: SourcePos -> FilePath -- | Line number [sourceLine] :: SourcePos -> !Pos -- | Column number [sourceColumn] :: SourcePos -> !Pos -- | Construct initial position (line 1, column 1) given name of source -- file. initialPos :: String -> SourcePos -- | Pretty-print a SourcePos. sourcePosPretty :: SourcePos -> String -- | Update a source position given a character. The first argument -- specifies tab width. If the character is a newline ('\n') the line -- number is incremented by 1. If the character is a tab ('\t') the -- column number is incremented to the nearest tab position. In all other -- cases, the column is incremented by 1. defaultUpdatePos :: Pos -> SourcePos -> Char -> (SourcePos, SourcePos) -- | Value of tab width used by default. Always prefer this constant when -- you want to refer to default tab width because actual value may -- change in future. Current value is 8. defaultTabWidth :: Pos instance GHC.Generics.Generic Text.Megaparsec.Pos.SourcePos instance Data.Data.Data Text.Megaparsec.Pos.SourcePos instance GHC.Classes.Ord Text.Megaparsec.Pos.SourcePos instance GHC.Classes.Eq Text.Megaparsec.Pos.SourcePos instance GHC.Read.Read Text.Megaparsec.Pos.SourcePos instance GHC.Show.Show Text.Megaparsec.Pos.SourcePos instance GHC.Generics.Generic Text.Megaparsec.Pos.InvalidPosException instance Data.Data.Data Text.Megaparsec.Pos.InvalidPosException instance GHC.Show.Show Text.Megaparsec.Pos.InvalidPosException instance GHC.Classes.Eq Text.Megaparsec.Pos.InvalidPosException instance Control.DeepSeq.NFData Text.Megaparsec.Pos.Pos instance Data.Data.Data Text.Megaparsec.Pos.Pos instance GHC.Classes.Ord Text.Megaparsec.Pos.Pos instance GHC.Classes.Eq Text.Megaparsec.Pos.Pos instance GHC.Show.Show Text.Megaparsec.Pos.Pos instance Data.Semigroup.Semigroup Text.Megaparsec.Pos.Pos instance GHC.Read.Read Text.Megaparsec.Pos.Pos instance GHC.Exception.Exception Text.Megaparsec.Pos.InvalidPosException instance Control.DeepSeq.NFData Text.Megaparsec.Pos.InvalidPosException instance Control.DeepSeq.NFData Text.Megaparsec.Pos.SourcePos -- | Parse errors. Current version of Megaparsec supports well-typed errors -- instead of String-based ones. This gives a lot of flexibility -- in describing what exactly went wrong as well as a way to return -- arbitrary data in case of failure. module Text.Megaparsec.Error -- | Data type that is used to represent “unexpected/expected” items in -- parse error. The data type is parametrized over token type t. data ErrorItem t -- | Non-empty stream of tokens Tokens :: (NonEmpty t) -> ErrorItem t -- | Label (cannot be empty) Label :: (NonEmpty Char) -> ErrorItem t -- | End of input EndOfInput :: ErrorItem t -- | The type class defines how to represent information about various -- exceptional situations. Data types that are used as custom data -- component in ParseError must be instances of this type class. class Ord e => ErrorComponent e -- | Represent message passed to fail in parser monad. representFail :: ErrorComponent e => String -> e -- | Represent information about incorrect indentation. representIndentation :: ErrorComponent e => Ordering -> Pos -> Pos -> e -- | “Default error component”. This in our instance of -- ErrorComponent provided out-of-box. data Dec -- | fail has been used in parser monad DecFail :: String -> Dec -- | Incorrect indentation error: desired ordering between reference level -- and actual level, reference indentation level, actual indentation -- level DecIndentation :: Ordering -> Pos -> Pos -> Dec -- | The data type ParseError represents parse errors. It provides -- the stack of source positions, set of expected and unexpected tokens -- as well as set of custom associated data. The data type is -- parametrized over token type t and custom data e. -- -- Note that stack of source positions contains current position as its -- head, and the rest of positions allows to track full sequence of -- include files with topmost source file at the end of the list. -- -- Semigroup (or Monoid) instance of the data type allows -- to merge parse errors from different branches of parsing. When merging -- two ParseErrors, longest match is preferred; if positions are -- the same, custom data sets and collections of message items are -- combined. data ParseError t e ParseError :: NonEmpty SourcePos -> Set (ErrorItem t) -> Set (ErrorItem t) -> Set e -> ParseError t e -- | Stack of source positions [errorPos] :: ParseError t e -> NonEmpty SourcePos -- | Unexpected items [errorUnexpected] :: ParseError t e -> Set (ErrorItem t) -- | Expected items [errorExpected] :: ParseError t e -> Set (ErrorItem t) -- | Associated data, if any [errorCustom] :: ParseError t e -> Set e -- | Type class ShowToken includes methods that allow to -- pretty-print single token as well as stream of tokens. This is used -- for rendering of error messages. class ShowToken a -- | Pretty-print non-empty stream of tokens. This function is also used to -- print single tokens (represented as singleton lists). showTokens :: ShowToken a => NonEmpty a -> String -- | The type class defines how to print custom data component of -- ParseError. class Ord a => ShowErrorComponent a -- | Pretty-print custom data component of ParseError. showErrorComponent :: ShowErrorComponent a => a -> String -- | Pretty-print ParseError. Note that rendered String -- always ends with a newline. parseErrorPretty :: (Ord t, ShowToken t, ShowErrorComponent e) => ParseError t e -> String -- | Pretty-print stack of source positions. sourcePosStackPretty :: NonEmpty SourcePos -> String instance GHC.Generics.Generic (Text.Megaparsec.Error.ParseError t e) instance (Data.Data.Data t, Data.Data.Data e, GHC.Classes.Ord t, GHC.Classes.Ord e) => Data.Data.Data (Text.Megaparsec.Error.ParseError t e) instance (GHC.Classes.Eq t, GHC.Classes.Eq e) => GHC.Classes.Eq (Text.Megaparsec.Error.ParseError t e) instance (GHC.Classes.Ord t, GHC.Classes.Ord e, GHC.Read.Read t, GHC.Read.Read e) => GHC.Read.Read (Text.Megaparsec.Error.ParseError t e) instance (GHC.Show.Show t, GHC.Show.Show e) => GHC.Show.Show (Text.Megaparsec.Error.ParseError t e) instance Data.Data.Data Text.Megaparsec.Error.Dec instance GHC.Classes.Ord Text.Megaparsec.Error.Dec instance GHC.Classes.Eq Text.Megaparsec.Error.Dec instance GHC.Read.Read Text.Megaparsec.Error.Dec instance GHC.Show.Show Text.Megaparsec.Error.Dec instance GHC.Generics.Generic (Text.Megaparsec.Error.ErrorItem t) instance Data.Data.Data t => Data.Data.Data (Text.Megaparsec.Error.ErrorItem t) instance GHC.Classes.Ord t => GHC.Classes.Ord (Text.Megaparsec.Error.ErrorItem t) instance GHC.Classes.Eq t => GHC.Classes.Eq (Text.Megaparsec.Error.ErrorItem t) instance GHC.Read.Read t => GHC.Read.Read (Text.Megaparsec.Error.ErrorItem t) instance GHC.Show.Show t => GHC.Show.Show (Text.Megaparsec.Error.ErrorItem t) instance Control.DeepSeq.NFData t => Control.DeepSeq.NFData (Text.Megaparsec.Error.ErrorItem t) instance Control.DeepSeq.NFData Text.Megaparsec.Error.Dec instance Text.Megaparsec.Error.ErrorComponent Text.Megaparsec.Error.Dec instance (Control.DeepSeq.NFData t, Control.DeepSeq.NFData e) => Control.DeepSeq.NFData (Text.Megaparsec.Error.ParseError t e) instance (GHC.Classes.Ord t, GHC.Classes.Ord e) => Data.Semigroup.Semigroup (Text.Megaparsec.Error.ParseError t e) instance (GHC.Classes.Ord t, GHC.Classes.Ord e) => GHC.Base.Monoid (Text.Megaparsec.Error.ParseError t e) instance (GHC.Show.Show t, Data.Typeable.Internal.Typeable t, GHC.Show.Show e, Data.Typeable.Internal.Typeable e) => GHC.Exception.Exception (Text.Megaparsec.Error.ParseError t e) instance Text.Megaparsec.Error.ShowToken GHC.Types.Char instance (GHC.Classes.Ord t, Text.Megaparsec.Error.ShowToken t) => Text.Megaparsec.Error.ShowErrorComponent (Text.Megaparsec.Error.ErrorItem t) instance Text.Megaparsec.Error.ShowErrorComponent Text.Megaparsec.Error.Dec -- | The primitive parser combinators. module Text.Megaparsec.Prim -- | This is Megaparsec's state, it's parametrized over stream type -- s. data State s State :: s -> NonEmpty SourcePos -> Pos -> State s [stateInput] :: State s -> s [statePos] :: State s -> NonEmpty SourcePos [stateTabWidth] :: State s -> Pos -- | An instance of Stream s has stream type s. Token -- type is determined by the stream and can be found via Token -- type function. class Ord (Token s) => Stream s where type Token s :: * where { type family Token s :: *; } -- | Get next token from the stream. If the stream is empty, return -- Nothing. uncons :: Stream s => s -> Maybe (Token s, s) -- | Update position in stream given tab width, current position, and -- current token. The result is a tuple where the first element will be -- used to report parse errors for current token, while the second -- element is the incremented position that will be stored in parser's -- state. -- -- When you work with streams where elements do not contain information -- about their position in input, result is usually consists of the third -- argument unchanged and incremented position calculated with respect to -- current token. This is how default instances of Stream work -- (they use defaultUpdatePos, which may be a good starting point -- for your own position-advancing function). -- -- When you wish to deal with stream of tokens where every token “knows” -- its start and end position in input (for example, you have produced -- the stream with Happy/Alex), then the best strategy is to use the -- start position as actual element position and provide the end position -- of the token as incremented one. updatePos :: Stream s => Proxy s -> Pos -> SourcePos -> Token s -> (SourcePos, SourcePos) -- | Parsec is non-transformer variant of more general -- ParsecT monad transformer. type Parsec e s = ParsecT e s Identity -- | ParsecT e s m a is a parser with custom data component of -- error e, stream type s, underlying monad m -- and return type a. data ParsecT e s m a -- | Type class describing parsers independent of input type. class (ErrorComponent e, Stream s, Alternative m, MonadPlus m) => MonadParsec e s m | m -> e s where hidden = label "" -- | The most general way to stop parsing and report ParseError. -- -- unexpected is defined in terms of this function: -- --
--   unexpected item = failure (Set.singleton item) Set.empty Set.empty
--   
failure :: MonadParsec e s m => Set (ErrorItem (Token s)) -> Set (ErrorItem (Token s)) -> Set e -> m a -- | The parser label name p behaves as parser p, but -- whenever the parser p fails without consuming any -- input, it replaces names of “expected” tokens with the name -- name. label :: MonadParsec e s m => String -> m a -> m a -- | hidden p behaves just like parser p, but it doesn't -- show any “expected” tokens in error message when p fails. hidden :: MonadParsec e s m => m a -> m a -- | The parser try p behaves like parser p, except that -- it pretends that it hasn't consumed any input when an error occurs. -- -- This combinator is used whenever arbitrary look ahead is needed. Since -- it pretends that it hasn't consumed any input when p fails, -- the (<|>) combinator will try its second alternative even -- when the first parser failed while consuming input. -- -- For example, here is a parser that is supposed to parse word “let” or -- “lexical”: -- --
--   >>> parseTest (string "let" <|> string "lexical") "lexical"
--   1:1:
--   unexpected "lex"
--   expecting "let"
--   
-- -- What happens here? First parser consumes “le” and fails (because it -- doesn't see a “t”). The second parser, however, isn't tried, since the -- first parser has already consumed some input! try fixes this -- behavior and allows backtracking to work: -- --
--   >>> parseTest (try (string "let") <|> string "lexical") "lexical"
--   "lexical"
--   
-- -- try also improves error messages in case of overlapping -- alternatives, because Megaparsec's hint system can be used: -- --
--   >>> parseTest (try (string "let") <|> string "lexical") "le"
--   1:1:
--   unexpected "le"
--   expecting "let" or "lexical"
--   
-- -- Please note that as of Megaparsec 4.4.0, string backtracks -- automatically (see tokens), so it does not need try. -- However, the examples above demonstrate the idea behind try so -- well that it was decided to keep them. try :: MonadParsec e s m => m a -> m a -- | lookAhead p parses p without consuming any input. -- -- If p fails and consumes some input, so does -- lookAhead. Combine with try if this is undesirable. lookAhead :: MonadParsec e s m => m a -> m a -- | notFollowedBy p only succeeds when parser p fails. -- This parser does not consume any input and can be used to implement -- the “longest match” rule. notFollowedBy :: MonadParsec e s m => m a -> m () -- | withRecovery r p allows continue parsing even if parser -- p fails. In this case r is called with actual -- ParseError as its argument. Typical usage is to return value -- signifying failure to parse this particular object and to consume some -- part of input up to start of next object. -- -- Note that if r fails, original error message is reported as -- if without withRecovery. In no way recovering parser r -- can influence error messages. withRecovery :: MonadParsec e s m => (ParseError (Token s) e -> m a) -> m a -> m a -- | This parser only succeeds at the end of the input. eof :: MonadParsec e s m => m () -- | The parser token test mrep accepts a token t with -- result x when the function test t returns -- Right x. mrep may provide representation of -- the token to report in error messages when input stream in empty. -- -- This is the most primitive combinator for accepting tokens. For -- example, the satisfy parser is implemented as: -- --
--   satisfy f = token testChar Nothing
--     where
--       testChar x =
--         if f x
--           then Right x
--           else Left (Set.singleton (Tokens (x:|[])), Set.empty, Set.empty)
--   
token :: MonadParsec e s m => (Token s -> Either (Set (ErrorItem (Token s)), Set (ErrorItem (Token s)), Set e) a) -> Maybe (Token s) -> m a -- | The parser tokens test parses list of tokens and returns it. -- Supplied predicate test is used to check equality of given -- and parsed tokens. -- -- This can be used for example to write string: -- --
--   string = tokens (==)
--   
-- -- Note that beginning from Megaparsec 4.4.0, this is an -- auto-backtracking primitive, which means that if it fails, it never -- consumes any input. This is done to make its consumption model match -- how error messages for this primitive are reported (which becomes an -- important thing as user gets more control with primitives like -- withRecovery): -- --
--   >>> parseTest (string "abc") "abd"
--   1:1:
--   unexpected "abd"
--   expecting "abc"
--   
-- -- This means, in particular, that it's no longer necessary to use -- try with tokens-based parsers, such as string and -- string'. This feature does not affect performance in any -- way. tokens :: MonadParsec e s m => (Token s -> Token s -> Bool) -> [Token s] -> m [Token s] -- | Returns the full parser state as a State record. getParserState :: MonadParsec e s m => m (State s) -- | updateParserState f applies function f to the parser -- state. updateParserState :: MonadParsec e s m => (State s -> State s) -> m () -- | A synonym for label in form of an operator. () :: MonadParsec e s m => m a -> String -> m a infix 0 -- | The parser unexpected item always fails with an error message -- telling about unexpected item item without consuming any -- input. unexpected :: MonadParsec e s m => ErrorItem (Token s) -> m a -- | Return the current input. getInput :: MonadParsec e s m => m s -- | setInput input continues parsing with input. The -- getInput and setInput functions can for example be used -- to deal with include files. setInput :: MonadParsec e s m => s -> m () -- | Return the current source position. -- -- See also: setPosition, pushPosition, popPosition, -- and SourcePos. getPosition :: MonadParsec e s m => m SourcePos -- | setPosition pos sets the current source position to -- pos. -- -- See also: getPosition, pushPosition, popPosition, -- and SourcePos. setPosition :: MonadParsec e s m => SourcePos -> m () -- | Push given position into stack of positions and continue parsing -- working with this position. Useful for working with include files and -- the like. -- -- See also: getPosition, setPosition, popPosition, -- and SourcePos. pushPosition :: MonadParsec e s m => SourcePos -> m () -- | Pop a position from stack of positions unless it only contains one -- element (in that case stack of positions remains the same). This is -- how to return to previous source file after pushPosition. -- -- See also: getPosition, setPosition, pushPosition, -- and SourcePos. popPosition :: MonadParsec e s m => m () -- | Return tab width. Default tab width is equal to -- defaultTabWidth. You can set different tab width with help of -- setTabWidth. getTabWidth :: MonadParsec e s m => m Pos -- | Set tab width. If argument of the function is not positive number, -- defaultTabWidth will be used. setTabWidth :: MonadParsec e s m => Pos -> m () -- | setParserState st set the full parser state to st. setParserState :: MonadParsec e s m => State s -> m () -- | runParser p file input runs parser p on the input -- list of tokens input, obtained from source file. The -- file is only used in error messages and may be the empty -- string. Returns either a ParseError (Left) or a value of -- type a (Right). -- --
--   parseFromFile p file = runParser p file <$> readFile file
--   
runParser :: Parsec e s a -> String -> s -> Either (ParseError (Token s) e) a -- | The function is similar to runParser with the difference that -- it accepts and returns parser state. This allows to specify arbitrary -- textual position at the beginning of parsing, for example. This is the -- most general way to run a parser over the Identity monad. runParser' :: Parsec e s a -> State s -> (State s, Either (ParseError (Token s) e) a) -- | runParserT p file input runs parser p on the input -- list of tokens input, obtained from source file. The -- file is only used in error messages and may be the empty -- string. Returns a computation in the underlying monad m that -- returns either a ParseError (Left) or a value of type -- a (Right). runParserT :: Monad m => ParsecT e s m a -> String -> s -> m (Either (ParseError (Token s) e) a) -- | This function is similar to runParserT, but like -- runParser' it accepts and returns parser state. This is thus -- the most general way to run a parser. runParserT' :: Monad m => ParsecT e s m a -> State s -> m (State s, Either (ParseError (Token s) e) a) -- | parse p file input runs parser p over -- Identity (see runParserT if you're using the -- ParsecT monad transformer; parse itself is just a -- synonym for runParser). It returns either a ParseError -- (Left) or a value of type a (Right). -- parseErrorPretty can be used to turn ParseError into the -- string representation of the error message. See -- Text.Megaparsec.Error if you need to do more advanced error -- analysis. -- --
--   main = case (parse numbers "" "11,2,43") of
--            Left err -> putStr (parseErrorPretty err)
--            Right xs -> print (sum xs)
--   
--   numbers = integer `sepBy` char ','
--   
parse :: Parsec e s a -> String -> s -> Either (ParseError (Token s) e) a -- | parseMaybe p input runs parser p on input -- and returns result inside Just on success and Nothing on -- failure. This function also parses eof, so if the parser -- doesn't consume all of its input, it will fail. -- -- The function is supposed to be useful for lightweight parsing, where -- error messages (and thus file name) are not important and entire input -- should be parsed. For example it can be used when parsing of single -- number according to specification of its format is desired. parseMaybe :: (ErrorComponent e, Stream s) => Parsec e s a -> s -> Maybe a -- | The expression parseTest p input applies a parser p -- against input input and prints the result to stdout. Useful -- for testing. parseTest :: (ShowErrorComponent e, Ord (Token s), ShowToken (Token s), Show a) => Parsec e s a -> s -> IO () instance GHC.Base.Monoid (Text.Megaparsec.Prim.Hints t) instance Data.Semigroup.Semigroup (Text.Megaparsec.Prim.Hints t) instance GHC.Generics.Generic (Text.Megaparsec.Prim.State s) instance Data.Data.Data s => Data.Data.Data (Text.Megaparsec.Prim.State s) instance GHC.Classes.Eq s => GHC.Classes.Eq (Text.Megaparsec.Prim.State s) instance GHC.Show.Show s => GHC.Show.Show (Text.Megaparsec.Prim.State s) instance Control.DeepSeq.NFData s => Control.DeepSeq.NFData (Text.Megaparsec.Prim.State s) instance Text.Megaparsec.Prim.Stream GHC.Base.String instance Text.Megaparsec.Prim.Stream Data.ByteString.Internal.ByteString instance Text.Megaparsec.Prim.Stream Data.ByteString.Lazy.Internal.ByteString instance Text.Megaparsec.Prim.Stream Data.Text.Internal.Text instance Text.Megaparsec.Prim.Stream Data.Text.Internal.Lazy.Text instance GHC.Base.Functor (Text.Megaparsec.Prim.ParsecT e s m) instance (Text.Megaparsec.Error.ErrorComponent e, Text.Megaparsec.Prim.Stream s) => GHC.Base.Applicative (Text.Megaparsec.Prim.ParsecT e s m) instance (Text.Megaparsec.Error.ErrorComponent e, Text.Megaparsec.Prim.Stream s) => GHC.Base.Alternative (Text.Megaparsec.Prim.ParsecT e s m) instance (Text.Megaparsec.Error.ErrorComponent e, Text.Megaparsec.Prim.Stream s) => GHC.Base.Monad (Text.Megaparsec.Prim.ParsecT e s m) instance (Text.Megaparsec.Error.ErrorComponent e, Text.Megaparsec.Prim.Stream s) => Control.Monad.Fail.MonadFail (Text.Megaparsec.Prim.ParsecT e s m) instance (Text.Megaparsec.Error.ErrorComponent e, Text.Megaparsec.Prim.Stream s, Control.Monad.IO.Class.MonadIO m) => Control.Monad.IO.Class.MonadIO (Text.Megaparsec.Prim.ParsecT e s m) instance (Text.Megaparsec.Error.ErrorComponent e, Text.Megaparsec.Prim.Stream s, Control.Monad.Reader.Class.MonadReader r m) => Control.Monad.Reader.Class.MonadReader r (Text.Megaparsec.Prim.ParsecT e s m) instance (Text.Megaparsec.Error.ErrorComponent e, Text.Megaparsec.Prim.Stream s, Control.Monad.State.Class.MonadState st m) => Control.Monad.State.Class.MonadState st (Text.Megaparsec.Prim.ParsecT e s m) instance (Text.Megaparsec.Error.ErrorComponent e, Text.Megaparsec.Prim.Stream s, Control.Monad.Cont.Class.MonadCont m) => Control.Monad.Cont.Class.MonadCont (Text.Megaparsec.Prim.ParsecT e s m) instance (Text.Megaparsec.Error.ErrorComponent e, Text.Megaparsec.Prim.Stream s, Control.Monad.Error.Class.MonadError e' m) => Control.Monad.Error.Class.MonadError e' (Text.Megaparsec.Prim.ParsecT e s m) instance (Text.Megaparsec.Error.ErrorComponent e, Text.Megaparsec.Prim.Stream s) => GHC.Base.MonadPlus (Text.Megaparsec.Prim.ParsecT e s m) instance Control.Monad.Trans.Class.MonadTrans (Text.Megaparsec.Prim.ParsecT e s) instance (Text.Megaparsec.Error.ErrorComponent e, Text.Megaparsec.Prim.Stream s) => Text.Megaparsec.Prim.MonadParsec e s (Text.Megaparsec.Prim.ParsecT e s m) instance Text.Megaparsec.Prim.MonadParsec e s m => Text.Megaparsec.Prim.MonadParsec e s (Control.Monad.Trans.State.Lazy.StateT st m) instance Text.Megaparsec.Prim.MonadParsec e s m => Text.Megaparsec.Prim.MonadParsec e s (Control.Monad.Trans.State.Strict.StateT st m) instance Text.Megaparsec.Prim.MonadParsec e s m => Text.Megaparsec.Prim.MonadParsec e s (Control.Monad.Trans.Reader.ReaderT st m) instance (GHC.Base.Monoid w, Text.Megaparsec.Prim.MonadParsec e s m) => Text.Megaparsec.Prim.MonadParsec e s (Control.Monad.Trans.Writer.Lazy.WriterT w m) instance (GHC.Base.Monoid w, Text.Megaparsec.Prim.MonadParsec e s m) => Text.Megaparsec.Prim.MonadParsec e s (Control.Monad.Trans.Writer.Strict.WriterT w m) instance Text.Megaparsec.Prim.MonadParsec e s m => Text.Megaparsec.Prim.MonadParsec e s (Control.Monad.Trans.Identity.IdentityT m) -- | Convenience definitions for working with strict ByteString. module Text.Megaparsec.ByteString -- | Modules corresponding to various types of streams define Parser -- accordingly, so user can use it to easily change type of input stream -- by importing different “type modules”. This one is for strict -- byte-strings. type Parser = Parsec Dec ByteString -- | Convenience definitions for working with lazy ByteString. module Text.Megaparsec.ByteString.Lazy -- | Modules corresponding to various types of streams define Parser -- accordingly, so user can use it to easily change type of input stream -- by importing different “type modules”. This one is for lazy -- byte-strings. type Parser = Parsec Dec ByteString -- | Convenience definitions for working with String as input -- stream. module Text.Megaparsec.String -- | Modules corresponding to various types of streams define Parser -- accordingly, so user can use it to easily change type of input stream -- by importing different “type modules”. This one is for strings. type Parser = Parsec Dec String -- | Convenience definitions for working with strict Text. module Text.Megaparsec.Text -- | Modules corresponding to various types of streams define Parser -- accordingly, so user can use it to easily change type of input stream -- by importing different “type modules”. This one is for strict text. type Parser = Parsec Dec Text -- | Convenience definitions for working with lazy Text. module Text.Megaparsec.Text.Lazy -- | Modules corresponding to various types of streams define Parser -- accordingly, so user can use it to easily change type of input stream -- by importing different “type modules”. This one is for lazy text. type Parser = Parsec Dec Text -- | Commonly used generic combinators. Note that all combinators works -- with any Alternative instances. module Text.Megaparsec.Combinator -- | between open close p parses open, followed by -- p and close. Returns the value returned by -- p. -- --
--   braces = between (symbol "{") (symbol "}")
--   
between :: Applicative m => m open -> m close -> m a -> m a -- | choice ps tries to apply the parsers in the list ps -- in order, until one of them succeeds. Returns the value of the -- succeeding parser. choice :: (Foldable f, Alternative m) => f (m a) -> m a -- | count n p parses n occurrences of p. If -- n is smaller or equal to zero, the parser equals to -- return []. Returns a list of n values. count :: Applicative m => Int -> m a -> m [a] -- | count' m n p parses from m to n occurrences -- of p. If n is not positive or m > n, the -- parser equals to return []. Returns a list of parsed values. -- -- Please note that m may be negative, in this case -- effect is the same as if it were equal to zero. count' :: Alternative m => Int -> Int -> m a -> m [a] -- | Combine two alternatives. eitherP :: Alternative m => m a -> m b -> m (Either a b) -- | endBy p sep parses zero or more occurrences of -- p, separated and ended by sep. Returns a list of -- values returned by p. -- --
--   cStatements = cStatement `endBy` semicolon
--   
endBy :: Alternative m => m a -> m sep -> m [a] -- | endBy1 p sep parses one or more occurrences of -- p, separated and ended by sep. Returns a list of -- values returned by p. endBy1 :: Alternative m => m a -> m sep -> m [a] -- | manyTill p end applies parser p zero or more -- times until parser end succeeds. Returns the list of values -- returned by p. This parser can be used to scan comments: -- --
--   simpleComment = string "<!--" >> manyTill anyChar (string "-->")
--   
manyTill :: Alternative m => m a -> m end -> m [a] -- | someTill p end works similarly to manyTill p end, -- but p should succeed at least once. someTill :: Alternative m => m a -> m end -> m [a] -- | option x p tries to apply parser p. If p -- fails without consuming input, it returns the value x, -- otherwise the value returned by p. -- --
--   priority = option 0 (digitToInt <$> digitChar)
--   
option :: Alternative m => a -> m a -> m a -- | sepBy p sep parses zero or more occurrences of -- p, separated by sep. Returns a list of values -- returned by p. -- --
--   commaSep p = p `sepBy` comma
--   
sepBy :: Alternative m => m a -> m sep -> m [a] -- | sepBy1 p sep parses one or more occurrences of -- p, separated by sep. Returns a list of values -- returned by p. sepBy1 :: Alternative m => m a -> m sep -> m [a] -- | sepEndBy p sep parses zero or more occurrences of -- p, separated and optionally ended by sep. Returns a -- list of values returned by p. sepEndBy :: Alternative m => m a -> m sep -> m [a] -- | sepEndBy1 p sep parses one or more occurrences of -- p, separated and optionally ended by sep. Returns a -- list of values returned by p. sepEndBy1 :: Alternative m => m a -> m sep -> m [a] -- | skipMany p applies the parser p zero or more -- times, skipping its result. -- --
--   space = skipMany spaceChar
--   
skipMany :: Alternative m => m a -> m () -- | skipSome p applies the parser p one or more -- times, skipping its result. skipSome :: Alternative m => m a -> m () -- | A helper module to parse expressions. It can build a parser given a -- table of operators. module Text.Megaparsec.Expr -- | This data type specifies operators that work on values of type -- a. An operator is either binary infix or unary prefix or -- postfix. A binary operator has also an associated associativity. data Operator m a -- | Non-associative infix InfixN :: (m (a -> a -> a)) -> Operator m a -- | Left-associative infix InfixL :: (m (a -> a -> a)) -> Operator m a -- | Right-associative infix InfixR :: (m (a -> a -> a)) -> Operator m a -- | Prefix Prefix :: (m (a -> a)) -> Operator m a -- | Postfix Postfix :: (m (a -> a)) -> Operator m a -- | makeExprParser term table builds an expression parser for -- terms term with operators from table, taking the -- associativity and precedence specified in table into account. -- -- table is a list of [Operator m a] lists. The list is -- ordered in descending precedence. All operators in one list have the -- same precedence (but may have different associativity). -- -- Prefix and postfix operators of the same precedence associate to the -- left (i.e. if ++ is postfix increment, than -2++ -- equals -1, not -3). -- -- Unary operators of the same precedence can only occur once (i.e. -- --2 is not allowed if - is prefix negate). If you -- need to parse several prefix or postfix operators in a row, (like C -- pointers — **i) you can use this approach: -- --
--   manyUnaryOp = foldr1 (.) <$> some singleUnaryOp
--   
-- -- This is not done by default because in some cases you don't want to -- allow repeating prefix or postfix operators. -- -- makeExprParser takes care of all the complexity involved in -- building an expression parser. Here is an example of an expression -- parser that handles prefix signs, postfix increment and basic -- arithmetic: -- --
--   expr = makeExprParser term table <?> "expression"
--   
--   term = parens expr <|> integer <?> "term"
--   
--   table = [ [ prefix  "-"  negate
--             , prefix  "+"  id ]
--           , [ postfix "++" (+1) ]
--           , [ binary  "*"  (*)
--             , binary  "/"  div  ]
--           , [ binary  "+"  (+)
--             , binary  "-"  (-)  ] ]
--   
--   binary  name f = InfixL  (f <$ symbol name)
--   prefix  name f = Prefix  (f <$ symbol name)
--   postfix name f = Postfix (f <$ symbol name)
--   
makeExprParser :: MonadParsec e s m => m a -> [[Operator m a]] -> m a -- | This module implements permutation parsers. The algorithm is described -- in: Parsing Permutation Phrases, by Arthur Baars, Andres Loh -- and Doaitse Swierstra. Published as a functional pearl at the Haskell -- Workshop 2001. module Text.Megaparsec.Perm -- | The type PermParser s m a denotes a permutation parser that, -- when converted by the makePermParser function, produces -- instance of MonadParsec m that parses s -- stream and returns a value of type a on success. -- -- Normally, a permutation parser is first build with special operators -- like (<||>) and than transformed into a normal parser -- using makePermParser. data PermParser s m a -- | The parser makePermParser perm parses a permutation of parser -- described by perm. For example, suppose we want to parse a -- permutation of: an optional string of a's, the character -- b and an optional c. This can be described by: -- --
--   test = makePermParser $
--            (,,) <$?> ("", some (char 'a'))
--                 <||> char 'b'
--                 <|?> ('_', char 'c')
--   
makePermParser :: MonadParsec e s m => PermParser s m a -> m a -- | The expression f <$$> p creates a fresh permutation -- parser consisting of parser p. The the final result of the -- permutation parser is the function f applied to the return -- value of p. The parser p is not allowed to accept -- empty input — use the optional combinator (<$?>) instead. -- -- If the function f takes more than one parameter, the type -- variable b is instantiated to a functional type which -- combines nicely with the adds parser p to the -- (<||>) combinator. This results in stylized code where a -- permutation parser starts with a combining function f -- followed by the parsers. The function f gets its parameters -- in the order in which the parsers are specified, but actual input can -- be in any order. (<$$>) :: MonadParsec e s m => (a -> b) -> m a -> PermParser s m b infixl 2 <$$> -- | The expression f <$?> (x, p) creates a fresh -- permutation parser consisting of parser p. The final result -- of the permutation parser is the function f applied to the -- return value of p. The parser p is optional — if it -- cannot be applied, the default value x will be used instead. (<$?>) :: MonadParsec e s m => (a -> b) -> (a, m a) -> PermParser s m b infixl 2 <$?> -- | The expression perm <||> p adds parser p to -- the permutation parser perm. The parser p is not -- allowed to accept empty input — use the optional combinator -- (<|?>) instead. Returns a new permutation parser that -- includes p. (<||>) :: MonadParsec e s m => PermParser s m (a -> b) -> m a -> PermParser s m b infixl 1 <||> -- | The expression perm <||> (x, p) adds parser p -- to the permutation parser perm. The parser p is -- optional — if it cannot be applied, the default value x will -- be used instead. Returns a new permutation parser that includes the -- optional parser p. (<|?>) :: MonadParsec e s m => PermParser s m (a -> b) -> (a, m a) -> PermParser s m b infixl 1 <|?> -- | Commonly used character parsers. module Text.Megaparsec.Char -- | Parses a newline character. newline :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses a carriage return character followed by a newline character. -- Returns sequence of characters parsed. crlf :: (MonadParsec e s m, Token s ~ Char) => m String -- | Parses a CRLF (see crlf) or LF (see newline) end of -- line. Returns the sequence of characters parsed. -- --
--   eol = (pure <$> newline) <|> crlf
--   
eol :: (MonadParsec e s m, Token s ~ Char) => m String -- | Parses a tab character. tab :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Skips zero or more white space characters. -- -- See also: skipMany and spaceChar. space :: (MonadParsec e s m, Token s ~ Char) => m () -- | Parses control characters, which are the non-printing characters of -- the Latin-1 subset of Unicode. controlChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses a Unicode space character, and the control characters: tab, -- newline, carriage return, form feed, and vertical tab. spaceChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses an upper-case or title-case alphabetic Unicode character. Title -- case is used by a small number of letter ligatures like the -- single-character form of Lj. upperChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses a lower-case alphabetic Unicode character. lowerChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses alphabetic Unicode characters: lower-case, upper-case and -- title-case letters, plus letters of case-less scripts and modifiers -- letters. letterChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses alphabetic or numeric digit Unicode characters. -- -- Note that numeric digits outside the ASCII range are parsed by this -- parser but not by digitChar. Such digits may be part of -- identifiers but are not used by the printer and reader to represent -- numbers. alphaNumChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses printable Unicode characters: letters, numbers, marks, -- punctuation, symbols and spaces. printChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses an ASCII digit, i.e between “0” and “9”. digitChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses an octal digit, i.e. between “0” and “7”. octDigitChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses a hexadecimal digit, i.e. between “0” and “9”, or “a” and “f”, -- or “A” and “F”. hexDigitChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses Unicode mark characters, for example accents and the like, -- which combine with preceding characters. markChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses Unicode numeric characters, including digits from various -- scripts, Roman numerals, et cetera. numberChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses Unicode punctuation characters, including various kinds of -- connectors, brackets and quotes. punctuationChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses Unicode symbol characters, including mathematical and currency -- symbols. symbolChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses Unicode space and separator characters. separatorChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses a character from the first 128 characters of the Unicode -- character set, corresponding to the ASCII character set. asciiChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses a character from the first 256 characters of the Unicode -- character set, corresponding to the ISO 8859-1 (Latin-1) character -- set. latin1Char :: (MonadParsec e s m, Token s ~ Char) => m Char -- | charCategory cat Parses character in Unicode General Category -- cat, see GeneralCategory. charCategory :: (MonadParsec e s m, Token s ~ Char) => GeneralCategory -> m Char -- | Returns human-readable name of Unicode General Category. categoryName :: GeneralCategory -> String -- | char c parses a single character c. -- --
--   semicolon = char ';'
--   
char :: (MonadParsec e s m, Token s ~ Char) => Char -> m Char -- | The same as char but case-insensitive. This parser returns -- actually parsed character preserving its case. -- --
--   >>> parseTest (char' 'e') "E"
--   'E'
--   
--   >>> parseTest (char' 'e') "G"
--   1:1:
--   unexpected 'G'
--   expecting 'E' or 'e'
--   
char' :: (MonadParsec e s m, Token s ~ Char) => Char -> m Char -- | This parser succeeds for any character. Returns the parsed character. anyChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | oneOf cs succeeds if the current character is in the supplied -- list of characters cs. Returns the parsed character. Note -- that this parser doesn't automatically generate “expected” component -- of error message, so usually you should label it manually with -- label or (<?>). -- -- See also: satisfy. -- --
--   digit = oneOf ['0'..'9'] <?> "digit"
--   
oneOf :: (Foldable f, MonadParsec e s m, Token s ~ Char) => f Char -> m Char -- | The same as oneOf, but case-insensitive. Returns the parsed -- character preserving its case. -- --
--   vowel = oneOf' "aeiou" <?> "vowel"
--   
oneOf' :: (Foldable f, MonadParsec e s m, Token s ~ Char) => f Char -> m Char -- | As the dual of oneOf, noneOf cs succeeds if the -- current character not in the supplied list of characters -- cs. Returns the parsed character. noneOf :: (Foldable f, MonadParsec e s m, Token s ~ Char) => f Char -> m Char -- | The same as noneOf, but case-insensitive. -- --
--   consonant = noneOf' "aeiou" <?> "consonant"
--   
noneOf' :: (Foldable f, MonadParsec e s m, Token s ~ Char) => f Char -> m Char -- | The parser satisfy f succeeds for any character for which the -- supplied function f returns True. Returns the -- character that is actually parsed. -- --
--   digitChar = satisfy isDigit <?> "digit"
--   oneOf cs  = satisfy (`elem` cs)
--   
satisfy :: (MonadParsec e s m, Token s ~ Char) => (Char -> Bool) -> m Char -- | string s parses a sequence of characters given by s. -- Returns the parsed string (i.e. s). -- --
--   divOrMod = string "div" <|> string "mod"
--   
string :: (MonadParsec e s m, Token s ~ Char) => String -> m String -- | The same as string, but case-insensitive. On success returns -- string cased as actually parsed input. -- --
--   >>> parseTest (string' "foobar") "foObAr"
--   "foObAr"
--   
string' :: (MonadParsec e s m, Token s ~ Char) => String -> m String -- | High-level parsers to help you write your lexer. The module doesn't -- impose how you should write your parser, but certain approaches may be -- more elegant than others. Especially important theme is parsing of -- white space, comments, and indentation. -- -- This module is intended to be imported qualified: -- --
--   import qualified Text.Megaparsec.Lexer as L
--   
module Text.Megaparsec.Lexer -- | space spaceChar lineComment blockComment produces parser that -- can parse white space in general. It's expected that you create such a -- parser once and pass it to other functions in this module as needed -- (when you see spaceConsumer in documentation, usually it -- means that something like space is expected there). -- -- spaceChar is used to parse trivial space characters. You can -- use spaceChar from Text.Megaparsec.Char for this purpose -- as well as your own parser (if you don't want to automatically consume -- newlines, for example). -- -- lineComment is used to parse line comments. You can use -- skipLineComment if you don't need anything special. -- -- blockComment is used to parse block (multi-line) comments. -- You can use skipBlockComment if you don't need anything -- special. -- -- Parsing of white space is an important part of any parser. We propose -- a convention where every lexeme parser assumes no spaces before the -- lexeme and consumes all spaces after the lexeme; this is what the -- lexeme combinator does, and so it's enough to wrap every lexeme -- parser with lexeme to achieve this. Note that you'll need to -- call space manually to consume any white space before the first -- lexeme (i.e. at the beginning of the file). space :: MonadParsec e s m => m () -> m () -> m () -> m () -- | This is wrapper for lexemes. Typical usage is to supply first argument -- (parser that consumes white space, probably defined via space) -- and use the resulting function to wrap parsers for every lexeme. -- --
--   lexeme  = L.lexeme spaceConsumer
--   integer = lexeme L.integer
--   
lexeme :: MonadParsec e s m => m () -> m a -> m a -- | This is a helper to parse symbols, i.e. verbatim strings. You pass the -- first argument (parser that consumes white space, probably defined via -- space) and then you can use the resulting function to parse -- strings: -- --
--   symbol    = L.symbol spaceConsumer
--   
--   parens    = between (symbol "(") (symbol ")")
--   braces    = between (symbol "{") (symbol "}")
--   angles    = between (symbol "<") (symbol ">")
--   brackets  = between (symbol "[") (symbol "]")
--   semicolon = symbol ";"
--   comma     = symbol ","
--   colon     = symbol ":"
--   dot       = symbol "."
--   
symbol :: (MonadParsec e s m, Token s ~ Char) => m () -> String -> m String -- | Case-insensitive version of symbol. This may be helpful if -- you're working with case-insensitive languages. symbol' :: (MonadParsec e s m, Token s ~ Char) => m () -> String -> m String -- | Given comment prefix this function returns parser that skips line -- comments. Note that it stops just before newline character but doesn't -- consume the newline. Newline is either supposed to be consumed by -- space parser or picked up manually. skipLineComment :: (MonadParsec e s m, Token s ~ Char) => String -> m () -- | skipBlockComment start end skips non-nested block comment -- starting with start and ending with end. skipBlockComment :: (MonadParsec e s m, Token s ~ Char) => String -> String -> m () -- | skipBlockCommentNested start end skips possibly nested block -- comment starting with start and ending with end. skipBlockCommentNested :: (MonadParsec e s m, Token s ~ Char) => String -> String -> m () -- | Return current indentation level. -- -- The function is a simple shortcut defined as: -- --
--   indentLevel = sourceColumn <$> getPosition
--   
indentLevel :: MonadParsec e s m => m Pos -- | Fail reporting incorrect indentation error. The error has attached -- information: -- -- incorrectIndent :: MonadParsec e s m => Ordering -> Pos -> Pos -> m a -- | indentGuard spaceConsumer ord ref first consumes all white -- space (indentation) with spaceConsumer parser, then it checks -- column position. Ordering between current indentation level and -- reference indentation level ref should be ord, -- otherwise the parser fails. On success current column position is -- returned. -- -- When you want to parse block of indentation first run this parser with -- arguments like indentGuard spaceConsumer GT (unsafePos 1) — -- this will make sure you have some indentation. Use returned value to -- check indentation on every subsequent line according to syntax of your -- language. indentGuard :: MonadParsec e s m => m () -> Ordering -> Pos -> m Pos -- | Parse non-indented construction. This ensures that there is no -- indentation before actual data. Useful, for example, as a wrapper for -- top-level function definitions. nonIndented :: MonadParsec e s m => m () -> m a -> m a -- | The data type represents available behaviors for parsing of indented -- tokens. This is used in indentBlock, which see. data IndentOpt m a b -- | Parse no indented tokens, just return the value IndentNone :: a -> IndentOpt m a b -- | Parse many indented tokens (possibly zero), use given indentation -- level (if Nothing, use level of the first indented token); the -- second argument tells how to get final result, and third argument -- describes how to parse indented token IndentMany :: (Maybe Pos) -> ([b] -> m a) -> (m b) -> IndentOpt m a b -- | Just like IndentMany, but requires at least one indented token -- to be present IndentSome :: (Maybe Pos) -> ([b] -> m a) -> (m b) -> IndentOpt m a b -- | Parse a “reference” token and a number of other tokens that have -- greater (but the same) level of indentation than that of “reference” -- token. Reference token can influence parsing, see IndentOpt for -- more information. -- -- Tokens must not consume newlines after them. On the other hand, -- the first argument of this function must consume newlines among -- other white space characters. indentBlock :: (MonadParsec e s m, Token s ~ Char) => m () -> m (IndentOpt m a b) -> m a -- | Create a parser that supports line-folding. The first argument is used -- to consume white space between components of line fold, thus it -- must consume newlines in order to work properly. The second -- argument is a callback that receives custom space-consuming parser as -- argument. This parser should be used after separate components of line -- fold that can be put on different lines. -- -- An example should clarify the usage pattern: -- --
--   sc = L.space (void spaceChar) empty empty
--   
--   myFold = L.lineFold sc $ \sc' -> do
--     L.symbol sc' "foo"
--     L.symbol sc' "bar"
--     L.symbol sc  "baz" -- for the last symbol we use normal space consumer
--   
lineFold :: MonadParsec e s m => m () -> (m () -> m a) -> m a -- | The lexeme parser parses a single literal character without quotes. -- Purpose of this parser is to help with parsing of conventional escape -- sequences. It's your responsibility to take care of character literal -- syntax in your language (by surrounding it with single quotes or -- similar). -- -- The literal character is parsed according to the grammar rules defined -- in the Haskell report. -- -- Note that you can use this parser as a building block to parse various -- string literals: -- --
--   stringLiteral = char '"' >> manyTill L.charLiteral (char '"')
--   
charLiteral :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parse an integer without sign in decimal representation (according to -- format of integer literals described in Haskell report). -- -- If you need to parse signed integers, see signed combinator. integer :: (MonadParsec e s m, Token s ~ Char) => m Integer -- | The same as integer, but integer is labeled with -- “integer” label, while this parser is labeled with “decimal integer”. decimal :: (MonadParsec e s m, Token s ~ Char) => m Integer -- | Parse an integer in hexadecimal representation. Representation of -- hexadecimal number is expected to be according to Haskell report -- except for the fact that this parser doesn't parse “0x” or “0X” -- prefix. It is responsibility of the programmer to parse correct prefix -- before parsing the number itself. -- -- For example you can make it conform to Haskell report like this: -- --
--   hexadecimal = char '0' >> char' 'x' >> L.hexadecimal
--   
hexadecimal :: (MonadParsec e s m, Token s ~ Char) => m Integer -- | Parse an integer in octal representation. Representation of octal -- number is expected to be according to Haskell report except for the -- fact that this parser doesn't parse “0o” or “0O” prefix. It is -- responsibility of the programmer to parse correct prefix before -- parsing the number itself. octal :: (MonadParsec e s m, Token s ~ Char) => m Integer -- | Parse floating point value as Scientific number. -- Scientific is great for parsing of arbitrary precision numbers -- coming from an untrusted source. See documentation in -- Data.Scientific for more information. Representation of -- floating point value is expected to be according to Haskell report. -- -- This function does not parse sign, if you need to parse signed -- numbers, see signed. scientific :: (MonadParsec e s m, Token s ~ Char) => m Scientific -- | Parse floating point number without sign. This is a simple shortcut -- defined as: -- --
--   float = toRealFloat <$> scientific
--   
float :: (MonadParsec e s m, Token s ~ Char) => m Double -- | Parse a number: either integer or floating point. The parser can -- handle overlapping grammars graciously. Use functions like -- floatingOrInteger from Data.Scientific to test and -- extract integer or real values. number :: (MonadParsec e s m, Token s ~ Char) => m Scientific -- | signed space p parser parses optional sign, then if there is -- a sign it will consume optional white space (using space -- parser), then it runs parser p which should return a number. -- Sign of the number is changed according to previously parsed sign. -- -- For example, to parse signed integer you can write: -- --
--   lexeme        = L.lexeme spaceConsumer
--   integer       = lexeme L.integer
--   signedInteger = L.signed spaceConsumer integer
--   
signed :: (MonadParsec e s m, Token s ~ Char, Num a) => m () -> m a -> m a -- | This module includes everything you need to get started writing a -- parser. If you are new to Megaparsec and don't know where to begin, -- take a look at our tutorials -- https://mrkkrp.github.io/megaparsec/tutorials.html. -- -- By default this module is set up to parse character data. If you'd -- like to parse the result of your own tokenizer you should start with -- the following imports: -- --
--   import Text.Megaparsec.Prim
--   import Text.Megaparsec.Combinator
--   
-- -- Then you can implement your own version of satisfy on top of -- the token primitive. -- -- Typical import section looks like this: -- --
--   import Text.Megaparsec
--   import Text.Megaparsec.String
--   -- import Text.Megaparsec.ByteString
--   -- import Text.Megaparsec.ByteString.Lazy
--   -- import Text.Megaparsec.Text
--   -- import Text.Megaparsec.Text.Lazy
--   
-- -- As you can see the second import depends on data type you want to use -- as input stream. It just defines useful type-synonym Parser. -- -- Megaparsec is capable of a lot. Apart from this standard functionality -- you can parse permutation phrases with Text.Megaparsec.Perm, -- expressions with Text.Megaparsec.Expr, and even entire -- languages with Text.Megaparsec.Lexer. These modules should be -- imported explicitly along with the two modules mentioned above. module Text.Megaparsec -- | Parsec is non-transformer variant of more general -- ParsecT monad transformer. type Parsec e s = ParsecT e s Identity -- | ParsecT e s m a is a parser with custom data component of -- error e, stream type s, underlying monad m -- and return type a. data ParsecT e s m a -- | runParser p file input runs parser p on the input -- list of tokens input, obtained from source file. The -- file is only used in error messages and may be the empty -- string. Returns either a ParseError (Left) or a value of -- type a (Right). -- --
--   parseFromFile p file = runParser p file <$> readFile file
--   
runParser :: Parsec e s a -> String -> s -> Either (ParseError (Token s) e) a -- | The function is similar to runParser with the difference that -- it accepts and returns parser state. This allows to specify arbitrary -- textual position at the beginning of parsing, for example. This is the -- most general way to run a parser over the Identity monad. runParser' :: Parsec e s a -> State s -> (State s, Either (ParseError (Token s) e) a) -- | runParserT p file input runs parser p on the input -- list of tokens input, obtained from source file. The -- file is only used in error messages and may be the empty -- string. Returns a computation in the underlying monad m that -- returns either a ParseError (Left) or a value of type -- a (Right). runParserT :: Monad m => ParsecT e s m a -> String -> s -> m (Either (ParseError (Token s) e) a) -- | This function is similar to runParserT, but like -- runParser' it accepts and returns parser state. This is thus -- the most general way to run a parser. runParserT' :: Monad m => ParsecT e s m a -> State s -> m (State s, Either (ParseError (Token s) e) a) -- | parse p file input runs parser p over -- Identity (see runParserT if you're using the -- ParsecT monad transformer; parse itself is just a -- synonym for runParser). It returns either a ParseError -- (Left) or a value of type a (Right). -- parseErrorPretty can be used to turn ParseError into the -- string representation of the error message. See -- Text.Megaparsec.Error if you need to do more advanced error -- analysis. -- --
--   main = case (parse numbers "" "11,2,43") of
--            Left err -> putStr (parseErrorPretty err)
--            Right xs -> print (sum xs)
--   
--   numbers = integer `sepBy` char ','
--   
parse :: Parsec e s a -> String -> s -> Either (ParseError (Token s) e) a -- | parseMaybe p input runs parser p on input -- and returns result inside Just on success and Nothing on -- failure. This function also parses eof, so if the parser -- doesn't consume all of its input, it will fail. -- -- The function is supposed to be useful for lightweight parsing, where -- error messages (and thus file name) are not important and entire input -- should be parsed. For example it can be used when parsing of single -- number according to specification of its format is desired. parseMaybe :: (ErrorComponent e, Stream s) => Parsec e s a -> s -> Maybe a -- | The expression parseTest p input applies a parser p -- against input input and prints the result to stdout. Useful -- for testing. parseTest :: (ShowErrorComponent e, Ord (Token s), ShowToken (Token s), Show a) => Parsec e s a -> s -> IO () -- | An associative binary operation (<|>) :: Alternative f => forall a. f a -> f a -> f a -- | Zero or more. many :: Alternative f => forall a. f a -> f [a] -- | One or more. some :: Alternative f => forall a. f a -> f [a] -- | One or none. optional :: Alternative f => f a -> f (Maybe a) -- | The parser unexpected item always fails with an error message -- telling about unexpected item item without consuming any -- input. unexpected :: MonadParsec e s m => ErrorItem (Token s) -> m a -- | The most general way to stop parsing and report ParseError. -- -- unexpected is defined in terms of this function: -- --
--   unexpected item = failure (Set.singleton item) Set.empty Set.empty
--   
failure :: MonadParsec e s m => Set (ErrorItem (Token s)) -> Set (ErrorItem (Token s)) -> Set e -> m a -- | A synonym for label in form of an operator. () :: MonadParsec e s m => m a -> String -> m a infix 0 -- | The parser label name p behaves as parser p, but -- whenever the parser p fails without consuming any -- input, it replaces names of “expected” tokens with the name -- name. label :: MonadParsec e s m => String -> m a -> m a -- | hidden p behaves just like parser p, but it doesn't -- show any “expected” tokens in error message when p fails. hidden :: MonadParsec e s m => m a -> m a -- | The parser try p behaves like parser p, except that -- it pretends that it hasn't consumed any input when an error occurs. -- -- This combinator is used whenever arbitrary look ahead is needed. Since -- it pretends that it hasn't consumed any input when p fails, -- the (<|>) combinator will try its second alternative even -- when the first parser failed while consuming input. -- -- For example, here is a parser that is supposed to parse word “let” or -- “lexical”: -- --
--   >>> parseTest (string "let" <|> string "lexical") "lexical"
--   1:1:
--   unexpected "lex"
--   expecting "let"
--   
-- -- What happens here? First parser consumes “le” and fails (because it -- doesn't see a “t”). The second parser, however, isn't tried, since the -- first parser has already consumed some input! try fixes this -- behavior and allows backtracking to work: -- --
--   >>> parseTest (try (string "let") <|> string "lexical") "lexical"
--   "lexical"
--   
-- -- try also improves error messages in case of overlapping -- alternatives, because Megaparsec's hint system can be used: -- --
--   >>> parseTest (try (string "let") <|> string "lexical") "le"
--   1:1:
--   unexpected "le"
--   expecting "let" or "lexical"
--   
-- -- Please note that as of Megaparsec 4.4.0, string backtracks -- automatically (see tokens), so it does not need try. -- However, the examples above demonstrate the idea behind try so -- well that it was decided to keep them. try :: MonadParsec e s m => m a -> m a -- | lookAhead p parses p without consuming any input. -- -- If p fails and consumes some input, so does -- lookAhead. Combine with try if this is undesirable. lookAhead :: MonadParsec e s m => m a -> m a -- | notFollowedBy p only succeeds when parser p fails. -- This parser does not consume any input and can be used to implement -- the “longest match” rule. notFollowedBy :: MonadParsec e s m => m a -> m () -- | withRecovery r p allows continue parsing even if parser -- p fails. In this case r is called with actual -- ParseError as its argument. Typical usage is to return value -- signifying failure to parse this particular object and to consume some -- part of input up to start of next object. -- -- Note that if r fails, original error message is reported as -- if without withRecovery. In no way recovering parser r -- can influence error messages. withRecovery :: MonadParsec e s m => (ParseError (Token s) e -> m a) -> m a -> m a -- | This parser only succeeds at the end of the input. eof :: MonadParsec e s m => m () -- | The parser token test mrep accepts a token t with -- result x when the function test t returns -- Right x. mrep may provide representation of -- the token to report in error messages when input stream in empty. -- -- This is the most primitive combinator for accepting tokens. For -- example, the satisfy parser is implemented as: -- --
--   satisfy f = token testChar Nothing
--     where
--       testChar x =
--         if f x
--           then Right x
--           else Left (Set.singleton (Tokens (x:|[])), Set.empty, Set.empty)
--   
token :: MonadParsec e s m => (Token s -> Either (Set (ErrorItem (Token s)), Set (ErrorItem (Token s)), Set e) a) -> Maybe (Token s) -> m a -- | The parser tokens test parses list of tokens and returns it. -- Supplied predicate test is used to check equality of given -- and parsed tokens. -- -- This can be used for example to write string: -- --
--   string = tokens (==)
--   
-- -- Note that beginning from Megaparsec 4.4.0, this is an -- auto-backtracking primitive, which means that if it fails, it never -- consumes any input. This is done to make its consumption model match -- how error messages for this primitive are reported (which becomes an -- important thing as user gets more control with primitives like -- withRecovery): -- --
--   >>> parseTest (string "abc") "abd"
--   1:1:
--   unexpected "abd"
--   expecting "abc"
--   
-- -- This means, in particular, that it's no longer necessary to use -- try with tokens-based parsers, such as string and -- string'. This feature does not affect performance in any -- way. tokens :: MonadParsec e s m => (Token s -> Token s -> Bool) -> [Token s] -> m [Token s] -- | between open close p parses open, followed by -- p and close. Returns the value returned by -- p. -- --
--   braces = between (symbol "{") (symbol "}")
--   
between :: Applicative m => m open -> m close -> m a -> m a -- | choice ps tries to apply the parsers in the list ps -- in order, until one of them succeeds. Returns the value of the -- succeeding parser. choice :: (Foldable f, Alternative m) => f (m a) -> m a -- | count n p parses n occurrences of p. If -- n is smaller or equal to zero, the parser equals to -- return []. Returns a list of n values. count :: Applicative m => Int -> m a -> m [a] -- | count' m n p parses from m to n occurrences -- of p. If n is not positive or m > n, the -- parser equals to return []. Returns a list of parsed values. -- -- Please note that m may be negative, in this case -- effect is the same as if it were equal to zero. count' :: Alternative m => Int -> Int -> m a -> m [a] -- | Combine two alternatives. eitherP :: Alternative m => m a -> m b -> m (Either a b) -- | endBy p sep parses zero or more occurrences of -- p, separated and ended by sep. Returns a list of -- values returned by p. -- --
--   cStatements = cStatement `endBy` semicolon
--   
endBy :: Alternative m => m a -> m sep -> m [a] -- | endBy1 p sep parses one or more occurrences of -- p, separated and ended by sep. Returns a list of -- values returned by p. endBy1 :: Alternative m => m a -> m sep -> m [a] -- | manyTill p end applies parser p zero or more -- times until parser end succeeds. Returns the list of values -- returned by p. This parser can be used to scan comments: -- --
--   simpleComment = string "<!--" >> manyTill anyChar (string "-->")
--   
manyTill :: Alternative m => m a -> m end -> m [a] -- | someTill p end works similarly to manyTill p end, -- but p should succeed at least once. someTill :: Alternative m => m a -> m end -> m [a] -- | option x p tries to apply parser p. If p -- fails without consuming input, it returns the value x, -- otherwise the value returned by p. -- --
--   priority = option 0 (digitToInt <$> digitChar)
--   
option :: Alternative m => a -> m a -> m a -- | sepBy p sep parses zero or more occurrences of -- p, separated by sep. Returns a list of values -- returned by p. -- --
--   commaSep p = p `sepBy` comma
--   
sepBy :: Alternative m => m a -> m sep -> m [a] -- | sepBy1 p sep parses one or more occurrences of -- p, separated by sep. Returns a list of values -- returned by p. sepBy1 :: Alternative m => m a -> m sep -> m [a] -- | sepEndBy p sep parses zero or more occurrences of -- p, separated and optionally ended by sep. Returns a -- list of values returned by p. sepEndBy :: Alternative m => m a -> m sep -> m [a] -- | sepEndBy1 p sep parses one or more occurrences of -- p, separated and optionally ended by sep. Returns a -- list of values returned by p. sepEndBy1 :: Alternative m => m a -> m sep -> m [a] -- | skipMany p applies the parser p zero or more -- times, skipping its result. -- --
--   space = skipMany spaceChar
--   
skipMany :: Alternative m => m a -> m () -- | skipSome p applies the parser p one or more -- times, skipping its result. skipSome :: Alternative m => m a -> m () -- | Parses a newline character. newline :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses a carriage return character followed by a newline character. -- Returns sequence of characters parsed. crlf :: (MonadParsec e s m, Token s ~ Char) => m String -- | Parses a CRLF (see crlf) or LF (see newline) end of -- line. Returns the sequence of characters parsed. -- --
--   eol = (pure <$> newline) <|> crlf
--   
eol :: (MonadParsec e s m, Token s ~ Char) => m String -- | Parses a tab character. tab :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Skips zero or more white space characters. -- -- See also: skipMany and spaceChar. space :: (MonadParsec e s m, Token s ~ Char) => m () -- | Parses control characters, which are the non-printing characters of -- the Latin-1 subset of Unicode. controlChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses a Unicode space character, and the control characters: tab, -- newline, carriage return, form feed, and vertical tab. spaceChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses an upper-case or title-case alphabetic Unicode character. Title -- case is used by a small number of letter ligatures like the -- single-character form of Lj. upperChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses a lower-case alphabetic Unicode character. lowerChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses alphabetic Unicode characters: lower-case, upper-case and -- title-case letters, plus letters of case-less scripts and modifiers -- letters. letterChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses alphabetic or numeric digit Unicode characters. -- -- Note that numeric digits outside the ASCII range are parsed by this -- parser but not by digitChar. Such digits may be part of -- identifiers but are not used by the printer and reader to represent -- numbers. alphaNumChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses printable Unicode characters: letters, numbers, marks, -- punctuation, symbols and spaces. printChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses an ASCII digit, i.e between “0” and “9”. digitChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses an octal digit, i.e. between “0” and “7”. octDigitChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses a hexadecimal digit, i.e. between “0” and “9”, or “a” and “f”, -- or “A” and “F”. hexDigitChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses Unicode mark characters, for example accents and the like, -- which combine with preceding characters. markChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses Unicode numeric characters, including digits from various -- scripts, Roman numerals, et cetera. numberChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses Unicode punctuation characters, including various kinds of -- connectors, brackets and quotes. punctuationChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses Unicode symbol characters, including mathematical and currency -- symbols. symbolChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses Unicode space and separator characters. separatorChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses a character from the first 128 characters of the Unicode -- character set, corresponding to the ASCII character set. asciiChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parses a character from the first 256 characters of the Unicode -- character set, corresponding to the ISO 8859-1 (Latin-1) character -- set. latin1Char :: (MonadParsec e s m, Token s ~ Char) => m Char -- | charCategory cat Parses character in Unicode General Category -- cat, see GeneralCategory. charCategory :: (MonadParsec e s m, Token s ~ Char) => GeneralCategory -> m Char -- | char c parses a single character c. -- --
--   semicolon = char ';'
--   
char :: (MonadParsec e s m, Token s ~ Char) => Char -> m Char -- | The same as char but case-insensitive. This parser returns -- actually parsed character preserving its case. -- --
--   >>> parseTest (char' 'e') "E"
--   'E'
--   
--   >>> parseTest (char' 'e') "G"
--   1:1:
--   unexpected 'G'
--   expecting 'E' or 'e'
--   
char' :: (MonadParsec e s m, Token s ~ Char) => Char -> m Char -- | This parser succeeds for any character. Returns the parsed character. anyChar :: (MonadParsec e s m, Token s ~ Char) => m Char -- | oneOf cs succeeds if the current character is in the supplied -- list of characters cs. Returns the parsed character. Note -- that this parser doesn't automatically generate “expected” component -- of error message, so usually you should label it manually with -- label or (<?>). -- -- See also: satisfy. -- --
--   digit = oneOf ['0'..'9'] <?> "digit"
--   
oneOf :: (Foldable f, MonadParsec e s m, Token s ~ Char) => f Char -> m Char -- | The same as oneOf, but case-insensitive. Returns the parsed -- character preserving its case. -- --
--   vowel = oneOf' "aeiou" <?> "vowel"
--   
oneOf' :: (Foldable f, MonadParsec e s m, Token s ~ Char) => f Char -> m Char -- | As the dual of oneOf, noneOf cs succeeds if the -- current character not in the supplied list of characters -- cs. Returns the parsed character. noneOf :: (Foldable f, MonadParsec e s m, Token s ~ Char) => f Char -> m Char -- | The same as noneOf, but case-insensitive. -- --
--   consonant = noneOf' "aeiou" <?> "consonant"
--   
noneOf' :: (Foldable f, MonadParsec e s m, Token s ~ Char) => f Char -> m Char -- | The parser satisfy f succeeds for any character for which the -- supplied function f returns True. Returns the -- character that is actually parsed. -- --
--   digitChar = satisfy isDigit <?> "digit"
--   oneOf cs  = satisfy (`elem` cs)
--   
satisfy :: (MonadParsec e s m, Token s ~ Char) => (Char -> Bool) -> m Char -- | string s parses a sequence of characters given by s. -- Returns the parsed string (i.e. s). -- --
--   divOrMod = string "div" <|> string "mod"
--   
string :: (MonadParsec e s m, Token s ~ Char) => String -> m String -- | The same as string, but case-insensitive. On success returns -- string cased as actually parsed input. -- --
--   >>> parseTest (string' "foobar") "foObAr"
--   "foObAr"
--   
string' :: (MonadParsec e s m, Token s ~ Char) => String -> m String -- | Positive integer that is used to represent line number, column number, -- and similar things like indentation level. Semigroup instance -- can be used to safely and purely add Poses together. data Pos -- | Construction of Pos from an instance of Integral. The -- function throws InvalidPosException when given non-positive -- argument. Note that the function is polymorphic with respect to -- MonadThrow m, so you can get result inside of -- Maybe, for example. mkPos :: (Integral a, MonadThrow m) => a -> m Pos -- | Extract Word from Pos. unPos :: Pos -> Word -- | Dangerous construction of Pos. Use when you know for sure that -- argument is positive. unsafePos :: Word -> Pos -- | The exception is thrown by mkPos when its argument is not a -- positive number. data InvalidPosException InvalidPosException :: InvalidPosException -- | The data type SourcePos represents source positions. It -- contains the name of the source file, a line number, and a column -- number. Source line and column positions change intensively during -- parsing, so we need to make them strict to avoid memory leaks. data SourcePos SourcePos :: FilePath -> !Pos -> !Pos -> SourcePos -- | Name of source file [sourceName] :: SourcePos -> FilePath -- | Line number [sourceLine] :: SourcePos -> !Pos -- | Column number [sourceColumn] :: SourcePos -> !Pos -- | Construct initial position (line 1, column 1) given name of source -- file. initialPos :: String -> SourcePos -- | Pretty-print a SourcePos. sourcePosPretty :: SourcePos -> String -- | Data type that is used to represent “unexpected/expected” items in -- parse error. The data type is parametrized over token type t. data ErrorItem t -- | Non-empty stream of tokens Tokens :: (NonEmpty t) -> ErrorItem t -- | Label (cannot be empty) Label :: (NonEmpty Char) -> ErrorItem t -- | End of input EndOfInput :: ErrorItem t -- | The type class defines how to represent information about various -- exceptional situations. Data types that are used as custom data -- component in ParseError must be instances of this type class. class Ord e => ErrorComponent e -- | Represent message passed to fail in parser monad. representFail :: ErrorComponent e => String -> e -- | Represent information about incorrect indentation. representIndentation :: ErrorComponent e => Ordering -> Pos -> Pos -> e -- | “Default error component”. This in our instance of -- ErrorComponent provided out-of-box. data Dec -- | fail has been used in parser monad DecFail :: String -> Dec -- | Incorrect indentation error: desired ordering between reference level -- and actual level, reference indentation level, actual indentation -- level DecIndentation :: Ordering -> Pos -> Pos -> Dec -- | The data type ParseError represents parse errors. It provides -- the stack of source positions, set of expected and unexpected tokens -- as well as set of custom associated data. The data type is -- parametrized over token type t and custom data e. -- -- Note that stack of source positions contains current position as its -- head, and the rest of positions allows to track full sequence of -- include files with topmost source file at the end of the list. -- -- Semigroup (or Monoid) instance of the data type allows -- to merge parse errors from different branches of parsing. When merging -- two ParseErrors, longest match is preferred; if positions are -- the same, custom data sets and collections of message items are -- combined. data ParseError t e ParseError :: NonEmpty SourcePos -> Set (ErrorItem t) -> Set (ErrorItem t) -> Set e -> ParseError t e -- | Stack of source positions [errorPos] :: ParseError t e -> NonEmpty SourcePos -- | Unexpected items [errorUnexpected] :: ParseError t e -> Set (ErrorItem t) -- | Expected items [errorExpected] :: ParseError t e -> Set (ErrorItem t) -- | Associated data, if any [errorCustom] :: ParseError t e -> Set e -- | Type class ShowToken includes methods that allow to -- pretty-print single token as well as stream of tokens. This is used -- for rendering of error messages. class ShowToken a -- | Pretty-print non-empty stream of tokens. This function is also used to -- print single tokens (represented as singleton lists). showTokens :: ShowToken a => NonEmpty a -> String -- | The type class defines how to print custom data component of -- ParseError. class Ord a => ShowErrorComponent a -- | Pretty-print custom data component of ParseError. showErrorComponent :: ShowErrorComponent a => a -> String -- | Pretty-print ParseError. Note that rendered String -- always ends with a newline. parseErrorPretty :: (Ord t, ShowToken t, ShowErrorComponent e) => ParseError t e -> String -- | An instance of Stream s has stream type s. Token -- type is determined by the stream and can be found via Token -- type function. class Ord (Token s) => Stream s where type Token s :: * where { type family Token s :: *; } -- | Get next token from the stream. If the stream is empty, return -- Nothing. uncons :: Stream s => s -> Maybe (Token s, s) -- | Update position in stream given tab width, current position, and -- current token. The result is a tuple where the first element will be -- used to report parse errors for current token, while the second -- element is the incremented position that will be stored in parser's -- state. -- -- When you work with streams where elements do not contain information -- about their position in input, result is usually consists of the third -- argument unchanged and incremented position calculated with respect to -- current token. This is how default instances of Stream work -- (they use defaultUpdatePos, which may be a good starting point -- for your own position-advancing function). -- -- When you wish to deal with stream of tokens where every token “knows” -- its start and end position in input (for example, you have produced -- the stream with Happy/Alex), then the best strategy is to use the -- start position as actual element position and provide the end position -- of the token as incremented one. updatePos :: Stream s => Proxy s -> Pos -> SourcePos -> Token s -> (SourcePos, SourcePos) -- | This is Megaparsec's state, it's parametrized over stream type -- s. data State s State :: s -> NonEmpty SourcePos -> Pos -> State s [stateInput] :: State s -> s [statePos] :: State s -> NonEmpty SourcePos [stateTabWidth] :: State s -> Pos -- | Return the current input. getInput :: MonadParsec e s m => m s -- | setInput input continues parsing with input. The -- getInput and setInput functions can for example be used -- to deal with include files. setInput :: MonadParsec e s m => s -> m () -- | Return the current source position. -- -- See also: setPosition, pushPosition, popPosition, -- and SourcePos. getPosition :: MonadParsec e s m => m SourcePos -- | setPosition pos sets the current source position to -- pos. -- -- See also: getPosition, pushPosition, popPosition, -- and SourcePos. setPosition :: MonadParsec e s m => SourcePos -> m () -- | Push given position into stack of positions and continue parsing -- working with this position. Useful for working with include files and -- the like. -- -- See also: getPosition, setPosition, popPosition, -- and SourcePos. pushPosition :: MonadParsec e s m => SourcePos -> m () -- | Pop a position from stack of positions unless it only contains one -- element (in that case stack of positions remains the same). This is -- how to return to previous source file after pushPosition. -- -- See also: getPosition, setPosition, pushPosition, -- and SourcePos. popPosition :: MonadParsec e s m => m () -- | Return tab width. Default tab width is equal to -- defaultTabWidth. You can set different tab width with help of -- setTabWidth. getTabWidth :: MonadParsec e s m => m Pos -- | Set tab width. If argument of the function is not positive number, -- defaultTabWidth will be used. setTabWidth :: MonadParsec e s m => Pos -> m () -- | Returns the full parser state as a State record. getParserState :: MonadParsec e s m => m (State s) -- | setParserState st set the full parser state to st. setParserState :: MonadParsec e s m => State s -> m () -- | updateParserState f applies function f to the parser -- state. updateParserState :: MonadParsec e s m => (State s -> State s) -> m ()