Copyright | (c) Eitan Chatav 2019 |
---|---|
Maintainer | eitan@morphism.tech |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
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 -XFlexibleContexts
>>>
:set -XOverloadedStrings -XTypeApplications -XTypeOperators -XGADTs
We'll need some imports.
>>>
import Control.Monad.IO.Class (liftIO)
>>>
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
.
>>>
:{
type UsersColumns = '[ "id" ::: 'Def :=> 'NotNull 'PGint4 , "name" ::: 'NoDef :=> 'NotNull 'PGtext ] type UsersConstraints = '[ "pk_users" ::: 'PrimaryKey '["id"] ] type EmailsColumns = '[ "id" ::: 'Def :=> 'NotNull 'PGint4 , "user_id" ::: 'NoDef :=> 'NotNull 'PGint4 , "email" ::: 'NoDef :=> 'Null 'PGtext ] type EmailsConstraints = '[ "pk_emails" ::: 'PrimaryKey '["id"] , "fk_user_id" ::: 'ForeignKey '["user_id"] "public" "users" '["id"] ] type Schema = '[ "users" ::: 'Table (UsersConstraints :=> UsersColumns) , "emails" ::: 'Table (EmailsConstraints :=> EmailsColumns) ] type DB = Public Schema :}
Notice the use of type operators.
:::
is used to pair an alias Symbol
with a SchemasType
, a SchemumType
,
a TableConstraint
or a ColumnType
. It is intended to connote Haskell's ::
operator.
:=>
is used to pair TableConstraints
with a ColumnsType
,
yielding a TableType
, or to pair an Optionality
with a NullType
,
yielding a ColumnType
. It is intended to connote Haskell's =>
operator
Next, we'll write Definition
s to set up and tear down the schema. In
Squeal, a Definition
like createTable
, alterTable
or dropTable
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 (Public '[]) DB setup = createTable #users ( serial `as` #id :* (text & notNullable) `as` #name ) ( primaryKey #id `as` #pk_users ) >>> createTable #emails ( serial `as` #id :* (int & notNullable) `as` #user_id :* (text & nullable) `as` #email ) ( primaryKey #id `as` #pk_emails :* foreignKey #user_id #users #id (OnDelete Cascade) (OnUpdate Cascade) `as` #fk_user_id ) :}
We can easily see the generated SQL is unsurprising looking.
>>>
printSQL 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 NULL, CONSTRAINT "pk_emails" PRIMARY KEY ("id"), CONSTRAINT "fk_user_id" FOREIGN KEY ("user_id") REFERENCES "users" ("id") ON DELETE CASCADE ON UPDATE CASCADE);
Notice that setup
starts with an empty public schema (Public '[])
and produces DB
.
In our createTable
commands we included TableConstraint
s to define
primary and foreign keys, making them somewhat complex. Our teardown
Definition
is simpler.
>>>
:{
let teardown :: Definition DB (Public '[]) teardown = dropTable #emails >>> dropTable #users :}
>>>
printSQL teardown
DROP TABLE "emails"; DROP TABLE "users";
We'll need a Haskell type for User
s. We give the type Generic
and
HasDatatypeInfo
instances so that we can encode and decode User
s.
>>>
:set -XDerivingStrategies -XDeriveAnyClass
>>>
:{
data User = User { userName :: Text, userEmail :: Maybe Text } deriving stock (Show, GHC.Generic) deriving anyclass (SOP.Generic, SOP.HasDatatypeInfo) :}
Next, we'll write Statement
s to insert User
s into our two tables.
A Statement
has three type parameters, the schemas it refers to,
input parameters and an output row. 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 serial, 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. We can do this in a single Statement
by using a
with
manipulation
.
>>>
:{
let insertUser :: Statement DB User () insertUser = manipulation $ with (u `as` #u) e where u = insertInto #users (Values_ (Default `as` #id :* Set (param @1) `as` #name)) OnConflictDoRaise (Returning_ (#id :* param @2 `as` #email)) e = insertInto_ #emails $ Select (Default `as` #id :* Set (#u ! #id) `as` #user_id :* Set (#u ! #email) `as` #email) (from (common #u)) :}
>>>
printSQL insertUser
WITH "u" AS (INSERT INTO "users" AS "users" ("id", "name") VALUES (DEFAULT, ($1 :: text)) RETURNING "id" AS "id", ($2 :: text) AS "email") INSERT INTO "emails" AS "emails" ("user_id", "email") SELECT "u"."id", "u"."email" FROM "u" AS "u"
Next we write a Statement
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 innerJoin
to get the right result.
>>>
:{
let getUsers :: Statement DB () User getUsers = query $ select_ (#u ! #name `as` #userName :* #e ! #email `as` #userEmail) ( from (table (#users `as` #u) & innerJoin (table (#emails `as` #e)) (#u ! #id .== #e ! #user_id)) ) :}
>>>
printSQL getUsers
SELECT "u"."name" AS "userName", "e"."email" AS "userEmail" FROM "users" AS "u" INNER JOIN "emails" AS "e" ON ("u"."id" = "e"."user_id")
Let's 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 DB DB IO () session = do executePrepared_ insertUser users usersResult <- execute getUsers usersRows <- getRows usersResult liftIO $ print usersRows in withConnection "host=localhost port=5432 dbname=exampledb user=postgres password=postgres" $ define setup & pqThen session & pqThen (define teardown) :} [User {userName = "Alice", userEmail = Just "alice@gmail.com"},User {userName = "Bob", userEmail = Nothing},User {userName = "Carole", userEmail = Just "carole@hotmail.com"}]
This should get you up and running with Squeal. Once you're writing more complicated queries and need a deeper understanding of Squeal's types and how everything fits together, check out the Core Concepts Handbook in the toplevel of Squeal's Git repo.
Synopsis
- module Squeal.PostgreSQL.Type.Schema
- module Squeal.PostgreSQL.Type.PG
- module Squeal.PostgreSQL.Type.List
- module Squeal.PostgreSQL.Type.Alias
- module Squeal.PostgreSQL.Type
- module Squeal.PostgreSQL.Session.Transaction
- module Squeal.PostgreSQL.Session.Statement
- module Squeal.PostgreSQL.Session.Result
- module Squeal.PostgreSQL.Session.Pool
- module Squeal.PostgreSQL.Session.Oid
- module Squeal.PostgreSQL.Session.Monad
- module Squeal.PostgreSQL.Session.Migration
- module Squeal.PostgreSQL.Session.Indexed
- module Squeal.PostgreSQL.Session.Exception
- module Squeal.PostgreSQL.Session.Encode
- module Squeal.PostgreSQL.Session.Decode
- module Squeal.PostgreSQL.Session.Connection
- module Squeal.PostgreSQL.Session
- module Squeal.PostgreSQL.Query.With
- module Squeal.PostgreSQL.Query.Values
- module Squeal.PostgreSQL.Query.Table
- module Squeal.PostgreSQL.Query.Select
- module Squeal.PostgreSQL.Query.From.Set
- module Squeal.PostgreSQL.Query.From.Join
- module Squeal.PostgreSQL.Query.From
- module Squeal.PostgreSQL.Query
- module Squeal.PostgreSQL.Manipulation.Update
- module Squeal.PostgreSQL.Manipulation.Insert
- module Squeal.PostgreSQL.Manipulation.Delete
- module Squeal.PostgreSQL.Manipulation.Call
- module Squeal.PostgreSQL.Manipulation
- module Squeal.PostgreSQL.Expression.Window
- module Squeal.PostgreSQL.Expression.Type
- module Squeal.PostgreSQL.Expression.Time
- module Squeal.PostgreSQL.Expression.TextSearch
- module Squeal.PostgreSQL.Expression.Text
- module Squeal.PostgreSQL.Expression.Subquery
- module Squeal.PostgreSQL.Expression.Sort
- module Squeal.PostgreSQL.Expression.Range
- module Squeal.PostgreSQL.Expression.Parameter
- module Squeal.PostgreSQL.Expression.Null
- module Squeal.PostgreSQL.Expression.Math
- module Squeal.PostgreSQL.Expression.Logic
- module Squeal.PostgreSQL.Expression.Inline
- module Squeal.PostgreSQL.Expression.Json
- module Squeal.PostgreSQL.Expression.Default
- module Squeal.PostgreSQL.Expression.Composite
- module Squeal.PostgreSQL.Expression.Comparison
- module Squeal.PostgreSQL.Expression.Array
- module Squeal.PostgreSQL.Expression.Aggregate
- module Squeal.PostgreSQL.Expression
- module Squeal.PostgreSQL.Definition.View
- module Squeal.PostgreSQL.Definition.Type
- module Squeal.PostgreSQL.Definition.Table
- module Squeal.PostgreSQL.Definition.Schema
- module Squeal.PostgreSQL.Definition.Procedure
- module Squeal.PostgreSQL.Definition.Index
- module Squeal.PostgreSQL.Definition.Function
- module Squeal.PostgreSQL.Definition.Constraint
- module Squeal.PostgreSQL.Definition.Comment
- module Squeal.PostgreSQL.Definition
- class RenderSQL sql where
- renderSQL :: sql -> ByteString
- printSQL :: (RenderSQL sql, MonadIO io) => sql -> io ()
Documentation
module Squeal.PostgreSQL.Type.PG
module Squeal.PostgreSQL.Type.List
module Squeal.PostgreSQL.Type.Alias
module Squeal.PostgreSQL.Type
module Squeal.PostgreSQL.Session
module Squeal.PostgreSQL.Query.With
module Squeal.PostgreSQL.Query.From
module Squeal.PostgreSQL.Query
module Squeal.PostgreSQL.Expression
module Squeal.PostgreSQL.Definition
class RenderSQL sql where Source #
A class for rendering SQL
renderSQL :: sql -> ByteString Source #