simple-sql-parser-0.5.0: A parser for SQL.

Safe HaskellSafe
LanguageHaskell2010

Language.SQL.SimpleSQL.Lex

Description

Lexer for SQL.

Synopsis

Documentation

data Token Source #

Represents a lexed token

Constructors

Symbol String

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

  • multi char symbols <> <= >= != ||
  • single char symbols: * + - ^ / % ~ & | ? ( ) [ ] , ; ( )
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

Instances
Eq Token Source # 
Instance details

Defined in Language.SQL.SimpleSQL.Lex

Methods

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

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

Show Token Source # 
Instance details

Defined in Language.SQL.SimpleSQL.Lex

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

lexSQL Source #

Arguments

:: 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.

Constructors

ParseError 

Fields

data Dialect Source #

Used to set the dialect used for parsing and pretty printing, very unfinished at the moment.

Constructors

Dialect 

Fields

Instances
Eq Dialect Source # 
Instance details

Defined in Language.SQL.SimpleSQL.Dialect

Methods

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

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

Data Dialect Source # 
Instance details

Defined in Language.SQL.SimpleSQL.Dialect

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dialect -> c Dialect #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Dialect #

toConstr :: Dialect -> Constr #

dataTypeOf :: Dialect -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Dialect) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Dialect) #

gmapT :: (forall b. Data b => b -> b) -> Dialect -> Dialect #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dialect -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dialect -> r #

gmapQ :: (forall d. Data d => d -> u) -> Dialect -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Dialect -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dialect -> m Dialect #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dialect -> m Dialect #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dialect -> m Dialect #

Read Dialect Source # 
Instance details

Defined in Language.SQL.SimpleSQL.Dialect

Show Dialect Source # 
Instance details

Defined in Language.SQL.SimpleSQL.Dialect

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.