beam-core-0.9.2.1: Type-safe, feature-complete SQL query and manipulation interface for Haskell
Safe HaskellNone
LanguageHaskell2010

Database.Beam.Backend.Types

Synopsis

Documentation

class BeamBackend be Source #

Class for all Beam backends

Associated Types

type BackendFromField be :: Type -> Constraint Source #

Requirements to marshal a certain type from a database of a particular backend

Instances

Instances details
BeamBackend (MockSqlBackend syntax) Source # 
Instance details

Defined in Database.Beam.Backend.SQL

Associated Types

type BackendFromField (MockSqlBackend syntax) :: Type -> Constraint Source #

data Exposed x Source #

newtype mainly used to inspect the tag structure of a particular Beamable. Prevents overlapping instances in some case. Usually not used in end-user code.

Instances

Instances details
FieldsFulfillConstraintNullable c t => GFieldsFulfillConstraint c (K1 R (t (Nullable Exposed)) :: Type -> Type) (K1 R (t (Nullable (HasConstraint c))) :: Type -> Type) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

FieldsFulfillConstraint c t => GFieldsFulfillConstraint c (K1 R (t Exposed) :: Type -> Type) (K1 R (t (HasConstraint c)) :: Type -> Type) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

Methods

gWithConstrainedFields :: Proxy c -> Proxy (K1 R (t Exposed)) -> K1 R (t (HasConstraint c)) () Source #

c x => GFieldsFulfillConstraint c (K1 R (Exposed x) :: Type -> Type) (K1 R (HasConstraint c x) :: Type -> Type) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

data Nullable (c :: Type -> Type) x Source #

Support for NULLable Foreign Key references.

data MyTable f = MyTable
               { nullableRef :: PrimaryKey AnotherTable (Nullable f)
               , ... }
                deriving (Generic, Typeable)

See Columnar for more information.

Instances

Instances details
Beamable t => ProjectibleWithPredicate AnyType () Text (t (Nullable (Const Text :: Type -> Type))) Source # 
Instance details

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)) -> 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 # 
Instance details

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, contextPredicate context) => ProjectibleWithPredicate contextPredicate be (WithExprContext (BeamSqlBackendExpressionSyntax' be)) (t (Nullable (QGenExpr context be s))) Source # 
Instance details

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 #

(BeamBackend be, Generic (tbl (Nullable Identity)), Generic (tbl (Nullable Exposed)), GFromBackendRow be (Rep (tbl (Nullable Exposed))) (Rep (tbl (Nullable Identity)))) => FromBackendRow be (tbl (Nullable Identity)) Source # 
Instance details

Defined in Database.Beam.Backend.SQL.Row

Beamable tbl => ThreadRewritable s (tbl (Nullable (QGenExpr ctxt syntax s))) Source # 
Instance details

Defined in Database.Beam.Query.Internal

Associated Types

type WithRewrittenThread s s' (tbl (Nullable (QGenExpr ctxt syntax s))) Source #

Methods

rewriteThread :: Proxy s' -> tbl (Nullable (QGenExpr ctxt syntax s)) -> WithRewrittenThread s s' (tbl (Nullable (QGenExpr ctxt syntax s))) Source #

(BeamSqlBackend be, Beamable t) => SqlDeconstructMaybe be (t (Nullable (QGenExpr ctxt be s))) (t (QGenExpr ctxt be s)) s Source # 
Instance details

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 #

FieldsFulfillConstraintNullable c t => GFieldsFulfillConstraint c (K1 R (t (Nullable Exposed)) :: Type -> Type) (K1 R (t (Nullable (HasConstraint c))) :: Type -> Type) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

Beamable tbl => ContextRewritable (tbl (Nullable (QGenExpr old syntax s))) Source # 
Instance details

Defined in Database.Beam.Query.Internal

Associated Types

type WithRewrittenContext (tbl (Nullable (QGenExpr old syntax s))) ctxt Source #

Methods

rewriteContext :: Proxy ctxt -> tbl (Nullable (QGenExpr old syntax s)) -> WithRewrittenContext (tbl (Nullable (QGenExpr old syntax s))) ctxt Source #

(Beamable table, BeamSqlBackend be, FieldsFulfillConstraintNullable (BeamSqlBackendCanSerialize be) table) => SqlValable (table (Nullable (QGenExpr ctxt be s))) Source # 
Instance details

Defined in Database.Beam.Query.Combinators

Methods

val_ :: HaskellLiteralForQExpr (table (Nullable (QGenExpr ctxt be s))) -> table (Nullable (QGenExpr ctxt be s)) Source #

TagReducesTo f f' => TagReducesTo (Nullable f) f' Source # 
Instance details

Defined in Database.Beam.Schema.Tables

Methods

reduceTag :: Functor m => (Columnar' f' a' -> m (Columnar' f' a')) -> Columnar' (Nullable f) a -> m (Columnar' (Nullable f) a) Source #

Table t => SqlJustable (t Identity) (t (Nullable Identity)) Source # 
Instance details

Defined in Database.Beam.Query.Combinators

(Table t, BeamSqlBackend be) => SqlJustable (t (QExpr be s)) (t (Nullable (QExpr be s))) Source # 
Instance details

Defined in Database.Beam.Query.Combinators

Methods

just_ :: t (QExpr be s) -> t (Nullable (QExpr be s)) Source #

nothing_ :: t (Nullable (QExpr be s)) Source #

Beamable tbl => QGroupable (tbl (Nullable (QExpr be s))) (tbl (Nullable (QGroupExpr be s))) Source #

group_ for any Beamable type. Adds every field in the type to the grouping key. This is the equivalent of including the grouping expression of each field in the type as part of the aggregate projection

Instance details

Defined in Database.Beam.Query.Aggregate

Methods

group_ :: tbl (Nullable (QExpr be s)) -> tbl (Nullable (QGroupExpr be s)) Source #

Table t => SqlJustable (PrimaryKey t Identity) (PrimaryKey t (Nullable Identity)) Source # 
Instance details

Defined in Database.Beam.Query.Combinators

(Table t, BeamSqlBackend be) => SqlJustable (PrimaryKey t (QExpr be s)) (PrimaryKey t (Nullable (QExpr be s))) Source # 
Instance details

Defined in Database.Beam.Query.Combinators

Methods

just_ :: PrimaryKey t (QExpr be s) -> PrimaryKey t (Nullable (QExpr be s)) Source #

nothing_ :: 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 # 
Instance details

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 #

type WithRewrittenThread s s' (tbl (Nullable (QGenExpr ctxt syntax s))) Source # 
Instance details

Defined in Database.Beam.Query.Internal

type WithRewrittenThread s s' (tbl (Nullable (QGenExpr ctxt syntax s))) = tbl (Nullable (QGenExpr ctxt syntax s'))
type QExprToField (table (Nullable (QGenExpr context syntax s))) Source # 
Instance details

Defined in Database.Beam.Query.Types

type QExprToField (table (Nullable (QGenExpr context syntax s))) = table (Nullable (QField s))
type QExprToIdentity (table (Nullable c)) Source # 
Instance details

Defined in Database.Beam.Query.Types

type QExprToIdentity (table (Nullable c)) = Maybe (QExprToIdentity (table c))
type HaskellLiteralForQExpr (table (Nullable f)) Source # 
Instance details

Defined in Database.Beam.Query.Combinators

type WithRewrittenContext (tbl (Nullable (QGenExpr old syntax s))) ctxt Source # 
Instance details

Defined in Database.Beam.Query.Internal

type WithRewrittenContext (tbl (Nullable (QGenExpr old syntax s))) ctxt = tbl (Nullable (QGenExpr ctxt syntax s))