1
Fork 0

restrict parsing of * and X.* as term in expressions

This commit is contained in:
Jake Wheat 2024-02-08 10:43:11 +00:00
parent 6e1e377308
commit 742382fcc0
7 changed files with 127 additions and 135 deletions

View file

@ -604,12 +604,19 @@ simpleLiteral = numberLit <|> stringLit
=== star === star
used in select *, select x.*, and agg(*) variations, and some other used in select *, select x.*, and agg(*) variations, and some other
places as well. The parser doesn't attempt to check that the star is places as well. The parser makes an attempt to not parse star in
in a valid context, it parses it OK in any scalar expression context. most contexts, to provide better experience when the user makes a mistake
in an expression containing * meaning multiple. It will parse a *
at the top level of a select item, or in arg in a app argument list.
-} -}
star :: Parser ScalarExpr star :: Parser ScalarExpr
star = Star <$ symbol "*" star =
hidden $ choice
[Star <$ symbol "*"
-- much easier to use try here than to left factor where
-- this is allowed and not allowed
,try (QStar <$> (names <* symbol "." <* symbol "*"))]
{- {-
== parameter == parameter
@ -957,12 +964,12 @@ app :: Parser ([Name] -> ScalarExpr)
app = app =
hidden openParen *> choice hidden openParen *> choice
[hidden duplicates [hidden duplicates
<**> (commaSep1 scalarExpr <**> (commaSep1 scalarExprOrStar
<**> ((hoption [] orderBy <* closeParen) <**> ((hoption [] orderBy <* closeParen)
<**> (hoptional afilter <$$$$$> AggregateApp))) <**> (hoptional afilter <$$$$$> AggregateApp)))
-- separate cases with no all or distinct which must have at -- separate cases with no all or distinct which must have at
-- least one scalar expr -- least one scalar expr
,commaSep1 scalarExpr ,commaSep1 scalarExprOrStar
<**> choice <**> choice
[closeParen *> hidden (choice [closeParen *> hidden (choice
[window [window
@ -1310,13 +1317,19 @@ documenting/fixing.
scalarExpr :: Parser ScalarExpr scalarExpr :: Parser ScalarExpr
scalarExpr = label "expression" $ E.makeExprParser term (opTable False) scalarExpr = label "expression" $ E.makeExprParser term (opTable False)
-- used when parsing contexts where a * or x.* is allowed
-- currently at the top level of a select item or top level of
-- argument passed to an app-like. This list may need to be extended.
scalarExprOrStar :: Parser ScalarExpr
scalarExprOrStar = label "expression" (star <|> scalarExpr)
term :: Parser ScalarExpr term :: Parser ScalarExpr
term = label "expression" $ term = label "expression" $
choice choice
[simpleLiteral [simpleLiteral
,parameter ,parameter
,positionalArg ,positionalArg
,star
,parensExpr ,parensExpr
,caseExpr ,caseExpr
,cast ,cast
@ -1383,8 +1396,12 @@ duplicates =
-} -}
selectItem :: Parser (ScalarExpr,Maybe Name) selectItem :: Parser (ScalarExpr,Maybe Name)
selectItem = label "select item" ((,) <$> scalarExpr <*> optional als) selectItem =
where als = label "alias" $ optional (keyword_ "as") *> name label "select item" $ choice
[(,Nothing) <$> star
,(,) <$> scalarExpr <*> optional als]
where
als = label "alias" $ optional (keyword_ "as") *> name
selectList :: Parser [(ScalarExpr,Maybe Name)] selectList :: Parser [(ScalarExpr,Maybe Name)]
selectList = commaSep1 selectItem selectList = commaSep1 selectItem

View file

@ -87,6 +87,7 @@ scalarExpr _ (IntervalLit s v f t) =
<+> me (\x -> pretty "to" <+> intervalTypeField x) t <+> me (\x -> pretty "to" <+> intervalTypeField x) t
scalarExpr _ (Iden i) = names i scalarExpr _ (Iden i) = names i
scalarExpr _ Star = pretty "*" scalarExpr _ Star = pretty "*"
scalarExpr _ (QStar nms) = names nms <> pretty ".*"
scalarExpr _ Parameter = pretty "?" scalarExpr _ Parameter = pretty "?"
scalarExpr _ (PositionalArg n) = pretty $ T.cons '$' $ showText n scalarExpr _ (PositionalArg n) = pretty $ T.cons '$' $ showText n
scalarExpr _ (HostParameter p i) = scalarExpr _ (HostParameter p i) =

View file

@ -105,8 +105,10 @@ data ScalarExpr
-- | identifier with parts separated by dots -- | identifier with parts separated by dots
| Iden [Name] | Iden [Name]
-- | star, as in select *, t.*, count(*) -- | star, as in select *, count(*)
| Star | Star
-- | qualified star, as in a.*, b.c.*
| QStar [Name]
| Parameter -- ^ Represents a ? in a parameterized query | Parameter -- ^ Represents a ? in a parameterized query
| PositionalArg Int -- ^ Represents an e.g. $1 in a parameterized query | PositionalArg Int -- ^ Represents an e.g. $1 in a parameterized query

View file

@ -3878,105 +3878,97 @@ expecting expression or query expr
scalarExpr scalarExpr
ansi2011 ansi2011
a >* a >*
BinOp (Iden [ Name Nothing "a" ]) [ Name Nothing ">" ] Star
1:4:
|
1 | a >*
| ^
unexpected *
expecting expression
queryExpr queryExpr
ansi2011 ansi2011
select a >* select a >*
Select 1:11:
{ qeSetQuantifier = SQDefault |
, qeSelectList = 1 | select a >*
[ ( BinOp (Iden [ Name Nothing "a" ]) [ Name Nothing ">" ] Star | ^
, Nothing unexpected *
) expecting expression
]
, qeFrom = []
, qeWhere = Nothing
, qeGroupBy = []
, qeHaving = Nothing
, qeOrderBy = []
, qeOffset = Nothing
, qeFetchFirst = Nothing
}
queryExpr queryExpr
ansi2011 ansi2011
select a >*, select a >*,
1:13: 1:11:
| |
1 | select a >*, 1 | select a >*,
| ^ | ^
unexpected end of input unexpected *
expecting select item expecting expression
queryExpr queryExpr
ansi2011 ansi2011
select a >* from select a >* from
1:17: 1:11:
| |
1 | select a >* from 1 | select a >* from
| ^ | ^
unexpected end of input unexpected *
expecting table ref expecting expression
scalarExpr scalarExpr
ansi2011 ansi2011
a >* b a >* b
1:6: 1:4:
| |
1 | a >* b 1 | a >* b
| ^ | ^
unexpected b unexpected *
expecting expression
queryExpr queryExpr
ansi2011 ansi2011
select a >* b select a >* b
Select 1:11:
{ qeSetQuantifier = SQDefault |
, qeSelectList = 1 | select a >* b
[ ( BinOp (Iden [ Name Nothing "a" ]) [ Name Nothing ">" ] Star | ^
, Just (Name Nothing "b") unexpected *
) expecting expression
]
, qeFrom = []
, qeWhere = Nothing
, qeGroupBy = []
, qeHaving = Nothing
, qeOrderBy = []
, qeOffset = Nothing
, qeFetchFirst = Nothing
}
queryExpr queryExpr
ansi2011 ansi2011
select a >* b, select a >* b,
1:15: 1:11:
| |
1 | select a >* b, 1 | select a >* b,
| ^ | ^
unexpected end of input unexpected *
expecting select item expecting expression
queryExpr queryExpr
ansi2011 ansi2011
select a >* b from select a >* b from
1:19: 1:11:
| |
1 | select a >* b from 1 | select a >* b from
| ^ | ^
unexpected end of input unexpected *
expecting table ref expecting expression
scalarExpr scalarExpr
@ -5147,94 +5139,61 @@ queryExpr
ansi2011 ansi2011
select * as a select * as a
Select 1:10:
{ qeSetQuantifier = SQDefault |
, qeSelectList = [ ( Star , Just (Name Nothing "a") ) ] 1 | select * as a
, qeFrom = [] | ^^
, qeWhere = Nothing unexpected as
, qeGroupBy = [] expecting from
, qeHaving = Nothing
, qeOrderBy = []
, qeOffset = Nothing
, qeFetchFirst = Nothing
}
queryExpr queryExpr
ansi2011 ansi2011
select t.* as a select t.* as a
Select 1:12:
{ qeSetQuantifier = SQDefault |
, qeSelectList = 1 | select t.* as a
[ ( BinOp (Iden [ Name Nothing "t" ]) [ Name Nothing "." ] Star | ^^
, Just (Name Nothing "a") unexpected as
) expecting from
]
, qeFrom = []
, qeWhere = Nothing
, qeGroupBy = []
, qeHaving = Nothing
, qeOrderBy = []
, qeOffset = Nothing
, qeFetchFirst = Nothing
}
queryExpr queryExpr
ansi2011 ansi2011
select 3 + * select 3 + *
Select 1:12:
{ qeSetQuantifier = SQDefault |
, qeSelectList = 1 | select 3 + *
[ ( BinOp (NumLit "3") [ Name Nothing "+" ] Star , Nothing ) ] | ^
, qeFrom = [] unexpected *
, qeWhere = Nothing expecting expression
, qeGroupBy = []
, qeHaving = Nothing
, qeOrderBy = []
, qeOffset = Nothing
, qeFetchFirst = Nothing
}
queryExpr queryExpr
ansi2011 ansi2011
select case when * then 1 end select case when * then 1 end
Select 1:18:
{ qeSetQuantifier = SQDefault |
, qeSelectList = 1 | select case when * then 1 end
[ ( Case | ^
{ caseTest = Nothing unexpected *
, caseWhens = [ ( [ Star ] , NumLit "1" ) ] expecting expression
, caseElse = Nothing
}
, Nothing
)
]
, qeFrom = []
, qeWhere = Nothing
, qeGroupBy = []
, qeHaving = Nothing
, qeOrderBy = []
, qeOffset = Nothing
, qeFetchFirst = Nothing
}
queryExpr queryExpr
ansi2011 ansi2011
select (*) select (*)
Select 1:9:
{ qeSetQuantifier = SQDefault |
, qeSelectList = [ ( Parens Star , Nothing ) ] 1 | select (*)
, qeFrom = [] | ^
, qeWhere = Nothing unexpected *
, qeGroupBy = [] expecting expression or query expr
, qeHaving = Nothing
, qeOrderBy = []
, qeOffset = Nothing
, qeFetchFirst = Nothing
}
queryExpr queryExpr
ansi2011 ansi2011

View file

@ -73,7 +73,22 @@ selectLists = Group "selectLists"
[(BinOp (Iden [Name Nothing "a"]) [Name Nothing "+"] [(BinOp (Iden [Name Nothing "a"]) [Name Nothing "+"]
(BinOp (Iden [Name Nothing "b"]) [Name Nothing "*"] (Iden [Name Nothing "c"])) (BinOp (Iden [Name Nothing "b"]) [Name Nothing "*"] (Iden [Name Nothing "c"]))
,Nothing)]} ,Nothing)]}
,q "select * from t"
$ toQueryExpr $ makeSelect {msSelectList = [(Star,Nothing)]
,msFrom = [TRSimple [Name Nothing "t"]]}
,q "select t.* from t"
$ toQueryExpr $ makeSelect {msSelectList = [(QStar [Name Nothing "t"],Nothing)]
,msFrom = [TRSimple [Name Nothing "t"]]}
,q "select t.*, a as b, u.* from t"
$ toQueryExpr $ makeSelect
{msSelectList =
[(QStar [Name Nothing "t"],Nothing)
,(Iden [Name Nothing "a"], Just $ Name Nothing "b")
,(QStar [Name Nothing "u"],Nothing)]
,msFrom = [TRSimple [Name Nothing "t"]]}
] ]
whereClause :: TestItem whereClause :: TestItem

View file

@ -3283,8 +3283,9 @@ querySpecification = Group "query specification"
,("select distinct a from t",toQueryExpr $ ms {msSetQuantifier = Distinct}) ,("select distinct a from t",toQueryExpr $ ms {msSetQuantifier = Distinct})
,("select * from t", toQueryExpr $ ms {msSelectList = [(Star,Nothing)]}) ,("select * from t", toQueryExpr $ ms {msSelectList = [(Star,Nothing)]})
,("select a.* from t" ,("select a.* from t"
,toQueryExpr $ ms {msSelectList = [(BinOp (Iden [Name Nothing "a"]) [Name Nothing "."] Star ,toQueryExpr $ ms {msSelectList =
,Nothing)]}) [(QStar [Name Nothing "a"]
,Nothing)]})
,("select a b from t" ,("select a b from t"
,toQueryExpr $ ms {msSelectList = [(Iden [Name Nothing "a"], Just $ Name Nothing "b")]}) ,toQueryExpr $ ms {msSelectList = [(Iden [Name Nothing "a"], Just $ Name Nothing "b")]})
,("select a as b from t" ,("select a as b from t"

View file

@ -68,9 +68,8 @@ identifiers = Group "identifiers"
star :: TestItem star :: TestItem
star = Group "star" star = Group "star"
[t "*" Star [t "count(*)" $ App [Name Nothing "count"] [Star]
--,("t.*", Star2 "t") ,t "ROW(t.*,42)" $ App [Name Nothing "ROW"] [QStar [Name Nothing "t"], NumLit "42"]
--,("ROW(t.*,42)", App "ROW" [Star2 "t", NumLit "42"])
] ]
parameter :: TestItem parameter :: TestItem
@ -81,10 +80,8 @@ parameter = Group "parameter"
dots :: TestItem dots :: TestItem
dots = Group "dot" dots = Group "dot"
[t "t.a" $ Iden [Name Nothing "t",Name Nothing "a"] [t "t.a" $ Iden [Name Nothing "t",Name Nothing "a"]
,t "t.*" $ BinOp (Iden [Name Nothing "t"]) [Name Nothing "."] Star
,t "a.b.c" $ Iden [Name Nothing "a",Name Nothing "b",Name Nothing "c"] ,t "a.b.c" $ Iden [Name Nothing "a",Name Nothing "b",Name Nothing "c"]
,t "ROW(t.*,42)" ,t "ROW(t.*,42)" $ App [Name Nothing "ROW"] [QStar [Name Nothing "t"], NumLit "42"]
$ App [Name Nothing "ROW"] [BinOp (Iden [Name Nothing "t"]) [Name Nothing "."] Star, NumLit "42"]
] ]
app :: TestItem app :: TestItem