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

Database.PostgreSQL.Entity.Types

Description

Types and classes

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 #

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 #

Associated Types

data Field Source #

A wrapper for table fields.

Since: 0.0.1.0

Instances

Instances details
Eq Field Source # 
Instance details

Defined in Database.PostgreSQL.Entity.Internal.Unsafe

Methods

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

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

Show Field Source # 
Instance details

Defined in Database.PostgreSQL.Entity.Internal.Unsafe

Methods

showsPrec :: Int -> Field -> ShowS #

show :: Field -> String #

showList :: [Field] -> ShowS #

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 #

field :: QuasiQuoter Source #

A quasi-quoter for safely constructing Fields.

Example:

instance Entity BlogPost where
  tableName  = "blogposts"
  primaryKey = [field| blogpost_id |]
  fields = [ [field| blogpost_id |]
           , [field| author_id |]
           , [field| uuid_list :: uuid[] |] -- ← This is where we specify an optional PostgreSQL type annotation
           , [field| title |]
           , [field| content |]
           , [field| created_at |]
           ]

Since: 0.1.0.0

fieldName :: Field -> Text Source #

Get the name of a field.

Since: 0.1.0.0

fieldType :: Field -> Maybe Text Source #

Get the type of a field, if any.

Since: 0.1.0.0

newtype UpdateRow a Source #

Wrapper used by the update function in order to have the primary key as the last parameter passed, since it appears in the WHERE clause.

Since: 0.0.1.0

Constructors

UpdateRow 

Fields

Instances

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

Defined in Database.PostgreSQL.Entity.Types

Methods

(==) :: UpdateRow a -> UpdateRow a -> Bool #

(/=) :: UpdateRow a -> UpdateRow a -> Bool #

Show a => Show (UpdateRow a) Source # 
Instance details

Defined in Database.PostgreSQL.Entity.Types

ToRow a => ToRow (UpdateRow a) Source # 
Instance details

Defined in Database.PostgreSQL.Entity.Types

Methods

toRow :: UpdateRow a -> [Action] #

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

Defined in Database.PostgreSQL.Entity.Types

Generics

data Options Source #

Term-level options

DerivingVia Options

newtype GenericEntity t e Source #

Constructors

GenericEntity 

Fields

Instances

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

Defined in Database.PostgreSQL.Entity.Types

class EntityOptions xs where Source #

Type-level options for Deriving Via

Instances

Instances details
EntityOptions ('[] :: [k]) Source # 
Instance details

Defined in Database.PostgreSQL.Entity.Types

(GetName name, EntityOptions xs) => EntityOptions (PrimaryKey name ': xs :: [Type]) Source # 
Instance details

Defined in Database.PostgreSQL.Entity.Types

(GetName name, EntityOptions xs) => EntityOptions (TableName name ': xs :: [Type]) Source # 
Instance details

Defined in Database.PostgreSQL.Entity.Types

data PrimaryKey t Source #

Instances

Instances details
(GetName name, EntityOptions xs) => EntityOptions (PrimaryKey name ': xs :: [Type]) Source # 
Instance details

Defined in Database.PostgreSQL.Entity.Types

data TableName t Source #

Instances

Instances details
(GetName name, EntityOptions xs) => EntityOptions (TableName name ': xs :: [Type]) Source # 
Instance details

Defined in Database.PostgreSQL.Entity.Types