Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
Instances
Eq Command Source # | |
Show Command Source # | |
IsSql92Syntax Command Source # | |
Defined in Database.Beam.Backend.SQL.AST type Sql92SelectSyntax Command :: * Source # type Sql92InsertSyntax Command :: * Source # type Sql92UpdateSyntax Command :: * Source # type Sql92DeleteSyntax Command :: * 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 |
Instances
Eq Select Source # | |
Show Select Source # | |
IsSql92SelectSyntax Select Source # | |
Defined in Database.Beam.Backend.SQL.AST type Sql92SelectSelectTableSyntax Select :: * Source # type Sql92SelectOrderingSyntax Select :: * Source # selectStmt :: Sql92SelectSelectTableSyntax Select -> [Sql92SelectOrderingSyntax Select] -> Maybe Integer -> Maybe Integer -> Select Source # | |
HasQBuilder Select Source # | |
Defined in Database.Beam.Query.Types buildSqlQuery :: Projectible (Sql92SelectExpressionSyntax Select) a => TablePrefix -> Q Select db s a -> 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 #
SelectTable | |
UnionTables Bool SelectTable SelectTable | |
IntersectTables Bool SelectTable SelectTable | |
ExceptTable Bool SelectTable SelectTable |
Instances
Insert | |
|
Instances
Eq Insert Source # | |
Show Insert Source # | |
IsSql92InsertSyntax Insert Source # | |
Defined in Database.Beam.Backend.SQL.AST type Sql92InsertValuesSyntax Insert :: * Source # insertStmt :: Text -> [Text] -> Sql92InsertValuesSyntax Insert -> Insert Source # | |
type Sql92InsertValuesSyntax Insert Source # | |
Defined in Database.Beam.Backend.SQL.AST |
data InsertValues Source #
Instances
Eq InsertValues Source # | |
Defined in Database.Beam.Backend.SQL.AST (==) :: InsertValues -> InsertValues -> Bool # (/=) :: InsertValues -> InsertValues -> Bool # | |
Show InsertValues Source # | |
Defined in Database.Beam.Backend.SQL.AST showsPrec :: Int -> InsertValues -> ShowS # show :: InsertValues -> String # showList :: [InsertValues] -> ShowS # | |
IsSql92InsertValuesSyntax InsertValues Source # | |
Defined in Database.Beam.Backend.SQL.AST | |
type Sql92InsertValuesExpressionSyntax InsertValues Source # | |
Defined in Database.Beam.Backend.SQL.AST | |
type Sql92InsertValuesSelectSyntax InsertValues Source # | |
Defined in Database.Beam.Backend.SQL.AST |
Update | |
|
Instances
Eq Update Source # | |
Show Update Source # | |
IsSql92UpdateSyntax Update Source # | |
Defined in Database.Beam.Backend.SQL.AST type Sql92UpdateFieldNameSyntax Update :: * Source # type Sql92UpdateExpressionSyntax Update :: * Source # | |
type Sql92UpdateFieldNameSyntax Update Source # | |
Defined in Database.Beam.Backend.SQL.AST | |
type Sql92UpdateExpressionSyntax Update Source # | |
Defined in Database.Beam.Backend.SQL.AST |
Delete | |
|
Instances
Eq Delete Source # | |
Show Delete Source # | |
IsSql92DeleteSyntax Delete Source # | |
Defined in Database.Beam.Backend.SQL.AST type Sql92DeleteExpressionSyntax Delete :: * Source # | |
type Sql92DeleteExpressionSyntax Delete Source # | |
Defined in Database.Beam.Backend.SQL.AST |
data ComparatorQuantifier Source #
Instances
Eq ComparatorQuantifier Source # | |
Defined in Database.Beam.Backend.SQL.AST (==) :: ComparatorQuantifier -> ComparatorQuantifier -> Bool # (/=) :: ComparatorQuantifier -> ComparatorQuantifier -> Bool # | |
Show ComparatorQuantifier Source # | |
Defined in Database.Beam.Backend.SQL.AST showsPrec :: Int -> ComparatorQuantifier -> ShowS # show :: ComparatorQuantifier -> String # showList :: [ComparatorQuantifier] -> ShowS # | |
IsSql92QuantifierSyntax ComparatorQuantifier Source # | |
data ExtractField Source #
Instances
Eq ExtractField Source # | |
Defined in Database.Beam.Backend.SQL.AST (==) :: ExtractField -> ExtractField -> Bool # (/=) :: ExtractField -> ExtractField -> Bool # | |
Show ExtractField Source # | |
Defined in Database.Beam.Backend.SQL.AST showsPrec :: Int -> ExtractField -> ShowS # show :: ExtractField -> String # showList :: [ExtractField] -> ShowS # |
data CastTarget Source #
Instances
Eq CastTarget Source # | |
Defined in Database.Beam.Backend.SQL.AST (==) :: CastTarget -> CastTarget -> Bool # (/=) :: CastTarget -> CastTarget -> Bool # | |
Show CastTarget Source # | |
Defined in Database.Beam.Backend.SQL.AST showsPrec :: Int -> CastTarget -> ShowS # show :: CastTarget -> String # showList :: [CastTarget] -> ShowS # |
Instances
Eq DataType Source # | |
Show DataType Source # | |
IsSql92DataTypeSyntax DataType Source # | |
Defined in Database.Beam.Backend.SQL.AST 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 |
data SetQuantifier Source #
Instances
Eq SetQuantifier Source # | |
Defined in Database.Beam.Backend.SQL.AST (==) :: SetQuantifier -> SetQuantifier -> Bool # (/=) :: SetQuantifier -> SetQuantifier -> Bool # | |
Show SetQuantifier Source # | |
Defined in Database.Beam.Backend.SQL.AST showsPrec :: Int -> SetQuantifier -> ShowS # show :: SetQuantifier -> String # showList :: [SetQuantifier] -> ShowS # | |
IsSql92AggregationSetQuantifierSyntax SetQuantifier Source # | |
data Expression Source #
Instances
newtype Projection Source #
ProjExprs [(Expression, Maybe Text)] |
Instances
Eq Projection Source # | |
Defined in Database.Beam.Backend.SQL.AST (==) :: Projection -> Projection -> Bool # (/=) :: Projection -> Projection -> Bool # | |
Show Projection Source # | |
Defined in Database.Beam.Backend.SQL.AST showsPrec :: Int -> Projection -> ShowS # show :: Projection -> String # showList :: [Projection] -> ShowS # | |
IsSql92ProjectionSyntax Projection Source # | |
Defined in Database.Beam.Backend.SQL.AST | |
type Sql92ProjectionExpressionSyntax Projection Source # | |
Defined in Database.Beam.Backend.SQL.AST |
Instances
Eq Grouping Source # | |
Show Grouping Source # | |
IsSql92GroupingSyntax Grouping Source # | |
Defined in Database.Beam.Backend.SQL.AST type Sql92GroupingExpressionSyntax Grouping :: * Source # | |
type Sql92GroupingExpressionSyntax Grouping Source # | |
Defined in Database.Beam.Backend.SQL.AST |
data TableSource Source #
Instances
Eq TableSource Source # | |
Defined in Database.Beam.Backend.SQL.AST (==) :: TableSource -> TableSource -> Bool # (/=) :: TableSource -> TableSource -> Bool # | |
Show TableSource Source # | |
Defined in Database.Beam.Backend.SQL.AST showsPrec :: Int -> TableSource -> ShowS # show :: TableSource -> String # showList :: [TableSource] -> ShowS # | |
IsSql92TableSourceSyntax TableSource Source # | |
Defined in Database.Beam.Backend.SQL.AST type Sql92TableSourceSelectSyntax TableSource :: * Source # | |
type Sql92TableSourceSelectSyntax TableSource Source # | |
Defined in Database.Beam.Backend.SQL.AST |
FromTable TableSource (Maybe Text) | |
InnerJoin From From (Maybe Expression) | |
LeftJoin From From (Maybe Expression) | |
RightJoin From From (Maybe Expression) | |
OuterJoin From From (Maybe Expression) |
Instances
Eq From Source # | |
Show From Source # | |
IsSql92FromSyntax From Source # | |
Defined in Database.Beam.Backend.SQL.AST type Sql92FromTableSourceSyntax From :: * Source # type Sql92FromExpressionSyntax From :: * Source # fromTable :: Sql92FromTableSourceSyntax From -> 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 #
Instances
Eq WindowFrame Source # | |
Defined in Database.Beam.Backend.SQL.AST (==) :: WindowFrame -> WindowFrame -> Bool # (/=) :: WindowFrame -> WindowFrame -> Bool # | |
Show WindowFrame Source # | |
Defined in Database.Beam.Backend.SQL.AST showsPrec :: Int -> WindowFrame -> ShowS # show :: WindowFrame -> String # showList :: [WindowFrame] -> ShowS # | |
IsSql2003WindowFrameSyntax WindowFrame Source # | |
Defined in Database.Beam.Backend.SQL.AST | |
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 #
Instances
Eq WindowFrameBounds Source # | |
Defined in Database.Beam.Backend.SQL.AST (==) :: WindowFrameBounds -> WindowFrameBounds -> Bool # (/=) :: WindowFrameBounds -> WindowFrameBounds -> Bool # | |
Show WindowFrameBounds Source # | |
Defined in Database.Beam.Backend.SQL.AST showsPrec :: Int -> WindowFrameBounds -> ShowS # show :: WindowFrameBounds -> String # showList :: [WindowFrameBounds] -> ShowS # | |
IsSql2003WindowFrameBoundsSyntax WindowFrameBounds Source # | |
type Sql2003WindowFrameBoundsBoundSyntax WindowFrameBounds Source # | |
data WindowFrameBound Source #
Instances
Eq WindowFrameBound Source # | |
Defined in Database.Beam.Backend.SQL.AST (==) :: WindowFrameBound -> WindowFrameBound -> Bool # (/=) :: WindowFrameBound -> WindowFrameBound -> Bool # | |
Show WindowFrameBound Source # | |
Defined in Database.Beam.Backend.SQL.AST showsPrec :: Int -> WindowFrameBound -> ShowS # show :: WindowFrameBound -> String # showList :: [WindowFrameBound] -> ShowS # | |
IsSql2003WindowFrameBoundSyntax WindowFrameBound Source # | |
Defined in Database.Beam.Backend.SQL.AST |