generated from tpl/purs
Make most fields optional in PoolConfiguration
This commit is contained in:
parent
8683419e85
commit
751ced6d76
71
README.md
71
README.md
@ -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
|
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].
|
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
|
## Generating SQL Queries
|
||||||
|
|
||||||
The purspgpp preprocessor has been replaced by [sqltopurs], which is a code
|
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
|
[sqltopurs]: https://github.com/rightfold/sqltopurs
|
||||||
|
|
||||||
|
|
||||||
## Testing
|
## Testing
|
||||||
|
|
||||||
To run tests you have to prepare "purspg" database and use standard command: `pulp test`.
|
To run tests you have to prepare "purspg" database and use standard command: `pulp test`.
|
||||||
|
@ -1,6 +1,7 @@
|
|||||||
module Database.PostgreSQL
|
module Database.PostgreSQL
|
||||||
( module Row
|
( module Row
|
||||||
, module Value
|
, module Value
|
||||||
|
, Database
|
||||||
, PoolConfiguration
|
, PoolConfiguration
|
||||||
, Pool
|
, Pool
|
||||||
, Connection
|
, Connection
|
||||||
@ -8,6 +9,7 @@ module Database.PostgreSQL
|
|||||||
, newPool
|
, newPool
|
||||||
, withConnection
|
, withConnection
|
||||||
, withTransaction
|
, withTransaction
|
||||||
|
, defaultPoolConfiguration
|
||||||
, command
|
, command
|
||||||
, execute
|
, execute
|
||||||
, query
|
, query
|
||||||
@ -17,33 +19,46 @@ module Database.PostgreSQL
|
|||||||
|
|
||||||
import Prelude
|
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 Control.Monad.Error.Class (catchError, throwError)
|
||||||
import Data.Array (head)
|
import Data.Array (head)
|
||||||
import Data.Either (Either(..))
|
import Data.Either (Either(..))
|
||||||
import Foreign (Foreign)
|
import Data.Maybe (Maybe(..))
|
||||||
import Data.Maybe (Maybe)
|
|
||||||
import Data.Newtype (class Newtype)
|
import Data.Newtype (class Newtype)
|
||||||
|
import Data.Nullable (Nullable, toNullable)
|
||||||
import Data.Traversable (traverse)
|
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(..), 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)
|
||||||
import Database.PostgreSQL.Value (class FromSQLValue, class ToSQLValue, fromSQLValue, instantFromString, instantToString, null, toSQLValue, unsafeIsBuffer) as Value
|
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.
|
-- | PostgreSQL connection pool configuration.
|
||||||
type PoolConfiguration =
|
type PoolConfiguration =
|
||||||
{ user :: String
|
{ database :: Database
|
||||||
, password :: String
|
, host :: Maybe String
|
||||||
, host :: String
|
, idleTimeoutMillis :: Maybe Int
|
||||||
, port :: Int
|
, max :: Maybe Int
|
||||||
, database :: String
|
, password :: Maybe String
|
||||||
, max :: Int
|
, port :: Maybe Int
|
||||||
, idleTimeoutMillis :: 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.
|
-- | PostgreSQL connection pool.
|
||||||
@ -59,10 +74,32 @@ derive instance newtypeQuery :: Newtype (Query i o) _
|
|||||||
|
|
||||||
-- | Create a new connection pool.
|
-- | Create a new connection pool.
|
||||||
newPool :: PoolConfiguration -> Aff 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
|
foreign import ffiNewPool
|
||||||
:: PoolConfiguration
|
:: PoolConfiguration'
|
||||||
-> Effect Pool
|
-> Effect Pool
|
||||||
|
|
||||||
-- | Run an action with a connection. The connection is released to the pool
|
-- | Run an action with a connection. The connection is released to the pool
|
||||||
|
Loading…
Reference in New Issue
Block a user