Safe Haskell | None |
---|---|
Language | Haskell2010 |
- Query type
- Various SQL functions and constructs
- SQL
UPDATE
assignments - Project Haskell values to
QGenExpr
s - General query combinators
- Window functions
- Ordering primitives
- Various combinators corresponding to SQL extensions
- Relationships
- SQL
EXTRACT
support - Operators
- Aggregates
- SQL Command construction and execution
Synopsis
- type Projectible be = ProjectibleWithPredicate AnyType be (WithExprContext (BeamSqlBackendExpressionSyntax' be))
- data QWindow be s
- type QExpr = QGenExpr QValueContext
- newtype QGenExpr context be s t = QExpr (TablePrefix -> BeamSqlBackendExpressionSyntax be)
- data Q be (db :: (Type -> Type) -> Type) s a
- class BeamSqlBackend be => HasQBuilder be where
- buildSqlQuery :: Projectible be a => TablePrefix -> Q be db s a -> BeamSqlBackendSelectSyntax be
- type family QExprToField x
- type family QExprToIdentity x
- data QAggregateContext
- data QGroupingContext
- data QValueContext
- data QWindowingContext
- data QWindowFrameContext
- type QGenExprTable ctxt be s tbl = tbl (QGenExpr ctxt be s)
- type QExprTable be s tbl = QGenExprTable QValueContext be s tbl
- data QAssignment be s
- data QField s ty
- data QFieldAssignment be tbl a
- data QBaseScope
- coalesce_ :: BeamSqlBackend be => [QGenExpr ctxt be s (Maybe a)] -> QGenExpr ctxt be s a -> QGenExpr ctxt be s a
- fromMaybe_ :: BeamSqlBackend be => QGenExpr ctxt be s a -> QGenExpr ctxt be s (Maybe a) -> QGenExpr ctxt be s a
- position_ :: (BeamSqlBackendIsString be text, BeamSqlBackend be, Integral b) => QExpr be s text -> QExpr be s text -> QExpr be s b
- charLength_ :: (BeamSqlBackend be, BeamSqlBackendIsString be text, Integral a) => QGenExpr context be s text -> QGenExpr context be s a
- octetLength_ :: (BeamSqlBackend be, BeamSqlBackendIsString be text, Integral a) => QGenExpr context be s text -> QGenExpr context be s a
- bitLength_ :: (BeamSqlBackend be, Integral a) => QGenExpr context be s SqlBitString -> QGenExpr context be s a
- currentTimestamp_ :: BeamSqlBackend be => QGenExpr ctxt be s LocalTime
- lower_ :: (BeamSqlBackendIsString be text, BeamSqlBackend be) => QGenExpr context be s text -> QGenExpr context be s text
- upper_ :: (BeamSqlBackendIsString be text, BeamSqlBackend be) => QGenExpr context be s text -> QGenExpr context be s text
- trim_ :: (BeamSqlBackendIsString be text, BeamSqlBackend be) => QGenExpr context be s text -> QGenExpr context be s text
- if_ :: BeamSqlBackend be => [QIfCond context be s a] -> QIfElse context be s a -> QGenExpr context be s a
- then_ :: QGenExpr context be s Bool -> QGenExpr context be s a -> QIfCond context be s a
- else_ :: QGenExpr context be s a -> QIfElse context be s a
- then_' :: QGenExpr context be s SqlBool -> QGenExpr context be s a -> QIfCond context be s a
- ifThenElse_ :: BeamSqlBackend be => QGenExpr context be s Bool -> QGenExpr context be s a -> QGenExpr context be s a -> QGenExpr context be s a
- bool_ :: BeamSqlBackend be => QGenExpr context be s a -> QGenExpr context be s a -> QGenExpr context be s Bool -> QGenExpr context be s a
- (<-.) :: SqlUpdatable be s lhs rhs => lhs -> rhs -> QAssignment be s
- current_ :: BeamSqlBackend be => QField s ty -> QExpr be s ty
- type family HaskellLiteralForQExpr x = a
- class SqlValable a where
- val_ :: HaskellLiteralForQExpr a -> a
- type SqlValableTable be table = (Beamable table, FieldsFulfillConstraint (HasSqlValueSyntax (BeamSqlBackendValueSyntax be)) table)
- default_ :: BeamSqlBackend be => QGenExpr ctxt be s a
- all_ :: (Database be db, BeamSqlBackend be) => DatabaseEntity be db (TableEntity table) -> Q be db s (table (QExpr be s))
- values_ :: forall be db s a. (Projectible be a, BeamSqlBackend be) => [a] -> Q be db s a
- allFromView_ :: (Database be db, Beamable table, BeamSqlBackend be) => DatabaseEntity be db (ViewEntity table) -> Q be db s (table (QExpr be s))
- join_ :: (Database be db, Table table, BeamSqlBackend be) => DatabaseEntity be db (TableEntity table) -> (table (QExpr be s) -> QExpr be s Bool) -> Q be db s (table (QExpr be s))
- join_' :: (Database be db, Table table, BeamSqlBackend be) => DatabaseEntity be db (TableEntity table) -> (table (QExpr be s) -> QExpr be s SqlBool) -> Q be db s (table (QExpr be s))
- guard_ :: forall be db s. BeamSqlBackend be => QExpr be s Bool -> Q be db s ()
- guard_' :: forall be db s. BeamSqlBackend be => QExpr be s SqlBool -> Q be db s ()
- filter_ :: forall r be db s. BeamSqlBackend be => (r -> QExpr be s Bool) -> Q be db s r -> Q be db s r
- filter_' :: forall r be db s. BeamSqlBackend be => (r -> QExpr be s SqlBool) -> Q be db s r -> Q be db s r
- related_ :: forall be db rel s. (Database be db, Table rel, BeamSqlBackend be, HasTableEquality be (PrimaryKey rel)) => DatabaseEntity be db (TableEntity rel) -> PrimaryKey rel (QExpr be s) -> Q be db s (rel (QExpr be s))
- relatedBy_ :: forall be db rel s. (Database be db, Table rel, BeamSqlBackend be) => DatabaseEntity be db (TableEntity rel) -> (rel (QExpr be s) -> QExpr be s Bool) -> Q be db s (rel (QExpr be s))
- relatedBy_' :: forall be db rel s. (Database be db, Table rel, BeamSqlBackend be) => DatabaseEntity be db (TableEntity rel) -> (rel (QExpr be s) -> QExpr be s SqlBool) -> Q be db s (rel (QExpr be s))
- leftJoin_ :: forall s r be db. (BeamSqlBackend be, Projectible be r, ThreadRewritable (QNested s) r, Retaggable (QExpr be s) (WithRewrittenThread (QNested s) s r)) => Q be db (QNested s) r -> (WithRewrittenThread (QNested s) s r -> QExpr be s Bool) -> Q be db s (Retag Nullable (WithRewrittenThread (QNested s) s r))
- leftJoin_' :: forall s r be db. (BeamSqlBackend be, Projectible be r, ThreadRewritable (QNested s) r, Retaggable (QExpr be s) (WithRewrittenThread (QNested s) s r)) => Q be db (QNested s) r -> (WithRewrittenThread (QNested s) s r -> QExpr be s SqlBool) -> Q be db s (Retag Nullable (WithRewrittenThread (QNested s) s r))
- perhaps_ :: forall s r be db. (Projectible be r, BeamSqlBackend be, ThreadRewritable (QNested s) r, Retaggable (QExpr be s) (WithRewrittenThread (QNested s) s r)) => Q be db (QNested s) r -> Q be db s (Retag Nullable (WithRewrittenThread (QNested s) s r))
- outerJoin_ :: forall s a b be db. (BeamSqlBackend be, BeamSqlBackendSupportsOuterJoin be, Projectible be a, Projectible be b, ThreadRewritable (QNested s) a, ThreadRewritable (QNested s) b, Retaggable (QExpr be s) (WithRewrittenThread (QNested s) s a), Retaggable (QExpr be s) (WithRewrittenThread (QNested s) s b)) => Q be db (QNested s) a -> Q be db (QNested s) b -> ((WithRewrittenThread (QNested s) s a, WithRewrittenThread (QNested s) s b) -> QExpr be s Bool) -> Q be db s (Retag Nullable (WithRewrittenThread (QNested s) s a), Retag Nullable (WithRewrittenThread (QNested s) s b))
- outerJoin_' :: forall s a b be db. (BeamSqlBackend be, BeamSqlBackendSupportsOuterJoin be, Projectible be a, Projectible be b, ThreadRewritable (QNested s) a, ThreadRewritable (QNested s) b, Retaggable (QExpr be s) (WithRewrittenThread (QNested s) s a), Retaggable (QExpr be s) (WithRewrittenThread (QNested s) s b)) => Q be db (QNested s) a -> Q be db (QNested s) b -> ((WithRewrittenThread (QNested s) s a, WithRewrittenThread (QNested s) s b) -> QExpr be s SqlBool) -> Q be db s (Retag Nullable (WithRewrittenThread (QNested s) s a), Retag Nullable (WithRewrittenThread (QNested s) s b))
- subselect_ :: forall s r be db. (ThreadRewritable (QNested s) r, Projectible be r) => Q be db (QNested s) r -> Q be db s (WithRewrittenThread (QNested s) s r)
- references_ :: (Table t, BeamSqlBackend be, HasTableEquality be (PrimaryKey t)) => PrimaryKey t (QGenExpr ctxt be s) -> t (QGenExpr ctxt be s) -> QGenExpr ctxt be s Bool
- references_' :: (Table t, BeamSqlBackend be, HasTableEquality be (PrimaryKey t)) => PrimaryKey t (QGenExpr ctxt be s) -> t (QGenExpr ctxt be s) -> QGenExpr ctxt be s SqlBool
- nub_ :: (BeamSqlBackend be, Projectible be r) => Q be db s r -> Q be db s r
- class SqlJustable a b | b -> a where
- class BeamSqlBackend be => SqlDeconstructMaybe be a nonNullA s | a s -> be, a -> nonNullA, a -> s, nonNullA -> s where
- class SqlOrderable be a | a -> be
- data QIfCond context be s a
- data QIfElse context be s a
- (<|>.) :: (SqlJustable a (QGenExpr ctxt syntax s y), SqlDeconstructMaybe syntax (QGenExpr ctxt syntax s y) a s) => QGenExpr ctxt syntax s y -> QGenExpr ctxt syntax s y -> QGenExpr ctxt syntax s y
- limit_ :: forall s a be db. (Projectible be a, ThreadRewritable (QNested s) a) => Integer -> Q be db (QNested s) a -> Q be db s (WithRewrittenThread (QNested s) s a)
- offset_ :: forall s a be db. (Projectible be a, ThreadRewritable (QNested s) a) => Integer -> Q be db (QNested s) a -> Q be db s (WithRewrittenThread (QNested s) s a)
- as_ :: forall a ctxt be s. QGenExpr ctxt be s a -> QGenExpr ctxt be s a
- exists_ :: (BeamSqlBackend be, HasQBuilder be, Projectible be a) => Q be db s a -> QExpr be s Bool
- unique_ :: (BeamSqlBackend be, HasQBuilder be, Projectible be a) => Q be db s a -> QExpr be s Bool
- distinct_ :: (BeamSqlBackend be, BeamSql99ExpressionBackend be, HasQBuilder be, Projectible be a) => Q be db s a -> QExpr be s Bool
- subquery_ :: (BeamSqlBackend be, HasQBuilder be, Projectible be (QExpr be s a)) => Q be db s (QExpr be s a) -> QGenExpr ctxt be s a
- union_ :: forall be db s a. (BeamSqlBackend be, Projectible be a, ThreadRewritable (QNested s) a) => Q be db (QNested s) a -> Q be db (QNested s) a -> Q be db s (WithRewrittenThread (QNested s) s a)
- unionAll_ :: forall be db s a. (BeamSqlBackend be, Projectible be a, ThreadRewritable (QNested s) a) => Q be db (QNested s) a -> Q be db (QNested s) a -> Q be db s (WithRewrittenThread (QNested s) s a)
- intersect_ :: forall be db s a. (BeamSqlBackend be, Projectible be a, ThreadRewritable (QNested s) a) => Q be db (QNested s) a -> Q be db (QNested s) a -> Q be db s (WithRewrittenThread (QNested s) s a)
- intersectAll_ :: forall be db s a. (BeamSqlBackend be, Projectible be a, ThreadRewritable (QNested s) a) => Q be db (QNested s) a -> Q be db (QNested s) a -> Q be db s (WithRewrittenThread (QNested s) s a)
- except_ :: forall be db s a. (BeamSqlBackend be, Projectible be a, ThreadRewritable (QNested s) a) => Q be db (QNested s) a -> Q be db (QNested s) a -> Q be db s (WithRewrittenThread (QNested s) s a)
- exceptAll_ :: forall be db s a. (BeamSqlBackend be, Projectible be a, ThreadRewritable (QNested s) a) => Q be db (QNested s) a -> Q be db (QNested s) a -> Q be db s (WithRewrittenThread (QNested s) s a)
- over_ :: BeamSql2003ExpressionBackend be => QAgg be s a -> QWindow be s -> QWindowExpr be s a
- frame_ :: forall be ordering partition s. (BeamSql2003ExpressionBackend be, SqlOrderable be ordering, Projectible be partition) => Maybe partition -> Maybe ordering -> QFrameBounds be -> QWindow be s
- bounds_ :: BeamSql2003ExpressionBackend be => QFrameBound be -> Maybe (QFrameBound be) -> QFrameBounds be
- unbounded_ :: BeamSql2003ExpressionBackend be => QFrameBound be
- nrows_ :: BeamSql2003ExpressionBackend be => Int -> QFrameBound be
- fromBound_ :: BeamSql2003ExpressionBackend be => QFrameBound be -> QFrameBounds be
- noBounds_ :: QFrameBounds be
- noOrder_ :: Integral a => Maybe (QOrd be s a)
- noPartition_ :: Integral a => Maybe (QExpr be s a)
- partitionBy_ :: partition -> Maybe partition
- orderPartitionBy_ :: partition -> Maybe partition
- withWindow_ :: forall window a s r be db. (ProjectibleWithPredicate WindowFrameContext be (WithExprContext (BeamSqlBackendWindowFrameSyntax' be)) window, Projectible be r, Projectible be a, ContextRewritable a, ThreadRewritable (QNested s) (WithRewrittenContext a QValueContext)) => (r -> window) -> (r -> window -> a) -> Q be db (QNested s) r -> Q be db s (WithRewrittenThread (QNested s) s (WithRewrittenContext a QValueContext))
- orderBy_ :: forall s a ordering be db. (Projectible be a, SqlOrderable be ordering, ThreadRewritable (QNested s) a) => (a -> ordering) -> Q be db (QNested s) a -> Q be db s (WithRewrittenThread (QNested s) s a)
- asc_ :: forall be s a. BeamSqlBackend be => QExpr be s a -> QOrd be s a
- desc_ :: forall be s a. BeamSqlBackend be => QExpr be s a -> QOrd be s a
- nullsFirst_ :: IsSql2003OrderingElementaryOLAPOperationsSyntax (BeamSqlBackendOrderingSyntax be) => QOrd be s a -> QOrd be s a
- nullsLast_ :: IsSql2003OrderingElementaryOLAPOperationsSyntax (BeamSqlBackendOrderingSyntax be) => QOrd be s a -> QOrd be s a
- ntile_ :: (BeamSqlBackend be, BeamSqlT614Backend be, Integral n) => QExpr be s n -> QAgg be s a
- lead1_ :: (BeamSqlBackend be, BeamSqlT615Backend be) => QExpr be s a -> QAgg be s a
- lag1_ :: (BeamSqlBackend be, BeamSqlT615Backend be) => QExpr be s a -> QAgg be s a
- lead_ :: (BeamSqlBackend be, BeamSqlT615Backend be, Integral n) => QExpr be s a -> QExpr be s n -> QAgg be s a
- lag_ :: (BeamSqlBackend be, BeamSqlT615Backend be, Integral n) => QExpr be s a -> QExpr be s n -> QAgg be s a
- leadWithDefault_ :: (BeamSqlBackend be, BeamSqlT615Backend be, Integral n) => QExpr be s a -> QExpr be s n -> QExpr be s a -> QAgg be s a
- lagWithDefault_ :: (BeamSqlBackend be, BeamSqlT615Backend be, Integral n) => QExpr be s a -> QExpr be s n -> QExpr be s a -> QAgg be s a
- firstValue_ :: (BeamSqlBackend be, BeamSqlT616Backend be) => QExpr be s a -> QAgg be s a
- lastValue_ :: (BeamSqlBackend be, BeamSqlT616Backend be) => QExpr be s a -> QAgg be s a
- nthValue_ :: (BeamSqlBackend be, BeamSqlT618Backend be, Integral n) => QExpr be s a -> QExpr be s n -> QAgg be s a
- (**.) :: (Floating a, BeamSqlBackend be, BeamSqlT621Backend be) => QGenExpr ctxt be s a -> QGenExpr ctxt be s a -> QGenExpr ctxt be s a
- ln_ :: (Floating a, BeamSqlBackend be, BeamSqlT621Backend be) => QGenExpr ctxt be s a -> QGenExpr ctxt be s a
- exp_ :: (Floating a, BeamSqlBackend be, BeamSqlT621Backend be) => QGenExpr ctxt be s a -> QGenExpr ctxt be s a
- sqrt_ :: (Floating a, BeamSqlBackend be, BeamSqlT621Backend be) => QGenExpr ctxt be s a -> QGenExpr ctxt be s a
- ceiling_ :: (RealFrac a, Integral b, BeamSqlBackend be, BeamSqlT621Backend be) => QGenExpr ctxt be s a -> QGenExpr ctxt be s b
- floor_ :: (RealFrac a, Integral b, BeamSqlBackend be, BeamSqlT621Backend be) => QGenExpr ctxt be s a -> QGenExpr ctxt be s b
- stddevPopOver_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QAgg be s b
- stddevSampOver_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QAgg be s b
- varPopOver_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QAgg be s b
- varSampOver_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QAgg be s b
- stddevPop_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => QExpr be s a -> QAgg be s b
- stddevSamp_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => QExpr be s a -> QAgg be s b
- varPop_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => QExpr be s a -> QAgg be s b
- varSamp_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => QExpr be s a -> QAgg be s b
- covarPopOver_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QExpr be s a -> QExpr be s b
- covarSampOver_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QExpr be s a -> QExpr be s b
- corrOver_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QExpr be s a -> QExpr be s b
- regrSlopeOver_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QExpr be s a -> QExpr be s b
- regrInterceptOver_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QExpr be s a -> QExpr be s b
- regrCountOver_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QExpr be s a -> QExpr be s b
- regrRSquaredOver_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QExpr be s a -> QExpr be s b
- regrAvgXOver_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QExpr be s a -> QExpr be s b
- regrAvgYOver_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QExpr be s a -> QExpr be s b
- regrSXXOver_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QExpr be s a -> QExpr be s b
- regrSYYOver_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QExpr be s a -> QExpr be s b
- regrSXYOver_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QExpr be s a -> QExpr be s b
- covarPop_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => QExpr be s a -> QExpr be s a -> QExpr be s b
- covarSamp_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => QExpr be s a -> QExpr be s a -> QExpr be s b
- corr_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => QExpr be s a -> QExpr be s a -> QExpr be s b
- regrSlope_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => QExpr be s a -> QExpr be s a -> QExpr be s b
- regrIntercept_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => QExpr be s a -> QExpr be s a -> QExpr be s b
- regrCount_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => QExpr be s a -> QExpr be s a -> QExpr be s b
- regrRSquared_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => QExpr be s a -> QExpr be s a -> QExpr be s b
- regrAvgX_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => QExpr be s a -> QExpr be s a -> QExpr be s b
- regrAvgY_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => QExpr be s a -> QExpr be s a -> QExpr be s b
- regrSXX_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => QExpr be s a -> QExpr be s a -> QExpr be s b
- regrSYY_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => QExpr be s a -> QExpr be s a -> QExpr be s b
- regrSXY_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => QExpr be s a -> QExpr be s a -> QExpr be s b
- type ManyToMany be db left right = forall s. (BeamSqlBackend be, SqlEq (QExpr be s) (PrimaryKey left (QExpr be s)), SqlEq (QExpr be s) (PrimaryKey right (QExpr be s))) => Q be db s (left (QExpr be s)) -> Q be db s (right (QExpr be s)) -> Q be db s (left (QExpr be s), right (QExpr be s))
- type ManyToManyThrough be db through left right = forall s. (BeamSqlBackend be, SqlEq (QExpr be s) (PrimaryKey left (QExpr be s)), SqlEq (QExpr be s) (PrimaryKey right (QExpr be s))) => Q be db s (left (QExpr be s)) -> Q be db s (right (QExpr be s)) -> Q be db s (through (QExpr be s), left (QExpr be s), right (QExpr be s))
- manyToMany_ :: (Database be db, Table joinThrough, Table left, Table right, BeamSqlBackend be, SqlEq (QExpr be s) (PrimaryKey left (QExpr be s)), SqlEq (QExpr be s) (PrimaryKey right (QExpr be s))) => DatabaseEntity be db (TableEntity joinThrough) -> (joinThrough (QExpr be s) -> PrimaryKey left (QExpr be s)) -> (joinThrough (QExpr be s) -> PrimaryKey right (QExpr be s)) -> Q be db s (left (QExpr be s)) -> Q be db s (right (QExpr be s)) -> Q be db s (left (QExpr be s), right (QExpr be s))
- manyToManyPassthrough_ :: (Database be db, Table joinThrough, Table left, Table right, BeamSqlBackend be, SqlEq (QExpr be s) (PrimaryKey left (QExpr be s)), SqlEq (QExpr be s) (PrimaryKey right (QExpr be s))) => DatabaseEntity be db (TableEntity joinThrough) -> (joinThrough (QExpr be s) -> PrimaryKey left (QExpr be s)) -> (joinThrough (QExpr be s) -> PrimaryKey right (QExpr be s)) -> Q be db s (left (QExpr be s)) -> Q be db s (right (QExpr be s)) -> Q be db s (joinThrough (QExpr be s), left (QExpr be s), right (QExpr be s))
- type OneToMany be db s one many = (BeamSqlBackend be, BeamSqlBackendCanSerialize be Bool) => one (QExpr be s) -> Q be db s (many (QExpr be s))
- type OneToManyOptional be db s tbl rel = (BeamSqlBackend be, BeamSqlBackendCanSerialize be Bool, BeamSqlBackendCanSerialize be SqlNull) => tbl (QExpr be s) -> Q be db s (rel (Nullable (QExpr be s)))
- oneToMany_ :: (Database be db, BeamSqlBackend be, HasTableEquality be (PrimaryKey tbl), Table tbl, Table rel) => DatabaseEntity be db (TableEntity rel) -> (rel (QExpr be s) -> PrimaryKey tbl (QExpr be s)) -> tbl (QExpr be s) -> Q be db s (rel (QExpr be s))
- oneToManyOptional_ :: (BeamSqlBackend be, Database be db, Table tbl, Table rel, HasTableEqualityNullable be (PrimaryKey tbl)) => DatabaseEntity be db (TableEntity rel) -> (rel (QExpr be s) -> PrimaryKey tbl (Nullable (QExpr be s))) -> tbl (QExpr be s) -> Q be db s (rel (Nullable (QExpr be s)))
- type OneToOne be db s one many = OneToMany be db s one many
- type OneToMaybe be db s tbl rel = OneToManyOptional be db s tbl rel
- oneToOne_ :: (Database be db, BeamSqlBackend be, HasTableEquality be (PrimaryKey tbl), Table tbl, Table rel) => DatabaseEntity be db (TableEntity rel) -> (rel (QExpr be s) -> PrimaryKey tbl (QExpr be s)) -> tbl (QExpr be s) -> Q be db s (rel (QExpr be s))
- oneToMaybe_ :: (BeamSqlBackend be, Database be db, Table tbl, Table rel, HasTableEqualityNullable be (PrimaryKey tbl)) => DatabaseEntity be db (TableEntity rel) -> (rel (QExpr be s) -> PrimaryKey tbl (Nullable (QExpr be s))) -> tbl (QExpr be s) -> Q be db s (rel (Nullable (QExpr be s)))
- data ReusableQ be db res
- data With be (db :: (Type -> Type) -> Type) a
- selecting :: forall res be db. (BeamSql99CommonTableExpressionBackend be, HasQBuilder be, Projectible be res, ThreadRewritable QAnyScope res) => Q be db QAnyScope res -> With be db (ReusableQ be db res)
- reuse :: forall s be db res. ReusableQ be db res -> Q be db s (WithRewrittenThread QAnyScope s res)
- newtype ExtractField be tgt a = ExtractField (Sql92ExtractFieldSyntax (BeamSqlBackendSyntax be))
- extract_ :: BeamSqlBackend be => ExtractField be tgt a -> QGenExpr ctxt be s tgt -> QGenExpr cxt be s a
- hour_ :: (BeamSqlBackend be, HasSqlTime tgt) => ExtractField be tgt Double
- minutes_ :: (BeamSqlBackend be, HasSqlTime tgt) => ExtractField be tgt Double
- seconds_ :: (BeamSqlBackend be, HasSqlTime tgt) => ExtractField be tgt Double
- year_ :: (BeamSqlBackend be, HasSqlDate tgt) => ExtractField be tgt Double
- month_ :: (BeamSqlBackend be, HasSqlDate tgt) => ExtractField be tgt Double
- day_ :: (BeamSqlBackend be, HasSqlDate tgt) => ExtractField be tgt Double
- class HasSqlTime tgt
- class HasSqlDate tgt
- data SqlBool
- (&&.) :: BeamSqlBackend be => QGenExpr context be s Bool -> QGenExpr context be s Bool -> QGenExpr context be s Bool
- (||.) :: BeamSqlBackend be => QGenExpr context be s Bool -> QGenExpr context be s Bool -> QGenExpr context be s Bool
- not_ :: forall be context s. BeamSqlBackend be => QGenExpr context be s Bool -> QGenExpr context be s Bool
- div_ :: (Integral a, BeamSqlBackend be) => QGenExpr context be s a -> QGenExpr context be s a -> QGenExpr context be s a
- mod_ :: (Integral a, BeamSqlBackend be) => QGenExpr context be s a -> QGenExpr context be s a -> QGenExpr context be s a
- (&&?.) :: BeamSqlBackend be => QGenExpr context be s SqlBool -> QGenExpr context be s SqlBool -> QGenExpr context be s SqlBool
- (||?.) :: BeamSqlBackend be => QGenExpr context be s SqlBool -> QGenExpr context be s SqlBool -> QGenExpr context be s SqlBool
- sqlNot_ :: forall be context s. BeamSqlBackend be => QGenExpr context be s SqlBool -> QGenExpr context be s SqlBool
- like_ :: (BeamSqlBackendIsString be text, BeamSqlBackend be) => QGenExpr ctxt be s text -> QGenExpr ctxt be s text -> QGenExpr ctxt be s Bool
- similarTo_ :: (BeamSqlBackendIsString be text, BeamSql99ExpressionBackend be) => QGenExpr ctxt be s text -> QGenExpr ctxt be s text -> QGenExpr ctxt be s text
- concat_ :: BeamSql99ConcatExpressionBackend be => [QGenExpr context be s Text] -> QGenExpr context be s Text
- isTrue_ :: BeamSqlBackend be => QGenExpr context be s SqlBool -> QGenExpr context be s Bool
- isNotTrue_ :: BeamSqlBackend be => QGenExpr context be s SqlBool -> QGenExpr context be s Bool
- isFalse_ :: BeamSqlBackend be => QGenExpr context be s SqlBool -> QGenExpr context be s Bool
- isNotFalse_ :: BeamSqlBackend be => QGenExpr context be s SqlBool -> QGenExpr context be s Bool
- isUnknown_ :: BeamSqlBackend be => QGenExpr context be s SqlBool -> QGenExpr context be s Bool
- isNotUnknown_ :: BeamSqlBackend be => QGenExpr context be s SqlBool -> QGenExpr context be s Bool
- unknownAs_ :: BeamSqlBackend be => Bool -> QGenExpr context be s SqlBool -> QGenExpr context be s Bool
- sqlBool_ :: QGenExpr context syntax s Bool -> QGenExpr context syntax s SqlBool
- possiblyNullBool_ :: QGenExpr context be s SqlBool -> QGenExpr context be s (Maybe Bool)
- fromPossiblyNullBool_ :: QGenExpr context be s (Maybe Bool) -> QGenExpr context be s SqlBool
- class BeamSqlBackend be => HasSqlEqualityCheck be a where
- sqlEqE, sqlNeqE :: Proxy a -> Proxy be -> BeamSqlBackendExpressionSyntax be -> BeamSqlBackendExpressionSyntax be -> BeamSqlBackendExpressionSyntax be
- sqlEqTriE, sqlNeqTriE :: Proxy a -> Proxy be -> BeamSqlBackendExpressionSyntax be -> BeamSqlBackendExpressionSyntax be -> BeamSqlBackendExpressionSyntax be
- class HasSqlEqualityCheck be a => HasSqlQuantifiedEqualityCheck be a where
- sqlQEqE, sqlQNeqE :: Proxy a -> Proxy be -> Maybe (BeamSqlBackendExpressionQuantifierSyntax be) -> BeamSqlBackendExpressionSyntax be -> BeamSqlBackendExpressionSyntax be -> BeamSqlBackendExpressionSyntax be
- type HasTableEquality be tbl = (FieldsFulfillConstraint (HasSqlEqualityCheck be) tbl, Beamable tbl)
- class SqlEq expr a | a -> expr where
- class SqlOrd expr e | e -> expr where
- class SqlIn expr a | a -> expr where
- class BeamSqlBackend be => HasSqlInTable be where
- inRowValuesE :: Proxy be -> BeamSqlBackendExpressionSyntax be -> [BeamSqlBackendExpressionSyntax be] -> BeamSqlBackendExpressionSyntax be
- class SqlEq expr a => SqlEqQuantified expr quantified a | a -> expr quantified where
- class SqlOrd expr e => SqlOrdQuantified expr quantified e | e -> expr quantified where
- data QQuantified be s r
- anyOf_ :: forall s a be db. (BeamSqlBackend be, HasQBuilder be) => Q be db (QNested s) (QExpr be (QNested s) a) -> QQuantified be s a
- allOf_ :: forall s a be db. (BeamSqlBackend be, HasQBuilder be) => Q be db (QNested s) (QExpr be (QNested s) a) -> QQuantified be s a
- anyIn_ :: forall s a be. BeamSqlBackend be => [QExpr be s a] -> QQuantified be s a
- allIn_ :: forall s a be. BeamSqlBackend be => [QExpr be s a] -> QQuantified be s a
- between_ :: BeamSqlBackend be => QGenExpr context be s a -> QGenExpr context be s a -> QGenExpr context be s a -> QGenExpr context be s Bool
- aggregate_ :: forall be a r db s. (BeamSqlBackend be, Aggregable be a, Projectible be r, Projectible be a, ContextRewritable a, ThreadRewritable (QNested s) (WithRewrittenContext a QValueContext)) => (r -> a) -> Q be db (QNested s) r -> Q be db s (WithRewrittenThread (QNested s) s (WithRewrittenContext a QValueContext))
- filterWhere_ :: BeamSqlT611Backend be => QAgg be s a -> QExpr be s Bool -> QAgg be s a
- filterWhere_' :: BeamSqlT611Backend be => QAgg be s a -> QExpr be s SqlBool -> QAgg be s a
- class QGroupable expr grouped | expr -> grouped, grouped -> expr where
- group_ :: expr -> grouped
- sum_ :: (BeamSqlBackend be, Num a) => QExpr be s a -> QAgg be s (Maybe a)
- avg_ :: (BeamSqlBackend be, Num a) => QExpr be s a -> QAgg be s (Maybe a)
- min_ :: BeamSqlBackend be => QExpr be s a -> QAgg be s (Maybe a)
- max_ :: BeamSqlBackend be => QExpr be s a -> QAgg be s (Maybe a)
- count_ :: (BeamSqlBackend be, Integral b) => QExpr be s a -> QAgg be s b
- countAll_ :: (BeamSqlBackend be, Integral a) => QAgg be s a
- rank_ :: (BeamSqlT611Backend be, Integral a) => QAgg be s a
- cumeDist_ :: BeamSqlT612Backend be => QAgg be s Double
- percentRank_ :: BeamSqlT612Backend be => QAgg be s Double
- denseRank_ :: (BeamSqlT612Backend be, Integral a) => QAgg be s a
- rowNumber_ :: (BeamSql2003ExpressionBackend be, Integral a) => QAgg be s a
- every_ :: BeamSql99AggregationBackend be => QExpr be s SqlBool -> QAgg be s SqlBool
- any_ :: BeamSql99AggregationBackend be => QExpr be s SqlBool -> QAgg be s SqlBool
- some_ :: BeamSql99AggregationBackend be => QExpr be s SqlBool -> QAgg be s SqlBool
- sumOver_ :: (BeamSqlBackend be, Num a) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QAgg be s (Maybe a)
- avgOver_ :: (BeamSqlBackend be, Num a) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QAgg be s (Maybe a)
- minOver_ :: BeamSqlBackend be => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QAgg be s (Maybe a)
- maxOver_ :: BeamSqlBackend be => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QAgg be s (Maybe a)
- countOver_ :: (BeamSqlBackend be, Integral b) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QAgg be s b
- everyOver_ :: BeamSql99AggregationBackend be => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s SqlBool -> QAgg be s SqlBool
- anyOver_ :: BeamSql99AggregationBackend be => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s SqlBool -> QAgg be s SqlBool
- someOver_ :: BeamSql99AggregationBackend be => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s SqlBool -> QAgg be s SqlBool
- distinctInGroup_ :: IsSql92AggregationSetQuantifierSyntax s => Maybe s
- allInGroup_ :: IsSql92AggregationSetQuantifierSyntax s => Maybe s
- allInGroupExplicitly_ :: IsSql92AggregationSetQuantifierSyntax s => Maybe s
- module Database.Beam.Query.CustomSQL
- module Database.Beam.Query.DataTypes
- newtype SqlSelect be a = SqlSelect (BeamSqlBackendSelectSyntax be)
- select :: forall be db res. (BeamSqlBackend be, HasQBuilder be, Projectible be res) => Q be db QBaseScope res -> SqlSelect be (QExprToIdentity res)
- selectWith :: forall be db res. (BeamSqlBackend be, BeamSql99CommonTableExpressionBackend be, HasQBuilder be, Projectible be res) => With be db (Q be db QBaseScope res) -> SqlSelect be (QExprToIdentity res)
- lookup_ :: (Database be db, Table table, BeamSqlBackend be, HasQBuilder be, SqlValableTable be (PrimaryKey table), HasTableEquality be (PrimaryKey table)) => DatabaseEntity be db (TableEntity table) -> PrimaryKey table Identity -> SqlSelect be (table Identity)
- runSelectReturningList :: (MonadBeam be m, BeamSqlBackend be, FromBackendRow be a) => SqlSelect be a -> m [a]
- runSelectReturningOne :: (MonadBeam be m, BeamSqlBackend be, FromBackendRow be a) => SqlSelect be a -> m (Maybe a)
- dumpSqlSelect :: Projectible (MockSqlBackend SqlSyntaxBuilder) res => Q (MockSqlBackend SqlSyntaxBuilder) db QBaseScope res -> IO ()
- data SqlInsert be (table :: (Type -> Type) -> Type)
- = SqlInsert !(TableSettings table) !(BeamSqlBackendInsertSyntax be)
- | SqlInsertNoRows
- insert :: (BeamSqlBackend be, ProjectibleWithPredicate AnyType () Text (table (QField s))) => DatabaseEntity be db (TableEntity table) -> SqlInsertValues be (table (QExpr be s)) -> SqlInsert be table
- insertOnly :: (BeamSqlBackend be, ProjectibleWithPredicate AnyType () Text (QExprToField r)) => DatabaseEntity be db (TableEntity table) -> (table (QField s) -> QExprToField r) -> SqlInsertValues be r -> SqlInsert be table
- runInsert :: (BeamSqlBackend be, MonadBeam be m) => SqlInsert be table -> m ()
- data SqlInsertValues be proj
- insertExpressions :: forall be table s. (BeamSqlBackend be, Beamable table) => (forall s'. [table (QExpr be s')]) -> SqlInsertValues be (table (QExpr be s))
- insertValues :: forall be table s. (BeamSqlBackend be, Beamable table, FieldsFulfillConstraint (BeamSqlBackendCanSerialize be) table) => [table Identity] -> SqlInsertValues be (table (QExpr be s))
- insertFrom :: (BeamSqlBackend be, HasQBuilder be, Projectible be r) => Q be db QBaseScope r -> SqlInsertValues be r
- insertData :: forall be r. (Projectible be r, BeamSqlBackend be) => [r] -> SqlInsertValues be r
- data SqlUpdate be (table :: (Type -> Type) -> Type)
- = SqlUpdate !(TableSettings table) !(BeamSqlBackendUpdateSyntax be)
- | SqlIdentityUpdate
- update :: (BeamSqlBackend be, Beamable table) => DatabaseEntity be db (TableEntity table) -> (forall s. table (QField s) -> QAssignment be s) -> (forall s. table (QExpr be s) -> QExpr be s Bool) -> SqlUpdate be table
- save :: forall table be db. (Table table, BeamSqlBackend be, SqlValableTable be (PrimaryKey table), SqlValableTable be table, HasTableEquality be (PrimaryKey table)) => DatabaseEntity be db (TableEntity table) -> table Identity -> SqlUpdate be table
- update' :: (BeamSqlBackend be, Beamable table) => DatabaseEntity be db (TableEntity table) -> (forall s. table (QField s) -> QAssignment be s) -> (forall s. table (QExpr be s) -> QExpr be s SqlBool) -> SqlUpdate be table
- save' :: forall table be db. (Table table, BeamSqlBackend be, SqlValableTable be (PrimaryKey table), SqlValableTable be table, HasTableEquality be (PrimaryKey table)) => DatabaseEntity be db (TableEntity table) -> table Identity -> SqlUpdate be table
- updateTable :: forall table db be. (BeamSqlBackend be, Beamable table) => DatabaseEntity be db (TableEntity table) -> table (QFieldAssignment be table) -> (forall s. table (QExpr be s) -> QExpr be s Bool) -> SqlUpdate be table
- updateTable' :: forall table db be. (BeamSqlBackend be, Beamable table) => DatabaseEntity be db (TableEntity table) -> table (QFieldAssignment be table) -> (forall s. table (QExpr be s) -> QExpr be s SqlBool) -> SqlUpdate be table
- set :: forall table be table'. Beamable table => table (QFieldAssignment be table')
- setFieldsTo :: forall table be table'. Table table => (forall s. table (QExpr be s)) -> table (QFieldAssignment be table')
- toNewValue :: (forall s. QExpr be s a) -> QFieldAssignment be table a
- toOldValue :: QFieldAssignment be table a
- toUpdatedValue :: (forall s. table (QExpr be s) -> QExpr be s a) -> QFieldAssignment be table a
- toUpdatedValueMaybe :: (forall s. table (QExpr be s) -> Maybe (QExpr be s a)) -> QFieldAssignment be table a
- updateRow :: (BeamSqlBackend be, Table table, HasTableEquality be (PrimaryKey table), SqlValableTable be (PrimaryKey table)) => DatabaseEntity be db (TableEntity table) -> table Identity -> (forall s. table (QField s) -> QAssignment be s) -> SqlUpdate be table
- updateTableRow :: (BeamSqlBackend be, Table table, HasTableEquality be (PrimaryKey table), SqlValableTable be (PrimaryKey table)) => DatabaseEntity be db (TableEntity table) -> table Identity -> table (QFieldAssignment be table) -> SqlUpdate be table
- updateRow' :: (BeamSqlBackend be, Table table, HasTableEquality be (PrimaryKey table), SqlValableTable be (PrimaryKey table)) => DatabaseEntity be db (TableEntity table) -> table Identity -> (forall s. table (QField s) -> QAssignment be s) -> SqlUpdate be table
- updateTableRow' :: (BeamSqlBackend be, Table table, HasTableEquality be (PrimaryKey table), SqlValableTable be (PrimaryKey table)) => DatabaseEntity be db (TableEntity table) -> table Identity -> table (QFieldAssignment be table) -> SqlUpdate be table
- runUpdate :: (BeamSqlBackend be, MonadBeam be m) => SqlUpdate be tbl -> m ()
- data SqlDelete be (table :: (Type -> Type) -> Type) = SqlDelete !(TableSettings table) !(BeamSqlBackendDeleteSyntax be)
- delete :: forall be db table. BeamSqlBackend be => DatabaseEntity be db (TableEntity table) -> (forall s. (forall s'. table (QExpr be s')) -> QExpr be s Bool) -> SqlDelete be table
- runDelete :: (BeamSqlBackend be, MonadBeam be m) => SqlDelete be table -> m ()
Query type
type Projectible be = ProjectibleWithPredicate AnyType be (WithExprContext (BeamSqlBackendExpressionSyntax' be)) Source #
Instances
contextPredicate QWindowFrameContext => ProjectibleWithPredicate contextPredicate be (WithExprContext (BeamSqlBackendWindowFrameSyntax' be)) (QWindow be s) Source # | |
Defined in Database.Beam.Query.Internal project' :: Monad m => Proxy contextPredicate -> Proxy (be, WithExprContext (BeamSqlBackendWindowFrameSyntax' be)) -> (forall context. contextPredicate context => Proxy context -> Proxy be -> WithExprContext (BeamSqlBackendWindowFrameSyntax' be) -> m (WithExprContext (BeamSqlBackendWindowFrameSyntax' be))) -> QWindow be s -> m (QWindow be s) Source # projectSkeleton' :: Monad m => Proxy contextPredicate -> Proxy (be, WithExprContext (BeamSqlBackendWindowFrameSyntax' be)) -> (forall context. contextPredicate context => Proxy context -> Proxy be -> m (WithExprContext (BeamSqlBackendWindowFrameSyntax' be))) -> m (QWindow be s) Source # |
type QExpr = QGenExpr QValueContext Source #
QGenExpr
s represent expressions not containing aggregates.
newtype QGenExpr context be s t Source #
The type of lifted beam expressions that will yield the haskell type t
.
context
is a type-level representation of the types of expressions this
can contain. For example, QAggregateContext
represents expressions that
may contain aggregates, and QWindowingContext
represents expressions that
may contain OVER
.
syntax
is the expression syntax being built (usually a type that
implements IsSql92ExpressionSyntax
at least, but not always).
s
is a state threading parameter that prevents QGenExpr
s from incompatible
sources to be combined. For example, this is used to prevent monadic joins
from depending on the result of previous joins (so-called LATERAL
joins).
Instances
data Q be (db :: (Type -> Type) -> Type) s a Source #
The type of queries over the database db
returning results of type a
.
The s
argument is a threading argument meant to restrict cross-usage of
QGenExpr
s. syntax
represents the SQL syntax that this query is building.
class BeamSqlBackend be => HasQBuilder be where Source #
buildSqlQuery :: Projectible be a => TablePrefix -> Q be db s a -> BeamSqlBackendSelectSyntax be Source #
Instances
BeamSqlBackend (MockSqlBackend cmd) => HasQBuilder (MockSqlBackend cmd) Source # | |
Defined in Database.Beam.Query.Types buildSqlQuery :: Projectible (MockSqlBackend cmd) a => TablePrefix -> Q (MockSqlBackend cmd) db s a -> BeamSqlBackendSelectSyntax (MockSqlBackend cmd) Source # |
type family QExprToField x Source #
Instances
type family QExprToIdentity x Source #
Instances
Query expression contexts
A context is a type-level value that signifies where an expression can
be used. For example, QGenExpr
corresponds to QGenExpr
s that result in
values. In reality, QGenExpr
is really QGenExpr
parameterized over the
QValueContext
. Similarly, QAgg
represents expressions that contain
aggregates, but it is just QGenExpr
parameterized over
QAggregateContext
data QAggregateContext Source #
Instances
type ContextName QAggregateContext Source # | |
Defined in Database.Beam.Query.Internal |
data QGroupingContext Source #
Instances
Beamable tbl => QGroupable (tbl (Nullable (QExpr be s))) (tbl (Nullable (QGroupExpr be s))) Source # |
|
Defined in Database.Beam.Query.Aggregate | |
Beamable tbl => QGroupable (tbl (QExpr be s)) (tbl (QGroupExpr be s)) Source # |
|
Defined in Database.Beam.Query.Aggregate group_ :: tbl (QExpr be s) -> tbl (QGroupExpr be s) Source # | |
QGroupable (QExpr be s a) (QGroupExpr be s a) Source # |
|
Defined in Database.Beam.Query.Aggregate group_ :: QExpr be s a -> QGroupExpr be s a Source # | |
type ContextName QGroupingContext Source # | |
Defined in Database.Beam.Query.Internal |
data QValueContext Source #
Instances
(Table t, BeamSqlBackend be) => SqlJustable (t (QExpr be s)) (t (Nullable (QExpr be s))) Source # | |
Beamable tbl => QGroupable (tbl (Nullable (QExpr be s))) (tbl (Nullable (QGroupExpr be s))) Source # |
|
Defined in Database.Beam.Query.Aggregate | |
Beamable tbl => QGroupable (tbl (QExpr be s)) (tbl (QGroupExpr be s)) Source # |
|
Defined in Database.Beam.Query.Aggregate group_ :: tbl (QExpr be s) -> tbl (QGroupExpr be s) Source # | |
(Table t, BeamSqlBackend be) => SqlJustable (PrimaryKey t (QExpr be s)) (PrimaryKey t (Nullable (QExpr be s))) Source # | |
Defined in Database.Beam.Query.Combinators just_ :: PrimaryKey t (QExpr be s) -> PrimaryKey t (Nullable (QExpr be s)) Source # | |
BeamSqlBackend be => SqlJustable (QExpr be s a) (QExpr be s (Maybe a)) Source # | |
QGroupable (QExpr be s a) (QGroupExpr be s a) Source # |
|
Defined in Database.Beam.Query.Aggregate group_ :: QExpr be s a -> QGroupExpr be s a Source # | |
type ContextName QValueContext Source # | |
Defined in Database.Beam.Query.Internal |
data QWindowingContext Source #
Instances
type ContextName QWindowingContext Source # | |
Defined in Database.Beam.Query.Internal |
data QWindowFrameContext Source #
Instances
type ContextName QWindowFrameContext Source # | |
Defined in Database.Beam.Query.Internal |
type QGenExprTable ctxt be s tbl = tbl (QGenExpr ctxt be s) Source #
A version of the table where each field is a QGenExpr
type QExprTable be s tbl = QGenExprTable QValueContext be s tbl Source #
data QAssignment be s Source #
Instances
Semigroup (QAssignment be s) Source # | |
Defined in Database.Beam.Query.Internal (<>) :: QAssignment be s -> QAssignment be s -> QAssignment be s # sconcat :: NonEmpty (QAssignment be s) -> QAssignment be s # stimes :: Integral b => b -> QAssignment be s -> QAssignment be s # | |
Monoid (QAssignment be s) Source # | |
Defined in Database.Beam.Query.Internal mempty :: QAssignment be s # mappend :: QAssignment be s -> QAssignment be s -> QAssignment be s # mconcat :: [QAssignment be s] -> QAssignment be s # |
Instances
data QFieldAssignment be tbl a Source #
data QBaseScope Source #
Various SQL functions and constructs
coalesce_ :: BeamSqlBackend be => [QGenExpr ctxt be s (Maybe a)] -> QGenExpr ctxt be s a -> QGenExpr ctxt be s a Source #
SQL COALESCE
support
fromMaybe_ :: BeamSqlBackend be => QGenExpr ctxt be s a -> QGenExpr ctxt be s (Maybe a) -> QGenExpr ctxt be s a Source #
Converta a Maybe
value to a concrete value, by suppling a default
position_ :: (BeamSqlBackendIsString be text, BeamSqlBackend be, Integral b) => QExpr be s text -> QExpr be s text -> QExpr be s b Source #
SQL POSITION(.. IN ..)
function
charLength_ :: (BeamSqlBackend be, BeamSqlBackendIsString be text, Integral a) => QGenExpr context be s text -> QGenExpr context be s a Source #
SQL CHAR_LENGTH
function
octetLength_ :: (BeamSqlBackend be, BeamSqlBackendIsString be text, Integral a) => QGenExpr context be s text -> QGenExpr context be s a Source #
SQL OCTET_LENGTH
function
bitLength_ :: (BeamSqlBackend be, Integral a) => QGenExpr context be s SqlBitString -> QGenExpr context be s a Source #
SQL BIT_LENGTH
function
currentTimestamp_ :: BeamSqlBackend be => QGenExpr ctxt be s LocalTime Source #
SQL CURRENT_TIMESTAMP
function
lower_ :: (BeamSqlBackendIsString be text, BeamSqlBackend be) => QGenExpr context be s text -> QGenExpr context be s text Source #
SQL LOWER
function
upper_ :: (BeamSqlBackendIsString be text, BeamSqlBackend be) => QGenExpr context be s text -> QGenExpr context be s text Source #
SQL UPPER
function
trim_ :: (BeamSqlBackendIsString be text, BeamSqlBackend be) => QGenExpr context be s text -> QGenExpr context be s text Source #
SQL TRIM
function
IF-THEN-ELSE
support
if_ :: BeamSqlBackend be => [QIfCond context be s a] -> QIfElse context be s a -> QGenExpr context be s a Source #
then_' :: QGenExpr context be s SqlBool -> QGenExpr context be s a -> QIfCond context be s a Source #
ifThenElse_ :: BeamSqlBackend be => QGenExpr context be s Bool -> QGenExpr context be s a -> QGenExpr context be s a -> QGenExpr context be s a Source #
bool_ :: BeamSqlBackend be => QGenExpr context be s a -> QGenExpr context be s a -> QGenExpr context be s Bool -> QGenExpr context be s a Source #
SQL UPDATE
assignments
(<-.) :: SqlUpdatable be s lhs rhs => lhs -> rhs -> QAssignment be s infix 4 Source #
current_ :: BeamSqlBackend be => QField s ty -> QExpr be s ty Source #
Extract an expression representing the current (non-UPDATEd) value of a QField
Project Haskell values to QGenExpr
s
type family HaskellLiteralForQExpr x = a Source #
Instances
type HaskellLiteralForQExpr (table (QGenExpr context be s)) Source # | |
Defined in Database.Beam.Query.Combinators | |
type HaskellLiteralForQExpr (table (Nullable f)) Source # | |
Defined in Database.Beam.Query.Combinators | |
type HaskellLiteralForQExpr (QGenExpr context be s a) Source # | |
Defined in Database.Beam.Query.Combinators |
class SqlValable a where Source #
val_ :: HaskellLiteralForQExpr a -> a Source #
Instances
(Beamable table, BeamSqlBackend be, FieldsFulfillConstraintNullable (BeamSqlBackendCanSerialize be) table) => SqlValable (table (Nullable (QGenExpr ctxt be s))) Source # | |
Defined in Database.Beam.Query.Combinators | |
(Beamable table, BeamSqlBackend be, FieldsFulfillConstraint (BeamSqlBackendCanSerialize be) table) => SqlValable (table (QGenExpr ctxt be s)) Source # | |
Defined in Database.Beam.Query.Combinators | |
(BeamSqlBackendCanSerialize be a, BeamSqlBackend be) => SqlValable (QGenExpr ctxt be s a) Source # | |
Defined in Database.Beam.Query.Combinators |
type SqlValableTable be table = (Beamable table, FieldsFulfillConstraint (HasSqlValueSyntax (BeamSqlBackendValueSyntax be)) table) Source #
default_ :: BeamSqlBackend be => QGenExpr ctxt be s a Source #
General query combinators
all_ :: (Database be db, BeamSqlBackend be) => DatabaseEntity be db (TableEntity table) -> Q be db s (table (QExpr be s)) Source #
Introduce all entries of a table into the Q
monad
values_ :: forall be db s a. (Projectible be a, BeamSqlBackend be) => [a] -> Q be db s a Source #
SQL VALUES
clause. Introduce the elements of the given list as
rows in a joined table.
allFromView_ :: (Database be db, Beamable table, BeamSqlBackend be) => DatabaseEntity be db (ViewEntity table) -> Q be db s (table (QExpr be s)) Source #
Introduce all entries of a view into the Q
monad
join_ :: (Database be db, Table table, BeamSqlBackend be) => DatabaseEntity be db (TableEntity table) -> (table (QExpr be s) -> QExpr be s Bool) -> Q be db s (table (QExpr be s)) Source #
join_' :: (Database be db, Table table, BeamSqlBackend be) => DatabaseEntity be db (TableEntity table) -> (table (QExpr be s) -> QExpr be s SqlBool) -> Q be db s (table (QExpr be s)) Source #
filter_ :: forall r be db s. BeamSqlBackend be => (r -> QExpr be s Bool) -> Q be db s r -> Q be db s r Source #
filter_' :: forall r be db s. BeamSqlBackend be => (r -> QExpr be s SqlBool) -> Q be db s r -> Q be db s r Source #
related_ :: forall be db rel s. (Database be db, Table rel, BeamSqlBackend be, HasTableEquality be (PrimaryKey rel)) => DatabaseEntity be db (TableEntity rel) -> PrimaryKey rel (QExpr be s) -> Q be db s (rel (QExpr be s)) Source #
Introduce all entries of the given table which are referenced by the given PrimaryKey
relatedBy_ :: forall be db rel s. (Database be db, Table rel, BeamSqlBackend be) => DatabaseEntity be db (TableEntity rel) -> (rel (QExpr be s) -> QExpr be s Bool) -> Q be db s (rel (QExpr be s)) Source #
Introduce all entries of the given table which for which the expression (which can depend on the queried table returns true)
relatedBy_' :: forall be db rel s. (Database be db, Table rel, BeamSqlBackend be) => DatabaseEntity be db (TableEntity rel) -> (rel (QExpr be s) -> QExpr be s SqlBool) -> Q be db s (rel (QExpr be s)) Source #
Introduce all entries of the given table which for which the expression (which can depend on the queried table returns true)
leftJoin_ :: forall s r be db. (BeamSqlBackend be, Projectible be r, ThreadRewritable (QNested s) r, Retaggable (QExpr be s) (WithRewrittenThread (QNested s) s r)) => Q be db (QNested s) r -> (WithRewrittenThread (QNested s) s r -> QExpr be s Bool) -> Q be db s (Retag Nullable (WithRewrittenThread (QNested s) s r)) Source #
Introduce a table using a left join. The ON clause is required here.Because this is not an inner join, the resulting table is made nullable. This means that each field that would normally have type 'QExpr x' will now have type 'QExpr (Maybe x)'.
The ON
condition given must return Bool
. For a version that
accepts an ON
condition returning SqlBool
, see leftJoin_'
.
leftJoin_' :: forall s r be db. (BeamSqlBackend be, Projectible be r, ThreadRewritable (QNested s) r, Retaggable (QExpr be s) (WithRewrittenThread (QNested s) s r)) => Q be db (QNested s) r -> (WithRewrittenThread (QNested s) s r -> QExpr be s SqlBool) -> Q be db s (Retag Nullable (WithRewrittenThread (QNested s) s r)) Source #
perhaps_ :: forall s r be db. (Projectible be r, BeamSqlBackend be, ThreadRewritable (QNested s) r, Retaggable (QExpr be s) (WithRewrittenThread (QNested s) s r)) => Q be db (QNested s) r -> Q be db s (Retag Nullable (WithRewrittenThread (QNested s) s r)) Source #
Introduce a table using a left join with no ON clause. Because this is not an inner join, the resulting table is made nullable. This means that each field that would normally have type 'QExpr x' will now have type 'QExpr (Maybe x)'.
outerJoin_ :: forall s a b be db. (BeamSqlBackend be, BeamSqlBackendSupportsOuterJoin be, Projectible be a, Projectible be b, ThreadRewritable (QNested s) a, ThreadRewritable (QNested s) b, Retaggable (QExpr be s) (WithRewrittenThread (QNested s) s a), Retaggable (QExpr be s) (WithRewrittenThread (QNested s) s b)) => Q be db (QNested s) a -> Q be db (QNested s) b -> ((WithRewrittenThread (QNested s) s a, WithRewrittenThread (QNested s) s b) -> QExpr be s Bool) -> Q be db s (Retag Nullable (WithRewrittenThread (QNested s) s a), Retag Nullable (WithRewrittenThread (QNested s) s b)) Source #
Outer join. every row of each table, returning NULL
for any row
of either table for which the join condition finds no related rows.
This expects a join expression returning Bool
, for a version that
accepts a SqlBool
(a possibly UNKNOWN
boolean, that maps more
closely to the SQL standard), see outerJoin_'
outerJoin_' :: forall s a b be db. (BeamSqlBackend be, BeamSqlBackendSupportsOuterJoin be, Projectible be a, Projectible be b, ThreadRewritable (QNested s) a, ThreadRewritable (QNested s) b, Retaggable (QExpr be s) (WithRewrittenThread (QNested s) s a), Retaggable (QExpr be s) (WithRewrittenThread (QNested s) s b)) => Q be db (QNested s) a -> Q be db (QNested s) b -> ((WithRewrittenThread (QNested s) s a, WithRewrittenThread (QNested s) s b) -> QExpr be s SqlBool) -> Q be db s (Retag Nullable (WithRewrittenThread (QNested s) s a), Retag Nullable (WithRewrittenThread (QNested s) s b)) Source #
Like outerJoin_
, but accepting SqlBool
. Pairs of rows for
which the join condition is unknown are considered to be unrelated,
by SQL compliant databases at least.
subselect_ :: forall s r be db. (ThreadRewritable (QNested s) r, Projectible be r) => Q be db (QNested s) r -> Q be db s (WithRewrittenThread (QNested s) s r) Source #
references_ :: (Table t, BeamSqlBackend be, HasTableEquality be (PrimaryKey t)) => PrimaryKey t (QGenExpr ctxt be s) -> t (QGenExpr ctxt be s) -> QGenExpr ctxt be s Bool Source #
Generate an appropriate boolean QGenExpr
comparing the given foreign key
to the given table. Useful for creating join conditions.
Use references_'
for a SqlBool
comparison.
references_' :: (Table t, BeamSqlBackend be, HasTableEquality be (PrimaryKey t)) => PrimaryKey t (QGenExpr ctxt be s) -> t (QGenExpr ctxt be s) -> QGenExpr ctxt be s SqlBool Source #
Generate an appropriate boolean QGenExpr
comparing the given foreign key
to the given table. Useful for creating join conditions.
Use references_
for a Bool
comparison.
nub_ :: (BeamSqlBackend be, Projectible be r) => Q be db s r -> Q be db s r Source #
Only return distinct values from a query
class SqlJustable a b | b -> a where Source #
Type class for things that can be nullable. This includes 'QExpr (Maybe a)', 'tbl (Nullable QExpr)', and 'PrimaryKey tbl (Nullable QExpr)'
Given something of type 'QExpr a', 'tbl QExpr', or 'PrimaryKey tbl QExpr', turn it into a 'QExpr (Maybe a)', 'tbl (Nullable QExpr)', or 'PrimaryKey t (Nullable QExpr)' respectively that contains the same values.
Return either a 'QExpr (Maybe x)' representing Nothing
or a nullable Table
or
PrimaryKey
filled with Nothing
.
Instances
Table t => SqlJustable (t Identity) (t (Nullable Identity)) Source # | |
(Table t, BeamSqlBackend be) => SqlJustable (t (QExpr be s)) (t (Nullable (QExpr be s))) Source # | |
Table t => SqlJustable (PrimaryKey t Identity) (PrimaryKey t (Nullable Identity)) Source # | |
Defined in Database.Beam.Query.Combinators just_ :: PrimaryKey t Identity -> PrimaryKey t (Nullable Identity) Source # | |
(Table t, BeamSqlBackend be) => SqlJustable (PrimaryKey t (QExpr be s)) (PrimaryKey t (Nullable (QExpr be s))) Source # | |
Defined in Database.Beam.Query.Combinators just_ :: PrimaryKey t (QExpr be s) -> PrimaryKey t (Nullable (QExpr be s)) Source # | |
BeamSqlBackend be => SqlJustable (QExpr be s a) (QExpr be s (Maybe a)) Source # | |
class BeamSqlBackend be => SqlDeconstructMaybe be a nonNullA s | a s -> be, a -> nonNullA, a -> s, nonNullA -> s where Source #
Type class for anything which can be checked for null-ness. This includes 'QExpr (Maybe a)' as
well as Table
s or PrimaryKey
s over 'Nullable QExpr'.
isJust_ :: a -> QGenExpr ctxt be s Bool Source #
Returns a QGenExpr
that evaluates to true when the first argument is not null
isNothing_ :: a -> QGenExpr ctxt be s Bool Source #
Returns a QGenExpr
that evaluates to true when the first argument is null
maybe_ :: QGenExpr ctxt be s y -> (nonNullA -> QGenExpr ctxt be s y) -> a -> QGenExpr ctxt be s y Source #
Given an object (third argument) which may or may not be null, return the default value if null (first argument), or transform the value that could be null to yield the result of the expression (second argument)
Instances
(BeamSqlBackend be, Beamable t) => SqlDeconstructMaybe be (t (Nullable (QGenExpr ctxt be s))) (t (QGenExpr ctxt be s)) s Source # | |
Defined in Database.Beam.Query.Combinators isJust_ :: t (Nullable (QGenExpr ctxt be s)) -> QGenExpr ctxt0 be s Bool Source # isNothing_ :: t (Nullable (QGenExpr ctxt be s)) -> QGenExpr ctxt0 be s Bool Source # maybe_ :: QGenExpr ctxt0 be s y -> (t (QGenExpr ctxt be s) -> QGenExpr ctxt0 be s y) -> t (Nullable (QGenExpr ctxt be s)) -> QGenExpr ctxt0 be s y Source # | |
BeamSqlBackend be => SqlDeconstructMaybe be (QGenExpr ctxt be s (Maybe x)) (QGenExpr ctxt be s x) s Source # | |
Defined in Database.Beam.Query.Combinators isJust_ :: QGenExpr ctxt be s (Maybe x) -> QGenExpr ctxt0 be s Bool Source # isNothing_ :: QGenExpr ctxt be s (Maybe x) -> QGenExpr ctxt0 be s Bool Source # maybe_ :: QGenExpr ctxt0 be s y -> (QGenExpr ctxt be s x -> QGenExpr ctxt0 be s y) -> QGenExpr ctxt be s (Maybe x) -> QGenExpr ctxt0 be s y Source # |
class SqlOrderable be a | a -> be Source #
makeSQLOrdering
Instances
(<|>.) :: (SqlJustable a (QGenExpr ctxt syntax s y), SqlDeconstructMaybe syntax (QGenExpr ctxt syntax s y) a s) => QGenExpr ctxt syntax s y -> QGenExpr ctxt syntax s y -> QGenExpr ctxt syntax s y infixl 3 Source #
limit_ :: forall s a be db. (Projectible be a, ThreadRewritable (QNested s) a) => Integer -> Q be db (QNested s) a -> Q be db s (WithRewrittenThread (QNested s) s a) Source #
Limit the number of results returned by a query.
offset_ :: forall s a be db. (Projectible be a, ThreadRewritable (QNested s) a) => Integer -> Q be db (QNested s) a -> Q be db s (WithRewrittenThread (QNested s) s a) Source #
Drop the first offset'
results.
as_ :: forall a ctxt be s. QGenExpr ctxt be s a -> QGenExpr ctxt be s a Source #
Convenience function that allows you to use type applications to specify
the result of a QGenExpr
.
Useful to disambiguate the types of QGenExpr
s without having to provide a
complete type signature. As an example, the countAll_
aggregate can
return a result of any Integral
type. Without further constraints, the
type is ambiguous. You can use as_
to disambiguate the return type.
For example, this is ambiguous
aggregate_ (\_ -> countAll_) ..
But this is not
aggregate_ (\_ -> as_ @Int32 countAll_) ..
Subqueries
exists_ :: (BeamSqlBackend be, HasQBuilder be, Projectible be a) => Q be db s a -> QExpr be s Bool Source #
Use the SQL EXISTS
operator to determine if the given query returns any results
unique_ :: (BeamSqlBackend be, HasQBuilder be, Projectible be a) => Q be db s a -> QExpr be s Bool Source #
Use the SQL UNIQUE
operator to determine if the given query produces a unique result
distinct_ :: (BeamSqlBackend be, BeamSql99ExpressionBackend be, HasQBuilder be, Projectible be a) => Q be db s a -> QExpr be s Bool Source #
Use the SQL99 DISTINCT
operator to determine if the given query produces a distinct result
subquery_ :: (BeamSqlBackend be, HasQBuilder be, Projectible be (QExpr be s a)) => Q be db s (QExpr be s a) -> QGenExpr ctxt be s a Source #
Project the (presumably) singular result of the given query as an expression
Set operations
Q
values can be combined using a variety of set operations. See the
manual section.
union_ :: forall be db s a. (BeamSqlBackend be, Projectible be a, ThreadRewritable (QNested s) a) => Q be db (QNested s) a -> Q be db (QNested s) a -> Q be db s (WithRewrittenThread (QNested s) s a) Source #
SQL UNION
operator
unionAll_ :: forall be db s a. (BeamSqlBackend be, Projectible be a, ThreadRewritable (QNested s) a) => Q be db (QNested s) a -> Q be db (QNested s) a -> Q be db s (WithRewrittenThread (QNested s) s a) Source #
SQL UNION ALL
operator
intersect_ :: forall be db s a. (BeamSqlBackend be, Projectible be a, ThreadRewritable (QNested s) a) => Q be db (QNested s) a -> Q be db (QNested s) a -> Q be db s (WithRewrittenThread (QNested s) s a) Source #
SQL INTERSECT
operator
intersectAll_ :: forall be db s a. (BeamSqlBackend be, Projectible be a, ThreadRewritable (QNested s) a) => Q be db (QNested s) a -> Q be db (QNested s) a -> Q be db s (WithRewrittenThread (QNested s) s a) Source #
SQL INTERSECT ALL
operator
except_ :: forall be db s a. (BeamSqlBackend be, Projectible be a, ThreadRewritable (QNested s) a) => Q be db (QNested s) a -> Q be db (QNested s) a -> Q be db s (WithRewrittenThread (QNested s) s a) Source #
SQL EXCEPT
operator
exceptAll_ :: forall be db s a. (BeamSqlBackend be, Projectible be a, ThreadRewritable (QNested s) a) => Q be db (QNested s) a -> Q be db (QNested s) a -> Q be db s (WithRewrittenThread (QNested s) s a) Source #
SQL EXCEPT ALL
operator
Window functions
See the corresponding manual section for more.
over_ :: BeamSql2003ExpressionBackend be => QAgg be s a -> QWindow be s -> QWindowExpr be s a Source #
Produce a window expression given an aggregate function and a window.
:: (BeamSql2003ExpressionBackend be, SqlOrderable be ordering, Projectible be partition) | |
=> Maybe partition | PARTITION BY |
-> Maybe ordering | ORDER BY |
-> QFrameBounds be | RANGE / ROWS |
-> QWindow be s |
Specify a window frame with all the options
bounds_ :: BeamSql2003ExpressionBackend be => QFrameBound be -> Maybe (QFrameBound be) -> QFrameBounds be Source #
unbounded_ :: BeamSql2003ExpressionBackend be => QFrameBound be Source #
nrows_ :: BeamSql2003ExpressionBackend be => Int -> QFrameBound be Source #
fromBound_ :: BeamSql2003ExpressionBackend be => QFrameBound be -> QFrameBounds be Source #
noBounds_ :: QFrameBounds be Source #
partitionBy_ :: partition -> Maybe partition Source #
orderPartitionBy_ :: partition -> Maybe partition Source #
:: (ProjectibleWithPredicate WindowFrameContext be (WithExprContext (BeamSqlBackendWindowFrameSyntax' be)) window, Projectible be r, Projectible be a, ContextRewritable a, ThreadRewritable (QNested s) (WithRewrittenContext a QValueContext)) | |
=> (r -> window) | Window builder function |
-> (r -> window -> a) | Projection builder function. Has access to the windows generated above |
-> Q be db (QNested s) r | Query to window over |
-> Q be db s (WithRewrittenThread (QNested s) s (WithRewrittenContext a QValueContext)) |
Compute a query over windows.
The first function builds window frames using the frame_
, partitionBy_
,
etc functions. The return type can be a single frame, tuples of frame, or
any arbitrarily nested tuple of the above. Instances up to 8-tuples are
provided.
The second function builds the resulting projection using the result of the
subquery as well as the window frames built in the first function. In this
function, window expressions can be included in the output using the
over_
function.
Ordering primitives
orderBy_ :: forall s a ordering be db. (Projectible be a, SqlOrderable be ordering, ThreadRewritable (QNested s) a) => (a -> ordering) -> Q be db (QNested s) a -> Q be db s (WithRewrittenThread (QNested s) s a) Source #
Order by the given expressions. The return type of the ordering key should
either be the result of asc_
or desc_
(or another ordering QOrd
generated by a backend-specific ordering) or an (possibly nested) tuple of
results of the former.
The manual section has more information.
asc_ :: forall be s a. BeamSqlBackend be => QExpr be s a -> QOrd be s a Source #
Produce a QOrd
corresponding to a SQL ASC
ordering
desc_ :: forall be s a. BeamSqlBackend be => QExpr be s a -> QOrd be s a Source #
Produce a QOrd
corresponding to a SQL DESC
ordering
nullsFirst_ :: IsSql2003OrderingElementaryOLAPOperationsSyntax (BeamSqlBackendOrderingSyntax be) => QOrd be s a -> QOrd be s a Source #
nullsLast_ :: IsSql2003OrderingElementaryOLAPOperationsSyntax (BeamSqlBackendOrderingSyntax be) => QOrd be s a -> QOrd be s a Source #
Various combinators corresponding to SQL extensions
T614 NTILE function
ntile_ :: (BeamSqlBackend be, BeamSqlT614Backend be, Integral n) => QExpr be s n -> QAgg be s a Source #
T615 LEAD and LAG function
lead1_ :: (BeamSqlBackend be, BeamSqlT615Backend be) => QExpr be s a -> QAgg be s a Source #
lag1_ :: (BeamSqlBackend be, BeamSqlT615Backend be) => QExpr be s a -> QAgg be s a Source #
lead_ :: (BeamSqlBackend be, BeamSqlT615Backend be, Integral n) => QExpr be s a -> QExpr be s n -> QAgg be s a Source #
lag_ :: (BeamSqlBackend be, BeamSqlT615Backend be, Integral n) => QExpr be s a -> QExpr be s n -> QAgg be s a Source #
leadWithDefault_ :: (BeamSqlBackend be, BeamSqlT615Backend be, Integral n) => QExpr be s a -> QExpr be s n -> QExpr be s a -> QAgg be s a Source #
lagWithDefault_ :: (BeamSqlBackend be, BeamSqlT615Backend be, Integral n) => QExpr be s a -> QExpr be s n -> QExpr be s a -> QAgg be s a Source #
T616 FIRST_VALUE and LAST_VALUE functions
firstValue_ :: (BeamSqlBackend be, BeamSqlT616Backend be) => QExpr be s a -> QAgg be s a Source #
lastValue_ :: (BeamSqlBackend be, BeamSqlT616Backend be) => QExpr be s a -> QAgg be s a Source #
T618 NTH_VALUE function
nthValue_ :: (BeamSqlBackend be, BeamSqlT618Backend be, Integral n) => QExpr be s a -> QExpr be s n -> QAgg be s a Source #
T621 Enhanced numeric functions
(**.) :: (Floating a, BeamSqlBackend be, BeamSqlT621Backend be) => QGenExpr ctxt be s a -> QGenExpr ctxt be s a -> QGenExpr ctxt be s a infixr 8 Source #
ln_ :: (Floating a, BeamSqlBackend be, BeamSqlT621Backend be) => QGenExpr ctxt be s a -> QGenExpr ctxt be s a Source #
exp_ :: (Floating a, BeamSqlBackend be, BeamSqlT621Backend be) => QGenExpr ctxt be s a -> QGenExpr ctxt be s a Source #
sqrt_ :: (Floating a, BeamSqlBackend be, BeamSqlT621Backend be) => QGenExpr ctxt be s a -> QGenExpr ctxt be s a Source #
ceiling_ :: (RealFrac a, Integral b, BeamSqlBackend be, BeamSqlT621Backend be) => QGenExpr ctxt be s a -> QGenExpr ctxt be s b Source #
floor_ :: (RealFrac a, Integral b, BeamSqlBackend be, BeamSqlT621Backend be) => QGenExpr ctxt be s a -> QGenExpr ctxt be s b Source #
stddevPopOver_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QAgg be s b Source #
stddevSampOver_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QAgg be s b Source #
varPopOver_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QAgg be s b Source #
varSampOver_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QAgg be s b Source #
stddevPop_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => QExpr be s a -> QAgg be s b Source #
stddevSamp_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => QExpr be s a -> QAgg be s b Source #
varPop_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => QExpr be s a -> QAgg be s b Source #
varSamp_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => QExpr be s a -> QAgg be s b Source #
covarPopOver_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QExpr be s a -> QExpr be s b Source #
covarSampOver_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QExpr be s a -> QExpr be s b Source #
corrOver_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QExpr be s a -> QExpr be s b Source #
regrSlopeOver_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QExpr be s a -> QExpr be s b Source #
regrInterceptOver_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QExpr be s a -> QExpr be s b Source #
regrCountOver_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QExpr be s a -> QExpr be s b Source #
regrRSquaredOver_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QExpr be s a -> QExpr be s b Source #
regrAvgXOver_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QExpr be s a -> QExpr be s b Source #
regrAvgYOver_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QExpr be s a -> QExpr be s b Source #
regrSXXOver_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QExpr be s a -> QExpr be s b Source #
regrSYYOver_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QExpr be s a -> QExpr be s b Source #
regrSXYOver_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QExpr be s a -> QExpr be s b Source #
covarPop_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => QExpr be s a -> QExpr be s a -> QExpr be s b Source #
covarSamp_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => QExpr be s a -> QExpr be s a -> QExpr be s b Source #
corr_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => QExpr be s a -> QExpr be s a -> QExpr be s b Source #
regrSlope_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => QExpr be s a -> QExpr be s a -> QExpr be s b Source #
regrIntercept_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => QExpr be s a -> QExpr be s a -> QExpr be s b Source #
regrCount_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => QExpr be s a -> QExpr be s a -> QExpr be s b Source #
regrRSquared_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => QExpr be s a -> QExpr be s a -> QExpr be s b Source #
regrAvgX_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => QExpr be s a -> QExpr be s a -> QExpr be s b Source #
regrAvgY_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => QExpr be s a -> QExpr be s a -> QExpr be s b Source #
regrSXX_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => QExpr be s a -> QExpr be s a -> QExpr be s b Source #
regrSYY_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => QExpr be s a -> QExpr be s a -> QExpr be s b Source #
regrSXY_ :: (Num a, Floating b, BeamSqlBackend be, BeamSqlT621Backend be) => QExpr be s a -> QExpr be s a -> QExpr be s b Source #
Relationships
Many-to-many relationships
type ManyToMany be db left right = forall s. (BeamSqlBackend be, SqlEq (QExpr be s) (PrimaryKey left (QExpr be s)), SqlEq (QExpr be s) (PrimaryKey right (QExpr be s))) => Q be db s (left (QExpr be s)) -> Q be db s (right (QExpr be s)) -> Q be db s (left (QExpr be s), right (QExpr be s)) Source #
Convenience type to declare many-to-many relationships. See the manual section on relationships for more information
type ManyToManyThrough be db through left right = forall s. (BeamSqlBackend be, SqlEq (QExpr be s) (PrimaryKey left (QExpr be s)), SqlEq (QExpr be s) (PrimaryKey right (QExpr be s))) => Q be db s (left (QExpr be s)) -> Q be db s (right (QExpr be s)) -> Q be db s (through (QExpr be s), left (QExpr be s), right (QExpr be s)) Source #
Convenience type to declare many-to-many relationships with additional data. See the manual section on relationships for more information
manyToMany_ :: (Database be db, Table joinThrough, Table left, Table right, BeamSqlBackend be, SqlEq (QExpr be s) (PrimaryKey left (QExpr be s)), SqlEq (QExpr be s) (PrimaryKey right (QExpr be s))) => DatabaseEntity be db (TableEntity joinThrough) -> (joinThrough (QExpr be s) -> PrimaryKey left (QExpr be s)) -> (joinThrough (QExpr be s) -> PrimaryKey right (QExpr be s)) -> Q be db s (left (QExpr be s)) -> Q be db s (right (QExpr be s)) -> Q be db s (left (QExpr be s), right (QExpr be s)) Source #
Used to define many-to-many relationships without any additional data.
Takes the join table and two key extraction functions from that table to the
related tables. Also takes two Q
s representing the table sources to relate.
See the manual for more information.
manyToManyPassthrough_ :: (Database be db, Table joinThrough, Table left, Table right, BeamSqlBackend be, SqlEq (QExpr be s) (PrimaryKey left (QExpr be s)), SqlEq (QExpr be s) (PrimaryKey right (QExpr be s))) => DatabaseEntity be db (TableEntity joinThrough) -> (joinThrough (QExpr be s) -> PrimaryKey left (QExpr be s)) -> (joinThrough (QExpr be s) -> PrimaryKey right (QExpr be s)) -> Q be db s (left (QExpr be s)) -> Q be db s (right (QExpr be s)) -> Q be db s (joinThrough (QExpr be s), left (QExpr be s), right (QExpr be s)) Source #
Used to define many-to-many relationships with additional data. Takes the
join table and two key extraction functions from that table to the related
tables. Also takes two Q
s representing the table sources to relate.
See the manual for more information.
One-to-many relationships
type OneToMany be db s one many = (BeamSqlBackend be, BeamSqlBackendCanSerialize be Bool) => one (QExpr be s) -> Q be db s (many (QExpr be s)) Source #
Convenience type to declare one-to-many relationships. See the manual section on relationships for more information
type OneToManyOptional be db s tbl rel = (BeamSqlBackend be, BeamSqlBackendCanSerialize be Bool, BeamSqlBackendCanSerialize be SqlNull) => tbl (QExpr be s) -> Q be db s (rel (Nullable (QExpr be s))) Source #
Convenience type to declare one-to-many relationships with a nullable foreign key. See the manual section on relationships for more information
:: (Database be db, BeamSqlBackend be, HasTableEquality be (PrimaryKey tbl), Table tbl, Table rel) | |
=> DatabaseEntity be db (TableEntity rel) | Table to fetch (many) |
-> (rel (QExpr be s) -> PrimaryKey tbl (QExpr be s)) | Foreign key |
-> tbl (QExpr be s) | |
-> Q be db s (rel (QExpr be s)) |
Used to define one-to-many (or one-to-one) relationships. Takes the table to fetch, a way to extract the foreign key from that table, and the table to relate to.
:: (BeamSqlBackend be, Database be db, Table tbl, Table rel, HasTableEqualityNullable be (PrimaryKey tbl)) | |
=> DatabaseEntity be db (TableEntity rel) | Table to fetch |
-> (rel (QExpr be s) -> PrimaryKey tbl (Nullable (QExpr be s))) | Foreign key |
-> tbl (QExpr be s) | |
-> Q be db s (rel (Nullable (QExpr be s))) |
Used to define one-to-many (or one-to-one) relationships with a nullable foreign key. Takes the table to fetch, a way to extract the foreign key from that table, and the table to relate to.
One-to-one relationshships
type OneToOne be db s one many = OneToMany be db s one many Source #
Synonym of OneToMany
. Useful for giving more meaningful types, when the
relationship is meant to be one-to-one.
type OneToMaybe be db s tbl rel = OneToManyOptional be db s tbl rel Source #
Synonym of OneToManyOptional
. Useful for giving more meaningful types,
when the relationship is meant to be one-to-one.
:: (Database be db, BeamSqlBackend be, HasTableEquality be (PrimaryKey tbl), Table tbl, Table rel) | |
=> DatabaseEntity be db (TableEntity rel) | Table to fetch (many) |
-> (rel (QExpr be s) -> PrimaryKey tbl (QExpr be s)) | Foreign key |
-> tbl (QExpr be s) | |
-> Q be db s (rel (QExpr be s)) |
Used to define one-to-many (or one-to-one) relationships. Takes the table to fetch, a way to extract the foreign key from that table, and the table to relate to.
:: (BeamSqlBackend be, Database be db, Table tbl, Table rel, HasTableEqualityNullable be (PrimaryKey tbl)) | |
=> DatabaseEntity be db (TableEntity rel) | Table to fetch |
-> (rel (QExpr be s) -> PrimaryKey tbl (Nullable (QExpr be s))) | Foreign key |
-> tbl (QExpr be s) | |
-> Q be db s (rel (Nullable (QExpr be s))) |
Used to define one-to-many (or one-to-one) relationships with a nullable foreign key. Takes the table to fetch, a way to extract the foreign key from that table, and the table to relate to.
data With be (db :: (Type -> Type) -> Type) a Source #
Monad in which SELECT
statements can be made (via selecting
)
and bound to result names for re-use later. This has the advantage
of only computing each result once. In SQL, this is translated to a
common table expression.
Once introduced, results can be re-used in future queries with reuse
.
With
is also a member of MonadFix
for backends that support
recursive CTEs. In this case, you can use mdo
or rec
notation
(with RecursiveDo
enabled) to bind result values (again, using
reuse
) even before they're introduced.
See further documentation here.
Instances
Monad (With be db) Source # | |
Functor (With be db) Source # | |
IsSql99RecursiveCommonTableExpressionSelectSyntax (BeamSqlBackendSelectSyntax be) => MonadFix (With be db) Source # | |
Defined in Database.Beam.Query.CTE | |
Applicative (With be db) Source # | |
Defined in Database.Beam.Query.CTE |
selecting :: forall res be db. (BeamSql99CommonTableExpressionBackend be, HasQBuilder be, Projectible be res, ThreadRewritable QAnyScope res) => Q be db QAnyScope res -> With be db (ReusableQ be db res) Source #
Introduce the result of a query as a result in a common table
expression. The returned value can be used in future queries by
applying reuse
.
reuse :: forall s be db res. ReusableQ be db res -> Q be db s (WithRewrittenThread QAnyScope s res) Source #
Introduces the result of a previous selecting
(a CTE) into a new query
SQL EXTRACT
support
newtype ExtractField be tgt a Source #
A field that can be extracted from SQL expressions of type tgt
that results in a type a
, in backend be
.
extract_ :: BeamSqlBackend be => ExtractField be tgt a -> QGenExpr ctxt be s tgt -> QGenExpr cxt be s a Source #
Extracts the given field from the target expression
SQL92 fields
hour_ :: (BeamSqlBackend be, HasSqlTime tgt) => ExtractField be tgt Double Source #
Extracts the hours, minutes, or seconds from any timestamp or time field
minutes_ :: (BeamSqlBackend be, HasSqlTime tgt) => ExtractField be tgt Double Source #
Extracts the hours, minutes, or seconds from any timestamp or time field
seconds_ :: (BeamSqlBackend be, HasSqlTime tgt) => ExtractField be tgt Double Source #
Extracts the hours, minutes, or seconds from any timestamp or time field
year_ :: (BeamSqlBackend be, HasSqlDate tgt) => ExtractField be tgt Double Source #
month_ :: (BeamSqlBackend be, HasSqlDate tgt) => ExtractField be tgt Double Source #
day_ :: (BeamSqlBackend be, HasSqlDate tgt) => ExtractField be tgt Double Source #
class HasSqlTime tgt Source #
Type-class for types that contain a time component
Instances
HasSqlTime UTCTime Source # | |
Defined in Database.Beam.Query.Extract | |
HasSqlTime LocalTime Source # | |
Defined in Database.Beam.Query.Extract | |
HasSqlTime TimeOfDay Source # | |
Defined in Database.Beam.Query.Extract |
class HasSqlDate tgt Source #
Type-class for types that contain a date component
Instances
HasSqlDate UTCTime Source # | |
Defined in Database.Beam.Query.Extract | |
HasSqlDate LocalTime Source # | |
Defined in Database.Beam.Query.Extract | |
HasSqlDate Day Source # | |
Defined in Database.Beam.Query.Extract |
Operators
Phantom type representing a SQL Tri-state boolean -- true, false, and unknown
This type has no values because it cannot be sent to or retrieved
from the database directly. Use isTrue_
, isFalse_
,
isNotTrue_
, isNotFalse_
, isUnknown_
, isNotUnknown_
, and
unknownAs_
to retrieve the corresponding Bool
value.
General-purpose operators
(&&.) :: BeamSqlBackend be => QGenExpr context be s Bool -> QGenExpr context be s Bool -> QGenExpr context be s Bool infixr 3 Source #
SQL AND
operator
(||.) :: BeamSqlBackend be => QGenExpr context be s Bool -> QGenExpr context be s Bool -> QGenExpr context be s Bool infixr 2 Source #
SQL OR
operator
not_ :: forall be context s. BeamSqlBackend be => QGenExpr context be s Bool -> QGenExpr context be s Bool Source #
SQL NOT
operator
div_ :: (Integral a, BeamSqlBackend be) => QGenExpr context be s a -> QGenExpr context be s a -> QGenExpr context be s a infixl 7 Source #
SQL /
operator
mod_ :: (Integral a, BeamSqlBackend be) => QGenExpr context be s a -> QGenExpr context be s a -> QGenExpr context be s a infixl 7 Source #
SQL %
operator
(&&?.) :: BeamSqlBackend be => QGenExpr context be s SqlBool -> QGenExpr context be s SqlBool -> QGenExpr context be s SqlBool infixr 3 Source #
SQL AND
operator for SqlBool
(||?.) :: BeamSqlBackend be => QGenExpr context be s SqlBool -> QGenExpr context be s SqlBool -> QGenExpr context be s SqlBool infixr 2 Source #
SQL OR
operator
sqlNot_ :: forall be context s. BeamSqlBackend be => QGenExpr context be s SqlBool -> QGenExpr context be s SqlBool Source #
SQL NOT
operator, but operating on SqlBool
instead
like_ :: (BeamSqlBackendIsString be text, BeamSqlBackend be) => QGenExpr ctxt be s text -> QGenExpr ctxt be s text -> QGenExpr ctxt be s Bool infix 4 Source #
SQL LIKE
operator
similarTo_ :: (BeamSqlBackendIsString be text, BeamSql99ExpressionBackend be) => QGenExpr ctxt be s text -> QGenExpr ctxt be s text -> QGenExpr ctxt be s text infix 4 Source #
SQL99 SIMILAR TO
operator
concat_ :: BeamSql99ConcatExpressionBackend be => [QGenExpr context be s Text] -> QGenExpr context be s Text Source #
SQL CONCAT
function
ANSI SQL Booleans
isTrue_ :: BeamSqlBackend be => QGenExpr context be s SqlBool -> QGenExpr context be s Bool Source #
SQL IS TRUE
operator
isNotTrue_ :: BeamSqlBackend be => QGenExpr context be s SqlBool -> QGenExpr context be s Bool Source #
SQL IS NOT TRUE
operator
isFalse_ :: BeamSqlBackend be => QGenExpr context be s SqlBool -> QGenExpr context be s Bool Source #
SQL IS FALSE
operator
isNotFalse_ :: BeamSqlBackend be => QGenExpr context be s SqlBool -> QGenExpr context be s Bool Source #
SQL IS NOT FALSE
operator
isUnknown_ :: BeamSqlBackend be => QGenExpr context be s SqlBool -> QGenExpr context be s Bool Source #
SQL IS UNKNOWN
operator
isNotUnknown_ :: BeamSqlBackend be => QGenExpr context be s SqlBool -> QGenExpr context be s Bool Source #
SQL IS NOT UNKNOWN
operator
unknownAs_ :: BeamSqlBackend be => Bool -> QGenExpr context be s SqlBool -> QGenExpr context be s Bool Source #
Return the first argument if the expression has the unknown SQL value
See sqlBool_
for the inverse
sqlBool_ :: QGenExpr context syntax s Bool -> QGenExpr context syntax s SqlBool Source #
Convert a known not null bool to a SqlBool
. See unknownAs_
for the inverse
fromPossiblyNullBool_ :: QGenExpr context be s (Maybe Bool) -> QGenExpr context be s SqlBool Source #
Unquantified comparison operators
class BeamSqlBackend be => HasSqlEqualityCheck be a where Source #
Class for Haskell types that can be compared for equality in the given backend
Nothing
sqlEqE :: Proxy a -> Proxy be -> BeamSqlBackendExpressionSyntax be -> BeamSqlBackendExpressionSyntax be -> BeamSqlBackendExpressionSyntax be Source #
sqlNeqE :: Proxy a -> Proxy be -> BeamSqlBackendExpressionSyntax be -> BeamSqlBackendExpressionSyntax be -> BeamSqlBackendExpressionSyntax be Source #
sqlEqTriE :: Proxy a -> Proxy be -> BeamSqlBackendExpressionSyntax be -> BeamSqlBackendExpressionSyntax be -> BeamSqlBackendExpressionSyntax be Source #
Tri-state equality
sqlNeqTriE :: Proxy a -> Proxy be -> BeamSqlBackendExpressionSyntax be -> BeamSqlBackendExpressionSyntax be -> BeamSqlBackendExpressionSyntax be Source #
Tri-state equality
Instances
class HasSqlEqualityCheck be a => HasSqlQuantifiedEqualityCheck be a where Source #
Class for Haskell types that can be compared for quantified equality in the given backend
Nothing
sqlQEqE :: Proxy a -> Proxy be -> Maybe (BeamSqlBackendExpressionQuantifierSyntax be) -> BeamSqlBackendExpressionSyntax be -> BeamSqlBackendExpressionSyntax be -> BeamSqlBackendExpressionSyntax be Source #
sqlQNeqE :: Proxy a -> Proxy be -> Maybe (BeamSqlBackendExpressionQuantifierSyntax be) -> BeamSqlBackendExpressionSyntax be -> BeamSqlBackendExpressionSyntax be -> BeamSqlBackendExpressionSyntax be Source #
Instances
type HasTableEquality be tbl = (FieldsFulfillConstraint (HasSqlEqualityCheck be) tbl, Beamable tbl) Source #
Constraint synonym to check if two tables can be compared for equality
class SqlEq expr a | a -> expr where Source #
Class for expression types or expression containers for which there is a notion of equality.
Instances are provided to check the equality of expressions of the same
type as well as entire Beamable
types parameterized over QGenExpr
(==.) :: a -> a -> expr Bool infix 4 Source #
Given two expressions, returns whether they are equal, using Haskell semantics (NULLs handled properly)
(/=.) :: a -> a -> expr Bool infix 4 Source #
Given two expressions, returns whether they are not equal, using Haskell semantics (NULLs handled properly)
(==?.) :: a -> a -> expr SqlBool infix 4 Source #
Given two expressions, returns the SQL tri-state boolean when compared for equality
(/=?.) :: a -> a -> expr SqlBool infix 4 Source #
Given two expressions, returns the SQL tri-state boolean when compared for inequality
Instances
(BeamSqlBackend be, Beamable tbl, FieldsFulfillConstraintNullable (HasSqlEqualityCheck be) tbl) => SqlEq (QGenExpr context be s) (tbl (Nullable (QGenExpr context be s))) Source # | |
Defined in Database.Beam.Query.Ord (==.) :: tbl (Nullable (QGenExpr context be s)) -> tbl (Nullable (QGenExpr context be s)) -> QGenExpr context be s Bool Source # (/=.) :: tbl (Nullable (QGenExpr context be s)) -> tbl (Nullable (QGenExpr context be s)) -> QGenExpr context be s Bool Source # (==?.) :: tbl (Nullable (QGenExpr context be s)) -> tbl (Nullable (QGenExpr context be s)) -> QGenExpr context be s SqlBool Source # (/=?.) :: tbl (Nullable (QGenExpr context be s)) -> tbl (Nullable (QGenExpr context be s)) -> QGenExpr context be s SqlBool Source # | |
(BeamSqlBackend be, Beamable tbl, FieldsFulfillConstraint (HasSqlEqualityCheck be) tbl) => SqlEq (QGenExpr context be s) (tbl (QGenExpr context be s)) Source # | Compare two arbitrary |
Defined in Database.Beam.Query.Ord (==.) :: tbl (QGenExpr context be s) -> tbl (QGenExpr context be s) -> QGenExpr context be s Bool Source # (/=.) :: tbl (QGenExpr context be s) -> tbl (QGenExpr context be s) -> QGenExpr context be s Bool Source # (==?.) :: tbl (QGenExpr context be s) -> tbl (QGenExpr context be s) -> QGenExpr context be s SqlBool Source # (/=?.) :: tbl (QGenExpr context be s) -> tbl (QGenExpr context be s) -> QGenExpr context be s SqlBool Source # | |
(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 |
Defined in Database.Beam.Query.Ord (==.) :: QGenExpr context be s a -> QGenExpr context be s a -> QGenExpr context be s Bool Source # (/=.) :: QGenExpr context be s a -> QGenExpr context be s a -> QGenExpr context be s Bool Source # (==?.) :: QGenExpr context be s a -> QGenExpr context be s a -> QGenExpr context be s SqlBool Source # (/=?.) :: QGenExpr context be s a -> QGenExpr context be s a -> QGenExpr context be s SqlBool Source # |
class SqlOrd expr e | e -> expr where Source #
Class for expression types or expression containers for which there is a notion of ordering.
Instances are provided to check the ordering of expressions of the same
type. Since there is no universal notion of ordering for an arbitrary
number of expressions, no instance is provided for Beamable
types.
(<.) :: e -> e -> expr Bool infix 4 Source #
(>.) :: e -> e -> expr Bool infix 4 Source #
Instances
BeamSqlBackend be => SqlOrd (QGenExpr context be s) (QGenExpr context be s a) Source # | |
Defined in Database.Beam.Query.Ord (<.) :: QGenExpr context be s a -> QGenExpr context be s a -> QGenExpr context be s Bool Source # (>.) :: QGenExpr context be s a -> QGenExpr context be s a -> QGenExpr context be s Bool Source # (<=.) :: QGenExpr context be s a -> QGenExpr context be s a -> QGenExpr context be s Bool Source # (>=.) :: QGenExpr context be s a -> QGenExpr context be s a -> QGenExpr context be s Bool Source # |
class BeamSqlBackend be => HasSqlInTable be where Source #
Class for backends which support SQL IN
on lists of row values, which is
not part of ANSI SQL. This is useful for IN
on primary keys.
Nothing
inRowValuesE :: Proxy be -> BeamSqlBackendExpressionSyntax be -> [BeamSqlBackendExpressionSyntax be] -> BeamSqlBackendExpressionSyntax be Source #
Quantified Comparison Operators
class SqlEq expr a => SqlEqQuantified expr quantified a | a -> expr quantified where Source #
Class for expression types for which there is a notion of quantified equality.
(==*.) :: a -> quantified -> expr SqlBool infix 4 Source #
Quantified equality and inequality using SQL semantics (tri-state boolean)
(/=*.) :: a -> quantified -> expr SqlBool infix 4 Source #
Quantified equality and inequality using SQL semantics (tri-state boolean)
Instances
(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. |
Defined in Database.Beam.Query.Ord |
class SqlOrd expr e => SqlOrdQuantified expr quantified e | e -> expr quantified where Source #
Class for things which can be quantifiably compared.
(<*.) :: e -> quantified -> expr Bool infix 4 Source #
(>*.) :: e -> quantified -> expr Bool infix 4 Source #
Instances
BeamSqlBackend be => SqlOrdQuantified (QGenExpr context be s) (QQuantified be s a) (QGenExpr context be s a) Source # | |
Defined in Database.Beam.Query.Ord (<*.) :: QGenExpr context be s a -> QQuantified be s a -> QGenExpr context be s Bool Source # (>*.) :: QGenExpr context be s a -> QQuantified be s a -> QGenExpr context be s Bool Source # (<=*.) :: QGenExpr context be s a -> QQuantified be s a -> QGenExpr context be s Bool Source # (>=*.) :: QGenExpr context be s a -> QQuantified be s a -> QGenExpr context be s Bool Source # |
data QQuantified be s r Source #
A data structure representing the set to quantify a comparison operator over.
Instances
BeamSqlBackend be => SqlOrdQuantified (QGenExpr context be s) (QQuantified be s a) (QGenExpr context be s a) Source # | |
Defined in Database.Beam.Query.Ord (<*.) :: QGenExpr context be s a -> QQuantified be s a -> QGenExpr context be s Bool Source # (>*.) :: QGenExpr context be s a -> QQuantified be s a -> QGenExpr context be s Bool Source # (<=*.) :: QGenExpr context be s a -> QQuantified be s a -> QGenExpr context be s Bool Source # (>=*.) :: QGenExpr context be s a -> QQuantified be s a -> QGenExpr context be s Bool Source # | |
(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. |
Defined in Database.Beam.Query.Ord |
anyOf_ :: forall s a be db. (BeamSqlBackend be, HasQBuilder be) => Q be db (QNested s) (QExpr be (QNested s) a) -> QQuantified be s a Source #
A QQuantified
representing a SQL ANY(..)
for use with a
quantified comparison operator
Accepts a subquery. Use anyIn_
for an explicit list
allOf_ :: forall s a be db. (BeamSqlBackend be, HasQBuilder be) => Q be db (QNested s) (QExpr be (QNested s) a) -> QQuantified be s a Source #
A QQuantified
representing a SQL ALL(..)
for use with a
quantified comparison operator
Accepts a subquery. Use allIn_
for an explicit list
anyIn_ :: forall s a be. BeamSqlBackend be => [QExpr be s a] -> QQuantified be s a Source #
A QQuantified
representing a SQL ANY(..)
for use with a
quantified comparison operator
Accepts an explicit list of typed expressions. Use anyOf_
for
a subquery
allIn_ :: forall s a be. BeamSqlBackend be => [QExpr be s a] -> QQuantified be s a Source #
A QQuantified
representing a SQL ALL(..)
for use with a
quantified comparison operator
Accepts an explicit list of typed expressions. Use allOf_
for
a subquery
between_ :: BeamSqlBackend be => QGenExpr context be s a -> QGenExpr context be s a -> QGenExpr context be s a -> QGenExpr context be s Bool infix 4 Source #
SQL BETWEEN
clause
Aggregates
See the corresponding manual section for more detail
:: (BeamSqlBackend be, Aggregable be a, Projectible be r, Projectible be a, ContextRewritable a, ThreadRewritable (QNested s) (WithRewrittenContext a QValueContext)) | |
=> (r -> a) | Aggregate projection |
-> Q be db (QNested s) r | Query to aggregate over |
-> Q be db s (WithRewrittenThread (QNested s) s (WithRewrittenContext a QValueContext)) |
Compute an aggregate over a query.
The supplied aggregate projection should return an aggregate expression (an
expression containing an aggregate function such as count_
, sum_
,
countAll_
, etc), a grouping key (specified with the group_
function),
or a combination of tuples of the above.
Appropriate instances are provided up to 8-tuples.
Semantically, all grouping expressions in the projection will be added to a
SQL GROUP BY
clause and all aggregate expressions will be computed.
The return value will be the type of the aggregate projection, but
transformed to be in the normal value context (i.e., everything will become
QGenExpr
s).
For usage examples, see the manual.
filterWhere_ :: BeamSqlT611Backend be => QAgg be s a -> QExpr be s Bool -> QAgg be s a Source #
Support for FILTER (WHERE ...) syntax for aggregates. Part of SQL2003 Elementary OLAP operations feature (T611).
See filterWhere_'
for a version that accepts SqlBool
.
filterWhere_' :: BeamSqlT611Backend be => QAgg be s a -> QExpr be s SqlBool -> QAgg be s a Source #
Like filterWhere_
but accepting SqlBool
.
class QGroupable expr grouped | expr -> grouped, grouped -> expr where Source #
Type class for grouping keys. expr
is the type of the grouping key after
projection. grouped
is the type of the grouping key in the aggregate
expression (usually something that contains QGenExpr
s in the
QGroupingContext
).
Instances
Beamable tbl => QGroupable (tbl (Nullable (QExpr be s))) (tbl (Nullable (QGroupExpr be s))) Source # |
|
Defined in Database.Beam.Query.Aggregate | |
Beamable tbl => QGroupable (tbl (QExpr be s)) (tbl (QGroupExpr be s)) Source # |
|
Defined in Database.Beam.Query.Aggregate group_ :: tbl (QExpr be s) -> tbl (QGroupExpr be s) Source # | |
QGroupable (QExpr be s a) (QGroupExpr be s a) Source # |
|
Defined in Database.Beam.Query.Aggregate group_ :: QExpr be s a -> QGroupExpr be s a Source # |
General-purpose aggregate functions
sum_ :: (BeamSqlBackend be, Num a) => QExpr be s a -> QAgg be s (Maybe a) Source #
SQL SUM(ALL ..)
function (but without the explicit ALL)
avg_ :: (BeamSqlBackend be, Num a) => QExpr be s a -> QAgg be s (Maybe a) Source #
SQL AVG(ALL ..)
function (but without the explicit ALL)
min_ :: BeamSqlBackend be => QExpr be s a -> QAgg be s (Maybe a) Source #
SQL MIN(ALL ..)
function (but without the explicit ALL)
max_ :: BeamSqlBackend be => QExpr be s a -> QAgg be s (Maybe a) Source #
SQL MAX(ALL ..)
function (but without the explicit ALL)
count_ :: (BeamSqlBackend be, Integral b) => QExpr be s a -> QAgg be s b Source #
SQL COUNT(ALL ..)
function (but without the explicit ALL)
rank_ :: (BeamSqlT611Backend be, Integral a) => QAgg be s a Source #
SQL2003 RANK
function (Requires T611 Elementary OLAP operations support)
cumeDist_ :: BeamSqlT612Backend be => QAgg be s Double Source #
SQL2003 CUME_DIST
function (Requires T612 Advanced OLAP operations support)
percentRank_ :: BeamSqlT612Backend be => QAgg be s Double Source #
SQL2003 PERCENT_RANK
function (Requires T612 Advanced OLAP operations support)
denseRank_ :: (BeamSqlT612Backend be, Integral a) => QAgg be s a Source #
SQL2003 DENSE_RANK
function (Requires T612 Advanced OLAP operations support)
rowNumber_ :: (BeamSql2003ExpressionBackend be, Integral a) => QAgg be s a Source #
SQL2003 ROW_NUMBER
function
every_ :: BeamSql99AggregationBackend be => QExpr be s SqlBool -> QAgg be s SqlBool Source #
SQL99 EVERY(ALL ..)
function (but without the explicit ALL)
any_ :: BeamSql99AggregationBackend be => QExpr be s SqlBool -> QAgg be s SqlBool Source #
SQL99 ANY(ALL ..)
function (but without the explicit ALL)
some_ :: BeamSql99AggregationBackend be => QExpr be s SqlBool -> QAgg be s SqlBool Source #
SQL99 SOME(ALL ..)
function (but without the explicit ALL)
Quantified aggregate functions
These functions correspond one-to-one with the <#gp-agg-funcs general-purpose aggregate functions>. However, they each take a mandatory "set quantifier", which is any of the set quantifier values.
sumOver_ :: (BeamSqlBackend be, Num a) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QAgg be s (Maybe a) Source #
avgOver_ :: (BeamSqlBackend be, Num a) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QAgg be s (Maybe a) Source #
minOver_ :: BeamSqlBackend be => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QAgg be s (Maybe a) Source #
maxOver_ :: BeamSqlBackend be => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QAgg be s (Maybe a) Source #
countOver_ :: (BeamSqlBackend be, Integral b) => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s a -> QAgg be s b Source #
everyOver_ :: BeamSql99AggregationBackend be => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s SqlBool -> QAgg be s SqlBool Source #
SQL EVERY
, SOME
, and ANY
aggregates. Operates over
SqlBool
only, as the result can be NULL
, even if all inputs are
known (no input rows).
anyOver_ :: BeamSql99AggregationBackend be => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s SqlBool -> QAgg be s SqlBool Source #
SQL EVERY
, SOME
, and ANY
aggregates. Operates over
SqlBool
only, as the result can be NULL
, even if all inputs are
known (no input rows).
someOver_ :: BeamSql99AggregationBackend be => Maybe (BeamSqlBackendAggregationQuantifierSyntax be) -> QExpr be s SqlBool -> QAgg be s SqlBool Source #
SQL EVERY
, SOME
, and ANY
aggregates. Operates over
SqlBool
only, as the result can be NULL
, even if all inputs are
known (no input rows).
Set quantifiers
distinctInGroup_ :: IsSql92AggregationSetQuantifierSyntax s => Maybe s Source #
Compute an aggregate only over distinct values in a group. Corresponds to
the AGG(DISTINCT ..)
syntax.
allInGroup_ :: IsSql92AggregationSetQuantifierSyntax s => Maybe s Source #
Compute an aggregate over all values in a group. Corresponds semantically
to the AGG(ALL ..)
syntax, but doesn't produce an explicit ALL
. To
produce ALL
expicitly, see allInGroupExplicitly_
.
allInGroupExplicitly_ :: IsSql92AggregationSetQuantifierSyntax s => Maybe s Source #
Compute an aggregate over all values in a group. Corresponds to the
AGG(ALL ..)
syntax. Note that ALL
is the default for most aggregations,
so you don't normally explicitly specify ALL
. However, if you need to,
you can use this function. To be explicit about quantification in the beam
query DSL, but not produce an explicit ALL
, use allInGroup_
.
allInGroup_
has the same semantic meaning, but does not produce an
explicit ALL
.
SQL Command construction and execution
SELECT
newtype SqlSelect be a Source #
Represents a select statement in the given backend, returning
rows of type a
.
select :: forall be db res. (BeamSqlBackend be, HasQBuilder be, Projectible be res) => Q be db QBaseScope res -> SqlSelect be (QExprToIdentity res) Source #
selectWith :: forall be db res. (BeamSqlBackend be, BeamSql99CommonTableExpressionBackend be, HasQBuilder be, Projectible be res) => With be db (Q be db QBaseScope res) -> SqlSelect be (QExprToIdentity res) Source #
lookup_ :: (Database be db, Table table, BeamSqlBackend be, HasQBuilder be, SqlValableTable be (PrimaryKey table), HasTableEquality be (PrimaryKey table)) => DatabaseEntity be db (TableEntity table) -> PrimaryKey table Identity -> SqlSelect be (table Identity) Source #
Convenience function to generate a SqlSelect
that looks up a table row
given a primary key.
runSelectReturningList :: (MonadBeam be m, BeamSqlBackend be, FromBackendRow be a) => SqlSelect be a -> m [a] Source #
runSelectReturningOne :: (MonadBeam be m, BeamSqlBackend be, FromBackendRow be a) => SqlSelect be a -> m (Maybe a) Source #
dumpSqlSelect :: Projectible (MockSqlBackend SqlSyntaxBuilder) res => Q (MockSqlBackend SqlSyntaxBuilder) db QBaseScope res -> IO () Source #
Use a special debug syntax to print out an ANSI Standard SELECT
statement
that may be generated for a given Q
.
INSERT
data SqlInsert be (table :: (Type -> Type) -> Type) Source #
Represents a SQL INSERT
command that has not yet been run
SqlInsert !(TableSettings table) !(BeamSqlBackendInsertSyntax be) | |
SqlInsertNoRows |
:: (BeamSqlBackend be, ProjectibleWithPredicate AnyType () Text (table (QField s))) | |
=> DatabaseEntity be db (TableEntity table) | Table to insert into |
-> SqlInsertValues be (table (QExpr be s)) | Values to insert. See |
-> SqlInsert be table |
Generate a SqlInsert
given a table and a source of values.
:: (BeamSqlBackend be, ProjectibleWithPredicate AnyType () Text (QExprToField r)) | |
=> DatabaseEntity be db (TableEntity table) | Table to insert into |
-> (table (QField s) -> QExprToField r) | |
-> SqlInsertValues be r | Values to insert. See |
-> SqlInsert be table |
Generate a SqlInsert
over only certain fields of a table
data SqlInsertValues be proj Source #
Represents a source of values that can be inserted into a table shaped like
tbl
.
insertExpressions :: forall be table s. (BeamSqlBackend be, Beamable table) => (forall s'. [table (QExpr be s')]) -> SqlInsertValues be (table (QExpr be s)) Source #
Build a SqlInsertValues
from series of expressions in tables
insertValues :: forall be table s. (BeamSqlBackend be, Beamable table, FieldsFulfillConstraint (BeamSqlBackendCanSerialize be) table) => [table Identity] -> SqlInsertValues be (table (QExpr be s)) Source #
Build a SqlInsertValues
from concrete table values
insertFrom :: (BeamSqlBackend be, HasQBuilder be, Projectible be r) => Q be db QBaseScope r -> SqlInsertValues be r Source #
Build a SqlInsertValues
from a SqlSelect
that returns the same table
insertData :: forall be r. (Projectible be r, BeamSqlBackend be) => [r] -> SqlInsertValues be r Source #
Build a SqlInsertValues
from arbitrarily shaped data containing expressions
UPDATE
data SqlUpdate be (table :: (Type -> Type) -> Type) Source #
Represents a SQL UPDATE
statement for the given table
.
SqlUpdate !(TableSettings table) !(BeamSqlBackendUpdateSyntax be) | |
SqlIdentityUpdate |
:: (BeamSqlBackend be, Beamable table) | |
=> DatabaseEntity be db (TableEntity table) | The table to insert into |
-> (forall s. table (QField s) -> QAssignment be s) | A sequence of assignments to make. |
-> (forall s. table (QExpr be s) -> QExpr be s Bool) | Build a |
-> SqlUpdate be table |
Build a SqlUpdate
given a table, a list of assignments, and a way to
build a WHERE
clause.
Use update'
for comparisons with SqlBool
.
See the '(<-.)' operator for ways to build assignments. The argument to the
second argument is a the table parameterized over QField
, which
represents the left hand side of assignments. Sometimes, you'd like to also
get the current value of a particular column. You can use the current_
function to convert a QField
to a QGenExpr
.
:: (Table table, BeamSqlBackend be, SqlValableTable be (PrimaryKey table), SqlValableTable be table, HasTableEquality be (PrimaryKey table)) | |
=> DatabaseEntity be db (TableEntity table) | Table to update |
-> table Identity | Value to set to |
-> SqlUpdate be table |
Generate a SqlUpdate
that will update the given table row with the given value.
The SQL UPDATE
that is generated will set every non-primary key field for
the row where each primary key field is exactly what is given.
Note: This is a pure SQL UPDATE
command. This does not upsert or merge values.
:: (BeamSqlBackend be, Beamable table) | |
=> DatabaseEntity be db (TableEntity table) | The table to insert into |
-> (forall s. table (QField s) -> QAssignment be s) | A sequence of assignments to make. |
-> (forall s. table (QExpr be s) -> QExpr be s SqlBool) | Build a |
-> SqlUpdate be table |
Build a SqlUpdate
given a table, a list of assignments, and a way to
build a WHERE
clause.
Uses a SqlBool
comparison. Use update
for comparisons with Bool
.
See the '(<-.)' operator for ways to build assignments. The argument to the
second argument is a the table parameterized over QField
, which
represents the left hand side of assignments. Sometimes, you'd like to also
get the current value of a particular column. You can use the current_
function to convert a QField
to a QGenExpr
.
:: (Table table, BeamSqlBackend be, SqlValableTable be (PrimaryKey table), SqlValableTable be table, HasTableEquality be (PrimaryKey table)) | |
=> DatabaseEntity be db (TableEntity table) | Table to update |
-> table Identity | Value to set to |
-> SqlUpdate be table |
Generate a SqlUpdate
that will update the given table row with the given value.
This is a variant using update'
and a SqlBool
comparison.
The SQL UPDATE
that is generated will set every non-primary key field for
the row where each primary key field is exactly what is given.
Note: This is a pure SQL UPDATE
command. This does not upsert or merge values.
:: (BeamSqlBackend be, Beamable table) | |
=> DatabaseEntity be db (TableEntity table) | The table to update |
-> table (QFieldAssignment be table) | Updates to be made (use |
-> (forall s. table (QExpr be s) -> QExpr be s Bool) | |
-> SqlUpdate be table |
A specialization of update
that is more convenient for normal tables.
Use updateTable'
for comparisons with SqlBool
.
:: (BeamSqlBackend be, Beamable table) | |
=> DatabaseEntity be db (TableEntity table) | The table to update |
-> table (QFieldAssignment be table) | Updates to be made (use |
-> (forall s. table (QExpr be s) -> QExpr be s SqlBool) | |
-> SqlUpdate be table |
A specialization of update'
that is more convenient for normal tables.
Use updateTable
for comparisons with Bool
.
set :: forall table be table'. Beamable table => table (QFieldAssignment be table') Source #
setFieldsTo :: forall table be table'. Table table => (forall s. table (QExpr be s)) -> table (QFieldAssignment be table') Source #
toNewValue :: (forall s. QExpr be s a) -> QFieldAssignment be table a Source #
Use with set
to set a field to an explicit new value that does
not depend on any other value
toOldValue :: QFieldAssignment be table a Source #
Use with set
to not modify the field
toUpdatedValue :: (forall s. table (QExpr be s) -> QExpr be s a) -> QFieldAssignment be table a Source #
Use with set
to set a field to a new value that is calculated
based on one or more fields from the existing row
toUpdatedValueMaybe :: (forall s. table (QExpr be s) -> Maybe (QExpr be s a)) -> QFieldAssignment be table a Source #
Use with set
to optionally set a fiield to a new value,
calculated based on one or more fields from the existing row
:: (BeamSqlBackend be, Table table, HasTableEquality be (PrimaryKey table), SqlValableTable be (PrimaryKey table)) | |
=> DatabaseEntity be db (TableEntity table) | The table to insert into |
-> table Identity | The row to update |
-> (forall s. table (QField s) -> QAssignment be s) | A sequence of assignments to make. |
-> SqlUpdate be table |
A specialization of update
that matches the given (already existing) row.
Use updateRow'
for an internal SqlBool
comparison.
:: (BeamSqlBackend be, Table table, HasTableEquality be (PrimaryKey table), SqlValableTable be (PrimaryKey table)) | |
=> DatabaseEntity be db (TableEntity table) | The table to update |
-> table Identity | The row to update |
-> table (QFieldAssignment be table) | Updates to be made (use |
-> SqlUpdate be table |
Convenience form of updateTable
that generates a WHERE
clause
that matches only the already existing entity.
Use updateTableRow'
for an internal SqlBool
comparison.
:: (BeamSqlBackend be, Table table, HasTableEquality be (PrimaryKey table), SqlValableTable be (PrimaryKey table)) | |
=> DatabaseEntity be db (TableEntity table) | The table to insert into |
-> table Identity | The row to update |
-> (forall s. table (QField s) -> QAssignment be s) | A sequence of assignments to make. |
-> SqlUpdate be table |
:: (BeamSqlBackend be, Table table, HasTableEquality be (PrimaryKey table), SqlValableTable be (PrimaryKey table)) | |
=> DatabaseEntity be db (TableEntity table) | The table to update |
-> table Identity | The row to update |
-> table (QFieldAssignment be table) | Updates to be made (use |
-> SqlUpdate be table |
Convenience form of updateTable'
that generates a WHERE
clause
that matches only the already existing entity.
Uses update'
with a SqlBool
comparison.
Use updateTableRow
for an internal Bool
comparison.
DELETE
data SqlDelete be (table :: (Type -> Type) -> Type) Source #
Represents a SQL DELETE
statement for the given table
SqlDelete !(TableSettings table) !(BeamSqlBackendDeleteSyntax be) |
:: BeamSqlBackend be | |
=> DatabaseEntity be db (TableEntity table) | Table to delete from |
-> (forall s. (forall s'. table (QExpr be s')) -> QExpr be s Bool) | Build a |
-> SqlDelete be table |
Build a SqlDelete
from a table and a way to build a WHERE
clause