generic-persistence-0.3.0.1: Database persistence using generics
Safe HaskellSafe-Inferred
LanguageGHC2021

Database.GP.GenericPersistence

Synopsis

Documentation

retrieveById :: forall a id. (Entity a, Convertible id SqlValue) => Conn -> id -> IO (Maybe a) Source #

This module defines RDBMS Persistence operations for Record Data Types that are instances of Data. I call instances of such a data type Entities.

The Persistence operations are using Haskell generics to provide compile time reflection capabilities. HDBC is used to access the RDBMS.

A function that retrieves an entity from a database. The function takes entity id as parameter. If an entity with the given id exists in the database, it is returned as a Just value. If no such entity exists, Nothing is returned. An error is thrown if there are more than one entity with the given id.

retrieveAll :: forall a. Entity a => Conn -> IO [a] Source #

This function retrieves all entities of type a from a database. The function takes an HDBC connection as parameter. The type a is determined by the context of the function call.

retrieveAllWhere :: forall a. Entity a => Conn -> String -> SqlValue -> IO [a] Source #

This function retrieves all entities of type a where a given field has a given value. The function takes an HDBC connection, the name of the field and the value as parameters. The type a is determined by the context of the function call. The function returns a (possibly empty) list of all matching entities.

entitiesFromRows :: forall a. Entity a => Conn -> [[SqlValue]] -> IO [a] Source #

This function converts a list of database rows, represented as a `[[SqlValue]]` to a list of entities. The function takes an HDBC connection and a list of database rows as parameters. The type a is determined by the context of the function call. The function returns a (possibly empty) list of all matching entities. The function is used internally by retrieveAll and retrieveAllWhere. But it can also be used to convert the result of a custom SQL query to a list of entities.

persist :: forall a. Entity a => Conn -> a -> IO () Source #

A function that persists an entity to a database. The function takes an HDBC connection and an entity as parameters. The entity is either inserted or updated, depending on whether it already exists in the database. The required SQL statements are generated dynamically using Haskell generics and reflection

insert :: forall a. Entity a => Conn -> a -> IO () Source #

A function that explicitely inserts an entity into a database.

insertMany :: forall a. Entity a => Conn -> [a] -> IO () Source #

A function that inserts a list of entities into a database. The function takes an HDBC connection and a list of entities as parameters. The insert-statement is compiled only once and then executed for each entity.

update :: forall a. Entity a => Conn -> a -> IO () Source #

A function that explicitely updates an entity in a database.

updateMany :: forall a. Entity a => Conn -> [a] -> IO () Source #

A function that updates a list of entities in a database. The function takes an HDBC connection and a list of entities as parameters. The update-statement is compiled only once and then executed for each entity.

delete :: forall a. Entity a => Conn -> a -> IO () Source #

A function that deletes an entity from a database. The function takes an HDBC connection and an entity as parameters.

setupTableFor :: forall a. Entity a => Conn -> IO () Source #

set up a table for a given entity type. The table is dropped (if existing) and recreated. The function takes an HDBC connection as parameter.

idValue :: forall a. Entity a => Conn -> a -> IO SqlValue Source #

A function that returns the primary key value of an entity as a SqlValue. The function takes an HDBC connection and an entity as parameters.

data Conn Source #

This module defines a wrapper around an HDBC IConnection. Using this wrapper Conn simplifies the signature of the functions in the GP module. It allows to use any HDBC connection without having to define a new function for each connection type. It also provides additional attributes to the connection, like the database type and the implicit commit flag. These attributes can be used to implement database specific functionality, modify transaction behaviour, etc.

This code has been inspired by the HDBC ConnectionWrapper and some parts have been copied from the HDBC Database.HDBC.Types module.

A wrapper around an HDBC IConnection.

Constructors

forall conn.IConnection conn => Conn 

Fields

Instances

Instances details
IConnection Conn Source #

manually implement the IConnection type class for the Conn type.

Instance details

Defined in Database.GP.Conn

connect :: forall conn. IConnection conn => Database -> conn -> Conn Source #

a smart constructor for the Conn type.

data Database Source #

An enumeration of the supported database types.

Constructors

Postgres 
MySQL 
SQLite 
Oracle 
MSSQL 

Instances

Instances details
Enum Database Source # 
Instance details

Defined in Database.GP.Conn

Show Database Source # 
Instance details

Defined in Database.GP.Conn

Eq Database Source # 
Instance details

Defined in Database.GP.Conn

class (Generic a, HasConstructor (Rep a), HasSelectors (Rep a)) => Entity a where Source #

This is the Entity class. It is a type class that is used to define the mapping between a Haskell product type in record notation and a database table. The class has a default implementation for all methods. The default implementation uses the type information to determine a simple 1:1 mapping.

That means that - the type name is used as the table name and the - field names are used as the column names. - A field named 'typeNameID' is used as the primary key field.

The default implementation can be overridden by defining a custom instance for a type.

Please note the following constraints, which apply to all valid Entity type, but that are not explicitely encoded in the type class definition:

  • The type must be a product type in record notation.
  • The type must have exactly one constructor.
  • There must be single primary key field, compund primary keys are not supported.

Minimal complete definition

Nothing

Methods

fromRow :: Conn -> [SqlValue] -> IO a Source #

Converts a database row to a value of type a.

default fromRow :: GFromRow (Rep a) => Conn -> [SqlValue] -> IO a Source #

toRow :: Conn -> a -> IO [SqlValue] Source #

Converts a value of type a to a database row.

default toRow :: GToRow (Rep a) => Conn -> a -> IO [SqlValue] Source #

idField :: String Source #

Returns the name of the primary key field for a type a.

default idField :: String Source #

fieldsToColumns :: [(String, String)] Source #

Returns a list of tuples that map field names to column names for a type a.

tableName :: String Source #

Returns the name of the table for a type a.

class GToRow f Source #

Minimal complete definition

gtoRow

Instances

Instances details
GToRow (U1 :: k -> Type) Source # 
Instance details

Defined in Database.GP.Entity

Methods

gtoRow :: forall (a :: k0). U1 a -> [SqlValue] Source #

(GToRow a, GToRow b) => GToRow (a :*: b :: k -> Type) Source # 
Instance details

Defined in Database.GP.Entity

Methods

gtoRow :: forall (a0 :: k0). (a :*: b) a0 -> [SqlValue] Source #

Convertible a SqlValue => GToRow (K1 i a :: k -> Type) Source # 
Instance details

Defined in Database.GP.Entity

Methods

gtoRow :: forall (a0 :: k0). K1 i a a0 -> [SqlValue] Source #

GToRow a => GToRow (M1 i c a :: k -> Type) Source # 
Instance details

Defined in Database.GP.Entity

Methods

gtoRow :: forall (a0 :: k0). M1 i c a a0 -> [SqlValue] Source #

class GFromRow f Source #

Minimal complete definition

gfromRow

Instances

Instances details
GFromRow (U1 :: k -> Type) Source # 
Instance details

Defined in Database.GP.Entity

Methods

gfromRow :: forall (a :: k0). [SqlValue] -> U1 a

(KnownNat (NumFields f), GFromRow f, GFromRow g) => GFromRow (f :*: g :: Type -> Type) Source #

This instance is the most interesting one. It splits the list of SqlValues into two parts, one for the first field and one for the rest. Then it uses the GFromRow instance for the first field to convert the first part of the list and the GFromRow instance for the rest of the fields to convert the second part of the list. Finally, it combines the two results using the :*: constructor. https://stackoverflow.com/questions/75485429/how-to-use-ghc-generics-to-convert-from-product-data-types-to-a-list-of-sqlvalue/75485650#75485650

Instance details

Defined in Database.GP.Entity

Methods

gfromRow :: forall (a :: k). [SqlValue] -> (f :*: g) a

Convertible SqlValue a => GFromRow (K1 i a :: k -> Type) Source # 
Instance details

Defined in Database.GP.Entity

Methods

gfromRow :: forall (a0 :: k0). [SqlValue] -> K1 i a a0

GFromRow a => GFromRow (M1 i c a :: k -> Type) Source # 
Instance details

Defined in Database.GP.Entity

Methods

gfromRow :: forall (a0 :: k0). [SqlValue] -> M1 i c a a0

columnNameFor :: forall a. Entity a => String -> String Source #

A convenience function: returns the name of the column for a field of a type a.

toString :: forall a. (Generic a, GShow' (Rep a)) => a -> String Source #

Returns a string representation of a value of type a.

type EntityId = (String, SqlValue) Source #

The EntityId is a tuple of the constructor name and the primary key value of an Entity.

entityId :: forall a. Entity a => Conn -> a -> IO EntityId Source #

Computes the EntityId of an entity. The EntityId of an entity is a (typeRep, idValue) tuple. The function takes an HDBC connection and an entity as parameters.

data TypeInfo a Source #

A data type holding meta-data about a type. The Phantom type parameter a ensures type safety for reflective functions that use this type to create type instances.

Instances

Instances details
Show (TypeInfo a) Source # 
Instance details

Defined in Database.GP.TypeInfo

Methods

showsPrec :: Int -> TypeInfo a -> ShowS #

show :: TypeInfo a -> String #

showList :: [TypeInfo a] -> ShowS #

typeInfo :: forall a. (HasConstructor (Rep a), HasSelectors (Rep a), Generic a) => TypeInfo a Source #

this function is a smart constructor for TypeInfo objects. It takes a value of type a and returns a `TypeInfo a` object. If the type has no named fields, an error is thrown. If the type has more than one constructor, an error is thrown.

Orphan instances

Enum a => Convertible SqlValue a Source #

These instances are needed to make the Convertible type class work with Enum types out of the box. This is needed because the Convertible type class is used to convert SqlValues to Haskell types.

Instance details

Enum a => Convertible a SqlValue Source # 
Instance details