-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Monadic parser combinators -- -- This is an industrial-strength monadic parser combinator library. -- Megaparsec is a feature-rich package that strikes a nice balance -- between speed, flexibility, and quality of parse errors. @package megaparsec @version 6.5.0 -- | Textual source position. The position includes name of file, line -- number, and column number. List of such positions can be used to model -- a stack of include files. -- -- You probably do not want to import this module directly because -- Text.Megaparsec re-exports it anyway. module Text.Megaparsec.Pos -- | Pos is the type for positive integers. This is used to -- represent line number, column number, and similar things like -- indentation level. Semigroup instance can be used to safely and -- efficiently add Poses together. data Pos -- | Construction of Pos from Int. The function throws -- InvalidPosException when given a non-positive argument. mkPos :: Int -> Pos -- | Extract Int from Pos. unPos :: Pos -> Int -- | Position with value 1. pos1 :: Pos -- | Value of tab width used by default. Always prefer this constant when -- you want to refer to the default tab width because actual value -- may change in future. defaultTabWidth :: Pos -- | The exception is thrown by mkPos when its argument is not a -- positive number. data InvalidPosException -- | The first value is the minimal allowed value, the second value is the -- actual value that was passed to mkPos. InvalidPosException :: Int -> 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 :: FilePath -> SourcePos -- | Pretty-print a SourcePos. sourcePosPretty :: SourcePos -> String 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 Control.DeepSeq.NFData Text.Megaparsec.Pos.SourcePos instance GHC.Exception.Exception Text.Megaparsec.Pos.InvalidPosException instance Control.DeepSeq.NFData Text.Megaparsec.Pos.InvalidPosException instance GHC.Base.Semigroup Text.Megaparsec.Pos.Pos instance GHC.Read.Read Text.Megaparsec.Pos.Pos -- | Megaparsec's input stream facilities. -- -- You probably do not want to import this module directly because -- Text.Megaparsec re-exports it anyway. module Text.Megaparsec.Stream -- | Type class for inputs that can be consumed by the library. class (Ord (Token s), Ord (Tokens s)) => Stream s where { type family Token s :: *; type family Tokens s :: *; } -- | Lift a single token to chunk of the stream. The default implementation -- is: -- --
--   tokenToChunk pxy = tokensToChunk pxy . pure
--   
-- -- However for some types of stream there may be a more efficient way to -- lift. tokenToChunk :: Stream s => Proxy s -> Token s -> Tokens s -- | The first method that establishes isomorphism between list of tokens -- and chunk of the stream. Valid implementation should satisfy: -- --
--   chunkToTokens pxy (tokensToChunk pxy ts) == ts
--   
tokensToChunk :: Stream s => Proxy s -> [Token s] -> Tokens s -- | The second method that establishes isomorphism between list of tokens -- and chunk of the stream. Valid implementation should satisfy: -- --
--   tokensToChunk pxy (chunkToTokens pxy chunk) == chunk
--   
chunkToTokens :: Stream s => Proxy s -> Tokens s -> [Token s] -- | Return length of a chunk of the stream. chunkLength :: Stream s => Proxy s -> Tokens s -> Int -- | Check if a chunk of the stream is empty. The default implementation is -- in terms of the more general chunkLength: -- --
--   chunkEmpty pxy ts = chunkLength pxy ts <= 0
--   
-- -- However for many streams there may be a more efficient implementation. chunkEmpty :: Stream s => Proxy s -> Tokens s -> Bool -- | Set source position at given token. By default, the given -- SourcePos (second argument) is just returned without looking at -- the token. This method is important when your stream is a collection -- of tokens where every token knows where it begins in the original -- input. positionAt1 :: Stream s => Proxy s -> SourcePos -> Token s -> SourcePos -- | The same as positionAt1, but for chunks of the stream. The -- function should return the position where the entire chunk begins. -- Again, by default the second argument is returned without -- modifications and the chunk is not looked at. positionAtN :: Stream s => Proxy s -> SourcePos -> Tokens s -> SourcePos -- | Advance position given a single token. The returned position is the -- position right after the token, or the position where the token ends. advance1 :: Stream s => Proxy s -> Pos -> SourcePos -> Token s -> SourcePos -- | Advance position given a chunk of stream. The returned position is the -- position right after the chunk, or the position where the chunk ends. advanceN :: Stream s => Proxy s -> Pos -> SourcePos -> Tokens s -> SourcePos -- | Extract a single token form the stream. Return Nothing if the -- stream is empty. take1_ :: Stream s => s -> Maybe (Token s, s) -- | takeN_ n s should try to extract a chunk of length -- n, or if the stream is too short, the rest of the stream. -- Valid implementation should follow the rules: -- -- takeN_ :: Stream s => Int -> s -> Maybe (Tokens s, s) -- | Extract chunk of the stream taking tokens while the supplied predicate -- returns True. Return the chunk and the rest of the stream. -- -- For many types of streams, the method allows for significant -- performance improvements, although it is not strictly necessary from -- conceptual point of view. takeWhile_ :: Stream s => (Token s -> Bool) -> s -> (Tokens s, s) instance Text.Megaparsec.Stream.Stream GHC.Base.String instance Text.Megaparsec.Stream.Stream Data.ByteString.Internal.ByteString instance Text.Megaparsec.Stream.Stream Data.ByteString.Lazy.Internal.ByteString instance Text.Megaparsec.Stream.Stream Data.Text.Internal.Text instance Text.Megaparsec.Stream.Stream Data.Text.Internal.Lazy.Text -- | 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. -- -- You probably do not want to import this module directly because -- Text.Megaparsec re-exports it anyway. module Text.Megaparsec.Error -- | Data type that is used to represent “unexpected/expected” items in -- ParseError. The data type is parametrized over the 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 -- | Additional error data, extendable by user. When no custom data is -- necessary, the type is typically indexed by Void to “cancel” -- the ErrorCustom constructor. data ErrorFancy e -- | fail has been used in parser monad ErrorFail :: String -> ErrorFancy e -- | Incorrect indentation error: desired ordering between reference level -- and actual level, reference indentation level, actual indentation -- level ErrorIndentation :: Ordering -> Pos -> Pos -> ErrorFancy e -- | Custom error data, can be conveniently disabled by indexing -- ErrorFancy by Void ErrorCustom :: e -> ErrorFancy e -- | ParseError t e represents a parse error parametrized -- over the token type t and the custom data e. -- -- Note that the 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 and Monoid instances of the data type allow to -- merge parse errors from different branches of parsing. When merging -- two ParseErrors, the longest match is preferred; if positions -- are the same, custom data sets and collections of message items are -- combined. Note that fancy errors take precedence over trivial errors -- in merging. data ParseError t e -- | Trivial errors, generated by Megaparsec's machinery. The data -- constructor includes the stack of source positions, unexpected token -- (if any), and expected tokens. TrivialError :: (NonEmpty SourcePos) -> (Maybe (ErrorItem t)) -> (Set (ErrorItem t)) -> ParseError t e -- | Fancy, custom errors. FancyError :: (NonEmpty SourcePos) -> (Set (ErrorFancy e)) -> ParseError t e -- | Get position of given ParseError. errorPos :: ParseError t e -> NonEmpty SourcePos -- | 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 -- | Type class for tokens that support operations necessary for selecting -- and displaying relevant line of input. class LineToken a -- | Convert a token to a Char. This is used to print relevant line -- from input stream by turning a list of tokens into a String. tokenAsChar :: LineToken a => a -> Char -- | Check if given token is a newline or contains newline. tokenIsNewline :: LineToken a => a -> Bool -- | 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 a ParseError. The rendered String always -- ends with a newline. parseErrorPretty :: (Ord t, ShowToken t, ShowErrorComponent e) => ParseError t e -> String -- | Pretty-print a ParseError and display the line on which the -- parse error occurred. The rendered String always ends with a -- newline. -- -- Note that if you work with include files and have a stack of -- SourcePoses in ParseError, it's up to you to provide -- correct input stream corresponding to the file in which parse error -- actually happened. -- -- parseErrorPretty' is defined in terms of the more general -- parseErrorPretty_ function which allows to specify tab width as -- well: -- --
--   parseErrorPretty' = parseErrorPretty_ defaultTabWidth
--   
parseErrorPretty' :: (ShowToken (Token s), LineToken (Token s), ShowErrorComponent e, Stream s) => s -> ParseError (Token s) e -> String -- | Just like parseErrorPretty', but allows to specify tab width. parseErrorPretty_ :: forall s e. (ShowToken (Token s), LineToken (Token s), ShowErrorComponent e, Stream s) => Pos -> s -> ParseError (Token s) e -> String -- | Pretty-print a stack of source positions. sourcePosStackPretty :: NonEmpty SourcePos -> String -- | Pretty-print a textual part of a ParseError, that is, -- everything except stack of source positions. The rendered staring -- always ends with a new line. parseErrorTextPretty :: (Ord t, ShowToken t, ShowErrorComponent e) => ParseError t e -> 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.Read.Read t, GHC.Read.Read e, GHC.Classes.Ord t, GHC.Classes.Ord 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 GHC.Base.Functor Text.Megaparsec.Error.ErrorFancy instance GHC.Generics.Generic (Text.Megaparsec.Error.ErrorFancy e) instance Data.Data.Data e => Data.Data.Data (Text.Megaparsec.Error.ErrorFancy e) instance GHC.Classes.Ord e => GHC.Classes.Ord (Text.Megaparsec.Error.ErrorFancy e) instance GHC.Classes.Eq e => GHC.Classes.Eq (Text.Megaparsec.Error.ErrorFancy e) instance GHC.Read.Read e => GHC.Read.Read (Text.Megaparsec.Error.ErrorFancy e) instance GHC.Show.Show e => GHC.Show.Show (Text.Megaparsec.Error.ErrorFancy e) instance GHC.Base.Functor Text.Megaparsec.Error.ErrorItem 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 (GHC.Show.Show t, GHC.Classes.Ord t, Text.Megaparsec.Error.ShowToken t, Data.Typeable.Internal.Typeable t, GHC.Show.Show e, Text.Megaparsec.Error.ShowErrorComponent e, Data.Typeable.Internal.Typeable e) => GHC.Exception.Exception (Text.Megaparsec.Error.ParseError t e) instance (GHC.Classes.Ord t, Text.Megaparsec.Error.ShowToken t) => Text.Megaparsec.Error.ShowErrorComponent (Text.Megaparsec.Error.ErrorItem t) instance Text.Megaparsec.Error.ShowErrorComponent e => Text.Megaparsec.Error.ShowErrorComponent (Text.Megaparsec.Error.ErrorFancy e) instance Text.Megaparsec.Error.ShowErrorComponent Data.Void.Void instance Text.Megaparsec.Error.LineToken GHC.Types.Char instance Text.Megaparsec.Error.LineToken GHC.Word.Word8 instance Text.Megaparsec.Error.ShowToken GHC.Types.Char instance Text.Megaparsec.Error.ShowToken GHC.Word.Word8 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) => GHC.Base.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 Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Text.Megaparsec.Error.ErrorFancy a) instance Control.DeepSeq.NFData t => Control.DeepSeq.NFData (Text.Megaparsec.Error.ErrorItem t) -- | A set of helpers that should make construction of ParseErrors -- more concise. This is primarily useful in test suites and for -- debugging, you most certainly don't need it for normal usage. module Text.Megaparsec.Error.Builder -- | Assemble a ParseError from source position and ET -- t value. To create source position, two helpers are available: -- posI and posN. ET t is a monoid and can -- be assembled by combining primitives provided by this module, see -- below. err :: NonEmpty SourcePos -> ET t -> ParseError t e -- | Like err, but constructs a “fancy” ParseError. errFancy :: NonEmpty SourcePos -> EF e -> ParseError t e -- | Initial source position with empty file name. posI :: NonEmpty SourcePos -- | posN n s returns source position achieved by applying -- advanceN method corresponding to the type of stream s. posN :: forall s. Stream s => Int -> s -> NonEmpty SourcePos -- | Construct an “unexpected token” error component. utok :: Ord t => t -> ET t -- | Construct an “unexpected tokens” error component. Empty string -- produces EndOfInput. utoks :: Ord t => [t] -> ET t -- | Construct an “unexpected label” error component. Do not use with empty -- strings (for empty strings it's bottom). ulabel :: Ord t => String -> ET t -- | Construct an “unexpected end of input” error component. ueof :: Ord t => ET t -- | Construct an “expected token” error component. etok :: Ord t => t -> ET t -- | Construct an “expected tokens” error component. Empty string produces -- EndOfInput. etoks :: Ord t => [t] -> ET t -- | Construct an “expected label” error component. Do not use with empty -- strings. elabel :: Ord t => String -> ET t -- | Construct an “expected end of input” error component. eeof :: Ord t => ET t -- | Construct a custom error component. fancy :: ErrorFancy e -> EF e -- | Auxiliary type for construction of trivial parse errors. data ET t -- | Auxiliary type for construction of fancy parse errors. data EF e instance GHC.Generics.Generic (Text.Megaparsec.Error.Builder.EF e) instance (Data.Data.Data e, GHC.Classes.Ord e) => Data.Data.Data (Text.Megaparsec.Error.Builder.EF e) instance GHC.Classes.Ord e => GHC.Classes.Ord (Text.Megaparsec.Error.Builder.EF e) instance GHC.Classes.Eq e => GHC.Classes.Eq (Text.Megaparsec.Error.Builder.EF e) instance GHC.Generics.Generic (Text.Megaparsec.Error.Builder.ET t) instance (Data.Data.Data t, GHC.Classes.Ord t) => Data.Data.Data (Text.Megaparsec.Error.Builder.ET t) instance GHC.Classes.Ord t => GHC.Classes.Ord (Text.Megaparsec.Error.Builder.ET t) instance GHC.Classes.Eq t => GHC.Classes.Eq (Text.Megaparsec.Error.Builder.ET t) instance GHC.Classes.Ord e => GHC.Base.Semigroup (Text.Megaparsec.Error.Builder.EF e) instance GHC.Classes.Ord e => GHC.Base.Monoid (Text.Megaparsec.Error.Builder.EF e) instance GHC.Classes.Ord t => GHC.Base.Semigroup (Text.Megaparsec.Error.Builder.ET t) instance GHC.Classes.Ord t => GHC.Base.Monoid (Text.Megaparsec.Error.Builder.ET t) -- | Internal definitions. Versioning rules do not apply here. Please do -- not rely on these unless you really know what you're doing. module Text.Megaparsec.Internal -- | Hints represent a collection of ErrorItems to be -- included into ParserError (when it's a TrivialError) -- 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 input
--   
-- -- We're getting better error messages with help of hints: -- --
--   >>> parseTest (many (char 'r') <* eof) "ra"
--   1:2:
--   unexpected 'a'
--   expecting 'r' or end of input
--   
newtype Hints t Hints :: [Set (ErrorItem t)] -> Hints t -- | All 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: Consumption, Result. data Reply e s a Reply :: (State s) -> Consumption -> (Result (Token s) e a) -> Reply e s a -- | This data structure represents an aspect of result of parser's work. -- -- See also: Result, Reply. data Consumption -- | Some part of input stream was consumed Consumed :: Consumption -- | No input was consumed Virgin :: Consumption -- | This data structure represents an aspect of result of parser's work. -- -- See also: Consumption, Reply. data Result t e a -- | Parser succeeded OK :: a -> Result t e a -- | Parser failed Error :: (ParseError t e) -> Result t e a -- | 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. newtype ParsecT e s m a ParsecT :: forall b. State s -> (a -> State s -> Hints (Token s) -> m b) -> (ParseError (Token s) e -> State s -> m b) -> (a -> State s -> Hints (Token s) -> m b) -> (ParseError (Token s) e -> State s -> m b) -> m b -> ParsecT e s m a [unParser] :: ParsecT e s m a -> forall b. State s -> (a -> State s -> Hints (Token s) -> m b) -> (ParseError (Token s) e -> State s -> m b) -> (a -> State s -> Hints (Token s) -> m b) -> (ParseError (Token s) e -> State s -> m b) -> m b -- | Convert ParseError record into Hints. toHints :: NonEmpty SourcePos -> ParseError t e -> Hints t -- | withHints hs c makes “error” continuation c use -- given hints hs. -- -- Note that if resulting continuation gets ParseError that has -- custom data in it, hints are ignored. withHints :: Ord (Token s) => Hints (Token s) -> (ParseError (Token s) e -> State s -> m b) -> ParseError (Token s) e -> State s -> m b -- | accHints hs c results in “OK” continuation that will add -- given hints hs to third argument of original continuation -- c. accHints :: Hints t -> (a -> State s -> Hints t -> m b) -> a -> State s -> Hints t -> m b -- | Replace the most recent group of hints (if any) with the given -- ErrorItem (or delete it if Nothing is given). This is -- used in label primitive. refreshLastHint :: Hints t -> Maybe (ErrorItem t) -> Hints t -- | Low-level unpacking of the ParsecT type. runParsecT :: Monad m => ParsecT e s m a -> State s -> m (Reply e s a) instance GHC.Base.Monoid (Text.Megaparsec.Internal.Hints t) instance GHC.Base.Semigroup (Text.Megaparsec.Internal.Hints t) instance (Text.Megaparsec.Stream.Stream s, GHC.Base.Semigroup a) => GHC.Base.Semigroup (Text.Megaparsec.Internal.ParsecT e s m a) instance (Text.Megaparsec.Stream.Stream s, GHC.Base.Monoid a) => GHC.Base.Monoid (Text.Megaparsec.Internal.ParsecT e s m a) instance (a ~ Text.Megaparsec.Stream.Tokens s, Data.String.IsString a, GHC.Classes.Eq a, Text.Megaparsec.Stream.Stream s, GHC.Classes.Ord e) => Data.String.IsString (Text.Megaparsec.Internal.ParsecT e s m a) instance GHC.Base.Functor (Text.Megaparsec.Internal.ParsecT e s m) instance Text.Megaparsec.Stream.Stream s => GHC.Base.Applicative (Text.Megaparsec.Internal.ParsecT e s m) instance (GHC.Classes.Ord e, Text.Megaparsec.Stream.Stream s) => GHC.Base.Alternative (Text.Megaparsec.Internal.ParsecT e s m) instance Text.Megaparsec.Stream.Stream s => GHC.Base.Monad (Text.Megaparsec.Internal.ParsecT e s m) instance Text.Megaparsec.Stream.Stream s => Control.Monad.Fail.MonadFail (Text.Megaparsec.Internal.ParsecT e s m) instance (Text.Megaparsec.Stream.Stream s, Control.Monad.IO.Class.MonadIO m) => Control.Monad.IO.Class.MonadIO (Text.Megaparsec.Internal.ParsecT e s m) instance (Text.Megaparsec.Stream.Stream s, Control.Monad.Reader.Class.MonadReader r m) => Control.Monad.Reader.Class.MonadReader r (Text.Megaparsec.Internal.ParsecT e s m) instance (Text.Megaparsec.Stream.Stream s, Control.Monad.State.Class.MonadState st m) => Control.Monad.State.Class.MonadState st (Text.Megaparsec.Internal.ParsecT e s m) instance (Text.Megaparsec.Stream.Stream s, Control.Monad.Cont.Class.MonadCont m) => Control.Monad.Cont.Class.MonadCont (Text.Megaparsec.Internal.ParsecT e s m) instance (Text.Megaparsec.Stream.Stream s, Control.Monad.Error.Class.MonadError e' m) => Control.Monad.Error.Class.MonadError e' (Text.Megaparsec.Internal.ParsecT e s m) instance (GHC.Classes.Ord e, Text.Megaparsec.Stream.Stream s) => GHC.Base.MonadPlus (Text.Megaparsec.Internal.ParsecT e s m) instance (Text.Megaparsec.Stream.Stream s, Control.Monad.Fix.MonadFix m) => Control.Monad.Fix.MonadFix (Text.Megaparsec.Internal.ParsecT e s m) instance Control.Monad.Trans.Class.MonadTrans (Text.Megaparsec.Internal.ParsecT e s) instance (GHC.Classes.Ord e, Text.Megaparsec.Stream.Stream s) => Text.Megaparsec.Class.MonadParsec e s (Text.Megaparsec.Internal.ParsecT e s m) -- | 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 the tutorials -- https://markkarpov.com/learn-haskell.html#megaparsec-tutorials. -- -- In addition to the Text.Megaparsec module, which exports and -- re-exports most everything that you may need, we advise to import -- Text.Megaparsec.Char if you plan to work with a stream of -- Char tokens or Text.Megaparsec.Byte if you intend to -- parse binary data. -- -- It is common to start working with the library by defining a type -- synonym like this: -- --
--   type Parser = Parsec Void Text
--                        ^    ^
--                        |    |
--   Custom error component    Type of input
--   
-- -- Then you can write type signatures like Parser Int—for a -- parser that returns an Int for example. -- -- Similarly (since it's known to cause confusion), you should use -- ParseError type parametrized like this: -- --
--   ParseError Char Void
--              ^    ^
--              |    |
--     Token type    Custom error component (the same you used in Parser)
--   
-- -- Token type for String and Text (strict and lazy) is -- Char, for ByteStrings it's Word8. -- -- Megaparsec uses some type-level machinery to provide flexibility -- without compromising on type safety. Thus type signatures are -- sometimes necessary to avoid ambiguous types. If you're seeing a error -- message that reads like “Type variable e0 is ambiguous …”, -- you need to give an explicit signature to your parser to resolve the -- ambiguity. It's a good idea to provide type signatures for all -- top-level definitions. -- -- 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, do lexing with -- Text.Megaparsec.Char.Lexer and -- Text.Megaparsec.Byte.Lexer. These modules should be imported -- explicitly along with the modules mentioned above. module Text.Megaparsec -- | This is the Megaparsec's state parametrized over stream type -- s. data State s State :: s -> NonEmpty SourcePos -> {-# UNPACK #-} !Int -> Pos -> State s -- | The rest of input to process [stateInput] :: State s -> s -- | Current position (column + line number) with support for include files [statePos] :: State s -> NonEmpty SourcePos -- | Number of processed tokens so far [stateTokensProcessed] :: State s -> {-# UNPACK #-} !Int -- | Tab width to use [stateTabWidth] :: State s -> Pos -- | Parsec is a non-transformer variant of the 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 -- | 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 the parser p on -- input and returns the 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 a single -- number according to a specification of its format is desired. parseMaybe :: (Ord e, Stream s) => Parsec e s a -> s -> Maybe a -- | The expression parseTest p input applies the 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 () -- | A version of parseTest that also prints offending line in parse -- errors. parseTest' :: (ShowErrorComponent e, ShowToken (Token s), LineToken (Token s), Show a, Stream s) => Parsec e s a -> s -> IO () -- | runParser p file input runs parser p on the -- input stream 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) -- | Type class describing monads that implement the full set of primitive -- parsers. -- -- Note carefully that the following primitives are “fast” and -- should be taken advantage of as much as possible if your aim is a fast -- parser: tokens, takeWhileP, takeWhile1P, and -- takeP. class (Stream s, Alternative m, MonadPlus m) => MonadParsec e s m | m -> e s -- | The most general way to stop parsing and report a trivial -- ParseError. failure :: MonadParsec e s m => Maybe (ErrorItem (Token s)) -> Set (ErrorItem (Token s)) -> m a -- | The most general way to stop parsing and report a fancy -- ParseError. To report a single custom parse error, see -- customFailure. fancyFailure :: MonadParsec e s m => Set (ErrorFancy 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. -- -- Please use hidden instead of the old label "" -- idiom. hidden :: MonadParsec e s m => m a -> m a -- | The parser try p behaves like parser p, -- except that it backtracks the parser state when p fails -- (either consuming input or not). -- -- 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 -- if the first parser failed while consuming input. -- -- For example, here is a parser that is supposed to parse the word “let” -- or the word “lexical”: -- --
--   >>> parseTest (string "let" <|> string "lexical") "lexical"
--   1:1:
--   unexpected "lex"
--   expecting "let"
--   
-- -- What happens here? The 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. You still need to -- use try when your alternatives are complex, composite parsers. try :: MonadParsec e s m => m a -> m a -- | If p in lookAhead p succeeds (either -- consuming input or not) the whole parser behaves like p -- succeeded without consuming anything (parser state is not updated as -- well). If p fails, lookAhead has no effect, i.e. it -- will fail consuming input if p fails consuming input. Combine -- with try if this is undesirable. lookAhead :: MonadParsec e s m => m a -> m a -- | notFollowedBy p only succeeds when the parser -- p fails. This parser never consumes any input and -- never modifies parser state. It 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 the -- actual ParseError as its argument. Typical usage is to return a -- value signifying failure to parse this particular object and to -- consume some part of the input up to the point where the next object -- starts. -- -- 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 -- | observing p allows to “observe” failure of the -- p parser, should it happen, without actually ending parsing, -- but instead getting the ParseError in Left. On success -- parsed value is returned in Right as usual. Note that this -- primitive just allows you to observe parse errors as they happen, it -- does not backtrack or change how the p parser works in any -- way. observing :: MonadParsec e s m => m a -> m (Either (ParseError (Token s) e) 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 (pure (Tokens (x:|[])), Set.empty)
--   
token :: MonadParsec e s m => (Token s -> Either (Maybe (ErrorItem (Token s)), Set (ErrorItem (Token s))) a) -> Maybe (Token s) -> m a -- | The parser tokens test parses a chunk of input and -- returns it. Supplied predicate test is used to check equality -- of given and parsed chunks after a candidate chunk of correct length -- is fetched from the stream. -- -- 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 => (Tokens s -> Tokens s -> Bool) -> Tokens s -> m (Tokens s) -- | Parse zero or more tokens for which the supplied predicate -- holds. Try to use this as much as possible because for many streams -- the combinator is much faster than parsers built with many and -- satisfy. -- -- The following equations should clarify the behavior: -- --
--   takeWhileP (Just "foo") f = many (satisfy f <?> "foo")
--   takeWhileP Nothing      f = many (satisfy f)
--   
-- -- The combinator never fails, although it may parse an empty chunk. takeWhileP :: MonadParsec e s m => Maybe String -> (Token s -> Bool) -> m (Tokens s) -- | Similar to takeWhileP, but fails if it can't parse at least one -- token. Note that the combinator either succeeds or fails without -- consuming any input, so try is not necessary with it. takeWhile1P :: MonadParsec e s m => Maybe String -> (Token s -> Bool) -> m (Tokens s) -- | Extract the specified number of tokens from the input stream and -- return them packed as a chunk of stream. If there is not enough tokens -- in the stream, a parse error will be signaled. It's guaranteed that if -- the parser succeeds, the requested number of tokens will be returned. -- -- The parser is roughly equivalent to: -- --
--   takeP (Just "foo") n = count n (anyChar <?> "foo")
--   takeP Nothing      n = count n anyChar
--   
-- -- Note that if the combinator fails due to insufficient number of tokens -- in the input stream, it backtracks automatically. No try is -- necessary with takeP. takeP :: MonadParsec e s m => Maybe String -> Int -> m (Tokens s) -- | Return the full parser state as a State record. getParserState :: MonadParsec e s m => m (State s) -- | updateParserState f applies the function f to -- the parser state. updateParserState :: MonadParsec e s m => (State s -> State s) -> m () -- | A synonym for label in the form of an operator. () :: MonadParsec e s m => m a -> String -> m a infix 0 -- | The parser unexpected item fails with an error message -- telling about unexpected item item without consuming any -- input. -- --
--   unexpected item = failure (pure item) Set.empty
--   
unexpected :: MonadParsec e s m => ErrorItem (Token s) -> m a -- | Report a custom parse error. For a more general version, see -- fancyFailure. customFailure :: MonadParsec e s m => e -> m a -- | Return both the result of a parse and a chunk of input that was -- consumed during parsing. This relies on the change of the -- stateTokensProcessed value to evaluate how many tokens were -- consumed. If you mess with it manually in the argument parser, prepare -- for troubles. match :: MonadParsec e s m => m a -> m (Tokens s, a) -- | Specify how to process ParseErrors that happen inside of this -- wrapper. As a side effect of the current implementation changing -- errorPos with this combinator will also change the final -- statePos in the parser state (try to avoid that because -- statePos will go out of sync with factual position in the input -- stream, which is probably OK if you finish parsing right after that, -- but be warned). region :: MonadParsec e s m => (ParseError (Token s) e -> ParseError (Token s) e) -> m a -> m a -- | Consume the rest of the input and return it as a chunk. This parser -- never fails, but may return an empty chunk. -- --
--   takeRest = takeWhileP Nothing (const True)
--   
takeRest :: MonadParsec e s m => m (Tokens s) -- | Return True when end of input has been reached. atEnd :: MonadParsec e s m => m Bool -- | 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 -- | Get the position where the next token in the stream begins. If the -- stream is empty, return Nothing. getNextTokenPosition :: forall e s m. MonadParsec e s m => m (Maybe 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 a 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 the stack of positions unless it only contains one -- element (in that case the 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 () -- | Get the number of tokens processed so far. getTokensProcessed :: MonadParsec e s m => m Int -- | Set the number of tokens processed so far. setTokensProcessed :: MonadParsec e s m => Int -> m () -- | Return the tab width. The default tab width is equal to -- defaultTabWidth. You can set a different tab width with the -- help of setTabWidth. getTabWidth :: MonadParsec e s m => m Pos -- | Set tab width. If the argument of the function is not a positive -- number, defaultTabWidth will be used. setTabWidth :: MonadParsec e s m => Pos -> m () -- | setParserState st sets the parser state to -- st. setParserState :: MonadParsec e s m => State s -> m () -- | dbg label p parser works exactly like p, but -- when it's evaluated it also prints information useful for debugging. -- The label is only used to refer to this parser in the -- debugging output. This combinator uses the trace function from -- Debug.Trace under the hood. -- -- Typical usage is to wrap every sub-parser in misbehaving parser with -- dbg assigning meaningful labels. Then give it a shot and go -- through the print-out. As of current version, this combinator prints -- all available information except for hints, which are probably -- only interesting to the maintainer of Megaparsec itself and may be -- quite verbose to output in general. Let me know if you would like to -- be able to see hints in the debugging output. -- -- The output itself is pretty self-explanatory, although the following -- abbreviations should be clarified (they are derived from the low-level -- source code): -- -- -- -- Finally, it's not possible to lift this function into some monad -- transformers without introducing surprising behavior (e.g. unexpected -- state backtracking) or adding otherwise redundant constraints (e.g. -- Show instance for state), so this helper is only available for -- ParsecT monad, not MonadParsec in general. dbg :: forall e s m a. (Stream s, ShowToken (Token s), ShowErrorComponent e, Show a) => String -> ParsecT e s m a -> ParsecT e s 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 <|?> -- | 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 the 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 allowing repeating -- prefix or postfix operators is not desirable. -- -- If you want to have an operator that is a prefix of another operator -- in the table, use the following (or similar) wrapper instead of plain -- symbol: -- --
--   op n = (lexeme . try) (string n <* notFollowedBy punctuationChar)
--   
-- -- 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 -- | Commonly used character parsers. module Text.Megaparsec.Char -- | Parse a newline character. newline :: (MonadParsec e s m, Token s ~ Char) => m (Token s) -- | Parse a carriage return character followed by a newline character. -- Return the sequence of characters parsed. crlf :: forall e s m. (MonadParsec e s m, Token s ~ Char) => m (Tokens s) -- | Parse a CRLF (see crlf) or LF (see newline) end of line. -- Return the sequence of characters parsed. eol :: forall e s m. (MonadParsec e s m, Token s ~ Char) => m (Tokens s) -- | Parse a tab character. tab :: (MonadParsec e s m, Token s ~ Char) => m (Token s) -- | Skip zero or more white space characters. -- -- See also: skipMany and spaceChar. space :: (MonadParsec e s m, Token s ~ Char) => m () -- | Skip one or more white space characters. -- -- See also: skipSome and spaceChar. space1 :: (MonadParsec e s m, Token s ~ Char) => m () -- | Parse a control character (a non-printing character of the Latin-1 -- subset of Unicode). controlChar :: (MonadParsec e s m, Token s ~ Char) => m (Token s) -- | Parse 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 (Token s) -- | Parse 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 (Token s) -- | Parse a lower-case alphabetic Unicode character. lowerChar :: (MonadParsec e s m, Token s ~ Char) => m (Token s) -- | Parse an alphabetic Unicode character: lower-case, upper-case, or -- title-case letter, or a letter of case-less scripts/modifier letter. letterChar :: (MonadParsec e s m, Token s ~ Char) => m (Token s) -- | Parse an alphabetic or numeric digit Unicode characters. -- -- Note that the 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 (Token s) -- | Parse a printable Unicode character: letter, number, mark, -- punctuation, symbol or space. printChar :: (MonadParsec e s m, Token s ~ Char) => m (Token s) -- | Parse an ASCII digit, i.e between “0” and “9”. digitChar :: (MonadParsec e s m, Token s ~ Char) => m (Token s) -- | Parse an octal digit, i.e. between “0” and “7”. octDigitChar :: (MonadParsec e s m, Token s ~ Char) => m (Token s) -- | Parse 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 (Token s) -- | Parse a Unicode mark character (accents and the like), which combines -- with preceding characters. markChar :: (MonadParsec e s m, Token s ~ Char) => m (Token s) -- | Parse a Unicode numeric character, including digits from various -- scripts, Roman numerals, etc. numberChar :: (MonadParsec e s m, Token s ~ Char) => m (Token s) -- | Parse a Unicode punctuation character, including various kinds of -- connectors, brackets and quotes. punctuationChar :: (MonadParsec e s m, Token s ~ Char) => m (Token s) -- | Parse a Unicode symbol characters, including mathematical and currency -- symbols. symbolChar :: (MonadParsec e s m, Token s ~ Char) => m (Token s) -- | Parse a Unicode space and separator characters. separatorChar :: (MonadParsec e s m, Token s ~ Char) => m (Token s) -- | Parse 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 (Token s) -- | Parse 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 (Token s) -- | charCategory cat parses character in Unicode General -- Category cat, see GeneralCategory. charCategory :: (MonadParsec e s m, Token s ~ Char) => GeneralCategory -> m (Token s) -- | Return the 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 -> m (Token s) -- | The same as char but case-insensitive. This parser returns the -- 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) => Token s -> m (Token s) -- | This parser succeeds for any character. Returns the parsed character. anyChar :: MonadParsec e s m => m (Token s) -- | Match any character but the given one. It's a good idea to attach a -- label to this parser manually. notChar :: MonadParsec e s m => Token s -> m (Token s) -- | oneOf cs succeeds if the current character is in the -- supplied collection of characters cs. Returns the parsed -- character. Note that this parser cannot automatically generate the -- “expected” component of error message, so usually you should label it -- manually with label or (<?>). -- -- See also: satisfy. -- --
--   digit = oneOf ['0'..'9'] <?> "digit"
--   
-- -- Performance note: prefer satisfy when you can because -- it's faster when you have only a couple of tokens to compare to: -- --
--   quoteFast = satisfy (\x -> x == '\'' || x == '\"')
--   quoteSlow = oneOf "'\""
--   
oneOf :: (Foldable f, MonadParsec e s m) => f (Token s) -> m (Token s) -- | As the dual of oneOf, noneOf cs succeeds if the -- current character not in the supplied list of characters -- cs. Returns the parsed character. Note that this parser -- cannot automatically generate the “expected” component of error -- message, so usually you should label it manually with label or -- (<?>). -- -- See also: satisfy. -- -- Performance note: prefer satisfy and notChar when -- you can because it's faster. noneOf :: (Foldable f, MonadParsec e s m) => f (Token s) -> m (Token s) -- | 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 -> Bool) -> m (Token s) -- | 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 => Tokens s -> m (Tokens s) -- | 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, FoldCase (Tokens s)) => Tokens s -> m (Tokens s) -- | 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. -- -- 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). -- -- This module is intended to be imported qualified: -- --
--   import qualified Text.Megaparsec.Char.Lexer as L
--   
-- -- To do lexing of byte streams, see Text.Megaparsec.Byte.Lexer. module Text.Megaparsec.Char.Lexer -- | space sc 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). -- -- sc is used to parse blocks of space characters. You can use -- space1 from Text.Megaparsec.Char for this purpose as -- well as your own parser (if you don't want to automatically consume -- newlines, for example). Make sure the parser does not succeed on empty -- input though. In earlier version spaceChar was recommended, but -- now parsers based on takeWhile1P are preferred because of their -- speed. -- -- 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 or skipBlockCommentNested -- if you don't need anything special. -- -- If you don't want to allow a kind of comment, simply pass empty -- which will fail instantly when parsing of that sort of comment is -- attempted and space will just move on or finish depending on -- whether there is more white space for it to consume. space :: MonadParsec e s m => m () -> m () -> m () -> m () -- | This is a wrapper for lexemes. Typical usage is to supply the 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.decimal
--   
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 => m () -> Tokens s -> m (Tokens s) -- | Case-insensitive version of symbol. This may be helpful if -- you're working with case-insensitive languages. symbol' :: (MonadParsec e s m, FoldCase (Tokens s)) => m () -> Tokens s -> m (Tokens s) -- | Given comment prefix this function returns a parser that skips line -- comments. Note that it stops just before the 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) => Tokens s -> m () -- | skipBlockComment start end skips non-nested block -- comment starting with start and ending with end. skipBlockComment :: (MonadParsec e s m, Token s ~ Char) => Tokens s -> Tokens s -> m () -- | skipBlockCommentNested start end skips possibly nested -- block comment starting with start and ending with -- end. skipBlockCommentNested :: (MonadParsec e s m, Token s ~ Char) => Tokens s -> Tokens s -> m () -- | Return the 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 the column position. Ordering between current indentation level -- and the reference indentation level ref should be -- ord, otherwise the parser fails. On success the current -- column position is returned. -- -- When you want to parse a block of indentation, first run this parser -- with arguments like indentGuard spaceConsumer GT -- pos1—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 a 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 the final result, and the third -- argument describes how to parse an 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 a 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. -- The 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 '"')
--   
-- -- Performance note: the parser is not particularly efficient at -- the moment. charLiteral :: (MonadParsec e s m, Token s ~ Char) => m Char -- | Parse an integer in decimal representation according to the format of -- integer literals described in the Haskell report. -- -- If you need to parse signed integers, see signed combinator. -- -- Note: before version 6.0.0 the function returned -- Integer, i.e. it wasn't polymorphic in its return type. decimal :: forall e s m a. (MonadParsec e s m, Token s ~ Char, Integral a) => m a -- | Parse an integer in octal representation. Representation of octal -- number is expected to be according to the Haskell report except for -- the fact that this parser doesn't parse “0o” or “0O” prefix. It is a -- responsibility of the programmer to parse correct prefix before -- parsing the number itself. -- -- For example you can make it conform to the Haskell report like this: -- --
--   octal = char '0' >> char' 'o' >> L.octal
--   
-- -- Note: before version 6.0.0 the function returned -- Integer, i.e. it wasn't polymorphic in its return type. octal :: forall e s m a. (MonadParsec e s m, Token s ~ Char, Integral a) => m a -- | Parse an integer in hexadecimal representation. Representation of -- hexadecimal number is expected to be according to the Haskell report -- except for the fact that this parser doesn't parse “0x” or “0X” -- prefix. It is a responsibility of the programmer to parse correct -- prefix before parsing the number itself. -- -- For example you can make it conform to the Haskell report like this: -- --
--   hexadecimal = char '0' >> char' 'x' >> L.hexadecimal
--   
-- -- Note: before version 6.0.0 the function returned -- Integer, i.e. it wasn't polymorphic in its return type. hexadecimal :: forall e s m a. (MonadParsec e s m, Token s ~ Char, Integral a) => m a -- | Parse a floating point value as a Scientific number. -- Scientific is great for parsing of arbitrary precision numbers -- coming from an untrusted source. See documentation in -- Data.Scientific for more information. -- -- The parser can be used to parse integers or floating point values. Use -- functions like floatingOrInteger from Data.Scientific to -- test and extract integer or real values. -- -- This function does not parse sign, if you need to parse signed -- numbers, see signed. scientific :: forall e s m. (MonadParsec e s m, Token s ~ Char) => m Scientific -- | Parse a floating point number according to the syntax for floating -- point literals described in the Haskell report. -- -- This function does not parse sign, if you need to parse signed -- numbers, see signed. -- -- Note: before version 6.0.0 the function returned Double, -- i.e. it wasn't polymorphic in its return type. -- -- Note: in versions 6.0.0–6.1.1 this function accepted plain -- integers. float :: (MonadParsec e s m, Token s ~ Char, RealFloat a) => m a -- | signed space p parser parses an optional sign -- character (“+” or “-”), then if there is a sign it consumes optional -- white space (using space parser), then it runs parser -- p which should return a number. Sign of the number is changed -- according to the previously parsed sign character. -- -- For example, to parse signed integer you can write: -- --
--   lexeme        = L.lexeme spaceConsumer
--   integer       = lexeme L.decimal
--   signedInteger = L.signed spaceConsumer integer
--   
signed :: (MonadParsec e s m, Token s ~ Char, Num a) => m () -> m a -> m a -- | Commonly used binary parsers. module Text.Megaparsec.Byte -- | Parse a newline byte. newline :: (MonadParsec e s m, Token s ~ Word8) => m (Token s) -- | Parse a carriage return character followed by a newline character. -- Return the sequence of characters parsed. crlf :: forall e s m. (MonadParsec e s m, Token s ~ Word8) => m (Tokens s) -- | Parse a CRLF (see crlf) or LF (see newline) end of line. -- Return the sequence of characters parsed. eol :: forall e s m. (MonadParsec e s m, Token s ~ Word8) => m (Tokens s) -- | Parse a tab character. tab :: (MonadParsec e s m, Token s ~ Word8) => m (Token s) -- | Skip zero or more white space characters. -- -- See also: skipMany and spaceChar. space :: (MonadParsec e s m, Token s ~ Word8) => m () -- | Skip one or more white space characters. -- -- See also: skipSome and spaceChar. space1 :: (MonadParsec e s m, Token s ~ Word8) => m () -- | Parse a control character. controlChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s) -- | Parse a space character, and the control characters: tab, newline, -- carriage return, form feed, and vertical tab. spaceChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s) -- | Parse an upper-case character. upperChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s) -- | Parse a lower-case alphabetic character. lowerChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s) -- | Parse an alphabetic character: lower-case or upper-case. letterChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s) -- | Parse an alphabetic or digit characters. alphaNumChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s) -- | Parse a printable character: letter, number, mark, punctuation, symbol -- or space. printChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s) -- | Parse an ASCII digit, i.e between “0” and “9”. digitChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s) -- | Parse an octal digit, i.e. between “0” and “7”. octDigitChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s) -- | Parse a hexadecimal digit, i.e. between “0” and “9”, or “a” and “f”, -- or “A” and “F”. hexDigitChar :: (MonadParsec e s m, Token s ~ Word8) => m (Token s) -- | Parse 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 ~ Word8) => m (Token s) -- | char c parses a single character c. -- --
--   semicolon = char ';'
--   
char :: MonadParsec e s m => Token s -> m (Token s) -- | The same as char but case-insensitive. This parser returns -- the actually parsed character preserving its case. -- --
--   >>> parseTest (char' 101) "E"
--   69 -- 'E'
--   
--   >>> parseTest (char' 101) "G"
--   1:1:
--   unexpected 'G'
--   expecting 'E' or 'e'
--   
char' :: (MonadParsec e s m, Token s ~ Word8) => Token s -> m (Token s) -- | This parser succeeds for any character. Returns the parsed character. anyChar :: MonadParsec e s m => m (Token s) -- | Match any character but the given one. It's a good idea to attach a -- label to this parser manually. notChar :: MonadParsec e s m => Token s -> m (Token s) -- | oneOf cs succeeds if the current character is in the -- supplied collection of characters cs. Returns the parsed -- character. Note that this parser cannot automatically generate the -- “expected” component of error message, so usually you should label it -- manually with label or (<?>). -- -- See also: satisfy. -- --
--   digit = oneOf ['0'..'9'] <?> "digit"
--   
-- -- Performance note: prefer satisfy when you can because -- it's faster when you have only a couple of tokens to compare to: -- --
--   quoteFast = satisfy (\x -> x == '\'' || x == '\"')
--   quoteSlow = oneOf "'\""
--   
oneOf :: (Foldable f, MonadParsec e s m) => f (Token s) -> m (Token s) -- | As the dual of oneOf, noneOf cs succeeds if the -- current character not in the supplied list of characters -- cs. Returns the parsed character. Note that this parser -- cannot automatically generate the “expected” component of error -- message, so usually you should label it manually with label or -- (<?>). -- -- See also: satisfy. -- -- Performance note: prefer satisfy and notChar when -- you can because it's faster. noneOf :: (Foldable f, MonadParsec e s m) => f (Token s) -> m (Token s) -- | 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 -> Bool) -> m (Token s) -- | 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 => Tokens s -> m (Tokens s) -- | 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, FoldCase (Tokens s)) => Tokens s -> m (Tokens s) -- | Stripped-down version of Text.Megaparsec.Char.Lexer for streams -- of bytes. -- -- This module is intended to be imported qualified: -- --
--   import qualified Text.Megaparsec.Byte.Lexer as L
--   
module Text.Megaparsec.Byte.Lexer -- | space sc 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). -- -- sc is used to parse blocks of space characters. You can use -- space1 from Text.Megaparsec.Char for this purpose as -- well as your own parser (if you don't want to automatically consume -- newlines, for example). Make sure the parser does not succeed on empty -- input though. In earlier version spaceChar was recommended, but -- now parsers based on takeWhile1P are preferred because of their -- speed. -- -- 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 or skipBlockCommentNested -- if you don't need anything special. -- -- If you don't want to allow a kind of comment, simply pass empty -- which will fail instantly when parsing of that sort of comment is -- attempted and space will just move on or finish depending on -- whether there is more white space for it to consume. space :: MonadParsec e s m => m () -> m () -> m () -> m () -- | This is a wrapper for lexemes. Typical usage is to supply the 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.decimal
--   
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 => m () -> Tokens s -> m (Tokens s) -- | Case-insensitive version of symbol. This may be helpful if -- you're working with case-insensitive languages. symbol' :: (MonadParsec e s m, FoldCase (Tokens s)) => m () -> Tokens s -> m (Tokens s) -- | Given comment prefix this function returns a parser that skips line -- comments. Note that it stops just before the 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 ~ Word8) => Tokens s -> m () -- | skipBlockComment start end skips non-nested block -- comment starting with start and ending with end. skipBlockComment :: (MonadParsec e s m, Token s ~ Word8) => Tokens s -> Tokens s -> m () -- | skipBlockCommentNested start end skips possibly nested -- block comment starting with start and ending with -- end. skipBlockCommentNested :: (MonadParsec e s m, Token s ~ Word8) => Tokens s -> Tokens s -> m () -- | Parse an integer in decimal representation according to the format of -- integer literals described in the Haskell report. -- -- If you need to parse signed integers, see signed combinator. decimal :: forall e s m a. (MonadParsec e s m, Token s ~ Word8, Integral a) => m a -- | Parse an integer in octal representation. Representation of octal -- number is expected to be according to the Haskell report except for -- the fact that this parser doesn't parse “0o” or “0O” prefix. It is a -- responsibility of the programmer to parse correct prefix before -- parsing the number itself. -- -- For example you can make it conform to the Haskell report like this: -- --
--   octal = char '0' >> char' 'o' >> L.octal
--   
octal :: forall e s m a. (MonadParsec e s m, Token s ~ Word8, Integral a) => m a -- | Parse an integer in hexadecimal representation. Representation of -- hexadecimal number is expected to be according to the Haskell report -- except for the fact that this parser doesn't parse “0x” or “0X” -- prefix. It is a responsibility of the programmer to parse correct -- prefix before parsing the number itself. -- -- For example you can make it conform to the Haskell report like this: -- --
--   hexadecimal = char '0' >> char' 'x' >> L.hexadecimal
--   
hexadecimal :: forall e s m a. (MonadParsec e s m, Token s ~ Word8, Integral a) => m a -- | Parse a floating point value as a Scientific number. -- Scientific is great for parsing of arbitrary precision numbers -- coming from an untrusted source. See documentation in -- Data.Scientific for more information. -- -- The parser can be used to parse integers or floating point values. Use -- functions like floatingOrInteger from Data.Scientific to -- test and extract integer or real values. -- -- This function does not parse sign, if you need to parse signed -- numbers, see signed. scientific :: forall e s m. (MonadParsec e s m, Token s ~ Word8) => m Scientific -- | Parse a floating point number according to the syntax for floating -- point literals described in the Haskell report. -- -- This function does not parse sign, if you need to parse signed -- numbers, see signed. -- -- Note: in versions 6.0.0–6.1.1 this function accepted plain -- integers. float :: (MonadParsec e s m, Token s ~ Word8, RealFloat a) => m a -- | signed space p parser parses an optional sign -- character (“+” or “-”), then if there is a sign it consumes optional -- white space (using space parser), then it runs parser -- p which should return a number. Sign of the number is changed -- according to the previously parsed sign character. -- -- For example, to parse signed integer you can write: -- --
--   lexeme        = L.lexeme spaceConsumer
--   integer       = lexeme L.decimal
--   signedInteger = L.signed spaceConsumer integer
--   
signed :: (MonadParsec e s m, Token s ~ Word8, Num a) => m () -> m a -> m a