2024-01-09 01:07:47 +01:00
|
|
|
|
|
|
|
-- Tests for parsing scalar expressions
|
|
|
|
|
2024-01-10 08:40:24 +01:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
2024-01-09 01:07:47 +01:00
|
|
|
module Language.SQL.SimpleSQL.ScalarExprs (scalarExprTests) where
|
|
|
|
|
|
|
|
import Language.SQL.SimpleSQL.TestTypes
|
|
|
|
import Language.SQL.SimpleSQL.Syntax
|
2024-02-04 17:00:59 +01:00
|
|
|
import Language.SQL.SimpleSQL.TestRunners
|
|
|
|
|
|
|
|
import Data.Text (Text)
|
2024-01-09 01:07:47 +01:00
|
|
|
|
|
|
|
scalarExprTests :: TestItem
|
|
|
|
scalarExprTests = Group "scalarExprTests"
|
|
|
|
[literals
|
|
|
|
,identifiers
|
|
|
|
,star
|
|
|
|
,parameter
|
|
|
|
,dots
|
|
|
|
,app
|
|
|
|
,caseexp
|
|
|
|
,convertfun
|
|
|
|
,operators
|
|
|
|
,parens
|
|
|
|
,subqueries
|
|
|
|
,aggregates
|
|
|
|
,windowFunctions
|
|
|
|
,functionsWithReservedNames
|
|
|
|
]
|
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
t :: HasCallStack => Text -> ScalarExpr -> TestItem
|
|
|
|
t src ast = testScalarExpr ansi2011 src ast
|
|
|
|
|
|
|
|
td :: HasCallStack => Dialect -> Text -> ScalarExpr -> TestItem
|
|
|
|
td d src ast = testScalarExpr d src ast
|
|
|
|
|
|
|
|
|
|
|
|
|
2024-01-09 01:07:47 +01:00
|
|
|
literals :: TestItem
|
2024-02-04 17:00:59 +01:00
|
|
|
literals = Group "literals"
|
|
|
|
[t "3" $ NumLit "3"
|
|
|
|
,t "3." $ NumLit "3."
|
|
|
|
,t "3.3" $ NumLit "3.3"
|
|
|
|
,t ".3" $ NumLit ".3"
|
|
|
|
,t "3.e3" $ NumLit "3.e3"
|
|
|
|
,t "3.3e3" $ NumLit "3.3e3"
|
|
|
|
,t ".3e3" $ NumLit ".3e3"
|
|
|
|
,t "3e3" $ NumLit "3e3"
|
|
|
|
,t "3e+3" $ NumLit "3e+3"
|
|
|
|
,t "3e-3" $ NumLit "3e-3"
|
|
|
|
,t "'string'" $ StringLit "'" "'" "string"
|
|
|
|
,t "'string with a '' quote'" $ StringLit "'" "'" "string with a '' quote"
|
|
|
|
,t "'1'" $ StringLit "'" "'" "1"
|
|
|
|
,t "interval '3' day"
|
|
|
|
$ IntervalLit Nothing "3" (Itf "day" Nothing) Nothing
|
|
|
|
,t "interval '3' day (3)"
|
|
|
|
$ IntervalLit Nothing "3" (Itf "day" $ Just (3,Nothing)) Nothing
|
|
|
|
,t "interval '3 weeks'" $ TypedLit (TypeName [Name Nothing "interval"]) "3 weeks"
|
2024-01-09 01:07:47 +01:00
|
|
|
]
|
2024-02-04 17:00:59 +01:00
|
|
|
|
2024-01-09 01:07:47 +01:00
|
|
|
identifiers :: TestItem
|
2024-02-04 17:00:59 +01:00
|
|
|
identifiers = Group "identifiers"
|
|
|
|
[t "iden1" $ Iden [Name Nothing "iden1"]
|
2024-01-09 01:07:47 +01:00
|
|
|
--,("t.a", Iden2 "t" "a")
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "\"quoted identifier\"" $ Iden [Name (Just ("\"","\"")) "quoted identifier"]
|
|
|
|
,t "\"from\"" $ Iden [Name (Just ("\"","\"")) "from"]
|
2024-01-09 01:07:47 +01:00
|
|
|
]
|
|
|
|
|
|
|
|
star :: TestItem
|
2024-02-04 17:00:59 +01:00
|
|
|
star = Group "star"
|
2024-02-08 11:43:11 +01:00
|
|
|
[t "count(*)" $ App [Name Nothing "count"] [Star]
|
|
|
|
,t "ROW(t.*,42)" $ App [Name Nothing "ROW"] [QStar [Name Nothing "t"], NumLit "42"]
|
2024-01-09 01:07:47 +01:00
|
|
|
]
|
|
|
|
|
|
|
|
parameter :: TestItem
|
|
|
|
parameter = Group "parameter"
|
2024-02-04 17:00:59 +01:00
|
|
|
[td ansi2011 "?" Parameter
|
|
|
|
,td postgres "$13" $ PositionalArg 13]
|
2024-01-09 01:07:47 +01:00
|
|
|
|
|
|
|
dots :: TestItem
|
2024-02-04 17:00:59 +01:00
|
|
|
dots = Group "dot"
|
|
|
|
[t "t.a" $ Iden [Name Nothing "t",Name Nothing "a"]
|
|
|
|
,t "a.b.c" $ Iden [Name Nothing "a",Name Nothing "b",Name Nothing "c"]
|
2024-02-08 11:43:11 +01:00
|
|
|
,t "ROW(t.*,42)" $ App [Name Nothing "ROW"] [QStar [Name Nothing "t"], NumLit "42"]
|
2024-01-09 01:07:47 +01:00
|
|
|
]
|
|
|
|
|
|
|
|
app :: TestItem
|
2024-02-04 17:00:59 +01:00
|
|
|
app = Group "app"
|
|
|
|
[t "f()" $ App [Name Nothing "f"] []
|
|
|
|
,t "f(a)" $ App [Name Nothing "f"] [Iden [Name Nothing "a"]]
|
|
|
|
,t "f(a,b)" $ App [Name Nothing "f"] [Iden [Name Nothing "a"], Iden [Name Nothing "b"]]
|
2024-01-09 01:07:47 +01:00
|
|
|
]
|
|
|
|
|
|
|
|
caseexp :: TestItem
|
2024-02-04 17:00:59 +01:00
|
|
|
caseexp = Group "caseexp"
|
|
|
|
[t "case a when 1 then 2 end"
|
|
|
|
$ Case (Just $ Iden [Name Nothing "a"]) [([NumLit "1"]
|
|
|
|
,NumLit "2")] Nothing
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "case a when 1 then 2 when 3 then 4 end"
|
|
|
|
$ Case (Just $ Iden [Name Nothing "a"]) [([NumLit "1"], NumLit "2")
|
|
|
|
,([NumLit "3"], NumLit "4")] Nothing
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "case a when 1 then 2 when 3 then 4 else 5 end"
|
|
|
|
$ Case (Just $ Iden [Name Nothing "a"]) [([NumLit "1"], NumLit "2")
|
2024-01-09 01:07:47 +01:00
|
|
|
,([NumLit "3"], NumLit "4")]
|
2024-02-04 17:00:59 +01:00
|
|
|
(Just $ NumLit "5")
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "case when a=1 then 2 when a=3 then 4 else 5 end"
|
|
|
|
$ Case Nothing [([BinOp (Iden [Name Nothing "a"]) [Name Nothing "="] (NumLit "1")], NumLit "2")
|
2024-01-09 01:07:47 +01:00
|
|
|
,([BinOp (Iden [Name Nothing "a"]) [Name Nothing "="] (NumLit "3")], NumLit "4")]
|
2024-02-04 17:00:59 +01:00
|
|
|
(Just $ NumLit "5")
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "case a when 1,2 then 10 when 3,4 then 20 end"
|
|
|
|
$ Case (Just $ Iden [Name Nothing "a"]) [([NumLit "1",NumLit "2"]
|
2024-01-09 01:07:47 +01:00
|
|
|
,NumLit "10")
|
|
|
|
,([NumLit "3",NumLit "4"]
|
|
|
|
,NumLit "20")]
|
2024-02-04 17:00:59 +01:00
|
|
|
Nothing
|
2024-01-09 01:07:47 +01:00
|
|
|
]
|
|
|
|
|
|
|
|
convertfun :: TestItem
|
2024-02-04 17:00:59 +01:00
|
|
|
convertfun = Group "convert"
|
|
|
|
[td sqlserver "CONVERT(varchar, 25.65)"
|
|
|
|
$ Convert (TypeName [Name Nothing "varchar"]) (NumLit "25.65") Nothing
|
|
|
|
,td sqlserver "CONVERT(datetime, '2017-08-25')"
|
|
|
|
$ Convert (TypeName [Name Nothing "datetime"]) (StringLit "'" "'" "2017-08-25") Nothing
|
|
|
|
,td sqlserver "CONVERT(varchar, '2017-08-25', 101)"
|
|
|
|
$ Convert (TypeName [Name Nothing "varchar"]) (StringLit "'" "'" "2017-08-25") (Just 101)
|
2024-01-09 01:07:47 +01:00
|
|
|
]
|
|
|
|
|
|
|
|
operators :: TestItem
|
|
|
|
operators = Group "operators"
|
|
|
|
[binaryOperators
|
|
|
|
,unaryOperators
|
|
|
|
,casts
|
|
|
|
,miscOps]
|
|
|
|
|
|
|
|
binaryOperators :: TestItem
|
2024-02-04 17:00:59 +01:00
|
|
|
binaryOperators = Group "binaryOperators"
|
|
|
|
[t "a + b" $ BinOp (Iden [Name Nothing "a"]) [Name Nothing "+"] (Iden [Name Nothing "b"])
|
2024-01-09 01:07:47 +01:00
|
|
|
-- sanity check fixities
|
|
|
|
-- todo: add more fixity checking
|
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "a + b * c"
|
|
|
|
$ BinOp (Iden [Name Nothing "a"]) [Name Nothing "+"]
|
|
|
|
(BinOp (Iden [Name Nothing "b"]) [Name Nothing "*"] (Iden [Name Nothing "c"]))
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "a * b + c"
|
|
|
|
$ BinOp (BinOp (Iden [Name Nothing "a"]) [Name Nothing "*"] (Iden [Name Nothing "b"]))
|
|
|
|
[Name Nothing "+"] (Iden [Name Nothing "c"])
|
2024-01-09 01:07:47 +01:00
|
|
|
]
|
|
|
|
|
|
|
|
unaryOperators :: TestItem
|
2024-02-04 17:00:59 +01:00
|
|
|
unaryOperators = Group "unaryOperators"
|
|
|
|
[t "not a" $ PrefixOp [Name Nothing "not"] $ Iden [Name Nothing "a"]
|
|
|
|
,t "not not a" $ PrefixOp [Name Nothing "not"] $ PrefixOp [Name Nothing "not"] $ Iden [Name Nothing "a"]
|
|
|
|
,t "+a" $ PrefixOp [Name Nothing "+"] $ Iden [Name Nothing "a"]
|
|
|
|
,t "-a" $ PrefixOp [Name Nothing "-"] $ Iden [Name Nothing "a"]
|
2024-01-09 01:07:47 +01:00
|
|
|
]
|
|
|
|
|
|
|
|
|
|
|
|
casts :: TestItem
|
2024-02-04 17:00:59 +01:00
|
|
|
casts = Group "operators"
|
|
|
|
[t "cast('1' as int)"
|
|
|
|
$ Cast (StringLit "'" "'" "1") $ TypeName [Name Nothing "int"]
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "int '3'"
|
|
|
|
$ TypedLit (TypeName [Name Nothing "int"]) "3"
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "cast('1' as double precision)"
|
|
|
|
$ Cast (StringLit "'" "'" "1") $ TypeName [Name Nothing "double precision"]
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "cast('1' as float(8))"
|
|
|
|
$ Cast (StringLit "'" "'" "1") $ PrecTypeName [Name Nothing "float"] 8
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "cast('1' as decimal(15,2))"
|
|
|
|
$ Cast (StringLit "'" "'" "1") $ PrecScaleTypeName [Name Nothing "decimal"] 15 2
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "double precision '3'"
|
|
|
|
$ TypedLit (TypeName [Name Nothing "double precision"]) "3"
|
2024-01-09 01:07:47 +01:00
|
|
|
]
|
|
|
|
|
|
|
|
subqueries :: TestItem
|
2024-02-04 17:00:59 +01:00
|
|
|
subqueries = Group "unaryOperators"
|
|
|
|
[t "exists (select a from t)" $ SubQueryExpr SqExists ms
|
|
|
|
,t "(select a from t)" $ SubQueryExpr SqSq ms
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "a in (select a from t)"
|
|
|
|
$ In True (Iden [Name Nothing "a"]) (InQueryExpr ms)
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "a not in (select a from t)"
|
|
|
|
$ In False (Iden [Name Nothing "a"]) (InQueryExpr ms)
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "a > all (select a from t)"
|
|
|
|
$ QuantifiedComparison (Iden [Name Nothing "a"]) [Name Nothing ">"] CPAll ms
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "a = some (select a from t)"
|
|
|
|
$ QuantifiedComparison (Iden [Name Nothing "a"]) [Name Nothing "="] CPSome ms
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "a <= any (select a from t)"
|
|
|
|
$ QuantifiedComparison (Iden [Name Nothing "a"]) [Name Nothing "<="] CPAny ms
|
2024-01-09 01:07:47 +01:00
|
|
|
]
|
|
|
|
where
|
2024-01-11 15:45:20 +01:00
|
|
|
ms = toQueryExpr $ makeSelect
|
|
|
|
{msSelectList = [(Iden [Name Nothing "a"],Nothing)]
|
|
|
|
,msFrom = [TRSimple [Name Nothing "t"]]
|
2024-01-09 01:07:47 +01:00
|
|
|
}
|
|
|
|
|
|
|
|
miscOps :: TestItem
|
2024-02-04 17:00:59 +01:00
|
|
|
miscOps = Group "unaryOperators"
|
|
|
|
[t "a in (1,2,3)"
|
|
|
|
$ In True (Iden [Name Nothing "a"]) $ InList $ map NumLit ["1","2","3"]
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "a is null" $ PostfixOp [Name Nothing "is null"] (Iden [Name Nothing "a"])
|
|
|
|
,t "a is not null" $ PostfixOp [Name Nothing "is not null"] (Iden [Name Nothing "a"])
|
|
|
|
,t "a is true" $ PostfixOp [Name Nothing "is true"] (Iden [Name Nothing "a"])
|
|
|
|
,t "a is not true" $ PostfixOp [Name Nothing "is not true"] (Iden [Name Nothing "a"])
|
|
|
|
,t "a is false" $ PostfixOp [Name Nothing "is false"] (Iden [Name Nothing "a"])
|
|
|
|
,t "a is not false" $ PostfixOp [Name Nothing "is not false"] (Iden [Name Nothing "a"])
|
|
|
|
,t "a is unknown" $ PostfixOp [Name Nothing "is unknown"] (Iden [Name Nothing "a"])
|
|
|
|
,t "a is not unknown" $ PostfixOp [Name Nothing "is not unknown"] (Iden [Name Nothing "a"])
|
|
|
|
,t "a is distinct from b" $ BinOp (Iden [Name Nothing "a"]) [Name Nothing "is distinct from"] (Iden [Name Nothing "b"])
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "a is not distinct from b"
|
|
|
|
$ BinOp (Iden [Name Nothing "a"]) [Name Nothing "is not distinct from"] (Iden [Name Nothing "b"])
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "a like b" $ BinOp (Iden [Name Nothing "a"]) [Name Nothing "like"] (Iden [Name Nothing "b"])
|
|
|
|
,t "a not like b" $ BinOp (Iden [Name Nothing "a"]) [Name Nothing "not like"] (Iden [Name Nothing "b"])
|
|
|
|
,t "a is similar to b"$ BinOp (Iden [Name Nothing "a"]) [Name Nothing "is similar to"] (Iden [Name Nothing "b"])
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "a is not similar to b"
|
|
|
|
$ BinOp (Iden [Name Nothing "a"]) [Name Nothing "is not similar to"] (Iden [Name Nothing "b"])
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "a overlaps b" $ BinOp (Iden [Name Nothing "a"]) [Name Nothing "overlaps"] (Iden [Name Nothing "b"])
|
2024-01-09 01:07:47 +01:00
|
|
|
|
|
|
|
-- special operators
|
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "a between b and c" $ SpecialOp [Name Nothing "between"] [Iden [Name Nothing "a"]
|
2024-01-09 01:07:47 +01:00
|
|
|
,Iden [Name Nothing "b"]
|
2024-02-04 17:00:59 +01:00
|
|
|
,Iden [Name Nothing "c"]]
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "a not between b and c" $ SpecialOp [Name Nothing "not between"] [Iden [Name Nothing "a"]
|
2024-01-09 01:07:47 +01:00
|
|
|
,Iden [Name Nothing "b"]
|
2024-02-04 17:00:59 +01:00
|
|
|
,Iden [Name Nothing "c"]]
|
|
|
|
,t "(1,2)"
|
|
|
|
$ SpecialOp [Name Nothing "rowctor"] [NumLit "1", NumLit "2"]
|
2024-01-09 01:07:47 +01:00
|
|
|
|
|
|
|
|
|
|
|
-- keyword special operators
|
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "extract(day from t)"
|
|
|
|
$ SpecialOpK [Name Nothing "extract"] (Just $ Iden [Name Nothing "day"]) [("from", Iden [Name Nothing "t"])]
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "substring(x from 1 for 2)"
|
|
|
|
$ SpecialOpK [Name Nothing "substring"] (Just $ Iden [Name Nothing "x"]) [("from", NumLit "1")
|
|
|
|
,("for", NumLit "2")]
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "substring(x from 1)"
|
|
|
|
$ SpecialOpK [Name Nothing "substring"] (Just $ Iden [Name Nothing "x"]) [("from", NumLit "1")]
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "substring(x for 2)"
|
|
|
|
$ SpecialOpK [Name Nothing "substring"] (Just $ Iden [Name Nothing "x"]) [("for", NumLit "2")]
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "substring(x from 1 for 2 collate C)"
|
|
|
|
$ SpecialOpK [Name Nothing "substring"] (Just $ Iden [Name Nothing "x"])
|
2024-01-09 01:07:47 +01:00
|
|
|
[("from", NumLit "1")
|
2024-02-04 17:00:59 +01:00
|
|
|
,("for", Collate (NumLit "2") [Name Nothing "C"])]
|
2024-01-09 01:07:47 +01:00
|
|
|
|
|
|
|
-- this doesn't work because of a overlap in the 'in' parser
|
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "POSITION( string1 IN string2 )"
|
|
|
|
$ SpecialOpK [Name Nothing "position"] (Just $ Iden [Name Nothing "string1"]) [("in", Iden [Name Nothing "string2"])]
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "CONVERT(char_value USING conversion_char_name)"
|
|
|
|
$ SpecialOpK [Name Nothing "convert"] (Just $ Iden [Name Nothing "char_value"])
|
|
|
|
[("using", Iden [Name Nothing "conversion_char_name"])]
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "TRANSLATE(char_value USING translation_name)"
|
|
|
|
$ SpecialOpK [Name Nothing "translate"] (Just $ Iden [Name Nothing "char_value"])
|
|
|
|
[("using", Iden [Name Nothing "translation_name"])]
|
2024-01-09 01:07:47 +01:00
|
|
|
|
|
|
|
{-
|
|
|
|
OVERLAY(string PLACING embedded_string FROM start
|
|
|
|
[FOR length])
|
|
|
|
-}
|
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "OVERLAY(string PLACING embedded_string FROM start)"
|
|
|
|
$ SpecialOpK [Name Nothing "overlay"] (Just $ Iden [Name Nothing "string"])
|
2024-01-09 01:07:47 +01:00
|
|
|
[("placing", Iden [Name Nothing "embedded_string"])
|
2024-02-04 17:00:59 +01:00
|
|
|
,("from", Iden [Name Nothing "start"])]
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "OVERLAY(string PLACING embedded_string FROM start FOR length)"
|
|
|
|
$ SpecialOpK [Name Nothing "overlay"] (Just $ Iden [Name Nothing "string"])
|
2024-01-09 01:07:47 +01:00
|
|
|
[("placing", Iden [Name Nothing "embedded_string"])
|
|
|
|
,("from", Iden [Name Nothing "start"])
|
2024-02-04 17:00:59 +01:00
|
|
|
,("for", Iden [Name Nothing "length"])]
|
2024-01-09 01:07:47 +01:00
|
|
|
|
|
|
|
{-
|
|
|
|
TRIM( [ [{LEADING | TRAILING | BOTH}] [removal_char] FROM ]
|
|
|
|
target_string
|
|
|
|
[COLLATE collation_name] )
|
|
|
|
-}
|
|
|
|
|
|
|
|
|
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "trim(from target_string)"
|
|
|
|
$ SpecialOpK [Name Nothing "trim"] Nothing
|
2024-01-09 01:07:47 +01:00
|
|
|
[("both", StringLit "'" "'" " ")
|
2024-02-04 17:00:59 +01:00
|
|
|
,("from", Iden [Name Nothing "target_string"])]
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "trim(leading from target_string)"
|
|
|
|
$ SpecialOpK [Name Nothing "trim"] Nothing
|
2024-01-09 01:07:47 +01:00
|
|
|
[("leading", StringLit "'" "'" " ")
|
2024-02-04 17:00:59 +01:00
|
|
|
,("from", Iden [Name Nothing "target_string"])]
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "trim(trailing from target_string)"
|
|
|
|
$ SpecialOpK [Name Nothing "trim"] Nothing
|
2024-01-09 01:07:47 +01:00
|
|
|
[("trailing", StringLit "'" "'" " ")
|
2024-02-04 17:00:59 +01:00
|
|
|
,("from", Iden [Name Nothing "target_string"])]
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "trim(both from target_string)"
|
|
|
|
$ SpecialOpK [Name Nothing "trim"] Nothing
|
2024-01-09 01:07:47 +01:00
|
|
|
[("both", StringLit "'" "'" " ")
|
2024-02-04 17:00:59 +01:00
|
|
|
,("from", Iden [Name Nothing "target_string"])]
|
2024-01-09 01:07:47 +01:00
|
|
|
|
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "trim(leading 'x' from target_string)"
|
|
|
|
$ SpecialOpK [Name Nothing "trim"] Nothing
|
2024-01-09 01:07:47 +01:00
|
|
|
[("leading", StringLit "'" "'" "x")
|
2024-02-04 17:00:59 +01:00
|
|
|
,("from", Iden [Name Nothing "target_string"])]
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "trim(trailing 'y' from target_string)"
|
|
|
|
$ SpecialOpK [Name Nothing "trim"] Nothing
|
2024-01-09 01:07:47 +01:00
|
|
|
[("trailing", StringLit "'" "'" "y")
|
2024-02-04 17:00:59 +01:00
|
|
|
,("from", Iden [Name Nothing "target_string"])]
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "trim(both 'z' from target_string collate C)"
|
|
|
|
$ SpecialOpK [Name Nothing "trim"] Nothing
|
2024-01-09 01:07:47 +01:00
|
|
|
[("both", StringLit "'" "'" "z")
|
2024-02-04 17:00:59 +01:00
|
|
|
,("from", Collate (Iden [Name Nothing "target_string"]) [Name Nothing "C"])]
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "trim(leading from target_string)"
|
|
|
|
$ SpecialOpK [Name Nothing "trim"] Nothing
|
2024-01-09 01:07:47 +01:00
|
|
|
[("leading", StringLit "'" "'" " ")
|
2024-02-04 17:00:59 +01:00
|
|
|
,("from", Iden [Name Nothing "target_string"])]
|
2024-01-09 01:07:47 +01:00
|
|
|
|
|
|
|
]
|
|
|
|
|
|
|
|
aggregates :: TestItem
|
2024-02-04 17:00:59 +01:00
|
|
|
aggregates = Group "aggregates"
|
|
|
|
[t "count(*)" $ App [Name Nothing "count"] [Star]
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "sum(a order by a)"
|
|
|
|
$ AggregateApp [Name Nothing "sum"] SQDefault [Iden [Name Nothing "a"]]
|
|
|
|
[SortSpec (Iden [Name Nothing "a"]) DirDefault NullsOrderDefault] Nothing
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "sum(all a)"
|
|
|
|
$ AggregateApp [Name Nothing "sum"] All [Iden [Name Nothing "a"]] [] Nothing
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "count(distinct a)"
|
|
|
|
$ AggregateApp [Name Nothing "count"] Distinct [Iden [Name Nothing "a"]] [] Nothing
|
2024-01-09 01:07:47 +01:00
|
|
|
]
|
|
|
|
|
|
|
|
windowFunctions :: TestItem
|
2024-02-04 17:00:59 +01:00
|
|
|
windowFunctions = Group "windowFunctions"
|
|
|
|
[t "max(a) over ()" $ WindowApp [Name Nothing "max"] [Iden [Name Nothing "a"]] [] [] Nothing
|
|
|
|
,t "count(*) over ()" $ WindowApp [Name Nothing "count"] [Star] [] [] Nothing
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "max(a) over (partition by b)"
|
|
|
|
$ WindowApp [Name Nothing "max"] [Iden [Name Nothing "a"]] [Iden [Name Nothing "b"]] [] Nothing
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "max(a) over (partition by b,c)"
|
|
|
|
$ WindowApp [Name Nothing "max"] [Iden [Name Nothing "a"]] [Iden [Name Nothing "b"],Iden [Name Nothing "c"]] [] Nothing
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "sum(a) over (order by b)"
|
|
|
|
$ WindowApp [Name Nothing "sum"] [Iden [Name Nothing "a"]] []
|
|
|
|
[SortSpec (Iden [Name Nothing "b"]) DirDefault NullsOrderDefault] Nothing
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "sum(a) over (order by b desc,c)"
|
|
|
|
$ WindowApp [Name Nothing "sum"] [Iden [Name Nothing "a"]] []
|
2024-01-09 01:07:47 +01:00
|
|
|
[SortSpec (Iden [Name Nothing "b"]) Desc NullsOrderDefault
|
2024-02-04 17:00:59 +01:00
|
|
|
,SortSpec (Iden [Name Nothing "c"]) DirDefault NullsOrderDefault] Nothing
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "sum(a) over (partition by b order by c)"
|
|
|
|
$ WindowApp [Name Nothing "sum"] [Iden [Name Nothing "a"]] [Iden [Name Nothing "b"]]
|
|
|
|
[SortSpec (Iden [Name Nothing "c"]) DirDefault NullsOrderDefault] Nothing
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "sum(a) over (partition by b order by c range unbounded preceding)"
|
|
|
|
$ WindowApp [Name Nothing "sum"] [Iden [Name Nothing "a"]] [Iden [Name Nothing "b"]]
|
2024-01-09 01:07:47 +01:00
|
|
|
[SortSpec (Iden [Name Nothing "c"]) DirDefault NullsOrderDefault]
|
2024-02-04 17:00:59 +01:00
|
|
|
$ Just $ FrameFrom FrameRange UnboundedPreceding
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "sum(a) over (partition by b order by c range 5 preceding)"
|
|
|
|
$ WindowApp [Name Nothing "sum"] [Iden [Name Nothing "a"]] [Iden [Name Nothing "b"]]
|
2024-01-09 01:07:47 +01:00
|
|
|
[SortSpec (Iden [Name Nothing "c"]) DirDefault NullsOrderDefault]
|
2024-02-04 17:00:59 +01:00
|
|
|
$ Just $ FrameFrom FrameRange $ Preceding (NumLit "5")
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "sum(a) over (partition by b order by c range current row)"
|
|
|
|
$ WindowApp [Name Nothing "sum"] [Iden [Name Nothing "a"]] [Iden [Name Nothing "b"]]
|
2024-01-09 01:07:47 +01:00
|
|
|
[SortSpec (Iden [Name Nothing "c"]) DirDefault NullsOrderDefault]
|
2024-02-04 17:00:59 +01:00
|
|
|
$ Just $ FrameFrom FrameRange Current
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "sum(a) over (partition by b order by c rows 5 following)"
|
|
|
|
$ WindowApp [Name Nothing "sum"] [Iden [Name Nothing "a"]] [Iden [Name Nothing "b"]]
|
2024-01-09 01:07:47 +01:00
|
|
|
[SortSpec (Iden [Name Nothing "c"]) DirDefault NullsOrderDefault]
|
2024-02-04 17:00:59 +01:00
|
|
|
$ Just $ FrameFrom FrameRows $ Following (NumLit "5")
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "sum(a) over (partition by b order by c range unbounded following)"
|
|
|
|
$ WindowApp [Name Nothing "sum"] [Iden [Name Nothing "a"]] [Iden [Name Nothing "b"]]
|
2024-01-09 01:07:47 +01:00
|
|
|
[SortSpec (Iden [Name Nothing "c"]) DirDefault NullsOrderDefault]
|
2024-02-04 17:00:59 +01:00
|
|
|
$ Just $ FrameFrom FrameRange UnboundedFollowing
|
2024-01-09 01:07:47 +01:00
|
|
|
|
2024-02-04 17:00:59 +01:00
|
|
|
,t "sum(a) over (partition by b order by c \n\
|
2024-01-09 01:07:47 +01:00
|
|
|
\range between 5 preceding and 5 following)"
|
2024-02-04 17:00:59 +01:00
|
|
|
$ WindowApp [Name Nothing "sum"] [Iden [Name Nothing "a"]] [Iden [Name Nothing "b"]]
|
2024-01-09 01:07:47 +01:00
|
|
|
[SortSpec (Iden [Name Nothing "c"]) DirDefault NullsOrderDefault]
|
|
|
|
$ Just $ FrameBetween FrameRange
|
|
|
|
(Preceding (NumLit "5"))
|
2024-02-04 17:00:59 +01:00
|
|
|
(Following (NumLit "5"))
|
2024-01-09 01:07:47 +01:00
|
|
|
|
|
|
|
]
|
|
|
|
|
|
|
|
parens :: TestItem
|
2024-02-04 17:00:59 +01:00
|
|
|
parens = Group "parens"
|
|
|
|
[t "(a)" $ Parens (Iden [Name Nothing "a"])
|
|
|
|
,t "(a + b)" $ Parens (BinOp (Iden [Name Nothing "a"]) [Name Nothing "+"] (Iden [Name Nothing "b"]))
|
2024-01-09 01:07:47 +01:00
|
|
|
]
|
|
|
|
|
|
|
|
functionsWithReservedNames :: TestItem
|
2024-02-04 17:00:59 +01:00
|
|
|
functionsWithReservedNames = Group "functionsWithReservedNames" $ map f
|
2024-01-09 01:07:47 +01:00
|
|
|
["abs"
|
|
|
|
,"char_length"
|
|
|
|
]
|
|
|
|
where
|
2024-02-04 17:00:59 +01:00
|
|
|
f fn = t (fn <> "(a)") $ App [Name Nothing fn] [Iden [Name Nothing "a"]]
|