| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Database.Beam.Query.Internal
Contents
Synopsis
- type ProjectibleInBackend be a = (Projectible be a, ProjectibleValue be a)
- type TablePrefix = Text
- data QF be (db :: (Type -> Type) -> Type) s next where- QDistinct :: forall be r (db :: (Type -> Type) -> Type) s next. Projectible be r => (r -> WithExprContext (BeamSqlBackendSetQuantifierSyntax be)) -> QM be db s r -> (r -> next) -> QF be db s next
- QAll :: forall be r next (db :: (Type -> Type) -> Type) s. Projectible be r => (TablePrefix -> Text -> BeamSqlBackendFromSyntax be) -> (Text -> r) -> (r -> Maybe (WithExprContext (BeamSqlBackendExpressionSyntax be))) -> ((Text, r) -> next) -> QF be db s next
- QArbitraryJoin :: forall be r (db :: (Type -> Type) -> Type) s next. Projectible be r => QM be db (QNested s) r -> Text -> (BeamSqlBackendFromSyntax be -> BeamSqlBackendFromSyntax be -> Maybe (BeamSqlBackendExpressionSyntax be) -> BeamSqlBackendFromSyntax be) -> (r -> Maybe (WithExprContext (BeamSqlBackendExpressionSyntax be))) -> (r -> next) -> QF be db s next
- QTwoWayJoin :: forall be a b (db :: (Type -> Type) -> Type) s next. (Projectible be a, Projectible be b) => QM be db (QNested s) a -> QM be db (QNested s) b -> (BeamSqlBackendFromSyntax be -> BeamSqlBackendFromSyntax be -> Maybe (BeamSqlBackendExpressionSyntax be) -> BeamSqlBackendFromSyntax be) -> ((a, b) -> Maybe (WithExprContext (BeamSqlBackendExpressionSyntax be))) -> ((a, b) -> next) -> QF be db s next
- QSubSelect :: forall be r (db :: (Type -> Type) -> Type) s next. Projectible be r => QM be db (QNested s) r -> (r -> next) -> QF be db s next
- QGuard :: forall be next (db :: (Type -> Type) -> Type) s. WithExprContext (BeamSqlBackendExpressionSyntax be) -> next -> QF be db s next
- QLimit :: forall be r (db :: (Type -> Type) -> Type) s next. Projectible be r => Integer -> QM be db (QNested s) r -> (r -> next) -> QF be db s next
- QOffset :: forall be r (db :: (Type -> Type) -> Type) s next. Projectible be r => Integer -> QM be db (QNested s) r -> (r -> next) -> QF be db s next
- QSetOp :: forall be r (db :: (Type -> Type) -> Type) s next. Projectible be r => (BeamSqlBackendSelectTableSyntax be -> BeamSqlBackendSelectTableSyntax be -> BeamSqlBackendSelectTableSyntax be) -> QM be db (QNested s) r -> QM be db (QNested s) r -> (r -> next) -> QF be db s next
- QOrderBy :: forall be r (db :: (Type -> Type) -> Type) s next. Projectible be r => (r -> WithExprContext [BeamSqlBackendOrderingSyntax be]) -> QM be db (QNested s) r -> (r -> next) -> QF be db s next
- QWindowOver :: forall be window r a (db :: (Type -> Type) -> Type) s next. (ProjectibleWithPredicate WindowFrameContext be (WithExprContext (BeamSqlBackendWindowFrameSyntax' be)) window, Projectible be r, Projectible be a) => (r -> window) -> (r -> window -> a) -> QM be db (QNested s) r -> (a -> next) -> QF be db s next
- QAggregate :: forall be grouping a (db :: (Type -> Type) -> Type) s next. (Projectible be grouping, Projectible be a) => (a -> TablePrefix -> (Maybe (BeamSqlBackendGroupingSyntax be), grouping)) -> QM be db (QNested s) a -> (grouping -> next) -> QF be db s next
- QForceSelect :: forall be r (db :: (Type -> Type) -> Type) s next. Projectible be r => (r -> BeamSqlBackendSelectTableSyntax be -> [BeamSqlBackendOrderingSyntax be] -> Maybe Integer -> Maybe Integer -> BeamSqlBackendSelectSyntax be) -> QM be db (QNested s) r -> (r -> next) -> QF be db s next
 
- type QM be (db :: (Type -> Type) -> Type) s = F (QF be db s)
- newtype Q be (db :: (Type -> Type) -> Type) s a = Q {}
- data QInternal
- data QNested s
- data QField s ty = QField {- qFieldShouldQualify :: !Bool
- qFieldTblName :: !Text
- qFieldName :: !Text
 
- newtype QAssignment be s = QAssignment {}
- newtype QFieldAssignment be (tbl :: (Type -> Type) -> Type) a = QFieldAssignment (forall s. tbl (QExpr be s) -> Maybe (QExpr be s a))
- data QAggregateContext
- data QGroupingContext
- data QValueContext
- data QWindowingContext
- data QWindowFrameContext
- newtype QGenExpr context be s t = QExpr (TablePrefix -> BeamSqlBackendExpressionSyntax be)
- newtype QOrd be s t = QOrd (TablePrefix -> BeamSqlBackendOrderingSyntax be)
- type WithExprContext a = TablePrefix -> a
- type QExpr = QGenExpr QValueContext
- type QAgg = QGenExpr QAggregateContext
- type QWindowExpr = QGenExpr QWindowingContext
- type QGroupExpr = QGenExpr QGroupingContext
- newtype QWindow be s = QWindow (WithExprContext (BeamSqlBackendWindowFrameSyntax be))
- newtype QFrameBounds be = QFrameBounds (Maybe (BeamSqlBackendWindowFrameBoundsSyntax be))
- newtype QFrameBound be = QFrameBound (BeamSqlBackendWindowFrameBoundSyntax be)
- qBinOpE :: BeamSqlBackend be => (BeamSqlBackendExpressionSyntax be -> BeamSqlBackendExpressionSyntax be -> BeamSqlBackendExpressionSyntax be) -> QGenExpr context be s a -> QGenExpr context be s b -> QGenExpr context be s c
- unsafeRetype :: QGenExpr ctxt be s a -> QGenExpr ctxt be s a'
- class Typeable context => AggregateContext context
- type family ContextName a :: Symbol
- type family IsAggregateContext a where ...
- type family AggregateContextSuggestion a :: ErrorMessage where ...
- class Typeable context => ValueContext context
- class Typeable context => WindowFrameContext context
- type family IsWindowFrameContext a where ...
- class AnyType a
- type family IsValueContext a where ...
- type family ValueContextSuggestion a :: ErrorMessage where ...
- type Projectible be = ProjectibleWithPredicate AnyType be (WithExprContext (BeamSqlBackendExpressionSyntax' be))
- type ProjectibleValue be = ProjectibleWithPredicate ValueContext be (WithExprContext (BeamSqlBackendExpressionSyntax' be))
- class ThreadRewritable s a | a -> s where- type WithRewrittenThread s s' a
- rewriteThread :: Proxy s' -> a -> WithRewrittenThread s s' a
 
- class ContextRewritable a where- type WithRewrittenContext a ctxt
- rewriteContext :: Proxy ctxt -> a -> WithRewrittenContext a ctxt
 
- newtype BeamSqlBackendExpressionSyntax' be = BeamSqlBackendExpressionSyntax' {}
- newtype BeamSqlBackendWindowFrameSyntax' be = BeamSqlBackendWindowFrameSyntax' {}
- class ProjectibleWithPredicate (contextPredicate :: Type -> Constraint) be res a | a -> be where- project' :: Monad m => Proxy contextPredicate -> Proxy (be, res) -> (forall context. contextPredicate context => Proxy context -> Proxy be -> res -> m res) -> a -> m a
- projectSkeleton' :: Monad m => Proxy contextPredicate -> Proxy (be, res) -> (forall context. contextPredicate context => Proxy context -> Proxy be -> m res) -> m a
 
- project :: Projectible be a => Proxy be -> a -> WithExprContext [BeamSqlBackendExpressionSyntax be]
- reproject :: (BeamSqlBackend be, Projectible be a) => Proxy be -> (Int -> BeamSqlBackendExpressionSyntax be) -> a -> a
- tableFieldsToExpressions :: (BeamSqlBackend be, Beamable table) => TableSettings table -> Text -> table (QGenExpr ctxt be s)
- mkFieldsSkeleton :: (Projectible be res, MonadState Int m) => (Int -> m (WithExprContext (BeamSqlBackendExpressionSyntax' be))) -> m res
- mkFieldNames :: (BeamSqlBackend be, Projectible be res) => (Text -> BeamSqlBackendFieldNameSyntax be) -> (res, [Text])
- tableNameFromEntity :: forall name be (tbl :: (Type -> Type) -> Type). IsSql92TableNameSyntax name => DatabaseEntityDescriptor be (TableEntity tbl) -> name
- rescopeQ :: forall be (db :: (Type -> Type) -> Type) s res s'. QM be db s res -> QM be db s' res
Documentation
type ProjectibleInBackend be a = (Projectible be a, ProjectibleValue be a) Source #
type TablePrefix = Text Source #
data QF be (db :: (Type -> Type) -> Type) s next where Source #
Constructors
| QDistinct :: forall be r (db :: (Type -> Type) -> Type) s next. Projectible be r => (r -> WithExprContext (BeamSqlBackendSetQuantifierSyntax be)) -> QM be db s r -> (r -> next) -> QF be db s next | |
| QAll :: forall be r next (db :: (Type -> Type) -> Type) s. Projectible be r => (TablePrefix -> Text -> BeamSqlBackendFromSyntax be) -> (Text -> r) -> (r -> Maybe (WithExprContext (BeamSqlBackendExpressionSyntax be))) -> ((Text, r) -> next) -> QF be db s next | |
| QArbitraryJoin :: forall be r (db :: (Type -> Type) -> Type) s next. Projectible be r => QM be db (QNested s) r -> Text -> (BeamSqlBackendFromSyntax be -> BeamSqlBackendFromSyntax be -> Maybe (BeamSqlBackendExpressionSyntax be) -> BeamSqlBackendFromSyntax be) -> (r -> Maybe (WithExprContext (BeamSqlBackendExpressionSyntax be))) -> (r -> next) -> QF be db s next | |
| QTwoWayJoin :: forall be a b (db :: (Type -> Type) -> Type) s next. (Projectible be a, Projectible be b) => QM be db (QNested s) a -> QM be db (QNested s) b -> (BeamSqlBackendFromSyntax be -> BeamSqlBackendFromSyntax be -> Maybe (BeamSqlBackendExpressionSyntax be) -> BeamSqlBackendFromSyntax be) -> ((a, b) -> Maybe (WithExprContext (BeamSqlBackendExpressionSyntax be))) -> ((a, b) -> next) -> QF be db s next | |
| QSubSelect :: forall be r (db :: (Type -> Type) -> Type) s next. Projectible be r => QM be db (QNested s) r -> (r -> next) -> QF be db s next | |
| QGuard :: forall be next (db :: (Type -> Type) -> Type) s. WithExprContext (BeamSqlBackendExpressionSyntax be) -> next -> QF be db s next | |
| QLimit :: forall be r (db :: (Type -> Type) -> Type) s next. Projectible be r => Integer -> QM be db (QNested s) r -> (r -> next) -> QF be db s next | |
| QOffset :: forall be r (db :: (Type -> Type) -> Type) s next. Projectible be r => Integer -> QM be db (QNested s) r -> (r -> next) -> QF be db s next | |
| QSetOp :: forall be r (db :: (Type -> Type) -> Type) s next. Projectible be r => (BeamSqlBackendSelectTableSyntax be -> BeamSqlBackendSelectTableSyntax be -> BeamSqlBackendSelectTableSyntax be) -> QM be db (QNested s) r -> QM be db (QNested s) r -> (r -> next) -> QF be db s next | |
| QOrderBy :: forall be r (db :: (Type -> Type) -> Type) s next. Projectible be r => (r -> WithExprContext [BeamSqlBackendOrderingSyntax be]) -> QM be db (QNested s) r -> (r -> next) -> QF be db s next | |
| QWindowOver :: forall be window r a (db :: (Type -> Type) -> Type) s next. (ProjectibleWithPredicate WindowFrameContext be (WithExprContext (BeamSqlBackendWindowFrameSyntax' be)) window, Projectible be r, Projectible be a) => (r -> window) -> (r -> window -> a) -> QM be db (QNested s) r -> (a -> next) -> QF be db s next | |
| QAggregate :: forall be grouping a (db :: (Type -> Type) -> Type) s next. (Projectible be grouping, Projectible be a) => (a -> TablePrefix -> (Maybe (BeamSqlBackendGroupingSyntax be), grouping)) -> QM be db (QNested s) a -> (grouping -> next) -> QF be db s next | |
| QForceSelect :: forall be r (db :: (Type -> Type) -> Type) s next. Projectible be r => (r -> BeamSqlBackendSelectTableSyntax be -> [BeamSqlBackendOrderingSyntax be] -> Maybe Integer -> Maybe Integer -> BeamSqlBackendSelectSyntax be) -> QM be db (QNested s) r -> (r -> next) -> QF be db s next | 
newtype 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
 QExprs. syntax represents the SQL syntax that this query is building.
Constructors
| QField | |
| Fields 
 | |
Instances
newtype QAssignment be s Source #
Constructors
| QAssignment | |
| Fields | |
Instances
| Monoid (QAssignment be s) Source # | |
| Defined in Database.Beam.Query.Internal Methods mempty :: QAssignment be s # mappend :: QAssignment be s -> QAssignment be s -> QAssignment be s # mconcat :: [QAssignment be s] -> QAssignment be s # | |
| Semigroup (QAssignment be s) Source # | |
| Defined in Database.Beam.Query.Internal Methods (<>) :: 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 # | |
newtype QFieldAssignment be (tbl :: (Type -> Type) -> Type) a Source #
Constructors
| QFieldAssignment (forall s. tbl (QExpr be s) -> Maybe (QExpr be s a)) | 
QGenExpr type
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 Methods 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 Methods group_ :: QExpr be s a -> QGroupExpr be s a Source # | |
| type ContextName QGroupingContext Source # | |
| Defined in Database.Beam.Query.Internal | |
data QValueContext 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 Methods group_ :: tbl (QExpr be s) -> tbl (QGroupExpr be s) Source # | |
| (Table t, BeamSqlBackend be) => SqlJustable (t (QExpr be s)) (t (Nullable (QExpr 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 Methods just_ :: PrimaryKey t (QExpr be s) -> PrimaryKey t (Nullable (QExpr be s)) Source # | |
| QGroupable (QExpr be s a) (QGroupExpr be s a) Source # | 
 | 
| Defined in Database.Beam.Query.Aggregate Methods group_ :: QExpr be s a -> QGroupExpr be s a Source # | |
| BeamSqlBackend be => SqlJustable (QExpr be s a) (QExpr be s (Maybe 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 | |
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 QExprs 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).
Constructors
| QExpr (TablePrefix -> BeamSqlBackendExpressionSyntax be) | 
Instances
| (Beamable t, contextPredicate context) => ProjectibleWithPredicate contextPredicate be (WithExprContext (BeamSqlBackendExpressionSyntax' be)) (t (Nullable (QGenExpr context be s))) Source # | |
| Defined in Database.Beam.Query.Internal Methods project' :: Monad m => Proxy contextPredicate -> Proxy (be, WithExprContext (BeamSqlBackendExpressionSyntax' be)) -> (forall context0. contextPredicate context0 => Proxy context0 -> Proxy be -> WithExprContext (BeamSqlBackendExpressionSyntax' be) -> m (WithExprContext (BeamSqlBackendExpressionSyntax' be))) -> t (Nullable (QGenExpr context be s)) -> m (t (Nullable (QGenExpr context be s))) Source # projectSkeleton' :: Monad m => Proxy contextPredicate -> Proxy (be, WithExprContext (BeamSqlBackendExpressionSyntax' be)) -> (forall context0. contextPredicate context0 => Proxy context0 -> Proxy be -> m (WithExprContext (BeamSqlBackendExpressionSyntax' be))) -> m (t (Nullable (QGenExpr context be s))) Source # | |
| (Beamable t, contextPredicate context) => ProjectibleWithPredicate contextPredicate be (WithExprContext (BeamSqlBackendExpressionSyntax' be)) (t (QGenExpr context be s)) Source # | |
| Defined in Database.Beam.Query.Internal Methods project' :: Monad m => Proxy contextPredicate -> Proxy (be, WithExprContext (BeamSqlBackendExpressionSyntax' be)) -> (forall context0. contextPredicate context0 => Proxy context0 -> Proxy be -> WithExprContext (BeamSqlBackendExpressionSyntax' be) -> m (WithExprContext (BeamSqlBackendExpressionSyntax' be))) -> t (QGenExpr context be s) -> m (t (QGenExpr context be s)) Source # projectSkeleton' :: Monad m => Proxy contextPredicate -> Proxy (be, WithExprContext (BeamSqlBackendExpressionSyntax' be)) -> (forall context0. contextPredicate context0 => Proxy context0 -> Proxy be -> m (WithExprContext (BeamSqlBackendExpressionSyntax' be))) -> m (t (QGenExpr context be s)) Source # | |
| contextPredicate context => ProjectibleWithPredicate contextPredicate be (WithExprContext (BeamSqlBackendExpressionSyntax' be)) (QGenExpr context be s a) Source # | |
| Defined in Database.Beam.Query.Internal Methods project' :: Monad m => Proxy contextPredicate -> Proxy (be, WithExprContext (BeamSqlBackendExpressionSyntax' be)) -> (forall context0. contextPredicate context0 => Proxy context0 -> Proxy be -> WithExprContext (BeamSqlBackendExpressionSyntax' be) -> m (WithExprContext (BeamSqlBackendExpressionSyntax' be))) -> QGenExpr context be s a -> m (QGenExpr context be s a) Source # projectSkeleton' :: Monad m => Proxy contextPredicate -> Proxy (be, WithExprContext (BeamSqlBackendExpressionSyntax' be)) -> (forall context0. contextPredicate context0 => Proxy context0 -> Proxy be -> m (WithExprContext (BeamSqlBackendExpressionSyntax' be))) -> m (QGenExpr context be s a) Source # | |
| Beamable tbl => ThreadRewritable s (tbl (Nullable (QGenExpr ctxt syntax s))) Source # | |
| Defined in Database.Beam.Query.Internal Methods rewriteThread :: Proxy s' -> tbl (Nullable (QGenExpr ctxt syntax s)) -> WithRewrittenThread s s' (tbl (Nullable (QGenExpr ctxt syntax s))) Source # | |
| Beamable tbl => ThreadRewritable s (tbl (QGenExpr ctxt syntax s)) Source # | |
| Defined in Database.Beam.Query.Internal Methods rewriteThread :: Proxy s' -> tbl (QGenExpr ctxt syntax s) -> WithRewrittenThread s s' (tbl (QGenExpr ctxt syntax s)) Source # | |
| (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 Methods 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 # | |
| (TypeError ('Text "Missing mandatory sorting order. Use either 'asc_' or 'desc_' to specify sorting order.") :: Constraint) => SqlOrderable be (QGenExpr ctx be s a) Source # | |
| Defined in Database.Beam.Query.Combinators Methods makeSQLOrdering :: Proxy be -> QGenExpr ctx be s a -> [WithExprContext (BeamSqlBackendOrderingSyntax be)] | |
| ThreadRewritable s (QGenExpr ctxt syntax s a) Source # | |
| Defined in Database.Beam.Query.Internal Methods rewriteThread :: Proxy s' -> QGenExpr ctxt syntax s a -> WithRewrittenThread s s' (QGenExpr ctxt syntax s a) Source # | |
| BeamSqlBackend be => SqlDeconstructMaybe be (QGenExpr ctxt be s (Maybe x)) (QGenExpr ctxt be s x) s Source # | |
| Defined in Database.Beam.Query.Combinators Methods 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 # | |
| (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 | |
| Beamable tbl => ContextRewritable (tbl (Nullable (QGenExpr old syntax s))) Source # | |
| Defined in Database.Beam.Query.Internal Methods rewriteContext :: Proxy ctxt -> tbl (Nullable (QGenExpr old syntax s)) -> WithRewrittenContext (tbl (Nullable (QGenExpr old syntax s))) ctxt Source # | |
| Beamable tbl => ContextRewritable (tbl (QGenExpr old syntax s)) Source # | |
| Defined in Database.Beam.Query.Internal Methods rewriteContext :: Proxy ctxt -> tbl (QGenExpr old syntax s) -> WithRewrittenContext (tbl (QGenExpr old syntax s)) ctxt 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 Methods group_ :: tbl (QExpr be s) -> tbl (QGroupExpr be s) Source # | |
| (Table t, BeamSqlBackend be) => SqlJustable (t (QExpr be s)) (t (Nullable (QExpr 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 Methods just_ :: PrimaryKey t (QExpr be s) -> PrimaryKey t (Nullable (QExpr be s)) Source # | |
| (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 Methods (==.) :: 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 Methods (==.) :: 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 # | |
| (HasSqlInTable be, Beamable table) => SqlIn (QGenExpr context be s) (table (QGenExpr context be s)) Source # | |
| QGroupable (QExpr be s a) (QGroupExpr be s a) Source # | 
 | 
| Defined in Database.Beam.Query.Aggregate Methods group_ :: QExpr be s a -> QGroupExpr be s a Source # | |
| BeamSqlBackend be => SqlJustable (QExpr be s a) (QExpr be s (Maybe a)) 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 | |
| BeamSqlBackend be => SqlOrdQuantified (QGenExpr context be s) (QQuantified be s a) (QGenExpr context be s a) Source # | |
| Defined in Database.Beam.Query.Ord Methods (<*.) :: 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, 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 Methods (==.) :: 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 # | |
| BeamSqlBackend be => SqlIn (QGenExpr context be s) (QGenExpr context be s a) Source # | |
| BeamSqlBackend be => SqlOrd (QGenExpr context be s) (QGenExpr context be s a) Source # | |
| Defined in Database.Beam.Query.Ord Methods (<.) :: 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 # | |
| Retaggable (QGenExpr ctxt expr s) (QGenExpr ctxt expr s t) Source # | |
| (BeamSqlBackendCanSerialize be a, BeamSqlBackend be) => SqlValable (QGenExpr ctxt be s a) Source # | |
| Defined in Database.Beam.Query.Combinators | |
| ContextRewritable (QGenExpr old syntax s a) Source # | |
| Defined in Database.Beam.Query.Internal Methods rewriteContext :: Proxy ctxt -> QGenExpr old syntax s a -> WithRewrittenContext (QGenExpr old syntax s a) ctxt Source # | |
| (BeamSqlBackend backend, BeamSqlBackendCanSerialize backend [Char]) => IsString (QGenExpr context backend s Text) Source # | |
| Defined in Database.Beam.Query.Internal Methods fromString :: String -> QGenExpr context backend s Text # | |
| (Num a, BeamSqlBackend be, BeamSqlBackendCanSerialize be a) => Num (QGenExpr context be s a) Source # | |
| Defined in Database.Beam.Query.Internal Methods (+) :: QGenExpr context be s a -> QGenExpr context be s a -> QGenExpr context be s a # (-) :: QGenExpr context be s a -> QGenExpr context be s a -> QGenExpr context be s a # (*) :: QGenExpr context be s a -> QGenExpr context be s a -> QGenExpr context be s a # negate :: QGenExpr context be s a -> QGenExpr context be s a # abs :: QGenExpr context be s a -> QGenExpr context be s a # signum :: QGenExpr context be s a -> QGenExpr context be s a # fromInteger :: Integer -> QGenExpr context be s a # | |
| (Fractional a, BeamSqlBackend be, BeamSqlBackendCanSerialize be a) => Fractional (QGenExpr context be s a) Source # | |
| BeamSqlBackend be => Eq (QGenExpr context be s t) Source # | |
| type WithRewrittenThread s s' (tbl (Nullable (QGenExpr ctxt syntax s))) Source # | |
| Defined in Database.Beam.Query.Internal type WithRewrittenThread s s' (tbl (Nullable (QGenExpr ctxt syntax s))) = tbl (Nullable (QGenExpr ctxt syntax s')) | |
| type WithRewrittenThread s s' (tbl (QGenExpr ctxt syntax s)) Source # | |
| Defined in Database.Beam.Query.Internal | |
| type WithRewrittenThread s s' (QGenExpr ctxt syntax s a) Source # | |
| Defined in Database.Beam.Query.Internal | |
| type Retag tag (QGenExpr ctxt expr s t) Source # | |
| Defined in Database.Beam.Query.Internal | |
| type HaskellLiteralForQExpr (table (QGenExpr context be s)) Source # | |
| Defined in Database.Beam.Query.Combinators | |
| type QExprToField (table (Nullable (QGenExpr context syntax s))) Source # | |
| Defined in Database.Beam.Query.Types | |
| type QExprToField (table (QGenExpr context syntax s)) Source # | |
| Defined in Database.Beam.Query.Types | |
| type QExprToIdentity (table (QGenExpr context syntax s)) Source # | |
| Defined in Database.Beam.Query.Types | |
| type WithRewrittenContext (tbl (Nullable (QGenExpr old syntax s))) ctxt Source # | |
| Defined in Database.Beam.Query.Internal type WithRewrittenContext (tbl (Nullable (QGenExpr old syntax s))) ctxt = tbl (Nullable (QGenExpr ctxt syntax s)) | |
| type WithRewrittenContext (tbl (QGenExpr old syntax s)) ctxt Source # | |
| Defined in Database.Beam.Query.Internal | |
| type HaskellLiteralForQExpr (QGenExpr context be s a) Source # | |
| Defined in Database.Beam.Query.Combinators | |
| type QExprToField (QGenExpr ctxt syntax s a) Source # | |
| Defined in Database.Beam.Query.Types | |
| type QExprToIdentity (QGenExpr context syntax s a) Source # | |
| Defined in Database.Beam.Query.Types | |
| type WithRewrittenContext (QGenExpr old syntax s a) ctxt Source # | |
| Defined in Database.Beam.Query.Internal | |
Constructors
| QOrd (TablePrefix -> BeamSqlBackendOrderingSyntax be) | 
Instances
| SqlOrderable be (QOrd be s a) Source # | |
| Defined in Database.Beam.Query.Combinators Methods makeSQLOrdering :: Proxy be -> QOrd be s a -> [WithExprContext (BeamSqlBackendOrderingSyntax be)] | |
type WithExprContext a = TablePrefix -> a Source #
type QAgg = QGenExpr QAggregateContext Source #
type QWindowExpr = QGenExpr QWindowingContext Source #
type QGroupExpr = QGenExpr QGroupingContext Source #
Constructors
| QWindow (WithExprContext (BeamSqlBackendWindowFrameSyntax be)) | 
Instances
| contextPredicate QWindowFrameContext => ProjectibleWithPredicate contextPredicate be (WithExprContext (BeamSqlBackendWindowFrameSyntax' be)) (QWindow be s) Source # | |
| Defined in Database.Beam.Query.Internal Methods 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 # | |
newtype QFrameBounds be Source #
Constructors
| QFrameBounds (Maybe (BeamSqlBackendWindowFrameBoundsSyntax be)) | 
newtype QFrameBound be Source #
Constructors
| QFrameBound (BeamSqlBackendWindowFrameBoundSyntax be) | 
qBinOpE :: BeamSqlBackend be => (BeamSqlBackendExpressionSyntax be -> BeamSqlBackendExpressionSyntax be -> BeamSqlBackendExpressionSyntax be) -> QGenExpr context be s a -> QGenExpr context be s b -> QGenExpr context be s c Source #
unsafeRetype :: QGenExpr ctxt be s a -> QGenExpr ctxt be s a' Source #
Sql Projections
class Typeable context => AggregateContext context Source #
Typeclass for all haskell data types that can be used to create a projection in a SQL select statement. This includes all tables as well as all tuple classes. Projections are only defined on tuples up to size 5. If you need more, follow the implementations here.
Instances
| (IsAggregateContext a, Typeable a) => AggregateContext a Source # | |
| Defined in Database.Beam.Query.Internal | |
type family ContextName a :: Symbol Source #
Instances
| type ContextName QAggregateContext Source # | |
| Defined in Database.Beam.Query.Internal | |
| type ContextName QGroupingContext Source # | |
| Defined in Database.Beam.Query.Internal | |
| type ContextName QValueContext Source # | |
| Defined in Database.Beam.Query.Internal | |
| type ContextName QWindowFrameContext Source # | |
| Defined in Database.Beam.Query.Internal | |
| type ContextName QWindowingContext Source # | |
| Defined in Database.Beam.Query.Internal | |
type family IsAggregateContext a where ... Source #
Equations
| IsAggregateContext QAggregateContext = () | |
| IsAggregateContext QGroupingContext = () | |
| IsAggregateContext a = TypeError (('Text "Non-aggregate expression where aggregate expected." ':$$: (('Text "Got " ':<>: 'Text (ContextName a)) ':<>: 'Text ". Expected an aggregate or a grouping")) ':$$: AggregateContextSuggestion a) :: Constraint | 
type family AggregateContextSuggestion a :: ErrorMessage where ... Source #
Equations
| AggregateContextSuggestion QValueContext = 'Text "Perhaps you forgot to wrap a value expression with 'group_'" | |
| AggregateContextSuggestion QWindowingContext = 'Text "Perhaps you meant to use 'window_' instead of 'aggregate_'" | |
| AggregateContextSuggestion b = 'Text "" | 
class Typeable context => ValueContext context Source #
Instances
| (IsValueContext a, Typeable a, a ~ QValueContext) => ValueContext a Source # | |
| Defined in Database.Beam.Query.Internal | |
class Typeable context => WindowFrameContext context Source #
Instances
| (Typeable context, IsWindowFrameContext context, context ~ QWindowFrameContext) => WindowFrameContext context Source # | |
| Defined in Database.Beam.Query.Internal | |
type family IsWindowFrameContext a where ... Source #
Equations
| IsWindowFrameContext QWindowFrameContext = () | |
| IsWindowFrameContext a = TypeError ('Text "Expected window frame." ':$$: (('Text "Got " ':<>: 'Text (ContextName a)) ':<>: 'Text ". Expected a window frame")) :: Constraint | 
type family IsValueContext a where ... Source #
Equations
| IsValueContext QValueContext = () | |
| IsValueContext a = TypeError (('Text "Non-scalar context in projection" ':$$: (('Text "Got " ':<>: 'Text (ContextName a)) ':<>: 'Text ". Expected a value")) ':$$: ValueContextSuggestion a) :: Constraint | 
type family ValueContextSuggestion a :: ErrorMessage where ... Source #
Equations
| ValueContextSuggestion QWindowingContext = 'Text "Use 'window_' to projecct aggregate expressions to the value level" | |
| ValueContextSuggestion QAggregateContext = 'Text "Aggregate functions and groupings cannot be contained in value expressions." ':$$: 'Text "Use 'aggregate_' to compute aggregations at the value level." | |
| ValueContextSuggestion QGroupingContext = ValueContextSuggestion QAggregateContext | |
| ValueContextSuggestion _1 = 'Text "" | 
type Projectible be = ProjectibleWithPredicate AnyType be (WithExprContext (BeamSqlBackendExpressionSyntax' be)) Source #
type ProjectibleValue be = ProjectibleWithPredicate ValueContext be (WithExprContext (BeamSqlBackendExpressionSyntax' be)) Source #
class ThreadRewritable s a | a -> s where Source #
Associated Types
type WithRewrittenThread s s' a Source #
Methods
rewriteThread :: Proxy s' -> a -> WithRewrittenThread s s' a Source #
Instances
class ContextRewritable a where Source #
Associated Types
type WithRewrittenContext a ctxt Source #
Methods
rewriteContext :: Proxy ctxt -> a -> WithRewrittenContext a ctxt Source #
Instances
newtype BeamSqlBackendExpressionSyntax' be Source #
Constructors
| BeamSqlBackendExpressionSyntax' | |
Instances
newtype BeamSqlBackendWindowFrameSyntax' be Source #
Constructors
| BeamSqlBackendWindowFrameSyntax' | |
Instances
| contextPredicate QWindowFrameContext => ProjectibleWithPredicate contextPredicate be (WithExprContext (BeamSqlBackendWindowFrameSyntax' be)) (QWindow be s) Source # | |
| Defined in Database.Beam.Query.Internal Methods 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 # | |
class ProjectibleWithPredicate (contextPredicate :: Type -> Constraint) be res a | a -> be where Source #
Methods
project' :: Monad m => Proxy contextPredicate -> Proxy (be, res) -> (forall context. contextPredicate context => Proxy context -> Proxy be -> res -> m res) -> a -> m a Source #
projectSkeleton' :: Monad m => Proxy contextPredicate -> Proxy (be, res) -> (forall context. contextPredicate context => Proxy context -> Proxy be -> m res) -> m a Source #
Instances
| Beamable t => ProjectibleWithPredicate AnyType () Text (t (Nullable (QField s))) Source # | |
| Defined in Database.Beam.Query.Internal Methods project' :: Monad m => Proxy AnyType -> Proxy ((), Text) -> (forall context. AnyType context => Proxy context -> Proxy () -> Text -> m Text) -> t (Nullable (QField s)) -> m (t (Nullable (QField s))) Source # projectSkeleton' :: Monad m => Proxy AnyType -> Proxy ((), Text) -> (forall context. AnyType context => Proxy context -> Proxy () -> m Text) -> m (t (Nullable (QField s))) Source # | |
| Beamable t => ProjectibleWithPredicate AnyType () Text (t (Nullable (Const Text :: Type -> Type))) Source # | |
| Defined in Database.Beam.Query.Internal Methods project' :: Monad m => Proxy AnyType -> Proxy ((), Text) -> (forall context. AnyType context => Proxy context -> Proxy () -> Text -> m Text) -> t (Nullable (Const Text :: Type -> Type)) -> m (t (Nullable (Const Text :: Type -> Type))) Source # projectSkeleton' :: Monad m => Proxy AnyType -> Proxy ((), Text) -> (forall context. AnyType context => Proxy context -> Proxy () -> m Text) -> m (t (Nullable (Const Text :: Type -> Type))) Source # | |
| Beamable t => ProjectibleWithPredicate AnyType () Text (t (QField s)) Source # | |
| Defined in Database.Beam.Query.Internal Methods project' :: Monad m => Proxy AnyType -> Proxy ((), Text) -> (forall context. AnyType context => Proxy context -> Proxy () -> Text -> m Text) -> t (QField s) -> m (t (QField s)) Source # projectSkeleton' :: Monad m => Proxy AnyType -> Proxy ((), Text) -> (forall context. AnyType context => Proxy context -> Proxy () -> m Text) -> m (t (QField s)) Source # | |
| Beamable t => ProjectibleWithPredicate AnyType () res (t (Const res :: Type -> Type)) Source # | |
| Defined in Database.Beam.Query.Internal Methods project' :: Monad m => Proxy AnyType -> Proxy ((), res) -> (forall context. AnyType context => Proxy context -> Proxy () -> res -> m res) -> t (Const res :: Type -> Type) -> m (t (Const res :: Type -> Type)) Source # projectSkeleton' :: Monad m => Proxy AnyType -> Proxy ((), res) -> (forall context. AnyType context => Proxy context -> Proxy () -> m res) -> m (t (Const res :: Type -> Type)) Source # | |
| ProjectibleWithPredicate AnyType () Text (QField s a) Source # | |
| Defined in Database.Beam.Query.Internal Methods project' :: Monad m => Proxy AnyType -> Proxy ((), Text) -> (forall context. AnyType context => Proxy context -> Proxy () -> Text -> m Text) -> QField s a -> m (QField s a) Source # projectSkeleton' :: Monad m => Proxy AnyType -> Proxy ((), Text) -> (forall context. AnyType context => Proxy context -> Proxy () -> m Text) -> m (QField s a) Source # | |
| (ProjectibleWithPredicate contextPredicate be res a, KnownNat n) => ProjectibleWithPredicate contextPredicate be res (Vector n a) Source # | |
| Defined in Database.Beam.Query.Internal Methods project' :: Monad m => Proxy contextPredicate -> Proxy (be, res) -> (forall context. contextPredicate context => Proxy context -> Proxy be -> res -> m res) -> Vector n a -> m (Vector n a) Source # projectSkeleton' :: Monad m => Proxy contextPredicate -> Proxy (be, res) -> (forall context. contextPredicate context => Proxy context -> Proxy be -> m res) -> m (Vector n a) Source # | |
| (ProjectibleWithPredicate contextPredicate be res a, ProjectibleWithPredicate contextPredicate be res b) => ProjectibleWithPredicate contextPredicate be res (a, b) Source # | |
| Defined in Database.Beam.Query.Internal Methods project' :: Monad m => Proxy contextPredicate -> Proxy (be, res) -> (forall context. contextPredicate context => Proxy context -> Proxy be -> res -> m res) -> (a, b) -> m (a, b) Source # projectSkeleton' :: Monad m => Proxy contextPredicate -> Proxy (be, res) -> (forall context. contextPredicate context => Proxy context -> Proxy be -> m res) -> m (a, b) Source # | |
| ProjectibleWithPredicate AnyType () res (Const res a) Source # | |
| Defined in Database.Beam.Query.Internal Methods project' :: Monad m => Proxy AnyType -> Proxy ((), res) -> (forall context. AnyType context => Proxy context -> Proxy () -> res -> m res) -> Const res a -> m (Const res a) Source # projectSkeleton' :: Monad m => Proxy AnyType -> Proxy ((), res) -> (forall context. AnyType context => Proxy context -> Proxy () -> m res) -> m (Const res a) Source # | |
| (ProjectibleWithPredicate contextPredicate be res a, ProjectibleWithPredicate contextPredicate be res b, ProjectibleWithPredicate contextPredicate be res c) => ProjectibleWithPredicate contextPredicate be res (a, b, c) Source # | |
| Defined in Database.Beam.Query.Internal Methods project' :: Monad m => Proxy contextPredicate -> Proxy (be, res) -> (forall context. contextPredicate context => Proxy context -> Proxy be -> res -> m res) -> (a, b, c) -> m (a, b, c) Source # projectSkeleton' :: Monad m => Proxy contextPredicate -> Proxy (be, res) -> (forall context. contextPredicate context => Proxy context -> Proxy be -> m res) -> m (a, b, c) Source # | |
| (ProjectibleWithPredicate contextPredicate be res a, ProjectibleWithPredicate contextPredicate be res b, ProjectibleWithPredicate contextPredicate be res c, ProjectibleWithPredicate contextPredicate be res d) => ProjectibleWithPredicate contextPredicate be res (a, b, c, d) Source # | |
| Defined in Database.Beam.Query.Internal Methods project' :: Monad m => Proxy contextPredicate -> Proxy (be, res) -> (forall context. contextPredicate context => Proxy context -> Proxy be -> res -> m res) -> (a, b, c, d) -> m (a, b, c, d) Source # projectSkeleton' :: Monad m => Proxy contextPredicate -> Proxy (be, res) -> (forall context. contextPredicate context => Proxy context -> Proxy be -> m res) -> m (a, b, c, d) Source # | |
| (ProjectibleWithPredicate contextPredicate be res a, ProjectibleWithPredicate contextPredicate be res b, ProjectibleWithPredicate contextPredicate be res c, ProjectibleWithPredicate contextPredicate be res d, ProjectibleWithPredicate contextPredicate be res e) => ProjectibleWithPredicate contextPredicate be res (a, b, c, d, e) Source # | |
| Defined in Database.Beam.Query.Internal Methods project' :: Monad m => Proxy contextPredicate -> Proxy (be, res) -> (forall context. contextPredicate context => Proxy context -> Proxy be -> res -> m res) -> (a, b, c, d, e) -> m (a, b, c, d, e) Source # projectSkeleton' :: Monad m => Proxy contextPredicate -> Proxy (be, res) -> (forall context. contextPredicate context => Proxy context -> Proxy be -> m res) -> m (a, b, c, d, e) Source # | |
| (ProjectibleWithPredicate contextPredicate be res a, ProjectibleWithPredicate contextPredicate be res b, ProjectibleWithPredicate contextPredicate be res c, ProjectibleWithPredicate contextPredicate be res d, ProjectibleWithPredicate contextPredicate be res e, ProjectibleWithPredicate contextPredicate be res f) => ProjectibleWithPredicate contextPredicate be res (a, b, c, d, e, f) Source # | |
| Defined in Database.Beam.Query.Internal Methods project' :: Monad m => Proxy contextPredicate -> Proxy (be, res) -> (forall context. contextPredicate context => Proxy context -> Proxy be -> res -> m res) -> (a, b, c, d, e, f) -> m (a, b, c, d, e, f) Source # projectSkeleton' :: Monad m => Proxy contextPredicate -> Proxy (be, res) -> (forall context. contextPredicate context => Proxy context -> Proxy be -> m res) -> m (a, b, c, d, e, f) Source # | |
| (ProjectibleWithPredicate contextPredicate be res a, ProjectibleWithPredicate contextPredicate be res b, ProjectibleWithPredicate contextPredicate be res c, ProjectibleWithPredicate contextPredicate be res d, ProjectibleWithPredicate contextPredicate be res e, ProjectibleWithPredicate contextPredicate be res f, ProjectibleWithPredicate contextPredicate be res g) => ProjectibleWithPredicate contextPredicate be res (a, b, c, d, e, f, g) Source # | |
| Defined in Database.Beam.Query.Internal Methods project' :: Monad m => Proxy contextPredicate -> Proxy (be, res) -> (forall context. contextPredicate context => Proxy context -> Proxy be -> res -> m res) -> (a, b, c, d, e, f, g) -> m (a, b, c, d, e, f, g) Source # projectSkeleton' :: Monad m => Proxy contextPredicate -> Proxy (be, res) -> (forall context. contextPredicate context => Proxy context -> Proxy be -> m res) -> m (a, b, c, d, e, f, g) Source # | |
| (ProjectibleWithPredicate contextPredicate be res a, ProjectibleWithPredicate contextPredicate be res b, ProjectibleWithPredicate contextPredicate be res c, ProjectibleWithPredicate contextPredicate be res d, ProjectibleWithPredicate contextPredicate be res e, ProjectibleWithPredicate contextPredicate be res f, ProjectibleWithPredicate contextPredicate be res g, ProjectibleWithPredicate contextPredicate be res h) => ProjectibleWithPredicate contextPredicate be res (a, b, c, d, e, f, g, h) Source # | |
| Defined in Database.Beam.Query.Internal Methods project' :: Monad m => Proxy contextPredicate -> Proxy (be, res) -> (forall context. contextPredicate context => Proxy context -> Proxy be -> res -> m res) -> (a, b, c, d, e, f, g, h) -> m (a, b, c, d, e, f, g, h) Source # projectSkeleton' :: Monad m => Proxy contextPredicate -> Proxy (be, res) -> (forall context. contextPredicate context => Proxy context -> Proxy be -> m res) -> m (a, b, c, d, e, f, g, h) Source # | |
| (Beamable t, contextPredicate context) => ProjectibleWithPredicate contextPredicate be (WithExprContext (BeamSqlBackendExpressionSyntax' be)) (t (Nullable (QGenExpr context be s))) Source # | |
| Defined in Database.Beam.Query.Internal Methods project' :: Monad m => Proxy contextPredicate -> Proxy (be, WithExprContext (BeamSqlBackendExpressionSyntax' be)) -> (forall context0. contextPredicate context0 => Proxy context0 -> Proxy be -> WithExprContext (BeamSqlBackendExpressionSyntax' be) -> m (WithExprContext (BeamSqlBackendExpressionSyntax' be))) -> t (Nullable (QGenExpr context be s)) -> m (t (Nullable (QGenExpr context be s))) Source # projectSkeleton' :: Monad m => Proxy contextPredicate -> Proxy (be, WithExprContext (BeamSqlBackendExpressionSyntax' be)) -> (forall context0. contextPredicate context0 => Proxy context0 -> Proxy be -> m (WithExprContext (BeamSqlBackendExpressionSyntax' be))) -> m (t (Nullable (QGenExpr context be s))) Source # | |
| (Beamable t, contextPredicate context) => ProjectibleWithPredicate contextPredicate be (WithExprContext (BeamSqlBackendExpressionSyntax' be)) (t (QGenExpr context be s)) Source # | |
| Defined in Database.Beam.Query.Internal Methods project' :: Monad m => Proxy contextPredicate -> Proxy (be, WithExprContext (BeamSqlBackendExpressionSyntax' be)) -> (forall context0. contextPredicate context0 => Proxy context0 -> Proxy be -> WithExprContext (BeamSqlBackendExpressionSyntax' be) -> m (WithExprContext (BeamSqlBackendExpressionSyntax' be))) -> t (QGenExpr context be s) -> m (t (QGenExpr context be s)) Source # projectSkeleton' :: Monad m => Proxy contextPredicate -> Proxy (be, WithExprContext (BeamSqlBackendExpressionSyntax' be)) -> (forall context0. contextPredicate context0 => Proxy context0 -> Proxy be -> m (WithExprContext (BeamSqlBackendExpressionSyntax' be))) -> m (t (QGenExpr context be s)) Source # | |
| contextPredicate QWindowFrameContext => ProjectibleWithPredicate contextPredicate be (WithExprContext (BeamSqlBackendWindowFrameSyntax' be)) (QWindow be s) Source # | |
| Defined in Database.Beam.Query.Internal Methods 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 # | |
| contextPredicate context => ProjectibleWithPredicate contextPredicate be (WithExprContext (BeamSqlBackendExpressionSyntax' be)) (QGenExpr context be s a) Source # | |
| Defined in Database.Beam.Query.Internal Methods project' :: Monad m => Proxy contextPredicate -> Proxy (be, WithExprContext (BeamSqlBackendExpressionSyntax' be)) -> (forall context0. contextPredicate context0 => Proxy context0 -> Proxy be -> WithExprContext (BeamSqlBackendExpressionSyntax' be) -> m (WithExprContext (BeamSqlBackendExpressionSyntax' be))) -> QGenExpr context be s a -> m (QGenExpr context be s a) Source # projectSkeleton' :: Monad m => Proxy contextPredicate -> Proxy (be, WithExprContext (BeamSqlBackendExpressionSyntax' be)) -> (forall context0. contextPredicate context0 => Proxy context0 -> Proxy be -> m (WithExprContext (BeamSqlBackendExpressionSyntax' be))) -> m (QGenExpr context be s a) Source # | |
project :: Projectible be a => Proxy be -> a -> WithExprContext [BeamSqlBackendExpressionSyntax be] Source #
reproject :: (BeamSqlBackend be, Projectible be a) => Proxy be -> (Int -> BeamSqlBackendExpressionSyntax be) -> a -> a Source #
tableFieldsToExpressions :: (BeamSqlBackend be, Beamable table) => TableSettings table -> Text -> table (QGenExpr ctxt be s) Source #
suitable as argument to QAll in the case of a table result
mkFieldsSkeleton :: (Projectible be res, MonadState Int m) => (Int -> m (WithExprContext (BeamSqlBackendExpressionSyntax' be))) -> m res Source #
mkFieldNames :: (BeamSqlBackend be, Projectible be res) => (Text -> BeamSqlBackendFieldNameSyntax be) -> (res, [Text]) Source #
tableNameFromEntity :: forall name be (tbl :: (Type -> Type) -> Type). IsSql92TableNameSyntax name => DatabaseEntityDescriptor be (TableEntity tbl) -> name Source #