rename some functions in parser
This commit is contained in:
parent
445c10a01d
commit
ddfac442ab
|
@ -42,16 +42,25 @@ TOC:
|
||||||
Names - parsing identifiers
|
Names - parsing identifiers
|
||||||
Typenames
|
Typenames
|
||||||
Value expressions
|
Value expressions
|
||||||
Simple literals
|
simple literals
|
||||||
star, param
|
star, param
|
||||||
parens expression, row constructor and scalar subquery
|
parens expression, row constructor and scalar subquery
|
||||||
case, cast, exists, unique, array/ multiset constructor
|
case, cast, exists, unique, array/ multiset constructor
|
||||||
typed literal, app, special function, aggregate, window function
|
typed literal, app, special function, aggregate, window function
|
||||||
suffixes: in, between, quantified comparison, match, array subscript,
|
suffixes: in, between, quantified comparison, match predicate, array
|
||||||
escape, collate
|
subscript, escape, collate
|
||||||
operators
|
operators
|
||||||
value expression top level
|
value expression top level
|
||||||
helpers
|
helpers
|
||||||
|
query expressions
|
||||||
|
select lists
|
||||||
|
from clause
|
||||||
|
other table expression clauses:
|
||||||
|
where, group by, having, order by, offset and fetch
|
||||||
|
common table expressions
|
||||||
|
query expression
|
||||||
|
set operations
|
||||||
|
utilities
|
||||||
|
|
||||||
> {-# LANGUAGE TupleSections #-}
|
> {-# LANGUAGE TupleSections #-}
|
||||||
> -- | This is the module with the parser functions.
|
> -- | This is the module with the parser functions.
|
||||||
|
@ -364,10 +373,10 @@ TODO: this code needs heavy refactoring
|
||||||
> ,LobOctets <$ keyword_ "octets"]
|
> ,LobOctets <$ keyword_ "octets"]
|
||||||
> -- deal with multiset and array suffixes
|
> -- deal with multiset and array suffixes
|
||||||
> tnSuffix x =
|
> tnSuffix x =
|
||||||
> multisetSuffix x <|> arraySuffix x <|> return x
|
> multisetSuffix x <|> arrayTNSuffix x <|> return x
|
||||||
> multisetSuffix x =
|
> multisetSuffix x =
|
||||||
> (MultisetTypeName x <$ keyword_ "multiset") >>= tnSuffix
|
> (MultisetTypeName x <$ keyword_ "multiset") >>= tnSuffix
|
||||||
> arraySuffix x =
|
> arrayTNSuffix x =
|
||||||
> (keyword_ "array" >> ArrayTypeName x
|
> (keyword_ "array" >> ArrayTypeName x
|
||||||
> <$> optionMaybe (brackets unsignedInteger)
|
> <$> optionMaybe (brackets unsignedInteger)
|
||||||
> ) >>= tnSuffix
|
> ) >>= tnSuffix
|
||||||
|
@ -421,27 +430,24 @@ TODO: this code needs heavy refactoring
|
||||||
|
|
||||||
See the stringToken lexer below for notes on string literal syntax.
|
See the stringToken lexer below for notes on string literal syntax.
|
||||||
|
|
||||||
> stringValue :: Parser ValueExpr
|
> stringLit :: Parser ValueExpr
|
||||||
> stringValue = StringLit <$> stringToken
|
> stringLit = StringLit <$> stringToken
|
||||||
|
|
||||||
> number :: Parser ValueExpr
|
> numberLit :: Parser ValueExpr
|
||||||
> number = NumLit <$> numberLiteral
|
> numberLit = NumLit <$> numberLiteral
|
||||||
|
|
||||||
> characterSetLiteral :: Parser ValueExpr
|
> characterSetLit :: Parser ValueExpr
|
||||||
> characterSetLiteral =
|
> characterSetLit =
|
||||||
> CSStringLit <$> shortCSPrefix <*> stringToken
|
> CSStringLit <$> shortCSPrefix <*> stringToken
|
||||||
> where
|
> where
|
||||||
> shortCSPrefix =
|
> shortCSPrefix = try $ choice
|
||||||
> choice
|
|
||||||
> [(:[]) <$> oneOf "nNbBxX"
|
> [(:[]) <$> oneOf "nNbBxX"
|
||||||
> ,string "u&"
|
> ,string "u&"
|
||||||
> ,string "U&"
|
> ,string "U&"
|
||||||
> ] <* lookAhead quote
|
> ] <* lookAhead quote
|
||||||
|
|
||||||
TODO: remove try and relocate some
|
> simpleLiteral :: Parser ValueExpr
|
||||||
|
> simpleLiteral = numberLit <|> stringLit <|> characterSetLit
|
||||||
> literal :: Parser ValueExpr
|
|
||||||
> literal = number <|> stringValue <|> try interval <|> try characterSetLiteral
|
|
||||||
|
|
||||||
== star, param, host param
|
== star, param, host param
|
||||||
|
|
||||||
|
@ -457,28 +463,23 @@ in any value expression context.
|
||||||
|
|
||||||
== parameter
|
== parameter
|
||||||
|
|
||||||
unnamed parameter
|
unnamed parameter or named parameter
|
||||||
use in e.g. select * from t where a = ?
|
use in e.g. select * from t where a = ?
|
||||||
|
|
||||||
> parameter :: Parser ValueExpr
|
|
||||||
> parameter = Parameter <$ questionMark
|
|
||||||
|
|
||||||
named parameter:
|
|
||||||
|
|
||||||
select x from t where x > :param
|
select x from t where x > :param
|
||||||
|
|
||||||
> hostParameter :: Parser ValueExpr
|
> parameter :: Parser ValueExpr
|
||||||
> hostParameter =
|
> parameter = choice
|
||||||
> HostParameter
|
> [Parameter <$ questionMark
|
||||||
> <$> hostParameterToken
|
> ,HostParameter
|
||||||
> <*> optionMaybe (keyword "indicator" *> hostParameterToken)
|
> <$> hostParameterToken
|
||||||
|
> <*> optionMaybe (keyword "indicator" *> hostParameterToken)]
|
||||||
|
|
||||||
== parens
|
== parens
|
||||||
|
|
||||||
value expression parens, row ctor and scalar subquery
|
value expression parens, row ctor and scalar subquery
|
||||||
|
|
||||||
> parensTerm :: Parser ValueExpr
|
> parensExpr :: Parser ValueExpr
|
||||||
> parensTerm = parens $ choice
|
> parensExpr = parens $ choice
|
||||||
> [SubQueryExpr SqSq <$> queryExpr
|
> [SubQueryExpr SqSq <$> queryExpr
|
||||||
> ,ctor <$> commaSep1 valueExpr]
|
> ,ctor <$> commaSep1 valueExpr]
|
||||||
> where
|
> where
|
||||||
|
@ -491,8 +492,8 @@ All of these start with a fixed keyword which is reserved.
|
||||||
|
|
||||||
=== case expression
|
=== case expression
|
||||||
|
|
||||||
> caseValue :: Parser ValueExpr
|
> caseExpr :: Parser ValueExpr
|
||||||
> caseValue =
|
> caseExpr =
|
||||||
> Case <$> (keyword_ "case" *> optionMaybe valueExpr)
|
> Case <$> (keyword_ "case" *> optionMaybe valueExpr)
|
||||||
> <*> many1 whenClause
|
> <*> many1 whenClause
|
||||||
> <*> optionMaybe elseClause
|
> <*> optionMaybe elseClause
|
||||||
|
@ -560,20 +561,21 @@ interval 'something'
|
||||||
then it is parsed as a regular typed literal. It must have a
|
then it is parsed as a regular typed literal. It must have a
|
||||||
interval-datetime-field suffix to parse as an intervallit
|
interval-datetime-field suffix to parse as an intervallit
|
||||||
|
|
||||||
> interval :: Parser ValueExpr
|
It uses try because of a conflict with interval type names: todo, fix
|
||||||
> interval = keyword_ "interval" >> do
|
this
|
||||||
|
|
||||||
|
> intervalLit :: Parser ValueExpr
|
||||||
|
> intervalLit = try (keyword_ "interval" >> do
|
||||||
> s <- optionMaybe $ choice [True <$ symbol_ "+"
|
> s <- optionMaybe $ choice [True <$ symbol_ "+"
|
||||||
> ,False <$ symbol_ "-"]
|
> ,False <$ symbol_ "-"]
|
||||||
> lit <- stringToken
|
> lit <- stringToken
|
||||||
> q <- optionMaybe intervalQualifier
|
> q <- optionMaybe intervalQualifier
|
||||||
> mkIt s lit q
|
> mkIt s lit q)
|
||||||
> where
|
> where
|
||||||
> mkIt Nothing val Nothing = return $ TypedLit (TypeName [Name "interval"]) val
|
> mkIt Nothing val Nothing = return $ TypedLit (TypeName [Name "interval"]) val
|
||||||
> mkIt s val (Just (a,b)) = return $ IntervalLit s val a b
|
> mkIt s val (Just (a,b)) = return $ IntervalLit s val a b
|
||||||
> mkIt (Just {}) _val Nothing = fail "cannot use sign without interval qualifier"
|
> mkIt (Just {}) _val Nothing = fail "cannot use sign without interval qualifier"
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
== typed literal, app, special, aggregate, window, iden
|
== typed literal, app, special, aggregate, window, iden
|
||||||
|
|
||||||
All of these start with identifiers (some of the special functions
|
All of these start with identifiers (some of the special functions
|
||||||
|
@ -589,16 +591,14 @@ all the value expressions which start with an identifier
|
||||||
|
|
||||||
(todo: really put all of them here instead of just some of them)
|
(todo: really put all of them here instead of just some of them)
|
||||||
|
|
||||||
> idenPrefixTerm :: Parser ValueExpr
|
> idenExpr :: Parser ValueExpr
|
||||||
> idenPrefixTerm =
|
> idenExpr =
|
||||||
> -- todo: work out how to left factor this
|
> -- todo: work out how to left factor this
|
||||||
> try (TypedLit <$> typeName <*> stringToken)
|
> try (TypedLit <$> typeName <*> stringToken)
|
||||||
> <|> (names >>= iden)
|
> <|> (names >>= iden)
|
||||||
> where
|
> where
|
||||||
> iden n = app n <|> return (Iden n)
|
> iden n = app n <|> return (Iden n)
|
||||||
|
|
||||||
typed literal
|
|
||||||
|
|
||||||
=== special
|
=== special
|
||||||
|
|
||||||
These are keyword operators which don't look like normal prefix,
|
These are keyword operators which don't look like normal prefix,
|
||||||
|
@ -844,8 +844,8 @@ and operator. This is the call to valueExprB.
|
||||||
|
|
||||||
a = any (select * from t)
|
a = any (select * from t)
|
||||||
|
|
||||||
> quantifiedComparison :: Parser (ValueExpr -> ValueExpr)
|
> quantifiedComparisonSuffix :: Parser (ValueExpr -> ValueExpr)
|
||||||
> quantifiedComparison = do
|
> quantifiedComparisonSuffix = do
|
||||||
> c <- comp
|
> c <- comp
|
||||||
> cq <- compQuan
|
> cq <- compQuan
|
||||||
> q <- parens queryExpr
|
> q <- parens queryExpr
|
||||||
|
@ -862,8 +862,8 @@ a = any (select * from t)
|
||||||
|
|
||||||
a match (select a from t)
|
a match (select a from t)
|
||||||
|
|
||||||
> matchPredicate :: Parser (ValueExpr -> ValueExpr)
|
> matchPredicateSuffix :: Parser (ValueExpr -> ValueExpr)
|
||||||
> matchPredicate = do
|
> matchPredicateSuffix = do
|
||||||
> keyword_ "match"
|
> keyword_ "match"
|
||||||
> u <- option False (True <$ keyword_ "unique")
|
> u <- option False (True <$ keyword_ "unique")
|
||||||
> q <- parens queryExpr
|
> q <- parens queryExpr
|
||||||
|
@ -871,15 +871,15 @@ a match (select a from t)
|
||||||
|
|
||||||
=== array subscript
|
=== array subscript
|
||||||
|
|
||||||
> arrayPostfix :: Parser (ValueExpr -> ValueExpr)
|
> arraySuffix :: Parser (ValueExpr -> ValueExpr)
|
||||||
> arrayPostfix = do
|
> arraySuffix = do
|
||||||
> es <- brackets (commaSep valueExpr)
|
> es <- brackets (commaSep valueExpr)
|
||||||
> return $ \v -> Array v es
|
> return $ \v -> Array v es
|
||||||
|
|
||||||
=== escape
|
=== escape
|
||||||
|
|
||||||
> escape :: Parser (ValueExpr -> ValueExpr)
|
> escapeSuffix :: Parser (ValueExpr -> ValueExpr)
|
||||||
> escape = do
|
> escapeSuffix = do
|
||||||
> ctor <- choice
|
> ctor <- choice
|
||||||
> [Escape <$ keyword_ "escape"
|
> [Escape <$ keyword_ "escape"
|
||||||
> ,UEscape <$ keyword_ "uescape"]
|
> ,UEscape <$ keyword_ "uescape"]
|
||||||
|
@ -888,11 +888,11 @@ a match (select a from t)
|
||||||
|
|
||||||
=== collate
|
=== collate
|
||||||
|
|
||||||
> collate :: Parser (ValueExpr -> ValueExpr)
|
> collateSuffix:: Parser (ValueExpr -> ValueExpr)
|
||||||
> collate = do
|
> collateSuffix = do
|
||||||
> keyword_ "collate"
|
> keyword_ "collate"
|
||||||
> i <- names
|
> i <- names
|
||||||
> return $ \v -> Collate v i
|
> return $ \v -> Collate v i
|
||||||
|
|
||||||
|
|
||||||
== operators
|
== operators
|
||||||
|
@ -915,13 +915,13 @@ messages, but both of these are too important.
|
||||||
> [-- parse match and quantified comparisons as postfix ops
|
> [-- parse match and quantified comparisons as postfix ops
|
||||||
> -- todo: left factor the quantified comparison with regular
|
> -- todo: left factor the quantified comparison with regular
|
||||||
> -- binary comparison, somehow
|
> -- binary comparison, somehow
|
||||||
> [E.Postfix $ try quantifiedComparison
|
> [E.Postfix $ try quantifiedComparisonSuffix
|
||||||
> ,E.Postfix matchPredicate
|
> ,E.Postfix matchPredicateSuffix
|
||||||
> ]
|
> ]
|
||||||
> ,[binarySym "." E.AssocLeft]
|
> ,[binarySym "." E.AssocLeft]
|
||||||
> ,[postfix' arrayPostfix
|
> ,[postfix' arraySuffix
|
||||||
> ,postfix' escape
|
> ,postfix' escapeSuffix
|
||||||
> ,postfix' collate]
|
> ,postfix' collateSuffix]
|
||||||
> ,[prefixSym "+", prefixSym "-"]
|
> ,[prefixSym "+", prefixSym "-"]
|
||||||
> ,[binarySym "^" E.AssocLeft]
|
> ,[binarySym "^" E.AssocLeft]
|
||||||
> ,[binarySym "*" E.AssocLeft
|
> ,[binarySym "*" E.AssocLeft
|
||||||
|
@ -1016,18 +1016,18 @@ fragile and could at least do with some heavy explanation.
|
||||||
> valueExpr = E.buildExpressionParser (opTable False) term
|
> valueExpr = E.buildExpressionParser (opTable False) term
|
||||||
|
|
||||||
> term :: Parser ValueExpr
|
> term :: Parser ValueExpr
|
||||||
> term = choice [literal
|
> term = choice [simpleLiteral
|
||||||
> ,parameter
|
> ,parameter
|
||||||
> ,hostParameter
|
|
||||||
> ,star
|
> ,star
|
||||||
> ,parensTerm
|
> ,parensExpr
|
||||||
> ,caseValue
|
> ,caseExpr
|
||||||
> ,cast
|
> ,cast
|
||||||
> ,arrayCtor
|
> ,arrayCtor
|
||||||
> ,multisetCtor
|
> ,multisetCtor
|
||||||
> ,subquery
|
> ,subquery
|
||||||
|
> ,intervalLit
|
||||||
> ,specialOpKs
|
> ,specialOpKs
|
||||||
> ,idenPrefixTerm]
|
> ,idenExpr]
|
||||||
> <?> "value expression"
|
> <?> "value expression"
|
||||||
|
|
||||||
expose the b expression for window frame clause range between
|
expose the b expression for window frame clause range between
|
||||||
|
|
Loading…
Reference in a new issue