(Beamable t, contextPredicate context) => ProjectibleWithPredicate contextPredicate be (WithExprContext (BeamSqlBackendExpressionSyntax' be)) (t (Nullable (QGenExpr context be s))) Source # | |
Instance detailsDefined in Database.Beam.Query.Internal |
(Beamable t, contextPredicate context) => ProjectibleWithPredicate contextPredicate be (WithExprContext (BeamSqlBackendExpressionSyntax' be)) (t (QGenExpr context be s)) Source # | |
Instance detailsDefined in Database.Beam.Query.Internal |
contextPredicate context => ProjectibleWithPredicate contextPredicate be (WithExprContext (BeamSqlBackendExpressionSyntax' be)) (QGenExpr context be s a) Source # | |
Instance detailsDefined in Database.Beam.Query.Internal |
Beamable tbl => ThreadRewritable s (tbl (Nullable (QGenExpr ctxt syntax s))) Source # | |
Instance detailsDefined in Database.Beam.Query.Internal |
Beamable tbl => ThreadRewritable s (tbl (QGenExpr ctxt syntax s)) Source # | |
Instance detailsDefined in Database.Beam.Query.Internal |
(BeamSqlBackend be, Beamable t) => SqlDeconstructMaybe be (t (Nullable (QGenExpr ctxt be s))) (t (QGenExpr ctxt be s)) s Source # | |
Instance detailsDefined in Database.Beam.Query.Combinators |
ThreadRewritable s (QGenExpr ctxt syntax s a) Source # | |
Instance detailsDefined in Database.Beam.Query.Internal |
BeamSqlBackend be => SqlDeconstructMaybe be (QGenExpr ctxt be s (Maybe x)) (QGenExpr ctxt be s x) s Source # | |
Instance detailsDefined in Database.Beam.Query.Combinators |
Beamable tbl => ContextRewritable (tbl (Nullable (QGenExpr old syntax s))) Source # | |
Instance detailsDefined in Database.Beam.Query.Internal |
Beamable tbl => ContextRewritable (tbl (QGenExpr old syntax s)) Source # | |
Instance detailsDefined in Database.Beam.Query.Internal |
(Beamable table, BeamSqlBackend be, FieldsFulfillConstraintNullable (BeamSqlBackendCanSerialize be) table) => SqlValable (table (Nullable (QGenExpr ctxt be s))) Source # | |
Instance detailsDefined in Database.Beam.Query.Combinators |
(Beamable table, BeamSqlBackend be, FieldsFulfillConstraint (BeamSqlBackendCanSerialize be) table) => SqlValable (table (QGenExpr ctxt be s)) Source # | |
Instance detailsDefined in Database.Beam.Query.Combinators |
(Table t, BeamSqlBackend be) => SqlJustable (t (QExpr be s)) (t (Nullable (QExpr be s))) Source # | |
Instance detailsDefined in Database.Beam.Query.Combinators |
Beamable tbl => QGroupable (tbl (Nullable (QExpr be s))) (tbl (Nullable (QGroupExpr be s))) Source # | group_ for any Beamable type. Adds every field in the type to the
grouping key. This is the equivalent of including the grouping expression
of each field in the type as part of the aggregate projection
|
Instance detailsDefined in Database.Beam.Query.Aggregate |
Beamable tbl => QGroupable (tbl (QExpr be s)) (tbl (QGroupExpr be s)) Source # | group_ for any Beamable type. Adds every field in the type to the
grouping key. This is the equivalent of including the grouping expression
of each field in the type as part of the aggregate projection
|
Instance detailsDefined in Database.Beam.Query.Aggregate |
(Table t, BeamSqlBackend be) => SqlJustable (PrimaryKey t (QExpr be s)) (PrimaryKey t (Nullable (QExpr be s))) Source # | |
Instance detailsDefined in Database.Beam.Query.Combinators |
(BeamSqlBackend be, Beamable tbl, FieldsFulfillConstraintNullable (HasSqlEqualityCheck be) tbl) => SqlEq (QGenExpr context be s) (tbl (Nullable (QGenExpr context be s))) Source # | |
Instance detailsDefined in Database.Beam.Query.Ord |
(BeamSqlBackend be, Beamable tbl, FieldsFulfillConstraint (HasSqlEqualityCheck be) tbl) => SqlEq (QGenExpr context be s) (tbl (QGenExpr context be s)) Source # | Compare two arbitrary Beamable types containing QGenExpr s for equality. |
Instance detailsDefined in Database.Beam.Query.Ord |
BeamSqlBackend be => SqlJustable (QExpr be s a) (QExpr be s (Maybe a)) Source # | |
Instance detailsDefined in Database.Beam.Query.Combinators |
QGroupable (QExpr be s a) (QGroupExpr be s a) Source # | group_ for simple value expressions.
|
Instance detailsDefined in Database.Beam.Query.Aggregate |
BeamSqlBackend be => SqlOrdQuantified (QGenExpr context be s) (QQuantified be s a) (QGenExpr context be s a) Source # | |
Instance detailsDefined in Database.Beam.Query.Ord |
(BeamSqlBackend be, HasSqlQuantifiedEqualityCheck be a) => SqlEqQuantified (QGenExpr context be s) (QQuantified be s a) (QGenExpr context be s a) Source # | Two arbitrary expressions can be quantifiably compared for equality. |
Instance detailsDefined in Database.Beam.Query.Ord |
Retaggable (QGenExpr ctxt expr s) (QGenExpr ctxt expr s t) Source # | |
Instance detailsDefined in Database.Beam.Query.Internal |
BeamSqlBackend be => SqlOrd (QGenExpr context be s) (QGenExpr context be s a) Source # | |
Instance detailsDefined in Database.Beam.Query.Ord |
(BeamSqlBackend be, HasSqlEqualityCheck be a) => SqlEq (QGenExpr context be s) (QGenExpr context be s a) Source # | Compare two arbitrary expressions (of the same type) for equality |
Instance detailsDefined in Database.Beam.Query.Ord |
BeamSqlBackend be => Eq (QGenExpr context be s t) Source # | |
Instance detailsDefined in Database.Beam.Query.Internal |
(Fractional a, BeamSqlBackend be, BeamSqlBackendCanSerialize be a) => Fractional (QGenExpr context be s a) Source # | |
Instance detailsDefined in Database.Beam.Query.Internal |
(Num a, BeamSqlBackend be, BeamSqlBackendCanSerialize be a) => Num (QGenExpr context be s a) Source # | |
Instance detailsDefined in Database.Beam.Query.Internal |
(BeamSqlBackend backend, BeamSqlBackendCanSerialize backend [Char]) => IsString (QGenExpr context backend s Text) Source # | |
Instance detailsDefined in Database.Beam.Query.Internal |
ContextRewritable (QGenExpr old syntax s a) Source # | |
Instance detailsDefined in Database.Beam.Query.Internal |
(BeamSqlBackendCanSerialize be a, BeamSqlBackend be) => SqlValable (QGenExpr ctxt be s a) Source # | |
Instance detailsDefined in Database.Beam.Query.Combinators |
type WithRewrittenThread s s' (tbl (Nullable (QGenExpr ctxt syntax s))) Source # | |
Instance detailsDefined in Database.Beam.Query.Internal |
type WithRewrittenThread s s' (tbl (QGenExpr ctxt syntax s)) Source # | |
Instance detailsDefined in Database.Beam.Query.Internal |
type WithRewrittenThread s s' (QGenExpr ctxt syntax s a) Source # | |
Instance detailsDefined in Database.Beam.Query.Internal |
type Retag tag (QGenExpr ctxt expr s t) Source # | |
Instance detailsDefined in Database.Beam.Query.Internal |
type QExprToField (table (Nullable (QGenExpr context syntax s))) Source # | |
Instance detailsDefined in Database.Beam.Query.Types |
type QExprToField (table (QGenExpr context syntax s)) Source # | |
Instance detailsDefined in Database.Beam.Query.Types |
type QExprToIdentity (table (QGenExpr context syntax s)) Source # | |
Instance detailsDefined in Database.Beam.Query.Types |
type HaskellLiteralForQExpr (table (QGenExpr context be s)) Source # | |
Instance detailsDefined in Database.Beam.Query.Combinators |
type WithRewrittenContext (tbl (Nullable (QGenExpr old syntax s))) ctxt Source # | |
Instance detailsDefined in Database.Beam.Query.Internal |
type WithRewrittenContext (tbl (QGenExpr old syntax s)) ctxt Source # | |
Instance detailsDefined in Database.Beam.Query.Internal |
type QExprToField (QGenExpr ctxt syntax s a) Source # | |
Instance detailsDefined in Database.Beam.Query.Types |
type QExprToIdentity (QGenExpr context syntax s a) Source # | |
Instance detailsDefined in Database.Beam.Query.Types |
type HaskellLiteralForQExpr (QGenExpr context be s a) Source # | |
Instance detailsDefined in Database.Beam.Query.Combinators |
type WithRewrittenContext (QGenExpr old syntax s a) ctxt Source # | |
Instance detailsDefined in Database.Beam.Query.Internal |