-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Monadic parser combinators -- -- Parsec is designed from scratch as an industrial-strength parser -- library. It is simple, safe, well documented (on the package -- homepage), has extensive libraries and good error messages, and is -- also fast. It is defined as a monad transformer that can be stacked on -- arbitrary monads, and it is also parametric in the input stream type. @package parsec @version 3.1.3 -- | Textual source positions. module Text.Parsec.Pos type SourceName = String type Line = Int type Column = Int -- | The abstract data type SourcePos represents source positions. -- It contains the name of the source (i.e. file name), a line number and -- a column number. SourcePos is an instance of the Show, -- Eq and Ord class. data SourcePos -- | Extracts the line number from a source position. sourceLine :: SourcePos -> Line -- | Extracts the column number from a source position. sourceColumn :: SourcePos -> Column -- | Extracts the name of the source from a source position. sourceName :: SourcePos -> SourceName -- | Increments the line number of a source position. incSourceLine :: SourcePos -> Line -> SourcePos -- | Increments the column number of a source position. incSourceColumn :: SourcePos -> Column -> SourcePos -- | Set the line number of a source position. setSourceLine :: SourcePos -> Line -> SourcePos -- | Set the column number of a source position. setSourceColumn :: SourcePos -> Column -> SourcePos -- | Set the name of the source. setSourceName :: SourcePos -> SourceName -> SourcePos -- | Create a new SourcePos with the given source name, line number -- and column number. newPos :: SourceName -> Line -> Column -> SourcePos -- | Create a new SourcePos with the given source name, and line -- number and column number set to 1, the upper left. initialPos :: SourceName -> SourcePos -- | Update a source position given a character. If the character is a -- newline ('\n') or carriage return ('\r') the line number is -- incremented by 1. If the character is a tab ('t') the column number is -- incremented to the nearest 8'th column, ie. column + 8 - -- ((column-1) `mod` 8). In all other cases, the column is -- incremented by 1. updatePosChar :: SourcePos -> Char -> SourcePos -- | The expression updatePosString pos s updates the source -- position pos by calling updatePosChar on every -- character in s, ie. foldl updatePosChar pos string. updatePosString :: SourcePos -> String -> SourcePos instance Typeable SourcePos instance Eq SourcePos instance Ord SourcePos instance Data SourcePos instance Show SourcePos -- | Parse errors module Text.Parsec.Error -- | This abstract data type represents parse error messages. There are -- four kinds of messages: -- --
--   data Message = SysUnExpect String
--                | UnExpect String
--                | Expect String
--                | Message String
--   
-- -- The fine distinction between different kinds of parse errors allows -- the system to generate quite good error messages for the user. It also -- allows error messages that are formatted in different languages. Each -- kind of message is generated by different combinators: -- -- data Message SysUnExpect :: !String -> Message UnExpect :: !String -> Message Expect :: !String -> Message Message :: !String -> Message -- | Extract the message string from an error message messageString :: Message -> String -- | The abstract data type ParseError represents parse errors. It -- provides the source position (SourcePos) of the error and a -- list of error messages (Message). A ParseError can be -- returned by the function parse. ParseError is an -- instance of the Show class. data ParseError -- | Extracts the source position from the parse error errorPos :: ParseError -> SourcePos -- | Extracts the list of error messages from the parse error errorMessages :: ParseError -> [Message] errorIsUnknown :: ParseError -> Bool showErrorMessages :: String -> String -> String -> String -> String -> [Message] -> String newErrorMessage :: Message -> SourcePos -> ParseError newErrorUnknown :: SourcePos -> ParseError addErrorMessage :: Message -> ParseError -> ParseError setErrorPos :: SourcePos -> ParseError -> ParseError setErrorMessage :: Message -> ParseError -> ParseError mergeError :: ParseError -> ParseError -> ParseError instance Show ParseError instance Ord Message instance Eq Message instance Enum Message -- | Parsec compatibility module module Text.ParserCombinators.Parsec.Error -- | This abstract data type represents parse error messages. There are -- four kinds of messages: -- --
--   data Message = SysUnExpect String
--                | UnExpect String
--                | Expect String
--                | Message String
--   
-- -- The fine distinction between different kinds of parse errors allows -- the system to generate quite good error messages for the user. It also -- allows error messages that are formatted in different languages. Each -- kind of message is generated by different combinators: -- -- data Message SysUnExpect :: !String -> Message UnExpect :: !String -> Message Expect :: !String -> Message Message :: !String -> Message -- | Extract the message string from an error message messageString :: Message -> String messageCompare :: Message -> Message -> Ordering messageEq :: Message -> Message -> Bool -- | The abstract data type ParseError represents parse errors. It -- provides the source position (SourcePos) of the error and a -- list of error messages (Message). A ParseError can be -- returned by the function parse. ParseError is an -- instance of the Show class. data ParseError -- | Extracts the source position from the parse error errorPos :: ParseError -> SourcePos -- | Extracts the list of error messages from the parse error errorMessages :: ParseError -> [Message] errorIsUnknown :: ParseError -> Bool showErrorMessages :: String -> String -> String -> String -> String -> [Message] -> String newErrorMessage :: Message -> SourcePos -> ParseError newErrorUnknown :: SourcePos -> ParseError addErrorMessage :: Message -> ParseError -> ParseError setErrorPos :: SourcePos -> ParseError -> ParseError setErrorMessage :: Message -> ParseError -> ParseError mergeError :: ParseError -> ParseError -> ParseError -- | Parsec compatibility module module Text.ParserCombinators.Parsec.Pos type SourceName = String type Line = Int type Column = Int -- | The abstract data type SourcePos represents source positions. -- It contains the name of the source (i.e. file name), a line number and -- a column number. SourcePos is an instance of the Show, -- Eq and Ord class. data SourcePos -- | Extracts the line number from a source position. sourceLine :: SourcePos -> Line -- | Extracts the column number from a source position. sourceColumn :: SourcePos -> Column -- | Extracts the name of the source from a source position. sourceName :: SourcePos -> SourceName -- | Increments the line number of a source position. incSourceLine :: SourcePos -> Line -> SourcePos -- | Increments the column number of a source position. incSourceColumn :: SourcePos -> Column -> SourcePos -- | Set the line number of a source position. setSourceLine :: SourcePos -> Line -> SourcePos -- | Set the column number of a source position. setSourceColumn :: SourcePos -> Column -> SourcePos -- | Set the name of the source. setSourceName :: SourcePos -> SourceName -> SourcePos -- | Create a new SourcePos with the given source name, line number -- and column number. newPos :: SourceName -> Line -> Column -> SourcePos -- | Create a new SourcePos with the given source name, and line -- number and column number set to 1, the upper left. initialPos :: SourceName -> SourcePos -- | Update a source position given a character. If the character is a -- newline ('\n') or carriage return ('\r') the line number is -- incremented by 1. If the character is a tab ('t') the column number is -- incremented to the nearest 8'th column, ie. column + 8 - -- ((column-1) `mod` 8). In all other cases, the column is -- incremented by 1. updatePosChar :: SourcePos -> Char -> SourcePos -- | The expression updatePosString pos s updates the source -- position pos by calling updatePosChar on every -- character in s, ie. foldl updatePosChar pos string. updatePosString :: SourcePos -> String -> SourcePos -- | The primitive parser combinators. module Text.Parsec.Prim unknownError :: State s u -> ParseError sysUnExpectError :: String -> SourcePos -> Reply s u a -- | The parser unexpected msg always fails with an unexpected -- error message msg without consuming any input. -- -- The parsers fail, (<?>) and unexpected -- are the three parsers used to generate error messages. Of these, only -- (<?>) is commonly used. For an example of the use of -- unexpected, see the definition of notFollowedBy. unexpected :: Stream s m t => String -> ParsecT s u m a -- | ParserT monad transformer and Parser type -- -- ParsecT s u m a is a parser with stream type s, user -- state type u, underlying monad m and return type -- a. Parsec is strict in the user state. If this is -- undesirable, simply used a data type like data Box a = Box a -- and the state type Box YourStateType to add a level of -- indirection. data ParsecT s u m a -- | Low-level unpacking of the ParsecT type. To run your parser, please -- look to runPT, runP, runParserT, runParser and other such functions. runParsecT :: Monad m => ParsecT s u m a -> State s u -> m (Consumed (m (Reply s u a))) -- | Low-level creation of the ParsecT type. You really shouldn't have to -- do this. mkPT :: Monad m => (State s u -> m (Consumed (m (Reply s u a)))) -> ParsecT s u m a type Parsec s u = ParsecT s u Identity data Consumed a Consumed :: a -> Consumed a Empty :: !a -> Consumed a data Reply s u a Ok :: a -> !State s u -> ParseError -> Reply s u a Error :: ParseError -> Reply s u a data State s u State :: s -> !SourcePos -> !u -> State s u stateInput :: State s u -> s statePos :: State s u -> !SourcePos stateUser :: State s u -> !u parsecMap :: (a -> b) -> ParsecT s u m a -> ParsecT s u m b parserReturn :: a -> ParsecT s u m a parserBind :: ParsecT s u m a -> (a -> ParsecT s u m b) -> ParsecT s u m b mergeErrorReply :: ParseError -> Reply s u a -> Reply s u a parserFail :: String -> ParsecT s u m a -- | parserZero always fails without consuming any input. -- parserZero is defined equal to the mzero member of the -- MonadPlus class and to the empty member of the -- Applicative class. parserZero :: ParsecT s u m a parserPlus :: ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a -- | The parser p ? msg behaves as parser p, but -- whenever the parser p fails without consuming any -- input, it replaces expect error messages with the expect error -- message msg. -- -- This is normally used at the end of a set alternatives where we want -- to return an error message in terms of a higher level construct rather -- than returning all possible characters. For example, if the -- expr parser from the try example would fail, the error -- message is: '...: expecting expression'. Without the -- (<?>) combinator, the message would be like '...: -- expecting "let" or letter', which is less friendly. () :: (ParsecT s u m a) -> String -> (ParsecT s u m a) -- | This combinator implements choice. The parser p <|> q -- first applies p. If it succeeds, the value of p is -- returned. If p fails without consuming any input, -- parser q is tried. This combinator is defined equal to the -- mplus member of the MonadPlus class and the -- (<|>) member of Alternative. -- -- The parser is called predictive since q is only tried -- when parser p didn't consume any input (i.e.. the look ahead -- is 1). This non-backtracking behaviour allows for both an efficient -- implementation of the parser combinators and the generation of good -- error messages. (<|>) :: (ParsecT s u m a) -> (ParsecT s u m a) -> (ParsecT s u m a) label :: ParsecT s u m a -> String -> ParsecT s u m a labels :: ParsecT s u m a -> [String] -> ParsecT s u m a -- | lookAhead p parses p without consuming any input. -- -- If p fails and consumes some input, so does -- lookAhead. Combine with try if this is undesirable. lookAhead :: Stream s m t => ParsecT s u m a -> ParsecT s u m a -- | An instance of Stream has stream type s, underlying -- monad m and token type t determined by the stream -- -- Some rough guidelines for a "correct" instance of Stream: -- -- class Monad m => Stream s m t | s -> t uncons :: Stream s m t => s -> m (Maybe (t, s)) tokens :: (Stream s m t, Eq t) => ([t] -> String) -> (SourcePos -> [t] -> SourcePos) -> [t] -> ParsecT s u m [t] -- | The parser try p behaves like parser p, except that -- it pretends that it hasn't consumed any input when an error occurs. -- -- This combinator is used whenever arbitrary look ahead is needed. Since -- it pretends that it hasn't consumed any input when p fails, -- the (<|>) combinator will try its second alternative even -- when the first parser failed while consuming input. -- -- The try combinator can for example be used to distinguish -- identifiers and reserved words. Both reserved words and identifiers -- are a sequence of letters. Whenever we expect a certain reserved word -- where we can also expect an identifier we have to use the try -- combinator. Suppose we write: -- --
--   expr        = letExpr <|> identifier <?> "expression"
--   
--   letExpr     = do{ string "let"; ... }
--   identifier  = many1 letter
--   
-- -- If the user writes "lexical", the parser fails with: unexpected -- 'x', expecting 't' in "let". Indeed, since the (<|>) -- combinator only tries alternatives when the first alternative hasn't -- consumed input, the identifier parser is never tried (because -- the prefix "le" of the string "let" parser is already -- consumed). The right behaviour can be obtained by adding the -- try combinator: -- --
--   expr        = letExpr <|> identifier <?> "expression"
--   
--   letExpr     = do{ try (string "let"); ... }
--   identifier  = many1 letter
--   
try :: ParsecT s u m a -> ParsecT s u m a -- | The parser token showTok posFromTok testTok accepts a token -- t with result x when the function testTok t -- returns Just x. The source position of the t -- should be returned by posFromTok t and the token can be shown -- using showTok t. -- -- This combinator is expressed in terms of tokenPrim. It is used -- to accept user defined token streams. For example, suppose that we -- have a stream of basic tokens tupled with source positions. We can -- than define a parser that accepts single tokens as: -- --
--   mytoken x
--     = token showTok posFromTok testTok
--     where
--       showTok (pos,t)     = show t
--       posFromTok (pos,t)  = pos
--       testTok (pos,t)     = if x == t then Just t else Nothing
--   
token :: Stream s Identity t => (t -> String) -> (t -> SourcePos) -> (t -> Maybe a) -> Parsec s u a -- | The parser tokenPrim showTok nextPos testTok accepts a token -- t with result x when the function testTok t -- returns Just x. The token can be shown using -- showTok t. The position of the next token should be -- returned when nextPos is called with the current source -- position pos, the current token t and the rest of -- the tokens toks, nextPos pos t toks. -- -- This is the most primitive combinator for accepting tokens. For -- example, the char parser could be implemented as: -- --
--   char c
--     = tokenPrim showChar nextPos testChar
--     where
--       showChar x        = "'" ++ x ++ "'"
--       testChar x        = if x == c then Just x else Nothing
--       nextPos pos x xs  = updatePosChar pos x
--   
tokenPrim :: Stream s m t => (t -> String) -> (SourcePos -> t -> s -> SourcePos) -> (t -> Maybe a) -> ParsecT s u m a tokenPrimEx :: Stream s m t => (t -> String) -> (SourcePos -> t -> s -> SourcePos) -> Maybe (SourcePos -> t -> s -> u -> u) -> (t -> Maybe a) -> ParsecT s u m a -- | many p applies the parser p zero or more -- times. Returns a list of the returned values of p. -- --
--   identifier  = do{ c  <- letter
--                   ; cs <- many (alphaNum <|> char '_')
--                   ; return (c:cs)
--                   }
--   
many :: ParsecT s u m a -> ParsecT s u m [a] -- | skipMany p applies the parser p zero or more -- times, skipping its result. -- --
--   spaces  = skipMany space
--   
skipMany :: ParsecT s u m a -> ParsecT s u m () manyAccum :: (a -> [a] -> [a]) -> ParsecT s u m a -> ParsecT s u m [a] runPT :: Stream s m t => ParsecT s u m a -> u -> SourceName -> s -> m (Either ParseError a) runP :: Stream s Identity t => Parsec s u a -> u -> SourceName -> s -> Either ParseError a -- | The most general way to run a parser. runParserT p state filePath -- input runs parser p on the input list of tokens -- input, obtained from source filePath with the -- initial user state st. The filePath is only used in -- error messages and may be the empty string. Returns a computation in -- the underlying monad m that return either a ParseError -- (Left) or a value of type a (Right). runParserT :: Stream s m t => ParsecT s u m a -> u -> SourceName -> s -> m (Either ParseError a) -- | The most general way to run a parser over the Identity monad. -- runParser p state filePath input runs parser p on -- the input list of tokens input, obtained from source -- filePath with the initial user state st. The -- filePath 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 fname
--     = do{ input <- readFile fname
--         ; return (runParser p () fname input)
--         }
--   
runParser :: Stream s Identity t => Parsec s u a -> u -> SourceName -> s -> Either ParseError a -- | parse p filePath input runs a parser p over Identity -- without user state. The filePath is only used in error -- messages and may be the empty string. Returns either a -- ParseError (Left) or a value of type a -- (Right). -- --
--   main    = case (parse numbers "" "11, 2, 43") of
--              Left err  -> print err
--              Right xs  -> print (sum xs)
--   
--   numbers = commaSep integer
--   
parse :: Stream s Identity t => Parsec s () a -> SourceName -> s -> Either ParseError a -- | The expression parseTest p input applies a parser p -- against input input and prints the result to stdout. Used for -- testing parsers. parseTest :: (Stream s Identity t, Show a) => Parsec s () a -> s -> IO () -- | Returns the current source position. See also SourcePos. getPosition :: Monad m => ParsecT s u m SourcePos -- | Returns the current input getInput :: Monad m => ParsecT s u m s -- | setPosition pos sets the current source position to -- pos. setPosition :: Monad m => SourcePos -> ParsecT s u m () -- | setInput input continues parsing with input. The -- getInput and setInput functions can for example be -- used to deal with #include files. setInput :: Monad m => s -> ParsecT s u m () -- | Returns the full parser state as a State record. getParserState :: Monad m => ParsecT s u m (State s u) -- | setParserState st set the full parser state to st. setParserState :: Monad m => State s u -> ParsecT s u m (State s u) -- | updateParserState f applies function f to the parser -- state. updateParserState :: (State s u -> State s u) -> ParsecT s u m (State s u) -- | Returns the current user state. getState :: Monad m => ParsecT s u m u -- | putState st set the user state to st. putState :: Monad m => u -> ParsecT s u m () -- | updateState f applies function f to the user state. -- Suppose that we want to count identifiers in a source, we could use -- the user state as: -- --
--   expr  = do{ x <- identifier
--             ; updateState (+1)
--             ; return (Id x)
--             }
--   
modifyState :: Monad m => (u -> u) -> ParsecT s u m () -- | An alias for putState for backwards compatibility. setState :: Monad m => u -> ParsecT s u m () -- | An alias for modifyState for backwards compatibility. updateState :: Monad m => (u -> u) -> ParsecT s u m () instance MonadTrans (ParsecT s u) instance MonadPlus (ParsecT s u m) instance MonadError e m => MonadError e (ParsecT s u m) instance MonadCont m => MonadCont (ParsecT s u m) instance MonadState s m => MonadState s (ParsecT s' u m) instance MonadReader r m => MonadReader r (ParsecT s u m) instance MonadIO m => MonadIO (ParsecT s u m) instance Monad (ParsecT s u m) instance Alternative (ParsecT s u m) instance Applicative (ParsecT s u m) instance Functor (ParsecT s u m) instance Functor (Reply s u) instance Functor Consumed -- | Commonly used character parsers. module Text.Parsec.Char -- | oneOf cs succeeds if the current character is in the supplied -- list of characters cs. Returns the parsed character. See also -- satisfy. -- --
--   vowel  = oneOf "aeiou"
--   
oneOf :: Stream s m Char => [Char] -> ParsecT s u m Char -- | As the dual of oneOf, noneOf cs succeeds if the -- current character not in the supplied list of characters -- cs. Returns the parsed character. -- --
--   consonant = noneOf "aeiou"
--   
noneOf :: Stream s m Char => [Char] -> ParsecT s u m Char -- | Skips zero or more white space characters. See also -- skipMany. spaces :: Stream s m Char => ParsecT s u m () -- | Parses a white space character (any character which satisfies -- isSpace) Returns the parsed character. space :: Stream s m Char => ParsecT s u m Char -- | Parses a newline character ('\n'). Returns a newline character. newline :: Stream s m Char => ParsecT s u m Char -- | Parses a tab character ('\t'). Returns a tab character. tab :: Stream s m Char => ParsecT s u m Char -- | Parses an upper case letter (a character between 'A' and 'Z'). Returns -- the parsed character. upper :: Stream s m Char => ParsecT s u m Char -- | Parses a lower case character (a character between 'a' and 'z'). -- Returns the parsed character. lower :: Stream s m Char => ParsecT s u m Char -- | Parses a letter or digit (a character between '0' and '9'). Returns -- the parsed character. alphaNum :: Stream s m Char => ParsecT s u m Char -- | Parses a letter (an upper case or lower case character). Returns the -- parsed character. letter :: Stream s m Char => ParsecT s u m Char -- | Parses a digit. Returns the parsed character. digit :: Stream s m Char => ParsecT s u m Char -- | Parses a hexadecimal digit (a digit or a letter between 'a' and 'f' or -- 'A' and 'F'). Returns the parsed character. hexDigit :: Stream s m Char => ParsecT s u m Char -- | Parses an octal digit (a character between '0' and '7'). Returns the -- parsed character. octDigit :: Stream s m Char => ParsecT s u m Char -- | char c parses a single character c. Returns the -- parsed character (i.e. c). -- --
--   semiColon  = char ';'
--   
char :: Stream s m Char => Char -> ParsecT s u m Char -- | This parser succeeds for any character. Returns the parsed character. anyChar :: Stream s m Char => ParsecT s u m Char -- | The parser satisfy f succeeds for any character for which the -- supplied function f returns True. Returns the -- character that is actually parsed. satisfy :: Stream s m Char => (Char -> Bool) -> ParsecT s u m Char -- | string s parses a sequence of characters given by s. -- Returns the parsed string (i.e. s). -- --
--   divOrMod    =   string "div" 
--               <|> string "mod"
--   
string :: Stream s m Char => String -> ParsecT s u m String -- | Commonly used generic combinators module Text.Parsec.Combinator -- | choice ps tries to apply the parsers in the list ps -- in order, until one of them succeeds. Returns the value of the -- succeeding parser. choice :: Stream s m t => [ParsecT s u m a] -> ParsecT s u m a -- | count n p parses n occurrences of p. If -- n is smaller or equal to zero, the parser equals to -- return []. Returns a list of n values returned by -- p. count :: Stream s m t => Int -> ParsecT s u m a -> ParsecT s u m [a] -- | between open close p parses open, followed by -- p and close. Returns the value returned by -- p. -- --
--   braces  = between (symbol "{") (symbol "}")
--   
between :: Stream s m t => ParsecT s u m open -> ParsecT s u m close -> ParsecT s u m a -> ParsecT s u m a -- | option x p tries to apply parser p. If p -- fails without consuming input, it returns the value x, -- otherwise the value returned by p. -- --
--   priority  = option 0 (do{ d <- digit
--                           ; return (digitToInt d) 
--                           })
--   
option :: Stream s m t => a -> ParsecT s u m a -> ParsecT s u m a -- | optionMaybe p tries to apply parser p. If p -- fails without consuming input, it return Nothing, otherwise it -- returns Just the value returned by p. optionMaybe :: Stream s m t => ParsecT s u m a -> ParsecT s u m (Maybe a) -- | optional p tries to apply parser p. It will parse -- p or nothing. It only fails if p fails after -- consuming input. It discards the result of p. optional :: Stream s m t => ParsecT s u m a -> ParsecT s u m () -- | skipMany1 p applies the parser p one or more -- times, skipping its result. skipMany1 :: Stream s m t => ParsecT s u m a -> ParsecT s u m () -- | many1 p applies the parser p one or more -- times. Returns a list of the returned values of p. -- --
--   word  = many1 letter
--   
many1 :: Stream s m t => ParsecT s u m a -> ParsecT s u m [a] -- | sepBy p sep parses zero or more occurrences of -- p, separated by sep. Returns a list of values -- returned by p. -- --
--   commaSep p  = p `sepBy` (symbol ",")
--   
sepBy :: Stream s m t => ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a] -- | sepBy1 p sep parses one or more occurrences of -- p, separated by sep. Returns a list of values -- returned by p. sepBy1 :: Stream s m t => ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a] -- | endBy p sep parses zero or more occurrences of -- p, seperated and ended by sep. Returns a list of -- values returned by p. -- --
--   cStatements  = cStatement `endBy` semi
--   
endBy :: Stream s m t => ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a] -- | endBy1 p sep parses one or more occurrences of -- p, seperated and ended by sep. Returns a list of -- values returned by p. endBy1 :: Stream s m t => ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a] -- | sepEndBy p sep parses zero or more occurrences of -- p, separated and optionally ended by sep, ie. -- haskell style statements. Returns a list of values returned by -- p. -- --
--   haskellStatements  = haskellStatement `sepEndBy` semi
--   
sepEndBy :: Stream s m t => ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a] -- | sepEndBy1 p sep parses one or more occurrences of -- p, separated and optionally ended by sep. Returns a -- list of values returned by p. sepEndBy1 :: Stream s m t => ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a] -- | chainl p op x parser zero or more occurrences of -- p, separated by op. Returns a value obtained by a -- left associative application of all functions returned by -- op to the values returned by p. If there are zero -- occurrences of p, the value x is returned. chainl :: Stream s m t => ParsecT s u m a -> ParsecT s u m (a -> a -> a) -> a -> ParsecT s u m a -- | chainl1 p op x parser one or more occurrences of -- p, separated by op Returns a value obtained by a -- left associative application of all functions returned by -- op to the values returned by p. . This parser can -- for example be used to eliminate left recursion which typically occurs -- in expression grammars. -- --
--   expr    = term   `chainl1` addop
--   term    = factor `chainl1` mulop
--   factor  = parens expr <|> integer
--   
--   mulop   =   do{ symbol "*"; return (*)   }
--           <|> do{ symbol "/"; return (div) }
--   
--   addop   =   do{ symbol "+"; return (+) }
--           <|> do{ symbol "-"; return (-) }
--   
chainl1 :: Stream s m t => ParsecT s u m a -> ParsecT s u m (a -> a -> a) -> ParsecT s u m a -- | chainr p op x parser zero or more occurrences of -- p, separated by op Returns a value obtained by a -- right associative application of all functions returned by -- op to the values returned by p. If there are no -- occurrences of p, the value x is returned. chainr :: Stream s m t => ParsecT s u m a -> ParsecT s u m (a -> a -> a) -> a -> ParsecT s u m a -- | chainr1 p op x parser one or more occurrences of |p|, -- separated by op Returns a value obtained by a right -- associative application of all functions returned by op to -- the values returned by p. chainr1 :: Stream s m t => ParsecT s u m a -> ParsecT s u m (a -> a -> a) -> ParsecT s u m a -- | This parser only succeeds at the end of the input. This is not a -- primitive parser but it is defined using notFollowedBy. -- --
--   eof  = notFollowedBy anyToken <?> "end of input"
--   
eof :: (Stream s m t, Show t) => ParsecT s u m () -- | notFollowedBy p only succeeds when parser p fails. -- This parser does not consume any input. This parser can be used to -- implement the 'longest match' rule. For example, when recognizing -- keywords (for example let), we want to make sure that a -- keyword is not followed by a legal identifier character, in which case -- the keyword is actually an identifier (for example lets). We -- can program this behaviour as follows: -- --
--   keywordLet  = try (do{ string "let"
--                        ; notFollowedBy alphaNum
--                        })
--   
notFollowedBy :: (Stream s m t, Show a) => ParsecT s u m a -> ParsecT s u m () -- | manyTill p end applies parser p zero or more -- times until parser end succeeds. Returns the list of values -- returned by p. This parser can be used to scan comments: -- --
--   simpleComment   = do{ string "<!--"
--                       ; manyTill anyChar (try (string "-->"))
--                       }
--   
-- -- Note the overlapping parsers anyChar and string -- "-->", and therefore the use of the try combinator. manyTill :: Stream s m t => ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a] -- | lookAhead p parses p without consuming any input. -- -- If p fails and consumes some input, so does -- lookAhead. Combine with try if this is undesirable. lookAhead :: Stream s m t => ParsecT s u m a -> ParsecT s u m a -- | The parser anyToken accepts any kind of token. It is for -- example used to implement eof. Returns the accepted token. anyToken :: (Stream s m t, Show t) => ParsecT s u m t -- | Parsec compatibility module module Text.ParserCombinators.Parsec.Combinator -- | choice ps tries to apply the parsers in the list ps -- in order, until one of them succeeds. Returns the value of the -- succeeding parser. choice :: Stream s m t => [ParsecT s u m a] -> ParsecT s u m a -- | count n p parses n occurrences of p. If -- n is smaller or equal to zero, the parser equals to -- return []. Returns a list of n values returned by -- p. count :: Stream s m t => Int -> ParsecT s u m a -> ParsecT s u m [a] -- | between open close p parses open, followed by -- p and close. Returns the value returned by -- p. -- --
--   braces  = between (symbol "{") (symbol "}")
--   
between :: Stream s m t => ParsecT s u m open -> ParsecT s u m close -> ParsecT s u m a -> ParsecT s u m a -- | option x p tries to apply parser p. If p -- fails without consuming input, it returns the value x, -- otherwise the value returned by p. -- --
--   priority  = option 0 (do{ d <- digit
--                           ; return (digitToInt d) 
--                           })
--   
option :: Stream s m t => a -> ParsecT s u m a -> ParsecT s u m a -- | optionMaybe p tries to apply parser p. If p -- fails without consuming input, it return Nothing, otherwise it -- returns Just the value returned by p. optionMaybe :: Stream s m t => ParsecT s u m a -> ParsecT s u m (Maybe a) -- | optional p tries to apply parser p. It will parse -- p or nothing. It only fails if p fails after -- consuming input. It discards the result of p. optional :: Stream s m t => ParsecT s u m a -> ParsecT s u m () -- | skipMany1 p applies the parser p one or more -- times, skipping its result. skipMany1 :: Stream s m t => ParsecT s u m a -> ParsecT s u m () -- | many1 p applies the parser p one or more -- times. Returns a list of the returned values of p. -- --
--   word  = many1 letter
--   
many1 :: Stream s m t => ParsecT s u m a -> ParsecT s u m [a] -- | sepBy p sep parses zero or more occurrences of -- p, separated by sep. Returns a list of values -- returned by p. -- --
--   commaSep p  = p `sepBy` (symbol ",")
--   
sepBy :: Stream s m t => ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a] -- | sepBy1 p sep parses one or more occurrences of -- p, separated by sep. Returns a list of values -- returned by p. sepBy1 :: Stream s m t => ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a] -- | endBy p sep parses zero or more occurrences of -- p, seperated and ended by sep. Returns a list of -- values returned by p. -- --
--   cStatements  = cStatement `endBy` semi
--   
endBy :: Stream s m t => ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a] -- | endBy1 p sep parses one or more occurrences of -- p, seperated and ended by sep. Returns a list of -- values returned by p. endBy1 :: Stream s m t => ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a] -- | sepEndBy p sep parses zero or more occurrences of -- p, separated and optionally ended by sep, ie. -- haskell style statements. Returns a list of values returned by -- p. -- --
--   haskellStatements  = haskellStatement `sepEndBy` semi
--   
sepEndBy :: Stream s m t => ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a] -- | sepEndBy1 p sep parses one or more occurrences of -- p, separated and optionally ended by sep. Returns a -- list of values returned by p. sepEndBy1 :: Stream s m t => ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a] -- | chainl p op x parser zero or more occurrences of -- p, separated by op. Returns a value obtained by a -- left associative application of all functions returned by -- op to the values returned by p. If there are zero -- occurrences of p, the value x is returned. chainl :: Stream s m t => ParsecT s u m a -> ParsecT s u m (a -> a -> a) -> a -> ParsecT s u m a -- | chainl1 p op x parser one or more occurrences of -- p, separated by op Returns a value obtained by a -- left associative application of all functions returned by -- op to the values returned by p. . This parser can -- for example be used to eliminate left recursion which typically occurs -- in expression grammars. -- --
--   expr    = term   `chainl1` addop
--   term    = factor `chainl1` mulop
--   factor  = parens expr <|> integer
--   
--   mulop   =   do{ symbol "*"; return (*)   }
--           <|> do{ symbol "/"; return (div) }
--   
--   addop   =   do{ symbol "+"; return (+) }
--           <|> do{ symbol "-"; return (-) }
--   
chainl1 :: Stream s m t => ParsecT s u m a -> ParsecT s u m (a -> a -> a) -> ParsecT s u m a -- | chainr p op x parser zero or more occurrences of -- p, separated by op Returns a value obtained by a -- right associative application of all functions returned by -- op to the values returned by p. If there are no -- occurrences of p, the value x is returned. chainr :: Stream s m t => ParsecT s u m a -> ParsecT s u m (a -> a -> a) -> a -> ParsecT s u m a -- | chainr1 p op x parser one or more occurrences of |p|, -- separated by op Returns a value obtained by a right -- associative application of all functions returned by op to -- the values returned by p. chainr1 :: Stream s m t => ParsecT s u m a -> ParsecT s u m (a -> a -> a) -> ParsecT s u m a -- | This parser only succeeds at the end of the input. This is not a -- primitive parser but it is defined using notFollowedBy. -- --
--   eof  = notFollowedBy anyToken <?> "end of input"
--   
eof :: (Stream s m t, Show t) => ParsecT s u m () -- | notFollowedBy p only succeeds when parser p fails. -- This parser does not consume any input. This parser can be used to -- implement the 'longest match' rule. For example, when recognizing -- keywords (for example let), we want to make sure that a -- keyword is not followed by a legal identifier character, in which case -- the keyword is actually an identifier (for example lets). We -- can program this behaviour as follows: -- --
--   keywordLet  = try (do{ string "let"
--                        ; notFollowedBy alphaNum
--                        })
--   
notFollowedBy :: (Stream s m t, Show a) => ParsecT s u m a -> ParsecT s u m () -- | manyTill p end applies parser p zero or more -- times until parser end succeeds. Returns the list of values -- returned by p. This parser can be used to scan comments: -- --
--   simpleComment   = do{ string "<!--"
--                       ; manyTill anyChar (try (string "-->"))
--                       }
--   
-- -- Note the overlapping parsers anyChar and string -- "-->", and therefore the use of the try combinator. manyTill :: Stream s m t => ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a] -- | lookAhead p parses p without consuming any input. -- -- If p fails and consumes some input, so does -- lookAhead. Combine with try if this is undesirable. lookAhead :: Stream s m t => ParsecT s u m a -> ParsecT s u m a -- | The parser anyToken accepts any kind of token. It is for -- example used to implement eof. Returns the accepted token. anyToken :: (Stream s m t, Show t) => ParsecT s u m t -- | Make Strings an instance of Stream with Char token type. module Text.Parsec.String type Parser = Parsec String () type GenParser tok st = Parsec [tok] st -- | parseFromFile p filePath runs a string parser p on -- the input read from filePath using readFile. Returns -- either a ParseError (Left) or a value of type a -- (Right). -- --
--   main    = do{ result <- parseFromFile numbers "digits.txt"
--               ; case result of
--                   Left err  -> print err
--                   Right xs  -> print (sum xs)
--               }
--   
parseFromFile :: Parser a -> String -> IO (Either ParseError a) instance Monad m => Stream [tok] m tok -- | Parsec compatibility module module Text.ParserCombinators.Parsec.Char type CharParser st = GenParser Char st -- | Skips zero or more white space characters. See also -- skipMany. spaces :: Stream s m Char => ParsecT s u m () -- | Parses a white space character (any character which satisfies -- isSpace) Returns the parsed character. space :: Stream s m Char => ParsecT s u m Char -- | Parses a newline character ('\n'). Returns a newline character. newline :: Stream s m Char => ParsecT s u m Char -- | Parses a tab character ('\t'). Returns a tab character. tab :: Stream s m Char => ParsecT s u m Char -- | Parses an upper case letter (a character between 'A' and 'Z'). Returns -- the parsed character. upper :: Stream s m Char => ParsecT s u m Char -- | Parses a lower case character (a character between 'a' and 'z'). -- Returns the parsed character. lower :: Stream s m Char => ParsecT s u m Char -- | Parses a letter or digit (a character between '0' and '9'). Returns -- the parsed character. alphaNum :: Stream s m Char => ParsecT s u m Char -- | Parses a letter (an upper case or lower case character). Returns the -- parsed character. letter :: Stream s m Char => ParsecT s u m Char -- | Parses a digit. Returns the parsed character. digit :: Stream s m Char => ParsecT s u m Char -- | Parses a hexadecimal digit (a digit or a letter between 'a' and 'f' or -- 'A' and 'F'). Returns the parsed character. hexDigit :: Stream s m Char => ParsecT s u m Char -- | Parses an octal digit (a character between '0' and '7'). Returns the -- parsed character. octDigit :: Stream s m Char => ParsecT s u m Char -- | char c parses a single character c. Returns the -- parsed character (i.e. c). -- --
--   semiColon  = char ';'
--   
char :: Stream s m Char => Char -> ParsecT s u m Char -- | string s parses a sequence of characters given by s. -- Returns the parsed string (i.e. s). -- --
--   divOrMod    =   string "div" 
--               <|> string "mod"
--   
string :: Stream s m Char => String -> ParsecT s u m String -- | This parser succeeds for any character. Returns the parsed character. anyChar :: Stream s m Char => ParsecT s u m Char -- | oneOf cs succeeds if the current character is in the supplied -- list of characters cs. Returns the parsed character. See also -- satisfy. -- --
--   vowel  = oneOf "aeiou"
--   
oneOf :: Stream s m Char => [Char] -> ParsecT s u m Char -- | As the dual of oneOf, noneOf cs succeeds if the -- current character not in the supplied list of characters -- cs. Returns the parsed character. -- --
--   consonant = noneOf "aeiou"
--   
noneOf :: Stream s m Char => [Char] -> ParsecT s u m Char -- | The parser satisfy f succeeds for any character for which the -- supplied function f returns True. Returns the -- character that is actually parsed. satisfy :: Stream s m Char => (Char -> Bool) -> ParsecT s u m Char -- | Make strict ByteStrings an instance of Stream with Char -- token type. module Text.Parsec.ByteString type Parser = Parsec ByteString () type GenParser t st = Parsec ByteString st -- | parseFromFile p filePath runs a strict bytestring parser -- p on the input read from filePath using -- readFile. Returns either a ParseError (Left) or a -- value of type a (Right). -- --
--   main    = do{ result <- parseFromFile numbers "digits.txt"
--               ; case result of
--                   Left err  -> print err
--                   Right xs  -> print (sum xs)
--               }
--   
parseFromFile :: Parser a -> String -> IO (Either ParseError a) instance Monad m => Stream ByteString m Char -- | Make lazy ByteStrings an instance of Stream with Char -- token type. module Text.Parsec.ByteString.Lazy type Parser = Parsec ByteString () type GenParser t st = Parsec ByteString st -- | parseFromFile p filePath runs a lazy bytestring parser -- p on the input read from filePath using -- readFile. Returns either a ParseError (Left) or a -- value of type a (Right). -- --
--   main    = do{ result <- parseFromFile numbers "digits.txt"
--               ; case result of
--                   Left err  -> print err
--                   Right xs  -> print (sum xs)
--               }
--   
parseFromFile :: Parser a -> String -> IO (Either ParseError a) instance Monad m => Stream ByteString m Char -- | Make Text an instance of Stream with Char token type. module Text.Parsec.Text type Parser = Parsec Text () type GenParser st = Parsec Text st instance Monad m => Stream Text m Char -- | Make Text an instance of Stream with Char token type. module Text.Parsec.Text.Lazy type Parser = Parsec Text () type GenParser st = Parsec Text st instance Monad m => Stream Text m Char -- | A helper module to parse lexical elements (tokens). See -- makeTokenParser for a description of how to use it. module Text.Parsec.Token type LanguageDef st = GenLanguageDef String st Identity -- | The GenLanguageDef type is a record that contains all -- parameterizable features of the Token module. The module -- Language contains some default definitions. data GenLanguageDef s u m LanguageDef :: String -> String -> String -> Bool -> ParsecT s u m Char -> ParsecT s u m Char -> ParsecT s u m Char -> ParsecT s u m Char -> [String] -> [String] -> Bool -> GenLanguageDef s u m -- | Describes the start of a block comment. Use the empty string if the -- language doesn't support block comments. For example "/*". commentStart :: GenLanguageDef s u m -> String -- | Describes the end of a block comment. Use the empty string if the -- language doesn't support block comments. For example "*/". commentEnd :: GenLanguageDef s u m -> String -- | Describes the start of a line comment. Use the empty string if the -- language doesn't support line comments. For example "//". commentLine :: GenLanguageDef s u m -> String -- | Set to True if the language supports nested block comments. nestedComments :: GenLanguageDef s u m -> Bool -- | This parser should accept any start characters of identifiers. For -- example letter <|> char "_". identStart :: GenLanguageDef s u m -> ParsecT s u m Char -- | This parser should accept any legal tail characters of identifiers. -- For example alphaNum <|> char "_". identLetter :: GenLanguageDef s u m -> ParsecT s u m Char -- | This parser should accept any start characters of operators. For -- example oneOf ":!#$%&*+./<=>?@\\^|-~" opStart :: GenLanguageDef s u m -> ParsecT s u m Char -- | This parser should accept any legal tail characters of operators. Note -- that this parser should even be defined if the language doesn't -- support user-defined operators, or otherwise the reservedOp -- parser won't work correctly. opLetter :: GenLanguageDef s u m -> ParsecT s u m Char -- | The list of reserved identifiers. reservedNames :: GenLanguageDef s u m -> [String] -- | The list of reserved operators. reservedOpNames :: GenLanguageDef s u m -> [String] -- | Set to True if the language is case sensitive. caseSensitive :: GenLanguageDef s u m -> Bool type TokenParser st = GenTokenParser String st Identity -- | The type of the record that holds lexical parsers that work on -- s streams with state u over a monad m. data GenTokenParser s u m TokenParser :: ParsecT s u m String -> (String -> ParsecT s u m ()) -> ParsecT s u m String -> (String -> ParsecT s u m ()) -> ParsecT s u m Char -> ParsecT s u m String -> ParsecT s u m Integer -> ParsecT s u m Integer -> ParsecT s u m Double -> ParsecT s u m (Either Integer Double) -> ParsecT s u m Integer -> ParsecT s u m Integer -> ParsecT s u m Integer -> (String -> ParsecT s u m String) -> (forall a. ParsecT s u m a -> ParsecT s u m a) -> ParsecT s u m () -> (forall a. ParsecT s u m a -> ParsecT s u m a) -> (forall a. ParsecT s u m a -> ParsecT s u m a) -> (forall a. ParsecT s u m a -> ParsecT s u m a) -> (forall a. ParsecT s u m a -> ParsecT s u m a) -> (forall a. ParsecT s u m a -> ParsecT s u m a) -> ParsecT s u m String -> ParsecT s u m String -> ParsecT s u m String -> ParsecT s u m String -> (forall a. ParsecT s u m a -> ParsecT s u m [a]) -> (forall a. ParsecT s u m a -> ParsecT s u m [a]) -> (forall a. ParsecT s u m a -> ParsecT s u m [a]) -> (forall a. ParsecT s u m a -> ParsecT s u m [a]) -> GenTokenParser s u m -- | This lexeme parser parses a legal identifier. Returns the identifier -- string. This parser will fail on identifiers that are reserved words. -- Legal identifier (start) characters and reserved words are defined in -- the LanguageDef that is passed to makeTokenParser. An -- identifier is treated as a single token using try. identifier :: GenTokenParser s u m -> ParsecT s u m String -- | The lexeme parser reserved name parses symbol name, -- but it also checks that the name is not a prefix of a valid -- identifier. A reserved word is treated as a single token -- using try. reserved :: GenTokenParser s u m -> String -> ParsecT s u m () -- | This lexeme parser parses a legal operator. Returns the name of the -- operator. This parser will fail on any operators that are reserved -- operators. Legal operator (start) characters and reserved operators -- are defined in the LanguageDef that is passed to -- makeTokenParser. An operator is treated as a single -- token using try. operator :: GenTokenParser s u m -> ParsecT s u m String -- | The lexeme parser reservedOp name parses symbol -- name, but it also checks that the name is not a prefix -- of a valid operator. A reservedOp is treated as a single -- token using try. reservedOp :: GenTokenParser s u m -> String -> ParsecT s u m () -- | This lexeme parser parses a single literal character. Returns the -- literal character value. This parsers deals correctly with escape -- sequences. The literal character is parsed according to the grammar -- rules defined in the Haskell report (which matches most programming -- languages quite closely). charLiteral :: GenTokenParser s u m -> ParsecT s u m Char -- | This lexeme parser parses a literal string. Returns the literal string -- value. This parsers deals correctly with escape sequences and gaps. -- The literal string is parsed according to the grammar rules defined in -- the Haskell report (which matches most programming languages quite -- closely). stringLiteral :: GenTokenParser s u m -> ParsecT s u m String -- | This lexeme parser parses a natural number (a positive whole number). -- Returns the value of the number. The number can be specified in -- decimal, hexadecimal or octal. The number is -- parsed according to the grammar rules in the Haskell report. natural :: GenTokenParser s u m -> ParsecT s u m Integer -- | This lexeme parser parses an integer (a whole number). This parser is -- like natural except that it can be prefixed with sign (i.e. '-' -- or '+'). Returns the value of the number. The number can be specified -- in decimal, hexadecimal or octal. The number is -- parsed according to the grammar rules in the Haskell report. integer :: GenTokenParser s u m -> ParsecT s u m Integer -- | This lexeme parser parses a floating point value. Returns the value of -- the number. The number is parsed according to the grammar rules -- defined in the Haskell report. float :: GenTokenParser s u m -> ParsecT s u m Double -- | This lexeme parser parses either natural or a float. -- Returns the value of the number. This parsers deals with any overlap -- in the grammar rules for naturals and floats. The number is parsed -- according to the grammar rules defined in the Haskell report. naturalOrFloat :: GenTokenParser s u m -> ParsecT s u m (Either Integer Double) -- | Parses a positive whole number in the decimal system. Returns the -- value of the number. decimal :: GenTokenParser s u m -> ParsecT s u m Integer -- | Parses a positive whole number in the hexadecimal system. The number -- should be prefixed with "0x" or "0X". Returns the value of the number. hexadecimal :: GenTokenParser s u m -> ParsecT s u m Integer -- | Parses a positive whole number in the octal system. The number should -- be prefixed with "0o" or "0O". Returns the value of the number. octal :: GenTokenParser s u m -> ParsecT s u m Integer -- | Lexeme parser symbol s parses string s and -- skips trailing white space. symbol :: GenTokenParser s u m -> String -> ParsecT s u m String -- | lexeme p first applies parser p and than the -- whiteSpace parser, returning the value of p. Every -- lexical token (lexeme) is defined using lexeme, this way -- every parse starts at a point without white space. Parsers that use -- lexeme are called lexeme parsers in this document. -- -- The only point where the whiteSpace parser should be called -- explicitly is the start of the main parser in order to skip any -- leading white space. -- --
--   mainParser  = do{ whiteSpace
--                    ; ds <- many (lexeme digit)
--                    ; eof
--                    ; return (sum ds)
--                    }
--   
lexeme :: GenTokenParser s u m -> forall a. ParsecT s u m a -> ParsecT s u m a -- | Parses any white space. White space consists of zero or more -- occurrences of a space, a line comment or a block (multi line) -- comment. Block comments may be nested. How comments are started and -- ended is defined in the LanguageDef that is passed to -- makeTokenParser. whiteSpace :: GenTokenParser s u m -> ParsecT s u m () -- | Lexeme parser parens p parses p enclosed in -- parenthesis, returning the value of p. parens :: GenTokenParser s u m -> forall a. ParsecT s u m a -> ParsecT s u m a -- | Lexeme parser braces p parses p enclosed in braces -- ('{' and '}'), returning the value of p. braces :: GenTokenParser s u m -> forall a. ParsecT s u m a -> ParsecT s u m a -- | Lexeme parser angles p parses p enclosed in angle -- brackets ('<' and '>'), returning the value of p. angles :: GenTokenParser s u m -> forall a. ParsecT s u m a -> ParsecT s u m a -- | Lexeme parser brackets p parses p enclosed in -- brackets ('[' and ']'), returning the value of p. brackets :: GenTokenParser s u m -> forall a. ParsecT s u m a -> ParsecT s u m a -- | DEPRECATED: Use brackets. squares :: GenTokenParser s u m -> forall a. ParsecT s u m a -> ParsecT s u m a -- | Lexeme parser |semi| parses the character ';' and skips any trailing -- white space. Returns the string ";". semi :: GenTokenParser s u m -> ParsecT s u m String -- | Lexeme parser comma parses the character ',' and skips any -- trailing white space. Returns the string ",". comma :: GenTokenParser s u m -> ParsecT s u m String -- | Lexeme parser colon parses the character ':' and skips any -- trailing white space. Returns the string ":". colon :: GenTokenParser s u m -> ParsecT s u m String -- | Lexeme parser dot parses the character '.' and skips any -- trailing white space. Returns the string ".". dot :: GenTokenParser s u m -> ParsecT s u m String -- | Lexeme parser semiSep p parses zero or more -- occurrences of p separated by semi. Returns a list of -- values returned by p. semiSep :: GenTokenParser s u m -> forall a. ParsecT s u m a -> ParsecT s u m [a] -- | Lexeme parser semiSep1 p parses one or more -- occurrences of p separated by semi. Returns a list of -- values returned by p. semiSep1 :: GenTokenParser s u m -> forall a. ParsecT s u m a -> ParsecT s u m [a] -- | Lexeme parser commaSep p parses zero or more -- occurrences of p separated by comma. Returns a list of -- values returned by p. commaSep :: GenTokenParser s u m -> forall a. ParsecT s u m a -> ParsecT s u m [a] -- | Lexeme parser commaSep1 p parses one or more -- occurrences of p separated by comma. Returns a list of -- values returned by p. commaSep1 :: GenTokenParser s u m -> forall a. ParsecT s u m a -> ParsecT s u m [a] -- | The expression makeTokenParser language creates a -- GenTokenParser record that contains lexical parsers that are -- defined using the definitions in the language record. -- -- The use of this function is quite stylized - one imports the -- appropiate language definition and selects the lexical parsers that -- are needed from the resulting GenTokenParser. -- --
--   module Main where
--   
--   import Text.Parsec
--   import qualified Text.Parsec.Token as P
--   import Text.Parsec.Language (haskellDef)
--   
--   -- The parser
--   ...
--   
--   expr  =   parens expr
--         <|> identifier
--         <|> ...
--        
--   
--   -- The lexer
--   lexer       = P.makeTokenParser haskellDef    
--       
--   parens      = P.parens lexer
--   braces      = P.braces lexer
--   identifier  = P.identifier lexer
--   reserved    = P.reserved lexer
--   ...
--   
makeTokenParser :: Stream s m Char => GenLanguageDef s u m -> GenTokenParser s u m -- | Parsec compatibility module module Text.ParserCombinators.Parsec.Token type LanguageDef st = GenLanguageDef String st Identity -- | The GenLanguageDef type is a record that contains all -- parameterizable features of the Token module. The module -- Language contains some default definitions. data GenLanguageDef s u m LanguageDef :: String -> String -> String -> Bool -> ParsecT s u m Char -> ParsecT s u m Char -> ParsecT s u m Char -> ParsecT s u m Char -> [String] -> [String] -> Bool -> GenLanguageDef s u m -- | Describes the start of a block comment. Use the empty string if the -- language doesn't support block comments. For example "/*". commentStart :: GenLanguageDef s u m -> String -- | Describes the end of a block comment. Use the empty string if the -- language doesn't support block comments. For example "*/". commentEnd :: GenLanguageDef s u m -> String -- | Describes the start of a line comment. Use the empty string if the -- language doesn't support line comments. For example "//". commentLine :: GenLanguageDef s u m -> String -- | Set to True if the language supports nested block comments. nestedComments :: GenLanguageDef s u m -> Bool -- | This parser should accept any start characters of identifiers. For -- example letter <|> char "_". identStart :: GenLanguageDef s u m -> ParsecT s u m Char -- | This parser should accept any legal tail characters of identifiers. -- For example alphaNum <|> char "_". identLetter :: GenLanguageDef s u m -> ParsecT s u m Char -- | This parser should accept any start characters of operators. For -- example oneOf ":!#$%&*+./<=>?@\\^|-~" opStart :: GenLanguageDef s u m -> ParsecT s u m Char -- | This parser should accept any legal tail characters of operators. Note -- that this parser should even be defined if the language doesn't -- support user-defined operators, or otherwise the reservedOp -- parser won't work correctly. opLetter :: GenLanguageDef s u m -> ParsecT s u m Char -- | The list of reserved identifiers. reservedNames :: GenLanguageDef s u m -> [String] -- | The list of reserved operators. reservedOpNames :: GenLanguageDef s u m -> [String] -- | Set to True if the language is case sensitive. caseSensitive :: GenLanguageDef s u m -> Bool type TokenParser st = GenTokenParser String st Identity -- | The type of the record that holds lexical parsers that work on -- s streams with state u over a monad m. data GenTokenParser s u m TokenParser :: ParsecT s u m String -> (String -> ParsecT s u m ()) -> ParsecT s u m String -> (String -> ParsecT s u m ()) -> ParsecT s u m Char -> ParsecT s u m String -> ParsecT s u m Integer -> ParsecT s u m Integer -> ParsecT s u m Double -> ParsecT s u m (Either Integer Double) -> ParsecT s u m Integer -> ParsecT s u m Integer -> ParsecT s u m Integer -> (String -> ParsecT s u m String) -> (forall a. ParsecT s u m a -> ParsecT s u m a) -> ParsecT s u m () -> (forall a. ParsecT s u m a -> ParsecT s u m a) -> (forall a. ParsecT s u m a -> ParsecT s u m a) -> (forall a. ParsecT s u m a -> ParsecT s u m a) -> (forall a. ParsecT s u m a -> ParsecT s u m a) -> (forall a. ParsecT s u m a -> ParsecT s u m a) -> ParsecT s u m String -> ParsecT s u m String -> ParsecT s u m String -> ParsecT s u m String -> (forall a. ParsecT s u m a -> ParsecT s u m [a]) -> (forall a. ParsecT s u m a -> ParsecT s u m [a]) -> (forall a. ParsecT s u m a -> ParsecT s u m [a]) -> (forall a. ParsecT s u m a -> ParsecT s u m [a]) -> GenTokenParser s u m -- | This lexeme parser parses a legal identifier. Returns the identifier -- string. This parser will fail on identifiers that are reserved words. -- Legal identifier (start) characters and reserved words are defined in -- the LanguageDef that is passed to makeTokenParser. An -- identifier is treated as a single token using try. identifier :: GenTokenParser s u m -> ParsecT s u m String -- | The lexeme parser reserved name parses symbol name, -- but it also checks that the name is not a prefix of a valid -- identifier. A reserved word is treated as a single token -- using try. reserved :: GenTokenParser s u m -> String -> ParsecT s u m () -- | This lexeme parser parses a legal operator. Returns the name of the -- operator. This parser will fail on any operators that are reserved -- operators. Legal operator (start) characters and reserved operators -- are defined in the LanguageDef that is passed to -- makeTokenParser. An operator is treated as a single -- token using try. operator :: GenTokenParser s u m -> ParsecT s u m String -- | The lexeme parser reservedOp name parses symbol -- name, but it also checks that the name is not a prefix -- of a valid operator. A reservedOp is treated as a single -- token using try. reservedOp :: GenTokenParser s u m -> String -> ParsecT s u m () -- | This lexeme parser parses a single literal character. Returns the -- literal character value. This parsers deals correctly with escape -- sequences. The literal character is parsed according to the grammar -- rules defined in the Haskell report (which matches most programming -- languages quite closely). charLiteral :: GenTokenParser s u m -> ParsecT s u m Char -- | This lexeme parser parses a literal string. Returns the literal string -- value. This parsers deals correctly with escape sequences and gaps. -- The literal string is parsed according to the grammar rules defined in -- the Haskell report (which matches most programming languages quite -- closely). stringLiteral :: GenTokenParser s u m -> ParsecT s u m String -- | This lexeme parser parses a natural number (a positive whole number). -- Returns the value of the number. The number can be specified in -- decimal, hexadecimal or octal. The number is -- parsed according to the grammar rules in the Haskell report. natural :: GenTokenParser s u m -> ParsecT s u m Integer -- | This lexeme parser parses an integer (a whole number). This parser is -- like natural except that it can be prefixed with sign (i.e. '-' -- or '+'). Returns the value of the number. The number can be specified -- in decimal, hexadecimal or octal. The number is -- parsed according to the grammar rules in the Haskell report. integer :: GenTokenParser s u m -> ParsecT s u m Integer -- | This lexeme parser parses a floating point value. Returns the value of -- the number. The number is parsed according to the grammar rules -- defined in the Haskell report. float :: GenTokenParser s u m -> ParsecT s u m Double -- | This lexeme parser parses either natural or a float. -- Returns the value of the number. This parsers deals with any overlap -- in the grammar rules for naturals and floats. The number is parsed -- according to the grammar rules defined in the Haskell report. naturalOrFloat :: GenTokenParser s u m -> ParsecT s u m (Either Integer Double) -- | Parses a positive whole number in the decimal system. Returns the -- value of the number. decimal :: GenTokenParser s u m -> ParsecT s u m Integer -- | Parses a positive whole number in the hexadecimal system. The number -- should be prefixed with "0x" or "0X". Returns the value of the number. hexadecimal :: GenTokenParser s u m -> ParsecT s u m Integer -- | Parses a positive whole number in the octal system. The number should -- be prefixed with "0o" or "0O". Returns the value of the number. octal :: GenTokenParser s u m -> ParsecT s u m Integer -- | Lexeme parser symbol s parses string s and -- skips trailing white space. symbol :: GenTokenParser s u m -> String -> ParsecT s u m String -- | lexeme p first applies parser p and than the -- whiteSpace parser, returning the value of p. Every -- lexical token (lexeme) is defined using lexeme, this way -- every parse starts at a point without white space. Parsers that use -- lexeme are called lexeme parsers in this document. -- -- The only point where the whiteSpace parser should be called -- explicitly is the start of the main parser in order to skip any -- leading white space. -- --
--   mainParser  = do{ whiteSpace
--                    ; ds <- many (lexeme digit)
--                    ; eof
--                    ; return (sum ds)
--                    }
--   
lexeme :: GenTokenParser s u m -> forall a. ParsecT s u m a -> ParsecT s u m a -- | Parses any white space. White space consists of zero or more -- occurrences of a space, a line comment or a block (multi line) -- comment. Block comments may be nested. How comments are started and -- ended is defined in the LanguageDef that is passed to -- makeTokenParser. whiteSpace :: GenTokenParser s u m -> ParsecT s u m () -- | Lexeme parser parens p parses p enclosed in -- parenthesis, returning the value of p. parens :: GenTokenParser s u m -> forall a. ParsecT s u m a -> ParsecT s u m a -- | Lexeme parser braces p parses p enclosed in braces -- ('{' and '}'), returning the value of p. braces :: GenTokenParser s u m -> forall a. ParsecT s u m a -> ParsecT s u m a -- | Lexeme parser angles p parses p enclosed in angle -- brackets ('<' and '>'), returning the value of p. angles :: GenTokenParser s u m -> forall a. ParsecT s u m a -> ParsecT s u m a -- | Lexeme parser brackets p parses p enclosed in -- brackets ('[' and ']'), returning the value of p. brackets :: GenTokenParser s u m -> forall a. ParsecT s u m a -> ParsecT s u m a -- | DEPRECATED: Use brackets. squares :: GenTokenParser s u m -> forall a. ParsecT s u m a -> ParsecT s u m a -- | Lexeme parser |semi| parses the character ';' and skips any trailing -- white space. Returns the string ";". semi :: GenTokenParser s u m -> ParsecT s u m String -- | Lexeme parser comma parses the character ',' and skips any -- trailing white space. Returns the string ",". comma :: GenTokenParser s u m -> ParsecT s u m String -- | Lexeme parser colon parses the character ':' and skips any -- trailing white space. Returns the string ":". colon :: GenTokenParser s u m -> ParsecT s u m String -- | Lexeme parser dot parses the character '.' and skips any -- trailing white space. Returns the string ".". dot :: GenTokenParser s u m -> ParsecT s u m String -- | Lexeme parser semiSep p parses zero or more -- occurrences of p separated by semi. Returns a list of -- values returned by p. semiSep :: GenTokenParser s u m -> forall a. ParsecT s u m a -> ParsecT s u m [a] -- | Lexeme parser semiSep1 p parses one or more -- occurrences of p separated by semi. Returns a list of -- values returned by p. semiSep1 :: GenTokenParser s u m -> forall a. ParsecT s u m a -> ParsecT s u m [a] -- | Lexeme parser commaSep p parses zero or more -- occurrences of p separated by comma. Returns a list of -- values returned by p. commaSep :: GenTokenParser s u m -> forall a. ParsecT s u m a -> ParsecT s u m [a] -- | Lexeme parser commaSep1 p parses one or more -- occurrences of p separated by comma. Returns a list of -- values returned by p. commaSep1 :: GenTokenParser s u m -> forall a. ParsecT s u m a -> ParsecT s u m [a] -- | The expression makeTokenParser language creates a -- GenTokenParser record that contains lexical parsers that are -- defined using the definitions in the language record. -- -- The use of this function is quite stylized - one imports the -- appropiate language definition and selects the lexical parsers that -- are needed from the resulting GenTokenParser. -- --
--   module Main where
--   
--   import Text.Parsec
--   import qualified Text.Parsec.Token as P
--   import Text.Parsec.Language (haskellDef)
--   
--   -- The parser
--   ...
--   
--   expr  =   parens expr
--         <|> identifier
--         <|> ...
--        
--   
--   -- The lexer
--   lexer       = P.makeTokenParser haskellDef    
--       
--   parens      = P.parens lexer
--   braces      = P.braces lexer
--   identifier  = P.identifier lexer
--   reserved    = P.reserved lexer
--   ...
--   
makeTokenParser :: Stream s m Char => GenLanguageDef s u m -> GenTokenParser s u m -- | A helper module to parse "expressions". Builds a parser given a table -- of operators and associativities. module Text.Parsec.Expr -- | This data type specifies the associativity of operators: left, right -- or none. data Assoc AssocNone :: Assoc AssocLeft :: Assoc AssocRight :: Assoc -- | 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 s u m a Infix :: (ParsecT s u m (a -> a -> a)) -> Assoc -> Operator s u m a Prefix :: (ParsecT s u m (a -> a)) -> Operator s u m a Postfix :: (ParsecT s u m (a -> a)) -> Operator s u m a -- | An OperatorTable s u m a is a list of Operator s u m -- a lists. The list is ordered in descending precedence. All -- operators in one list have the same precedence (but may have a -- different associativity). type OperatorTable s u m a = [[Operator s u m a]] -- | buildExpressionParser table term builds an expression parser -- for terms term with operators from table, taking the -- associativity and precedence specified in table into account. -- Prefix and postfix operators of the same precedence can only occur -- once (i.e. --2 is not allowed if - is prefix -- negate). Prefix and postfix operators of the same precedence associate -- to the left (i.e. if ++ is postfix increment, than -- -2++ equals -1, not -3). -- -- The buildExpressionParser takes care of all the complexity -- involved in building expression parser. Here is an example of an -- expression parser that handles prefix signs, postfix increment and -- basic arithmetic. -- --
--   expr    = buildExpressionParser table term
--           <?> "expression"
--   
--   term    =  parens expr 
--           <|> natural
--           <?> "simple expression"
--   
--   table   = [ [prefix "-" negate, prefix "+" id ]
--             , [postfix "++" (+1)]
--             , [binary "*" (*) AssocLeft, binary "/" (div) AssocLeft ]
--             , [binary "+" (+) AssocLeft, binary "-" (-)   AssocLeft ]
--             ]
--           
--   binary  name fun assoc = Infix (do{ reservedOp name; return fun }) assoc
--   prefix  name fun       = Prefix (do{ reservedOp name; return fun })
--   postfix name fun       = Postfix (do{ reservedOp name; return fun })
--   
buildExpressionParser :: Stream s m t => OperatorTable s u m a -> ParsecT s u m a -> ParsecT s u m a -- | Parsec compatibility module module Text.ParserCombinators.Parsec.Prim -- | The parser p ? msg behaves as parser p, but -- whenever the parser p fails without consuming any -- input, it replaces expect error messages with the expect error -- message msg. -- -- This is normally used at the end of a set alternatives where we want -- to return an error message in terms of a higher level construct rather -- than returning all possible characters. For example, if the -- expr parser from the try example would fail, the error -- message is: '...: expecting expression'. Without the -- (<?>) combinator, the message would be like '...: -- expecting "let" or letter', which is less friendly. () :: (ParsecT s u m a) -> String -> (ParsecT s u m a) -- | This combinator implements choice. The parser p <|> q -- first applies p. If it succeeds, the value of p is -- returned. If p fails without consuming any input, -- parser q is tried. This combinator is defined equal to the -- mplus member of the MonadPlus class and the -- (<|>) member of Alternative. -- -- The parser is called predictive since q is only tried -- when parser p didn't consume any input (i.e.. the look ahead -- is 1). This non-backtracking behaviour allows for both an efficient -- implementation of the parser combinators and the generation of good -- error messages. (<|>) :: (ParsecT s u m a) -> (ParsecT s u m a) -> (ParsecT s u m a) type Parser = Parsec String () type GenParser tok st = Parsec [tok] st runParser :: GenParser tok st a -> st -> SourceName -> [tok] -> Either ParseError a -- | parse p filePath input runs a parser p over Identity -- without user state. The filePath is only used in error -- messages and may be the empty string. Returns either a -- ParseError (Left) or a value of type a -- (Right). -- --
--   main    = case (parse numbers "" "11, 2, 43") of
--              Left err  -> print err
--              Right xs  -> print (sum xs)
--   
--   numbers = commaSep integer
--   
parse :: Stream s Identity t => Parsec s () a -> SourceName -> s -> Either ParseError a -- | parseFromFile p filePath runs a string parser p on -- the input read from filePath using readFile. Returns -- either a ParseError (Left) or a value of type a -- (Right). -- --
--   main    = do{ result <- parseFromFile numbers "digits.txt"
--               ; case result of
--                   Left err  -> print err
--                   Right xs  -> print (sum xs)
--               }
--   
parseFromFile :: Parser a -> String -> IO (Either ParseError a) -- | The expression parseTest p input applies a parser p -- against input input and prints the result to stdout. Used for -- testing parsers. parseTest :: (Stream s Identity t, Show a) => Parsec s () a -> s -> IO () -- | The parser token showTok posFromTok testTok accepts a token -- t with result x when the function testTok t -- returns Just x. The source position of the t -- should be returned by posFromTok t and the token can be shown -- using showTok t. -- -- This combinator is expressed in terms of tokenPrim. It is used -- to accept user defined token streams. For example, suppose that we -- have a stream of basic tokens tupled with source positions. We can -- than define a parser that accepts single tokens as: -- --
--   mytoken x
--     = token showTok posFromTok testTok
--     where
--       showTok (pos,t)     = show t
--       posFromTok (pos,t)  = pos
--       testTok (pos,t)     = if x == t then Just t else Nothing
--   
token :: Stream s Identity t => (t -> String) -> (t -> SourcePos) -> (t -> Maybe a) -> Parsec s u a tokens :: (Stream s m t, Eq t) => ([t] -> String) -> (SourcePos -> [t] -> SourcePos) -> [t] -> ParsecT s u m [t] -- | The parser tokenPrim showTok nextPos testTok accepts a token -- t with result x when the function testTok t -- returns Just x. The token can be shown using -- showTok t. The position of the next token should be -- returned when nextPos is called with the current source -- position pos, the current token t and the rest of -- the tokens toks, nextPos pos t toks. -- -- This is the most primitive combinator for accepting tokens. For -- example, the char parser could be implemented as: -- --
--   char c
--     = tokenPrim showChar nextPos testChar
--     where
--       showChar x        = "'" ++ x ++ "'"
--       testChar x        = if x == c then Just x else Nothing
--       nextPos pos x xs  = updatePosChar pos x
--   
tokenPrim :: Stream s m t => (t -> String) -> (SourcePos -> t -> s -> SourcePos) -> (t -> Maybe a) -> ParsecT s u m a tokenPrimEx :: Stream s m t => (t -> String) -> (SourcePos -> t -> s -> SourcePos) -> Maybe (SourcePos -> t -> s -> u -> u) -> (t -> Maybe a) -> ParsecT s u m a try :: GenParser tok st a -> GenParser tok st a label :: ParsecT s u m a -> String -> ParsecT s u m a labels :: ParsecT s u m a -> [String] -> ParsecT s u m a -- | The parser unexpected msg always fails with an unexpected -- error message msg without consuming any input. -- -- The parsers fail, (<?>) and unexpected -- are the three parsers used to generate error messages. Of these, only -- (<?>) is commonly used. For an example of the use of -- unexpected, see the definition of notFollowedBy. unexpected :: Stream s m t => String -> ParsecT s u m a pzero :: GenParser tok st a -- | many p applies the parser p zero or more -- times. Returns a list of the returned values of p. -- --
--   identifier  = do{ c  <- letter
--                   ; cs <- many (alphaNum <|> char '_')
--                   ; return (c:cs)
--                   }
--   
many :: ParsecT s u m a -> ParsecT s u m [a] -- | skipMany p applies the parser p zero or more -- times, skipping its result. -- --
--   spaces  = skipMany space
--   
skipMany :: ParsecT s u m a -> ParsecT s u m () -- | Returns the current user state. getState :: Monad m => ParsecT s u m u -- | An alias for putState for backwards compatibility. setState :: Monad m => u -> ParsecT s u m () -- | An alias for modifyState for backwards compatibility. updateState :: Monad m => (u -> u) -> ParsecT s u m () -- | Returns the current source position. See also SourcePos. getPosition :: Monad m => ParsecT s u m SourcePos -- | setPosition pos sets the current source position to -- pos. setPosition :: Monad m => SourcePos -> ParsecT s u m () -- | Returns the current input getInput :: Monad m => ParsecT s u m s -- | setInput input continues parsing with input. The -- getInput and setInput functions can for example be -- used to deal with #include files. setInput :: Monad m => s -> ParsecT s u m () data State s u State :: s -> !SourcePos -> !u -> State s u stateInput :: State s u -> s statePos :: State s u -> !SourcePos stateUser :: State s u -> !u -- | Returns the full parser state as a State record. getParserState :: Monad m => ParsecT s u m (State s u) -- | setParserState st set the full parser state to st. setParserState :: Monad m => State s u -> ParsecT s u m (State s u) -- | Parsec compatibility module module Text.ParserCombinators.Parsec -- | The abstract data type ParseError represents parse errors. It -- provides the source position (SourcePos) of the error and a -- list of error messages (Message). A ParseError can be -- returned by the function parse. ParseError is an -- instance of the Show class. data ParseError -- | Extracts the source position from the parse error errorPos :: ParseError -> SourcePos -- | The abstract data type SourcePos represents source positions. -- It contains the name of the source (i.e. file name), a line number and -- a column number. SourcePos is an instance of the Show, -- Eq and Ord class. data SourcePos type SourceName = String type Line = Int type Column = Int -- | Extracts the name of the source from a source position. sourceName :: SourcePos -> SourceName -- | Extracts the line number from a source position. sourceLine :: SourcePos -> Line -- | Extracts the column number from a source position. sourceColumn :: SourcePos -> Column -- | Increments the line number of a source position. incSourceLine :: SourcePos -> Line -> SourcePos -- | Increments the column number of a source position. incSourceColumn :: SourcePos -> Column -> SourcePos -- | Set the line number of a source position. setSourceLine :: SourcePos -> Line -> SourcePos -- | Set the column number of a source position. setSourceColumn :: SourcePos -> Column -> SourcePos -- | Set the name of the source. setSourceName :: SourcePos -> SourceName -> SourcePos -- | Parsec compatibility module module Text.ParserCombinators.Parsec.Expr -- | This data type specifies the associativity of operators: left, right -- or none. data Assoc AssocNone :: Assoc AssocLeft :: Assoc AssocRight :: Assoc data Operator tok st a Infix :: (GenParser tok st (a -> a -> a)) -> Assoc -> Operator tok st a Prefix :: (GenParser tok st (a -> a)) -> Operator tok st a Postfix :: (GenParser tok st (a -> a)) -> Operator tok st a type OperatorTable tok st a = [[Operator tok st a]] buildExpressionParser :: OperatorTable tok st a -> GenParser tok st a -> GenParser tok st a module Text.Parsec -- | The abstract data type ParseError represents parse errors. It -- provides the source position (SourcePos) of the error and a -- list of error messages (Message). A ParseError can be -- returned by the function parse. ParseError is an -- instance of the Show class. data ParseError -- | Extracts the source position from the parse error errorPos :: ParseError -> SourcePos -- | The abstract data type SourcePos represents source positions. -- It contains the name of the source (i.e. file name), a line number and -- a column number. SourcePos is an instance of the Show, -- Eq and Ord class. data SourcePos type SourceName = String type Line = Int type Column = Int -- | Extracts the name of the source from a source position. sourceName :: SourcePos -> SourceName -- | Extracts the line number from a source position. sourceLine :: SourcePos -> Line -- | Extracts the column number from a source position. sourceColumn :: SourcePos -> Column -- | Increments the line number of a source position. incSourceLine :: SourcePos -> Line -> SourcePos -- | Increments the column number of a source position. incSourceColumn :: SourcePos -> Column -> SourcePos -- | Set the line number of a source position. setSourceLine :: SourcePos -> Line -> SourcePos -- | Set the column number of a source position. setSourceColumn :: SourcePos -> Column -> SourcePos -- | Set the name of the source. setSourceName :: SourcePos -> SourceName -> SourcePos -- | A helper module that defines some language definitions that can be -- used to instantiate a token parser (see Text.Parsec.Token). module Text.Parsec.Language -- | The language definition for the Haskell language. haskellDef :: LanguageDef st -- | A lexer for the haskell language. haskell :: TokenParser st -- | The language definition for the language Mondrian. mondrianDef :: LanguageDef st -- | A lexer for the mondrian language. mondrian :: TokenParser st emptyDef :: LanguageDef st -- | This is a minimal token definition for Haskell style languages. It -- defines the style of comments, valid identifiers and case sensitivity. -- It does not define any reserved words or operators. haskellStyle :: LanguageDef st -- | This is a minimal token definition for Java style languages. It -- defines the style of comments, valid identifiers and case sensitivity. -- It does not define any reserved words or operators. javaStyle :: LanguageDef st type LanguageDef st = GenLanguageDef String st Identity -- | The GenLanguageDef type is a record that contains all -- parameterizable features of the Token module. The module -- Language contains some default definitions. data GenLanguageDef s u m -- | Parsec compatibility module module Text.ParserCombinators.Parsec.Language -- | The language definition for the Haskell language. haskellDef :: LanguageDef st -- | A lexer for the haskell language. haskell :: TokenParser st -- | The language definition for the language Mondrian. mondrianDef :: LanguageDef st -- | A lexer for the mondrian language. mondrian :: TokenParser st emptyDef :: LanguageDef st -- | This is a minimal token definition for Haskell style languages. It -- defines the style of comments, valid identifiers and case sensitivity. -- It does not define any reserved words or operators. haskellStyle :: LanguageDef st -- | This is a minimal token definition for Java style languages. It -- defines the style of comments, valid identifiers and case sensitivity. -- It does not define any reserved words or operators. javaStyle :: LanguageDef st type LanguageDef st = GenLanguageDef String st Identity -- | The GenLanguageDef type is a record that contains all -- parameterizable features of the Token module. The module -- Language contains some default definitions. data GenLanguageDef s u m LanguageDef :: String -> String -> String -> Bool -> ParsecT s u m Char -> ParsecT s u m Char -> ParsecT s u m Char -> ParsecT s u m Char -> [String] -> [String] -> Bool -> GenLanguageDef s u m -- | Describes the start of a block comment. Use the empty string if the -- language doesn't support block comments. For example "/*". commentStart :: GenLanguageDef s u m -> String -- | Describes the end of a block comment. Use the empty string if the -- language doesn't support block comments. For example "*/". commentEnd :: GenLanguageDef s u m -> String -- | Describes the start of a line comment. Use the empty string if the -- language doesn't support line comments. For example "//". commentLine :: GenLanguageDef s u m -> String -- | Set to True if the language supports nested block comments. nestedComments :: GenLanguageDef s u m -> Bool -- | This parser should accept any start characters of identifiers. For -- example letter <|> char "_". identStart :: GenLanguageDef s u m -> ParsecT s u m Char -- | This parser should accept any legal tail characters of identifiers. -- For example alphaNum <|> char "_". identLetter :: GenLanguageDef s u m -> ParsecT s u m Char -- | This parser should accept any start characters of operators. For -- example oneOf ":!#$%&*+./<=>?@\\^|-~" opStart :: GenLanguageDef s u m -> ParsecT s u m Char -- | This parser should accept any legal tail characters of operators. Note -- that this parser should even be defined if the language doesn't -- support user-defined operators, or otherwise the reservedOp -- parser won't work correctly. opLetter :: GenLanguageDef s u m -> ParsecT s u m Char -- | The list of reserved identifiers. reservedNames :: GenLanguageDef s u m -> [String] -- | The list of reserved operators. reservedOpNames :: GenLanguageDef s u m -> [String] -- | Set to True if the language is case sensitive. caseSensitive :: GenLanguageDef s u m -> Bool -- | This module implements permutation parsers. The algorithm used is -- fairly complex since we push the type system to its limits :-) 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.Parsec.Perm -- | Provided for backwards compatibility. The tok type is ignored. type PermParser tok st a = StreamPermParser String st a -- | The type StreamPermParser s st a denotes a permutation parser -- that, when converted by the permute function, parses s -- streams with user state st 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 permute. data StreamPermParser s st a -- | The parser permute 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  = permute (tuple <$?> ("",many1 (char 'a'))
--                          <||> char 'b' 
--                          <|?> ('_',char 'c'))
--         where
--           tuple a b c  = (a,b,c)
--   
permute :: Stream s Identity tok => StreamPermParser s st a -> Parsec s st a -- | 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. (<||>) :: Stream s Identity tok => StreamPermParser s st (a -> b) -> Parsec s st a -> StreamPermParser s st b -- | 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. (<$$>) :: Stream s Identity tok => (a -> b) -> Parsec s st a -> StreamPermParser s st b -- | The expression perm <||> (x,p) adds parser p -- to the permutation parser perm. The parser p is -- optional - if it can not be applied, the default value x will -- be used instead. Returns a new permutation parser that includes the -- optional parser p. (<|?>) :: Stream s Identity tok => StreamPermParser s st (a -> b) -> (a, Parsec s st a) -> StreamPermParser s st b -- | The expression f <$?> (x,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 optional - if it can not -- be applied, the default value x will be used instead. (<$?>) :: Stream s Identity tok => (a -> b) -> (a, Parsec s st a) -> StreamPermParser s st b -- | Parsec compatibility module module Text.ParserCombinators.Parsec.Perm -- | Provided for backwards compatibility. The tok type is ignored. type PermParser tok st a = StreamPermParser String st a -- | The parser permute 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  = permute (tuple <$?> ("",many1 (char 'a'))
--                          <||> char 'b' 
--                          <|?> ('_',char 'c'))
--         where
--           tuple a b c  = (a,b,c)
--   
permute :: Stream s Identity tok => StreamPermParser s st a -> Parsec s st a -- | 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. (<||>) :: Stream s Identity tok => StreamPermParser s st (a -> b) -> Parsec s st a -> StreamPermParser s st b -- | 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. (<$$>) :: Stream s Identity tok => (a -> b) -> Parsec s st a -> StreamPermParser s st b -- | The expression perm <||> (x,p) adds parser p -- to the permutation parser perm. The parser p is -- optional - if it can not be applied, the default value x will -- be used instead. Returns a new permutation parser that includes the -- optional parser p. (<|?>) :: Stream s Identity tok => StreamPermParser s st (a -> b) -> (a, Parsec s st a) -> StreamPermParser s st b -- | The expression f <$?> (x,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 optional - if it can not -- be applied, the default value x will be used instead. (<$?>) :: Stream s Identity tok => (a -> b) -> (a, Parsec s st a) -> StreamPermParser s st b