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

Database.Beam.Schema.Tables

Description

Defines a generic schema type that can be used to define schemas for Beam tables

Synopsis

Database Types

class Database be db Source #

Allows introspection into database types.

All database types must be of kind '(Type -> Type) -> Type'. If the type parameter is named f, each field must be of the type of f applied to some type for which an IsDatabaseEntity instance exists.

The be type parameter is necessary so that the compiler can ensure that backend-specific entities only work on the proper backend.

Entities are documented under the corresponding section and in the manual

zipTables :: (Database be db, Applicative m) => Proxy be -> (forall tbl. (IsDatabaseEntity be tbl, DatabaseEntityRegularRequirements be tbl) => f tbl -> g tbl -> m (h tbl)) -> db f -> db g -> m (db h) Source #

Default derived function. Do not implement this yourself.

The idea is that, for any two databases over particular entity tags f and g, if we can take any entity in f and g to the corresponding entity in h (in the possibly effectful applicative functor m), then we can transform the two databases over f and g to a database in h, within m.

If that doesn't make sense, don't worry. This is mostly beam internal

type DatabaseSettings be db = db (DatabaseEntity be db) Source #

When parameterized by this entity tag, a database type will hold meta-information on the Haskell mappings of database entities. Under the hood, each entity type is transformed into its DatabaseEntityDescriptor type. For tables this includes the table name as well as the corresponding TableSettings, which provides names for each column.

class RenamableWithRule (FieldRenamer (DatabaseEntityDescriptor be entityType)) => IsDatabaseEntity be entityType where Source #

Associated Types

data DatabaseEntityDescriptor be entityType :: Type Source #

type DatabaseEntityDefaultRequirements be entityType :: Constraint Source #

type DatabaseEntityRegularRequirements be entityType :: Constraint Source #

Instances

Instances details
IsDatabaseEntity be (DomainTypeEntity ty) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

Beamable tbl => IsDatabaseEntity be (ViewEntity tbl) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

Beamable tbl => IsDatabaseEntity be (TableEntity tbl) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

data DatabaseEntity be (db :: (Type -> Type) -> Type) entityType where Source #

Represents a meta-description of a particular entityType. Mostly, a wrapper around 'DatabaseEntityDescriptor be entityType', but carries around the IsDatabaseEntity dictionary.

Constructors

DatabaseEntity :: IsDatabaseEntity be entityType => DatabaseEntityDescriptor be entityType -> DatabaseEntity be db entityType 

Instances

Instances details
Database be db => RenamableWithRule (db (EntityModification (DatabaseEntity be db) be)) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

IsDatabaseEntity be entity => RenamableWithRule (EntityModification (DatabaseEntity be db) be entity) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

data TableEntity (tbl :: (Type -> Type) -> Type) Source #

An entity tag for tables. See the documentation for Table or consult the manual for more.

Instances

Instances details
Beamable tbl => IsDatabaseEntity be (TableEntity tbl) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

Beamable tbl => RenamableWithRule (FieldRenamer (DatabaseEntityDescriptor be (TableEntity tbl))) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

data DatabaseEntityDescriptor be (TableEntity tbl) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

data DatabaseEntityDescriptor be (TableEntity tbl) where
type DatabaseEntityDefaultRequirements be (TableEntity tbl) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

type DatabaseEntityRegularRequirements be (TableEntity tbl) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

data ViewEntity (view :: (Type -> Type) -> Type) Source #

Instances

Instances details
Beamable tbl => IsDatabaseEntity be (ViewEntity tbl) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

Beamable tbl => RenamableWithRule (FieldRenamer (DatabaseEntityDescriptor be (ViewEntity tbl))) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

data DatabaseEntityDescriptor be (ViewEntity tbl) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

data DatabaseEntityDescriptor be (ViewEntity tbl) where
type DatabaseEntityDefaultRequirements be (ViewEntity tbl) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

type DatabaseEntityRegularRequirements be (ViewEntity tbl) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

data DomainTypeEntity (ty :: Type) Source #

Instances

Instances details
IsDatabaseEntity be (DomainTypeEntity ty) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

RenamableWithRule (FieldRenamer (DatabaseEntityDescriptor be (DomainTypeEntity ty))) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

data DatabaseEntityDescriptor be (DomainTypeEntity ty) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

type DatabaseEntityDefaultRequirements be (DomainTypeEntity ty) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

type DatabaseEntityRegularRequirements be (DomainTypeEntity ty) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

type DatabaseModification f be db = db (EntityModification f be) Source #

A helper data type that lets you modify a database schema. Converts all entities in the database into functions from that entity to itself.

newtype EntityModification f be e Source #

A newtype wrapper around 'f e -> f e' (i.e., an endomorphism between entity types in f). You usually want to use modifyTable or another function to contstruct these for you.

Constructors

EntityModification (Endo (f e)) 

Instances

Instances details
Database be db => RenamableWithRule (db (EntityModification (DatabaseEntity be db) be)) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

Semigroup (EntityModification f be e) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

Monoid (EntityModification f be e) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

IsDatabaseEntity be entity => RenamableWithRule (EntityModification (DatabaseEntity be db) be entity) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

newtype FieldModification f a Source #

A newtype wrapper around 'Columnar f a -> Columnar f a' (i.e., an endomorphism between Columnars over f). You usually want to use fieldNamed or the IsString instance to rename the field, when 'f ~ TableField'

Constructors

FieldModification (Columnar f a -> Columnar f a) 

Instances

Instances details
(Beamable tbl, RenamableField f) => RenamableWithRule (tbl (FieldModification f)) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

IsString (FieldModification (TableField tbl) a) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

dbModification :: forall f be db. Database be db => DatabaseModification f be db Source #

Return a DatabaseModification that does nothing. This is useful if you only want to rename one table. You can do

dbModification { tbl1 = modifyTable (\oldNm -> "NewTableName") tableModification }

tableModification :: forall f tbl. Beamable tbl => tbl (FieldModification f) Source #

Return a table modification (for use with modifyTable) that does nothing. Useful if you only want to change the table name, or if you only want to modify a few fields.

For example,

tableModification { field1 = "Column1" }

is a table modification (where 'f ~ TableField tbl') that changes the column name of field1 to Column1.

withDbModification :: forall db be entity. Database be db => db (entity be db) -> DatabaseModification (entity be db) be db -> db (entity be db) Source #

Modify a database according to a given modification. Most useful for DatabaseSettings to change the name mappings of tables and fields. For example, you can use this to modify the default names of a table

db :: DatabaseSettings MyDb
db = defaultDbSettings `withDbModification`
     dbModification {
       -- Change default name "table1" to "Table_1". Change the name of "table1Field1" to "first_name"
       table1 = modifyTable (\_ -> "Table_1") (tableModification { table1Field1 = "first_name" }
     }

withTableModification :: Beamable tbl => tbl (FieldModification f) -> tbl f -> tbl f Source #

Modify a table according to the given field modifications. Invoked by modifyTable to apply the modification in the database. Not used as often in user code, but provided for completeness.

modifyTable :: (Beamable tbl, Table tbl) => (Text -> Text) -> tbl (FieldModification (TableField tbl)) -> EntityModification (DatabaseEntity be db) be (TableEntity tbl) Source #

Deprecated: Instead of 'modifyTable fTblNm fFields', use 'modifyEntityName _ <> modifyTableFields _'

Provide an EntityModification for TableEntitys. Allows you to modify the name of the table and provide a modification for each field in the table. See the examples for withDbModification for more.

modifyEntityName :: IsDatabaseEntity be entity => (Text -> Text) -> EntityModification (DatabaseEntity be db) be entity Source #

Construct an EntityModification to rename any database entity

setEntityName :: IsDatabaseEntity be entity => Text -> EntityModification (DatabaseEntity be db) be entity Source #

Change the entity name without consulting the beam-assigned one

modifyTableFields :: tbl (FieldModification (TableField tbl)) -> EntityModification (DatabaseEntity be db) be (TableEntity tbl) Source #

Construct an EntityModification to rename the fields of a TableEntity

fieldNamed :: Text -> FieldModification (TableField tbl) a Source #

A field modification to rename the field. Also offered under the IsString instance for 'FieldModification (TableField tbl) a' for convenience.

modifyEntitySchema :: IsDatabaseEntity be entity => (Maybe Text -> Maybe Text) -> EntityModification (DatabaseEntity be db) be entity Source #

Construct an EntityModification to set the schema of a database entity

defaultDbSettings :: (Generic (DatabaseSettings be db), GAutoDbSettings (Rep (DatabaseSettings be db) ())) => DatabaseSettings be db Source #

Automatically provide names for tables, and descriptions for tables (using defTblFieldSettings). Your database must implement Generic, and must be auto-derivable. For more information on name generation, see the manual

class RenamableWithRule mod where Source #

Methods

renamingFields :: (NonEmpty Text -> Text) -> mod Source #

Instances

Instances details
(Beamable tbl, RenamableField f) => RenamableWithRule (tbl (FieldModification f)) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

Database be db => RenamableWithRule (db (EntityModification (DatabaseEntity be db) be)) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

RenamableWithRule (FieldRenamer (DatabaseEntityDescriptor be (DomainTypeEntity ty))) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

Beamable tbl => RenamableWithRule (FieldRenamer (DatabaseEntityDescriptor be (ViewEntity tbl))) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

Beamable tbl => RenamableWithRule (FieldRenamer (DatabaseEntityDescriptor be (TableEntity tbl))) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

IsDatabaseEntity be entity => RenamableWithRule (EntityModification (DatabaseEntity be db) be entity) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

class RenamableField f where Source #

Methods

renameField :: Proxy f -> Proxy a -> (NonEmpty Text -> Text) -> Columnar f a -> Columnar f a Source #

Instances

Instances details
RenamableField (TableField tbl) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

Methods

renameField :: Proxy (TableField tbl) -> Proxy a -> (NonEmpty Text -> Text) -> Columnar (TableField tbl) a -> Columnar (TableField tbl) a Source #

data Lenses (t :: (Type -> Type) -> Type) (f :: Type -> Type) x Source #

data LensFor t x where Source #

Constructors

LensFor :: Generic t => Lens' t x -> LensFor t x 

Columnar and Column Tags

type family Columnar (f :: Type -> Type) x where ... Source #

A type family that we use to "tag" columns in our table datatypes.

This is what allows us to use the same table type to hold table data, describe table settings, derive lenses, and provide expressions.

The basic rules are

Columnar Identity x = x

Thus, any Beam table applied to Identity will yield a simplified version of the data type, that contains just what you'd expect.

The Nullable type is used when referencing PrimaryKeys that we want to include optionally. For example, if we have a table with a PrimaryKey, like the following

data BeamTableT f = BeamTableT
                  { _refToAnotherTable :: PrimaryKey AnotherTableT f
                  , ... }

we would typically be required to provide values for the PrimaryKey embedded into BeamTableT. We can use Nullable to lift this constraint.

data BeamTableT f = BeamTableT
                  { _refToAnotherTable :: PrimaryKey AnotherTableT (Nullable f)
                  , ... }

Now we can use justRef and nothingRef to refer to this table optionally. The embedded PrimaryKey in _refToAnotherTable automatically has its fields converted into Maybe using Nullable.

The last Columnar rule is

Columnar f x = f x

Use this rule if you'd like to parameterize your table type over any other functor. For example, this is used in the query modules to write expressions such as 'TableT QExpr', which returns a table whose fields have been turned into query expressions.

The other rules are used within Beam to provide lenses and to expose the inner structure of the data type.

Equations

Columnar Exposed x = Exposed x 
Columnar Identity x = x 
Columnar (Lenses t f) x = LensFor (t f) (Columnar f x) 
Columnar (Nullable c) x = Columnar c (Maybe x) 
Columnar f x = f x 

type C f a = Columnar f a Source #

A short type-alias for Columnar. May shorten your schema definitions

newtype Columnar' f a Source #

If you declare a function 'Columnar f a -> b' and try to constrain your function by a type class for f, GHC will complain, because f is ambiguous in 'Columnar f a'. For example, 'Columnar Identity (Maybe a) ~ Maybe a' and 'Columnar (Nullable Identity) a ~ Maybe a', so given a type 'Columnar f a', we cannot know the type of f.

Thus, if you need to know f, you can instead use Columnar'. Since its a newtype, it carries around the f paramater unambiguously. Internally, it simply wraps 'Columnar f a'

Constructors

Columnar' (Columnar f a) 

newtype ComposeColumnar f g a Source #

Like Compose, but with an intermediate Columnar

Constructors

ComposeColumnar (f (Columnar g a)) 

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))

data TableField (table :: (Type -> Type) -> Type) ty Source #

Metadata for a field of type ty in table.

Essentially a wrapper over the field name, but with a phantom type parameter, so that it forms an appropriate column tag.

Usually you use the defaultDbSettings function to generate an appropriate naming convention for you, and then modify it with withDbModification if necessary. Under this scheme, the field n be renamed using the IsString instance for TableField, or the fieldNamed function.

Constructors

TableField 

Fields

Instances

Instances details
RenamableField (TableField tbl) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

Methods

renameField :: Proxy (TableField tbl) -> Proxy a -> (NonEmpty Text -> Text) -> Columnar (TableField tbl) a -> Columnar (TableField tbl) a Source #

TagReducesTo (TableField tbl) (TableField tbl) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

Methods

reduceTag :: Functor m => (Columnar' (TableField tbl) a' -> m (Columnar' (TableField tbl) a')) -> Columnar' (TableField tbl) a -> m (Columnar' (TableField tbl) a) Source #

Eq (TableField table ty) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

Methods

(==) :: TableField table ty -> TableField table ty -> Bool #

(/=) :: TableField table ty -> TableField table ty -> Bool #

Show (TableField table ty) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

Methods

showsPrec :: Int -> TableField table ty -> ShowS #

show :: TableField table ty -> String #

showList :: [TableField table ty] -> ShowS #

IsString (FieldModification (TableField tbl) a) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

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

fieldName :: Lens' (TableField table ty) Text Source #

Van Laarhoven lens to retrieve or set the field name from a TableField.

type TableSettings table = table (TableField table) Source #

Represents a table that contains metadata on its fields. In particular, each field of type 'Columnar f a' is transformed into 'TableField table a'. You can get or update the name of each field by using the fieldName lens.

type HaskellTable table = table Identity Source #

The regular Haskell version of the table. Equivalent to 'tbl Identity'

type TableSkeleton table = table Ignored Source #

A form of table all fields Ignored. Useful as a parameter to zipTables when you only care about one table.

data Ignored x Source #

Column tag that ignores the type.

Constructors

Ignored 

class GFieldsFulfillConstraint (c :: Type -> Constraint) (exposed :: Type -> Type) withconstraint where Source #

Methods

gWithConstrainedFields :: Proxy c -> Proxy exposed -> withconstraint () Source #

Instances

Instances details
GFieldsFulfillConstraint c (U1 :: Type -> Type) (U1 :: Type -> Type) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

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

(GFieldsFulfillConstraint c aExp aC, GFieldsFulfillConstraint c bExp bC) => GFieldsFulfillConstraint c (aExp :*: bExp) (aC :*: bC) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

Methods

gWithConstrainedFields :: Proxy c -> Proxy (aExp :*: bExp) -> (aC :*: bC) () Source #

GFieldsFulfillConstraint c exposed withconstraint => GFieldsFulfillConstraint c (M1 s m exposed) (M1 s m withconstraint) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

Methods

gWithConstrainedFields :: Proxy c -> Proxy (M1 s m exposed) -> M1 s m withconstraint () Source #

data WithConstraint (c :: Type -> Constraint) x where Source #

Carry a constraint instance and the value it applies to.

Constructors

WithConstraint :: c x => x -> WithConstraint c x 

data HasConstraint (c :: Type -> Constraint) x where Source #

Carry a constraint instance.

Constructors

HasConstraint :: c x => HasConstraint c x 

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

class TagReducesTo f f' | f -> f' where Source #

Class to automatically unwrap nested Nullables

Methods

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

Instances

Instances details
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 #

TagReducesTo (TableField tbl) (TableField tbl) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

Methods

reduceTag :: Functor m => (Columnar' (TableField tbl) a' -> m (Columnar' (TableField tbl) a')) -> Columnar' (TableField tbl) a -> m (Columnar' (TableField tbl) a) Source #

type family ReplaceBaseTag tag f where ... Source #

Equations

ReplaceBaseTag tag (Nullable f) = Nullable (ReplaceBaseTag tag f) 
ReplaceBaseTag tag x = tag 

withConstrainedFields :: forall c tbl. (FieldsFulfillConstraint c tbl, Beamable tbl) => tbl Identity -> tbl (WithConstraint c) Source #

withConstraints :: forall c tbl. (Beamable tbl, FieldsFulfillConstraint c tbl) => tbl (HasConstraint c) Source #

Tables

class (Typeable table, Beamable table, Beamable (PrimaryKey table)) => Table (table :: (Type -> Type) -> Type) where Source #

The big Kahuna! All beam tables implement this class.

The kind of all table types is '(Type -> Type) -> Type'. This is because all table types are actually table type constructors. Every table type takes in another type constructor, called the column tag, and uses that constructor to instantiate the column types. See the documentation for Columnar.

This class is mostly Generic-derivable. You need only specify a type for the table's primary key and a method to extract the primary key given the table.

An example table:

data BlogPostT f = BlogPost
                 { _blogPostSlug    :: Columnar f Text
                 , _blogPostBody    :: Columnar f Text
                 , _blogPostDate    :: Columnar f UTCTime
                 , _blogPostAuthor  :: PrimaryKey AuthorT f
                 , _blogPostTagline :: Columnar f (Maybe Text)
                 , _blogPostImageGallery :: PrimaryKey ImageGalleryT (Nullable f) }
                   deriving Generic
instance Beamable BlogPostT
instance Table BlogPostT where
   data PrimaryKey BlogPostT f = BlogPostId (Columnar f Text) deriving Generic
   primaryKey = BlogPostId . _blogPostSlug
instance Beamable (PrimaryKey BlogPostT)

We can interpret this as follows:

  • The _blogPostSlug, _blogPostBody, _blogPostDate, and _blogPostTagline fields are of types Text, Text, UTCTime, and 'Maybe Text' respectfully.
  • Since _blogPostSlug, _blogPostBody, _blogPostDate, _blogPostAuthor must be provided (i.e, they cannot contain Nothing), they will be given SQL NOT NULL constraints. _blogPostTagline is declared Maybe so Nothing will be stored as NULL in the database. _blogPostImageGallery will be allowed to be empty because it uses the Nullable tag modifier.
  • blogPostAuthor references the AuthorT table (not given here) and is required.
  • blogPostImageGallery references the ImageGalleryT table (not given here), but this relation is not required (i.e., it may be Nothing. See Nullable).

Associated Types

data PrimaryKey table (column :: Type -> Type) :: Type Source #

A data type representing the types of primary keys for this table. In order to play nicely with the default deriving mechanism, this type must be an instance of Generic.

Methods

primaryKey :: table column -> PrimaryKey table column Source #

Given a table, this should return the PrimaryKey from the table. By keeping this polymorphic over column, we ensure that the primary key values come directly from the table (i.e., they can't be arbitrary constants)

class Beamable table where Source #

Provides a number of introspection routines for the beam library. Allows us to "zip" tables with different column tags together. Always instantiate an empty Beamable instance for tables, primary keys, and any type that you would like to embed within either. See the manual for more information on embedding.

Minimal complete definition

Nothing

Methods

zipBeamFieldsM :: Applicative m => (forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a)) -> table f -> table g -> m (table h) Source #

default zipBeamFieldsM :: (HasBeamFields table f g h, Applicative m) => (forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a)) -> table f -> table g -> m (table h) Source #

tblSkeleton :: TableSkeleton table Source #

default tblSkeleton :: (Generic (TableSkeleton table), GTableSkeleton (Rep (TableSkeleton table))) => TableSkeleton table Source #

class Retaggable f x | x -> f where Source #

Associated Types

type Retag (tag :: (Type -> Type) -> Type -> Type) x :: Type Source #

Methods

retag :: (forall a. Columnar' f a -> Columnar' (tag f) a) -> x -> Retag tag x Source #

Instances

Instances details
Beamable tbl => Retaggable f (tbl f) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

Associated Types

type Retag tag (tbl f) Source #

Methods

retag :: forall (tag :: (Type -> Type) -> Type -> Type). (forall a. Columnar' f a -> Columnar' (tag f) a) -> tbl f -> Retag tag (tbl f) Source #

(Retaggable f a, Retaggable f b) => Retaggable f (a, b) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

Associated Types

type Retag tag (a, b) Source #

Methods

retag :: forall (tag :: (Type -> Type) -> Type -> Type). (forall a0. Columnar' f a0 -> Columnar' (tag f) a0) -> (a, b) -> Retag tag (a, b) Source #

(Retaggable f a, Retaggable f b, Retaggable f c) => Retaggable f (a, b, c) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

Associated Types

type Retag tag (a, b, c) Source #

Methods

retag :: forall (tag :: (Type -> Type) -> Type -> Type). (forall a0. Columnar' f a0 -> Columnar' (tag f) a0) -> (a, b, c) -> Retag tag (a, b, c) Source #

(Retaggable f a, Retaggable f b, Retaggable f c, Retaggable f d) => Retaggable f (a, b, c, d) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

Associated Types

type Retag tag (a, b, c, d) Source #

Methods

retag :: forall (tag :: (Type -> Type) -> Type -> Type). (forall a0. Columnar' f a0 -> Columnar' (tag f) a0) -> (a, b, c, d) -> Retag tag (a, b, c, d) Source #

(Retaggable f a, Retaggable f b, Retaggable f c, Retaggable f d, Retaggable f e) => Retaggable f (a, b, c, d, e) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

Associated Types

type Retag tag (a, b, c, d, e) Source #

Methods

retag :: forall (tag :: (Type -> Type) -> Type -> Type). (forall a0. Columnar' f a0 -> Columnar' (tag f) a0) -> (a, b, c, d, e) -> Retag tag (a, b, c, d, e) Source #

(Retaggable f' a, Retaggable f' b, Retaggable f' c, Retaggable f' d, Retaggable f' e, Retaggable f' f) => Retaggable f' (a, b, c, d, e, f) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

Associated Types

type Retag tag (a, b, c, d, e, f) Source #

Methods

retag :: forall (tag :: (Type -> Type) -> Type -> Type). (forall a0. Columnar' f' a0 -> Columnar' (tag f') a0) -> (a, b, c, d, e, f) -> Retag tag (a, b, c, d, e, f) Source #

(Retaggable f' a, Retaggable f' b, Retaggable f' c, Retaggable f' d, Retaggable f' e, Retaggable f' f, Retaggable f' g) => Retaggable f' (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

Associated Types

type Retag tag (a, b, c, d, e, f, g) Source #

Methods

retag :: forall (tag :: (Type -> Type) -> Type -> Type). (forall a0. Columnar' f' a0 -> Columnar' (tag f') a0) -> (a, b, c, d, e, f, g) -> Retag tag (a, b, c, d, e, f, g) Source #

(Retaggable f' a, Retaggable f' b, Retaggable f' c, Retaggable f' d, Retaggable f' e, Retaggable f' f, Retaggable f' g, Retaggable f' h) => Retaggable f' (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

Associated Types

type Retag tag (a, b, c, d, e, f, g, h) Source #

Methods

retag :: forall (tag :: (Type -> Type) -> Type -> Type). (forall a0. Columnar' f' a0 -> Columnar' (tag f') a0) -> (a, b, c, d, e, f, g, h) -> Retag tag (a, b, c, d, e, f, g, h) Source #

Retaggable (QGenExpr ctxt expr s) (QGenExpr ctxt expr s t) Source # 
Instance details

Defined in Database.Beam.Query.Internal

Associated Types

type Retag tag (QGenExpr ctxt expr s t) Source #

Methods

retag :: forall (tag :: (Type -> Type) -> Type -> Type). (forall a. Columnar' (QGenExpr ctxt expr s) a -> Columnar' (tag (QGenExpr ctxt expr s)) a) -> QGenExpr ctxt expr s t -> Retag tag (QGenExpr ctxt expr s t) Source #

data ((f :: k -> Type) :*: (g :: k -> Type)) (p :: k) infixr 6 #

Products: encode multiple arguments to constructors

Constructors

(f p) :*: (g p) infixr 6 

Instances

Instances details
(Monoid pairs, RecordToPairs enc pairs arity a, RecordToPairs enc pairs arity b) => RecordToPairs enc pairs arity (a :*: b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

recordToPairs :: Options -> ToArgs enc arity a0 -> (a :*: b) a0 -> pairs

(EncodeProduct arity a, EncodeProduct arity b) => GToJSON' Encoding arity (a :*: b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Encoding arity a0 -> (a :*: b) a0 -> Encoding

(WriteProduct arity a, WriteProduct arity b, ProductSize a, ProductSize b) => GToJSON' Value arity (a :*: b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Value arity a0 -> (a :*: b) a0 -> Value

Generic1 (f :*: g :: k -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (f :*: g) :: k -> Type #

Methods

from1 :: forall (a :: k0). (f :*: g) a -> Rep1 (f :*: g) a #

to1 :: forall (a :: k0). Rep1 (f :*: g) a -> (f :*: g) a #

(EncodeProduct arity a, EncodeProduct arity b) => EncodeProduct arity (a :*: b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

encodeProduct :: Options -> ToArgs Encoding arity a0 -> (a :*: b) a0 -> Encoding' InArray

(WriteProduct arity a, WriteProduct arity b) => WriteProduct arity (a :*: b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

writeProduct :: Options -> ToArgs Value arity a0 -> MVector s Value -> Int -> Int -> (a :*: b) a0 -> ST s ()

(ProductFromJSON arity a, ProductFromJSON arity b) => ProductFromJSON arity (a :*: b) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

productParseJSON :: (ConName :* (TypeName :* (Options :* FromArgs arity a0))) -> Array -> Int -> Int -> Parser ((a :*: b) a0)

(FieldNames a, FieldNames b) => FieldNames (a :*: b :: k -> Type) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

fieldNames :: forall (a0 :: k0). (a :*: b) a0 -> [String] -> [String]

(RecordFromJSON' arity a, RecordFromJSON' arity b) => RecordFromJSON' arity (a :*: b) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

recordParseJSON' :: (ConName :* (TypeName :* (Options :* FromArgs arity a0))) -> Object -> Parser ((a :*: b) a0)

(GFieldsFulfillConstraint c aExp aC, GFieldsFulfillConstraint c bExp bC) => GFieldsFulfillConstraint c (aExp :*: bExp) (aC :*: bC) Source # 
Instance details

Defined in Database.Beam.Schema.Tables

Methods

gWithConstrainedFields :: Proxy c -> Proxy (aExp :*: bExp) -> (aC :*: bC) () Source #

(Monad f, Monad g) => Monad (f :*: g)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

(>>=) :: (f :*: g) a -> (a -> (f :*: g) b) -> (f :*: g) b #

(>>) :: (f :*: g) a -> (f :*: g) b -> (f :*: g) b #

return :: a -> (f :*: g) a #

(Functor f, Functor g) => Functor (f :*: g)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> (f :*: g) a -> (f :*: g) b #

(<$) :: a -> (f :*: g) b -> (f :*: g) a #

(MonadFix f, MonadFix g) => MonadFix (f :*: g)

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> (f :*: g) a) -> (f :*: g) a #

(Applicative f, Applicative g) => Applicative (f :*: g)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

pure :: a -> (f :*: g) a #

(<*>) :: (f :*: g) (a -> b) -> (f :*: g) a -> (f :*: g) b #

liftA2 :: (a -> b -> c) -> (f :*: g) a -> (f :*: g) b -> (f :*: g) c #

(*>) :: (f :*: g) a -> (f :*: g) b -> (f :*: g) b #

(<*) :: (f :*: g) a -> (f :*: g) b -> (f :*: g) a #

(Foldable f, Foldable g) => Foldable (f :*: g)

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => (f :*: g) m -> m #

foldMap :: Monoid m => (a -> m) -> (f :*: g) a -> m #

foldMap' :: Monoid m => (a -> m) -> (f :*: g) a -> m #

foldr :: (a -> b -> b) -> b -> (f :*: g) a -> b #

foldr' :: (a -> b -> b) -> b -> (f :*: g) a -> b #

foldl :: (b -> a -> b) -> b -> (f :*: g) a -> b #

foldl' :: (b -> a -> b) -> b -> (f :*: g) a -> b #

foldr1 :: (a -> a -> a) -> (f :*: g) a -> a #

foldl1 :: (a -> a -> a) -> (f :*: g) a -> a #

toList :: (f :*: g) a -> [a] #

null :: (f :*: g) a -> Bool #

length :: (f :*: g) a -> Int #

elem :: Eq a => a -> (f :*: g) a -> Bool #

maximum :: Ord a => (f :*: g) a -> a #

minimum :: Ord a => (f :*: g) a -> a #

sum :: Num a => (f :*: g) a -> a #

product :: Num a => (f :*: g) a -> a #

(Traversable f, Traversable g) => Traversable (f :*: g)

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f0 => (a -> f0 b) -> (f :*: g) a -> f0 ((f :*: g) b) #

sequenceA :: Applicative f0 => (f :*: g) (f0 a) -> f0 ((f :*: g) a) #

mapM :: Monad m => (a -> m b) -> (f :*: g) a -> m ((f :*: g) b) #

sequence :: Monad m => (f :*: g) (m a) -> m ((f :*: g) a) #

(Representable f, Representable g) => Representable (f :*: g) 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep (f :*: g) #

Methods

tabulate :: (Rep (f :*: g) -> a) -> (f :*: g) a #

index :: (f :*: g) a -> Rep (f :*: g) -> a #

(Alternative f, Alternative g) => Alternative (f :*: g)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

empty :: (f :*: g) a #

(<|>) :: (f :*: g) a -> (f :*: g) a -> (f :*: g) a #

some :: (f :*: g) a -> (f :*: g) [a] #

many :: (f :*: g) a -> (f :*: g) [a] #

(MonadPlus f, MonadPlus g) => MonadPlus (f :*: g)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

mzero :: (f :*: g) a #

mplus :: (f :*: g) a -> (f :*: g) a -> (f :*: g) a #

(GUniform f, GUniform g) => GUniform (f :*: g) 
Instance details

Defined in System.Random.Internal

Methods

guniformM :: forall g0 (m :: Type -> Type) r a. StatefulGen g0 m => g0 -> ContT r m ((f :*: g) a)

(GIndex f, GIndex g) => GIndex (f :*: g) 
Instance details

Defined in Data.Functor.Rep

Methods

gindex' :: (f :*: g) a -> GRep' (f :*: g) -> a

(GTabulate f, GTabulate g) => GTabulate (f :*: g) 
Instance details

Defined in Data.Functor.Rep

Methods

gtabulate' :: (GRep' (f :*: g) -> a) -> (f :*: g) a

(Eq (f p), Eq (g p)) => Eq ((f :*: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: (f :*: g) p -> (f :*: g) p -> Bool #

(/=) :: (f :*: g) p -> (f :*: g) p -> Bool #

(Ord (f p), Ord (g p)) => Ord ((f :*: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: (f :*: g) p -> (f :*: g) p -> Ordering #

(<) :: (f :*: g) p -> (f :*: g) p -> Bool #

(<=) :: (f :*: g) p -> (f :*: g) p -> Bool #

(>) :: (f :*: g) p -> (f :*: g) p -> Bool #

(>=) :: (f :*: g) p -> (f :*: g) p -> Bool #

max :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p #

min :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p #

(Read (f p), Read (g p)) => Read ((f :*: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

readsPrec :: Int -> ReadS ((f :*: g) p) #

readList :: ReadS [(f :*: g) p] #

readPrec :: ReadPrec ((f :*: g) p) #

readListPrec :: ReadPrec [(f :*: g) p] #

(Show (f p), Show (g p)) => Show ((f :*: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> (f :*: g) p -> ShowS #

show :: (f :*: g) p -> String #

showList :: [(f :*: g) p] -> ShowS #

Generic ((f :*: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :*: g) p) :: Type -> Type #

Methods

from :: (f :*: g) p -> Rep ((f :*: g) p) x #

to :: Rep ((f :*: g) p) x -> (f :*: g) p #

(Semigroup (f p), Semigroup (g p)) => Semigroup ((f :*: g) p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

(<>) :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p #

sconcat :: NonEmpty ((f :*: g) p) -> (f :*: g) p #

stimes :: Integral b => b -> (f :*: g) p -> (f :*: g) p #

(Monoid (f p), Monoid (g p)) => Monoid ((f :*: g) p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: (f :*: g) p #

mappend :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p #

mconcat :: [(f :*: g) p] -> (f :*: g) p #

type Rep1 (f :*: g :: k -> Type) 
Instance details

Defined in GHC.Generics

type Rep (f :*: g) 
Instance details

Defined in Data.Functor.Rep

type Rep (f :*: g) = Either (Rep f) (Rep g)
type GRep' (f :*: g) 
Instance details

Defined in Data.Functor.Rep

type GRep' (f :*: g) = Either (GRep' f) (GRep' g)
type Rep ((f :*: g) p) 
Instance details

Defined in GHC.Generics

defTblFieldSettings :: (Generic (TableSettings table), GDefaultTableFieldSettings (Rep (TableSettings table) ())) => TableSettings table Source #

Return a TableSettings for the appropriate table type where each column has been given its default name. See the manual for information on the default naming convention.

pk :: Table t => t f -> PrimaryKey t f Source #

Synonym for primaryKey

allBeamValues :: Beamable table => (forall a. Columnar' f a -> b) -> table f -> [b] Source #

changeBeamRep :: Beamable table => (forall a. Columnar' f a -> Columnar' g a) -> table f -> table g Source #

alongsideTable :: Beamable tbl => tbl f -> tbl g -> tbl (Columnar' f :*: Columnar' g) Source #

defaultFieldName :: NonEmpty Text -> Text Source #

Produce the beam default field name for the given path