Safe Haskell | None |
---|---|
Language | Haskell2010 |
Database.Beam.Backend.SQL.AST
Description
This module implements an AST type for SQL92. It allows us to realize the call structure of the builders defined in Database.Beam.Backend.SQL.SQL92
Documentation
Constructors
SelectCommand Select | |
InsertCommand Insert | |
UpdateCommand Update | |
DeleteCommand Delete |
Instances
Eq Command Source # | |
Show Command Source # | |
IsSql92Syntax Command Source # | |
Defined in Database.Beam.Backend.SQL.AST Associated Types type Sql92SelectSyntax Command :: Type Source # type Sql92InsertSyntax Command :: Type Source # type Sql92UpdateSyntax Command :: Type Source # type Sql92DeleteSyntax Command :: Type Source # | |
type Sql92SelectSyntax Command Source # | |
Defined in Database.Beam.Backend.SQL.AST | |
type Sql92InsertSyntax Command Source # | |
Defined in Database.Beam.Backend.SQL.AST | |
type Sql92UpdateSyntax Command Source # | |
Defined in Database.Beam.Backend.SQL.AST | |
type Sql92DeleteSyntax Command Source # | |
Defined in Database.Beam.Backend.SQL.AST |
Constructors
Select | |
Fields |
Instances
Eq Select Source # | |
Show Select Source # | |
IsSql92SelectSyntax Select Source # | |
Defined in Database.Beam.Backend.SQL.AST Associated Types type Sql92SelectSelectTableSyntax Select :: Type Source # type Sql92SelectOrderingSyntax Select :: Type Source # Methods selectStmt :: Sql92SelectSelectTableSyntax Select -> [Sql92SelectOrderingSyntax Select] -> Maybe Integer -> Maybe Integer -> Select Source # | |
type Sql92SelectSelectTableSyntax Select Source # | |
Defined in Database.Beam.Backend.SQL.AST | |
type Sql92SelectOrderingSyntax Select Source # | |
Defined in Database.Beam.Backend.SQL.AST |
data SelectTable Source #
Constructors
SelectTable | |
Fields | |
UnionTables Bool SelectTable SelectTable | |
IntersectTables Bool SelectTable SelectTable | |
ExceptTable Bool SelectTable SelectTable |
Instances
Constructors
Insert | |
Fields
|
Instances
Eq Insert Source # | |
Show Insert Source # | |
IsSql92InsertSyntax Insert Source # | |
Defined in Database.Beam.Backend.SQL.AST Associated Types type Sql92InsertValuesSyntax Insert :: Type Source # type Sql92InsertTableNameSyntax Insert :: Type Source # Methods insertStmt :: Sql92InsertTableNameSyntax Insert -> [Text] -> Sql92InsertValuesSyntax Insert -> Insert Source # | |
type Sql92InsertValuesSyntax Insert Source # | |
Defined in Database.Beam.Backend.SQL.AST | |
type Sql92InsertTableNameSyntax Insert Source # | |
Defined in Database.Beam.Backend.SQL.AST |
data InsertValues Source #
Constructors
InsertValues | |
Fields | |
InsertSelect | |
Fields |
Instances
Eq InsertValues Source # | |
Defined in Database.Beam.Backend.SQL.AST | |
Show InsertValues Source # | |
Defined in Database.Beam.Backend.SQL.AST Methods showsPrec :: Int -> InsertValues -> ShowS # show :: InsertValues -> String # showList :: [InsertValues] -> ShowS # | |
IsSql92InsertValuesSyntax InsertValues Source # | |
Defined in Database.Beam.Backend.SQL.AST Associated Types type Sql92InsertValuesExpressionSyntax InsertValues :: Type Source # type Sql92InsertValuesSelectSyntax InsertValues :: Type Source # | |
type Sql92InsertValuesExpressionSyntax InsertValues Source # | |
Defined in Database.Beam.Backend.SQL.AST | |
type Sql92InsertValuesSelectSyntax InsertValues Source # | |
Defined in Database.Beam.Backend.SQL.AST |
Constructors
Update | |
Fields
|
Instances
Eq Update Source # | |
Show Update Source # | |
IsSql92UpdateSyntax Update Source # | |
Defined in Database.Beam.Backend.SQL.AST Associated Types type Sql92UpdateTableNameSyntax Update :: Type Source # type Sql92UpdateFieldNameSyntax Update :: Type Source # type Sql92UpdateExpressionSyntax Update :: Type Source # | |
type Sql92UpdateTableNameSyntax Update Source # | |
Defined in Database.Beam.Backend.SQL.AST | |
type Sql92UpdateFieldNameSyntax Update Source # | |
Defined in Database.Beam.Backend.SQL.AST | |
type Sql92UpdateExpressionSyntax Update Source # | |
Defined in Database.Beam.Backend.SQL.AST |
Constructors
Delete | |
Fields |
Instances
Eq Delete Source # | |
Show Delete Source # | |
IsSql92DeleteSyntax Delete Source # | |
Defined in Database.Beam.Backend.SQL.AST Associated Types type Sql92DeleteTableNameSyntax Delete :: Type Source # type Sql92DeleteExpressionSyntax Delete :: Type Source # Methods deleteStmt :: Sql92DeleteTableNameSyntax Delete -> Maybe Text -> Maybe (Sql92DeleteExpressionSyntax Delete) -> Delete Source # | |
type Sql92DeleteTableNameSyntax Delete Source # | |
Defined in Database.Beam.Backend.SQL.AST | |
type Sql92DeleteExpressionSyntax Delete Source # | |
Defined in Database.Beam.Backend.SQL.AST |
Constructors
QualifiedField Text Text | |
UnqualifiedField Text |
data ComparatorQuantifier Source #
Constructors
ComparatorQuantifierAny | |
ComparatorQuantifierAll |
Instances
Eq ComparatorQuantifier Source # | |
Defined in Database.Beam.Backend.SQL.AST Methods (==) :: ComparatorQuantifier -> ComparatorQuantifier -> Bool # (/=) :: ComparatorQuantifier -> ComparatorQuantifier -> Bool # | |
Show ComparatorQuantifier Source # | |
Defined in Database.Beam.Backend.SQL.AST Methods showsPrec :: Int -> ComparatorQuantifier -> ShowS # show :: ComparatorQuantifier -> String # showList :: [ComparatorQuantifier] -> ShowS # | |
IsSql92QuantifierSyntax ComparatorQuantifier Source # | |
Defined in Database.Beam.Backend.SQL.AST |
data ExtractField Source #
Constructors
Instances
Eq ExtractField Source # | |
Defined in Database.Beam.Backend.SQL.AST | |
Show ExtractField Source # | |
Defined in Database.Beam.Backend.SQL.AST Methods showsPrec :: Int -> ExtractField -> ShowS # show :: ExtractField -> String # showList :: [ExtractField] -> ShowS # | |
IsSql92ExtractFieldSyntax ExtractField Source # | |
Defined in Database.Beam.Backend.SQL.AST |
Constructors
Instances
Eq DataType Source # | |
Show DataType Source # | |
IsSql92DataTypeSyntax DataType Source # | |
Defined in Database.Beam.Backend.SQL.AST Methods domainType :: Text -> DataType Source # charType :: Maybe Word -> Maybe Text -> DataType Source # varCharType :: Maybe Word -> Maybe Text -> DataType Source # nationalCharType :: Maybe Word -> DataType Source # nationalVarCharType :: Maybe Word -> DataType Source # bitType :: Maybe Word -> DataType Source # varBitType :: Maybe Word -> DataType Source # numericType :: Maybe (Word, Maybe Word) -> DataType Source # decimalType :: Maybe (Word, Maybe Word) -> DataType Source # smallIntType :: DataType Source # floatType :: Maybe Word -> DataType Source # doubleType :: DataType Source # | |
IsSql99DataTypeSyntax DataType Source # | |
IsSql2008BigIntDataTypeSyntax DataType Source # | |
Defined in Database.Beam.Backend.SQL.AST Methods |
data SetQuantifier Source #
Constructors
SetQuantifierAll | |
SetQuantifierDistinct |
Instances
Eq SetQuantifier Source # | |
Defined in Database.Beam.Backend.SQL.AST Methods (==) :: SetQuantifier -> SetQuantifier -> Bool # (/=) :: SetQuantifier -> SetQuantifier -> Bool # | |
Show SetQuantifier Source # | |
Defined in Database.Beam.Backend.SQL.AST Methods showsPrec :: Int -> SetQuantifier -> ShowS # show :: SetQuantifier -> String # showList :: [SetQuantifier] -> ShowS # | |
IsSql92AggregationSetQuantifierSyntax SetQuantifier Source # | |
Defined in Database.Beam.Backend.SQL.AST |
data Expression Source #
Constructors
Instances
newtype Projection Source #
Constructors
ProjExprs [(Expression, Maybe Text)] |
Instances
Eq Projection Source # | |
Defined in Database.Beam.Backend.SQL.AST | |
Show Projection Source # | |
Defined in Database.Beam.Backend.SQL.AST Methods showsPrec :: Int -> Projection -> ShowS # show :: Projection -> String # showList :: [Projection] -> ShowS # | |
IsSql92ProjectionSyntax Projection Source # | |
Defined in Database.Beam.Backend.SQL.AST Associated Types type Sql92ProjectionExpressionSyntax Projection :: Type Source # Methods projExprs :: [(Sql92ProjectionExpressionSyntax Projection, Maybe Text)] -> Projection Source # | |
type Sql92ProjectionExpressionSyntax Projection Source # | |
Defined in Database.Beam.Backend.SQL.AST |
Constructors
OrderingAsc Expression | |
OrderingDesc Expression |
Instances
Eq Ordering Source # | |
Show Ordering Source # | |
IsSql92OrderingSyntax Ordering Source # | |
Defined in Database.Beam.Backend.SQL.AST Associated Types type Sql92OrderingExpressionSyntax Ordering :: Type Source # | |
type Sql92OrderingExpressionSyntax Ordering Source # | |
Defined in Database.Beam.Backend.SQL.AST |
Constructors
Grouping [Expression] |
Instances
Eq Grouping Source # | |
Show Grouping Source # | |
IsSql92GroupingSyntax Grouping Source # | |
Defined in Database.Beam.Backend.SQL.AST Associated Types type Sql92GroupingExpressionSyntax Grouping :: Type Source # Methods groupByExpressions :: [Sql92GroupingExpressionSyntax Grouping] -> Grouping Source # | |
type Sql92GroupingExpressionSyntax Grouping Source # | |
Defined in Database.Beam.Backend.SQL.AST |
Instances
Eq TableName Source # | |
Ord TableName Source # | |
Show TableName Source # | |
IsSql92TableNameSyntax TableName Source # | |
data TableSource Source #
Constructors
TableNamed TableName | |
TableFromSubSelect Select | |
TableFromValues [[Expression]] |
Instances
Eq TableSource Source # | |
Defined in Database.Beam.Backend.SQL.AST | |
Show TableSource Source # | |
Defined in Database.Beam.Backend.SQL.AST Methods showsPrec :: Int -> TableSource -> ShowS # show :: TableSource -> String # showList :: [TableSource] -> ShowS # | |
IsSql92TableSourceSyntax TableSource Source # | |
Defined in Database.Beam.Backend.SQL.AST Associated Types type Sql92TableSourceSelectSyntax TableSource :: Type Source # type Sql92TableSourceExpressionSyntax TableSource :: Type Source # type Sql92TableSourceTableNameSyntax TableSource :: Type Source # | |
type Sql92TableSourceSelectSyntax TableSource Source # | |
Defined in Database.Beam.Backend.SQL.AST | |
type Sql92TableSourceExpressionSyntax TableSource Source # | |
Defined in Database.Beam.Backend.SQL.AST | |
type Sql92TableSourceTableNameSyntax TableSource Source # | |
Defined in Database.Beam.Backend.SQL.AST |
Constructors
Instances
Eq From Source # | |
Show From Source # | |
IsSql92FromSyntax From Source # | |
Defined in Database.Beam.Backend.SQL.AST Associated Types type Sql92FromTableSourceSyntax From :: Type Source # type Sql92FromExpressionSyntax From :: Type Source # Methods fromTable :: Sql92FromTableSourceSyntax From -> Maybe (Text, Maybe [Text]) -> From Source # innerJoin :: From -> From -> Maybe (Sql92FromExpressionSyntax From) -> From Source # leftJoin :: From -> From -> Maybe (Sql92FromExpressionSyntax From) -> From Source # rightJoin :: From -> From -> Maybe (Sql92FromExpressionSyntax From) -> From Source # | |
type Sql92FromTableSourceSyntax From Source # | |
Defined in Database.Beam.Backend.SQL.AST | |
type Sql92FromExpressionSyntax From Source # | |
Defined in Database.Beam.Backend.SQL.AST |
Instances
data WindowFrame Source #
Constructors
WindowFrame | |
Fields |
Instances
Eq WindowFrame Source # | |
Defined in Database.Beam.Backend.SQL.AST | |
Show WindowFrame Source # | |
Defined in Database.Beam.Backend.SQL.AST Methods showsPrec :: Int -> WindowFrame -> ShowS # show :: WindowFrame -> String # showList :: [WindowFrame] -> ShowS # | |
IsSql2003WindowFrameSyntax WindowFrame Source # | |
Defined in Database.Beam.Backend.SQL.AST Associated Types type Sql2003WindowFrameExpressionSyntax WindowFrame :: Type Source # type Sql2003WindowFrameOrderingSyntax WindowFrame :: Type Source # type Sql2003WindowFrameBoundsSyntax WindowFrame :: Type Source # | |
type Sql2003WindowFrameExpressionSyntax WindowFrame Source # | |
Defined in Database.Beam.Backend.SQL.AST | |
type Sql2003WindowFrameOrderingSyntax WindowFrame Source # | |
Defined in Database.Beam.Backend.SQL.AST | |
type Sql2003WindowFrameBoundsSyntax WindowFrame Source # | |
data WindowFrameBounds Source #
Constructors
WindowFrameBounds | |
Fields |
Instances
Eq WindowFrameBounds Source # | |
Defined in Database.Beam.Backend.SQL.AST Methods (==) :: WindowFrameBounds -> WindowFrameBounds -> Bool # (/=) :: WindowFrameBounds -> WindowFrameBounds -> Bool # | |
Show WindowFrameBounds Source # | |
Defined in Database.Beam.Backend.SQL.AST Methods showsPrec :: Int -> WindowFrameBounds -> ShowS # show :: WindowFrameBounds -> String # showList :: [WindowFrameBounds] -> ShowS # | |
IsSql2003WindowFrameBoundsSyntax WindowFrameBounds Source # | |
Defined in Database.Beam.Backend.SQL.AST Associated Types type Sql2003WindowFrameBoundsBoundSyntax WindowFrameBounds :: Type Source # | |
type Sql2003WindowFrameBoundsBoundSyntax WindowFrameBounds Source # | |
data WindowFrameBound Source #
Constructors
WindowFrameUnbounded | |
WindowFrameBoundNRows Int |
Instances
Eq WindowFrameBound Source # | |
Defined in Database.Beam.Backend.SQL.AST Methods (==) :: WindowFrameBound -> WindowFrameBound -> Bool # (/=) :: WindowFrameBound -> WindowFrameBound -> Bool # | |
Show WindowFrameBound Source # | |
Defined in Database.Beam.Backend.SQL.AST Methods showsPrec :: Int -> WindowFrameBound -> ShowS # show :: WindowFrameBound -> String # showList :: [WindowFrameBound] -> ShowS # | |
IsSql2003WindowFrameBoundSyntax WindowFrameBound Source # | |
Defined in Database.Beam.Backend.SQL.AST Methods |