reformat
This commit is contained in:
parent
97189fb802
commit
b6633bf73c
|
@ -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
|
||||||
|
|
|
@ -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.
|
||||||
|
|
|
@ -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
|
||||||
|
|
|
@ -20,99 +20,88 @@
|
||||||
> ) where
|
> ) where
|
||||||
|
|
||||||
> -- | Represents a scalar expression
|
> -- | Represents a scalar expression
|
||||||
> data ScalarExpr = -- | a numeric literal optional decimal point, e+-
|
> data ScalarExpr
|
||||||
> -- integral exponent, e.g
|
> = -- | a numeric literal optional decimal point, e+-
|
||||||
> --
|
> -- integral exponent, e.g
|
||||||
> -- * 10
|
> --
|
||||||
> --
|
> -- * 10
|
||||||
> -- * 10.
|
> --
|
||||||
> --
|
> -- * 10.
|
||||||
> -- * .1
|
> --
|
||||||
> --
|
> -- * .1
|
||||||
> -- * 10.1
|
> --
|
||||||
> --
|
> -- * 10.1
|
||||||
> -- * 1e5
|
> --
|
||||||
> --
|
> -- * 1e5
|
||||||
> -- * 12.34e-6
|
> --
|
||||||
> NumLit String
|
> -- * 12.34e-6
|
||||||
|
> NumLit String
|
||||||
> -- | string literal, currently only basic strings
|
> -- | string literal, currently only basic strings between
|
||||||
> -- between single quotes without escapes (no
|
> -- single quotes without escapes (no single quotes in strings
|
||||||
> -- single quotes in strings then)
|
> -- 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
|
> -- | identifier without dots
|
||||||
> (Maybe Int)
|
> | Iden String
|
||||||
> -- | identifier without dots
|
> -- | identifier with one dot
|
||||||
> | Iden String
|
> | Iden2 String String
|
||||||
> -- | identifier with one dot
|
> -- | star
|
||||||
> | Iden2 String String
|
> | Star
|
||||||
> -- | star
|
> -- | star with qualifier, e.g t.*
|
||||||
> | Star
|
> | Star2 String
|
||||||
> -- | star with qualifier, e.g t.*
|
> -- | function application (anything that looks like c style
|
||||||
> | Star2 String
|
> -- function application syntactically)
|
||||||
> -- | function application (anything that looks
|
> | App String [ScalarExpr]
|
||||||
> -- like c style function application syntactically)
|
> -- | aggregate application, which adds distinct or all, and
|
||||||
> | App String [ScalarExpr]
|
> -- order by, to regular function application
|
||||||
> -- | aggregate application, which adds distinct or
|
> | AggregateApp String (Maybe Duplicates)
|
||||||
> -- all, and order by, to regular function
|
> [ScalarExpr]
|
||||||
> -- application
|
> [(ScalarExpr,Direction)]
|
||||||
> | AggregateApp String (Maybe Duplicates)
|
> -- | window application, which adds over (partition by a order
|
||||||
> [ScalarExpr]
|
> -- by b) to regular function application. Explicit frames are
|
||||||
> [(ScalarExpr,Direction)]
|
> -- not currently supported
|
||||||
> -- | window application, which adds over
|
> | WindowApp String [ScalarExpr] [ScalarExpr] [(ScalarExpr,Direction)]
|
||||||
> -- (partition by a order by b) to regular function
|
> -- | Infix binary operators. This is used for symbol operators
|
||||||
> -- application. Explicit frames are not currently
|
> -- (a + b), keyword operators (a and b) and multiple keyword
|
||||||
> -- supported
|
> -- operators (a is similar to b)
|
||||||
> | WindowApp String [ScalarExpr] [ScalarExpr] [(ScalarExpr,Direction)]
|
> | BinOp ScalarExpr String ScalarExpr
|
||||||
> -- | Infix binary operators. This is used for
|
> -- | Prefix unary operators. This is used for symbol
|
||||||
> -- symbol operators (a + b), keyword operators (a
|
> -- operators, keyword operators and multiple keyword operators
|
||||||
> -- and b) and multiple keyword operators (a is
|
> | PrefixOp String ScalarExpr
|
||||||
> -- similar to b)
|
> -- | Postfix unary operators. This is used for symbol
|
||||||
> | BinOp ScalarExpr String ScalarExpr
|
> -- operators, keyword operators and multiple keyword operators
|
||||||
> -- | Prefix unary operators. This is used for
|
> | PostfixOp String ScalarExpr
|
||||||
> -- symbol operators, keyword operators and
|
> -- | Used for ternary, mixfix and other non orthodox
|
||||||
> -- multiple keyword operators
|
> -- operators, including the function looking calls which use
|
||||||
> | PrefixOp String ScalarExpr
|
> -- keywords instead of commas to separate the arguments,
|
||||||
> -- | Postfix unary operators. This is used for
|
> -- e.g. substring(t from 1 to 5)
|
||||||
> -- symbol operators, keyword operators and multiple
|
> | SpecialOp String [ScalarExpr]
|
||||||
> -- keyword operators
|
> -- | case expression. both flavours supported. Multiple
|
||||||
> | PostfixOp String ScalarExpr
|
> -- condition when branches not currently supported (case when
|
||||||
> -- | Used for ternary, mixfix and other non
|
> -- a=4,b=5 then x end)
|
||||||
> -- orthodox operators, including the function
|
> | Case (Maybe ScalarExpr) -- test value
|
||||||
> -- looking calls which use keywords instead of
|
> [(ScalarExpr,ScalarExpr)] -- when branches
|
||||||
> -- commas to separate the arguments,
|
> (Maybe ScalarExpr) -- else value
|
||||||
> -- e.g. substring(t from 1 to 5)
|
> | Parens ScalarExpr
|
||||||
> | SpecialOp String [ScalarExpr]
|
> -- | cast(a as typename)
|
||||||
> -- | case expression. both flavours
|
> | Cast ScalarExpr TypeName
|
||||||
> -- supported. Multiple condition when branches not
|
> -- | prefix 'typed literal', e.g. int '42'
|
||||||
> -- currently supported (case when a=4,b=5 then x
|
> | CastOp TypeName String
|
||||||
> -- end)
|
> -- | exists, all, any, some subqueries
|
||||||
> | Case (Maybe ScalarExpr) -- test value
|
> | SubQueryExpr SubQueryExprType QueryExpr
|
||||||
> [(ScalarExpr,ScalarExpr)] -- when branches
|
> -- | in list literal and in subquery, if the bool is false it
|
||||||
> (Maybe ScalarExpr) -- else value
|
> -- means not in was used ('a not in (1,2)')
|
||||||
> | Parens ScalarExpr
|
> | In Bool ScalarExpr InThing
|
||||||
> -- | cast(a as typename)
|
> deriving (Eq,Show,Read)
|
||||||
> | Cast ScalarExpr TypeName
|
|
||||||
> -- | prefix 'typed literal', e.g. int '42'
|
|
||||||
> | CastOp TypeName String
|
|
||||||
> -- | exists, all, any, some subqueries
|
|
||||||
> | SubQueryExpr SubQueryExprType QueryExpr
|
|
||||||
> -- | in list literal and in subquery, if the bool
|
|
||||||
> -- is false it means not in was used ('a not in
|
|
||||||
> -- (1,2)')
|
|
||||||
> | In Bool -- true if in, false if not in
|
|
||||||
> ScalarExpr InThing
|
|
||||||
> deriving (Eq,Show,Read)
|
|
||||||
|
|
||||||
> -- | Represents a type name, used in casts.
|
> -- | Represents a type name, used in casts.
|
||||||
> data TypeName = TypeName String deriving (Eq,Show,Read)
|
> data TypeName = TypeName String deriving (Eq,Show,Read)
|
||||||
|
|
||||||
|
|
||||||
> -- | 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
3
TODO
|
@ -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
|
||||||
|
|
Loading…
Reference in a new issue