Kawaii-Parser-2.0.0: A simple parsing library.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Parser.Parser

Description

  • Parser
  • Filter
  • Parsing locations
  • Parsing brackets
  • Parsing lists
Synopsis

Documentation

(<+>) :: Eq token => Parser' token t -> Parser' token t -> Parser' token t infixr 3 Source #

Symmetric choice between two parsers that selects the longest match. Note that if both parsers successfully reach the same location it will result in an ambiguity error that, unlike a normal parse error, is not recoverable by backtracking. Also note that you should not attempt to recover a filter error. While this operator is normally associative this property does not hold when ambiguity errors are involved.

data Parse_error' token Source #

Parse errors.

Instances

Instances details
Show token => Show (Parse_error' token) Source # 
Instance details

Defined in Parser.Parser

Methods

showsPrec :: Int -> Parse_error' token -> ShowS #

show :: Parse_error' token -> String #

showList :: [Parse_error' token] -> ShowS #

data Parser' token t Source #

A parser that works on any kind of tokens.

Instances

Instances details
Monad (Parser' token) Source # 
Instance details

Defined in Parser.Parser

Methods

(>>=) :: Parser' token a -> (a -> Parser' token b) -> Parser' token b #

(>>) :: Parser' token a -> Parser' token b -> Parser' token b #

return :: a -> Parser' token a #

Functor (Parser' token) Source # 
Instance details

Defined in Parser.Parser

Methods

fmap :: (a -> b) -> Parser' token a -> Parser' token b #

(<$) :: a -> Parser' token b -> Parser' token a #

Applicative (Parser' token) Source # 
Instance details

Defined in Parser.Parser

Methods

pure :: a -> Parser' token a #

(<*>) :: Parser' token (a -> b) -> Parser' token a -> Parser' token b #

liftA2 :: (a -> b -> c) -> Parser' token a -> Parser' token b -> Parser' token c #

(*>) :: Parser' token a -> Parser' token b -> Parser' token b #

(<*) :: Parser' token a -> Parser' token b -> Parser' token a #

add_location :: Parser' token t -> Parser' token (L t) Source #

Parse something with an added location from the first token.

filter_Parser :: Ord token => String -> (t -> Bool) -> Parser' token t -> Parser' token t Source #

Filter the parse results - for example, restrict an integer parser to positive numbers. You also have to provide an error string. Note that filter errors, unlike token matching errors, are non-recoverable.

fmap_filter_Parser :: Ord token => String -> (t -> Maybe u) -> Parser' token t -> Parser' token u Source #

Filter and transform the parse results. You also have to provide an error string. Note that filter errors, unlike token matching errors, are non-recoverable.

parse :: Eq token => (Char -> char_class) -> (char_class -> Line_and_char -> Line_and_char) -> Tokeniser' char_class token err () -> Parser' token t -> (Parse_error' token -> err) -> String -> Either Error (Either err t) Source #

Parse the text. You have to provide a function that classifies characters, a function that tells how to update the location depending on the character, a tokeniser, a parser and a function that converts parse errors to your preferred type.

parse_brackets :: Parser' token () -> Parser' token () -> Parser' token t -> Parser' token t Source #

Parse a term in brackets.

parse_empty_list :: Parser' token [t] Source #

Returns an empty list.

parse_line_and_char :: Parser' token Line_and_char Source #

Get the current location.

parse_list :: Eq token => Parser' token () -> Parser' token t -> Parser' token [t] Source #

Parse a (possibly empty) list with separators.

parse_many :: Eq token => Parser' token t -> Parser' token [t] Source #

Parse a (possibly empty) list without separators.

parse_non_empty_list :: Eq token => Parser' token () -> Parser' token t -> Parser' token [t] Source #

Parse a non-empty list with separators.

parse_some :: Eq token => Parser' token t -> Parser' token [t] Source #

Parse a non-empty list without separators.

parse_token :: Eq token => token -> String -> Parser' token () Source #

Parse a certain token (for example, a delimiter or a keyword) without returning any results. You also have to provide a string that briefly describes the kind of token that is expected - it is used to provide detailed parse errors.

parse_token' :: Eq token => (token -> Maybe t) -> String -> Parser' token t Source #

Parses tokens that fit a certain pattern and transforms them into something more useful - for example, a string or an integer. You also have to provide a string that briefly describes the kind of token that is expected - it is used to provide detailed parse errors.

write_parse_error :: (token -> String) -> String -> Parse_error' token -> String Source #

Write parse errors. You have to provide a function that converts tokens to strings and the file name.