postgresql-orm-0.4.1: An ORM (Object Relational Mapping) and migrations DSL for PostgreSQL.

Safe HaskellNone
LanguageHaskell2010

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:

  1. The data type must have a single constructor that is defined using record selector syntax.
  2. The very first field of the data type must be a DBKey to represent the primary key. Other orders will cause a compilation error.
  3. Every field of the data structure must be an instance of FromField and ToField.

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).

Synopsis

The Model class

class Model a where Source

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:

  1. The data type must have a single constructor that is defined using record selector syntax.
  2. The very first field of the data type must be a DBKey to represent the primary key. Other orders will cause a compilation error.
  3. Every field of the data structure must be an instance of FromField and ToField.

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).

Minimal complete definition

Nothing

Methods

modelInfo :: ModelInfo a Source

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 a Source

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 a Source

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:

  -- Call field 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 saved.

modelQueries :: ModelQueries a Source

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 a Source

Extra constraints, if any, to place in a CREATE TABLE statement. Only used by Database.PostgreSQL.ORM.CreateTable.

modelValid :: a -> ValidationError Source

Perform a validation of the model, returning any errors if it is invalid.

Instances

FromField t => Model [t] Source 
Model a => Model (Maybe a) Source

A degenerate model that lifts any model to a Maybe version. Returns Nothing on a parse failure. Useful, for example, for performing outer joins: dbJoin modelDBSelect "LEFT OUTER JOIN" (addWhere 'foo = 123' $ modelDBSelect) "USING a.id = b.a_id" :: (A :. Maybe B)

FromField t => Model (Only t) Source 
(FromField a, FromField b) => Model (a, b) Source 
(Model a, Model b) => Model ((:.) a b) Source

A degenerate instance of model representing a database join. The :. instance does not allow normal model operations such as findRow, save, and destroy. Attempts to use such functions will result in an exception.

(Model a, RowAlias as) => Model (As as a) Source

A degenerate instance of Model that re-names the row with a SQL AS keyword. This is primarily useful when joining a model with itself. Hence, standard operations (findRow, save, destroy) are not allowed on As models.

(FromField a, FromField b, FromField c) => Model (a, b, c) Source 
(FromField a, FromField b, FromField c, FromField d) => Model (a, b, c, d) Source 
(FromField a, FromField b, FromField c, FromField d, FromField e) => Model (a, b, c, d, e) Source 

data ModelInfo a Source

A ModelInfo T contains the information necessary for mapping T to a database table. Each Model type has a single 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

modelTable :: !ByteString

The name of the database table corresponding to this model. The default modelInfo instance uses defaultModelTable, which is the name of your data type with the first letter downcased.

modelColumns :: ![ByteString]

The names of the database columns corresponding to fields of this model. The column names should appear in the order in which the fields are defined in the Haskell data type a (which should also be the order in which modelRead parses them to an a and modelWrite marshalls them).

Note that all queries generated by the library specify explicit column names. Hence the order of columns does not need to match their order in the database table. They should instead match the order of fields in the Haskell data structure.

The default, given by defaultModelColumns, is to use the Haskell field names for a. This default will fail to compile if a is not defined using record syntax.

modelPrimaryColumn :: !Int

The 0-based index of the primary key column in modelColumns. This should be 0 when your data structure's first field is its DBKey (highly recommended, and required by defaultModelGetPrimaryKey). If you customize this field, you must also customize modelGetPrimaryKey--no check is made that the two are consistent.

modelGetPrimaryKey :: !(a -> DBKey)

Return the primary key of a particular model instance. If you customize this field, you must also customize modelPrimaryColumn--no check is made that the two are consistent.

Instances

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

modelQTable :: !ByteString

Literal SQL for the name of the table.

modelQColumns :: ![ByteString]

Literal SQL for each, table-qualified column.

modelQPrimaryColumn :: ByteString

Literal SQL for the model's table-qualified primary key column.

modelQWriteColumns :: [ByteString]

Literal SQL for all the columns except the primary key. These are the columns that should be included in an INSERT or UPDATE. Note that unlike the other fields, these column names should not be table-qualified.

modelQualifier :: !(Maybe ByteString)

When all columns in modelQColumns are qualified by the same table name, this field contains Just the table name. For the :. type (in which different columns have different table qualifications), this field is Nothing.

For normal models, this field will be identical to modelQTable. However, for As models, modelQTable will contain unquoted SQL such as "\"MyType\" AS \"my_alias\"", in which case modelQualifier will contain Just "\"my_alias\"".

modelOrigTable :: !(Maybe ByteString)

The original, unquoted name of the table representing the model in the database. Ordinarily, this should be the same as modelTable in ModelInfo, but in the case of As aliases, the modelTable is an alias, and modelOrigTable is the original table. Nothing for joins.

data ModelQueries a Source

Standard CRUD (create/read/update/delete) queries on a model.

Constructors

ModelQueries 

Fields

modelLookupQuery :: !Query

A query template for looking up a model by its primary key. Expects a single query parameter, namely the DBKey or DBRef being looked up.

modelUpdateQuery :: !Query

A query template for updating an existing Model in the database. Expects as query parameters a value for every column of the model except the primary key, followed by the primary key. (The primary key is not written to the database, just used to select the row to change.)

modelInsertQuery :: !Query

A query template for inserting a new Model in the database. The query parameters are values for all columns except the primary key. The query returns the full row as stored in the database (including the values of fields, such as the primary key, that have been chosen by the database server).

modelDeleteQuery :: !Query

A query template for deleting a Model from the database. Should have a single query parameter, namely the DBKey of the row to delete.

Instances

underscoreModelInfo :: (Generic a, GToRow (Rep a), GFromRow (Rep a), GPrimaryKey0 (Rep a), GColumns (Rep a), GDatatypeName (Rep a)) => ByteString -> ModelInfo a Source

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

type DBKeyType = Int64 Source

A type large enough to hold database primary keys. Do not use this type directly in your data structures. Use DBKey to hold a Model's primary key and DBRef to reference the primary key of another model.

data DBKey Source

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.

Constructors

DBKey !DBKeyType 
NullKey 

isNullKey :: DBKey -> Bool Source

Returns True when a DBKey is NullKey.

type DBRef = GDBRef NormalRef Source

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 DBRefUnique represents a one-to-one relationship.

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 UniqueRef Source

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 DBRef represents a many-to-one relationship.

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).

Constructors

DBRef DBKeyType 

Instances

Model a => SqlType (DBRefUnique a) Source 
Model a => SqlType (DBRef a) Source 
Bounded (GDBRef reftype table) Source 
Enum (GDBRef reftype table) Source 
Eq (GDBRef reftype table) Source 
Integral (GDBRef reftype table) Source 
(Data reftype, Data table) => Data (GDBRef reftype table) Source 
Num (GDBRef reftype table) Source 
Ord (GDBRef reftype table) Source 
Model t => Read (GDBRef rt t) Source 
Real (GDBRef reftype table) Source 
Model t => Show (GDBRef rt t) Source 
Generic (GDBRef reftype table) Source 
ToJSON (GDBRef t a) Source 
FromJSON (GDBRef t a) Source 
ToField (GDBRef rt t) Source 
FromField (GDBRef rt t) Source 
type Rep (GDBRef reftype table) Source 

mkDBRef :: Model a => a -> GDBRef rt a Source

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

Dump an entire model. Useful for development and debugging only, as every row will be read into memory before the function returns.

Note that unlike the other primary model operations, it is OK to call findAll even on degenerate models such as As and :..

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 r Source

Like trySave but instead of returning an Either, throws a ValidationError if the Model is invalid.

save_ :: Model r => Connection -> r -> IO () Source

save but returning '()' instead of the saved model.

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 -> ByteString Source

Lookup the modelTable of a Model (modelName _ = modelTable (modelInfo :: ModelInfo a)).

primaryKey :: Model a => a -> DBKey Source

Lookup the primary key of a Model.

modelSelectFragment :: ModelIdentifiers a -> ByteString Source

Generate a SQL SELECT statement with no WHERE predicate. For example, defaultModelLookupQuery consists of modelSelectFragment followed by "WHERE primary-key = ?".

newtype LookupRow a Source

A newtype wrapper in the FromRow class, permitting every model to be used as the result of a database query.

Constructors

LookupRow 

Fields

lookupRow :: a
 

Instances

newtype UpdateRow a Source

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 

Instances

newtype InsertRow a Source

A newtype wrapper in the ToRow class, which marshalls every field except the primary key. For use with modelInsertQuery.

Constructors

InsertRow a 

Instances

Table aliases

newtype As alias row Source

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 instance RowAlias X where rowAliasName = const "x"

... r <- dbSelect c $ addWhere_ "bar.bar_key = x.bar_parent" modelDBSelect :: IO [Bar :. As X Bar] @

Constructors

As 

Fields

unAs :: row
 

Instances

(RowAlias alias, Show row) => Show (As alias row) Source 
(Model a, RowAlias as) => Model (As as a) Source

A degenerate instance of Model that re-names the row with a SQL AS keyword. This is primarily useful when joining a model with itself. Hence, standard operations (findRow, save, destroy) are not allowed on As models.

fromAs :: alias -> As alias row -> row Source

fromAs extracts the row from an As alias row, but constrains the type of alias 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

toAs :: alias -> row -> As alias row Source

A type-restricted wrapper around the As constructor, under the same rationale as fromAs. Not strict in its first argument.

class RowAlias a where Source

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).

Minimal complete definition

Nothing

Methods

rowAliasName :: g a row -> ByteString Source

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 a Source

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 -> ByteString Source

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 -> DBKey Source

Extract the primary key of type DBKey from a model when the DBKey is the first element of the data structure. Fails to compile if the first field is not of type DBKey.

defaultModelIdentifiers :: ModelInfo a -> ModelIdentifiers a Source

The default simply quotes the modelInfo and modelColumns fields of ModelInfo using quoteIdent.

defaultModelWrite :: forall a. (Model a, Generic a, GToRow (Rep a)) => a -> [Action] Source

Returns a series of Actions serializing each field of a data structure (in the order of the Haskell datatype definition), except the primary key, since the primary key should never be written to a database. Every field must be an instance of ToField.

defaultModelLookupQuery :: ModelIdentifiers a -> Query Source

Default SQL lookup query for a model.

defaultModelUpdateQuery :: ModelIdentifiers a -> Query Source

Default SQL update query for a model.

defaultModelInsertQuery :: ModelIdentifiers a -> Query Source

Default SQL insert query for a model.

defaultModelDeleteQuery :: ModelIdentifiers a -> Query Source

Default SQL delete query for a model.

Helper functions and miscellaneous internals

quoteIdent :: ByteString -> ByteString Source

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.

data NormalRef Source

Phantom type for instantiating GDBRef that represents a one-to-many relationship between tables.

Constructors

NormalRef 

data UniqueRef Source

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

modelCreateColumnTypeExceptions :: ![(ByteString, ByteString)]

A list of (column-name, type) pairs for which you want to override the default.

modelCreateExtraConstraints :: !ByteString

Extra constraints to stick at the end of the CREATE TABLE statement.

Instances

emptyModelCreateInfo :: ModelCreateInfo a Source

A ModelCreateInfo that doesn't imply any extra constraints or exceptions.

defaultFromRow :: (Generic a, GFromRow (Rep a)) => RowParser a Source

This function provides a fromRow function for Generic types, suitable as a default of the FromRow class. This module uses it as the default implementation of modelRead.

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.

printq :: Query -> IO () Source

Print to stdout the query statement.

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.

Minimal complete definition

gPrimaryKey0

class GColumns f Source

This class extracts the field names of a Haskell data structure. Only defined for types with a single constructor that uses record syntax.

Minimal complete definition

gColumns

class GDatatypeName f Source

This class returns the name of a datatype.

Minimal complete definition

gDatatypeName

Instances

class GFromRow f Source

Minimal complete definition

gFromRow

Instances

class GToRow f Source

Minimal complete definition

gToRow

Instances

GToRow U1 Source 
ToField c => GToRow (K1 i c) Source 
(GToRow a, GToRow b) => GToRow ((:*:) a b) Source 
GToRow f => GToRow (M1 i c f) Source