Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- class Database be db
- type DatabaseSettings be db = db (DatabaseEntity be db)
- data DatabaseEntity be (db :: (Type -> Type) -> Type) entityType
- data TableEntity (tbl :: (Type -> Type) -> Type)
- 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
- defTblFieldSettings :: (Generic (TableSettings table), GDefaultTableFieldSettings (Rep (TableSettings table) ())) => TableSettings table
- pk :: Table t => t f -> PrimaryKey t f
- type family Columnar (f :: Type -> Type) x where ...
- type C f a = Columnar f a
- data Columnar' f a
- data Nullable (c :: Type -> Type) x
- data TableField (table :: (Type -> Type) -> Type) ty
- fieldName :: Lens' (TableField table ty) Text
- type TableSettings table = table (TableField table)
- type HaskellTable table = table Identity
- defaultDbSettings :: (Generic (DatabaseSettings be db), GAutoDbSettings (Rep (DatabaseSettings be db) ())) => DatabaseSettings be db
- type DatabaseModification f be db = db (EntityModification f be)
- data EntityModification f be e
- data FieldModification f a
- 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
- dbModification :: forall f be db. Database be db => DatabaseModification f be db
- tableModification :: forall f tbl. Beamable tbl => tbl (FieldModification f)
- modifyTable :: (Beamable tbl, Table tbl) => (Text -> Text) -> tbl (FieldModification (TableField tbl)) -> EntityModification (DatabaseEntity be db) be (TableEntity tbl)
- fieldNamed :: Text -> FieldModification (TableField tbl) a
- setEntityName :: IsDatabaseEntity be entity => Text -> EntityModification (DatabaseEntity be db) be entity
- modifyEntityName :: IsDatabaseEntity be entity => (Text -> Text) -> EntityModification (DatabaseEntity be db) be entity
- modifyTableFields :: tbl (FieldModification (TableField tbl)) -> EntityModification (DatabaseEntity be db) be (TableEntity tbl)
- data Lenses (t :: (Type -> Type) -> Type) (f :: Type -> Type) x
- data LensFor t x where
- tableLenses :: (lensType ~ Lenses t f, Generic (t lensType), Generic (t f), GTableLenses t f (Rep (t f)) (Rep (t lensType))) => t (Lenses t f)
- newtype TableLens f db (x :: k) = TableLens (Lens' (db f) (f x))
- dbLenses :: (Generic (db (TableLens f db)), Generic (db f), GDatabaseLenses (db f) (Rep (db f)) (Rep (db (TableLens f db)))) => db (TableLens f db)
Database construction
Types and functions to express database types and auto-generate name mappings for them. See the manual for more information.
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
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.
data DatabaseEntity be (db :: (Type -> Type) -> Type) entityType Source #
Represents a meta-description of a particular entityType. Mostly, a wrapper
around 'DatabaseEntityDescriptor be entityType', but carries around the
IsDatabaseEntity
dictionary.
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 # |
Database entities
Database entities represent things that can go into databases. Each entity in
your database that you want to access from Haskell must be given a field in
your database type. Each type of entity gets a particular entity tag, such as
TableEntity
or DomainTypeEntity
data TableEntity (tbl :: (Type -> Type) -> Type) Source #
Instances
Table construction
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 typesErrorMessage
,ErrorMessage
,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 (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
.
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)
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.
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
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 a = Columnar f a Source #
A short type-alias for Columnar
. May shorten your schema definitions
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'
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.
Instances
fieldName :: Lens' (TableField table ty) Text Source #
Van Laarhoven lens to retrieve or set the field name from a TableField
.
type TableSettings table = table (TableField table) Source #
Represents a table that contains metadata on its fields. In particular,
each field of type 'Columnar f a' is transformed into 'TableField table a'.
You can get or update the name of each field by using the fieldName
lens.
type HaskellTable table = table Identity Source #
The regular Haskell version of the table. Equivalent to 'tbl Identity'
Generic
-deriving mechanisms
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
Modifying the derived schema
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.
data 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.
Instances
data FieldModification f 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'
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 # |
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 = setEntityName "Table_1" <> modifyTableFields 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.
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.
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 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.
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.
setEntityName :: IsDatabaseEntity be entity => Text -> EntityModification (DatabaseEntity be db) be entity Source #
Change the entity name without consulting the beam-assigned one
modifyEntityName :: IsDatabaseEntity be entity => (Text -> Text) -> EntityModification (DatabaseEntity be db) be entity Source #
Construct an EntityModification
to rename any database entity
modifyTableFields :: tbl (FieldModification (TableField tbl)) -> EntityModification (DatabaseEntity be db) be (TableEntity tbl) Source #
Construct an EntityModification
to rename the fields of a TableEntity
Types for lens generation
tableLenses :: (lensType ~ Lenses t f, Generic (t lensType), Generic (t f), GTableLenses t f (Rep (t f)) (Rep (t lensType))) => t (Lenses t f) Source #
Automatically deduce lenses for a table over any column tag. lenses at
global level by doing a top-level pattern match on tableLenses
, replacing
every column in the pattern with `LensFor nameOfLensForField'. The lenses
are generated per-column, not per field in the record. Thus if you have
nested Beamable
types, lenses are generated for each nested field.
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 :: PrimaryKey AuthorT f , _blogPostTagline :: Columnar f (Maybe Text) } deriving Generic instance Table BlogPostT where data PrimaryKey BlogPostT f = BlogPostId (Columnar f Text) primaryKey = BlogPostId . _blogPostSlug instance Table AuthorT where data PrimaryKey AuthorT f = AuthorId (Columnar f Text) primaryKey = AuthorId . _authorEmail
BlogPost (LensFor blogPostSlug (LensFor blogPostBody) (LensFor blogPostDate) (AuthorId (LensFor blogPostAuthorEmail)) (LensFor blogPostTagLine) = tableLenses
Note: In order to have GHC deduce the right type, you will need to turn off
the monomorphism restriction. This is a part of the Haskell standard that
specifies that top-level definitions must be inferred to have a monomorphic
type. However, lenses need a polymorphic type to work properly. You can
turn off the monomorphism restriction by enabling the
NoMonomorphismRestriction
extension. You can do this per-file by using
the {-# LANGUAGE NoMonomorphismRestriction #-} pragma at the top of the
file. You can also pass the -XNoMonomorphismRestriction
command line flag
to GHC during compilation.