1
Fork 0

work on array constructors and expressions

This commit is contained in:
Jake Wheat 2014-04-17 22:57:33 +03:00
parent 4cf84eba7b
commit 211174cfb4
4 changed files with 71 additions and 17 deletions

View file

@ -462,6 +462,17 @@ a match (select a from t)
> return $ \v -> Match v u q > return $ \v -> Match v u q
> arrayPostfix :: Parser (ValueExpr -> ValueExpr)
> arrayPostfix = do
> es <- brackets (commaSep valueExpr)
> return $ \v -> Array v es
> arrayCtor :: Parser ValueExpr
> arrayCtor = keyword_ "array" >>
> choice
> [ArrayCtor <$> parens queryExpr
> ,Array (Iden (Name "array")) <$> brackets (commaSep valueExpr)]
typename: used in casts. Special cases for the multi keyword typenames typename: used in casts. Special cases for the multi keyword typenames
that SQL supports. that SQL supports.
@ -529,6 +540,7 @@ TODO: carefully review the precedences and associativities.
> [E.Postfix $ try quantifiedComparison > [E.Postfix $ try quantifiedComparison
> ,E.Postfix matchPredicate] > ,E.Postfix matchPredicate]
> ,[binarySym "." E.AssocLeft] > ,[binarySym "." E.AssocLeft]
> ,[postfix' arrayPostfix]
> ,[prefixSym "+", prefixSym "-"] > ,[prefixSym "+", prefixSym "-"]
> ,[binarySym "^" E.AssocLeft] > ,[binarySym "^" E.AssocLeft]
> ,[binarySym "*" E.AssocLeft > ,[binarySym "*" E.AssocLeft
@ -618,6 +630,7 @@ fragile and could at least do with some heavy explanation.
> ,hostParameter > ,hostParameter
> ,caseValue > ,caseValue
> ,cast > ,cast
> ,arrayCtor
> ,specialOpKs > ,specialOpKs
> ,parensTerm > ,parensTerm
> ,subquery > ,subquery
@ -961,6 +974,13 @@ todo: work out the symbol parsing better
> closeParen :: Parser Char > closeParen :: Parser Char
> closeParen = lexeme $ char ')' > closeParen = lexeme $ char ')'
> openBracket :: Parser Char
> openBracket = lexeme $ char '['
> closeBracket :: Parser Char
> closeBracket = lexeme $ char ']'
> comma :: Parser Char > comma :: Parser Char
> comma = lexeme $ char ',' > comma = lexeme $ char ','
@ -1005,6 +1025,9 @@ todo: work out the symbol parsing better
> parens :: Parser a -> Parser a > parens :: Parser a -> Parser a
> parens = between openParen closeParen > parens = between openParen closeParen
> brackets :: Parser a -> Parser a
> brackets = between openBracket closeBracket
> commaSep :: Parser a -> Parser [a] > commaSep :: Parser a -> Parser [a]
> commaSep = (`sepBy` comma) > commaSep = (`sepBy` comma)

View file

@ -14,7 +14,7 @@ which have been changed to try to improve the layout of the output.
> import Language.SQL.SimpleSQL.Syntax > import Language.SQL.SimpleSQL.Syntax
> import Text.PrettyPrint (render, vcat, text, (<>), (<+>), empty, parens, > import Text.PrettyPrint (render, vcat, text, (<>), (<+>), empty, parens,
> nest, Doc, punctuate, comma, sep, quotes, > nest, Doc, punctuate, comma, sep, quotes,
> doubleQuotes) > doubleQuotes, brackets)
> import Data.Maybe (maybeToList, catMaybes) > import Data.Maybe (maybeToList, catMaybes)
> -- | Convert a query expr ast to concrete syntax. > -- | Convert a query expr ast to concrete syntax.
@ -162,7 +162,6 @@ which have been changed to try to improve the layout of the output.
> <+> (if u then text "unique" else empty) > <+> (if u then text "unique" else empty)
> <+> parens (queryExpr sq) > <+> parens (queryExpr sq)
> valueExpr (In b se x) = > valueExpr (In b se x) =
> valueExpr se <+> > valueExpr se <+>
> (if b then empty else text "not") > (if b then empty else text "not")
@ -172,6 +171,13 @@ which have been changed to try to improve the layout of the output.
> InList es -> commaSep $ map valueExpr es > InList es -> commaSep $ map valueExpr es
> InQueryExpr qe -> queryExpr qe) > InQueryExpr qe -> queryExpr qe)
> valueExpr (Array v es) =
> valueExpr v <> brackets (commaSep $ map valueExpr es)
> valueExpr (ArrayCtor q) =
> text "array" <> parens (queryExpr q)
> unname :: Name -> String > unname :: Name -> String
> unname (QName n) = "\"" ++ n ++ "\"" > unname (QName n) = "\"" ++ n ++ "\""
> unname (Name n) = n > unname (Name n) = n

View file

@ -134,6 +134,12 @@
> QueryExpr > QueryExpr
> | Match ValueExpr Bool -- true if unique > | Match ValueExpr Bool -- true if unique
> QueryExpr > QueryExpr
> | Array ValueExpr [ValueExpr] -- ^ represents an array
> -- access expression, or an array ctor
> -- e.g. a[3]. The first
> -- valueExpr is the array, the
> -- second is the subscripts/ctor args
> | ArrayCtor QueryExpr -- ^ this is used for the query expression version of array constructors, e.g. array(select * from t)> deriving (Eq,Show,Read,Data,Typeable)
> deriving (Eq,Show,Read,Data,Typeable) > deriving (Eq,Show,Read,Data,Typeable)
> -- | Represents an identifier name, which can be quoted or unquoted. > -- | Represents an identifier name, which can be quoted or unquoted.
@ -154,7 +160,7 @@
> | InQueryExpr QueryExpr > | InQueryExpr QueryExpr
> deriving (Eq,Show,Read,Data,Typeable) > deriving (Eq,Show,Read,Data,Typeable)
not sure if scalar subquery and aexists and unique should be represented like this not sure if scalar subquery, exists and unique should be represented like this
> -- | A subquery in a value expression. > -- | A subquery in a value expression.
> data SubQueryExprType > data SubQueryExprType

View file

@ -27,13 +27,13 @@ large amount of the SQL.
> --,typeNames > --,typeNames
> --,parenthesizedValueExpression > --,parenthesizedValueExpression
> ,targetSpecification > ,targetSpecification
> --,contextuallyTypeValueSpec > ,contextuallyTypeValueSpec
> --,nextValueExpression > --,nextValueExpression
> --,arrayElementReference > ,arrayElementReference
> --,multisetElementReference > --,multisetElementReference
> --,numericValueExpression > --,numericValueExpression
> --,booleanValueExpression > --,booleanValueExpression
> --,arrayValueConstructor > ,arrayValueConstructor
> --,tableValueConstructor > --,tableValueConstructor
> --,fromClause > --,fromClause
> --,whereClause > --,whereClause
@ -1076,7 +1076,7 @@ TODO: review how the special keywords are parsed and add tests for these
> ,(":hostparam indicator :another_host_param" > ,(":hostparam indicator :another_host_param"
> ,HostParameter "hostparam" $ Just "another_host_param") > ,HostParameter "hostparam" $ Just "another_host_param")
> ,("?", Parameter) > ,("?", Parameter)
> --,(":h[3]", Array (HostParameter "h" Nothing) [NumLit "3"]) > ,(":h[3]", Array (HostParameter "h" Nothing) [NumLit "3"])
> ] > ]
TODO: modules stuff, not sure what current_collation is TODO: modules stuff, not sure what current_collation is
@ -1102,10 +1102,10 @@ for or how it works
> contextuallyTypeValueSpec :: TestItem > contextuallyTypeValueSpec :: TestItem
> contextuallyTypeValueSpec = Group "ontextually typed value specification" $ map (uncurry TestValueExpr) > contextuallyTypeValueSpec = Group "ontextually typed value specification" $ map (uncurry TestValueExpr)
> [("null", undefined) > [("null", Iden "null")
> ,("array[]", undefined) > ,("array[]", Array (Iden "array") [])
> ,("multiset[]", undefined) > --,("multiset[]", undefined)
> ,("default", undefined) > ,("default", Iden "default")
> ] > ]
todo: trigraphs? todo: trigraphs?
@ -1352,8 +1352,16 @@ TODO: reference resolution
> arrayElementReference :: TestItem > arrayElementReference :: TestItem
> arrayElementReference = Group "array element reference" $ map (uncurry TestValueExpr) > arrayElementReference = Group "array element reference" $ map (uncurry TestValueExpr)
> [("something[3]", undefined) > [("something[3]"
> ,("(something(a))[x][y] ", undefined) > ,Array (Iden "something") [NumLit "3"])
> ,("(something(a))[x]"
> ,Array (Parens (App "something" [Iden "a"]))
> [Iden "x"])
> ,("(something(a))[x][y] "
> ,Array (
> Array (Parens (App "something" [Iden "a"]))
> [Iden "x"])
> [Iden "y"])
> ] > ]
TODO: work out the precendence of the array element reference suffix TODO: work out the precendence of the array element reference suffix
@ -1765,10 +1773,21 @@ operator is ||, same as the string concatenation operator.
> arrayValueConstructor :: TestItem > arrayValueConstructor :: TestItem
> arrayValueConstructor = Group "array value constructor" $ map (uncurry TestValueExpr) > arrayValueConstructor = Group "array value constructor" $ map (uncurry TestValueExpr)
> [("array[1,2,3]", undefined) > [("array[1,2,3]"
> ,("array[a,b,c]", undefined) > ,Array (Iden "array")
> ,("array(select * from t)", undefined) > [NumLit "1", NumLit "2", NumLit "3"])
> ,("array(select * from t order by a)", undefined) > ,("array[a,b,c]"
> ,Array (Iden "array")
> [Iden "a", Iden "b", Iden "c"])
> ,("array(select * from t)"
> ,ArrayCtor (makeSelect
> {qeSelectList = [(Star,Nothing)]
> ,qeFrom = [TRSimple "t"]}))
> ,("array(select * from t order by a)"
> ,ArrayCtor (makeSelect
> {qeSelectList = [(Star,Nothing)]
> ,qeFrom = [TRSimple "t"]
> ,qeOrderBy = [SortSpec (Iden "a") Asc NullsOrderDefault] }))
> ] > ]
== 6.37 <multiset value expression> (p286) == 6.37 <multiset value expression> (p286)