1
Fork 0

add Data and Typeable to the syntax

This commit is contained in:
Jake Wheat 2014-04-10 18:53:11 +03:00
parent da27d3147f
commit 4989f5251b
2 changed files with 23 additions and 21 deletions

View file

@ -1,5 +1,6 @@
> -- | The AST for SQL queries. > -- | The AST for SQL queries.
> {-# LANGUAGE DeriveDataTypeable #-}
> module Language.SQL.SimpleSQL.Syntax > module Language.SQL.SimpleSQL.Syntax
> (-- * Value expressions > (-- * Value expressions
> ValueExpr(..) > ValueExpr(..)
@ -27,6 +28,7 @@
> ,JoinCondition(..) > ,JoinCondition(..)
> ) where > ) where
> import Data.Data
> -- | Represents a value expression. This is used for the expressions > -- | Represents a value expression. This is used for the expressions
> -- in select lists. It is also used for expressions in where, group > -- in select lists. It is also used for expressions in where, group
@ -119,25 +121,25 @@
> -- means not in was used ('a not in (1,2)') > -- means not in was used ('a not in (1,2)')
> | In Bool ValueExpr InPredValue > | In Bool ValueExpr InPredValue
> | Parameter -- ^ Represents a ? in a parameterized query > | Parameter -- ^ Represents a ? in a parameterized query
> deriving (Eq,Show,Read) > 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.
> data Name = Name String > data Name = Name String
> | QName String > | QName String
> deriving (Eq,Show,Read) > deriving (Eq,Show,Read,Data,Typeable)
> -- | Represents a type name, used in casts. > -- | Represents a type name, used in casts.
> data TypeName = TypeName String > data TypeName = TypeName String
> | PrecTypeName String Int > | PrecTypeName String Int
> | PrecScaleTypeName String Int Int > | PrecScaleTypeName String Int Int
> deriving (Eq,Show,Read) > deriving (Eq,Show,Read,Data,Typeable)
> -- | Used for 'expr in (value expression list)', and 'expr in > -- | Used for 'expr in (value expression list)', and 'expr in
> -- (subquery)' syntax. > -- (subquery)' syntax.
> data InPredValue = InList [ValueExpr] > data InPredValue = InList [ValueExpr]
> | InQueryExpr QueryExpr > | InQueryExpr QueryExpr
> deriving (Eq,Show,Read) > deriving (Eq,Show,Read,Data,Typeable)
> -- | A subquery in a value expression. > -- | A subquery in a value expression.
> data SubQueryExprType > data SubQueryExprType
@ -151,28 +153,28 @@
> | SqSome > | SqSome
> -- | any (query expr) > -- | any (query expr)
> | SqAny > | SqAny
> deriving (Eq,Show,Read) > deriving (Eq,Show,Read,Data,Typeable)
> -- | Represents one field in an order by list. > -- | Represents one field in an order by list.
> data SortSpec = SortSpec ValueExpr Direction NullsOrder > data SortSpec = SortSpec ValueExpr Direction NullsOrder
> deriving (Eq,Show,Read) > deriving (Eq,Show,Read,Data,Typeable)
> -- | Represents 'nulls first' or 'nulls last' in an order by clause. > -- | Represents 'nulls first' or 'nulls last' in an order by clause.
> data NullsOrder = NullsOrderDefault > data NullsOrder = NullsOrderDefault
> | NullsFirst > | NullsFirst
> | NullsLast > | NullsLast
> deriving (Eq,Show,Read) > deriving (Eq,Show,Read,Data,Typeable)
> -- | Represents the frame clause of a window > -- | Represents the frame clause of a window
> -- this can be [range | rows] frame_start > -- this can be [range | rows] frame_start
> -- or [range | rows] between frame_start and frame_end > -- or [range | rows] between frame_start and frame_end
> data Frame = FrameFrom FrameRows FramePos > data Frame = FrameFrom FrameRows FramePos
> | FrameBetween FrameRows FramePos FramePos > | FrameBetween FrameRows FramePos FramePos
> deriving (Eq,Show,Read) > deriving (Eq,Show,Read,Data,Typeable)
> -- | Represents whether a window frame clause is over rows or ranges. > -- | Represents whether a window frame clause is over rows or ranges.
> data FrameRows = FrameRows | FrameRange > data FrameRows = FrameRows | FrameRange
> deriving (Eq,Show,Read) > deriving (Eq,Show,Read,Data,Typeable)
> -- | represents the start or end of a frame > -- | represents the start or end of a frame
> data FramePos = UnboundedPreceding > data FramePos = UnboundedPreceding
@ -180,7 +182,7 @@
> | Current > | Current
> | Following ValueExpr > | Following ValueExpr
> | UnboundedFollowing > | UnboundedFollowing
> deriving (Eq,Show,Read) > deriving (Eq,Show,Read,Data,Typeable)
> -- | Represents a query expression, which can be: > -- | Represents a query expression, which can be:
> -- > --
@ -226,7 +228,7 @@ This would make some things a bit cleaner?
> ,qeQueryExpression :: QueryExpr} > ,qeQueryExpression :: QueryExpr}
> | Values [[ValueExpr]] > | Values [[ValueExpr]]
> | Table Name > | Table Name
> deriving (Eq,Show,Read) > deriving (Eq,Show,Read,Data,Typeable)
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
@ -261,14 +263,14 @@ 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
> -- application, or in a query expression set operator. > -- application, or in a query expression set operator.
> data SetQuantifier = Distinct | All deriving (Eq,Show,Read) > data SetQuantifier = Distinct | All deriving (Eq,Show,Read,Data,Typeable)
> -- | The direction for a column in order by. > -- | The direction for a column in order by.
> data Direction = Asc | Desc deriving (Eq,Show,Read) > data Direction = Asc | Desc deriving (Eq,Show,Read,Data,Typeable)
> -- | Query expression set operators. > -- | Query expression set operators.
> data CombineOp = Union | Except | Intersect deriving (Eq,Show,Read) > data CombineOp = Union | Except | Intersect deriving (Eq,Show,Read,Data,Typeable)
> -- | 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,Data,Typeable)
> -- | Represents an item in a group by clause. > -- | Represents an item in a group by clause.
> data GroupingExpr > data GroupingExpr
@ -277,7 +279,7 @@ I'm not sure if this is valid syntax or not.
> | Rollup [GroupingExpr] > | Rollup [GroupingExpr]
> | GroupingSets [GroupingExpr] > | GroupingSets [GroupingExpr]
> | SimpleGroup ValueExpr > | SimpleGroup ValueExpr
> deriving (Eq,Show,Read) > deriving (Eq,Show,Read,Data,Typeable)
> -- | Represents a entry in the csv of tables in the from clause. > -- | Represents a entry in the csv of tables in the from clause.
> data TableRef = -- | from t > data TableRef = -- | from t
@ -296,20 +298,20 @@ I'm not sure if this is valid syntax or not.
> | TRFunction Name [ValueExpr] > | TRFunction Name [ValueExpr]
> -- | from lateral t > -- | from lateral t
> | TRLateral TableRef > | TRLateral TableRef
> deriving (Eq,Show,Read) > deriving (Eq,Show,Read,Data,Typeable)
> -- | Represents an alias for a table valued expression, used in with > -- | Represents an alias for a table valued expression, used in with
> -- queries and in from alias, e.g. select a from t u, select a from t u(b), > -- queries and in from alias, e.g. select a from t u, select a from t u(b),
> -- with a(c) as select 1, select * from a. > -- with a(c) as select 1, select * from a.
> data Alias = Alias Name (Maybe [Name]) > data Alias = Alias Name (Maybe [Name])
> deriving (Eq,Show,Read) > deriving (Eq,Show,Read,Data,Typeable)
> -- | The type of a join. > -- | The type of a join.
> data JoinType = JInner | JLeft | JRight | JFull | JCross > data JoinType = JInner | JLeft | JRight | JFull | JCross
> deriving (Eq,Show,Read) > deriving (Eq,Show,Read,Data,Typeable)
> -- | The join condition. > -- | The join condition.
> data JoinCondition = JoinOn ValueExpr -- ^ on expr > data JoinCondition = JoinOn ValueExpr -- ^ on expr
> | JoinUsing [Name] -- ^ using (column list) > | JoinUsing [Name] -- ^ using (column list)
> | JoinNatural -- ^ natural join was used > | JoinNatural -- ^ natural join was used
> deriving (Eq,Show,Read) > deriving (Eq,Show,Read,Data,Typeable)

View file

@ -64,7 +64,7 @@ Test-Suite Tests
Language.SQL.SimpleSQL.Tests, Language.SQL.SimpleSQL.Tests,
Language.SQL.SimpleSQL.Tpch Language.SQL.SimpleSQL.Tpch
other-extensions: TupleSections,OverloadedStrings other-extensions: TupleSections,OverloadedStrings,DeriveDataTypeable
default-language: Haskell2010 default-language: Haskell2010
ghc-options: -Wall ghc-options: -Wall