| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Database.Beam.Schema
Description
- class Database db where
- data GenDatabaseTable db where
- GenDatabaseTable :: DatabaseTable db table -> GenDatabaseTable db
- data DatabaseTable db table where
- DatabaseTable :: Table table => Proxy table -> Text -> DatabaseTable db table
- type DatabaseSettings db = db (DatabaseTable db)
- type ReifiedDatabaseSchema = [(Text, ReifiedTableSchema)]
- type ReifiedTableSchema = [(Text, SQLColumnSchema)]
- autoDbSettings :: (Generic (DatabaseSettings db), GAutoDbSettings (Rep (DatabaseSettings db) ())) => DatabaseSettings db
- allTableSettings :: Database db => DatabaseSettings db -> [GenDatabaseTable db]
- newtype BeamEnum a = BeamEnum {
- unBeamEnum :: a
- newtype SqlValue' x = SqlValue' SqlValue
- data Lenses t f x
- data LensFor t x where
- type family Columnar f x
- newtype Columnar' f a = Columnar' (Columnar f a)
- data Nullable c x
- data TableField table ty = TableField {}
- fieldName :: Lens' (TableField table ty) Text
- fieldConstraints :: Lens' (TableField table ty) [SQLConstraint]
- fieldSettings :: Lens (TableField table a) (TableField table b) (FieldSettings a) (FieldSettings b)
- type TableSettings table = table (TableField table)
- class Typeable table => Table table where
- data PrimaryKey table column :: *
- primaryKey :: table column -> PrimaryKey table column
- pkChangeRep :: (forall a. Columnar' f a -> Columnar' g a) -> PrimaryKey table f -> PrimaryKey table g
- changeRep :: (forall a. FieldSchema a => Columnar' f a -> Columnar' g a) -> table f -> table g
- pkAllValues :: (forall a. FieldSchema a => Columnar' f a -> b) -> PrimaryKey table f -> [b]
- fieldAllValues :: (forall a. FieldSchema a => Columnar' f a -> b) -> table f -> [b]
- tblFieldSettings :: TableSettings table
- pkMakeSqlValues :: PrimaryKey table Identity -> PrimaryKey table SqlValue'
- makeSqlValues :: table Identity -> table SqlValue'
- tableFromSqlValues :: FromSqlValuesM (table Identity)
- defTblFieldSettings :: (Generic (TableSettings table), GDefaultTableFieldSettings (Rep (TableSettings table) ())) => TableSettings table
- defFieldSettings :: FieldSchema fs => Text -> TableField table fs
- reifyTableSchema :: Table table => Proxy table -> ReifiedTableSchema
- tableValuesNeeded :: Table table => Proxy table -> Int
- pk :: Table t => t f -> PrimaryKey t f
- class (Show (FieldSettings fs), Typeable fs, Show fs) => FieldSchema fs where
- data FieldSettings fs :: *
- defSettings :: FieldSettings fs
- colDescFromSettings :: FieldSettings fs -> SQLColumnSchema
- makeSqlValue :: fs -> SqlValue
- fromSqlValue :: FromSqlValuesM fs
- type FromSqlValuesM a = ErrorT String (State [SqlValue]) a
- class FromSqlValues a where
- fromSqlValues' :: FromSqlValuesM a
- valuesNeeded :: Proxy a -> Int
- popSqlValue :: FromSqlValuesM SqlValue
- peekSqlValue :: FromSqlValuesM SqlValue
- data CharOrVarchar
- data AutoId
- tableConfigLenses :: (lensType ~ Lenses t (TableField t), Generic (t lensType), Generic (t (TableField t)), GTableLenses t (TableField t) (Rep (t (TableField t))) (Rep (t lensType))) => t (Lenses t (TableField t))
Database Types
data GenDatabaseTable db where Source
Constructors
| GenDatabaseTable :: DatabaseTable db table -> GenDatabaseTable db |
data DatabaseTable db table where Source
Constructors
| DatabaseTable :: Table table => Proxy table -> Text -> DatabaseTable db table |
type DatabaseSettings db = db (DatabaseTable db) Source
type ReifiedDatabaseSchema = [(Text, ReifiedTableSchema)] Source
type ReifiedTableSchema = [(Text, SQLColumnSchema)] Source
autoDbSettings :: (Generic (DatabaseSettings db), GAutoDbSettings (Rep (DatabaseSettings db) ())) => DatabaseSettings db Source
allTableSettings :: Database db => DatabaseSettings db -> [GenDatabaseTable db] Source
Constructors
| BeamEnum | |
Fields
| |
Instances
| Show a => Show (BeamEnum a) Source | |
data FieldSettings (BeamEnum a) = EnumSettings {
|
Columnar and Column Tags
type family Columnar f x 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 Columnar Identity (BeamEnum 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. Enum types tagged with BeamEnum, are automatically unwrapped in the simplified data
structure.
Columnar (Nullable c) x = Columnar c (Maybe x)
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.
Support for NULLable Foreign Key references.
data MyTable f = MyTable
{ nullableRef :: PrimaryKey AnotherTable (Nullable f)
, ... }
deriving (Generic, Typeable)See Columnar for more information.
data TableField table ty Source
Metadata for a field of type ty in table.
Columnar (TableField table) ty = TableField table ty
This is used to declare tblFieldSettings in the Table class.
It is easiest to access these fields through the lenses fieldName, fieldConstraints, and fieldSettings.
data EmployeeT f = Employee
{ _employeeId :: Columnar f AutoId
, _employeeDepartment :: Columnar f Text
, _employeeFirstName :: Columnar f Text
, _employeeLastName :: Columnar f Text }
deriving GenericNow we can use tableConfigLenses and the TableField lenses to modify the default table configuration
Employee (LensFor employeeIdC) (LensFor employeeDepartmentC) (LensFor employeeFirstNameC) (LensFor employeeLastNameC) = tableConfigLenses
instance Table EmployeeT where
type PrimaryKey EmployeeT f = PK f AutoId
primaryKey = PK . _beamEmployeeId
tblFieldSettings = defTblFieldSettings
& employeeFirstNameC . fieldName .~ "fname"
& employeeLastNameC . fieldName .~ "lname"
& employeeLastNameC . fieldSettings .~ Varchar (Just 128) -- Give it a 128 character limitConstructors
| TableField | |
Fields
| |
Instances
| Show (FieldSettings ty) => Show (TableField t ty) Source |
fieldName :: Lens' (TableField table ty) Text Source
fieldConstraints :: Lens' (TableField table ty) [SQLConstraint] Source
fieldSettings :: Lens (TableField table a) (TableField table b) (FieldSettings a) (FieldSettings b) Source
type TableSettings table = table (TableField table) Source
Tables
class Typeable table => Table table where Source
The big Kahuna! All beam tables implement this class.
The kind of all table types is `(* -> *) -> *`. 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. In order for the default deriving to work, every type passed into Columnar must be an instance
of FieldSchema.
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.
Even though all methods are derivable, you are free to override them. Typically, you may want to override tblFieldSettings if you want
to specify options for column storage or to rename columns. See TableField for more information. You may want to use tableConfigLenses
to simplify accessing tblFieldSettings.
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 Table BlogPostT where
type PrimaryKey BlogPostT f = PK f Text
primaryKey = PK . _blogPostSlugWe 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).
Minimal complete definition
Associated Types
data PrimaryKey table column :: * 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)
pkChangeRep :: (forall a. Columnar' f a -> Columnar' g a) -> PrimaryKey table f -> PrimaryKey table g Source
changeRep :: (forall a. FieldSchema a => Columnar' f a -> Columnar' g a) -> table f -> table g Source
pkAllValues :: (forall a. FieldSchema a => Columnar' f a -> b) -> PrimaryKey table f -> [b] Source
fieldAllValues :: (forall a. FieldSchema a => Columnar' f a -> b) -> table f -> [b] Source
tblFieldSettings :: TableSettings table Source
pkMakeSqlValues :: PrimaryKey table Identity -> PrimaryKey table SqlValue' Source
makeSqlValues :: table Identity -> table SqlValue' Source
tableFromSqlValues :: FromSqlValuesM (table Identity) Source
defTblFieldSettings :: (Generic (TableSettings table), GDefaultTableFieldSettings (Rep (TableSettings table) ())) => TableSettings table Source
defFieldSettings :: FieldSchema fs => Text -> TableField table fs Source
reifyTableSchema :: Table table => Proxy table -> ReifiedTableSchema Source
tableValuesNeeded :: Table table => Proxy table -> Int Source
pk :: Table t => t f -> PrimaryKey t f Source
Synonym for primaryKey
Fields
class (Show (FieldSettings fs), Typeable fs, Show fs) => FieldSchema fs where Source
Associated Types
data FieldSettings fs :: * Source
Methods
defSettings :: FieldSettings fs Source
colDescFromSettings :: FieldSettings fs -> SQLColumnSchema Source
makeSqlValue :: fs -> SqlValue Source
fromSqlValue :: FromSqlValuesM fs Source
Instances
class FromSqlValues a where Source
Minimal complete definition
Nothing
Instances
| FromSqlValues Int Source | |
| FromSqlValues AutoId Source | |
| Table tbl => FromSqlValues (tbl Identity) Source | |
| FromSqlValues t => FromSqlValues (Maybe t) Source | |
| (FromSqlValues a, FromSqlValues b) => FromSqlValues (a, b) Source | |
| (FromSqlValues a, FromSqlValues b, FromSqlValues c) => FromSqlValues (a, b, c) Source |
Fields
Text field
data CharOrVarchar Source
Instances
Auto-increment fields
Constructors
| UnassignedId | |
| AssignedId !Int |
tableConfigLenses :: (lensType ~ Lenses t (TableField t), Generic (t lensType), Generic (t (TableField t)), GTableLenses t (TableField t) (Rep (t (TableField t))) (Rep (t lensType))) => t (Lenses t (TableField t)) Source
Automatically deduce lenses for 'TableSettings table'. You can expose the lenses at global level by doing a
top-level pattern match on tableConfigLenses, replacing every column in the pattern with `LensFor nameOfLensForField'.
For example,
data AuthorT f = AuthorT
{ _authorEmail :: Columnar f Text
, _authorFirstName :: Columnar f Text
, _authorLastName :: Columnar f Text }
deriving Generic
data BlogPostT f = BlogPost
{ _blogPostSlug :: Columnar f Text
, _blogPostBody :: Columnar f Text
, _blogPostDate :: Columnar f UTCTime
, _blogPostAuthor :: ForeignKey AuthorT f
, _blogPostTagline :: Columnar f (Maybe Text) }
deriving Generic
instance Table BlogPostT where
type PrimaryKey BlogPostT f = PK f Text
primaryKey = PK . _blogPostSlug
instance Table AuthorT where
type PrimaryKey AuthorT f = PK f Text
primaryKey = PK . _authorEmailBlogPost (LensFor blogPostSlug
(LensFor blogPostBody)
(LensFor blogPostDate)
(ForeignKey (PK (LensFor blogPostAuthorEmail)))
(LensFor blogPostTagLine) = tableConfigLenses