Go to file
2024-06-25 15:40:05 -05:00
bun feat: allow instances of serialize + deserialize outside this lib 2024-04-05 20:06:23 -05:00
src fix: parRE is alt 2024-06-25 15:40:05 -05:00
test feat!: rework error handling 2024-06-25 13:54:13 -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
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.9 2024-06-25 15:07:46 -05:00
spago.lock chore: prepare v2.0.8 2024-06-25 15:07:39 -05:00
spago.yaml chore: prepare v2.0.9 2024-06-25 15:07:46 -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

Single SQL values are serialized to and deserialized from JS via pg-types (with some tweaks).

The conversion between Raw JS values and purescript values is done with the Serialize and Deserialize typeclasses.

The Rep class indicates a type is Representable as a SQL value. Rep is automatically implemented for all types that are Serialize and Deserialize.

Implementations are provided for Int, String, DateTime, Buffer, BigInt, Boolean, Number, Array, Ranges, Maybe, Null and Unit.

Data - Rows

A single row (multiple SQL values) are deserialized using FromRow, which is implemented for:

  • n-tuples of Rep types
  • Array a where a is Rep
  • A single Rep type

Examples:

(fromRow []     :: Maybe Int)  == Nothing
(fromRow [1]    :: Maybe Int)  == Just 1
(fromRow [1, 2] :: Maybe Int)  == Just 1
(fromRow []     :: Int /\ Int) == Error
(fromRow [1, 2] :: Int /\ Int) == 1 /\ 2
(fromRow []     :: Array Int)  == []
(fromRow [1, 2] :: Array Int)  == [1, 2]

Multiple rows are deserialized using FromRows, which is implemented for:

  • Array a where a is FromRow
  • Maybe a where a is FromRow (equivalent to Array.head <<< fromRows)
  • a where a is FromRow (throws if 0 rows yielded)
  • RowsAffected
    • Extracts the number of rows processed by the last command in the query (ex. INSERT INTO foo (bar) VALUES ('a'), ('b') -> INSERT 2 -> RowsAffected 2)

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: