Safe Haskell | None |
---|
Database.PostgreSQL.ORM.Model
Contents
Description
The main database ORM interface. This module contains functionality for moving a Haskell data structure in and out of a database table.
The most important feature is the Model
class, which encodes a
typed database interface (i.e., the ORM layer). This class has a
default implementation for types that are members of the Generic
class (using GHC's DeriveGeneric
extension), provided the
following conditions hold:
- The data type must have a single constructor that is defined using record selector syntax.
- The very first field of the data type must be a
DBKey
to represent the primary key. Other orders will cause a compilation error. - Every field of the data structure must be an instance of
FromField
andToField
.
If these three conditions hold and your database naming scheme
follows the conventions of defaultModelInfo
--namely that the
table name is the same as the type name with the first character
downcased, and the field names are the same as the column
names--then it is reasonable to have a completely empty (default)
instance declaration:
data MyType = MyType { myKey :: !DBKey , myName :: !S.ByteString , myCamelCase :: !Int , ... } deriving (Show, Generic) instance Model MyType
The default modelInfo
method is called defaultModelInfo
. You
may wish to use almost all of the defaults, but tweak a few things.
This is easily accomplished by overriding a few fields of the
default structure. For example, suppose your database columns use
exactly the same name as your Haskell field names, but the name of
your database table is not the same as the name of the Haskell data
type. You can override the database table name (field modelTable
)
as follows:
instance Model MyType where modelInfo = defaultModelInfo { modelTable = "my_type" }
Finally, if you dislike the conventions followed by
defaultModelInfo
, you can simply implement an alternate pattern.
An example of this is underscoreModelInfo
, which strips a prefix
off every field name and converts everything from camel-case to
underscore notation:
instance Model MyType where modelInfo = underscoreModelInfo "my"
The above code will associate MyType
with a database table
my_type
having column names key
, name
, camel_case
, etc.
You can implement other patterns like underscoreModelInfo
by
calling defaultModelInfo
and modifying the results.
Alternatively, you can directly call the lower-level functions from
which defaultModelInfo
is built (defaultModelTable
,
defaultModelColumns
, defaultModelGetPrimaryKey
).
- class Model a where
- modelInfo :: ModelInfo a
- modelIdentifiers :: ModelIdentifiers a
- modelRead :: RowParser a
- modelWrite :: a -> [Action]
- modelQueries :: ModelQueries a
- modelCreateInfo :: ModelCreateInfo a
- modelValid :: a -> ValidationError
- data ModelInfo a = ModelInfo {
- modelTable :: !ByteString
- modelColumns :: ![ByteString]
- modelPrimaryColumn :: !Int
- modelGetPrimaryKey :: !(a -> DBKey)
- data ModelIdentifiers a = ModelIdentifiers {}
- data ModelQueries a = ModelQueries {}
- underscoreModelInfo :: (Generic a, GToRow (Rep a), GFromRow (Rep a), GPrimaryKey0 (Rep a), GColumns (Rep a), GDatatypeName (Rep a)) => ByteString -> ModelInfo a
- type DBKeyType = Int64
- data DBKey
- isNullKey :: DBKey -> Bool
- type DBRef = GDBRef NormalRef
- type DBRefUnique = GDBRef UniqueRef
- newtype GDBRef reftype table = DBRef DBKeyType
- mkDBRef :: Model a => a -> GDBRef rt a
- findAll :: forall r. Model r => Connection -> IO [r]
- findRow :: forall r rt. Model r => Connection -> GDBRef rt r -> IO (Maybe r)
- save :: Model r => Connection -> r -> IO r
- trySave :: forall r. Model r => Connection -> r -> IO (Either ValidationError r)
- destroy :: forall a. Model a => Connection -> a -> IO ()
- destroyByRef :: forall a rt. Model a => Connection -> GDBRef rt a -> IO ()
- modelName :: forall a. Model a => a -> ByteString
- primaryKey :: Model a => a -> DBKey
- modelSelectFragment :: ModelIdentifiers a -> ByteString
- newtype LookupRow a = LookupRow {
- lookupRow :: a
- newtype UpdateRow a = UpdateRow a
- newtype InsertRow a = InsertRow a
- newtype As alias row = As {
- unAs :: row
- fromAs :: alias -> As alias row -> row
- toAs :: alias -> row -> As alias row
- class RowAlias a where
- rowAliasName :: g a row -> ByteString
- defaultModelInfo :: forall a. (Generic a, GDatatypeName (Rep a), GColumns (Rep a), GPrimaryKey0 (Rep a)) => ModelInfo a
- defaultModelTable :: (Generic a, GDatatypeName (Rep a)) => a -> ByteString
- defaultModelColumns :: (Generic a, GColumns (Rep a)) => a -> [ByteString]
- defaultModelGetPrimaryKey :: (Generic a, GPrimaryKey0 (Rep a)) => a -> DBKey
- defaultModelIdentifiers :: ModelInfo a -> ModelIdentifiers a
- defaultModelWrite :: forall a. (Model a, Generic a, GToRow (Rep a)) => a -> [Action]
- defaultModelQueries :: ModelIdentifiers a -> ModelQueries a
- defaultModelLookupQuery :: ModelIdentifiers a -> Query
- defaultModelUpdateQuery :: ModelIdentifiers a -> Query
- defaultModelInsertQuery :: ModelIdentifiers a -> Query
- defaultModelDeleteQuery :: ModelIdentifiers a -> Query
- quoteIdent :: ByteString -> ByteString
- data NormalRef = NormalRef
- data UniqueRef = UniqueRef
- data ModelCreateInfo a = ModelCreateInfo {}
- emptyModelCreateInfo :: ModelCreateInfo a
- defaultFromRow :: (Generic a, GFromRow (Rep a)) => RowParser a
- defaultToRow :: (Generic a, GToRow (Rep a)) => a -> [Action]
- printq :: Query -> IO ()
- class GPrimaryKey0 f
- class GColumns f
- class GDatatypeName f
- class GFromRow f
- class GToRow f
The Model class
The class of data types that represent a database table. This
class conveys information necessary to move a Haskell data
structure in and out of a database table. The most important field
is modelInfo
, which describes the database table and column
names. modelInfo
has a reasonable default implementation for
types that are members of the Generic
class (using GHC's
DeriveGeneric
extension), provided the following conditions hold:
- The data type must have a single constructor that is defined using record selector syntax.
- The very first field of the data type must be a
DBKey
to represent the primary key. Other orders will cause a compilation error. - Every field of the data structure must be an instance of
FromField
andToField
.
If these three conditions hold and your database naming scheme
follows the conventions of defaultModelInfo
--namely that the
table name is the same as the type name with the first character
downcased, and the field names are the same as the column
names--then it is reasonable to have a completely empty (default)
instance declaration:
data MyType = MyType { myKey :: !DBKey , myName :: !S.ByteString , myCamelCase :: !Int , ... } deriving (Show, Generic) instance Model MyType
The default modelInfo
method is called defaultModelInfo
. You
may wish to use almost all of the defaults, but tweak a few things.
This is easily accomplished by overriding a few fields of the
default structure. For example, suppose your database columns use
exactly the same name as your Haskell field names, but the name of
your database table is not the same as the name of the Haskell data
type. You can override the database table name (field
modelTable
) as follows:
instance Model MyType where modelInfo = defaultModelInfo { modelTable = "my_type" }
Finally, if you dislike the conventions followed by
defaultModelInfo
, you can simply implement an alternate pattern.
An example of this is underscoreModelInfo
, which strips a prefix
off every field name and converts everything from camel-case to
underscore notation:
instance Model MyType where modelInfo = underscoreModelInfo "my"
The above code will associate MyType
with a database table
my_type
having column names key
, name
, camel_case
, etc.
You can implement other patterns like underscoreModelInfo
by
calling defaultModelInfo
and modifying the results.
Alternatively, you can directly call the lower-level functions from
which defaultModelInfo
is built (defaultModelTable
,
defaultModelColumns
, defaultModelGetPrimaryKey
).
Methods
modelInfo :: ModelInfo aSource
modelInfo
provides information about how the Haskell data
type is stored in the database, in the form of a ModelInfo
data
structure. Among other things, this structure specifies the name
of the database table, the names of the database columns
corresponding to the Haskell data structure fields, and the
position of the primary key in both the database columns and the
Haskell data structure.
modelIdentifiers :: ModelIdentifiers aSource
modelIdentifiers
contains the table and column names verbatim
as they should be inserted into SQL queries. For normal models,
these are simply double-quoted (with quoteIdent
) versions of
the names in modelInfo
, with the column names qualified by the
double-quoted table name. However, for special cases such as
join relations (with :.
) or row aliases (with As
),
modelIdentifiers
can modify the table name with unquoted SQL
identifiers (such as JOIN
and AS
) and change the qualified
column names appropriately.
modelRead :: RowParser aSource
modelRead
converts from a database query
result to the
Haskell data type of the Model
, namely a
. Note that if type
a
is an instance of FromRow
, a fine definition of modelRead
is modelRead = fromRow
. The default is to construct a row
parser using the Generic
class. However, it is crucial that
the columns be parsed in the same order they are listed in the
modelColumns
field of a
's ModelInfo
structure, and this
should generally be the same order they are defined in the
Haskell data structure. Hence modelRead
should generally look
like:
-- Callfield
as many times as there are fields in your type modelRead = Constructor <$>field
<*>field
<*>field
modelWrite :: a -> [Action]Source
Marshal all fields of a
except the primary key. As with
modelRead
, the fields must be marshalled in the same order the
corresponding columns are listed in modelColumns
, only with the
primary key (generally column 0) deleted.
Do not define this as toRow
, even if a
is an instance of
ToRow
, because toRow
would include the primary key.
Similarly, do not define this as defaultToRow
. On the other
hand, it is reasonable for modelWrite
to return an error for
degenerate models (such as joins) that should never be save
d.
modelQueries :: ModelQueries aSource
modelQueries
provides pre-formatted Query
templates for
findRow
, save
, and destroy
. The default modelQueries
value is generated from modelIdentifiers
and should not be
modified. However, for degenerate tables (such as joins created
with :.
), it is reasonable to make modelQueries
always throw
an exception, thereby disallowing ordinary queries and requiring
use of more general query functions.
This method should either throw an exception or use the default implementation.
modelCreateInfo :: ModelCreateInfo aSource
Extra constraints, if any, to place in a CREATE TABLE
statement. Only used by Database.PostgreSQL.ORM.CreateTable.
modelValid :: a -> ValidationErrorSource
Perform a validation of the model, returning any errors if it is invalid.
Instances
FromField t => Model [t] | |
FromField t => Model (Only t) | |
(FromField a, FromField b) => Model (a, b) | |
(Model a, Model b) => Model (:. a b) | A degenerate instance of model representing a database join. The
|
(Model a, RowAlias as) => Model (As as a) | A degenerate instance of |
(FromField a, FromField b, FromField c) => Model (a, b, c) | |
(FromField a, FromField b, FromField c, FromField d) => Model (a, b, c, d) | |
(FromField a, FromField b, FromField c, FromField d, FromField e) => Model (a, b, c, d, e) |
A ModelInfo T
contains the information necessary for mapping
T
to a database table. Each
type has a single
Model
ModelInfo
associated with it, accessible through the modelInfo
method of the Model
class. Note the table and column names must
all be unquoted in this data structure, as they will later be
quoted using quoteIdent
by the modelIdentifiers
method.
Constructors
ModelInfo | |
Fields
|
data ModelIdentifiers a Source
SQL table and column identifiers that should be copied verbatim
into queries. For normal models, these will simply be quoted
versions of the fields in the corresponding ModelInfo
. However,
for special cases, the fields of this structure can contain
unquoted SQL including JOIN
keywords. In the case of joins,
different elements of modelQColumns
may be qualified by different
table names.
Note that modelQColumns
and modelQPrimaryColumn
both contain
table-qualified names (e.g., "\"my_type\".\"key\""
),
while modelQWriteColumns
contains only the quoted column names.
Constructors
ModelIdentifiers | |
Fields
|
Instances
Show (ModelIdentifiers a) |
data ModelQueries a Source
Standard CRUD (create/read/update/delete) queries on a model.
Constructors
ModelQueries | |
Fields
|
Instances
Show (ModelQueries a) |
underscoreModelInfo :: (Generic a, GToRow (Rep a), GFromRow (Rep a), GPrimaryKey0 (Rep a), GColumns (Rep a), GDatatypeName (Rep a)) => ByteString -> ModelInfo aSource
An alternate Model
pattern in which Haskell type and field
names are converted from camel-case to underscore notation. The
first argument is a prefix to be removed from field names (since
Haskell requires field names to be unique across data types, while
SQL allows the same column names to be used in different tables).
For example:
data Bar = Bar { barId :: !DBKey , barNameOfBar :: !String , barParent :: !(Maybe (DBRef Bar)) } deriving (Show, Generic) instance Model Bar where modelInfo = underscoreModelInfo "bar"
would associate type Bar
with a database table called bar
with
fields id
, name_of_bar
, and parent
.
Data types for holding primary keys
The type of the Haskell data structure field containing a model's primary key.
Every Model
must have exactly one DBKey
, and the DBKey
must
be the Model
's very first field in the Haskel data type
definition. (The ordering is enforced by
defaultModelGetPrimaryKey
, which, through use of the
DeriveGeneric
extension, fails to compile when the first field is
not a DBKey
.)
Each Model
stored in the database should have a unique non-null
primary key. However, the key is determined at the time the
Model
is inserted into the database. While you are constructing
a new Model
to insert, you will not have its key. Hence, you
should use the value NullKey
to let the database chose the key.
If you wish to store a Model
's primary key as a reference in
another Model
, do not copy the DBKey
structure. Use mkDBRef
to convert the Model
's primary key to a foreign key reference.
type DBRef = GDBRef NormalRefSource
A DBRef T
represents a many-to-one relationship between tables. For
example, if type A
contains a DBRef B
, then each B
is associated
with many A
's. By contrast, a
represents a one-to-one
relationship.
DBRefUnique
DBRef
is a type alias of kind * -> *
. The type DBRef T
references an instance of type T
by the primary key of its
database row. The type argument T
should be an instance of
Model
.
type DBRefUnique = GDBRef UniqueRefSource
A DBRefUnique T
represents a one-to-one relationship between types. For
example, if type A
contains a DBRefUnique B
, then each A
is associated
with one (or at most one) B
, and each B
has one (or at most one) A
associated with it.
By contrast, a
represents a many-to-one relationship.
DBRef
newtype GDBRef reftype table Source
Many operations can take either a DBRef
or a DBRefUnique
(both of which consist internally of a DBKeyType
). Hence, these
two types are just type aliases to a generalized reference type
GDBRef
, where GDBRef
's first type argument, reftype
, is a
phantom type denoting the flavor of reference (NormalRef
or
UniqueRef
).
Instances
Typeable2 GDBRef | |
Model a => SqlType (DBRefUnique a) | |
Model a => SqlType (DBRef a) | |
Bounded (GDBRef reftype table) | |
Enum (GDBRef reftype table) | |
Eq (GDBRef reftype table) | |
Integral (GDBRef reftype table) | |
(Data reftype, Data table) => Data (GDBRef reftype table) | |
Num (GDBRef reftype table) | |
Ord (GDBRef reftype table) | |
Model t => Read (GDBRef rt t) | |
Real (GDBRef reftype table) | |
Model t => Show (GDBRef rt t) | |
ToJSON (GDBRef t a) | |
FromJSON (GDBRef t a) | |
FromField (GDBRef rt t) | |
ToField (GDBRef rt t) |
mkDBRef :: Model a => a -> GDBRef rt aSource
Create a reference to the primary key of a Model
, suitable for
storing in a DBRef
or DBRefUnique
field of a different Model
.
Database operations on Models
findAll :: forall r. Model r => Connection -> IO [r]Source
findRow :: forall r rt. Model r => Connection -> GDBRef rt r -> IO (Maybe r)Source
Follow a DBRef
or DBRefUnique
and fetch the target row from
the database into a Model
type r
.
save :: Model r => Connection -> r -> IO rSource
Like trySave
but instead of returning an Either
, throws a
ValidationError
if the Model
is invalid.
trySave :: forall r. Model r => Connection -> r -> IO (Either ValidationError r)Source
Write a Model
to the database. If the primary key is
NullKey
, the item is written with an INSERT
query, read back
from the database, and returned with its primary key filled in. If
the primary key is not NullKey
, then the Model
is written with
an UPDATE
query and returned as-is.
If the Model
is invalid (i.e. the return value of modelValid
is
non-empty), a list of InvalidError
is returned instead.
destroy :: forall a. Model a => Connection -> a -> IO ()Source
Remove the row corresponding to a particular data structure from the database. This function only looks at the primary key in the data structure. It is an error to call this function if the primary key is not set.
destroyByRef :: forall a rt. Model a => Connection -> GDBRef rt a -> IO ()Source
Remove a row from the database without fetching it first.
Functions for accessing and using Models
modelName :: forall a. Model a => a -> ByteStringSource
Lookup the modelTable
of a Model
(modelName _ =
).
modelTable
(modelInfo
:: ModelInfo
a)
primaryKey :: Model a => a -> DBKeySource
Lookup the primary key of a Model
.
modelSelectFragment :: ModelIdentifiers a -> ByteStringSource
Generate a SQL SELECT
statement with no WHERE
predicate. For
example, defaultModelLookupQuery
consists of
modelSelectFragment
followed by "WHERE
primary-key = ?".
A newtype wrapper in the FromRow
class, permitting every model
to be used as the result of a database query.
A newtype wrapper in the ToRow
class, which marshalls every
field except the primary key, followed by the primary key. For use
with modelUpdateQuery
.
Constructors
UpdateRow a |
A newtype wrapper in the ToRow
class, which marshalls every
field except the primary key. For use with modelInsertQuery
.
Constructors
InsertRow a |
Table aliases
The newtype As
can be wrapped around an existing type to give
it a table name alias in a query. This is necessary when a model
is being joined with itself, to distinguish the two joined
instances of the same table.
For example:
{-# LANGUAGE OverloadedStrings #-} data X = X instanceRowAlias
X where rowAliasName = const "x" ... r <-dbSelect
c $ addWhere_ "bar.bar_key = x.bar_parent" modelDBSelect :: IO [Bar :. As X Bar]
Instances
(RowAlias alias, Show row) => Show (As alias row) | |
(Model a, RowAlias as) => Model (As as a) | A degenerate instance of |
fromAs :: alias -> As alias row -> rowSource
fromAs
extracts the row
from an
, but
constrains the type of As
alias rowalias
to be the same as its first argument
(which is non-strict). This can save you from explicitly
specifying types. For example:
data X = X deriving (Generic) instance RowAlias X where rowAliasName = const "x" ... r <- map (\(b1 :. b2) -> (b1, fromAs X b2)) <$> dbSelect c $ addWhere \"bar.bar_key = x.bar_parent\" modelDBSelect
The class of types that can be used as tags in as As
alias.
Such types should be unit types--in other words, have exactly one
constructor where the constructor is nullary (take no arguments).
The reason for this class is that the Model
instance for As
requires a way to extract the name of the row alias without having
a concrete instance of the type. This is provided by the
rowAliasName
method (which must be non-strict).
Methods
rowAliasName :: g a row -> ByteStringSource
Return the SQL identifier for the row alias. This method must be non-strict in its argument. Hence, it should discard the argument and return the name of the alias. For example:
{-# LANGUAGE OverloadedStrings #-} data My_alias = My_alias instance RowAlias My_alias where rowAliasName _ = "my_alias"
Keep in mind that PostgreSQL folds unquoted identifiers to
lower-case. However, this library quotes row aliases in SELECT
statements, thereby preserving case. Hence, if you want to call
construct a WHERE
clause without double-quoting row aliases in
your Query
, you should avoid capital letters in alias names.
A default implementation of rowAliasName
exists for unit types
(as well as empty data declarations) in the Generic
class. The
default converts the first character of the type name to
lower-case, following the logic of defaultModelTable
.
Low-level functions providing manual access to defaults
defaultModelInfo :: forall a. (Generic a, GDatatypeName (Rep a), GColumns (Rep a), GPrimaryKey0 (Rep a)) => ModelInfo aSource
The default definition of modelInfo
. See the documentation at
Model
for more information. Sets modelTable
to the name of the
type with the first character converted to lower-case. Sets
modelColumns
to the names of the Haskell field selectors. Sets
modelPrimaryColumn
to 0
and extracts the first field of the
structure for modelGetPrimaryKey
. Will fail to compile unless
the data structure is defined with record syntax and that its first
field is of type DBKey
.
Note that defaults for the individual fields are available in
separate functions (e.g., defaultModelTable
) with fewer class
requirements in the context, in case you want to make piecemeal use
of defaults. The default for modelPrimaryColumn
is 0. If you
overwrite that, you will need to overwrite modelGetPrimaryKey
as
well (and likely vice versa).
defaultModelTable :: (Generic a, GDatatypeName (Rep a)) => a -> ByteStringSource
The default name of the database table corresponding to a Haskell type. The default is the same as the type name with the first letter converted to lower-case. (The rationale is that Haskell requires types to start with a capital letter, but all-lower-case table names are easier to use in queries because PostgreSQL generally does not require them to be quoted.)
defaultModelColumns :: (Generic a, GColumns (Rep a)) => a -> [ByteString]Source
Returns the Haskell field names in a data structure.
defaultModelGetPrimaryKey :: (Generic a, GPrimaryKey0 (Rep a)) => a -> DBKeySource
defaultModelIdentifiers :: ModelInfo a -> ModelIdentifiers aSource
The default simply quotes the modelInfo
and modelColumns
fields of ModelInfo
using quoteIdent
.
defaultModelQueries :: ModelIdentifiers a -> ModelQueries aSource
The default value of modelQueries
.
defaultModelLookupQuery :: ModelIdentifiers a -> QuerySource
Default SQL lookup query for a model.
defaultModelUpdateQuery :: ModelIdentifiers a -> QuerySource
Default SQL update query for a model.
defaultModelInsertQuery :: ModelIdentifiers a -> QuerySource
Default SQL insert query for a model.
defaultModelDeleteQuery :: ModelIdentifiers a -> QuerySource
Default SQL delete query for a model.
Helper functions and miscellaneous internals
quoteIdent :: ByteString -> ByteStringSource
Quote an identifier such as a table or column name using
double-quote characters. Note this has nothing to do with quoting
values, which must be quoted using single quotes. (Anyway, all
values should be quoted by query
or fmtSql
.) This function
uses a unicode escape sequence to escape '?' characters, which
would otherwise be expanded by query
, formatQuery
, or fmtSql
.
>>>
S8.putStrLn $ quoteIdent "hello \"world\"!"
"hello ""world""!">>>
S8.putStrLn $ quoteIdent "hello \"world\"?"
U&"hello ""world""\003f"
Note that this quoting function is correct only if
client_encoding
is SQL_ASCII
, client_coding
is UTF8
, or the
identifier contains no multi-byte characters. For other coding
schemes, this function may erroneously duplicate bytes that look
like quote characters but are actually part of a multi-byte
character code. In such cases, maliciously crafted identifiers
will, even after quoting, allow injection of arbitrary SQL commands
to the server.
The upshot is that it is unwise to use this function on identifiers
provided by untrustworthy sources. Note this is true anyway,
regardless of client_encoding
setting, because certain "system
column" names (e.g., oid
, tableoid
, xmin
, cmin
, xmax
,
cmax
, ctid
) are likely to produce unexpected results even when
properly quoted.
See Id
for a convenient way to include quoted identifiers in
parameter lists.
Phantom type for instantiating GDBRef
that represents a one-to-many
relationship between tables.
Constructors
NormalRef |
Phantom type for instantiating GDBRef
that represents a one-to-one
relationship between tables.
Constructors
UniqueRef |
data ModelCreateInfo a Source
Extra information for Database.PostgreSQL.ORM.CreateTable. You probably don't need to use this.
Constructors
ModelCreateInfo | |
Fields
|
Instances
Show (ModelCreateInfo a) |
emptyModelCreateInfo :: ModelCreateInfo aSource
A ModelCreateInfo
that doesn't imply any extra constraints or
exceptions.
defaultToRow :: (Generic a, GToRow (Rep a)) => a -> [Action]Source
This function provides a toRow
function for Generic
types
that marshalls each field of the data type in the order in which it
appears in the type definition. This function is not a suitable
implementation of modelWrite
(since it marshals the primary key,
which is not supposed to be written). However, it is required
internally by defaultModelWrite
, and exposed in the unlikely
event it is of use to alternate generic modelWrite
functions.
You probably don't want to call this function.
Helper classes
These classes are used internally to manipulate the Rep
representations of Generic
data structures. You should not be
defining instances of or using these classes directly. The names
are exported so that you can include them in the context of the
type signatures of your functions, should you wish to make use of
the various default
... funcitons in this file.
class GPrimaryKey0 f Source
This class extracts the first field in a data structure when the
field is of type DBKey
. If you get a compilation error because
of this class, then move the DBKey
first in your data structure.
Instances
GPrimaryKey0 a => GPrimaryKey0 (:*: a b) | |
GPrimaryKey0 f => GPrimaryKey0 (D1 c f) | |
GPrimaryKey0 f => GPrimaryKey0 (C1 c f) | |
RequireSelector c => GPrimaryKey0 (S1 c (K1 i DBKey)) |
This class extracts the field names of a Haskell data structure. Only defined for types with a single constructor that uses record syntax.
class GDatatypeName f Source
This class returns the name of a datatype.
Instances
Datatype c => GDatatypeName (D1 c f) |