Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Lexer for SQL.
Synopsis
- data Token
- lexSQL :: Dialect -> FilePath -> Maybe (Int, Int) -> String -> Either ParseError [((String, Int, Int), Token)]
- prettyToken :: Dialect -> Token -> String
- prettyTokens :: Dialect -> [Token] -> String
- data ParseError = ParseError {
- peErrorString :: String
- peFilename :: FilePath
- pePosition :: (Int, Int)
- peFormattedError :: String
- tokenListWillPrintAndLex :: Dialect -> [Token] -> Bool
- ansi2011 :: Dialect
Documentation
Represents a lexed token
Symbol String | A symbol (in ansi dialect) is one of the following |
Identifier (Maybe (String, String)) String | This is an identifier or keyword. The first field is the quotes used, or nothing if no quotes were used. The quotes can be " or u& or something dialect specific like [] |
PrefixedVariable Char String | This is a prefixed variable symbol, such as :var, @var or #var (only :var is used in ansi dialect) |
PositionalArg Int | This is a positional arg identifier e.g. $1 |
SqlString String String String | This is a string literal. The first two fields are the -- start and end quotes, which are usually both ', but can be the character set (one of nNbBxX, or u&, U&), or a dialect specific string quoting (such as $$ in postgres) |
SqlNumber String | A number literal (integral or otherwise), stored in original format unchanged |
Whitespace String | Whitespace, one or more of space, tab or newline. |
LineComment String | A commented line using --, contains every character starting with the '--' and including the terminating newline character if there is one - this will be missing if the last line in the source is a line comment with no trailing newline |
BlockComment String | A block comment, /* stuff */, includes the comment delimiters |
:: Dialect | dialect of SQL to use |
-> FilePath | filename to use in error messages |
-> Maybe (Int, Int) | line number and column number of the first character in the source to use in error messages |
-> String | the SQL source to lex |
-> Either ParseError [((String, Int, Int), Token)] |
Lex some SQL to a list of tokens.
prettyToken :: Dialect -> Token -> String Source #
Pretty printing, if you lex a bunch of tokens, then pretty print them, should should get back exactly the same string
data ParseError Source #
Type to represent parse errors.
ParseError | |
|
Instances
Eq ParseError Source # | |
Defined in Language.SQL.SimpleSQL.Errors (==) :: ParseError -> ParseError -> Bool # (/=) :: ParseError -> ParseError -> Bool # | |
Show ParseError Source # | |
Defined in Language.SQL.SimpleSQL.Errors showsPrec :: Int -> ParseError -> ShowS # show :: ParseError -> String # showList :: [ParseError] -> ShowS # |