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

Safe HaskellNone
LanguageHaskell2010

Database.PostgreSQL.ORM

Contents

Synopsis

The Model class and related types

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.

modelValid :: a -> ValidationError Source

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

Instances

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

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) 
(FromField a, FromField b) => Model (a, b) 
(Model a, Model b) => Model ((:.) a b)

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)

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

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

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

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

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.

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.

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

Lookup the primary key of a Model.

data h :. t :: * -> * -> * infixr 3

A composite type to parse your custom data structures without having to define dummy newtype wrappers every time.

instance FromRow MyData where ...
instance FromRow MyData2 where ...

then I can do the following for free:

res <- query' c "..."
forM res $ \(MyData{..} :. MyData2{..}) -> do
  ....

Instances

(Eq h, Eq t) => Eq ((:.) h t) 
(Ord h, Ord t) => Ord ((:.) h t) 
(Read h, Read t) => Read ((:.) h t) 
(Show h, Show t) => Show ((:.) h t) 
(FromRow a, FromRow b) => FromRow ((:.) a b) 
(ToRow a, ToRow b) => ToRow ((:.) a b) 
(Model a, Model b) => Model ((:.) a b)

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.

Typeable (* -> * -> *) (:.) 

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) 
(Model a, RowAlias as) => Model (As as a)

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.

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.

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

Single-row operations

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.

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

save :: Model r => Connection -> r -> IO r Source

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.

Abstracted select queries

data DBSelect a Source

A deconstructed SQL select statement that allows easier manipulation of individual terms. Several functions are provided to combine the selFields, selFrom, and selWhere clauses of muliple DBSelect structures. Other clauses may be discarded when combining queries with join operations. Hence it is advisable to set the other clauses at the end (or, if you set these fields, to collapse your DBSelect structure into a subquery using dbProject').

Constructors

DBSelect 

Fields

selWith :: !Query
 
selSelectKeyword :: !Query

By default "SELECT", but might usefully be set to something else such as "SELECT DISTINCT" in some situations.

selFields :: Query
 
selFrom :: !FromClause
 
selWhereKeyword :: !Query

Empty by default, but set to "WHERE" if any WHERE clauses are added to the selWhere field.

selWhere :: !Query
 
selGroupBy :: !Query
 
selHaving :: !Query
 
selOrderBy :: !Query
 
selLimit :: !Query
 
selOffset :: !Query
 

Instances

Show (DBSelect a) 
Generic (DBSelect a) 
type Rep (DBSelect a) 

modelDBSelect :: forall a. Model a => DBSelect a Source

A DBSelect that returns all rows of a model.

dbSelectParams :: (Model a, ToRow p) => DBSelect a -> Connection -> p -> IO [a] Source

Run a DBSelect query on parameters. The number of '?' characters embedeed in various fields of the DBSelect must exactly match the number of fields in parameter type p. Note the order of arguments is such that the DBSelect can be pre-rendered and the parameters supplied later. Hence, you should use this version when the DBSelect is static. For dynamically modified DBSelect structures, you may prefer dbSelect.

dbSelect :: Model a => Connection -> DBSelect a -> IO [a] Source

Run a DBSelect query and return the resulting models.

addWhere_ :: Query -> DBSelect a -> DBSelect a Source

Add a where clause verbatim to a DBSelect. The clause must not contain the WHERE keyword (which is added automatically by addWhere_ if needed). If the DBSelect has existing WHERE clauses, the new clause is appended with AND. If the query contains any '?' characters, they will be rendered into the query and matching parameters will later have to be filled in via a call to dbSelectParams.

addWhere :: ToRow p => Query -> p -> DBSelect a -> DBSelect a Source

Add a where clause, and pre-render parameters directly into the clause. The argument p must have exactly as many fields as there are '?' characters in the Query. Example:

bars <- dbSelect c $ addWhere "bar_id = ?" (Only target_id) $
                     (modelDBSelect :: DBSelect Bar)

setOrderBy :: Query -> DBSelect a -> DBSelect a Source

Set the ORDER BY clause of a DBSelect. Example:

dbSelect c $ setOrderBy "\"employeeName\" DESC NULLS FIRST" $
               modelDBSelect

setLimit :: Int -> DBSelect a -> DBSelect a Source

Set the LIMIT clause of a DBSelect.

setOffset :: Int -> DBSelect a -> DBSelect a Source

Set the OFFSET clause of a DBSelect.

Associations between models

data Association a b Source

A data structure representing a relationship between a model a and a model b. At a high level, an Association a b tells you how to find rows of type b given rows of type a. More concretely, this boils down to being able to make two types of query.

  • You want to look up a bunch of (a :. b)s, filtering using predicates on both a and b (e.g., get a list of recent posts and their authors). For this purpose, you can use assocSelect, which allows you to addWhere predicates mentioning columns in both a and b.
  • You already have an instance of type a, and want to find all the bs associated with it. For that you use either assocWhere or findAssoc (which internally access fields assocSelectOnlyB, assocWhereQuery, and assocWhereParam). This type of query is strictly less general than the first one, but can be formulated in a more efficient way by extracting values directly from a concrete instance of a without needing to touch table a in the database.

Note that an Association is asymmetric. It tells you how to get bs from as, but not vice versa. In practice, there will almost always be an association in the other direction, too. Functions such as dbrefAssocs and jtAssocs therefore create an Association and its inverse simultaneously, returning them as a pair.

Instances

assocSelect :: Association a b -> DBSelect (a :. b) Source

General select returning all instances of a and b that match according to the association.

assocProject :: Model b => Association a b -> DBSelect b Source

A projection of assocSelect, extracting only the fields of model b. Note that this query touches table a even if it does not return results from a. Hence, you can use addWhere to add predicates on both a and b. (Note the contrast to assocSelectOnlyB, which does not touch table a at all, and hence in the case of an INNER JOIN might return rows of b that should not be part of the association. assocSelectOnlyB is intended for use only in conjunction with assocWhereQuery.)

assocWhere :: Model b => Association a b -> a -> DBSelect b Source

Returns a DBSelect for all bs associated with a particular a.

findAssoc :: Model b => Association a b -> Connection -> a -> IO [b] Source

Follow an association to return all of the bs associated with a particular a. The behavior is similar to:

findAssoc' ab c a = dbSelect c $ assocWhere ab a

But if the first argument is a static association, this function may be marginally faster because it pre-renders most of the query.

Parent-child associations

data GDBRefInfo reftype child parent Source

A common type of association is when one model contains a DBRef or DBRefUnique pointing to another model. In this case, the model containing the DBRef is known as the child, and the referenced model is known as the parent.

Two pieces of information are required to describe a parent-child relationship: First, the field selector that extracts the Haskell DBRef from the haskell type child, and second the name of the database column that stores this DBRef field.

For example, consider the following:

data Author = Author {
    authorId :: DBKey
  } deriving (Show, Generic)
instance Model Author

data Post = Post {
    postId :: DBKey
  , postAuthorId :: DBRef Author
  } deriving (Show, Generic)
instance Model Post

post_author_refinfo :: DBRefInfo Post Author
post_author_refinfo = DBRefInfo {
    dbrefSelector = postAuthorId
  , dbrefQColumn = "\"post\".\"postAuthorId\""
  }

Note that the parent-child relationship described by a GDBRefInfo is asymmetric, but bidirectional. When a DBRefInfo child parent exists, the schema should generally not permit the existence of a valid DBRefInfo parent child structure. However, the dbrefAssocs function generates Associations in both directions from a single DBRefInfo.

Constructing such parent-child Associations requires knowing how to extract primary keys from the parent type as well as the name of the column storing primary keys in parent. Fortunately, this information is already available from the Model class, and thus does not need to be in the GDBRefInfo. (Most functions on GDBRefInfos require parent and child to be instances of Model.)

When your Models are instances of Generic (which will usually be the case), a DBRefInfo structure can be computed automatically by defaultDBRefInfo. This is the recommended way to produce a GDBRefInfo. (Alternatively, see has and belongsTo to make use of an entirely implicit DBRefInfo.)

Constructors

DBRefInfo 

Fields

dbrefSelector :: !(child -> GDBRef reftype parent)

Field selector returning a reference.

dbrefQColumn :: !ByteString

Literal SQL for the database column storing the reference. This should be double-quoted and table-qualified, in case the column name is a reserved keyword, contains capital letters, or conflicts with the name of a column in the joined table. An example would be:

dbrefQColumn = "\"table_name\".\"column_name\""

Instances

Show (GDBRefInfo rt c p) 

type DBRefInfo = GDBRefInfo NormalRef Source

DBRefInfo is a type alias for the common case that the reference in a GDBRefInfo is a DBRef (as opposed to a DBRefUnique). The functions in this library do not care what type of reference is used. The type is generalized to GDBRefInfo just to make it easier to assign a selector to dbrefSelector when the selector returns a DBRefUnique. Note, however, that defaultDBRefInfo returns a DBRefInfo regardless of the flavor of reference actually encountered.

defaultDBRefInfo :: forall child parent. (Model child, Model parent, GetField ExtractRef child (DBRef parent)) => DBRefInfo child parent Source

Creates a DBRefInfo from a model child that references parent. For this to work, the child type must be an instance of Generic and must contain exactly one field of the any of the following types:

  1. GDBRef rt parent, which matches both DBRef parent and DBRefUnique parent.
  2. Maybe (GDBRef rt parent), for cases where the reference might be NULL. Note, however, that an exception will be thrown if you call findAssoc on a child whose reference is Nothing.

A special case arises when a Model contains a DBRef to itself. If you just wish to find parents and children given an existing structure (i.e., findAssoc), it is okay to declare an Association MyType MyType. However, in this case attempts to use assocSelect will then fail. To work around this problem, the parent must use a row alias.

Note that currently aliasing the child will not work, since the As data structure will not contain a DBRef field, only the contents of the As data structure. An example of doing this correctly (using has and belongsTo, both of which wrap defaultDBRefInfo):

data Bar = Bar {
    barId :: !DBKey
  , barName :: !String
  , barParent :: !(Maybe (DBRef Bar))
  } deriving (Show, Generic)
instance Model Bar where modelInfo = underscoreModelInfo "bar"

data ParentBar = ParentBar
instance RowAlias ParentBar where rowAliasName _ = "parent_bar"

toParent :: Association Bar (As ParentBar Bar)
toParent = belongsTo

toChild :: Association (As ParentBar Bar) Bar
toChild = has

dbrefAssocs :: forall child parent rt. (Model child, Model parent) => GDBRefInfo rt child parent -> (Association child parent, Association parent child) Source

Generate both the child-parent and parent-child Associations implied by a GDBRefInfo.

has :: (Model child, Model parent, GetField ExtractRef child (DBRef parent)) => Association parent child Source

Short for

snd $ dbrefAssocs defaultDBRefInfo

Note the inverse Association is given by belongsTo. For example, given the Author and Post models described in the documentation for GDBRefInfo, in which each Post references an Author, you might say:

author_post :: Association Author Post
author_post = has

post_author :: Association Post Author
post_author = belongsTo

belongsTo :: (Model child, Model parent, GetField ExtractRef child (DBRef parent)) => Association child parent Source

The inverse of has. Short for

fst $ dbrefAssocs defaultDBRefInfo

See an example at has.

Join table associations

data JoinTable a b Source

A data structure representing a dedicated join table in the database. A join table differs from a model in that rows do not have primary keys. Hence, model operations do not apply. Nonetheless a join table conveys information about a relationship between models.

Note that all names in a JoinTable should be unquoted.

Constructors

JoinTable 

Fields

jtTable :: !ByteString

Name of the join table in the database. (Not quoted.)

jtColumnA :: !ByteString

Name of the column in table jtTable that contains a DBRef to model a. (Not quoted or table-qualified.)

jtColumnB :: !ByteString

Like jtColumnA for model b.

Instances

Show (JoinTable a b) 

defaultJoinTable :: forall a b. (Model a, Model b) => JoinTable a b Source

The default join table has the following fields:

  • jtName is the name of the two models (in alphabetical order), separated by an '_' character.
  • jtColumnA is the name of model a, an '_' character, and the name of the primary key column in table a.
  • jtColumnB is the name of model b, an '_' character, and the name of the primary key column in table b.

Note that defaultJoinTable cannot create a default join table for joining a model to itself, as following these rules the two columns would have the same name. If you wish to join a table to itself, you have two options: First, you can define the join table and assign the column names manually. This will permit you to call findAssoc, but you still will not be able to use assocSelect for more complex queries, since SQL does not permit joins between two tables with the same name. The second option is to give one of the sides of the join table a row alias with As. For example:

data ParentBar = ParentBar
instance RowAlias ParentBar where rowAliasName _ = "parent_bar"

selfJoinTable :: JoinTable Bar (As ParentBar Bar)
selfJoinTable = defaultJoinTable

selfJoin :: Association Bar (As ParentBar Bar)
otherSelfJoin :: Association (As ParentBar Bar) Bar
(selfJoin, otherSelfJoin) = jtAssocs selfJoinTable

jtAssocs :: (Model a, Model b) => JoinTable a b -> (Association a b, Association b a) Source

Generate the two associations implied by a JoinTable.

jtAdd :: (Model a, Model b) => JoinTable a b -> Connection -> a -> b -> IO Bool Source

Add an association between two models to a join table. Returns True if the association was not already there.

jtRemove :: (Model a, Model b) => JoinTable a b -> Connection -> a -> b -> IO Bool Source

Remove an association from a join table. Returns True if the association was previously there.

jtRemoveByRef :: (Model a, Model b) => JoinTable a b -> Connection -> GDBRef rt a -> GDBRef rt b -> IO Bool Source

Remove an assocation from a join table when you don't have the target instances of the two models handy, but do have references.

Chaining associations

nestAssoc :: (Model a, Model b) => Association a b -> Association b c -> Association a (b :. c) Source

Combine two associations into one.

chainAssoc :: (Model a, Model b, Model c) => Association a b -> Association b c -> Association a c Source

Combine two associations into one, and project away the middle type. (The middle type can still be mentioned in WHERE clauses.)

An example:

data Author = Author {
    authorId :: DBKey
  } deriving (Show, Generic)
instance Model Author where modelInfo = underscoreModelInfo "author"

data Post = Post {
    postId :: DBKey
  , postAuthorId :: DBRef Author
  } deriving (Show, Generic)
instance Model Post where modelInfo = underscoreModelInfo "post"

data Comment = Comment {
    commentId :: DBKey
  , commentPostId :: DBRef Post
  } deriving (Show, Generic)
instance Model Comment where modelInfo = underscoreModelInfo "comment"

author_posts :: Association Author Post
post_author :: Association Post Author
(post_author, author_posts) = dbrefAssocs defaultDBRefInfo

-- Could equally well use dbrefAssocs as above
post_comments :: Association Post Comment
post_comments = has

comment_post :: Association Comment Post
comment_post = belongsTo

comment_author :: Association Comment Author
comment_author = chainAssoc comment_post post_author

author_comments :: Association Author Comment
author_comments =  chainAssoc author_posts post_comments

Validations

validate Source

Arguments

:: (a -> Bool) 
-> Text

Column name

-> Text

Error description

-> ValidationFunc a