squeal-postgresql: Squeal PostgreSQL Library

[ bsd3, database, library, program ] [ Propose Tags ]
Versions [RSS] 0.1.0.0, 0.1.1.0, 0.1.1.1, 0.1.1.2, 0.1.1.3, 0.1.1.4, 0.2, 0.2.0.1, 0.2.1.0, 0.3.0.0, 0.3.1.0, 0.3.2.0, 0.4.0.0, 0.5.0.0, 0.5.1.0, 0.5.2.0, 0.6.0.0, 0.6.0.1, 0.6.0.2, 0.7.0.0, 0.7.0.1, 0.8.0.0, 0.8.1.0, 0.8.1.1, 0.9.0.0, 0.9.1.0, 0.9.1.1, 0.9.1.2, 0.9.1.3
Dependencies aeson (>=1.2.4.0), base (>=4.10.1.0 && <5), bytestring (>=0.10.8.2), deepseq (>=1.4.3.0), generics-sop (>=0.3.2.0), lifted-base (>=0.2.3.12), mmorph (>=1.1.1), monad-control (>=1.0.2.3), mtl (>=2.2.2), network-ip (>=0.3.0.2), postgresql-binary (>=0.12.1), postgresql-libpq (>=0.9.4.1), resource-pool (>=0.2.3.2), scientific (>=0.3.5.3), squeal-postgresql, text (>=1.2.3.0), time (>=1.8.0.2), transformers (>=0.5.2.0), transformers-base (>=0.4.4), uuid-types (>=1.0.3), vector (>=0.12.0.1) [details]
License BSD-3-Clause
Copyright Copyright (c) 2017 Morphism, LLC
Author Eitan Chatav
Maintainer eitan.chatav@gmail.com
Category Database
Home page https://github.com/morphismtech/squeal
Bug tracker https://github.com/morphismtech/squeal/issues
Source repo head: git clone https://github.com/morphismtech/squeal.git
Uploaded by echatav at 2018-03-27T01:56:15Z
Distributions LTSHaskell:0.9.1.3
Reverse Dependencies 4 direct, 1 indirect [details]
Executables squeal-postgresql-example
Downloads 10869 total (71 in the last 30 days)
Rating 2.25 (votes: 2) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2018-03-27 [all 1 reports]

Readme for squeal-postgresql-0.2

[back to package description]

squeal

squeal-icon

CircleCI

Github

Hackage

Stackage

installation

stack install squeal-postgresql

usage

Squeal is a deep embedding of PostgreSQL in Haskell. Let's see an example! First, we need some language extensions because Squeal uses modern GHC features.

>>> :set -XDataKinds -XDeriveGeneric -XOverloadedLabels
>>> :set -XOverloadedStrings -XTypeApplications -XTypeOperators

We'll need some imports.

>>> import Control.Monad (void)
>>> import Control.Monad.Base (liftBase)
>>> import Data.Int (Int32)
>>> import Data.Text (Text)
>>> import Squeal.PostgreSQL

We'll use generics to easily convert between Haskell and PostgreSQL values.

>>> import qualified Generics.SOP as SOP
>>> import qualified GHC.Generics as GHC

The first step is to define the schema of our database. This is where we use DataKinds and TypeOperators. The schema consists of a type-level list of tables, a ::: pairing of a type level string or Symbol and a list a columns, itself a ::: pairing of a Symbol and a ColumnType. The ColumnType describes the PostgreSQL type of the column as well as whether or not it may contain NULL and whether or not inserts and updates can use a DEFAULT. For our schema, we'll define two tables, a users table and an emails table.

>>> :{
type Schema =
  '[ "users" :::
       '[ "pk_users" ::: 'PrimaryKey '["id"] ] :=>
       '[ "id" ::: 'Def :=> 'NotNull 'PGint4
        , "name" ::: 'NoDef :=> 'NotNull 'PGtext
        ]
   , "emails" :::
       '[  "pk_emails" ::: 'PrimaryKey '["id"]
        , "fk_user_id" ::: 'ForeignKey '["user_id"] "users" '["id"]
        ] :=>
       '[ "id" ::: 'Def :=> 'NotNull 'PGint4
        , "user_id" ::: 'NoDef :=> 'NotNull 'PGint4
        , "email" ::: 'NoDef :=> 'Null 'PGtext
        ]
   ]
:}

Next, we'll write Definitions to set up and tear down the schema. In Squeal, a Definition is a createTable, alterTable or dropTable command and has two type parameters, corresponding to the schema before being run and the schema after. We can compose definitions using >>>. Here and in the rest of our commands we make use of overloaded labels to refer to named tables and columns in our schema.

>>> :{
let
  setup :: Definition '[] Schema
  setup = 
   createTable #users
     ( serial `As` #id :*
       (text & notNull) `As` #name :* Nil )
     ( primaryKey (Column #id :* Nil) `As` #pk_users :* Nil ) >>>
   createTable #emails
     ( serial `As` #id :*
       (int & notNull) `As` #user_id :*
       text `As` #email :* Nil )
     ( primaryKey (Column #id :* Nil) `As` #pk_emails :*
       foreignKey (Column #user_id :* Nil) #users (Column #id :* Nil)
         OnDeleteCascade OnUpdateCascade `As` #fk_user_id :* Nil )
:}

We can easily see the generated SQL is unsuprising looking.

>>> renderDefinition setup
"CREATE TABLE users (id serial, name text NOT NULL, CONSTRAINT pk_users PRIMARY KEY (id)); CREATE TABLE emails (id serial, user_id int NOT NULL, email text, CONSTRAINT pk_emails PRIMARY KEY (id), CONSTRAINT fk_user_id FOREIGN KEY (user_id) REFERENCES rs (id) ON DELETE CASCADE ON UPDATE CASCADE);"

Notice that setup starts with an empty schema '[] and produces Schema. In our createTable commands we included TableConstraints to define primary and foreign keys, making them somewhat complex. Our tear down Definition is simpler.

>>> :{
let
  teardown :: Definition Schema '[]
  teardown = dropTable #emails >>> dropTable #users
:}
>>> renderDefinition teardown
"DROP TABLE emails; DROP TABLE users;"

Next, we'll write Manipulations to insert data into our two tables. A Manipulation is a insertInto, update or deleteFrom command and has three type parameters, the schema it refers to, a list of parameters it can take as input, and a list of columns it produces as output. When we insert into the users table, we will need a parameter for the name field but not for the id field. Since it's optional, we can use a default value. However, since the emails table refers to the users table, we will need to retrieve the user id that the insert generates and insert it into the emails table. Take a careful look at the type and definition of both of our inserts.

>>> :{
let
  insertUser :: Manipulation Schema '[ 'NotNull 'PGtext ]
    '[ "fromOnly" ::: 'NotNull 'PGint4 ]
  insertUser = insertRow #users
    (Default `As` #id :* Set (param `1) `As` #name :* Nil)
    OnConflictDoNothing (Returning (#id `As` #fromOnly :* Nil))
:}
>>> :{
let
  insertEmail :: Manipulation Schema '[ 'NotNull 'PGint4, 'Null 'PGtext] '[]
  insertEmail = insertRow #emails
    ( Default `As` #id :*
      Set (param `1) `As` #user_id :*
      Set (param `2) `As` #email :* Nil )
    OnConflictDoNothing (Returning Nil)
:}
>>> renderManipulation insertUser
"INSERT INTO users (id, name) VALUES (DEFAULT, ($1 :: text)) ON CONFLICT DO NOTHING URNING id AS fromOnly;"
>>> renderManipulation insertEmail
"INSERT INTO emails (id, user_id, email) VALUES (DEFAULT, ($1 :: int4), ($2 :: text)N CONFLICT DO NOTHING;"

Next we write a Query to retrieve users from the database. We're not interested in the ids here, just the usernames and email addresses. We need to use an inner join to get the right result. A Query is like a Manipulation with the same kind of type parameters.

>>> :{
let
  getUsers :: Query Schema '[]
    '[ "userName" ::: 'NotNull 'PGtext
     , "userEmail" ::: 'Null 'PGtext ]
  getUsers = select
    (#u ! #name `As` #userName :* #e ! #email `As` #userEmail :* Nil)
    ( from (table (#users `As` #u)
      & innerJoin (table (#emails `As` #e))
        (#u ! #id .== #e ! #user_id)) )
:}
>>> renderQuery getUsers
"SELECT u.name AS userName, e.email AS userEmail FROM users AS u INNER JOIN emails e ON (u.id = e.user_id)"

Now that we've defined the SQL side of things, we'll need a Haskell type for users. We give the type Generics.SOP.Generic and Generics.SOP.HasDatatypeInfo instances so that we can decode the rows we receive when we run getUsers. Notice that the record fields of the User type match the column names of getUsers.

>>> data User = User { userName :: Text, userEmail :: Maybe Text } deriving (Show, .Generic)
>>> instance SOP.Generic User
>>> instance SOP.HasDatatypeInfo User

Let's also create some users to add to the database.

>>> :{
let
  users :: [User]
  users = 
    [ User "Alice" (Just "alice`gmail.com")
    , User "Bob" Nothing
    , User "Carole" (Just "carole`hotmail.com")
    ]
:}

Now we can put together all the pieces into a program. The program connects to the database, sets up the schema, inserts the user data (using prepared statements as an optimization), queries the user data and prints it out and finally closes the connection. We can thread the changing schema information through by using the indexed PQ monad transformer and when the schema doesn't change we can use Monad and MonadPQ functionality.

>>> :{
let
  session :: PQ Schema Schema IO ()
  session = do
    idResults <- traversePrepared insertUser (Only . userName <$> users)
    ids <- traverse (fmap fromOnly . getRow (RowNumber 0)) idResults
    traversePrepared_ insertEmail (zip (ids :: [Int32]) (userEmail <$> users))
    usersResult <- runQuery getUsers
    usersRows <- getRows usersResult
    liftBase $ print (usersRows :: [User])
:}
>>> :{
void . withConnection "host=localhost port=5432 dbname=exampledb" $
  define setup
  & pqThen session
  & thenDefine teardown
:}
[User {userName = "Alice", userEmail = Just "alice`gmail.com"},User {userName = "Bob", userEmail = Nothing},User {userName = "Carole", userEmail = Just role`hotmail.com"}]