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

Parser.Tokeniser

Description

  • Tokeniser
Synopsis

Documentation

data Tokeniser' char_class token err t Source #

A tokeniser that works with any kind of custom characters, tokens and errors. The custom character type is useful if you need to classify characters according to their behavior before tokenisation - for example, wrap all operators, letters, delimiters or digits in the same constructor to simplify pattern matching.

Instances

Instances details
Monad (Tokeniser' char_class token err) Source # 
Instance details

Defined in Parser.Tokeniser

Methods

(>>=) :: Tokeniser' char_class token err a -> (a -> Tokeniser' char_class token err b) -> Tokeniser' char_class token err b #

(>>) :: Tokeniser' char_class token err a -> Tokeniser' char_class token err b -> Tokeniser' char_class token err b #

return :: a -> Tokeniser' char_class token err a #

Functor (Tokeniser' char_class token err) Source # 
Instance details

Defined in Parser.Tokeniser

Methods

fmap :: (a -> b) -> Tokeniser' char_class token err a -> Tokeniser' char_class token err b #

(<$) :: a -> Tokeniser' char_class token err b -> Tokeniser' char_class token err a #

Applicative (Tokeniser' char_class token err) Source # 
Instance details

Defined in Parser.Tokeniser

Methods

pure :: a -> Tokeniser' char_class token err a #

(<*>) :: Tokeniser' char_class token err (a -> b) -> Tokeniser' char_class token err a -> Tokeniser' char_class token err b #

liftA2 :: (a -> b -> c) -> Tokeniser' char_class token err a -> Tokeniser' char_class token err b -> Tokeniser' char_class token err c #

(*>) :: Tokeniser' char_class token err a -> Tokeniser' char_class token err b -> Tokeniser' char_class token err b #

(<*) :: Tokeniser' char_class token err a -> Tokeniser' char_class token err b -> Tokeniser' char_class token err a #

data Tokens' token Source #

A sequence of tokens with locations. For internal use in the parser.

Instances

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

Defined in Parser.Tokeniser

Methods

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

show :: Tokens' token -> String #

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

add_token :: token -> Tokeniser' char_class token err () Source #

Add the token to the output. Note that the order of adding tokens is important and you have to add the token before deleting the respective characters to get the correct location.

current_line_and_char :: Tokens' token -> Line_and_char Source #

Get the location of the first token or, if there are none, the end of file. For internal use in the parser.

delete_char :: Tokeniser' char_class token err () Source #

Delete the first character from the remaining text. Automatically updates the location.

gather_token :: (char_class -> Maybe Char) -> (String -> token) -> Tokeniser' char_class token err () Source #

Add a token that consists of several characters - for example, an operator, a word or a number. You have to provide a function that recognises suitable characters and a function that transforms the resulting string into a token.

get_char :: Int -> Tokeniser' char_class token err (Maybe char_class) Source #

Take a look at a character without deleting it. Returns Nothing if the index is negative or if the remaining text is too short.

get_token :: Tokens' token -> Maybe token Source #

Get the first token without deleting it. For internal use in the parser.

take_token :: (token -> Maybe t) -> Tokens' token -> Maybe (t, Tokens' token) Source #

Recognises tokens that fit a certain pattern and transforms them into something more useful - for example, a string or an integer. Returns Nothing if the first token does not fit the pattern, and returns the transformed token and the rest of the sequence if it does fit. For internal use in the parser.

tokenisation_error :: (Line_and_char -> err) -> Tokeniser' char_class token err t Source #

Throw a tokenisation error at the current location.

tokenise :: (Char -> char_class) -> (char_class -> Line_and_char -> Line_and_char) -> Tokeniser' char_class token err () -> String -> Either Error (Either err (Tokens' token)) Source #

Tokenise the text. For internal use in the parser.

tokens_ended :: Tokens' token -> Bool Source #

Check whether the sequence of tokens has ended. For internal use in the parser.