DEV Community

Zelenya
Zelenya

Posted on

How to use PostgreSQL with Haskell: squeal

Okay, what if we did something quite similar but quite different?

Squeal “is a type-safe embedding of PostgreSQL in Haskell”, which means “that Squeal embeds both SQL terms and SQL types into Haskell at the term and type levels respectively. This leads to a very high level of type-safety”.

Install squeal-postgresql (0.9.1.3 released in 2023) and generics-sop, which the library uses for generic encodings of Haskell tuples and records.

Enable: DataKinds, GADTs, and OverloadedLabels

💡 (It’s not very important, but) We assume you’ve seen the part on postgresql-simple, which covers the same topics but at a slower pace.

How to connect to a database

We pass libpq connection string (e.g., "host=localhost port=5432 user=postgres dbname=warehouse password=password") to withConnection:

withConnection Hardcoded.connectionString $ 
  doFoo 
    & pqThen doBar
    & pqThen doBaz
Enter fullscreen mode Exit fullscreen mode

We can also create a connection pool using createConnectionPool and use the pool with usingConnectionPool.

How to define tables

First, we define table columns and constraints:

type ProductColumns =
  '[ "id" ::: 'Def :=> 'NotNull 'PGint4
   , "label" ::: 'NoDef :=> 'NotNull 'PGtext
   , "description" ::: 'NoDef :=> 'Null 'PGtext
   ]

type ProductConstraints = '["pk_product" ::: 'PrimaryKey '["id"]]
Enter fullscreen mode Exit fullscreen mode

'Def means that DEFAULT is available for inserts and updates, 'NoDef — unavailable. We specify nullability with 'NotNull and 'Null and the primary key with 'PrimaryKey.

We use the ::: type operators to pair a Symbol with schema types, constraints, column types, etc. We use :=> to specify constraints as well as optionality.

All the other tables look pretty similar (with additional 'ForeignKey constraints here and there); see the repo for the rest of the boilerplate.

Then, we define a schema:

type Schema =
  '[ "product" ::: 'Table (ProductConstraints :=> ProductColumns)
   , "category" ::: 'Table (CategoryConstraints :=> CategoryColumns)
   , "product_category" ::: 'Table (ProductCategoryConstraints :=> ProductCategoryColumns)
   , "warehouse" ::: 'Table (WarehouseConstraints :=> WarehouseColumns)
   ]

type DB = Public Schema
Enter fullscreen mode Exit fullscreen mode

We use generics to convert between Haskell and PostgreSQL values:

import qualified Generics.SOP as SOP
import qualified GHC.Generics as GHC
Enter fullscreen mode Exit fullscreen mode
data BasicProduct = BasicProduct {label :: Text, description :: Maybe Text}
  deriving stock (Show, GHC.Generic)
  deriving anyclass (SOP.Generic, SOP.HasDatatypeInfo)
Enter fullscreen mode Exit fullscreen mode

The SOP.Generic and SOP.HasDatatypeInfo instances allow us to encode and decode BasicProducts.

How to modify data

We can execute raw statements:

cleanUp :: PQ DB DB IO ()
cleanUp =
  execute_ teardown
 where
  teardown :: Statement db () ()
  teardown = manipulation $ UnsafeManipulation "truncate warehouse, product_category, product, category"
Enter fullscreen mode Exit fullscreen mode

Manipulation represents update, insert, and delete statements.

We can specify the schema changes by using concrete PQ; when the schema doesn't change, we can use MonadPQ constraint (e.g., cleanUp :: (MonadPQ DB m) => m ()). In the end, we’ll turn either into IO:

withConnection Hardcoded.connectionString
  $ cleanUp
Enter fullscreen mode Exit fullscreen mode

Let’s insert a product:

insertProduct :: Statement DB BasicProduct ()
insertProduct =
  manipulation
    $ insertInto_
      #product
      (Values_ (Default `as` #id :* Set (param @1) `as` #label :* Set (param @2) `as` #description))
Enter fullscreen mode Exit fullscreen mode

Statement is either a Manipulation or a Query that can be run in a MonadPQ.

We use manipulation and insertInto_ to construct an insert. We pass a table and what to insert. Values_ describes a single n-ary product, where we must match all the columns. We can use Default value for id and set the rest using relevant parameters.

And then, we use executePrepared_ to run a statement that returns nothing. The function prepares the statement and runs it on each element.

insertStuff :: (MonadPQ DB m) => m ()
insertStuff = do
  executePrepared_
    insertProduct
    [ BasicProduct "Wood Screw Kit 1" (Just "245-pieces")
    , BasicProduct "Wood Screw Kit 2" Nothing
    ]
Enter fullscreen mode Exit fullscreen mode

insertInto_ is a specialized version of insertInto with OnConflictDoRaise (what to do in case of conflict) and no ReturningClause (what to return). ReturningClause returns a value based on each row; for example, we can use it to return the created id:

insertCategory :: Statement DB Category (Only Int32)
insertCategory =
  manipulation
    $ insertInto
      #category
      (Values_ (Default `as` #id :* Set (param @1) `as` #label))
      OnConflictDoRaise
      (Returning_ (#id `as` #fromOnly))
Enter fullscreen mode Exit fullscreen mode

Note that we have to use Only and #fromOnly, because we can’t use primitive types (because they don’t have named labels that the library relies on).

This time we have to use executePrepared, which returns a list of results:

insertStuff :: (MonadPQ DB m, MonadIO m) => m ()
insertStuff = do
  result :: [Result (Only Int32)] <-
    executePrepared insertCategory [Category "Screws", Category "Wood Screws", Category "Concrete Screws"]
  rows <- traverse getRows result
  liftIO $ putStrLn $ "Inserted categories: " <> show rows
Enter fullscreen mode Exit fullscreen mode

We use getRows to get all rows from a Result.

How to query data

To retrieve data, we also write Statements, this time using query and select_:

query1 :: Statement DB () BasicProduct
query1 =
  query
    $ select_
      (#product ! #label :* #product ! #description)
      (from (table #product))
Enter fullscreen mode Exit fullscreen mode

The query returns all the products from the table.

💡 Note that we can use printSQL to print statements and see what sql queries get executed.


💡 We can’t return tuples or primitive types because they don't have named fields. You must define a new datatype and derive Squeal typeclasses to return something new.

If you try using tuples, you get an error:

The type `(Text, Text)' is not a record type.
It has no labelled fields.
Enter fullscreen mode Exit fullscreen mode

And then we execute the query:

insertStuff :: (MonadPQ DB m, MonadIO m) => m ()
insertStuff = do
  result1 <- execute query1
  rows1 <- getRows result1
  liftIO $ putStrLn $ "Query 1: " <> show rows1
Enter fullscreen mode Exit fullscreen mode

We can select specific fields and narrow down the results:

query2 :: Statement DB (Only Text) BasicProduct
query2 =
  query
    $ select_
      (#product ! #label :* #product ! #description)
      (from (table #product) & where_ (#product ! #label .== (param @1)))
Enter fullscreen mode Exit fullscreen mode

We use where_ to filter the rows and .== to compare for equality.

This time, we use executeParams to pass the parameters into the statement:

queryData :: PQ DB DB IO ()
queryData = do
  result2 <- executeParams query2 (Only "Wood Screw Kit 1") >>= getRows
  liftIO $ putStrLn $ "Query 2: " <> show result2
Enter fullscreen mode Exit fullscreen mode

We can also use in_:

query3 tasks =
  query
    $ select_
      (#product ! #label :* #product ! #description)
      (from (table #product) & where_ (#product ! #label `in_` tasks))
Enter fullscreen mode Exit fullscreen mode
do
  (result3 :: [BasicProduct]) <- execute (query3 ["Wood Screw Kit 2", "Wood Screw Kit 3"]) >>= getRows
  liftIO $ putStrLn $ "Query 3: " <> show result3
Enter fullscreen mode Exit fullscreen mode

How to use transactions

We can wrap computation in transactionally_:

insertWithTransaction :: PQ DB DB IO ()
insertWithTransaction =
  transactionally_
    ( do
        result1 <- executePrepared insertProduct [BasicProduct "Drywall Screws Set" (Just "8000pcs")]
        productIds <- join <$> traverse getRows result1

        result2 <- executePrepared insertCategory [Category "Drywall Screws"]
        categoryIds <- join <$> traverse getRows result2

        case (productIds, categoryIds) of
          ([Only productId], [Only categoryId]) -> do
            executePrepared_ insertProductCategory [(productId, categoryId)]
            executePrepared_ insertListing [(productId, 10)]
          _ ->
            throwM $ userError "Failed to insert product/category"
    )
    >> liftIO (putStrLn $ "Insert with transaction")
Enter fullscreen mode Exit fullscreen mode

In case of exception, it rollbacks the transaction and rethrows the exception.

How to query using joins

We use innerJoin and leftOuterJoin to join the tables:

query1 :: Statement DB (Only Int32) Listing
query1 =
  query
    $ select_
      (#w ! #quantity `as` #quantity :* #p ! #label `as` #label :* #p ! #description `as` #description :* #c ! #label `as` #category)
      ( from
          ( table (#warehouse `as` #w)
              & innerJoin
                (table (#product `as` #p))
                (#w ! #product_id .== #p ! #id)
              & leftOuterJoin
                (table (#product_category `as` #pc))
                (#pc ! #product_id .== #p ! #id)
              & leftOuterJoin
                (table (#category `as` #c))
                (#c ! #id .== #pc ! #category_id)
          )
          & where_ (#w ! #quantity .> (param @1))
      )
Enter fullscreen mode Exit fullscreen mode

Which generates:

SELECT "w"."quantity"    AS "quantity",
       "p"."label"       AS "label",
       "p"."description" AS "description",
       "c"."label"       AS "category"
FROM   "warehouse" AS "w"
       inner join "product" AS "p"
               ON ( "w"."product_id" = "p"."id" )
       left outer join "product_category" AS "pc"
                    ON ( "pc"."product_id" = "p"."id" )
       left outer join "category" AS "c"
                    ON ( "c"."id" = "pc"."category_id" )
WHERE  ( "w"."quantity" > ( $1 :: int4 ) )
Enter fullscreen mode Exit fullscreen mode

Errors

If you forget or mistype anything, most of the time, the error messages are rarely simple.

Sometimes, they overwhelm:

_ :: NP
(Aliased
(Optional
(Expression
'Ungrouped
'[]
'[]
'["public"
::: '["product" ::: 'Table (ProductConstraints :=> ProductColumns),
"category" ::: 'Table (CategoryConstraints :=> CategoryColumns),
"product_category"
::: 'Table (ProductCategoryConstraints :=> ProductCategoryColumns),
"warehouse"
::: 'Table (WarehouseConstraints :=> WarehouseColumns)]]
'[ 'NotNull 'PGtext, 'Null 'PGtext]
from0)))
'["description" ::: ('NoDef :=> 'Null 'PGtext)]
Where: from0 is an ambiguous type variable
Enter fullscreen mode Exit fullscreen mode

Sometimes, they leak:

Couldn't match type: TupleOf (TupleCodeOf Text (SOP.Code Text))
               with: null10 'PGtext : xs0
Enter fullscreen mode Exit fullscreen mode
Ambiguous type variable y0 arising from a use of manipulation
prevents the constraint (SOP.Generic y0) from being solved.
Enter fullscreen mode Exit fullscreen mode
Couldn't match type: '["description"
::: ('NoDef :=> 'Null 'PGtext)]
with: '[]
Enter fullscreen mode Exit fullscreen mode

Sometimes, they really leak:

Couldn't match type: records-sop-0.1.1.1:Generics.SOP.Record.ExtractTypesFromRecordCode
                       (records-sop-0.1.1.1:Generics.SOP.Record.ToRecordCode_Datatype
                          y (SOP.DatatypeInfoOf y) (SOP.Code y))
                with: records-sop-0.1.1.1:Generics.SOP.Record.GetSingleton
                       (SOP.Code y)
  arising from a use of manipulation
Enter fullscreen mode Exit fullscreen mode

But when it comes to runtime SQL errors, the library provides a convenient SquealException for exceptions that Squeal can throw and a nice API for working with them built on top of exceptions. For example, we can use catchSqueal:

errors :: PQ DB DB IO ()
errors = do
  insertDuplicateScrew
  insertDuplicateScrew
    `catchSqueal` (\err -> liftIO $ putStrLn $ "Caught Squeal/SQL Error: " <> displayException err)
 where
  insertDuplicateScrew = executePrepared_ insertProduct [BasicProduct "Duplicate screw" Nothing]
  insertProduct =
    manipulation
      $ insertInto_
        #product
        (Values_ (Default `as` #id :* Set (param @1) `as` #label :* Set (param @2) `as` #description))
Enter fullscreen mode Exit fullscreen mode

Resources

The library comes with a quickstart and Core Concepts Handbook.

Migrations

The library has a Migration module to change the database schema over time. They support linear, pure or impure, one-way or rewindable migrations.

In summary

Squeal is another type-safe postgres library not suitable for beginners. You should be comfortable working on the type level, reading generic-related errors, etc. The library uses generic encodings (generics-sop) of records/tuples, which keep getting into the error messages.

Top comments (0)