squeal-postgresql-0.8.0.0: Squeal PostgreSQL Library
Copyright(c) Eitan Chatav 2019
Maintainereitan@morphism.tech
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Squeal.PostgreSQL

Description

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 Definitions 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 TableConstraints 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 Users. We give the type Generic and HasDatatypeInfo instances so that we can encode and decode Users.

>>> :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 Statements to insert Users 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

Documentation

class RenderSQL sql where Source #

A class for rendering SQL

Methods

renderSQL :: sql -> ByteString Source #

Instances

Instances details
RenderSQL Materialization Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.With

RenderSQL TimeUnit Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Time

RenderSQL Waiting Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

RenderSQL LockStrength Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

RenderSQL DeferrableMode Source #

Render a DeferrableMode.

Instance details

Defined in Squeal.PostgreSQL.Session.Transaction.Unsafe

RenderSQL AccessMode Source #

Render an AccessMode.

Instance details

Defined in Squeal.PostgreSQL.Session.Transaction.Unsafe

RenderSQL IsolationLevel Source #

Render an IsolationLevel.

Instance details

Defined in Squeal.PostgreSQL.Session.Transaction.Unsafe

RenderSQL TransactionMode Source #

Render a TransactionMode.

Instance details

Defined in Squeal.PostgreSQL.Session.Transaction.Unsafe

RenderSQL ReferentialAction Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Constraint

RenderSQL OnUpdateClause Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Constraint

RenderSQL OnDeleteClause Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Constraint

RenderSQL [SortExpression grp lat with db params from] Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Sort

Methods

renderSQL :: [SortExpression grp lat with db params from] -> ByteString Source #

KnownSymbol alias => RenderSQL (Alias alias) Source #
>>> printSQL (#jimbob :: Alias "jimbob")
"jimbob"
Instance details

Defined in Squeal.PostgreSQL.Type.Alias

Methods

renderSQL :: Alias alias -> ByteString Source #

KnownSymbol label => RenderSQL (PGlabel label) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type.Schema

Methods

renderSQL :: PGlabel label -> ByteString Source #

(KnownSymbol q, KnownSymbol a) => RenderSQL (QualifiedAlias q a) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type.Alias

RenderSQL (ColumnTypeExpression db ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

RenderSQL (TypeExpression db ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Type

RenderSQL (LockingClause from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

RenderSQL (By from by) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

Methods

renderSQL :: By from by -> ByteString Source #

RenderSQL (Definition db0 db1) Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition

Methods

renderSQL :: Definition db0 db1 -> ByteString Source #

RenderSQL (IndexMethod ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Index

All KnownSymbol aliases => RenderSQL (NP Alias aliases) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type.Alias

Methods

renderSQL :: NP Alias aliases -> ByteString Source #

All KnownSymbol labels => RenderSQL (NP PGlabel labels) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type.Schema

Methods

renderSQL :: NP PGlabel labels -> ByteString Source #

(forall (x :: k). RenderSQL (expr x)) => RenderSQL (Optional expr ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Default

Methods

renderSQL :: Optional expr ty -> ByteString Source #

RenderSQL (Statement db x y) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Statement

Methods

renderSQL :: Statement db x y -> ByteString Source #

RenderSQL (ConflictTarget constraints) Source #

Render a ConflictTarget

Instance details

Defined in Squeal.PostgreSQL.Manipulation.Insert

Methods

renderSQL :: ConflictTarget constraints -> ByteString Source #

RenderSQL (GroupByClause grp from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Table

Methods

renderSQL :: GroupByClause grp from -> ByteString Source #

RenderSQL (Manipulation with db params columns) Source # 
Instance details

Defined in Squeal.PostgreSQL.Manipulation

Methods

renderSQL :: Manipulation with db params columns -> ByteString Source #

RenderSQL (QueryClause with db params columns) Source # 
Instance details

Defined in Squeal.PostgreSQL.Manipulation.Insert

Methods

renderSQL :: QueryClause with db params columns -> ByteString Source #

RenderSQL (TableConstraintExpression sch tab db constraint) Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Constraint

Methods

renderSQL :: TableConstraintExpression sch tab db constraint -> ByteString Source #

RenderSQL (ProcedureDefinition db args) Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Procedure

RenderSQL (Query lat with db params row) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query

Methods

renderSQL :: Query lat with db params row -> ByteString Source #

(forall (c :: FromType) (s :: SchemasType) (p :: [NullType]) (r :: RowType). RenderSQL (statement c s p r)) => RenderSQL (CommonTableExpression statement db params with0 with1) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.With

Methods

renderSQL :: CommonTableExpression statement db params with0 with1 -> ByteString Source #

RenderSQL (FromClause lat with db params from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.From

Methods

renderSQL :: FromClause lat with db params from -> ByteString Source #

RenderSQL (ReturningClause with db params from row) Source # 
Instance details

Defined in Squeal.PostgreSQL.Manipulation

Methods

renderSQL :: ReturningClause with db params from row -> ByteString Source #

RenderSQL (ConflictAction tab with db params table) Source # 
Instance details

Defined in Squeal.PostgreSQL.Manipulation.Insert

Methods

renderSQL :: ConflictAction tab with db params table -> ByteString Source #

SListI (TableToColumns table) => RenderSQL (ConflictClause tab with db params table) Source #

Render a ConflictClause.

Instance details

Defined in Squeal.PostgreSQL.Manipulation.Insert

Methods

renderSQL :: ConflictClause tab with db params table -> ByteString Source #

RenderSQL (SortExpression grp lat with db params from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Sort

Methods

renderSQL :: SortExpression grp lat with db params from -> ByteString Source #

RenderSQL (HavingClause grp lat with db params from) Source #

Render a HavingClause.

Instance details

Defined in Squeal.PostgreSQL.Query.Table

Methods

renderSQL :: HavingClause grp lat with db params from -> ByteString Source #

RenderSQL (TableExpression grp lat with db params from) Source #

Render a TableExpression

Instance details

Defined in Squeal.PostgreSQL.Query.Table

Methods

renderSQL :: TableExpression grp lat with db params from -> ByteString Source #

RenderSQL (JoinItem lat with db params left right) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.From.Join

Methods

renderSQL :: JoinItem lat with db params left right -> ByteString Source #

SListI xs => RenderSQL (AggregateArg xs lat with db params from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Aggregate

Methods

renderSQL :: AggregateArg xs lat with db params from -> ByteString Source #

RenderSQL (WindowDefinition grp lat with db params from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Window

Methods

renderSQL :: WindowDefinition grp lat with db params from -> ByteString Source #

RenderSQL (FunctionDefinition db args ret) Source # 
Instance details

Defined in Squeal.PostgreSQL.Definition.Function

RenderSQL (Expression grp lat with db params from ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

renderSQL :: Expression grp lat with db params from ty -> ByteString Source #

SListI args => RenderSQL (WindowArg grp args lat with db params from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Window

Methods

renderSQL :: WindowArg grp args lat with db params from -> ByteString Source #

RenderSQL (WindowFunction grp lat with db params from ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Window

Methods

renderSQL :: WindowFunction grp lat with db params from ty -> ByteString Source #

RenderSQL (Selection grp lat with db params from row) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query.Select

Methods

renderSQL :: Selection grp lat with db params from row -> ByteString Source #

printSQL :: (RenderSQL sql, MonadIO io) => sql -> io () Source #

Print SQL.