{      !"#$%&'()*+,-./0123456789:;<=>?@ABCDEFGHIJKLMNOPQRSTUVWXYZ[\]^_`abcdefghijklmnopqrstuvwxyz{|}~ # 2015 2016 Megaparsec contributorsFreeBSD"Mark Karpov <markkarpov@opmbx.org> experimentalportableNone05IL 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.Name of source file Line number Column number The exception is thrown by  - when its argument is not a positive number. sPositive integer that is used to represent line number, column number, and similar things like indentation level. 0 instance can be used to safely and purely add   es together. Construction of   from an instance of . The function throws  Z when given non-positive argument. Note that the function is polymorphic with respect to  m#, so you can get result inside of , for example. Dangerous construction of  8. Use when you know for sure that argument is positive.Extract  from  .IConstruct initial position (line 1, column 1) given name of source file.Pretty-print a .4Update 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.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.   Tab widthCurrent position Current token(Actual position and incremented position      # 2015 2016 Megaparsec contributorsFreeBSD"Mark Karpov <markkarpov@opmbx.org> experimentalportableNone059:;'>The type class defines how to print custom data component of +.(&Pretty-print custom data component of +.) Type class ) includes methods that allow to pretty-print single token as well as stream of tokens. This is used for rendering of error messages.*}Pretty-print non-empty stream of tokens. This function is also used to print single tokens (represented as singleton lists).+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. (or p) instance of the data type allows to merge parse errors from different branches of parsing. When merging two +zs, longest match is preferred; if positions are the same, custom data sets and collections of message items are combined.-Stack of source positions.Unexpected items/Expected items0Associated data, if any13 Default error component . This in our instance of 4 provided out-of-box.2 has been used in parser monad3Incorrect indentation error: desired ordering between reference level and actual level, reference indentation level, actual indentation level4The type class defines how to represent information about various exceptional situations. Data types that are used as custom data component in +& must be instances of this type class.5Represent message passed to  in parser monad.62Represent information about incorrect indentation.7Data type that is used to represent unexpected/expected  items in parse error. The data type is parametrized over token type t.8Non-empty stream of tokens9Label (cannot be empty): End of inputMerge two error data structures into one joining their collections of message items and preferring longest match. In other words, earlier error message is discarded. This may seem counter-intuitive, but ~ is only used to merge error messages of alternative branches of parsing and in this case longest match should be preferred.stringPretty s) returns pretty representation of string s>. This is used when printing string tokens in error messages. charPretty chA returns user-friendly string representation of given character ch', suitable for using in error messages.; Pretty-print +. Note that rendered   always ends with a newline.<'Pretty-print stack of source positions. DTransforms list of error messages into their textual representation. wPrint a pretty list where items are separated with commas and the word or  according to rules of English punctuation.%'()*+,-./0123456789:;Parse error to renderResult of rendering< Prefix to prependCollection of messagesResult of rendering =>?@ABCDEF'()*+,-./0123456789:;<789:456123+,-./0)*'(;<'()*+,-./0123456789:;<  =>?@ABCDEFp 2015 2016 Megaparsec contributors 2007 Paolo Martini 1999 2001 Daan LeijenFreeBSD"Mark Karpov <markkarpov@opmbx.org> experimental non-portableNone059:;<=?DILORT7W8Type class describing parsers independent of input type.X0The most general way to stop parsing and report +.p& is defined in terms of this function: Bunexpected item = failure (Set.singleton item) Set.empty Set.emptyY The parser  label name p behaves as parser p, but whenever the parser p fails without consuming any input8, it replaces names of expected  tokens with the name name.Zhidden p behaves just like parser pC, but it doesn't show any expected  tokens in error message when p fails.[ The parser try p behaves like parser pR, 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 (f) combinator will try its second alternative even when the first parser failed while consuming input.QFor example, here is a parser that is supposed to parse word let  or lexical :7parseTest (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! try6 fixes this behavior and allows backtracking to work:=parseTest (try (string "let") <|> string "lexical") "lexical" "lexical"tryq also improves error messages in case of overlapping alternatives, because Megaparsec's hint system can be used:8parseTest (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 a), so it does not need [;. However, the examples above demonstrate the idea behind [+ so well that it was decided to keep them.\ lookAhead p parses p without consuming any input.If p( fails and consumes some input, so does  lookAhead. Combine with [ if this is undesirable.]notFollowedBy p only succeeds when parser pg fails. This parser does not consume any input and can be used to implement the longest match  rule.^withRecovery r p( allows continue parsing even if parser p fails. In this case r is called with actual + 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 ^. In no way recovering parser r can influence error messages._2This parser only succeeds at the end of the input.` The parser token test mrep accepts a token t with result x when the function test t returns   x. mrepb may provide representation of the token to report in error messages when input stream in empty.NThis is the most primitive combinator for accepting tokens. For example, the   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)a The parser  tokens test; parses list of tokens and returns it. Supplied predicate test7 is used to check equality of given and parsed tokens.&This can be used for example to write  : string = tokens (==)GNote 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 ^):parseTest (string "abc") "abd"1:1:unexpected "abd"expecting "abc"@This means, in particular, that it's no longer necessary to use [ with a-based parsers, such as   and  . This feature does not affect performance in any way.b#Returns the full parser state as a j record.cupdateParserState f applies function f to the parser state.dParsecT e s m a1 is a parser with custom data component of error e, stream type s, underlying monad m and return type a.eParsec, is non-transformer variant of more general d monad transformer.fAn instance of Stream s has stream type s?. Token type is determined by the stream and can be found via g type function.gType of token in stream.h@Get next token from the stream. If the stream is empty, return  .iUpdate 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 f work (they use P, which may be a good starting point for your own position-advancing function).7When 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.6 represent collection of strings to be included into  ParserError as expected  message items when a parser fails without consuming input right after successful parser that produced the hints.)For example, without hints you could get:'parseTest (many (char 'r') <* eof) "ra"1:2:unexpected 'a'expecting end of input7We're getting better error messages with help of hints:'parseTest (many (char 'r') <* eof) "ra"1:2:unexpected 'a'expecting 'r' or end of inputEThis data structure represents an aspect of result of parser's work. See also: , .Parser succeeded Parser failedEThis data structure represents an aspect of result of parser's work. See also: , .&Some part of input stream was consumedNo input was consumedAll information available after parsing. This includes consumption of input, success (with returned value) or failure (with parse error), and parser state at the end of parsing. See also: , .j?This is Megaparsec's state, it's parametrized over stream type s.Convert + record into .withHints hs c makes error  continuation c use given hints hs.)Note that if resulting continuation gets +\ that has only custom data in it (no unexpected  or expected  items), hints are ignored. accHints hs c9 results in OK  continuation that will add given hints hs, to third argument of original continuation c.7Replace most recent group of hints (if any) with given 7 (or delete it if   is given). This is used in Y primitive.Low-level creation of the d type.tFrom two states, return the one with greater textual position. If the positions are equal, prefer the latter state.oA synonym for Y in form of an operator.p The parser unexpected itemC always fails with an error message telling about unexpected item item without consuming any input.-Make a singleton non-empty list from a value.qReturn the current input.rsetInput input continues parsing with input. The q and r> functions can for example be used to deal with include files.s#Return the current source position. See also: t, u, v, and .tsetPosition pos% sets the current source position to pos. See also: s, u, v, and .uPush given position into stack of positions and continue parsing working with this position. Useful for working with include files and the like. See also: s, t, v, and .vPop 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 u. See also: s, t, u, and .w0Return tab width. Default tab width is equal to 0. You can set different tab width with help of x.xDSet tab width. If argument of the function is not positive number,  will be used.ysetParserState st set the full parser state to st.zparse p file input runs parser p over  (see  if you're using the d monad transformer; z itself is just a synonym for }). It returns either a + () or a value of type a ( ). ; can be used to turn +; into the string representation of the error message. See Text.Megaparsec.Error0 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 ','{parseMaybe p input runs parser p on input and returns result inside  on success and  ( on failure. This function also parses _C, 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.|The expression parseTest p input applies a parser p against input input5 and prints the result to stdout. Useful for testing.}runParser p file input runs parser p on the input list of tokens input, obtained from source file. The fileO is only used in error messages and may be the empty string. Returns either a + () or a value of type a ( ). 9parseFromFile p file = runParser p file <$> readFile file~The function is similar to } 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  monad.runParserT p file input runs parser p on the input list of tokens input, obtained from source file. The filem is only used in error messages and may be the empty string. Returns a computation in the underlying monad m that returns either a + () or a value of type a ( ).This function is similar to  , but like ~Z it accepts and returns parser state. This is thus the most general way to run a parser. GGiven name of source file and input construct initial state for parser.!Low-level unpacking of the d type.  and } are built upon this.lWXYZ[\]^_`abcd"#efghi$%jklmn Hints to useContinuation to influence(First argument of resulting continuation)Second argument of resulting continuation to addAn OK  continuation to alter(First argument of resulting continuation)Second argument of resulting continuation(Third argument of resulting continuation&'()*+,-./0123456789opqrstuvwxyz Parser to runName of source fileInput for parser{| Parser to runInput for parser} Parser to runName of source fileInput for parser~ Parser to run Initial state Parser to runName of source fileInput for parser Parser to run Initial state ! Parser to run Initial state*W[_\YXZ]^`abcdefghijklmnopqrstuvwxyz{|}~*jklmnfghiedWXYZ[\]^_`abcopqrstuvwxy}~z{|QW XYZ[\]^_`abcd"#efghi$%jklmn&'()*+,-./0123456789opqrstuvwxyz{|}~ !o0# 2015 2016 Megaparsec contributorsFreeBSD"Mark Karpov <markkarpov@opmbx.org> experimentalportableNone9Modules corresponding to various types of streams define  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.# 2015 2016 Megaparsec contributorsFreeBSD"Mark Karpov <markkarpov@opmbx.org> experimentalportableNone9Modules corresponding to various types of streams define  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.# 2015 2016 Megaparsec contributorsFreeBSD"Mark Karpov <markkarpov@opmbx.org> experimentalportableNone9Modules corresponding to various types of streams define  accordingly, so user can use it to easily change type of input stream by importing different type modules . This one is for strings.# 2015 2016 Megaparsec contributorsFreeBSD"Mark Karpov <markkarpov@opmbx.org> experimentalportableNone9Modules corresponding to various types of streams define  accordingly, so user can use it to easily change type of input stream by importing different type modules . This one is for strict text. # 2015 2016 Megaparsec contributorsFreeBSD"Mark Karpov <markkarpov@opmbx.org> experimentalportableNone9Modules corresponding to various types of streams define  accordingly, so user can use it to easily change type of input stream by importing different type modules . This one is for lazy text. p 2015 2016 Megaparsec contributors 2007 Paolo Martini 1999 2001 Daan LeijenFreeBSD"Mark Karpov <markkarpov@opmbx.org> experimentalportableSafebetween open close p parses open, followed by p and close!. Returns the value returned by p. *braces = between (symbol "{") (symbol "}") choice ps( tries to apply the parsers in the list psS in order, until one of them succeeds. Returns the value of the succeeding parser. count n p parses n occurrences of p. If n4 is smaller or equal to zero, the parser equals to  return []. Returns a list of n values. 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 mayK be negative, in this case effect is the same as if it were equal to zero.Combine two alternatives. 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 endBy1 p sep parses one or more occurrences of p, separated and ended by sep'. Returns a list of values returned by p.manyTill p end applies parser p zero or more times until parser end2 succeeds. Returns the list of values returned by p,. This parser can be used to scan comments: @simpleComment = string "<!--" >> manyTill anyChar (string "-->")someTill p end works similarly to manyTill p end, but p should succeed at least once. option x p tries to apply parser p. If p6 fails without consuming input, it returns the value x#, otherwise the value returned by p. .priority = option 0 (digitToInt <$> digitChar) 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 sepBy1 p sep parses one or more occurrences of p, separated by sep'. Returns a list of values returned by p.sepEndBy p sep parses zero or more occurrences of p%, separated and optionally ended by sep(. Returns a list of values returned by p.sepEndBy1 p sep parses one or more occurrences of p%, separated and optionally ended by sep(. Returns a list of values returned by p. skipMany p applies the parser p zero% or more times, skipping its result. space = skipMany spaceChar skipSome p applies the parser p one% or more times, skipping its result. p 2015 2016 Megaparsec contributors 2007 Paolo Martini 1999 2001 Daan LeijenFreeBSD"Mark Karpov <markkarpov@opmbx.org> experimental non-portableNone ?This data type specifies operators that work on values of type az. An operator is either binary infix or unary prefix or postfix. A binary operator has also an associated associativity.Non-associative infixLeft-associative infixRight-associative infixPrefixPostfixmakeExprParser term table( builds an expression parser for terms term with operators from table8, 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).TPrefix and postfix operators of the same precedence associate to the left (i.e. if ++ is postfix increment, than -2++ equals -1, not -3).AUnary operators of the same precedence can only occur once (i.e. --2 is not allowed if -k 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 singleUnaryOpqThis 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):addPrecLevel p ops* adds ability to parse operators in table ops to parser p.;pTerm prefix term postfix parses term with termE surrounded by optional prefix and postfix unary operators. Parsers prefix and postfix# are allowed to fail, in this case < is used.=pInfixN op p x' parses non-associative infix operator op, then term with parser p5, then returns result of the operator application on x and the term.>pInfixL op p x( parses left-associative infix operator op, then term with parser p5, then returns result of the operator application on x and the term.?pInfixR op p x) parses right-associative infix operator op, then term with parser p6, then returns result of the operator application on x and the term.@sA helper to separate various operators (binary, unary, and according to associativity) and return them in a tuple.A Term parserOperator table, see Resulting expression parser:;=>?@ A:;=>?@ p 2015 2016 Megaparsec contributors 2007 Paolo Martini 1999 2001 Daan LeijenFreeBSD"Mark Karpov <markkarpov@opmbx.org> experimental non-portableNoneAT The type PermParser s m a; denotes a permutation parser that, when converted by the ! function, produces instance of W m that parses s$ stream and returns a value of type a on success.LNormally, a permutation parser is first build with special operators like (3) and than transformed into a normal parser using . The parser makePermParser perm. parses a permutation of parser described by permQ. 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')The expression f <$$> p: creates a fresh permutation parser consisting of parser pB. The the final result of the permutation parser is the function f applied to the return value of p . The parser pF is not allowed to accept empty input  use the optional combinator ( ) instead.If the function f2 takes more than one parameter, the type variable bS is instantiated to a functional type which combines nicely with the adds parser p to the (i) combinator. This results in stylized code where a permutation parser starts with a combining function f( followed by the parsers. The function fl gets its parameters in the order in which the parsers are specified, but actual input can be in any order.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.The expression  perm <||> p adds parser p to the permutation parser perm . The parser pF is not allowed to accept empty input  use the optional combinator (;) instead. Returns a new permutation parser that includes p.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. BCDGiven permutation parserNormal parser built from it$Function to use on result of parsing Normal parser Permutation parser build from it$Function to use on result of parsingDefault value and parserPermutation parserGiven permutation parser-Parser to add (should not accept empty input)Resulting parserGiven permutation parserDefault value and parserResulting parserEFGH BCDEFGH2211 p 2015 2016 Megaparsec contributors 2007 Paolo Martini 1999 2001 Daan LeijenFreeBSD"Mark Karpov <markkarpov@opmbx.org> experimental non-portableNone:DR%Parses a newline character.kParses a carriage return character followed by a newline character. Returns sequence of characters parsed.Parses a CRLF (see  ) or LF (see :) end of line. Returns the sequence of characters parsed. !eol = (pure <$> newline) <|> crlfParses a tab character.Skips zero or more white space characters. See also:  and .cParses control characters, which are the non-printing characters of the Latin-1 subset of Unicode.zParses a Unicode space character, and the control characters: tab, newline, carriage return, form feed, and vertical tab.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.1Parses a lower-case alphabetic Unicode character.Parses alphabetic Unicode characters: lower-case, upper-case and title-case letters, plus letters of case-less scripts and modifiers letters.6Parses alphabetic or numeric digit Unicode characters.WNote that numeric digits outside the ASCII range are parsed by this parser but not by j. Such digits may be part of identifiers but are not used by the printer and reader to represent numbers._Parses printable Unicode characters: letters, numbers, marks, punctuation, symbols and spaces./Parses an ASCII digit, i.e between 0  and 9 .0Parses an octal digit, i.e. between 0  and 7 .VParses a hexadecimal digit, i.e. between 0  and 9 , or a  and f , or A  and F .kParses Unicode mark characters, for example accents and the like, which combine with preceding characters.eParses Unicode numeric characters, including digits from various scripts, Roman numerals, et cetera.cParses Unicode punctuation characters, including various kinds of connectors, brackets and quotes.OParses Unicode symbol characters, including mathematical and currency symbols..Parses Unicode space and separator characters.yParses a character from the first 128 characters of the Unicode character set, corresponding to the ASCII character set.Parses a character from the first 256 characters of the Unicode character set, corresponding to the ISO 8859-1 (Latin-1) character set.charCategory cat. Parses character in Unicode General Category cat, see I.8Returns human-readable name of Unicode General Category.char c parses a single character c. semicolon = char ';' The same as Z 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'EThis parser succeeds for any character. Returns the parsed character.oneOf csJ 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 Y or (o). See also: . $digit = oneOf ['0'..'9'] <?> "digit" The same as J, but case-insensitive. Returns the parsed character preserving its case. "vowel = oneOf' "aeiou" <?> "vowel"As the dual of ,  noneOf cs$ succeeds if the current character not$ in the supplied list of characters cs . Returns the parsed character. The same as , but case-insensitive. +consonant = noneOf' "aeiou" <?> "consonant" The parser  satisfy f= succeeds for any character for which the supplied function f returns J1. Returns the character that is actually parsed. GdigitChar = satisfy isDigit <?> "digit" oneOf cs = satisfy (`elem` cs)string s* parses a sequence of characters given by s#. Returns the parsed string (i.e. s). (divOrMod = string "div" <|> string "mod" The same as R, but case-insensitive. On success returns string cased as actually parsed input.%parseTest (string' "foobar") "foObAr""foObAr"K.Case-insensitive equality test for characters.LCase-insensitive M.NCase-insensitive O.%KLN""%KLNp 2015 2016 Megaparsec contributors 2007 Paolo Martini 1999 2001 Daan LeijenFreeBSD"Mark Karpov <markkarpov@opmbx.org> experimental non-portableNone:DR^The data type represents available behaviors for parsing of indented tokens. This is used in  , which see./Parse no indented tokens, just return the valueMParse many indented tokens (possibly zero), use given indentation level (if  , 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 Just like 9, but requires at least one indented token to be present(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  spaceConsumer9 in documentation, usually it means that something like  is expected there). spaceChar9 is used to parse trivial space characters. You can use  from Text.Megaparsec.Charr 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 $ if you don't need anything special. blockComment< is used to parse block (multi-line) comments. You can use $ 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 H combinator does, and so it's enough to wrap every lexeme parser with 0 to achieve this. Note that you'll need to call c manually to consume any white space before the first lexeme (i.e. at the beginning of the file).This is wrapper for lexemes. Typical usage is to supply first argument (parser that consumes white space, probably defined via C) and use the resulting function to wrap parsers for every lexeme. ;lexeme = L.lexeme spaceConsumer integer = lexeme L.integerThis is a helper to parse symbols, i.e. verbatim strings. You pass the first argument (parser that consumes white space, probably defined via ?) and then you can use the resulting function to parse strings: 7symbol = 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 "."Case-insensitive version of I. This may be helpful if you're working with case-insensitive languages.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  parser or picked up manually.skipBlockComment start end/ skips non-nested block comment starting with start and ending with end. skipBlockCommentNested start end4 skips possibly nested block comment starting with start and ending with end.!Return current indentation level.-The function is a simple shortcut defined as: *indentLevel = sourceColumn <$> getPositionPFail reporting incorrect indentation error. The error has attached information:9Desired ordering between reference level and actual levelReference indentation levelActual indentation level!indentGuard spaceConsumer ord ref4 first consumes all white space (indentation) with  spaceConsumerv parser, then it checks column position. Ordering between current indentation level and reference indentation level ref should be ordN, otherwise the parser fails. On success current column position is returned.WWhen 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.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.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  for more information.Tokens must notV consume newlines after them. On the other hand, the first argument of this function must6 consume newlines among other white space characters.P*Grab indented items. This is a helper for !, it's not a part of public API.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 consumerThe 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.XNote that you can use this parser as a building block to parse various string literals: =stringLiteral = char '"' >> manyTill L.charLiteral (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  combinator. The same as , but  is YNed with integer  label, while this parser is labeled with decimal 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: 4hexadecimal = char '0' >> char' 'x' >> L.hexadecimal#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.Q nump prefix p parses one or more characters with p parser, then prepends prefix` to returned value and tries to interpret the result as an integer according to Haskell syntax.Parse floating point value as R number. Rm is great for parsing of arbitrary precision numbers coming from an untrusted source. See documentation in Data.Scientificn for more information. Representation of floating point value is expected to be according to Haskell report.MThis function does not parse sign, if you need to parse signed numbers, see .PParse floating point number without sign. This is a simple shortcut defined as: "float = toRealFloat <$> scientificSThis is a helper for c parser. It parses fractional part of floating point number, that is, dot and everything after it.T6This helper parses exponent of floating point numbers.~Parse a number: either integer or floating point. The parser can handle overlapping grammars graciously. Use functions like  from Data.Scientific- to test and extract integer or real values.signed space pc parser parses optional sign, then if there is a sign it will consume optional white space (using space parser), then it runs parser pb which should return a number. Sign of the number is changed according to previously parsed sign.3For example, to parse signed integer you can write: vlexeme = L.lexeme spaceConsumer integer = lexeme L.integer signedInteger = L.signed spaceConsumer integerUParse a sign and return either < or V according to parsed sign.%A parser for a space character (e.g. )"A parser for a line comment (e.g. )#A parser for a block comment (e.g. )'How to consume white space after lexemeHow to parse actual lexeme'How to consume white space after lexemeString to parse'How to consume white space after lexeme"String to parse (case-insensitive)Line comment prefixStart of block commentEnd of block commentStart of block commentEnd of block comment9Desired ordering between reference level and actual levelReference indentation levelActual indentation level(How to consume indentation (white space)9Desired ordering between reference level and actual levelReference indentation level"Current column (indentation level)(How to consume indentation (white space)How to parse actual data(How to consume indentation (white space)How to parse reference  tokenPReference indentation level"Level of the first indented item (\ed)(How to consume indentation (white space)How to parse indented tokens(How to consume indentation (white space)*Callback that uses provided space-consumerQSTUPQSTUp 2015 2016 Megaparsec contributors 2007 Paolo Martini 1999 2001 Daan LeijenFreeBSD"Mark Karpov <markkarpov@opmbx.org> experimentalportableNone '()*+,-./0123456789:;cba`_^]\[ZYXdefghijklmnopqrstuvwxyz{|}~ed}~z{|pXoYZ[\]^_`a  789:456123+,-./0)*'(;fghijklmnqrstuvwxbycW !"#$%&'()*+,-./0123456789:;<=>?@@ABCDEFGHIJKLMNOPQRSTUVWXYZ[\]^_`abcdefghijklmnopqrstuvwxyz{|}~~                  !"#$%&'()*+,-./0123x4"56789:;<=>?@ABCDEFGH I JK L M N O P Q Q R S T U VWXY Z [\] ^\_`abcdefghi'megaparsec-5.0.1-8N1BMUMVDcXHJNhpuo08WuText.MegaparsecText.Megaparsec.PosText.Megaparsec.ErrorText.Megaparsec.PrimText.Megaparsec.ByteStringText.Megaparsec.ByteString.LazyText.Megaparsec.StringText.Megaparsec.TextText.Megaparsec.Text.LazyText.Megaparsec.CombinatorText.Megaparsec.ExprText.Megaparsec.PermText.Megaparsec.CharText.Megaparsec.Lexersatisfystringstring'Data.ScientificfloatingOrIntegerbaseControl.ApplicativeoptionalGHC.Basemanysome<|> SourcePos sourceName sourceLine sourceColumnInvalidPosExceptionPosmkPos unsafePosunPos initialPossourcePosPrettydefaultUpdatePosdefaultTabWidth$fNFDataSourcePos$fNFDataInvalidPosException$fExceptionInvalidPosException $fReadPos$fSemigroupPos $fShowPos$fEqPos$fOrdPos $fDataPos $fNFDataPos$fEqInvalidPosException$fShowInvalidPosException$fDataInvalidPosException$fGenericInvalidPosException$fShowSourcePos$fReadSourcePos $fEqSourcePos$fOrdSourcePos$fDataSourcePos$fGenericSourcePosShowErrorComponentshowErrorComponent ShowToken showTokens ParseErrorerrorPoserrorUnexpected errorExpected errorCustomDecDecFailDecIndentationErrorComponent representFailrepresentIndentation ErrorItemTokensLabel EndOfInputparseErrorPrettysourcePosStackPretty$fShowErrorComponentDec$fShowErrorComponentErrorItem$fShowTokenChar$fExceptionParseError$fMonoidParseError$fSemigroupParseError$fNFDataParseError$fErrorComponentDec $fNFDataDec$fNFDataErrorItem$fShowErrorItem$fReadErrorItem $fEqErrorItem$fOrdErrorItem$fDataErrorItem$fGenericErrorItem $fShowDec $fReadDec$fEqDec$fOrdDec $fDataDec$fShowParseError$fReadParseError$fEqParseError$fDataParseError$fGenericParseError MonadParsecfailurelabelhiddentry lookAhead notFollowedBy withRecoveryeoftokentokensgetParserStateupdateParserStateParsecTParsecStreamTokenuncons updatePosState stateInputstatePos stateTabWidth unexpectedgetInputsetInput getPosition setPosition pushPosition popPosition getTabWidth setTabWidthsetParserStateparse parseMaybe parseTest runParser runParser' runParserT runParserT'$fMonadParsecesIdentityT$fMonadParsecesWriterT$fMonadParsecesWriterT0$fMonadParsecesReaderT$fMonadParsecesStateT$fMonadParsecesStateT0$fMonadParsecesParsecT$fMonadTransParsecT$fMonadPlusParsecT$fMonadErrore'ParsecT$fMonadContParsecT$fMonadStatestParsecT$fMonadReaderrParsecT$fMonadIOParsecT$fMonadFailParsecT$fMonadParsecT$fAlternativeParsecT$fApplicativeParsecT$fFunctorParsecT $fStreamText $fStreamText0$fStreamByteString$fStreamByteString0 $fStream[] $fNFDataState $fShowState $fEqState $fDataState$fGenericState$fSemigroupHints $fMonoidHintsParserbetweenchoicecountcount'eitherPendByendBy1manyTillsomeTilloptionsepBysepBy1sepEndBy sepEndBy1skipManyskipSomeOperatorInfixNInfixLInfixRPrefixPostfixmakeExprParser PermParsermakePermParser<$$><$?><||><|?>newlinecrlfeoltabspace controlChar spaceChar upperChar lowerChar letterChar alphaNumChar printChar digitChar octDigitChar hexDigitCharmarkChar numberCharpunctuationChar symbolChar separatorChar asciiChar latin1Char charCategory categoryNamecharchar'anyCharoneOfoneOf'noneOfnoneOf' IndentOpt IndentNone IndentMany IndentSomelexemesymbolsymbol'skipLineCommentskipBlockCommentskipBlockCommentNested indentLevelincorrectIndent indentGuard nonIndented indentBlocklineFold charLiteralintegerdecimal hexadecimaloctal scientificfloatnumbersignedData.Semigroup SemigroupGHC.RealIntegral)exceptions-0.8.2.1-JBQJzRdlubk7otWf6cOKjrControl.Monad.Catch MonadThrowMaybeghc-prim GHC.TypesWordMonoidfail mergeError stringPretty charPrettyStringmessageItemsPrettyorList Data.EitherRightNothingHintsResult ConsumptionReplyOKErrorConsumedVirgintoHints withHintsaccHintsrefreshLastHintmkPT longestMatchnesData.Functor.IdentityIdentityLeftJust initialState runParsecTunParserpMappApmanyAccmanyErrpPurepBindpFailpZeropPluspFailurepLabelpTry pLookAheadpNotFollowedBy pWithRecoverypEofpTokenpTokenspGetParserStatepUpdateParserState addPrecLevelpTermidpInfixNpInfixLpInfixRsplitOpBatchBranchPermnewpermaddaddoptmapPerms GHC.UnicodeGeneralCategoryTruecaseielemi Data.FoldableelemnotEleminotElem indentedItemsnump)scientific-0.3.4.8-KQsa4BEnVKXIHSm6K6CxUB ScientificfractionfExpsignGHC.Numnegate