| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Database.Beam.Schema.Tables
Description
Defines a generic schema type that can be used to define schemas for Beam tables
Synopsis
- class Database be db
 - 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 = db (DatabaseEntity be db)
 - class RenamableWithRule (FieldRenamer (DatabaseEntityDescriptor be entityType)) => IsDatabaseEntity be entityType where
- data DatabaseEntityDescriptor be entityType :: Type
 - type DatabaseEntityDefaultRequirements be entityType :: Constraint
 - type DatabaseEntityRegularRequirements be entityType :: Constraint
 - dbEntityName :: Lens' (DatabaseEntityDescriptor be entityType) Text
 - dbEntitySchema :: Traversal' (DatabaseEntityDescriptor be entityType) (Maybe Text)
 - dbEntityAuto :: DatabaseEntityDefaultRequirements be entityType => Text -> DatabaseEntityDescriptor be entityType
 
 - data DatabaseEntity be (db :: (Type -> Type) -> Type) entityType where
- DatabaseEntity :: 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 :: Type)
 - dbEntityDescriptor :: SimpleGetter (DatabaseEntity be db entityType) (DatabaseEntityDescriptor be entityType)
 - type DatabaseModification f be db = db (EntityModification f be)
 - newtype EntityModification f be e = EntityModification (Endo (f e))
 - newtype FieldModification f a = FieldModification (Columnar f a -> Columnar f a)
 - dbModification :: forall f be db. Database be db => DatabaseModification f be db
 - tableModification :: forall f tbl. Beamable tbl => tbl (FieldModification f)
 - withDbModification :: forall db be entity. Database be db => db (entity be db) -> DatabaseModification (entity be db) be db -> db (entity be db)
 - withTableModification :: Beamable tbl => tbl (FieldModification f) -> tbl f -> tbl f
 - modifyTable :: (Beamable tbl, Table tbl) => (Text -> Text) -> tbl (FieldModification (TableField tbl)) -> EntityModification (DatabaseEntity be db) be (TableEntity tbl)
 - modifyEntityName :: IsDatabaseEntity be entity => (Text -> Text) -> EntityModification (DatabaseEntity be db) be entity
 - setEntityName :: IsDatabaseEntity be entity => Text -> EntityModification (DatabaseEntity be db) be entity
 - modifyTableFields :: tbl (FieldModification (TableField tbl)) -> EntityModification (DatabaseEntity be db) be (TableEntity tbl)
 - fieldNamed :: Text -> FieldModification (TableField tbl) a
 - modifyEntitySchema :: IsDatabaseEntity be entity => (Maybe Text -> Maybe Text) -> EntityModification (DatabaseEntity be db) be entity
 - setEntitySchema :: IsDatabaseEntity be entity => Maybe Text -> EntityModification (DatabaseEntity be db) be entity
 - defaultDbSettings :: (Generic (DatabaseSettings be db), GAutoDbSettings (Rep (DatabaseSettings be db) ())) => DatabaseSettings be db
 - class RenamableWithRule mod where
- renamingFields :: (NonEmpty Text -> Text) -> mod
 
 - class RenamableField f 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 a = Columnar f a
 - newtype Columnar' f a = Columnar' (Columnar f a)
 - newtype ComposeColumnar f g 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 :: Lens' (TableField table ty) Text
 - fieldPath :: Traversal' (TableField table ty) Text
 - type TableSettings table = table (TableField table)
 - type HaskellTable table = table Identity
 - type TableSkeleton table = table Ignored
 - data Ignored x = Ignored
 - class GFieldsFulfillConstraint (c :: Type -> Constraint) (exposed :: Type -> Type) withconstraint where
- gWithConstrainedFields :: Proxy c -> Proxy exposed -> withconstraint ()
 
 - type FieldsFulfillConstraint (c :: Type -> Constraint) t = (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 = (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 :: c x => x -> WithConstraint c x
 
 - data HasConstraint (c :: Type -> Constraint) x where
- HasConstraint :: c x => HasConstraint c x
 
 - class TagReducesTo f f' | f -> f' where
 - type family ReplaceBaseTag tag f where ...
 - withConstrainedFields :: forall c tbl. (FieldsFulfillConstraint c tbl, Beamable tbl) => tbl Identity -> tbl (WithConstraint c)
 - withConstraints :: forall c tbl. (Beamable tbl, FieldsFulfillConstraint c tbl) => tbl (HasConstraint c)
 - withNullableConstrainedFields :: forall c tbl. (FieldsFulfillConstraintNullable c tbl, Beamable tbl) => tbl (Nullable Identity) -> tbl (Nullable (WithConstraint c))
 - withNullableConstraints :: forall c 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 (column :: Type -> Type) :: Type
 - primaryKey :: table column -> PrimaryKey table column
 
 - class Beamable table where
- zipBeamFieldsM :: 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 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 :: Beamable table => Proxy table -> Int
 - pk :: Table t => t f -> PrimaryKey t f
 - allBeamValues :: Beamable table => (forall a. Columnar' f a -> b) -> table f -> [b]
 - changeBeamRep :: Beamable table => (forall a. Columnar' f a -> Columnar' g a) -> table f -> table g
 - alongsideTable :: Beamable tbl => tbl f -> tbl g -> tbl (Columnar' f :*: Columnar' g)
 - defaultFieldName :: NonEmpty Text -> Text
 
Database Types
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 #
Methods
dbEntityName :: Lens' (DatabaseEntityDescriptor be entityType) Text Source #
dbEntitySchema :: Traversal' (DatabaseEntityDescriptor be entityType) (Maybe Text) Source #
dbEntityAuto :: DatabaseEntityDefaultRequirements be entityType => Text -> DatabaseEntityDescriptor be entityType Source #
Instances
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
| Database be db => RenamableWithRule (db (EntityModification (DatabaseEntity be db) be)) Source # | |
Defined in Database.Beam.Schema.Tables Methods 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 Methods renamingFields :: (NonEmpty Text -> Text) -> EntityModification (DatabaseEntity be db) be entity Source #  | |
data TableEntity (tbl :: (Type -> Type) -> Type) Source #
Instances
data ViewEntity (view :: (Type -> Type) -> Type) Source #
Instances
data DomainTypeEntity (ty :: Type) Source #
Instances
dbEntityDescriptor :: SimpleGetter (DatabaseEntity be db entityType) (DatabaseEntityDescriptor be entityType) Source #
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
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
| (Beamable tbl, RenamableField f) => RenamableWithRule (tbl (FieldModification f)) Source # | |
Defined in Database.Beam.Schema.Tables Methods renamingFields :: (NonEmpty Text -> Text) -> tbl (FieldModification f) Source #  | |
| IsString (FieldModification (TableField tbl) a) Source # | |
Defined in Database.Beam.Schema.Tables Methods fromString :: String -> FieldModification (TableField tbl) a #  | |
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
setEntitySchema :: 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
class RenamableWithRule mod where Source #
Instances
class RenamableField f where Source #
Methods
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 Methods renameField :: Proxy (TableField tbl) -> Proxy a -> (NonEmpty Text -> Text) -> Columnar (TableField tbl) a -> Columnar (TableField tbl) a Source #  | |
newtype FieldRenamer entity Source #
Constructors
| FieldRenamer | |
Fields 
  | |
Instances
| RenamableWithRule (FieldRenamer (DatabaseEntityDescriptor be (DomainTypeEntity ty))) Source # | |
Defined in Database.Beam.Schema.Tables Methods renamingFields :: (NonEmpty Text -> Text) -> FieldRenamer (DatabaseEntityDescriptor be (DomainTypeEntity ty)) Source #  | |
| Beamable tbl => RenamableWithRule (FieldRenamer (DatabaseEntityDescriptor be (ViewEntity tbl))) Source # | |
Defined in Database.Beam.Schema.Tables Methods renamingFields :: (NonEmpty Text -> Text) -> FieldRenamer (DatabaseEntityDescriptor be (ViewEntity tbl)) Source #  | |
| Beamable tbl => RenamableWithRule (FieldRenamer (DatabaseEntityDescriptor be (TableEntity tbl))) Source # | |
Defined in Database.Beam.Schema.Tables Methods renamingFields :: (NonEmpty Text -> Text) -> FieldRenamer (DatabaseEntityDescriptor be (TableEntity tbl)) 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 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.
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'
newtype ComposeColumnar f g a Source #
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
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
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
| FieldsFulfillConstraintNullable c t => GFieldsFulfillConstraint c (K1 R (t (Nullable Exposed)) :: Type -> Type) (K1 R (t (Nullable (HasConstraint c))) :: 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  | |
| c x => GFieldsFulfillConstraint c (K1 R (Exposed x) :: Type -> Type) (K1 R (HasConstraint c x) :: Type -> Type) Source # | |
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.
fieldPath :: Traversal' (TableField table ty) Text Source #
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 #
class GFieldsFulfillConstraint (c :: Type -> Constraint) (exposed :: Type -> Type) withconstraint where Source #
Methods
gWithConstrainedFields :: Proxy c -> Proxy exposed -> withconstraint () Source #
Instances
type FieldsFulfillConstraint (c :: Type -> Constraint) t = (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 = (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.
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
| FieldsFulfillConstraintNullable c t => GFieldsFulfillConstraint c (K1 R (t (Nullable Exposed)) :: Type -> Type) (K1 R (t (Nullable (HasConstraint c))) :: 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  | |
| c x => GFieldsFulfillConstraint c (K1 R (Exposed x) :: Type -> Type) (K1 R (HasConstraint c x) :: Type -> Type) Source # | |
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
| TagReducesTo f f' => TagReducesTo (Nullable f) f' Source # | |
| TagReducesTo (TableField tbl) (TableField tbl) Source # | |
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 #
withNullableConstrainedFields :: forall c tbl. (FieldsFulfillConstraintNullable c tbl, Beamable tbl) => tbl (Nullable Identity) -> tbl (Nullable (WithConstraint c)) Source #
withNullableConstraints :: forall c 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_blogPostTaglinefields are of typesText,Text,UTCTime, and 'Maybe Text' respectfully. - Since 
_blogPostSlug,_blogPostBody,_blogPostDate,_blogPostAuthormust be provided (i.e, they cannot containNothing), they will be given SQL NOT NULL constraints._blogPostTaglineis declaredMaybesoNothingwill be stored as NULL in the database._blogPostImageGallerywill be allowed to be empty because it uses theNullabletag modifier. blogPostAuthorreferences theAuthorTtable (not given here) and is required.blogPostImageGalleryreferences theImageGalleryTtable (not given here), but this relation is not required (i.e., it may beNothing. SeeNullable).
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 #
Instances
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
| (Monoid pairs, RecordToPairs enc pairs arity a, RecordToPairs enc pairs arity b) => RecordToPairs enc pairs arity (a :*: b) | |
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) | |
| (WriteProduct arity a, WriteProduct arity b, ProductSize a, ProductSize b) => GToJSON' Value arity (a :*: b) | |
| Generic1 (f :*: g :: k -> Type) | Since: base-4.9.0.0  | 
| (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) | |
| (ProductFromJSON arity a, ProductFromJSON arity b) => ProductFromJSON arity (a :*: b) | |
Defined in Data.Aeson.Types.FromJSON  | |
| (FieldNames a, FieldNames b) => FieldNames (a :*: b :: k -> Type) | |
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) | |
Defined in Data.Aeson.Types.FromJSON  | |
| (GFieldsFulfillConstraint c aExp aC, GFieldsFulfillConstraint c bExp bC) => GFieldsFulfillConstraint c (aExp :*: bExp) (aC :*: bC) Source # | |
Defined in Database.Beam.Schema.Tables  | |
| (Monad f, Monad g) => Monad (f :*: g) | Since: base-4.9.0.0  | 
| (Functor f, Functor g) => Functor (f :*: g) | Since: base-4.9.0.0  | 
| (MonadFix f, MonadFix g) => MonadFix (f :*: g) | Since: base-4.9.0.0  | 
Defined in Control.Monad.Fix  | |
| (Applicative f, Applicative g) => Applicative (f :*: g) | Since: base-4.9.0.0  | 
| (Foldable f, Foldable g) => Foldable (f :*: g) | Since: base-4.9.0.0  | 
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] # 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 Data.Traversable  | |
| (Representable f, Representable g) => Representable (f :*: g) | |
| (Alternative f, Alternative g) => Alternative (f :*: g) | Since: base-4.9.0.0  | 
| (MonadPlus f, MonadPlus g) => MonadPlus (f :*: g) | Since: base-4.9.0.0  | 
| (GIndex f, GIndex g) => GIndex (f :*: g) | |
Defined in Data.Functor.Rep  | |
| (GTabulate f, GTabulate g) => GTabulate (f :*: g) | |
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  | 
| (Ord (f p), Ord (g p)) => Ord ((f :*: g) p) | Since: base-4.7.0.0  | 
Defined in GHC.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  | 
| Generic ((f :*: g) p) | Since: base-4.7.0.0  | 
| (Semigroup (f p), Semigroup (g p)) => Semigroup ((f :*: g) p) | Since: base-4.12.0.0  | 
| (Monoid (f p), Monoid (g p)) => Monoid ((f :*: g) p) | Since: base-4.12.0.0  | 
| type Rep1 (f :*: g :: k -> Type) | |
Defined in GHC.Generics type Rep1 (f :*: g :: k -> Type) = D1 ('MetaData ":*:" "GHC.Generics" "base" '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 Rep (f :*: g) | |
| type GRep' (f :*: g) | |
Defined in Data.Functor.Rep  | |
| type Rep ((f :*: g) p) | |
Defined in GHC.Generics type Rep ((f :*: g) p) = D1 ('MetaData ":*:" "GHC.Generics" "base" '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.
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 #