generic-persistence: Database persistence using generics

This is a package candidate release! Here you can preview how this package release will appear once published to the main package index (which can be accomplished via the 'maintain' link below). Please note that once a package has been published to the main package index it cannot be undone! Please consult the package uploading documentation for more information.

[maintain] [Publish]

Please see the README on GitHub at https://github.com/thma/generic-persistence#readme


[Skip to Readme]

Properties

Versions 0.2.0.0, 0.2.0.1, 0.3.0.0, 0.3.0.0, 0.3.0.1, 0.4.0.0, 0.5.0, 0.6.0
Change log None available
Dependencies base (>=4.7 && <5), convertible (<1.2), generic-deriving (<1.15), generic-persistence, HDBC (<2.5), HDBC-sqlite3 (<2.4) [details]
License BSD-3-Clause
Copyright 2023 Thomas Mahler
Author Thomas Mahler
Maintainer thma@apache.org
Category Database
Home page https://github.com/thma/generic-persistence#readme
Bug tracker https://github.com/thma/generic-persistence/issues
Source repo head: git clone https://github.com/thma/generic-persistence
Uploaded by thma at 2023-02-25T09:59:28Z

Modules

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees


Readme for generic-persistence-0.3.0.0

[back to package description]

GenericPersistence - A Haskell Persistence Layer using Generics

Actions Status

GP Logo

Introduction

GenericPersistence is a minimalistic Haskell persistence layer for relational databases. The approach relies on GHC.Generics. The actual database access is provided by the HDBC library.

The functional goal of the persistence layer is to provide hassle-free RDBMS persistence for Haskell data types in Record notation (for brevity I call them Entities).

That is, it provides means for inserting, updating, deleting and quering such enties to/from relational databases.

The main design goal is to minimize the boilerplate code required:

In an ideal world we would be able to take any POHO (Plain old Haskell Object) and persist it to any RDBMS without any additional effort.

Status

The library is in an early stage of development. All test cases are green and it should be ready for early adopters. Several things are still missing:

Feature requests, feedback and pull requests are welcome!

Available on Hackage

https://hackage.haskell.org/package/generic-persistence

Add the following to your package.yaml file:

dependencies:
- generic-persistence

I would also recommend to add the setting language: GHC2021 to your package.yaml file:

language: GHC2021

This drastically reduces the amount of LANGUAGE extensions that need to be added to your source files.

Short demo

Here now follows a short demo that shows how the library looks and feels from the user's point of view.

{-# LANGUAGE DeriveAnyClass #-} -- allows automatic derivation from Entity type class

module Main (main) where

import           Database.GP         
import           Database.HDBC
import           Database.HDBC.Sqlite3
import           GHC.Generics

-- | An Entity data type with several fields, using record syntax.
data Person = Person
  { personID :: Int,
    name     :: String,
    age      :: Int,
    address  :: String
  }
  deriving (Generic, Entity, Show) -- deriving Entity allows us to use the GenericPersistence API


main :: IO ()
main = do
  -- connect to a database
  conn <- connect SQLite <$> connectSqlite3 "sqlite.db"

  -- initialize Person table
  setupTableFor @Person conn

  -- create a Person entity
  let alice = Person {personID = 123456, name = "Alice", age = 25, address = "Elmstreet 1"}

  -- insert a Person into a database
  insert conn alice

  -- update a Person
  update conn alice {address = "Main Street 200"}

  -- select a Person from a database
  -- The result type must be provided by the call site, 
  -- as `retrieveEntityById` has a polymorphic return type `IO (Maybe a)`.
  alice' <- retrieveById @Person conn "123456" 
  print alice'

  -- select all Persons from a database
  allPersons <- retrieveAll @Person conn
  print allPersons

  -- delete a Person from a database
  delete conn alice

  -- select all Persons from a database. Now it should be empty.
  allPersons' <- retrieveAll conn :: IO [Person]
  print allPersons'

  -- close connection
  disconnect conn

How it works

In order to store Haskell data types in a relational database, we need to define a mapping between Haskell types and database tables. This mapping is defined by the Entity type class. This type class comes with default implementations for all methods which define the standard behaviour. (The default implementations internally use GHC.Generics.)

This default mapping will work for many cases, but it can be customized by overriding the default implementations.

The Entity type class

The Entity type class specifies the following methods:

class (Generic a, HasConstructor (Rep a), HasSelectors (Rep a)) => Entity a where
  -- | Converts a database row to a value of type 'a'.
  fromRow :: Conn -> [SqlValue] -> IO a

  -- | Converts a value of type 'a' to a database row.
  toRow :: Conn -> a -> IO [SqlValue]

  -- | Returns the name of the primary key field for a type 'a'.
  idField :: String

  -- | Returns a list of tuples that map field names to column names for a type 'a'.
  fieldsToColumns :: [(String, String)]

  -- | Returns the name of the table for a type 'a'.
  tableName :: String

Default Behaviour

idField, fieldsToColumns and tableName are used to define the mapping between Haskell types and database tables.

fromRow and toRow are used to convert between Haskell types and database rows.

The default implementations of fromRow and toRow expects that type a has a single constructor and a selector for each field. All fields are expected to have a 1:1 mapping to a column in the database table. Thus each field must have a type that can be converted to and from a SqlValue.

For example

toRow conn (Person {personID = 1234, name = "Alice", age = 27, address = "Elmstreet 1"}) 

will return

[SqlInt64 1234,SqlString "Alice",SqlInt64 27,SqlString "Elmstreet 1"]

And fromRow does the inverse:

fromRow conn [SqlInt64 1234,SqlString "Alice",SqlInt64 27,SqlString "Elmstreet 1"] :: IO Person

returns

Person {personID = 1234, name = "Alice", age = 27, address = "Elmstreet 1"}

The conversion functions toRow and fromRow both carry an additional Conn argument. This argument is not used by the default implementations, but it can be used to provide database access during the conversion process. We will cover this later.

Customizing the default behaviour

The default implementations of idField, fieldsToColumns, tableName, fromRow and toRow can be customized by overriding the default implementations. Overiding idField, fieldsToColumns and tableName will be required when your database tables do not follow the default naming conventions.

For example, if we have a database table BOOK_TBL with the following columns:

CREATE TABLE BOOK_TBL 
  ( bookId INTEGER PRIMARY KEY, 
    bookTitle TEXT, 
    bookAuthor TEXT, 
    bookYear INTEGER
  );

and we want to map this table to a Haskell data type Book:

data Book = Book
  { book_id :: Int,
    title   :: String,
    author  :: String,
    year    :: Int
  }
  deriving (Generic, Show)

Then we can customize the default implementations of idField, fieldsToColumns and tableName to achieve the desired mapping:

instance Entity Book where
  -- this is the primary key field of the Book data type (not following the default naming convention)
  idField = "book_id"

  -- this defines the mapping between the field names of the Book data type and the column names of the database table
  fieldsToColumns = [("book_id", "bookId"), ("title", "bookTitle"), ("author", "bookAuthor"), ("year", "bookYear")]

  -- this is the name of the database table
  tableName = "BOOK_TBL"

Overriding fromRow and toRow will be required when your database tables do not follow the default mapping conventions. We will see some examples in later sections.

Handling enumeration fields

Say we have a data type Book with an enumeration field of type BookCategory:

data Book = Book
  { bookID :: Int,
    title   :: String,
    author  :: String,
    year    :: Int,
    category :: BookCategory
  }
  deriving (Generic, Entity, Show)

data BookCategory = Fiction | Travel | Arts | Science | History | Biography | Other
  deriving (Generic, Show, Enum)

In this case everything works out of the box, because GenericPersistence provides Convertible instances for all Enum types. Convertible instances are used to convert between Haskell types and database types.

If you do not want to use Enum types for your enumeration fields, you have to implement Convertible instances manually:

data BookCategory = Fiction | Travel | Arts | Science | History | Biography | Other
  deriving (Generic, Show, Read)

instance Convertible BookCategory SqlValue where
  safeConvert = Right . toSql . show
  
instance Convertible SqlValue BookCategory where
  safeConvert = Right . read . fromSql  

Handling embedded Objects

Say we have a data type Article with a field of type Author:

data Article = Article
  { articleID :: Int,
    title     :: String,
    author    :: Author,
    year      :: Int
  }
  deriving (Generic, Show, Eq)

data Author = Author
  { authorID :: Int,
    name     :: String,
    address  :: String
  }
  deriving (Generic, Show, Eq)  

If we don't want to store the Author as a separate table, we can use the following approach to embed the Author into the Article table:

instance Entity Article where
  -- in the fields to column mapping we specify that all fields of the 
  -- Author type are also mapped to columns of the Article table:
  fieldsToColumns :: [(String, String)]
  fieldsToColumns = [("articleID", "articleID"),
                       ("title", "title"), 
                       ("authorID", "authorID"), 
                       ("authorName", "authorName"), 
                       ("authorAddress", "authorAddress"),
                       ("year", "year")
                    ]

  -- in fromRow we have to manually construct the Author object from the 
  -- respective columns of the Article table and insert it 
  -- into the Article object:
  fromRow _conn row = return $ Article (col 0) (col 1) author (col 5)
    where
      col i = fromSql (row !! i)
      author = Author (col 2) (col 3) (col 4)

  -- in toRow we have to manually extract the fields of the Author object
  -- and insert them into the respective columns of the Article table:
  toRow _conn a = return [toSql (articleID a), toSql (title a), toSql authID, toSql authorName, toSql authorAddress, toSql (year a)]
    where 
      authID = authorID (author a)
      authorName = name (author a)
      authorAddress = address (author a)

Handling 1:1 references

If we have the same data types as in the previous example, but we want to store the Author in a separate table, we can use the following approach:

data Article = Article
  { articleID :: Int,
    title     :: String,
    author    :: Author,
    year      :: Int
  }
  deriving (Generic, Show, Eq)

data Author = Author
  { authorID :: Int,
    name     :: String,
    address  :: String
  }
  deriving (Generic, Entity, Show, Eq)


instance Entity Article where
  fieldsToColumns :: [(String, String)]                      -- ommitting the author field,
  fieldsToColumns =                                          -- as this can not be mapped to a single column
    [ ("articleID", "articleID"),                            -- instead we invent a new column authorID         
      ("title", "title"),
      ("authorID", "authorID"),
      ("year", "year")
    ]

  fromRow :: Conn -> [SqlValue] -> IO Article
  fromRow conn row = do    
    authorById <- fromJust <$> retrieveById conn (row !! 2)  -- load author by foreign key
    return $ rawArticle {author = authorById}                -- add author to article
    where
      rawArticle = Article (col 0) (col 1)                   -- create article from row, 
                           (Author (col 2) "" "") (col 3)    -- using a dummy author
        where
          col i = fromSql (row !! i)

  toRow :: Conn -> Article -> IO [SqlValue]
  toRow conn a = do
    persist conn (author a)                                  -- persist author first
    return [toSql (articleID a), toSql (title a),            -- return row for article table where 
            toSql $ authorID (author a), toSql (year a)]     -- authorID is foreign key to author table 

Persisting the Authoras a side effect in toRow may sound like an interesting idea... This step is optional. But then the user has to make sure that the Author is persisted before the Article is persisted.

Handling 1:n references

Now let's change the previous example by having a list of Articles in the Author type:

data Author = Author
  { authorID :: Int,
    name     :: String,
    address  :: String,
    articles :: [Article]
  }
  deriving (Generic, Show, Eq)

data Article = Article
  { articleID :: Int,
    title     :: String,
    authorId  :: Int,
    year      :: Int
  }
  deriving (Generic, Entity, Show, Eq)

So now we have a 1:n relationship between Author and Article.

We can handle this situation by using the following instance declaration for Author:

instance Entity Author where
  fieldsToColumns :: [(String, String)]                   -- ommitting the articles field, 
  fieldsToColumns =                                       -- as this can not be mapped to a single column
    [ ("authorID", "authorID"),
      ("name", "name"),
      ("address", "address")
    ]

  fromRow :: Conn -> [SqlValue] -> IO Author
  fromRow conn row = do
    let authID = head row                                 -- authorID is the first column
    articlesBy <- retrieveAllWhere conn "authorId" authID -- retrieve all articles by this author
    return rawAuthor {articles = articlesBy}              -- add the articles to the author
    where
      rawAuthor = Author (col 0) (col 1) (col 2) []       -- create the author from row (w/o articles)
      col i = fromSql (row !! i)                          -- helper function to convert SqlValue to Haskell type

  toRow :: Conn -> Author -> IO [SqlValue]
  toRow conn a = do
    mapM_ (persist conn) (articles a)                     -- persist all articles of this author (update or insert)
    return [toSql (authorID a),                           -- return the author as a list of SqlValues
            toSql (name a), toSql (address a)]

Persisting all articles of an author as a side effect during the conversion of the author to a row may seem special... You can ommit this step. But then you have to persist the articles manually before persisting the author.

Integrating user defined queries

As of now, the library only supports very basic support for queries:

If you want to use more complex queries, you can integrate HDBC SQL queries by using the entitiesFromRows function as in the following example:

main :: IO ()
main = do
  -- connect to a database
  conn <- connect SQLite <$> connectSqlite3 ":memory:" 

  -- initialize Person table
  setupTableFor @Person conn

  let alice = Person 1 "Alice" 25 "123 Main St"
      bob = Person 2 "Bob" 30 "456 Elm St"
      charlie = Person 3 "Charlie" 35 "789 Pine St"
      dave = Person 4 "Dave" 40 "1011 Oak St"
      eve = Person 5 "Eve" 45 "1213 Maple St"
      frank = Person 6 "Frank" 50 "1415 Walnut St"
      people = [alice, bob, charlie, dave, eve, frank]
      
  -- insert all persons into the database
  insertMany conn people

  -- perform a custom query with HDBC
  stmt = "SELECT * FROM Person WHERE age >= ?"
  resultRows <- quickQuery conn stmt [toSql (40 :: Int)]

  -- convert the resulting rows into a list of Person objects
  fourtplussers <- entitiesFromRows @Person conn resultRows
  print fourtplussers

Of course this approach is not type safe. It is up to the user to make sure that the query returns the correct columns.

The Conn Connection Type

The Conn type is a wrapper around an IConnection obtained from an HDBC backend driver like HDBC-sqlite3 or hdbc-postgresql. It is used to pass the connection to the database to Generic-Persistence. All functions of the library that require a database connection take a Conn as an argument.

HDBC provides a very similar type called ConnectionWrapper. The main reason for such a wrapper type is to simplify the type signatures of the library functions.

In addition, the Conn type provides additional database related information that is not available in the ConnectionWrapper type. For example, the Conn type contains the name of the database driver that is used. This information can be used to generate the correct SQL statements for different database backends. Conn also carries a flag that indicates whether implicit commits should be used by the library. This flag is set to True by default. If you want to use explicit commits, you can set the flag to False by modifying the Conn value:

c <- connect SQLite <$> connectSqlite3 ":memory:"
let conn = c {implicitCommit = False}