| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Language.Lua.Lexer
Contents
- luaLexer :: Lexer Token
- data LexicalError :: * = LexicalError !Pos
- data TokenStream tok :: * -> *
- = TsToken tok (TokenStream tok)
- | TsEof
- | TsError LexicalError
- runLexer :: Lexer tok -> String -> String -> TokenStream (L tok)
- streamToList :: TokenStream tok -> [tok]
- streamToEitherList :: TokenStream tok -> Either LexicalError [tok]
Documentation
luaLexer :: Lexer Token Source
lex :: String -> [L Token] lex =streamToList.runLexerluaLexer""
>>>lex "5+5"[TkIntLit "5",TkPlus,TkIntLit "5"]>>>lex "foo?"[TkIdent "foo"*** Exception: Lexical error at :1:4
lexer-applicative re-exports
data TokenStream tok :: * -> *
A stream of tokens
Constructors
| TsToken tok (TokenStream tok) | |
| TsEof | |
| TsError LexicalError |
Instances
| Functor TokenStream | |
| Eq tok => Eq (TokenStream tok) | |
| Show tok => Show (TokenStream tok) |
Arguments
| :: Lexer tok | lexer specification |
| -> String | source file name (used in locations) |
| -> String | source text |
| -> TokenStream (L tok) |
Run a lexer on a string and produce a lazy stream of tokens
streamToList :: TokenStream tok -> [tok]
Convert a TokenStream to a list of tokens. Turn TsError into
a runtime LexicalError exception.
streamToEitherList :: TokenStream tok -> Either LexicalError [tok]
Convert a TokenStream into either a token list or a LexicalError.
This function may be occasionally useful, but in general its use is
discouraged because it needs to force the whole stream before returning
a result.