| Safe Haskell | None |
|---|
Database.PostgreSQL.ORM.Association
Contents
- data Association a b = Association {
- assocSelect :: !(DBSelect (a :. b))
- assocSelectOnlyB :: !(DBSelect b)
- assocWhereQuery :: !Query
- assocWhereParam :: !(a -> [Action])
- assocProject :: Model b => Association a b -> DBSelect b
- assocWhere :: Model b => Association a b -> a -> DBSelect b
- findAssoc :: Model b => Association a b -> Connection -> a -> IO [b]
- data GDBRefInfo reftype child parent = DBRefInfo {
- dbrefSelector :: !(child -> GDBRef reftype parent)
- dbrefQColumn :: !ByteString
- type DBRefInfo = GDBRefInfo NormalRef
- defaultDBRefInfo :: forall child parent. (Model child, Model parent, GetField ExtractRef child (DBRef parent)) => DBRefInfo child parent
- dbrefAssocs :: forall child parent rt. (Model child, Model parent) => GDBRefInfo rt child parent -> (Association child parent, Association parent child)
- has :: (Model child, Model parent, GetField ExtractRef child (DBRef parent)) => Association parent child
- belongsTo :: (Model child, Model parent, GetField ExtractRef child (DBRef parent)) => Association child parent
- data JoinTable a b = JoinTable {
- jtTable :: !ByteString
- jtColumnA :: !ByteString
- jtColumnB :: !ByteString
- defaultJoinTable :: forall a b. (Model a, Model b) => JoinTable a b
- jtAssocs :: (Model a, Model b) => JoinTable a b -> (Association a b, Association b a)
- joinTable :: (Model a, Model b) => Association a b
- jtAdd :: (Model a, Model b) => JoinTable a b -> Connection -> a -> b -> IO Bool
- jtRemove :: (Model a, Model b) => JoinTable a b -> Connection -> a -> b -> IO Bool
- jtRemoveByRef :: (Model a, Model b) => JoinTable a b -> Connection -> GDBRef rt a -> GDBRef rt b -> IO Bool
- jtAddStatement :: JoinTable a b -> Query
- jtRemoveStatement :: JoinTable a b -> Query
- jtParam :: (Model a, Model b) => JoinTable a b -> a -> b -> [Action]
- jtFlip :: JoinTable a b -> JoinTable b a
- jtAssoc :: forall a b. (Model a, Model b) => JoinTable a b -> Association a b
- nestAssoc :: (Model a, Model b) => Association a b -> Association b c -> Association a (b :. c)
- chainAssoc :: (Model a, Model b, Model c) => Association a b -> Association b c -> Association a c
Documentation
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
(as, filtering using predicates on both:.b)aandb(e.g., get a list of recent posts and their authors). For this purpose, you can useassocSelect, which allows you toaddWherepredicates mentioning columns in bothaandb. - You already have an instance of type
a, and want to find all thebs associated with it. For that you use eitherassocWhereorfindAssoc(which internally access fieldsassocSelectOnlyB,assocWhereQuery, andassocWhereParam). 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 ofawithout needing to touch tableain 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.
Constructors
| Association | |
Fields
| |
Instances
| Show (Association a b) |
assocProject :: Model b => Association a b -> DBSelect bSource
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 bSource
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.
Associations based on parent-child relationships
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 exists, the schema should generally not permit the
existence of a valid DBRefInfo child
parent structure.
However, the DBRefInfo parent childdbrefAssocs 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
| |
Instances
| Show (GDBRefInfo rt c p) |
type DBRefInfo = GDBRefInfo NormalRefSource
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 parentSource
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:
-
, which matches bothGDBRefrt parentandDBRefparent.DBRefUniqueparent -
Maybe (, for cases where the reference might beGDBRefrt parent)NULL. Note, however, that an exception will be thrown if you callfindAssocon a child whose reference isNothing.
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
. However, in this case attempts to
use Association MyType MyTypeassocSelect 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 childSource
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 parentSource
Join table Associations
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
| |
defaultJoinTable :: forall a b. (Model a, Model b) => JoinTable a bSource
The default join table has the following fields:
-
jtNameis the name of the two models (in alphabetical order), separated by an'_'character. -
jtColumnAis the name of modela, an'_'character, and the name of the primary key column in tablea. -
jtColumnBis the name of modelb, an'_'character, and the name of the primary key column in tableb.
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.
joinTable :: (Model a, Model b) => Association a bSource
Generate a one-way association based on the default join table
naming scheme described at defaultJoinTable. Defined as:
joinTable = jtAssoc defaultJoinTable
For example:
aToB :: Association A B aToB = joinTable bToA :: Association B A bToA = joinTable
Operations on join tables
jtAdd :: (Model a, Model b) => JoinTable a b -> Connection -> a -> b -> IO BoolSource
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 BoolSource
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 BoolSource
Remove an assocation from a join table when you don't have the target instances of the two models handy, but do have references.
Semi-internal join table functions
jtAddStatement :: JoinTable a b -> QuerySource
A SQL statement suitable for adding a pair to a join table. Note
that the statement takes two parameters (i.e., contains two '?'
characters) corresponding to the primary keys of the two models
being associated. These parameters can be supplied by jtParam.
jtRemoveStatement :: JoinTable a b -> QuerySource
A SQL statement for removing a pair from a join table. Like
jtAddStatement, the query is parameterized by two primary keys.
jtParam :: (Model a, Model b) => JoinTable a b -> a -> b -> [Action]Source
Generate parameters for jtAddStatement and jtRemoveStatement.
The returned list is suitable for use as a ToRow instance. For
example:
execute conn (jtAddStatement my_join_table) (jtParam a b)
jtFlip :: JoinTable a b -> JoinTable b aSource
Flip a join table. This doesn't change the name of the table (since the same join table is used in both directions, and the default join table name glues together the two model names in alphabetical order anyway).
Nested and chained 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 cSource
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