Go to file
2024-08-20 21:47:39 -05:00
bun docs: update readme 2024-08-20 21:45:17 -05:00
src docs: update readme 2024-08-20 21:45:17 -05:00
test fix: correct implementations of MonadAff, MonadEffect, Fork, Bracket 2024-06-29 14:42:47 -05:00
.gitignore fix: test client bindings 2024-03-27 15:26:40 -05:00
.prettierrc.cjs Initial commit 2024-03-26 17:08:20 +00:00
.tool-versions fix: JSON support 2024-03-27 12:20:33 -05:00
bun.lockb fix: add interval support 2024-06-14 17:00:22 -05:00
docker-compose.yml fix: test client bindings 2024-03-27 15:26:40 -05:00
jsconfig.json Initial commit 2024-03-26 17:08:20 +00:00
LICENSE docs: add LICENSE 2024-07-10 13:47:30 -05:00
package-lock.json fix: JSON support 2024-03-27 12:20:33 -05:00
package.json fix: add interval support 2024-06-14 17:00:22 -05:00
README.md chore: prepare v2.0.19 2024-08-20 21:47:39 -05:00
spago.lock fix: use package set 2024-08-20 21:47:22 -05:00
spago.yaml chore: prepare v2.0.19 2024-08-20 21:47:39 -05:00

postgresql

Purescript PostgreSQL driver

Table of Contents

Getting Started

Install with:

> spago install postgresql
# (npm | yarn | bun) install pg

Next, create a pool Config object:

-- from a connection string:
pgConfig =
  { connectionString: "postgresql://postgres:password@localhost:5432/postgres"
  }

-- or explicitly:
pgConfig =
  { username: "postgres"
  , password: "password"
  , host: "localhost"
  , port: 5432
  , database: "postgres"
  }

Then in an Aff, use runPostgres to connect to the database and execute queries:

module Main where

import Prelude
import Effect (Effect)
import Effect.Class (liftEffect)
import Effect.Aff (launchAff_)
import Effect.Console (log)
import Control.Monad.Postgres (runPostgres, query)

main :: Effect Unit
main =
  launchAff_ do
    msg <- runPostgres pgConfig $ query "select 'hello, world!'"
    liftEffect $ log msg -- logs 'hello, world!'

runPostgres creates a connection pool, then executes a PostgresT monad, which is an Aff with access to a connection pool.

runPostgres :: forall a. <partial config> -> PostgresT Aff a -> Aff a

query accepts any q that can be turned into a query (here just a String), and unmarshals the result into a destination type r.

query is from MonadSession, which PostgresT implements:

class MonadSession m where
  query :: forall q r. AsQuery q => FromRows r => q -> m r
  -- ...

Data

Scalar values are serialized & deserialized using the Serialize / Deserialize typeclasses. Implemented for Int, String, DateTime, Buffer, BigInt, Boolean, Number, Array, Ranges, Maybe, Null and Unit.

There aren't any typeclass instances for unmarshalling rows by design. The rationale: as apps grow we often need to ask more of a relational database than just CRUD operations. Queries tend to be somewhat living, with joins and columns being added and removed, so it should be easy to modify queries and reflect the change in the purescript type they're unmarshalled into.

The lib does this by transforming the js row array Array<Array<unknown>> with FromRows ("how many rows do you expect?"), then each row with FromRow, then each value with Deserialize.

Starting with querying directly into the loose rows as Array (Array Raw):

a :: Array (Array Raw) <- query "select a, b, c from (values (1, 'foo', true), (4, 'bar', false)) as foo(a, b, c)"
liftEffect $ log $ show a -- [[1, "foo", true], [4, "bar", false]]

We can tell the query to deserialize the rows as Int /\ String /\ Boolean (postgres shape of (int, text, boolean) ):

a :: Array (Int /\ String /\ Boolean) <- query "select a, b, c from (values (1, 'foo', true), (4, 'bar', false)) as foo(a, b, c)"
liftEffect $ log $ show a -- [Tuple 1 (Tuple "foo" true), Tuple 1 (Tuple "foo" true)]

From there we could unmarshal to Maybe to get 0 or 1, or directly into the row type if expect at least 1 row:

a :: Maybe (Int /\ String /\ Boolean) <- query "select a, b, c from (values (1, 'foo', true), (4, 'bar', false)) as foo(a, b, c)"
liftEffect $ log $ show a -- Just (Tuple 1 (Tuple "foo" true))

b :: Int /\ String /\ Boolean <- query "select 1, 'foo', true"
liftEffect $ log $ show b -- Tuple 1 (Tuple "foo" true)

c :: Maybe (Int /\ String /\ Boolean) <- query "select null, null, null limit 0"
liftEffect $ log $ show c -- Nothing

FromRows row supports Array row, Maybe row or just row (failing if 0 returned).

FromRow row supports Array a, Tuple a b, Maybe a, or a (where a / b are Deserialize)

The idea is that you can deserialize query results directly to the purescript type you care about:

  • a :: Int <- query "select 1"
    • because there's no outer Array, we're saying this just returns 1 row. because there's no inner Array, we're saying the row just has 1 value; the int!
  • a :: Array Int <- query "select foo.a from (values (1), (2), (3)) as foo(a)"
    • Now there's an outer Array, so we expect the query to yield multiple rows of shape (int)
  • a :: Array (Maybe Int) <- query "select foo.a from (values (1), (null), (3)) as foo(a)"
    • Some of them are NULL!
  • a :: Int /\ Int <- query "select 1, 2"
    • 1 row of (int, int)
  • a :: Array (Int /\ String) <- query "select id, email from users"
    • Multiple rows of (int, string)
  • a :: Maybe (String /\ String /\ String) <- query $ "select first_name, last_name, email from users where id = $1" /\ userId
    • 0 or 1 rows of (text, text, text)

Data - Ranges

Postgres ranges are represented with Range.

Ranges can be created with:

and combined with append:

mempty <> lt 100 -- (,100)
gte 10 <> lt 100 -- [10,100)

Queries

Queries can be executed with any type that implements AsQuery, which converts it into a Query:

newtype Query = Query { text :: String, values :: Array Raw, name :: Maybe String }

class AsQuery a where
  asQuery :: a -> Effect Query

AsQuery is implemented for:

  • Query
  • String
  • String /\ n where n is:
    • n-tuple of Rep query parameters
    • a single Rep query parameter
    • Array Raw

Queries - Builder

For complex parameterized queries, there is a provided Query.Builder:

runPostgres {} do
  exec_ "create table person (id int, first_name text, last_name text, age int, born timestamptz);"
  exec_
    $ Query.Builder.build
    $ do
        id <- Query.Builder.param 1
        firstName <- Query.Builder.param "Henry"
        lastName <- Query.Builder.param "Cavill"
        age <- Query.Builder.param 38
        born <- Query.Builder.param "1985-05-05"
        pure
          $ intercalate "\n"
            [ "insert into person (id, first_name, last_name, age, born)"
            , "values"
            , "("
            , intercalate ", " [id, firstName, lastName, age, born])
            , ")"
            ]

Query.Builder.param accepts any Rep value and returns a string (ex. "$2") that will reference that value in the query.

Query.Builder.build renders the query to Query

Monads

Monads - PostgresT

PostgresT is the database driver's main entry point, and is just an Aff with access to a Pool.

Run in Aff with runPostgres:

main :: Effect Unit
main =
  launchAff_ do
    hi <- runPostgres {} $ query "select 'hi!'"
    liftEffect $ log hi

Execute SessionT monads with session or transaction:

dbMain :: PostgresT Aff Unit
dbMain = do
  transaction do
    exec_ """
      create table persons
        ( id int primary key generated always as identity
        , name text not null unique
        );
    """
    exec_ $ "insert into persons (name) values ($1);" /\ "Henry"
  pure unit

Implements MonadSession as a shorthand for single-query sessions:

dbMain :: PostgresT Aff Int
dbMain = exec_ $ "insert into persons (name) values ($1);" /\ "Sarah"
-- equivalent to:
-- dbMain = session $ exec_ ...

Execute CursorT monads with cursor:

dbMain :: PostgresT Aff Int
dbMain =
  cursor @(Int /\ String) "people_cursor" "select id, name from persons" do
    a <- fetchOne -- Just (1 /\ "Henry")
    b <- fetchOne -- Just (2 /\ "Sarah")
    void $ move (MoveRelative -2)
    c <- fetchAll -- [1 /\ "Henry", 2 /\ "Sarah"]
    d <- fetchOne -- Nothing

Monads - SessionT

SessionT is an Aff with access to a Client issued by a Pool, connected to the database.

Run in PostgresT with session or transaction

Perform queries with query, exec or exec_

Monads - CursorT

CursorT is a transaction SessionT with access to a named server-side cursor.

Run in PostgresT with cursor

node-postgres style

You may also choose to use the Aff API directly, which closely mirrors the api of node-postgres: