simple-sql-parser-0.7.1: A parser for SQL.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.SQL.SimpleSQL.Lex

Description

Lexer for SQL.

Synopsis

Documentation

data Token Source #

Represents a lexed token

Constructors

Symbol Text

A symbol (in ansi dialect) is one of the following

  • multi char symbols <> <= >= != ||
  • single char symbols: * + - ^ / % ~ & | ? ( ) [ ] , ; ( )
Identifier (Maybe (Text, Text)) Text

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 Text

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 Text Text Text

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 Text

A number literal (integral or otherwise), stored in original format unchanged

Whitespace Text

Whitespace, one or more of space, tab or newline.

LineComment Text

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 Text

A block comment, /* stuff */, includes the comment delimiters

Instances

Instances details
Show Token Source # 
Instance details

Defined in Language.SQL.SimpleSQL.Lex

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

Eq Token Source # 
Instance details

Defined in Language.SQL.SimpleSQL.Lex

Methods

(==) :: Token -> Token -> Bool #

(/=) :: Token -> Token -> Bool #

Ord Token Source # 
Instance details

Defined in Language.SQL.SimpleSQL.Lex

Methods

compare :: Token -> Token -> Ordering #

(<) :: Token -> Token -> Bool #

(<=) :: Token -> Token -> Bool #

(>) :: Token -> Token -> Bool #

(>=) :: Token -> Token -> Bool #

max :: Token -> Token -> Token #

min :: Token -> Token -> Token #

data WithPos a Source #

Positional information added to tokens to preserve source positions for the parser

Constructors

WithPos 

Instances

Instances details
Show a => Show (WithPos a) Source # 
Instance details

Defined in Language.SQL.SimpleSQL.Lex

Methods

showsPrec :: Int -> WithPos a -> ShowS #

show :: WithPos a -> String #

showList :: [WithPos a] -> ShowS #

Eq a => Eq (WithPos a) Source # 
Instance details

Defined in Language.SQL.SimpleSQL.Lex

Methods

(==) :: WithPos a -> WithPos a -> Bool #

(/=) :: WithPos a -> WithPos a -> Bool #

Ord a => Ord (WithPos a) Source # 
Instance details

Defined in Language.SQL.SimpleSQL.Lex

Methods

compare :: WithPos a -> WithPos a -> Ordering #

(<) :: WithPos a -> WithPos a -> Bool #

(<=) :: WithPos a -> WithPos a -> Bool #

(>) :: WithPos a -> WithPos a -> Bool #

(>=) :: WithPos a -> WithPos a -> Bool #

max :: WithPos a -> WithPos a -> WithPos a #

min :: WithPos a -> WithPos a -> WithPos a #

lexSQL Source #

Arguments

:: Dialect

dialect of SQL to use

-> Text

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

-> Text

the SQL source to lex

-> Either ParseError [Token] 

Lex some SQL to a list of tokens.

lexSQLWithPositions Source #

Arguments

:: Dialect

dialect of SQL to use

-> Text

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

-> Text

the SQL source to lex

-> Either ParseError [WithPos Token] 

Lex some SQL to a list of tokens.

prettyToken :: Dialect -> Token -> Text Source #

Pretty printing, if you lex a bunch of tokens, then pretty print them, should should get back exactly the same string

tokenListWillPrintAndLex :: Dialect -> [Token] -> Bool Source #

Utility function to tell you if a list of tokens will pretty print then lex back to the same set of tokens. Used internally, might be useful for generating SQL via lexical tokens.

ansi2011 :: Dialect Source #

ansi sql 2011 dialect

data SQLStream Source #

Wrapper to allow using the lexer as input to a megaparsec parser.

Constructors

SQLStream