1
Fork 0
This commit is contained in:
Jake Wheat 2013-12-17 20:27:11 +02:00
parent 9b1bbbf307
commit e61672ebf8
7 changed files with 26 additions and 13 deletions

View file

@ -117,7 +117,7 @@ the fixity code.
> var = HSE.Var . HSE.UnQual . HSE.Ident
> sym = HSE.UnQual . HSE.Symbol
> name n = case n of
> QName q -> "\"" ++ q
> QName q -> '"' ++ q
> Name m -> m
> orderExps = map (toHaskell . (\(OrderField a _ _) -> a))
> orderInf = map (\(OrderField _ b c) -> (b,c))

View file

@ -183,8 +183,8 @@ always used with the optionSuffix combinator.
> partitionBy = try (keyword_ "partition") >>
> keyword_ "by" >> commaSep1 scalarExpr'
> frameClause =
> mkFrame <$> (choice [FrameRows <$ keyword_ "rows"
> ,FrameRange <$ keyword_ "range"])
> mkFrame <$> choice [FrameRows <$ keyword_ "rows"
> ,FrameRange <$ keyword_ "range"]
> <*> frameStartEnd
> frameStartEnd =
> choice

View file

@ -101,7 +101,7 @@
> scalarExpr (PrefixOp f e) = name f <+> scalarExpr e
> scalarExpr (PostfixOp f e) = scalarExpr e <+> name f
> scalarExpr e@(BinOp _ op _) | op `elem` [(Name "and"), (Name "or")] =
> scalarExpr e@(BinOp _ op _) | op `elem` [Name "and", Name "or"] =
> -- special case for and, or, get all the ands so we can vcat them
> -- nicely
> case ands e of

View file

@ -66,7 +66,7 @@
> -- order by, to regular function application
> | AggregateApp
> {aggName :: Name -- ^ aggregate function name
> ,aggDistinct :: (Maybe Duplicates)-- ^ distinct
> ,aggDistinct :: Maybe Duplicates -- ^ distinct
> ,aggArgs :: [ScalarExpr]-- ^ args
> ,aggOrderBy :: [OrderField] -- ^ order by
> }

18
TODO
View file

@ -1,6 +1,15 @@
next release:
add to website: pretty printed tpch, maybe other queries as
demonstration
check haddock
reformat the source for some of the tests
----
next release after that:
review tests to copy from hssqlppp
collate? -> postfix operator which binds very tightly:
@ -21,8 +30,6 @@ review syntax to replace maybe and bool with better ctors
----
add to website: pretty printed tpch, maybe other queries as
demonstration
demo: convert tpch to sql server syntax exe processor
----
@ -61,6 +68,11 @@ left factor parsing code in remaining places
quasi quotes?
ast checker: checks the ast represents valid syntax, the parser
doesn't check as much as it could, and this can also be used to
check generated trees. Maybe this doesn't belong in this package
though?
= sql support
proper character sets for identifiers, escapes, etc.

View file

@ -9,7 +9,7 @@ revisited when the dialect support is added.
> --import Language.SQL.SimpleSQL.Syntax
> postgresTests :: TestItem
> postgresTests = Group "postgresTests" $ map ParseQueryExpr $
> postgresTests = Group "postgresTests" $ map ParseQueryExpr
lexical syntax section

View file

@ -227,7 +227,8 @@ Tests for parsing scalar expressions
> [("count(*)",App "count" [Star])
> ,("sum(a order by a)"
> ,AggregateApp "sum" Nothing [Iden "a"] [(OrderField (Iden "a") Asc NullsOrderDefault)])
> ,AggregateApp "sum" Nothing [Iden "a"]
> [OrderField (Iden "a") Asc NullsOrderDefault])
> ,("sum(all a)"
> ,AggregateApp "sum" (Just All) [Iden "a"] [])
@ -248,11 +249,11 @@ Tests for parsing scalar expressions
> ,WindowApp "max" [Iden "a"] [Iden "b",Iden "c"] [] Nothing)
> ,("sum(a) over (order by b)"
> ,WindowApp "sum" [Iden "a"] [] [(OrderField (Iden "b") Asc NullsOrderDefault)] Nothing)
> ,WindowApp "sum" [Iden "a"] [] [OrderField (Iden "b") Asc NullsOrderDefault] Nothing)
> ,("sum(a) over (order by b desc,c)"
> ,WindowApp "sum" [Iden "a"] [] [(OrderField (Iden "b") Desc NullsOrderDefault)
> ,(OrderField (Iden "c") Asc NullsOrderDefault)] Nothing)
> ,WindowApp "sum" [Iden "a"] [] [OrderField (Iden "b") Desc NullsOrderDefault
> ,OrderField (Iden "c") Asc NullsOrderDefault] Nothing)
> ,("sum(a) over (partition by b order by c)"
> ,WindowApp "sum" [Iden "a"] [Iden "b"] [OrderField (Iden "c") Asc NullsOrderDefault] Nothing)