Safe Haskell | None |
---|---|
Language | Haskell2010 |
Defines a generic schema type that can be used to define schemas for Beam tables
Synopsis
- class Database be (db :: (Type -> Type) -> Type)
- 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)
- type DatabaseSettings be (db :: (Type -> Type) -> Type) = db (DatabaseEntity be db)
- class RenamableWithRule (FieldRenamer (DatabaseEntityDescriptor be entityType)) => IsDatabaseEntity be entityType where
- data DatabaseEntityDescriptor be entityType
- type DatabaseEntityDefaultRequirements be entityType
- type DatabaseEntityRegularRequirements be entityType
- dbEntityName :: Lens' (DatabaseEntityDescriptor be entityType) Text
- dbEntitySchema :: Traversal' (DatabaseEntityDescriptor be entityType) (Maybe Text)
- dbEntityAuto :: Text -> DatabaseEntityDescriptor be entityType
- data family DatabaseEntityDescriptor be entityType
- data DatabaseEntity be (db :: (Type -> Type) -> Type) entityType where
- DatabaseEntity :: forall be entityType (db :: (Type -> Type) -> Type). IsDatabaseEntity be entityType => DatabaseEntityDescriptor be entityType -> DatabaseEntity be db entityType
- data TableEntity (tbl :: (Type -> Type) -> Type)
- data ViewEntity (view :: (Type -> Type) -> Type)
- data DomainTypeEntity ty
- dbEntityDescriptor :: forall be (db :: (Type -> Type) -> Type) entityType r. Getting r (DatabaseEntity be db entityType) (DatabaseEntityDescriptor be entityType)
- type DatabaseModification (f :: Type -> Type) be (db :: (Type -> Type) -> Type) = db (EntityModification f be)
- newtype EntityModification (f :: Type -> Type) be e = EntityModification (Endo (f e))
- newtype FieldModification (f :: Type -> Type) a = FieldModification (Columnar f a -> Columnar f a)
- dbModification :: forall (f :: Type -> Type) be db. Database be db => DatabaseModification f be db
- tableModification :: forall (f :: Type -> Type) tbl. Beamable tbl => tbl (FieldModification f)
- withDbModification :: forall db be (entity :: Type -> ((Type -> Type) -> Type) -> Type -> Type). Database be db => db (entity be db) -> DatabaseModification (entity be db) be db -> db (entity be db)
- withTableModification :: forall tbl (f :: Type -> Type). Beamable tbl => tbl (FieldModification f) -> tbl f -> tbl f
- modifyTable :: forall tbl be (db :: (Type -> Type) -> Type). (Beamable tbl, Table tbl) => (Text -> Text) -> tbl (FieldModification (TableField tbl)) -> EntityModification (DatabaseEntity be db) be (TableEntity tbl)
- modifyEntityName :: forall be entity (db :: (Type -> Type) -> Type). IsDatabaseEntity be entity => (Text -> Text) -> EntityModification (DatabaseEntity be db) be entity
- setEntityName :: forall be entity (db :: (Type -> Type) -> Type). IsDatabaseEntity be entity => Text -> EntityModification (DatabaseEntity be db) be entity
- modifyTableFields :: forall tbl be (db :: (Type -> Type) -> Type). tbl (FieldModification (TableField tbl)) -> EntityModification (DatabaseEntity be db) be (TableEntity tbl)
- fieldNamed :: forall (tbl :: (Type -> Type) -> Type) a. Text -> FieldModification (TableField tbl) a
- modifyEntitySchema :: forall be entity (db :: (Type -> Type) -> Type). IsDatabaseEntity be entity => (Maybe Text -> Maybe Text) -> EntityModification (DatabaseEntity be db) be entity
- setEntitySchema :: forall be entity (db :: (Type -> Type) -> Type). IsDatabaseEntity be entity => Maybe Text -> EntityModification (DatabaseEntity be db) be entity
- defaultDbSettings :: (Generic (DatabaseSettings be db), GAutoDbSettings (Rep (DatabaseSettings be db) ())) => DatabaseSettings be db
- embedDatabase :: forall be embedded (db :: (Type -> Type) -> Type). Database be embedded => DatabaseSettings be embedded -> embedded (EntityModification (DatabaseEntity be db) be)
- class RenamableWithRule mod where
- renamingFields :: (NonEmpty Text -> Text) -> mod
- class RenamableField (f :: Type -> Type) where
- newtype FieldRenamer entity = FieldRenamer {
- withFieldRenamer :: entity -> entity
- data Lenses (t :: (Type -> Type) -> Type) (f :: Type -> Type) x
- data LensFor t x where
- type family Columnar (f :: Type -> Type) x where ...
- type C (f :: Type -> Type) a = Columnar f a
- newtype Columnar' (f :: Type -> Type) a = Columnar' (Columnar f a)
- newtype ComposeColumnar (f :: Type -> Type) (g :: Type -> Type) a = ComposeColumnar (f (Columnar g a))
- data Nullable (c :: Type -> Type) x
- data TableField (table :: (Type -> Type) -> Type) ty = TableField {
- _fieldPath :: NonEmpty Text
- _fieldName :: Text
- data Exposed x
- fieldName :: forall (table :: (Type -> Type) -> Type) ty f. Functor f => (Text -> f Text) -> TableField table ty -> f (TableField table ty)
- fieldPath :: forall (table :: (Type -> Type) -> Type) ty f. Applicative f => (Text -> f Text) -> TableField table ty -> f (TableField table ty)
- type TableSettings (table :: (Type -> Type) -> Type) = table (TableField table)
- type HaskellTable (table :: (Type -> Type) -> Type) = table Identity
- type TableSkeleton (table :: (Type -> Type) -> Type) = table Ignored
- data Ignored x = Ignored
- class GFieldsFulfillConstraint (c :: Type -> Constraint) (exposed :: Type -> Type) (withconstraint :: Type -> Type) where
- gWithConstrainedFields :: Proxy c -> Proxy exposed -> withconstraint ()
- type FieldsFulfillConstraint (c :: Type -> Constraint) (t :: (Type -> Type) -> Type) = (Generic (t (HasConstraint c)), Generic (t Identity), Generic (t Exposed), GFieldsFulfillConstraint c (Rep (t Exposed)) (Rep (t (HasConstraint c))))
- type FieldsFulfillConstraintNullable (c :: Type -> Constraint) (t :: (Type -> Type) -> Type) = (Generic (t (Nullable (HasConstraint c))), Generic (t (Nullable Identity)), Generic (t (Nullable Exposed)), GFieldsFulfillConstraint c (Rep (t (Nullable Exposed))) (Rep (t (Nullable (HasConstraint c)))))
- data WithConstraint (c :: Type -> Constraint) x where
- WithConstraint :: forall (c :: Type -> Constraint) x. c x => x -> WithConstraint c x
- data HasConstraint (c :: Type -> Constraint) x where
- HasConstraint :: forall (c :: Type -> Constraint) x. c x => HasConstraint c x
- class TagReducesTo (f :: Type -> Type) (f' :: Type -> Type) | f -> f' where
- type family ReplaceBaseTag (tag :: Type -> Type) (f :: Type -> Type) :: Type -> Type where ...
- withConstrainedFields :: forall (c :: Type -> Constraint) tbl. (FieldsFulfillConstraint c tbl, Beamable tbl) => tbl Identity -> tbl (WithConstraint c)
- withConstraints :: forall (c :: Type -> Constraint) tbl. (Beamable tbl, FieldsFulfillConstraint c tbl) => tbl (HasConstraint c)
- withNullableConstrainedFields :: forall (c :: Type -> Constraint) tbl. (FieldsFulfillConstraintNullable c tbl, Beamable tbl) => tbl (Nullable Identity) -> tbl (Nullable (WithConstraint c))
- withNullableConstraints :: forall (c :: Type -> Constraint) tbl. (Beamable tbl, FieldsFulfillConstraintNullable c tbl) => tbl (Nullable (HasConstraint c))
- class (Typeable table, Beamable table, Beamable (PrimaryKey table)) => Table (table :: (Type -> Type) -> Type) where
- data PrimaryKey (table :: (Type -> Type) -> Type) (column :: Type -> Type)
- primaryKey :: forall (column :: Type -> Type). table column -> PrimaryKey table column
- class Beamable (table :: (Type -> Type) -> Type) where
- zipBeamFieldsM :: forall m (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type). Applicative m => (forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a)) -> table f -> table g -> m (table h)
- tblSkeleton :: TableSkeleton table
- class Retaggable (f :: Type -> Type) x | x -> f where
- data ((f :: k -> Type) :*: (g :: k -> Type)) (p :: k) = (f p) :*: (g p)
- defTblFieldSettings :: (Generic (TableSettings table), GDefaultTableFieldSettings (Rep (TableSettings table) ())) => TableSettings table
- tableValuesNeeded :: forall (table :: (Type -> Type) -> Type). Beamable table => Proxy table -> Int
- pk :: forall t (f :: Type -> Type). Table t => t f -> PrimaryKey t f
- allBeamValues :: forall table (f :: Type -> Type) b. Beamable table => (forall a. Columnar' f a -> b) -> table f -> [b]
- changeBeamRep :: forall table (f :: Type -> Type) (g :: Type -> Type). Beamable table => (forall a. Columnar' f a -> Columnar' g a) -> table f -> table g
- alongsideTable :: forall tbl (f :: Type -> Type) (g :: Type -> Type). Beamable tbl => tbl f -> tbl g -> tbl (Columnar' f :*: Columnar' g)
- defaultFieldName :: NonEmpty Text -> Text
- class GZipTables (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type) (exposedRep :: Type -> Type) (fRep :: Type -> Type) (gRep :: Type -> Type) (hRep :: Type -> Type) where
- gZipTables :: Applicative m => Proxy exposedRep -> (forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a)) -> fRep () -> gRep () -> m (hRep ())
- class GTableSkeleton (x :: Type -> Type) where
- gTblSkeleton :: Proxy x -> x ()
- class GZipDatabase be (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type) (x :: Type -> Type) (y :: Type -> Type) (z :: Type -> Type) where
- gZipDatabase :: Applicative m => (Proxy f, Proxy g, Proxy h, Proxy be) -> (forall tbl. (IsDatabaseEntity be tbl, DatabaseEntityRegularRequirements be tbl) => f tbl -> g tbl -> m (h tbl)) -> x () -> y () -> m (z ())
- class GAutoDbSettings x where
- autoDbSettings' :: x
- class GDefaultTableFieldSettings x where
- gDefTblFieldSettings :: Proxy x -> x
- type family ChooseSubTableStrategy (tbl :: (Type -> Type) -> Type) (sub :: (Type -> Type) -> Type) :: SubTableStrategy where ...
- class SubTableStrategyImpl (strategy :: SubTableStrategy) (f :: Type -> Type) (sub :: (Type -> Type) -> Type)
Database Types
class Database be (db :: (Type -> Type) -> Type) 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 :: (Type -> Type) -> Type) = 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 #
data DatabaseEntityDescriptor be entityType Source #
type DatabaseEntityDefaultRequirements be entityType Source #
type DatabaseEntityRegularRequirements be entityType Source #
dbEntityName :: Lens' (DatabaseEntityDescriptor be entityType) Text Source #
dbEntitySchema :: Traversal' (DatabaseEntityDescriptor be entityType) (Maybe Text) Source #
dbEntityAuto :: Text -> DatabaseEntityDescriptor be entityType Source #
Instances
data family DatabaseEntityDescriptor be entityType Source #
Instances
RenamableWithRule (FieldRenamer (DatabaseEntityDescriptor be (DomainTypeEntity ty))) Source # | |
Defined in Database.Beam.Schema.Tables renamingFields :: (NonEmpty Text -> Text) -> FieldRenamer (DatabaseEntityDescriptor be (DomainTypeEntity ty)) Source # | |
Beamable tbl => RenamableWithRule (FieldRenamer (DatabaseEntityDescriptor be (TableEntity tbl))) Source # | |
Defined in Database.Beam.Schema.Tables renamingFields :: (NonEmpty Text -> Text) -> FieldRenamer (DatabaseEntityDescriptor be (TableEntity tbl)) Source # | |
Beamable tbl => RenamableWithRule (FieldRenamer (DatabaseEntityDescriptor be (ViewEntity tbl))) Source # | |
Defined in Database.Beam.Schema.Tables renamingFields :: (NonEmpty Text -> Text) -> FieldRenamer (DatabaseEntityDescriptor be (ViewEntity tbl)) Source # | |
data DatabaseEntityDescriptor be (DomainTypeEntity ty) Source # | |
Defined in Database.Beam.Schema.Tables | |
data DatabaseEntityDescriptor be (TableEntity tbl) Source # | |
Defined in Database.Beam.Schema.Tables data DatabaseEntityDescriptor be (TableEntity tbl) where
| |
data DatabaseEntityDescriptor be (ViewEntity tbl) Source # | |
Defined in Database.Beam.Schema.Tables data DatabaseEntityDescriptor be (ViewEntity tbl) where
|
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.
DatabaseEntity :: forall be entityType (db :: (Type -> Type) -> Type). IsDatabaseEntity be entityType => DatabaseEntityDescriptor be entityType -> DatabaseEntity be db entityType |
Instances
Database be db => RenamableWithRule (db (EntityModification (DatabaseEntity be db) be)) Source # | |
Defined in Database.Beam.Schema.Tables renamingFields :: (NonEmpty Text -> Text) -> db (EntityModification (DatabaseEntity be db) be) Source # | |
IsDatabaseEntity be entity => RenamableWithRule (EntityModification (DatabaseEntity be db) be entity) Source # | |
Defined in Database.Beam.Schema.Tables renamingFields :: (NonEmpty Text -> Text) -> EntityModification (DatabaseEntity be db) be entity Source # | |
(Selector f, IsDatabaseEntity be x, DatabaseEntityDefaultRequirements be x) => GAutoDbSettings (S1 f (K1 R (DatabaseEntity be db x) :: Type -> Type) p) Source # | |
Defined in Database.Beam.Schema.Tables autoDbSettings' :: S1 f (K1 R (DatabaseEntity be db x) :: Type -> Type) p Source # | |
(Database be embedded, Generic (DatabaseSettings be embedded), GAutoDbSettings (Rep (DatabaseSettings be embedded) ())) => GAutoDbSettings (S1 f (K1 R (embedded (DatabaseEntity be super)) :: Type -> Type) p) Source # | |
Defined in Database.Beam.Schema.Tables autoDbSettings' :: S1 f (K1 R (embedded (DatabaseEntity be super)) :: Type -> Type) p Source # |
data TableEntity (tbl :: (Type -> Type) -> Type) Source #
Instances
Beamable tbl => IsDatabaseEntity be (TableEntity tbl) Source # | |||||||||||||
Defined in Database.Beam.Schema.Tables
dbEntityName :: Lens' (DatabaseEntityDescriptor be (TableEntity tbl)) Text Source # dbEntitySchema :: Traversal' (DatabaseEntityDescriptor be (TableEntity tbl)) (Maybe Text) Source # dbEntityAuto :: Text -> DatabaseEntityDescriptor be (TableEntity tbl) Source # | |||||||||||||
Beamable tbl => RenamableWithRule (FieldRenamer (DatabaseEntityDescriptor be (TableEntity tbl))) Source # | |||||||||||||
Defined in Database.Beam.Schema.Tables renamingFields :: (NonEmpty Text -> Text) -> FieldRenamer (DatabaseEntityDescriptor be (TableEntity tbl)) Source # | |||||||||||||
type DatabaseEntityDefaultRequirements be (TableEntity tbl) Source # | |||||||||||||
Defined in Database.Beam.Schema.Tables type DatabaseEntityDefaultRequirements be (TableEntity tbl) = (GDefaultTableFieldSettings (Rep (TableSettings tbl) ()), Generic (TableSettings tbl), Table tbl, Beamable tbl) | |||||||||||||
data DatabaseEntityDescriptor be (TableEntity tbl) Source # | |||||||||||||
Defined in Database.Beam.Schema.Tables data DatabaseEntityDescriptor be (TableEntity tbl) where
| |||||||||||||
type DatabaseEntityRegularRequirements be (TableEntity tbl) Source # | |||||||||||||
Defined in Database.Beam.Schema.Tables |
data ViewEntity (view :: (Type -> Type) -> Type) Source #
Instances
Beamable tbl => IsDatabaseEntity be (ViewEntity tbl) Source # | |||||||||||||
Defined in Database.Beam.Schema.Tables
dbEntityName :: Lens' (DatabaseEntityDescriptor be (ViewEntity tbl)) Text Source # dbEntitySchema :: Traversal' (DatabaseEntityDescriptor be (ViewEntity tbl)) (Maybe Text) Source # dbEntityAuto :: Text -> DatabaseEntityDescriptor be (ViewEntity tbl) Source # | |||||||||||||
Beamable tbl => RenamableWithRule (FieldRenamer (DatabaseEntityDescriptor be (ViewEntity tbl))) Source # | |||||||||||||
Defined in Database.Beam.Schema.Tables renamingFields :: (NonEmpty Text -> Text) -> FieldRenamer (DatabaseEntityDescriptor be (ViewEntity tbl)) Source # | |||||||||||||
type DatabaseEntityDefaultRequirements be (ViewEntity tbl) Source # | |||||||||||||
Defined in Database.Beam.Schema.Tables type DatabaseEntityDefaultRequirements be (ViewEntity tbl) = (GDefaultTableFieldSettings (Rep (TableSettings tbl) ()), Generic (TableSettings tbl), Beamable tbl) | |||||||||||||
data DatabaseEntityDescriptor be (ViewEntity tbl) Source # | |||||||||||||
Defined in Database.Beam.Schema.Tables data DatabaseEntityDescriptor be (ViewEntity tbl) where
| |||||||||||||
type DatabaseEntityRegularRequirements be (ViewEntity tbl) Source # | |||||||||||||
Defined in Database.Beam.Schema.Tables |
data DomainTypeEntity ty Source #
Instances
IsDatabaseEntity be (DomainTypeEntity ty) Source # | |||||||||||||
Defined in Database.Beam.Schema.Tables
dbEntityName :: Lens' (DatabaseEntityDescriptor be (DomainTypeEntity ty)) Text Source # dbEntitySchema :: Traversal' (DatabaseEntityDescriptor be (DomainTypeEntity ty)) (Maybe Text) Source # dbEntityAuto :: Text -> DatabaseEntityDescriptor be (DomainTypeEntity ty) Source # | |||||||||||||
RenamableWithRule (FieldRenamer (DatabaseEntityDescriptor be (DomainTypeEntity ty))) Source # | |||||||||||||
Defined in Database.Beam.Schema.Tables renamingFields :: (NonEmpty Text -> Text) -> FieldRenamer (DatabaseEntityDescriptor be (DomainTypeEntity ty)) Source # | |||||||||||||
type DatabaseEntityDefaultRequirements be (DomainTypeEntity ty) Source # | |||||||||||||
Defined in Database.Beam.Schema.Tables | |||||||||||||
data DatabaseEntityDescriptor be (DomainTypeEntity ty) Source # | |||||||||||||
Defined in Database.Beam.Schema.Tables | |||||||||||||
type DatabaseEntityRegularRequirements be (DomainTypeEntity ty) Source # | |||||||||||||
Defined in Database.Beam.Schema.Tables |
dbEntityDescriptor :: forall be (db :: (Type -> Type) -> Type) entityType r. Getting r (DatabaseEntity be db entityType) (DatabaseEntityDescriptor be entityType) Source #
type DatabaseModification (f :: Type -> Type) be (db :: (Type -> Type) -> Type) = 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 :: Type -> Type) 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.
EntityModification (Endo (f e)) |
Instances
Database be db => RenamableWithRule (db (EntityModification (DatabaseEntity be db) be)) Source # | |
Defined in Database.Beam.Schema.Tables renamingFields :: (NonEmpty Text -> Text) -> db (EntityModification (DatabaseEntity be db) be) Source # | |
IsDatabaseEntity be entity => RenamableWithRule (EntityModification (DatabaseEntity be db) be entity) Source # | |
Defined in Database.Beam.Schema.Tables renamingFields :: (NonEmpty Text -> Text) -> EntityModification (DatabaseEntity be db) be entity Source # | |
Monoid (EntityModification f be e) Source # | |
Defined in Database.Beam.Schema.Tables mempty :: EntityModification f be e # mappend :: EntityModification f be e -> EntityModification f be e -> EntityModification f be e # mconcat :: [EntityModification f be e] -> EntityModification f be e # | |
Semigroup (EntityModification f be e) Source # | |
Defined in Database.Beam.Schema.Tables (<>) :: EntityModification f be e -> EntityModification f be e -> EntityModification f be e # sconcat :: NonEmpty (EntityModification f be e) -> EntityModification f be e # stimes :: Integral b => b -> EntityModification f be e -> EntityModification f be e # |
newtype FieldModification (f :: Type -> Type) a Source #
A newtype wrapper around 'Columnar f a -> Columnar f a' (i.e., an
endomorphism between Columnar
s over f
). You usually want to use
fieldNamed
or the IsString
instance to rename the field, when 'f ~
TableField'
FieldModification (Columnar f a -> Columnar f a) |
Instances
(Beamable tbl, RenamableField f) => RenamableWithRule (tbl (FieldModification f)) Source # | |
Defined in Database.Beam.Schema.Tables renamingFields :: (NonEmpty Text -> Text) -> tbl (FieldModification f) Source # | |
IsString (FieldModification (TableField tbl) a) Source # | |
Defined in Database.Beam.Schema.Tables fromString :: String -> FieldModification (TableField tbl) a # |
dbModification :: forall (f :: Type -> Type) 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 :: Type -> Type) 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 :: Type -> ((Type -> Type) -> Type) -> Type -> Type). 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 = setEntityName "Table_1" <> modifyTableFields tableModification { table1Field1 = "first_name" } }
withTableModification :: forall tbl (f :: Type -> Type). 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 :: forall tbl be (db :: (Type -> Type) -> Type). (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 TableEntity
s. 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 :: forall be entity (db :: (Type -> Type) -> Type). IsDatabaseEntity be entity => (Text -> Text) -> EntityModification (DatabaseEntity be db) be entity Source #
Construct an EntityModification
to rename any database entity
setEntityName :: forall be entity (db :: (Type -> Type) -> Type). IsDatabaseEntity be entity => Text -> EntityModification (DatabaseEntity be db) be entity Source #
Change the entity name without consulting the beam-assigned one
modifyTableFields :: forall tbl be (db :: (Type -> Type) -> Type). tbl (FieldModification (TableField tbl)) -> EntityModification (DatabaseEntity be db) be (TableEntity tbl) Source #
Construct an EntityModification
to rename the fields of a TableEntity
fieldNamed :: forall (tbl :: (Type -> Type) -> Type) a. 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 :: forall be entity (db :: (Type -> Type) -> Type). 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
setEntitySchema :: forall be entity (db :: (Type -> Type) -> Type). IsDatabaseEntity be entity => Maybe Text -> EntityModification (DatabaseEntity be db) be entity Source #
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
embedDatabase :: forall be embedded (db :: (Type -> Type) -> Type). Database be embedded => DatabaseSettings be embedded -> embedded (EntityModification (DatabaseEntity be db) be) Source #
Embed database settings in a larger database
class RenamableWithRule mod where Source #
Instances
RenamableWithRule (FieldRenamer (DatabaseEntityDescriptor be (DomainTypeEntity ty))) Source # | |
Defined in Database.Beam.Schema.Tables renamingFields :: (NonEmpty Text -> Text) -> FieldRenamer (DatabaseEntityDescriptor be (DomainTypeEntity ty)) Source # | |
Beamable tbl => RenamableWithRule (FieldRenamer (DatabaseEntityDescriptor be (TableEntity tbl))) Source # | |
Defined in Database.Beam.Schema.Tables renamingFields :: (NonEmpty Text -> Text) -> FieldRenamer (DatabaseEntityDescriptor be (TableEntity tbl)) Source # | |
Beamable tbl => RenamableWithRule (FieldRenamer (DatabaseEntityDescriptor be (ViewEntity tbl))) Source # | |
Defined in Database.Beam.Schema.Tables renamingFields :: (NonEmpty Text -> Text) -> FieldRenamer (DatabaseEntityDescriptor be (ViewEntity tbl)) Source # | |
Database be db => RenamableWithRule (db (EntityModification (DatabaseEntity be db) be)) Source # | |
Defined in Database.Beam.Schema.Tables renamingFields :: (NonEmpty Text -> Text) -> db (EntityModification (DatabaseEntity be db) be) Source # | |
(Beamable tbl, RenamableField f) => RenamableWithRule (tbl (FieldModification f)) Source # | |
Defined in Database.Beam.Schema.Tables renamingFields :: (NonEmpty Text -> Text) -> tbl (FieldModification f) Source # | |
IsDatabaseEntity be entity => RenamableWithRule (EntityModification (DatabaseEntity be db) be entity) Source # | |
Defined in Database.Beam.Schema.Tables renamingFields :: (NonEmpty Text -> Text) -> EntityModification (DatabaseEntity be db) be entity Source # |
class RenamableField (f :: Type -> Type) where Source #
renameField :: Proxy f -> Proxy a -> (NonEmpty Text -> Text) -> Columnar f a -> Columnar f a Source #
Instances
RenamableField (TableField tbl) Source # | |
Defined in Database.Beam.Schema.Tables renameField :: Proxy (TableField tbl) -> Proxy a -> (NonEmpty Text -> Text) -> Columnar (TableField tbl) a -> Columnar (TableField tbl) a Source # |
newtype FieldRenamer entity Source #
FieldRenamer | |
|
Instances
RenamableWithRule (FieldRenamer (DatabaseEntityDescriptor be (DomainTypeEntity ty))) Source # | |
Defined in Database.Beam.Schema.Tables renamingFields :: (NonEmpty Text -> Text) -> FieldRenamer (DatabaseEntityDescriptor be (DomainTypeEntity ty)) Source # | |
Beamable tbl => RenamableWithRule (FieldRenamer (DatabaseEntityDescriptor be (TableEntity tbl))) Source # | |
Defined in Database.Beam.Schema.Tables renamingFields :: (NonEmpty Text -> Text) -> FieldRenamer (DatabaseEntityDescriptor be (TableEntity tbl)) Source # | |
Beamable tbl => RenamableWithRule (FieldRenamer (DatabaseEntityDescriptor be (ViewEntity tbl))) Source # | |
Defined in Database.Beam.Schema.Tables renamingFields :: (NonEmpty Text -> Text) -> FieldRenamer (DatabaseEntityDescriptor be (ViewEntity tbl)) Source # |
data Lenses (t :: (Type -> Type) -> Type) (f :: Type -> Type) x Source #
Instances
(Generic (sub (Nullable m)), Generic (sub (Nullable (Lenses t m))), GTableLenses t m (Rep (sub (Nullable m))) (Rep (sub (Nullable (Lenses t m))))) => GTableLenses t m (K1 R (sub (Nullable m)) :: k -> Type) (K1 R (sub (Nullable (Lenses t m))) :: Type -> Type) Source # | |
(Generic (sub m), Generic (sub (Lenses t m)), GTableLenses t m (Rep (sub m)) (Rep (sub (Lenses t m)))) => GTableLenses t m (K1 R (sub m) :: k -> Type) (K1 R (sub (Lenses t m)) :: Type -> Type) Source # | |
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 PrimaryKey
s 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 just_
and nothing_
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.
type C (f :: Type -> Type) a = Columnar f a Source #
A short type-alias for Columnar
. May shorten your schema definitions
newtype Columnar' (f :: Type -> Type) 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'
newtype ComposeColumnar (f :: Type -> Type) (g :: Type -> Type) a Source #
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
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 (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 :: 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 # | |
(Generic (sub (Nullable m)), Generic (sub (Nullable (Lenses t m))), GTableLenses t m (Rep (sub (Nullable m))) (Rep (sub (Nullable (Lenses t m))))) => GTableLenses t m (K1 R (sub (Nullable m)) :: k -> Type) (K1 R (sub (Nullable (Lenses t m))) :: Type -> Type) Source # | |
Beamable tbl => GZipTables f g h (K1 R (tbl (Nullable Exposed)) :: Type -> Type) (K1 R (tbl (Nullable f)) :: Type -> Type) (K1 R (tbl (Nullable g)) :: Type -> Type) (K1 R (tbl (Nullable h)) :: Type -> Type) 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 # | |
(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 # | |
Defined in Database.Beam.Backend.SQL.Row fromBackendRow :: FromBackendRowM be (tbl (Nullable Identity)) Source # valuesNeeded :: Proxy be -> Proxy (tbl (Nullable Identity)) -> Int Source # | |
Beamable tbl => ThreadRewritable s (tbl (Nullable (QGenExpr ctxt syntax s))) Source # | |
Defined in Database.Beam.Query.Internal 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 # | |
Defined in Database.Beam.Query.Combinators isJust_ :: t (Nullable (QGenExpr ctxt be s)) -> QGenExpr ctxt0 be s Bool Source # isNothing_ :: t (Nullable (QGenExpr ctxt be s)) -> QGenExpr ctxt0 be s Bool Source # maybe_ :: QGenExpr ctxt0 be s y -> (t (QGenExpr ctxt be s) -> QGenExpr ctxt0 be s y) -> t (Nullable (QGenExpr ctxt be s)) -> QGenExpr ctxt0 be s y Source # | |
FromBackendRow be (t (Nullable Identity)) => GFromBackendRow be (K1 R (t (Nullable Exposed)) :: Type -> Type) (K1 R (t (Nullable Identity)) :: Type -> Type) Source # | |
Defined in Database.Beam.Backend.SQL.Row | |
FieldsFulfillConstraintNullable c t => GFieldsFulfillConstraint c (K1 R (t (Nullable Exposed)) :: Type -> Type) (K1 R (t (Nullable (HasConstraint c))) :: Type -> Type) Source # | |
(Beamable table, BeamSqlBackend be, FieldsFulfillConstraintNullable (BeamSqlBackendCanSerialize be) table) => SqlValable (table (Nullable (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 rewriteContext :: Proxy ctxt -> tbl (Nullable (QGenExpr old syntax s)) -> WithRewrittenContext (tbl (Nullable (QGenExpr old syntax s))) ctxt Source # | |
TagReducesTo f f' => TagReducesTo (Nullable f) f' Source # | |
Beamable tbl => QGroupable (tbl (Nullable (QExpr be s))) (tbl (Nullable (QGroupExpr be s))) Source # |
|
Defined in Database.Beam.Query.Aggregate | |
(Table t, BeamSqlBackend be) => SqlJustable (t (QExpr be s)) (t (Nullable (QExpr be s))) Source # | |
Table t => SqlJustable (t Identity) (t (Nullable Identity)) Source # | |
(Table t, BeamSqlBackend be) => SqlJustable (PrimaryKey t (QExpr be s)) (PrimaryKey t (Nullable (QExpr be s))) Source # | |
Defined in Database.Beam.Query.Combinators just_ :: PrimaryKey t (QExpr be s) -> PrimaryKey t (Nullable (QExpr be s)) Source # | |
Table t => SqlJustable (PrimaryKey t Identity) (PrimaryKey t (Nullable Identity)) Source # | |
Defined in Database.Beam.Query.Combinators just_ :: PrimaryKey t Identity -> PrimaryKey t (Nullable Identity) Source # | |
Beamable tbl => GTableSkeleton (K1 R (tbl (Nullable Ignored)) :: Type -> Type) 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 (==.) :: 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 # | |
Defined in Database.Beam.Query.Internal type WithRewrittenThread s s' (tbl (Nullable (QGenExpr ctxt syntax s))) = tbl (Nullable (QGenExpr ctxt syntax s')) | |
type HaskellLiteralForQExpr (table (Nullable f)) Source # | |
Defined in Database.Beam.Query.Combinators | |
type QExprToField (table (Nullable (QGenExpr context syntax s))) Source # | |
Defined in Database.Beam.Query.Types | |
type QExprToIdentity (table (Nullable c)) 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)) |
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.
TableField | |
|
Instances
RenamableField (TableField tbl) Source # | |
Defined in Database.Beam.Schema.Tables renameField :: Proxy (TableField tbl) -> Proxy a -> (NonEmpty Text -> Text) -> Columnar (TableField tbl) a -> Columnar (TableField tbl) a Source # | |
TagReducesTo (TableField tbl) (TableField tbl) Source # | |
Defined in Database.Beam.Schema.Tables reduceTag :: Functor m => (Columnar' (TableField tbl) a' -> m (Columnar' (TableField tbl) a')) -> Columnar' (TableField tbl) a -> m (Columnar' (TableField tbl) a) Source # | |
IsString (FieldModification (TableField tbl) a) Source # | |
Defined in Database.Beam.Schema.Tables fromString :: String -> FieldModification (TableField tbl) a # | |
Show (TableField table ty) Source # | |
Defined in Database.Beam.Schema.Tables showsPrec :: Int -> TableField table ty -> ShowS # show :: TableField table ty -> String # showList :: [TableField table ty] -> ShowS # | |
Eq (TableField table ty) Source # | |
Defined in Database.Beam.Schema.Tables (==) :: TableField table ty -> TableField table ty -> Bool # (/=) :: TableField table ty -> TableField table ty -> Bool # | |
Selector f => GDefaultTableFieldSettings (S1 f (K1 R (TableField table field) :: Type -> Type) p) Source # | |
Defined in Database.Beam.Schema.Tables |
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
(fa ~ Columnar f a, ga ~ Columnar g a, ha ~ Columnar h a, ha ~ Columnar h a) => GZipTables f g h (K1 R (Exposed a) :: Type -> Type) (K1 R fa :: Type -> Type) (K1 R ga :: Type -> Type) (K1 R ha :: Type -> Type) Source # | |
Beamable tbl => GZipTables f g h (K1 R (tbl Exposed) :: Type -> Type) (K1 R (tbl f) :: Type -> Type) (K1 R (tbl g) :: Type -> Type) (K1 R (tbl h) :: Type -> Type) Source # | |
Beamable tbl => GZipTables f g h (K1 R (tbl (Nullable Exposed)) :: Type -> Type) (K1 R (tbl (Nullable f)) :: Type -> Type) (K1 R (tbl (Nullable g)) :: Type -> Type) (K1 R (tbl (Nullable h)) :: Type -> Type) Source # | |
FromBackendRow be x => GFromBackendRow be (K1 R (Exposed x) :: Type -> Type) (K1 R (Identity x) :: Type -> Type) Source # | |
FromBackendRow be x => GFromBackendRow be (K1 R (Exposed x) :: Type -> Type) (K1 R x :: Type -> Type) Source # | |
FromBackendRow be (t Identity) => GFromBackendRow be (K1 R (t Exposed) :: Type -> Type) (K1 R (t Identity) :: Type -> Type) Source # | |
FromBackendRow be (t (Nullable Identity)) => GFromBackendRow be (K1 R (t (Nullable Exposed)) :: Type -> Type) (K1 R (t (Nullable Identity)) :: Type -> Type) Source # | |
Defined in Database.Beam.Backend.SQL.Row | |
c x => GFieldsFulfillConstraint c (K1 R (Exposed x) :: Type -> Type) (K1 R (HasConstraint c x) :: Type -> Type) Source # | |
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 # | |
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 # | |
fieldName :: forall (table :: (Type -> Type) -> Type) ty f. Functor f => (Text -> f Text) -> TableField table ty -> f (TableField table ty) Source #
Van Laarhoven lens to retrieve or set the field name from a TableField
.
fieldPath :: forall (table :: (Type -> Type) -> Type) ty f. Applicative f => (Text -> f Text) -> TableField table ty -> f (TableField table ty) Source #
type TableSettings (table :: (Type -> Type) -> Type) = 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 :: (Type -> Type) -> Type) = table Identity Source #
The regular Haskell version of the table. Equivalent to 'tbl Identity'
Column tag that ignores the type.
class GFieldsFulfillConstraint (c :: Type -> Constraint) (exposed :: Type -> Type) (withconstraint :: Type -> Type) where Source #
gWithConstrainedFields :: Proxy c -> Proxy exposed -> withconstraint () Source #
Instances
GFieldsFulfillConstraint c (U1 :: Type -> Type) (U1 :: Type -> Type) Source # | |
Defined in Database.Beam.Schema.Tables | |
(GFieldsFulfillConstraint c aExp aC, GFieldsFulfillConstraint c bExp bC) => GFieldsFulfillConstraint c (aExp :*: bExp) (aC :*: bC) Source # | |
Defined in Database.Beam.Schema.Tables | |
c x => GFieldsFulfillConstraint c (K1 R (Exposed x) :: Type -> Type) (K1 R (HasConstraint c x) :: Type -> Type) Source # | |
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 # | |
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 # | |
GFieldsFulfillConstraint c exposed withconstraint => GFieldsFulfillConstraint c (M1 s m exposed) (M1 s m withconstraint) Source # | |
Defined in Database.Beam.Schema.Tables |
type FieldsFulfillConstraint (c :: Type -> Constraint) (t :: (Type -> Type) -> Type) = (Generic (t (HasConstraint c)), Generic (t Identity), Generic (t Exposed), GFieldsFulfillConstraint c (Rep (t Exposed)) (Rep (t (HasConstraint c)))) Source #
type FieldsFulfillConstraintNullable (c :: Type -> Constraint) (t :: (Type -> Type) -> Type) = (Generic (t (Nullable (HasConstraint c))), Generic (t (Nullable Identity)), Generic (t (Nullable Exposed)), GFieldsFulfillConstraint c (Rep (t (Nullable Exposed))) (Rep (t (Nullable (HasConstraint c))))) Source #
data WithConstraint (c :: Type -> Constraint) x where Source #
Carry a constraint instance and the value it applies to.
WithConstraint :: forall (c :: Type -> Constraint) x. c x => x -> WithConstraint c x |
data HasConstraint (c :: Type -> Constraint) x where Source #
Carry a constraint instance.
HasConstraint :: forall (c :: Type -> Constraint) x. c x => HasConstraint c x |
Instances
c x => GFieldsFulfillConstraint c (K1 R (Exposed x) :: Type -> Type) (K1 R (HasConstraint c x) :: Type -> Type) Source # | |
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 # | |
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 # | |
class TagReducesTo (f :: Type -> Type) (f' :: Type -> Type) | f -> f' where Source #
Class to automatically unwrap nested Nullables
reduceTag :: Functor m => (Columnar' f' a' -> m (Columnar' f' a')) -> Columnar' f a -> m (Columnar' f a) Source #
Instances
TagReducesTo f f' => TagReducesTo (Nullable f) f' Source # | |
TagReducesTo (TableField tbl) (TableField tbl) Source # | |
Defined in Database.Beam.Schema.Tables 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 :: Type -> Type) (f :: Type -> Type) :: Type -> Type where ... Source #
ReplaceBaseTag tag (Nullable f) = Nullable (ReplaceBaseTag tag f) | |
ReplaceBaseTag tag x = tag |
withConstrainedFields :: forall (c :: Type -> Constraint) tbl. (FieldsFulfillConstraint c tbl, Beamable tbl) => tbl Identity -> tbl (WithConstraint c) Source #
withConstraints :: forall (c :: Type -> Constraint) tbl. (Beamable tbl, FieldsFulfillConstraint c tbl) => tbl (HasConstraint c) Source #
withNullableConstrainedFields :: forall (c :: Type -> Constraint) tbl. (FieldsFulfillConstraintNullable c tbl, Beamable tbl) => tbl (Nullable Identity) -> tbl (Nullable (WithConstraint c)) Source #
withNullableConstraints :: forall (c :: Type -> Constraint) tbl. (Beamable tbl, FieldsFulfillConstraintNullable c tbl) => tbl (Nullable (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 typesText
,Text
,UTCTime
, and 'Maybe Text' respectfully. - Since
_blogPostSlug
,_blogPostBody
,_blogPostDate
,_blogPostAuthor
must be provided (i.e, they cannot containNothing
), they will be given SQL NOT NULL constraints._blogPostTagline
is declaredMaybe
soNothing
will be stored as NULL in the database._blogPostImageGallery
will be allowed to be empty because it uses theNullable
tag modifier. blogPostAuthor
references theAuthorT
table (not given here) and is required.blogPostImageGallery
references theImageGalleryT
table (not given here), but this relation is not required (i.e., it may beNothing
. SeeNullable
).
data PrimaryKey (table :: (Type -> Type) -> Type) (column :: 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
.
primaryKey :: forall (column :: Type -> Type). 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 :: (Type -> Type) -> Type) 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.
Nothing
zipBeamFieldsM :: forall m (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type). Applicative m => (forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a)) -> table f -> table g -> m (table h) Source #
default zipBeamFieldsM :: forall (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type) m. (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 :: Type -> Type) x | x -> f where Source #
retag :: forall (tag :: (Type -> Type) -> Type -> Type). (forall a. Columnar' f a -> Columnar' (tag f) a) -> x -> Retag tag x Source #
Instances
Beamable tbl => Retaggable f (tbl f) Source # | |
(Retaggable f a, Retaggable f b) => Retaggable f (a, b) Source # | |
(Retaggable f a, Retaggable f b, Retaggable f c) => Retaggable f (a, b, c) Source # | |
(Retaggable f a, Retaggable f b, Retaggable f c, Retaggable f d) => Retaggable f (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 # | |
(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 # | |
(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 # | |
(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 # | |
Retaggable (QGenExpr ctxt expr s) (QGenExpr ctxt expr s t) Source # | |
data ((f :: k -> Type) :*: (g :: k -> Type)) (p :: k) infixr 6 #
Products: encode multiple arguments to constructors
(f p) :*: (g p) infixr 6 |
Instances
(GZipDatabase be f g h ax ay az, GZipDatabase be f g h bx by bz) => GZipDatabase be f g h (ax :*: bx) (ay :*: by) (az :*: bz) Source # | |||||
Defined in Database.Beam.Schema.Tables gZipDatabase :: Applicative m => (Proxy f, Proxy g, Proxy h, Proxy be) -> (forall tbl. (IsDatabaseEntity be tbl, DatabaseEntityRegularRequirements be tbl) => f tbl -> g tbl -> m (h tbl)) -> (ax :*: bx) () -> (ay :*: by) () -> m ((az :*: bz) ()) Source # | |||||
(Monoid pairs, RecordToPairs enc pairs arity a, RecordToPairs enc pairs arity b) => RecordToPairs enc pairs arity (a :*: b) | |||||
Defined in Data.Aeson.Types.ToJSON recordToPairs :: Options -> ToArgs enc arity a0 -> (a :*: b) a0 -> pairs | |||||
(GTableLenses t m a aLens, GTableLenses t m b bLens) => GTableLenses t m (a :*: b :: k -> Type) (aLens :*: bLens) Source # | |||||
Defined in Database.Beam.Schema.Lenses | |||||
(GZipTables f g h exp1 f1 g1 h1, GZipTables f g h exp2 f2 g2 h2) => GZipTables f g h (exp1 :*: exp2) (f1 :*: f2) (g1 :*: g2) (h1 :*: h2) Source # | |||||
Defined in Database.Beam.Schema.Tables | |||||
(EncodeProduct arity a, EncodeProduct arity b) => GToJSON' Encoding arity (a :*: b) | |||||
(WriteProduct arity a, WriteProduct arity b, ProductSize a, ProductSize b) => GToJSON' Value arity (a :*: b) | |||||
(GDatabaseLenses db a al, GDatabaseLenses db b bl) => GDatabaseLenses db (a :*: b :: k -> Type) (al :*: bl) Source # | |||||
Defined in Database.Beam.Schema.Lenses | |||||
(FieldNames a, FieldNames b) => FieldNames (a :*: b :: k -> Type) | |||||
Defined in Data.Aeson.Types.FromJSON fieldNames :: forall (a0 :: k). (a :*: b) a0 -> [String] -> [String] | |||||
(ProductFromJSON arity a, ProductFromJSON arity b) => ProductFromJSON arity (a :*: b) | |||||
Defined in Data.Aeson.Types.FromJSON | |||||
(RecordFromJSON' arity a, RecordFromJSON' arity b) => RecordFromJSON' arity (a :*: b) | |||||
Defined in Data.Aeson.Types.FromJSON | |||||
(EncodeProduct arity a, EncodeProduct arity b) => EncodeProduct arity (a :*: b) | |||||
Defined in Data.Aeson.Types.ToJSON | |||||
(WriteProduct arity a, WriteProduct arity b) => WriteProduct arity (a :*: b) | |||||
(GNFData arity a, GNFData arity b) => GNFData arity (a :*: b) | |||||
Defined in Control.DeepSeq | |||||
Generic1 (f :*: g :: k -> Type) | |||||
Defined in GHC.Internal.Generics
| |||||
(GFromBackendRow be aExp a, GFromBackendRow be bExp b) => GFromBackendRow be (aExp :*: bExp) (a :*: b) Source # | |||||
Defined in Database.Beam.Backend.SQL.Row | |||||
(GFieldsFulfillConstraint c aExp aC, GFieldsFulfillConstraint c bExp bC) => GFieldsFulfillConstraint c (aExp :*: bExp) (aC :*: bC) Source # | |||||
Defined in Database.Beam.Schema.Tables | |||||
(GIndex f, GIndex g) => GIndex (f :*: g) | |||||
Defined in Data.Functor.Rep | |||||
(GTabulate f, GTabulate g) => GTabulate (f :*: g) | |||||
Defined in Data.Functor.Rep gtabulate' :: (GRep' (f :*: g) -> a) -> (f :*: g) a | |||||
(Representable f, Representable g) => Representable (f :*: g) | |||||
(MonadZip f, MonadZip g) => MonadZip (f :*: g) | Since: base-4.9.0.0 | ||||
(Foldable1 f, Foldable1 g) => Foldable1 (f :*: g) | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 fold1 :: Semigroup m => (f :*: g) m -> m # foldMap1 :: Semigroup m => (a -> m) -> (f :*: g) a -> m # foldMap1' :: Semigroup m => (a -> m) -> (f :*: g) a -> m # toNonEmpty :: (f :*: g) a -> NonEmpty a # maximum :: Ord a => (f :*: g) a -> a # minimum :: Ord a => (f :*: g) a -> a # foldrMap1 :: (a -> b) -> (a -> b -> b) -> (f :*: g) a -> b # foldlMap1' :: (a -> b) -> (b -> a -> b) -> (f :*: g) a -> b # foldlMap1 :: (a -> b) -> (b -> a -> b) -> (f :*: g) a -> b # foldrMap1' :: (a -> b) -> (a -> b -> b) -> (f :*: g) a -> b # | |||||
(Contravariant f, Contravariant g) => Contravariant (f :*: g) | |||||
(GTableSkeleton a, GTableSkeleton b) => GTableSkeleton (a :*: b) Source # | |||||
Defined in Database.Beam.Schema.Tables | |||||
(Alternative f, Alternative g) => Alternative (f :*: g) | @since base-4.9.0.0 | ||||
(Applicative f, Applicative g) => Applicative (f :*: g) | @since base-4.9.0.0 | ||||
(Functor f, Functor g) => Functor (f :*: g) | @since base-4.9.0.0 | ||||
(Monad f, Monad g) => Monad (f :*: g) | @since base-4.9.0.0 | ||||
(MonadPlus f, MonadPlus g) => MonadPlus (f :*: g) | @since base-4.9.0.0 | ||||
(MonadFix f, MonadFix g) => MonadFix (f :*: g) | @since base-4.9.0.0 | ||||
Defined in GHC.Internal.Control.Monad.Fix | |||||
(Foldable f, Foldable g) => Foldable (f :*: g) | @since base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Foldable 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] # 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 # | |||||
(Traversable f, Traversable g) => Traversable (f :*: g) | @since base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Traversable | |||||
(GUniform f, GUniform g) => GUniform (f :*: g) | |||||
Defined in System.Random.Internal | |||||
(GAutoDbSettings (x p), GAutoDbSettings (y p)) => GAutoDbSettings ((x :*: y) p) Source # | |||||
Defined in Database.Beam.Schema.Tables autoDbSettings' :: (x :*: y) p Source # | |||||
(GDefaultTableFieldSettings (a p), GDefaultTableFieldSettings (b p)) => GDefaultTableFieldSettings ((a :*: b) p) Source # | |||||
Defined in Database.Beam.Schema.Tables | |||||
(Monoid (f p), Monoid (g p)) => Monoid ((f :*: g) p) | @since base-4.12.0.0 | ||||
(Semigroup (f p), Semigroup (g p)) => Semigroup ((f :*: g) p) | @since base-4.12.0.0 | ||||
Generic ((f :*: g) p) | |||||
Defined in GHC.Internal.Generics
| |||||
(Read (f p), Read (g p)) => Read ((f :*: g) p) | @since base-4.7.0.0 | ||||
(Show (f p), Show (g p)) => Show ((f :*: g) p) | @since base-4.7.0.0 | ||||
(Eq (f p), Eq (g p)) => Eq ((f :*: g) p) | @since base-4.7.0.0 | ||||
(Ord (f p), Ord (g p)) => Ord ((f :*: g) p) | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Generics | |||||
type Rep1 (f :*: g :: k -> Type) | @since base-4.9.0.0 | ||||
Defined in GHC.Internal.Generics type Rep1 (f :*: g :: k -> Type) = D1 ('MetaData ":*:" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons ":*:" ('InfixI 'RightAssociative 6) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 f) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 g))) | |||||
type GRep' (f :*: g) | |||||
Defined in Data.Functor.Rep | |||||
type Rep (f :*: g) | |||||
type Rep ((f :*: g) p) | @since base-4.7.0.0 | ||||
Defined in GHC.Internal.Generics type Rep ((f :*: g) p) = D1 ('MetaData ":*:" "GHC.Internal.Generics" "ghc-internal" 'False) (C1 ('MetaCons ":*:" ('InfixI 'RightAssociative 6) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f p)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (g p)))) |
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.
tableValuesNeeded :: forall (table :: (Type -> Type) -> Type). Beamable table => Proxy table -> Int Source #
pk :: forall t (f :: Type -> Type). Table t => t f -> PrimaryKey t f Source #
Synonym for primaryKey
allBeamValues :: forall table (f :: Type -> Type) b. Beamable table => (forall a. Columnar' f a -> b) -> table f -> [b] Source #
changeBeamRep :: forall table (f :: Type -> Type) (g :: Type -> Type). Beamable table => (forall a. Columnar' f a -> Columnar' g a) -> table f -> table g Source #
alongsideTable :: forall tbl (f :: Type -> Type) (g :: Type -> Type). 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
Exported so we can override defaults
For Beamable
class GZipTables (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type) (exposedRep :: Type -> Type) (fRep :: Type -> Type) (gRep :: Type -> Type) (hRep :: Type -> Type) where Source #
gZipTables :: Applicative m => Proxy exposedRep -> (forall a. Columnar' f a -> Columnar' g a -> m (Columnar' h a)) -> fRep () -> gRep () -> m (hRep ()) Source #
Instances
GZipTables f g h (U1 :: Type -> Type) (U1 :: Type -> Type) (U1 :: Type -> Type) (U1 :: Type -> Type) Source # | |
Defined in Database.Beam.Schema.Tables | |
(GZipTables f g h exp1 f1 g1 h1, GZipTables f g h exp2 f2 g2 h2) => GZipTables f g h (exp1 :*: exp2) (f1 :*: f2) (g1 :*: g2) (h1 :*: h2) Source # | |
Defined in Database.Beam.Schema.Tables | |
(fa ~ Columnar f a, ga ~ Columnar g a, ha ~ Columnar h a, ha ~ Columnar h a) => GZipTables f g h (K1 R (Exposed a) :: Type -> Type) (K1 R fa :: Type -> Type) (K1 R ga :: Type -> Type) (K1 R ha :: Type -> Type) Source # | |
Beamable tbl => GZipTables f g h (K1 R (tbl Exposed) :: Type -> Type) (K1 R (tbl f) :: Type -> Type) (K1 R (tbl g) :: Type -> Type) (K1 R (tbl h) :: Type -> Type) Source # | |
Beamable tbl => GZipTables f g h (K1 R (tbl (Nullable Exposed)) :: Type -> Type) (K1 R (tbl (Nullable f)) :: Type -> Type) (K1 R (tbl (Nullable g)) :: Type -> Type) (K1 R (tbl (Nullable h)) :: Type -> Type) Source # | |
GZipTables f g h exp fRep gRep hRep => GZipTables f g h (M1 x y exp) (M1 x y fRep) (M1 x y gRep) (M1 x y hRep) Source # | |
Defined in Database.Beam.Schema.Tables |
class GTableSkeleton (x :: Type -> Type) where Source #
gTblSkeleton :: Proxy x -> x () Source #
Instances
GTableSkeleton (U1 :: Type -> Type) Source # | |
Defined in Database.Beam.Schema.Tables | |
(GTableSkeleton a, GTableSkeleton b) => GTableSkeleton (a :*: b) Source # | |
Defined in Database.Beam.Schema.Tables | |
GTableSkeleton (K1 R (Ignored field) :: Type -> Type) Source # | |
Beamable tbl => GTableSkeleton (K1 R (tbl (Nullable Ignored)) :: Type -> Type) Source # | |
Beamable tbl => GTableSkeleton (K1 R (tbl Ignored) :: Type -> Type) Source # | |
GTableSkeleton p => GTableSkeleton (M1 t f p) Source # | |
Defined in Database.Beam.Schema.Tables |
For Database
class GZipDatabase be (f :: Type -> Type) (g :: Type -> Type) (h :: Type -> Type) (x :: Type -> Type) (y :: Type -> Type) (z :: Type -> Type) where Source #
gZipDatabase :: Applicative m => (Proxy f, Proxy g, Proxy h, Proxy be) -> (forall tbl. (IsDatabaseEntity be tbl, DatabaseEntityRegularRequirements be tbl) => f tbl -> g tbl -> m (h tbl)) -> x () -> y () -> m (z ()) Source #
Instances
(GZipDatabase be f g h ax ay az, GZipDatabase be f g h bx by bz) => GZipDatabase be f g h (ax :*: bx) (ay :*: by) (az :*: bz) Source # | |
Defined in Database.Beam.Schema.Tables gZipDatabase :: Applicative m => (Proxy f, Proxy g, Proxy h, Proxy be) -> (forall tbl. (IsDatabaseEntity be tbl, DatabaseEntityRegularRequirements be tbl) => f tbl -> g tbl -> m (h tbl)) -> (ax :*: bx) () -> (ay :*: by) () -> m ((az :*: bz) ()) Source # | |
Database be db => GZipDatabase be f g h (K1 R (db f) :: Type -> Type) (K1 R (db g) :: Type -> Type) (K1 R (db h) :: Type -> Type) Source # | |
Defined in Database.Beam.Schema.Tables gZipDatabase :: Applicative m => (Proxy f, Proxy g, Proxy h, Proxy be) -> (forall tbl. (IsDatabaseEntity be tbl, DatabaseEntityRegularRequirements be tbl) => f tbl -> g tbl -> m (h tbl)) -> K1 R (db f) () -> K1 R (db g) () -> m (K1 R (db h) ()) Source # | |
(IsDatabaseEntity be tbl, DatabaseEntityRegularRequirements be tbl) => GZipDatabase be f g h (K1 R (f tbl) :: Type -> Type) (K1 R (g tbl) :: Type -> Type) (K1 R (h tbl) :: Type -> Type) Source # | |
Defined in Database.Beam.Schema.Tables gZipDatabase :: Applicative m => (Proxy f, Proxy g, Proxy h, Proxy be) -> (forall tbl0. (IsDatabaseEntity be tbl0, DatabaseEntityRegularRequirements be tbl0) => f tbl0 -> g tbl0 -> m (h tbl0)) -> K1 R (f tbl) () -> K1 R (g tbl) () -> m (K1 R (h tbl) ()) Source # | |
GZipDatabase be f g h x y z => GZipDatabase be f g h (M1 a b x) (M1 a b y) (M1 a b z) Source # | |
Defined in Database.Beam.Schema.Tables gZipDatabase :: Applicative m => (Proxy f, Proxy g, Proxy h, Proxy be) -> (forall tbl. (IsDatabaseEntity be tbl, DatabaseEntityRegularRequirements be tbl) => f tbl -> g tbl -> m (h tbl)) -> M1 a b x () -> M1 a b y () -> m (M1 a b z ()) Source # |
For defaultDbSettings
class GAutoDbSettings x where Source #
autoDbSettings' :: x Source #
Instances
(GAutoDbSettings (x p), GAutoDbSettings (y p)) => GAutoDbSettings ((x :*: y) p) Source # | |
Defined in Database.Beam.Schema.Tables autoDbSettings' :: (x :*: y) p Source # | |
GAutoDbSettings (x p) => GAutoDbSettings (C1 f x p) Source # | |
Defined in Database.Beam.Schema.Tables autoDbSettings' :: C1 f x p Source # | |
GAutoDbSettings (x p) => GAutoDbSettings (D1 f x p) Source # | |
Defined in Database.Beam.Schema.Tables autoDbSettings' :: D1 f x p Source # | |
(Selector f, IsDatabaseEntity be x, DatabaseEntityDefaultRequirements be x) => GAutoDbSettings (S1 f (K1 R (DatabaseEntity be db x) :: Type -> Type) p) Source # | |
Defined in Database.Beam.Schema.Tables autoDbSettings' :: S1 f (K1 R (DatabaseEntity be db x) :: Type -> Type) p Source # | |
(Database be embedded, Generic (DatabaseSettings be embedded), GAutoDbSettings (Rep (DatabaseSettings be embedded) ())) => GAutoDbSettings (S1 f (K1 R (embedded (DatabaseEntity be super)) :: Type -> Type) p) Source # | |
Defined in Database.Beam.Schema.Tables autoDbSettings' :: S1 f (K1 R (embedded (DatabaseEntity be super)) :: Type -> Type) p Source # |
class GDefaultTableFieldSettings x where Source #
gDefTblFieldSettings :: Proxy x -> x Source #
Instances
(GDefaultTableFieldSettings (a p), GDefaultTableFieldSettings (b p)) => GDefaultTableFieldSettings ((a :*: b) p) Source # | |
Defined in Database.Beam.Schema.Tables | |
GDefaultTableFieldSettings (p x) => GDefaultTableFieldSettings (C1 f p x) Source # | |
Defined in Database.Beam.Schema.Tables | |
GDefaultTableFieldSettings (p x) => GDefaultTableFieldSettings (D1 f p x) Source # | |
Defined in Database.Beam.Schema.Tables | |
(TypeError ('Text "All Beamable types must be record types, so appropriate names can be given to columns") :: Constraint) => GDefaultTableFieldSettings (K1 r f p) Source # | |
Defined in Database.Beam.Schema.Tables | |
Selector f => GDefaultTableFieldSettings (S1 f (K1 R (TableField table field) :: Type -> Type) p) Source # | |
Defined in Database.Beam.Schema.Tables | |
(Selector f', ChooseSubTableStrategy tbl sub ~ strategy, SubTableStrategyImpl strategy f sub, TagReducesTo f (TableField tbl), Beamable sub) => GDefaultTableFieldSettings (S1 f' (K1 R (sub f) :: Type -> Type) p) Source # | |
type family ChooseSubTableStrategy (tbl :: (Type -> Type) -> Type) (sub :: (Type -> Type) -> Type) :: SubTableStrategy where ... Source #
ChooseSubTableStrategy tbl (PrimaryKey tbl) = 'RecursiveKeyStrategy | |
ChooseSubTableStrategy tbl (PrimaryKey rel) = 'PrimaryKeyStrategy | |
ChooseSubTableStrategy tbl sub = 'BeamableStrategy |