Safe Haskell | None |
---|---|
Language | Haskell2010 |
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 :: Projectible be r => (r -> WithExprContext (BeamSqlBackendSetQuantifierSyntax be)) -> QM be db s r -> (r -> next) -> QF be db s next
- QAll :: Projectible be r => (TablePrefix -> Text -> BeamSqlBackendFromSyntax be) -> (Text -> r) -> (r -> Maybe (WithExprContext (BeamSqlBackendExpressionSyntax be))) -> ((Text, r) -> next) -> QF be db s next
- QArbitraryJoin :: Projectible be r => QM be db (QNested s) r -> (BeamSqlBackendFromSyntax be -> BeamSqlBackendFromSyntax be -> Maybe (BeamSqlBackendExpressionSyntax be) -> BeamSqlBackendFromSyntax be) -> (r -> Maybe (WithExprContext (BeamSqlBackendExpressionSyntax be))) -> (r -> next) -> QF be db s next
- QTwoWayJoin :: (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 :: Projectible be r => QM be db (QNested s) r -> (r -> next) -> QF be db s next
- QGuard :: WithExprContext (BeamSqlBackendExpressionSyntax be) -> next -> QF be db s next
- QLimit :: Projectible be r => Integer -> QM be db (QNested s) r -> (r -> next) -> QF be db s next
- QOffset :: Projectible be r => Integer -> QM be db (QNested s) r -> (r -> next) -> QF be db s next
- QSetOp :: 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 :: Projectible be r => (r -> WithExprContext [BeamSqlBackendOrderingSyntax be]) -> QM be db (QNested s) r -> (r -> next) -> QF be db s next
- QWindowOver :: (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 :: (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 :: 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 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 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 :: Constraint where ...
- type family AggregateContextSuggestion a :: ErrorMessage where ...
- class Typeable context => ValueContext context
- class Typeable context => WindowFrameContext context
- type family IsWindowFrameContext a :: Constraint where ...
- class AnyType a
- type family IsValueContext a :: Constraint 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 :: Type) (a :: Type) | a -> s where
- type WithRewrittenThread s (s' :: Type) a :: Type
- rewriteThread :: Proxy s' -> a -> WithRewrittenThread s s' a
- class ContextRewritable a where
- type WithRewrittenContext a ctxt :: Type
- 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 :: forall be a. Projectible be a => Proxy be -> a -> WithExprContext [BeamSqlBackendExpressionSyntax be]
- reproject :: forall be a. (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 :: forall be res m. (Projectible be res, MonadState Int m) => (Int -> m (WithExprContext (BeamSqlBackendExpressionSyntax' be))) -> m res
- mkFieldNames :: forall be res. (BeamSqlBackend be, Projectible be res) => (Text -> BeamSqlBackendFieldNameSyntax be) -> (res, [Text])
- tableNameFromEntity :: IsSql92TableNameSyntax name => DatabaseEntityDescriptor be (TableEntity tbl) -> name
- rescopeQ :: 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 #
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
QExpr
s. syntax
represents the SQL syntax that this query is building.
QField | |
|
Instances
newtype 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 # |
newtype QFieldAssignment be tbl a Source #
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 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 |
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 QExpr
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
Instances
SqlOrderable be (QOrd be s a) Source # | |
Defined in Database.Beam.Query.Combinators 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 #
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 # |
newtype QFrameBounds be Source #
newtype QFrameBound be Source #
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 QWindowFrameContext Source # | |
Defined in Database.Beam.Query.Internal | |
type ContextName QWindowingContext Source # | |
Defined in Database.Beam.Query.Internal | |
type ContextName QValueContext Source # | |
Defined in Database.Beam.Query.Internal | |
type ContextName QGroupingContext Source # | |
Defined in Database.Beam.Query.Internal | |
type ContextName QAggregateContext Source # | |
Defined in Database.Beam.Query.Internal |
type family IsAggregateContext a :: Constraint where ... Source #
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) |
type family AggregateContextSuggestion a :: ErrorMessage where ... Source #
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 :: Constraint where ... Source #
IsWindowFrameContext QWindowFrameContext = () | |
IsWindowFrameContext a = TypeError ('Text "Expected window frame." :$$: (('Text "Got " :<>: 'Text (ContextName a)) :<>: 'Text ". Expected a window frame")) |
Instances
AnyType a Source # | |
Defined in Database.Beam.Query.Internal | |
Beamable t => ProjectibleWithPredicate AnyType () res (t (Const res :: Type -> Type)) Source # | |
Defined in Database.Beam.Query.Internal project' :: Monad m => Proxy AnyType -> Proxy ((), res) -> (forall context. AnyType context => Proxy context -> Proxy () -> res -> m res) -> t (Const res) -> m (t (Const res)) Source # projectSkeleton' :: Monad m => Proxy AnyType -> Proxy ((), res) -> (forall context. AnyType context => Proxy context -> Proxy () -> m res) -> m (t (Const res)) Source # | |
Beamable t => ProjectibleWithPredicate AnyType () Text (t (Nullable (Const Text :: Type -> Type))) Source # | |
Defined in Database.Beam.Query.Internal project' :: Monad m => Proxy AnyType -> Proxy ((), Text) -> (forall context. AnyType context => Proxy context -> Proxy () -> Text -> m Text) -> t (Nullable (Const Text)) -> m (t (Nullable (Const Text))) Source # projectSkeleton' :: Monad m => Proxy AnyType -> Proxy ((), Text) -> (forall context. AnyType context => Proxy context -> Proxy () -> m Text) -> m (t (Nullable (Const Text))) Source # | |
Beamable t => ProjectibleWithPredicate AnyType () Text (t (Nullable (QField s))) Source # | |
Defined in Database.Beam.Query.Internal 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 (QField s)) Source # | |
Defined in Database.Beam.Query.Internal 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 # | |
ProjectibleWithPredicate AnyType () Text (QField s a) Source # | |
Defined in Database.Beam.Query.Internal 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 AnyType () res (Const res a) Source # | |
Defined in Database.Beam.Query.Internal 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 # |
type family IsValueContext a :: Constraint where ... Source #
IsValueContext QValueContext = () | |
IsValueContext a = TypeError (('Text "Non-scalar context in projection" :$$: (('Text "Got " :<>: 'Text (ContextName a)) :<>: 'Text ". Expected a value")) :$$: ValueContextSuggestion a) |
type family ValueContextSuggestion a :: ErrorMessage where ... Source #
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 _ = 'Text "" |
type Projectible be = ProjectibleWithPredicate AnyType be (WithExprContext (BeamSqlBackendExpressionSyntax' be)) Source #
type ProjectibleValue be = ProjectibleWithPredicate ValueContext be (WithExprContext (BeamSqlBackendExpressionSyntax' be)) Source #
class ThreadRewritable (s :: Type) (a :: Type) | a -> s where Source #
type WithRewrittenThread s (s' :: Type) a :: Type Source #
rewriteThread :: Proxy s' -> a -> WithRewrittenThread s s' a Source #
Instances
class ContextRewritable a where Source #
type WithRewrittenContext a ctxt :: Type Source #
rewriteContext :: Proxy ctxt -> a -> WithRewrittenContext a ctxt Source #
Instances
newtype BeamSqlBackendExpressionSyntax' be Source #
Instances
newtype BeamSqlBackendWindowFrameSyntax' 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 # |
class ProjectibleWithPredicate (contextPredicate :: Type -> Constraint) be res a | a -> be where Source #
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 () res (t (Const res :: Type -> Type)) Source # | |
Defined in Database.Beam.Query.Internal project' :: Monad m => Proxy AnyType -> Proxy ((), res) -> (forall context. AnyType context => Proxy context -> Proxy () -> res -> m res) -> t (Const res) -> m (t (Const res)) Source # projectSkeleton' :: Monad m => Proxy AnyType -> Proxy ((), res) -> (forall context. AnyType context => Proxy context -> Proxy () -> m res) -> m (t (Const res)) Source # | |
Beamable t => ProjectibleWithPredicate AnyType () Text (t (Nullable (Const Text :: Type -> Type))) Source # | |
Defined in Database.Beam.Query.Internal project' :: Monad m => Proxy AnyType -> Proxy ((), Text) -> (forall context. AnyType context => Proxy context -> Proxy () -> Text -> m Text) -> t (Nullable (Const Text)) -> m (t (Nullable (Const Text))) Source # projectSkeleton' :: Monad m => Proxy AnyType -> Proxy ((), Text) -> (forall context. AnyType context => Proxy context -> Proxy () -> m Text) -> m (t (Nullable (Const Text))) Source # | |
Beamable t => ProjectibleWithPredicate AnyType () Text (t (Nullable (QField s))) Source # | |
Defined in Database.Beam.Query.Internal 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 (QField s)) Source # | |
Defined in Database.Beam.Query.Internal 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 # | |
(ProjectibleWithPredicate contextPredicate be res a, ProjectibleWithPredicate contextPredicate be res b) => ProjectibleWithPredicate contextPredicate be res (a, b) Source # | |
Defined in Database.Beam.Query.Internal 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 contextPredicate be res a, KnownNat n) => ProjectibleWithPredicate contextPredicate be res (Vector n a) Source # | |
Defined in Database.Beam.Query.Internal 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 AnyType () Text (QField s a) Source # | |
Defined in Database.Beam.Query.Internal 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, ProjectibleWithPredicate contextPredicate be res b, ProjectibleWithPredicate contextPredicate be res c) => ProjectibleWithPredicate contextPredicate be res (a, b, c) Source # | |
Defined in Database.Beam.Query.Internal 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 AnyType () res (Const res a) Source # | |
Defined in Database.Beam.Query.Internal 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 d) => ProjectibleWithPredicate contextPredicate be res (a, b, c, d) Source # | |
Defined in Database.Beam.Query.Internal 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 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 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 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 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 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 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 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 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 :: forall be a. Projectible be a => Proxy be -> a -> WithExprContext [BeamSqlBackendExpressionSyntax be] Source #
reproject :: forall be a. (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 :: forall be res m. (Projectible be res, MonadState Int m) => (Int -> m (WithExprContext (BeamSqlBackendExpressionSyntax' be))) -> m res Source #
mkFieldNames :: forall be res. (BeamSqlBackend be, Projectible be res) => (Text -> BeamSqlBackendFieldNameSyntax be) -> (res, [Text]) Source #
tableNameFromEntity :: IsSql92TableNameSyntax name => DatabaseEntityDescriptor be (TableEntity tbl) -> name Source #