pg-entity-0.0.4.4: A pleasant PostgreSQL layer
Copyright© Clément Delafargue 2018
Théophile Choutri 2021
LicenseMIT
Maintainertheophile@choutri.eu
Stabilitystable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Database.PostgreSQL.Entity

Description

A PostgreSQL database layer that does not get in your way.

See the Database.PostgreSQL.Entity.Internal.BlogPost module for an example of a data-type implementing the Entity typeclass.

Synopsis

The Entity Typeclass

class Entity e where Source #

An Entity stores the following information about the structure of a database table:

  • Its name
  • Its primary key
  • The fields it contains

Example

data ExampleEntity = E
  { key    :: Key
  , field1 :: Int
  , field2 :: Bool
  }
  deriving stock (Eq, Show, Generic)
  deriving anyclass (FromRow, ToRow)
  deriving Entity
     via (GenericEntity '[TableName "entities"] ExampleEntity)

When using the functions provided by this library, you will sometimes need to be explicit about the Entity you are referring to.

Since: 0.0.1.0

Minimal complete definition

Nothing

Methods

tableName :: Text Source #

The name of the table in the PostgreSQL database.

default tableName :: GetTableName (Rep e) => Text Source #

schema :: Maybe Text Source #

The name of the schema; will be appended to the table name: schema."tablename"

primaryKey :: Field Source #

The name of the primary key for the table.

default primaryKey :: GetFields (Rep e) => Field Source #

fields :: Vector Field Source #

The fields of the table.

default fields :: GetFields (Rep e) => Vector Field Source #

Instances

Instances details
Entity a => Entity (UpdateRow a) Source # 
Instance details

Defined in Database.PostgreSQL.Entity.Types

(EntityOptions t, GetTableName (Rep e), GetFields (Rep e)) => Entity (GenericEntity t e) Source # 
Instance details

Defined in Database.PostgreSQL.Entity.Types

Associated Types

data Field Source #

A wrapper for table fields.

Since: 0.0.1.0

Instances

Instances details
ForbiddenIsString => IsString Field Source #

Using the Overloaded String syntax for Field names is forbidden.

Instance details

Defined in Database.PostgreSQL.Entity.Internal.Unsafe

Methods

fromString :: String -> Field #

Show Field Source # 
Instance details

Defined in Database.PostgreSQL.Entity.Internal.Unsafe

Methods

showsPrec :: Int -> Field -> ShowS #

show :: Field -> String #

showList :: [Field] -> ShowS #

Eq Field Source # 
Instance details

Defined in Database.PostgreSQL.Entity.Internal.Unsafe

Methods

(==) :: Field -> Field -> Bool #

(/=) :: Field -> Field -> Bool #

High-level API

Glossary / Tips’n’Tricks

  • e, e1, e2: Represents an Entity
  • value: Represents a Haskell value that can be serialised to PostgreSQL
  • Field: Parameters of type Field can most often be passed in their textual form inside the field quasi-quoter, like [field| author_id :: uuid|]. This metaprogramming technique is here to better prevent empty fields from being passed. The PostgreSQL type annotation is optional, but necessary for arrays of UUIDs and of custom enums.

Consult the test suite to see those functions in action.

selectById :: forall e value m. (Entity e, FromRow e, MonadIO m, ToRow value) => value -> DBT m (Maybe e) Source #

Select an entity by its primary key.

Since: 0.0.1.0

selectOneByField :: forall e value m. (Entity e, FromRow e, MonadIO m, ToRow value) => Field -> value -> DBT m (Maybe e) Source #

Select precisely one entity by a provided field.

Since: 0.0.1.0

selectManyByField :: forall e value m. (Entity e, FromRow e, MonadIO m, ToRow value) => Field -> value -> DBT m (Vector e) Source #

Select potentially many entities by a provided field.

Since: 0.0.1.0

selectWhereNotNull :: forall e m. (Entity e, FromRow e, MonadIO m) => Vector Field -> DBT m (Vector e) Source #

Select statement with a non-null condition

See _selectWhereNotNull for the generated query.

Since: 0.0.1.0

selectWhereNull :: forall e m. (Entity e, FromRow e, MonadIO m) => Vector Field -> DBT m (Vector e) Source #

Select statement with a null condition

See _selectWhereNull for the generated query.

Since: 0.0.1.0

selectOneWhereIn :: forall e m. (Entity e, FromRow e, MonadIO m) => Field -> Vector Text -> DBT m (Maybe e) Source #

Select statement when for an entity where the field is one of the options passed

Since: 0.0.2.0

joinSelectById :: forall e1 e2 m. (Entity e1, Entity e2, FromRow e1, MonadIO m) => DBT m (Vector e1) Source #

Perform a INNER JOIN between two entities

Since: 0.0.1.0

joinSelectOneByField Source #

Arguments

:: forall e1 e2 value m. (Entity e1, Entity e2, FromRow e1, MonadIO m, ToField value) 
=> Field

The field over which the two tables will be joined

-> Field

The field in the where clause

-> value

The value of the where clause

-> DBT m (Vector e1) 

Perform a INNER JOIN ON field1 WHERE field2 = value between two entities

Since: 0.0.2.0

selectOrderBy :: forall e m. (Entity e, FromRow e, MonadIO m) => Vector (Field, SortKeyword) -> DBT m (Vector e) Source #

Perform a SELECT + ORDER BY query on an entity

Since: 0.0.2.0

Insertion

insert :: forall e values m. (Entity e, ToRow values, MonadIO m) => values -> DBT m () Source #

Insert an entity.

Since: 0.0.1.0

insertMany :: forall e values m. (Entity e, ToRow values, MonadIO m) => [values] -> DBT m () Source #

Insert multiple rows of an entity.

Since: 0.0.2.0

upsert Source #

Arguments

:: forall e values m. (Entity e, ToRow values, MonadIO m) 
=> values

Entity to insert

-> Vector Field

Fields to replace in case of conflict

-> DBT m () 

Insert an entity with a "ON CONFLICT DO UPDATE" clause on the primary key as the conflict target

Since: 0.0.2.0

Update

update :: forall e newValue m. (Entity e, ToRow newValue, MonadIO m) => newValue -> DBT m () Source #

Update an entity.

The Id of the entity is put at the end of the query automatically through the use of UpdateRow. Examples

let newAuthor = oldAuthor{…}
update @Author newAuthor

Since: 0.0.1.0

updateFieldsBy Source #

Arguments

:: forall e v1 v2 m. (Entity e, MonadIO m, ToRow v2, ToField v1) 
=> Vector Field

Fields to change

-> (Field, v1)

Field on which to match and its value

-> v2

New values of those fields

-> DBT m Int64 

Update rows of an entity matching the given value

Example

let newName = "Tiberus McElroy" :: Text
let oldName = "Johnson McElroy" :: Text
updateFieldsBy @Author [[field| name |]] ([field| name |], oldName) (Only newName)

Since: 0.0.1.0

Deletion

delete :: forall e value m. (Entity e, ToRow value, MonadIO m) => value -> DBT m () Source #

Delete an entity according to its primary key.

Since: 0.0.1.0

deleteByField :: forall e values m. (Entity e, ToRow values, MonadIO m) => Vector Field -> values -> DBT m () Source #

Delete rows according to the given fields

Example

deleteByField @BlogPost [[field| title |]] (Only "Echoes from the other world")

Since: 0.0.1.0

SQL Combinators API

Selection

_select :: forall e. Entity e => Query Source #

Produce a SELECT statement for a given entity.

Examples

>>> _select @BlogPost
"SELECT blogposts.\"blogpost_id\", blogposts.\"author_id\", blogposts.\"uuid_list\", blogposts.\"title\", blogposts.\"content\", blogposts.\"created_at\" FROM \"blogposts\""

Since: 0.0.1.0

_selectWithFields :: forall e. Entity e => Vector Field -> Query Source #

Produce a SELECT statement with explicit fields for a given entity

Examples

>>> _selectWithFields @BlogPost [ [field| blogpost_id |], [field| created_at |] ]
"SELECT \"blogposts\".\"blogpost_id\", \"blogposts\".\"created_at\" FROM \"\"blogposts\"\""

Since: 0.0.1.0

_where :: Vector Field -> Query Source #

Produce a WHERE clause, given a vector of fields.

It is most useful composed with a _select or _delete, which is why these two combinations have their dedicated functions, but the user is free to compose their own queries.

The Entity constraint is required for _where in order to get any type annotation that was given in the schema. Fields that do not exist in the Entity will be kept so that PostgreSQL can report the error.

Examples

>>> _select @BlogPost <> _where [[field| blogpost_id |]]
"SELECT blogposts.\"blogpost_id\", blogposts.\"author_id\", blogposts.\"uuid_list\", blogposts.\"title\", blogposts.\"content\", blogposts.\"created_at\" FROM \"blogposts\" WHERE \"blogpost_id\" = ?"
>>> _select @BlogPost <> _where [ [field| uuid_list |] ]
"SELECT blogposts.\"blogpost_id\", blogposts.\"author_id\", blogposts.\"uuid_list\", blogposts.\"title\", blogposts.\"content\", blogposts.\"created_at\" FROM \"blogposts\" WHERE \"uuid_list\" = ?"

Since: 0.0.1.0

_selectWhere :: forall e. Entity e => Vector Field -> Query Source #

Produce a SELECT statement for a given entity and fields.

Examples

>>> _selectWhere @BlogPost [ [field| author_id |] ]
"SELECT blogposts.\"blogpost_id\", blogposts.\"author_id\", blogposts.\"uuid_list\", blogposts.\"title\", blogposts.\"content\", blogposts.\"created_at\" FROM \"blogposts\" WHERE \"author_id\" = ?"
>>> _selectWhere @BlogPost [ [field| author_id |], [field| title |]]
"SELECT blogposts.\"blogpost_id\", blogposts.\"author_id\", blogposts.\"uuid_list\", blogposts.\"title\", blogposts.\"content\", blogposts.\"created_at\" FROM \"blogposts\" WHERE \"author_id\" = ? AND \"title\" = ?"

Since: 0.0.1.0

_selectWhereNotNull :: forall e. Entity e => Vector Field -> Query Source #

Produce a SELECT statement where the provided fields are checked for being non-null. r

>>> _selectWhereNotNull @BlogPost [ [field| author_id |] ]
"SELECT blogposts.\"blogpost_id\", blogposts.\"author_id\", blogposts.\"uuid_list\", blogposts.\"title\", blogposts.\"content\", blogposts.\"created_at\" FROM \"blogposts\" WHERE \"author_id\" IS NOT NULL"

Since: 0.0.1.0

_selectWhereNull :: forall e. Entity e => Vector Field -> Query Source #

Produce a SELECT statement where the provided fields are checked for being null.

>>> _selectWhereNull @BlogPost [ [field| author_id |] ]
"SELECT blogposts.\"blogpost_id\", blogposts.\"author_id\", blogposts.\"uuid_list\", blogposts.\"title\", blogposts.\"content\", blogposts.\"created_at\" FROM \"blogposts\" WHERE \"author_id\" IS NULL"

Since: 0.0.1.0

_selectWhereIn :: forall e. Entity e => Field -> Vector Text -> Query Source #

Produce a SELECT statement where the given field is checked aginst the provided array of values .

>>> _selectWhereIn @BlogPost [field| title |] [ "Unnamed", "Mordred's Song" ]
"SELECT blogposts.\"blogpost_id\", blogposts.\"author_id\", blogposts.\"uuid_list\", blogposts.\"title\", blogposts.\"content\", blogposts.\"created_at\" FROM \"blogposts\" WHERE \"title\" IN ('Unnamed', 'Mordred''s Song')"

Since: 0.0.2.0

_joinSelect :: forall e1 e2. (Entity e1, Entity e2) => Query Source #

Produce a "SELECT FROM" over two entities.

Examples

>>> _joinSelect @BlogPost @Author
"SELECT blogposts.\"blogpost_id\", blogposts.\"author_id\", blogposts.\"uuid_list\", blogposts.\"title\", blogposts.\"content\", blogposts.\"created_at\", authors.\"author_id\", authors.\"name\", authors.\"created_at\" FROM \"blogposts\" INNER JOIN \"authors\" USING(author_id)"

Since: 0.0.1.0

_innerJoin :: forall e. Entity e => Field -> Query Source #

Produce a "INNER JOIN … USING(…)" fragment.

Examples

>>> _innerJoin @BlogPost [field| author_id |]
" INNER JOIN \"blogposts\" USING(author_id)"

Since: 0.0.1.0

_joinSelectWithFields :: forall e1 e2. (Entity e1, Entity e2) => Vector Field -> Vector Field -> Query Source #

Produce a "SELECT [table1_fields, table2_fields] FROM table1 INNER JOIN table2 USING(table2_pk)" statement. The primary is used as the join point between the two tables.

Examples

>>> _joinSelectWithFields @BlogPost @Author [ [field| title |] ] [ [field| name |] ]
"SELECT \"blogposts\".\"title\", \"authors\".\"name\" FROM \"blogposts\" INNER JOIN \"authors\" USING(author_id)"

Since: 0.0.1.0

_joinSelectOneByField :: forall e1 e2. (Entity e1, Entity e2) => Field -> Field -> Query Source #

Produce a "SELECT FROM" over two entities.

Examples

>>> _joinSelectOneByField @BlogPost @Author [field| author_id |] [field| name |] :: Query
"SELECT blogposts.\"blogpost_id\", blogposts.\"author_id\", blogposts.\"uuid_list\", blogposts.\"title\", blogposts.\"content\", blogposts.\"created_at\" FROM \"blogposts\" INNER JOIN \"authors\" ON \"blogposts\".\"author_id\" = \"authors\".\"author_id\" WHERE authors.\"name\" = ?"

Since: 0.0.2.0

Insertion

_insert :: forall e. Entity e => Query Source #

Produce an INSERT statement for the given entity.

Examples

>>> _insert @BlogPost
"INSERT INTO \"blogposts\" (\"blogpost_id\", \"author_id\", \"uuid_list\", \"title\", \"content\", \"created_at\") VALUES (?, ?, ?, ?, ?, ?)"

Since: 0.0.1.0

_onConflictDoUpdate :: Vector Field -> Vector Field -> Query Source #

Produce a "ON CONFLICT (target) DO UPDATE SET …" statement.

Examples

>>> _onConflictDoUpdate [[field| blogpost_id |]] [ [field| title |], [field| content |]]
" ON CONFLICT (blogpost_id) DO UPDATE SET title = EXCLUDED.title, content = EXCLUDED.content"
>>> _onConflictDoUpdate [[field| blogpost_id |], [field| author_id |]] [ [field| title |], [field| content |]]
" ON CONFLICT (blogpost_id, author_id) DO UPDATE SET title = EXCLUDED.title, content = EXCLUDED.content"
>>> _insert @BlogPost <> _onConflictDoUpdate [[field| blogpost_id |]] [ [field| title |], [field| content |]]
"INSERT INTO \"blogposts\" (\"blogpost_id\", \"author_id\", \"uuid_list\", \"title\", \"content\", \"created_at\") VALUES (?, ?, ?, ?, ?, ?) ON CONFLICT (blogpost_id) DO UPDATE SET title = EXCLUDED.title, content = EXCLUDED.content"

Since: 0.0.2.0

Update

_update :: forall e. Entity e => Query Source #

Produce an UPDATE statement for the given entity by primary key

Examples

>>> _update @Author
"UPDATE \"authors\" SET (\"name\", \"created_at\") = ROW(?, ?) WHERE \"author_id\" = ?"
>>> _update @BlogPost
"UPDATE \"blogposts\" SET (\"author_id\", \"uuid_list\", \"title\", \"content\", \"created_at\") = ROW(?, ?, ?, ?, ?) WHERE \"blogpost_id\" = ?"

Since: 0.0.1.0

_updateBy :: forall e. Entity e => Field -> Query Source #

Produce an UPDATE statement for the given entity by the given field.

Examples

>>> _updateBy @Author [field| name |]
"UPDATE \"authors\" SET (\"name\", \"created_at\") = ROW(?, ?) WHERE \"name\" = ?"

Since: 0.0.1.0

_updateFields :: forall e. Entity e => Vector Field -> Query Source #

Produce an UPDATE statement for the given entity and fields, by primary key.

>>> _updateFields @Author [ [field| name |] ]
"UPDATE \"authors\" SET (\"name\") = ROW(?) WHERE \"author_id\" = ?"

Since: 0.0.1.0

_updateFieldsBy Source #

Arguments

:: forall e. Entity e 
=> Vector Field

Field names to update

-> Field

Field on which to match

-> Query 

Produce an UPDATE statement for the given entity and fields, by the specified field.

>>> _updateFieldsBy @Author [ [field| name |] ] [field| name |]
"UPDATE \"authors\" SET (\"name\") = ROW(?) WHERE \"name\" = ?"
>>> _updateFieldsBy @BlogPost [[field| author_id |], [field| title |]] [field| title |]
"UPDATE \"blogposts\" SET (\"author_id\", \"title\") = ROW(?, ?) WHERE \"title\" = ?"

Since: 0.0.1.0

Deletion

_delete :: forall e. Entity e => Query Source #

Produce a DELETE statement for the given entity, with a match on the Primary Key

Examples

>>> _delete @BlogPost
"DELETE FROM \"blogposts\" WHERE \"blogpost_id\" = ?"

Since: 0.0.1.0

_deleteWhere :: forall e. Entity e => Vector Field -> Query Source #

Produce a DELETE statement for the given entity and fields

Examples

>>> _deleteWhere @BlogPost [[field| title |], [field| created_at |]]
"DELETE FROM \"blogposts\" WHERE \"title\" = ? AND \"created_at\" = ?"

Since: 0.0.1.0

_orderBy :: (Field, SortKeyword) -> Query Source #

Produce an ORDER BY clause with one field and a sorting keyword

Examples

>>> _orderBy ([field| title |], ASC)
" ORDER BY \"title\" ASC"

Since: 0.0.2.0

_orderByMany :: Vector (Field, SortKeyword) -> Query Source #

Produce an ORDER BY clause with many fields and sorting keywords

Examples

>>> _orderByMany (V.fromList [([field| title |], ASC), ([field| created_at |], DESC)])
" ORDER BY \"title\" ASC, \"created_at\" DESC"

Since: 0.0.2.0