1
Fork 0
This commit is contained in:
Jake Wheat 2013-12-14 16:58:35 +02:00
parent 97189fb802
commit b6633bf73c
5 changed files with 97 additions and 102 deletions

View file

@ -4,7 +4,7 @@ trees for the operator precedence and associativity (aka 'fixity').
It currently uses haskell-src-exts as a hack, the algorithm from there It currently uses haskell-src-exts as a hack, the algorithm from there
should be ported to work on these trees natively. Maybe it could be should be ported to work on these trees natively. Maybe it could be
made generic? made generic to use in places other than the scalar expr parser?
> {-# LANGUAGE TupleSections #-} > {-# LANGUAGE TupleSections #-}
> module Language.SQL.SimpleSQL.Fixity > module Language.SQL.SimpleSQL.Fixity

View file

@ -331,7 +331,8 @@ There aren't any multi keyword prefix operators currently supported.
> prefixUnOpSymbolNames :: [String] > prefixUnOpSymbolNames :: [String]
> prefixUnOpSymbolNames = ["+", "-"] > prefixUnOpSymbolNames = ["+", "-"]
There aren't any single keyword postfix operators currently supported. Maybe all these 'is's can be left factored? There aren't any single keyword postfix operators currently
supported. Maybe all these 'is's can be left factored?
> postfixOpKeywords :: [String] > postfixOpKeywords :: [String]
> postfixOpKeywords = ["is null" > postfixOpKeywords = ["is null"
@ -664,8 +665,12 @@ blacklist of keywords which aren't supported as identifiers.
> ,"when", "then", "case", "end", "in" > ,"when", "then", "case", "end", "in"
> ,"except", "intersect", "union"] > ,"except", "intersect", "union"]
TODO: talk about what must be in the blacklist, and what doesn't need These blacklisted names are mostly needed when we parse something with
to be. an optional alias, e.g. select a a from t. If we write select a from
t, we have to make sure the from isn't parsed as an alias. I'm not
sure what other places strictly need the blacklist, and in theory it
could be tuned differently for each place the identifierString/
identifier parsers are used to only blacklist the bare minimum.
String literals: limited at the moment, no escaping \' or other String literals: limited at the moment, no escaping \' or other
variations. variations.

View file

@ -2,7 +2,9 @@
This is the pretty printer code which takes AST values and turns them This is the pretty printer code which takes AST values and turns them
back into SQL source text. It attempts to format the output nicely. back into SQL source text. It attempts to format the output nicely.
> -- | These is the pretty printing functions, which produce SQL source from ASTs. The code attempts to format the output in a readable way. > -- | These is the pretty printing functions, which produce SQL
> -- source from ASTs. The code attempts to format the output in a
> -- readable way.
> module Language.SQL.SimpleSQL.Pretty > module Language.SQL.SimpleSQL.Pretty
> (prettyQueryExpr > (prettyQueryExpr
> ,prettyScalarExpr > ,prettyScalarExpr
@ -21,7 +23,8 @@ back into SQL source text. It attempts to format the output nicely.
> prettyScalarExpr :: ScalarExpr -> String > prettyScalarExpr :: ScalarExpr -> String
> prettyScalarExpr = render . scalarExpr > prettyScalarExpr = render . scalarExpr
> -- | Convert a list of query exprs to concrete syntax. A semi colon is inserted following each query expr. > -- | Convert a list of query exprs to concrete syntax. A semi colon
> -- is inserted after each query expr.
> prettyQueryExprs :: [QueryExpr] -> String > prettyQueryExprs :: [QueryExpr] -> String
> prettyQueryExprs = render . vcat . map ((<> text ";\n") . queryExpr) > prettyQueryExprs = render . vcat . map ((<> text ";\n") . queryExpr)
@ -204,7 +207,8 @@ back into SQL source text. It attempts to format the output nicely.
> JCross -> text "cross" > JCross -> text "cross"
> ,text "join"] > ,text "join"]
> joinCond (Just (JoinOn e)) = text "on" <+> scalarExpr e > joinCond (Just (JoinOn e)) = text "on" <+> scalarExpr e
> joinCond (Just (JoinUsing es)) = text "using" <+> parens (commaSep $ map text es) > joinCond (Just (JoinUsing es)) =
> text "using" <+> parens (commaSep $ map text es)
> joinCond Nothing = empty > joinCond Nothing = empty
> joinCond (Just JoinNatural) = empty > joinCond (Just JoinNatural) = empty
@ -226,7 +230,6 @@ back into SQL source text. It attempts to format the output nicely.
> f (e,Asc) = scalarExpr e > f (e,Asc) = scalarExpr e
> f (e,Desc) = scalarExpr e <+> text "desc" > f (e,Desc) = scalarExpr e <+> text "desc"
= utils = utils
> commaSep :: [Doc] -> Doc > commaSep :: [Doc] -> Doc

View file

@ -20,7 +20,8 @@
> ) where > ) where
> -- | Represents a scalar expression > -- | Represents a scalar expression
> data ScalarExpr = -- | a numeric literal optional decimal point, e+- > data ScalarExpr
> = -- | a numeric literal optional decimal point, e+-
> -- integral exponent, e.g > -- integral exponent, e.g
> -- > --
> -- * 10 > -- * 10
@ -35,16 +36,13 @@
> -- > --
> -- * 12.34e-6 > -- * 12.34e-6
> NumLit String > NumLit String
> -- | string literal, currently only basic strings between
> -- | string literal, currently only basic strings > -- single quotes without escapes (no single quotes in strings
> -- between single quotes without escapes (no > -- then)
> -- single quotes in strings then)
> | StringLit String > | StringLit String
> -- | text of interval literal, units of interval > -- | text of interval literal, units of interval precision,
> -- precision, e.g. interval 3 days (3) > -- e.g. interval 3 days (3)
> | IntervalLit String > | IntervalLit String String (Maybe Int)
> String
> (Maybe Int)
> -- | identifier without dots > -- | identifier without dots
> | Iden String > | Iden String
> -- | identifier with one dot > -- | identifier with one dot
@ -53,43 +51,36 @@
> | Star > | Star
> -- | star with qualifier, e.g t.* > -- | star with qualifier, e.g t.*
> | Star2 String > | Star2 String
> -- | function application (anything that looks > -- | function application (anything that looks like c style
> -- like c style function application syntactically) > -- function application syntactically)
> | App String [ScalarExpr] > | App String [ScalarExpr]
> -- | aggregate application, which adds distinct or > -- | aggregate application, which adds distinct or all, and
> -- all, and order by, to regular function > -- order by, to regular function application
> -- application
> | AggregateApp String (Maybe Duplicates) > | AggregateApp String (Maybe Duplicates)
> [ScalarExpr] > [ScalarExpr]
> [(ScalarExpr,Direction)] > [(ScalarExpr,Direction)]
> -- | window application, which adds over > -- | window application, which adds over (partition by a order
> -- (partition by a order by b) to regular function > -- by b) to regular function application. Explicit frames are
> -- application. Explicit frames are not currently > -- not currently supported
> -- supported
> | WindowApp String [ScalarExpr] [ScalarExpr] [(ScalarExpr,Direction)] > | WindowApp String [ScalarExpr] [ScalarExpr] [(ScalarExpr,Direction)]
> -- | Infix binary operators. This is used for > -- | Infix binary operators. This is used for symbol operators
> -- symbol operators (a + b), keyword operators (a > -- (a + b), keyword operators (a and b) and multiple keyword
> -- and b) and multiple keyword operators (a is > -- operators (a is similar to b)
> -- similar to b)
> | BinOp ScalarExpr String ScalarExpr > | BinOp ScalarExpr String ScalarExpr
> -- | Prefix unary operators. This is used for > -- | Prefix unary operators. This is used for symbol
> -- symbol operators, keyword operators and > -- operators, keyword operators and multiple keyword operators
> -- multiple keyword operators
> | PrefixOp String ScalarExpr > | PrefixOp String ScalarExpr
> -- | Postfix unary operators. This is used for > -- | Postfix unary operators. This is used for symbol
> -- symbol operators, keyword operators and multiple > -- operators, keyword operators and multiple keyword operators
> -- keyword operators
> | PostfixOp String ScalarExpr > | PostfixOp String ScalarExpr
> -- | Used for ternary, mixfix and other non > -- | Used for ternary, mixfix and other non orthodox
> -- orthodox operators, including the function > -- operators, including the function looking calls which use
> -- looking calls which use keywords instead of > -- keywords instead of commas to separate the arguments,
> -- commas to separate the arguments,
> -- e.g. substring(t from 1 to 5) > -- e.g. substring(t from 1 to 5)
> | SpecialOp String [ScalarExpr] > | SpecialOp String [ScalarExpr]
> -- | case expression. both flavours > -- | case expression. both flavours supported. Multiple
> -- supported. Multiple condition when branches not > -- condition when branches not currently supported (case when
> -- currently supported (case when a=4,b=5 then x > -- a=4,b=5 then x end)
> -- end)
> | Case (Maybe ScalarExpr) -- test value > | Case (Maybe ScalarExpr) -- test value
> [(ScalarExpr,ScalarExpr)] -- when branches > [(ScalarExpr,ScalarExpr)] -- when branches
> (Maybe ScalarExpr) -- else value > (Maybe ScalarExpr) -- else value
@ -100,11 +91,9 @@
> | CastOp TypeName String > | CastOp TypeName String
> -- | exists, all, any, some subqueries > -- | exists, all, any, some subqueries
> | SubQueryExpr SubQueryExprType QueryExpr > | SubQueryExpr SubQueryExprType QueryExpr
> -- | in list literal and in subquery, if the bool > -- | in list literal and in subquery, if the bool is false it
> -- is false it means not in was used ('a not in > -- means not in was used ('a not in (1,2)')
> -- (1,2)') > | In Bool ScalarExpr InThing
> | In Bool -- true if in, false if not in
> ScalarExpr InThing
> deriving (Eq,Show,Read) > deriving (Eq,Show,Read)
> -- | Represents a type name, used in casts. > -- | Represents a type name, used in casts.
@ -112,7 +101,7 @@
> -- | Used for 'expr in (scalar expression list)', and 'expr in > -- | Used for 'expr in (scalar expression list)', and 'expr in
> -- | (subquery)' syntax > -- (subquery)' syntax
> data InThing = InList [ScalarExpr] > data InThing = InList [ScalarExpr]
> | InQueryExpr QueryExpr > | InQueryExpr QueryExpr
> deriving (Eq,Show,Read) > deriving (Eq,Show,Read)
@ -146,7 +135,8 @@
> data QueryExpr > data QueryExpr
> = Select > = Select
> {qeDuplicates :: Duplicates > {qeDuplicates :: Duplicates
> ,qeSelectList :: [(Maybe String,ScalarExpr)] -- ^ the column aliases and the expressions > ,qeSelectList :: [(Maybe String,ScalarExpr)]
> -- ^ the column aliases and the expressions
> ,qeFrom :: [TableRef] > ,qeFrom :: [TableRef]
> ,qeWhere :: Maybe ScalarExpr > ,qeWhere :: Maybe ScalarExpr
> ,qeGroupBy :: [ScalarExpr] > ,qeGroupBy :: [ScalarExpr]
@ -167,8 +157,7 @@
TODO: add queryexpr parens to deal with e.g. TODO: add queryexpr parens to deal with e.g.
(select 1 union select 2) union select 3 (select 1 union select 2) union select 3
I'm not sure if this is valid syntax or not I'm not sure if this is valid syntax or not.
> -- | represents the Distinct or All keywords, which can be used > -- | represents the Distinct or All keywords, which can be used
> -- before a select list, in an aggregate/window function > -- before a select list, in an aggregate/window function
@ -182,7 +171,8 @@ I'm not sure if this is valid syntax or not
> -- | Corresponding, an option for the set operators > -- | Corresponding, an option for the set operators
> data Corresponding = Corresponding | Respectively deriving (Eq,Show,Read) > data Corresponding = Corresponding | Respectively deriving (Eq,Show,Read)
> -- | helper/'default' value for query exprs to make creating query expr values a little easier > -- | helper/'default' value for query exprs to make creating query
> -- expr values a little easier
> makeSelect :: QueryExpr > makeSelect :: QueryExpr
> makeSelect = Select {qeDuplicates = All > makeSelect = Select {qeDuplicates = All
> ,qeSelectList = [] > ,qeSelectList = []

3
TODO
View file

@ -1,9 +1,6 @@
first release: first release:
check the pretty printer on the tpch queries
fix the fixity issue
add automated tests to cabal add automated tests to cabal
do code documentation and haddock do code documentation and haddock
check the order of exports, imports and functions/cases in the files check the order of exports, imports and functions/cases in the files