Make most fields optional in PoolConfiguration

This commit is contained in:
Tomasz Rybarczyk 2018-10-21 03:24:58 +02:00
parent 8683419e85
commit 751ced6d76
2 changed files with 125 additions and 17 deletions

View File

@ -7,6 +7,76 @@ purescript-postgresql-client is a PostgreSQL client library for PureScript.
To use this library, you need to add `pg` and `decimal.js` as an npm dependency. You can also
find first of them on [https://github.com/brianc/node-postgres][pg].
## Usage
This guide is a literate Purescript file which is compiled into testing module (using [`literate-purescript`](https://github.com/Thimoteus/literate-purescript) - check `bin/docs.sh`) so it is a little verbose.
Let's start with imports and some testing boilerplate.
``` purescript
module Test.Example where
import Prelude
import Database.PostgreSQL (defaultPoolConfiguration, execute, newPool, Query(Query), withConnection)
import Database.PostgreSQL.Row (Row0(Row0), Row3(Row3))
import Data.Decimal as Decimal
import Data.Maybe (Maybe(..))
import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff)
-- Our interaction with db is performed asynchronously in `Aff`
run ∷ Aff Unit
run = do
-- Now we are able to setup connection. We are assuming here
-- that postgres is running on a standard local port.
-- We use `ident` authentication so configuration can be nearly empty.
-- It requires only database name which we pass to `newPool` function.
-- We want to close connection after a second (`idleTimeoutMillis` setting) because this code
-- would be run by our test suite ;-)
-- Of course you can provide additional configuration settings if you need to.
pool <- newPool ((defaultPoolConfiguration "purspg") { idleTimeoutMillis = Just 1000 })
withConnection pool \conn -> do
-- We can now create our temporary table which we are going to query in this example.
-- `execute` performs this query. It ignores result value by default.
execute conn (Query """
CREATE TEMPORARY TABLE foods (
name text NOT NULL,
delicious boolean NOT NULL,
price NUMERIC(4,2) NOT NULL,
added TIMESTAMP WITH TIME ZONE NOT NULL DEFAULT CURRENT_TIMESTAMP,
PRIMARY KEY (name)
);
""") Row0
-- We can insert some data calling `execute` function with `INSERT` statement.
-- Please notice that we are passing a tuple of arguments to this query
-- using dedicated constructor (in this case `Row3`).
-- This library provides types from `Row0` to `Row19` and they are wrappers which
-- provides instances for automatic conversions from and to SQL values.
execute conn (Query """
INSERT INTO foods (name, delicious, price)
VALUES ($1, $2, $3)
""") (Row3 "pork" true (Decimal.fromString "8.30"))
-- You can also use nested tuples instead of `Row*` types but this can be a bit more
-- verbose. `/\` is just an alias for `Tuple` constructor.
execute conn (Query """
INSERT INTO foods (name, delicious, price)
VALUES ($1, $2, $3)
""") ("sauerkraut" /\ false /\ Decimal.fromString "3.30")
```
## Generating SQL Queries
The purspgpp preprocessor has been replaced by [sqltopurs], which is a code
@ -14,6 +84,7 @@ generator instead of a preprocessor, and easier to use.
[sqltopurs]: https://github.com/rightfold/sqltopurs
## Testing
To run tests you have to prepare "purspg" database and use standard command: `pulp test`.

View File

@ -1,6 +1,7 @@
module Database.PostgreSQL
( module Row
, module Value
, Database
, PoolConfiguration
, Pool
, Connection
@ -8,6 +9,7 @@ module Database.PostgreSQL
, newPool
, withConnection
, withTransaction
, defaultPoolConfiguration
, command
, execute
, query
@ -17,33 +19,46 @@ module Database.PostgreSQL
import Prelude
import Effect.Aff (Aff, bracket)
import Effect.Aff.Compat (EffectFnAff, fromEffectFnAff)
import Effect (Effect)
import Effect.Class (liftEffect)
import Effect.Exception (error)
import Control.Monad.Error.Class (catchError, throwError)
import Data.Array (head)
import Data.Either (Either(..))
import Foreign (Foreign)
import Data.Maybe (Maybe)
import Data.Maybe (Maybe(..))
import Data.Newtype (class Newtype)
import Data.Nullable (Nullable, toNullable)
import Data.Traversable (traverse)
import Database.PostgreSQL.Row (class FromSQLRow, class ToSQLRow, Row0(..), Row1(..), fromSQLRow, toSQLRow)
import Database.PostgreSQL.Row (class FromSQLRow, class ToSQLRow, Row0(..), Row1(..), Row10(..), Row11(..), Row12(..), Row13(..), Row14(..), Row15(..), Row16(..), Row17(..), Row18(..), Row19(..), Row2(..), Row3(..), Row4(..), Row5(..), Row6(..), Row7(..), Row8(..), Row9(..), fromSQLRow, toSQLRow) as Row
import Database.PostgreSQL.Row (class FromSQLRow, class ToSQLRow, Row0(..), Row1(..), fromSQLRow, toSQLRow)
import Database.PostgreSQL.Value (class FromSQLValue)
import Database.PostgreSQL.Value (class FromSQLValue, class ToSQLValue, fromSQLValue, instantFromString, instantToString, null, toSQLValue, unsafeIsBuffer) as Value
import Effect (Effect)
import Effect.Aff (Aff, bracket)
import Effect.Aff.Compat (EffectFnAff, fromEffectFnAff)
import Effect.Class (liftEffect)
import Effect.Exception (error)
import Foreign (Foreign)
type Database = String
-- | PostgreSQL connection pool configuration.
type PoolConfiguration =
{ user :: String
, password :: String
, host :: String
, port :: Int
, database :: String
, max :: Int
, idleTimeoutMillis :: Int
{ database :: Database
, host :: Maybe String
, idleTimeoutMillis :: Maybe Int
, max :: Maybe Int
, password :: Maybe String
, port :: Maybe Int
, user :: Maybe String
}
defaultPoolConfiguration :: Database -> PoolConfiguration
defaultPoolConfiguration database =
{ database
, host: Nothing
, idleTimeoutMillis: Nothing
, max: Nothing
, password: Nothing
, port: Nothing
, user: Nothing
}
-- | PostgreSQL connection pool.
@ -59,10 +74,32 @@ derive instance newtypeQuery :: Newtype (Query i o) _
-- | Create a new connection pool.
newPool :: PoolConfiguration -> Aff Pool
newPool = liftEffect <<< ffiNewPool
newPool cfg =
liftEffect <<< ffiNewPool $ cfg'
where
cfg' =
{ user: toNullable cfg.user
, password: toNullable cfg.password
, host: toNullable cfg.host
, port: toNullable cfg.port
, database: cfg.database
, max: toNullable cfg.max
, idleTimeoutMillis: toNullable cfg.idleTimeoutMillis
}
-- | Configuration which we actually pass to FFI.
type PoolConfiguration' =
{ user :: Nullable String
, password :: Nullable String
, host :: Nullable String
, port :: Nullable Int
, database :: String
, max :: Nullable Int
, idleTimeoutMillis :: Nullable Int
}
foreign import ffiNewPool
:: PoolConfiguration
:: PoolConfiguration'
-> Effect Pool
-- | Run an action with a connection. The connection is released to the pool